You are running into a quirk in the type system.  The haskell standard says that sub expressions in where clauses that have type annotations with variables in them (pack'), the variables are not the same as the variables in the toplevel expression (pack).  When you wrote this code, haskell inferred a type of pack :: (Eq a1) => [a1] -> [[a1]], and then pack' is correctly the type pack' :: [a] -> [[a]], but that a1 and that a are different types as far as ghc is concerned.  But based on how they are used, ghc says no, they should be the same type, ERROR FIX IT.  Even if you specify a type for pack that uses "a", the problem still persists because they are still considered different a's.

There are two ways to fix this.  First one is just remove the type info from pack'.  Just remove that line and ghc will infer all the types correctly and you can get on with your day.

The other way is to use the ScopedTypeVariables extension, which everyone generally loves and uses when they need it.  It has a niggle where it requires a forall for each type variable in the overall type, but from that point on it works the way you would expect.

{-# LANGUAGE ScopedTypeVariables #-}
pack :: forall a. (Eq a) => [a] -> [[a]]
pack xs = pack' xs
         where
         pack' :: [a] -> [[a]]
         pack' [] = []
         pack' (x:y) = extra x xs ++ pack' y



On Sun, Apr 20, 2014 at 8:35 AM, raffa f <freitasraffa@gmail.com> wrote:
hi everyone, i'm a complete beginner on programming and i've been solving the 99 haskell problems and i've come into a situation. just like all my problems with haskell, it's about types. i wrote a little thing that takes a list and puts all the equal characters together, like [1,1,3,2,3] will be [  [1,1],  [3,3], [2]  ]. here it is:

pack xs = pack' xs

         where

         pack' :: [a] -> [[a]]

         pack' [] = []

         pack' (x:y) = extra x xs ++ pack' y 



extra x xs = [sum' (map (remover x) (map ((==) x) xs))]



remover :: a -> Bool -> [a]

remover y x = if x then [y] else []



sum' :: [[a]] -> [a]

sum' [] = []

sum' (x:xs) = x ++ sum' xs


i know, i know, this code is probably terrible and i'm sure there are more clever ways to do this...but i wanna understand what's wrong. the "extra" function works perfectly, it takes a variable and then looks at how many times it's presented on a list and outputs a list with a list of that variable the amount of times that it was presented on the original list.

however, pack does not work quite right. first of all, it'll use extra on repeated characters, creating repeated lists, but that doesn't matter because i have a function that fixes that issue and i'll use it after i figure out what's wrong with pack. now, the real problem is with types. here's what haskell says when i try to load it:

noventa.hs:77:32:
    Couldn't match type `a' with `a1'
      `a' is a rigid type variable bound by
          the inferred type of pack :: [a] -> [[a]] at noventa.hs:73:1
      `a1' is a rigid type variable bound by
           the type signature for pack' :: [a1] -> [[a1]] at noventa.hs:75:19
    Expected type: [a1]
      Actual type: [a]
    In the second argument of `extra', namely `xs'
    In the first argument of `(++)', namely `extra x xs'
    In the expression: extra x xs ++ pack' y
Failed, modules loaded: none.


i don't understand this at all! if i replace [a] with String and [[a]] with [String], it works! but i want pack to work for lists of numbers too... types are so confusing. can anyone help me?

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners