
I would like to know why I'm getting a particular compile time error message. In this program, I am specifying a function type on /combs'/ in the where clause: -------- module Main where import List (delete) combs :: Eq a => [a] -> Int -> [[a]] combs l 1 = map (\x -> [x]) l combs l n = foldl combs' [] l where combs' :: Eq a => [[a]] -> a -> [[a]] combs' acc x = let sl = delete x l in (map (\i -> x:i) $ combs sl (n-1)) ++ acc main = do print $ combs ["a","b","c","d"] 3 -------- I get this error message from GHC 6.8.3: cafe1.hs:9:43: Couldn't match expected type `a1' against inferred type `a' `a1' is a rigid type variable bound by the type signature for `combs'' at cafe1.hs:8:23 `a' is a rigid type variable bound by the type signature for `combs' at cafe1.hs:5:12 Expected type: [a1] Inferred type: [a] In the second argument of `delete', namely `l' In the expression: delete x l I don't understand why I'm seeing this. The type /a/ is the same type in /combs/ and /combs'/. I realize I can remove the type specification from /combs'/, and the code will compile. However, I'd like to get a better understanding of why GHC objects to this. Thank you, Rob.