Infinite type ... or 'not enough type arguments'...

Further to my recent attempts to scan a CSV file and build a map, I now have a foldl calling this with an empty map: --forwardRoutes :: M.Map String [String] -> Record -> M.Map forwardRoutes map row = case lookup map (row!!0) of Nothing -> M.insert (row!!0) [(row !! 1)] map Just routes -> M.insert (row!!0) (row!!1):routes map With the type declaration commented out I get this: scread.hs:102:46: Occurs check: cannot construct the infinite type: a = M.Map [(a, b)] [[(a, b)]] Expected type: M.Map [(a, b)] [[(a, b)]] Inferred type: a In the third argument of `M.insert', namely `map' In the expression: M.insert (row !! 0) [(row !! 1)] map and with it 'in#' i get this error instead... scread.hs:99:52: `M.Map' is not applied to enough type arguments Expected kind `?', but `M.Map' has kind `* -> * -> *' In the type signature for `forwardRoutes': forwardRoutes :: M.Map String [String] -> Record -> M.Map Can anybody help me to understand both problems. I thought I had declared the type signature of forwardRoutes correctly but obv. not! LOL I have seen information that says the "infinite error" message can be cured by supplying types so I did...... Thanks again. Sean

On Thursday 09 June 2011, 13:57:47, Sean Charles wrote:
Further to my recent attempts to scan a CSV file and build a map, I now have a foldl calling this with an empty map:
--forwardRoutes :: M.Map String [String] -> Record -> M.Map forwardRoutes map row = case lookup map (row!!0) of Nothing -> M.insert (row!!0) [(row !! 1)] map Just routes -> M.insert (row!!0) (row!!1):routes map
Needs parentheses Just routes -> M.insert (row!!0) ((row!!1):routes) map Without, it's parsed (M.insert (row!!0) (row!!1)) : (routes map) I'm not in the mood to figure out how the type inference reaches its conclusion, I can tell however, that it started inferring the type with the Just-branch.
With the type declaration commented out I get this: scread.hs:102:46: Occurs check: cannot construct the infinite type: a = M.Map [(a, b)] [[(a, b)]] Expected type: M.Map [(a, b)] [[(a, b)]] Inferred type: a In the third argument of `M.insert', namely `map' In the expression: M.insert (row !! 0) [(row !! 1)] map
and with it 'in#' i get this error instead... scread.hs:99:52: `M.Map' is not applied to enough type arguments Expected kind `?', but `M.Map' has kind `* -> * -> *' In the type signature for `forwardRoutes': forwardRoutes :: M.Map String [String] -> Record -> M.Map
You forgot the type arguments of Map in the result type. M.Map is a type constructor taking two arguments, but type arguments of (->) must be fully applied type constructors
Can anybody help me to understand both problems. I thought I had declared the type signature of forwardRoutes correctly but obv. not! LOL
I have seen information that says the "infinite error" message can be cured by supplying types so I did......
Thanks again. Sean

Here are the snippets of my code currently hurting my coding ulcer... routes :: [Record] -> IO () routes legodata = do let all = foldl forwardRoutes M.empty legodata -- [Record] return () forwardRoutes :: M.Map String [String] -> Record -> M.Map String [String] forwardRoutes map row = let key = row !! 0 in let val = row !! 1 in case lookup key map of Nothing -> M.insert key [val] map Just routes -> M.insert key val:routes map -- some 'deductions' by me, probably erroneous, to help me try to figure it out -- --if legodata is [Record] -- then row is Record => [Field] -- -- if map is "String [String]" -- then key is Field because row is [Field] -- then val is Field because row is [Field] -- Field is "String" -- -- lookup key map => lookup String M.Map String [String] -- If I am fold-ing over [Record] then I assume that the data that is passed to the callback function is of the type Record, i.e. a single thing from the list of things. Record is defined as [Field] so presumably I could use [Field] or Record in my function 'forwardRoutes'. When I compile the above I get: scread.hs:92:18: Couldn't match expected type `[(Field, b)]' against inferred type `M.Map String [String]' In the second argument of `lookup', namely `map' In the expression: lookup key map In the expression: case lookup key map of { Nothing -> M.insert key [val] map Just routes -> M.insert key val : routes map } I have spent a long time searching and reading and trying to fathom it out from first principles but I cannot for the life of me figure out where '[(Field, b)]' is coming from! I can smell Field in there because Record is typed as [Field], but a tuple? And what is 'b' ? The 'inferred type' matches what I thought it should be in the error message and I am right (I think) in stating that the 'expected type' is what it actually got from the code at compile time?! Help! :)

It is this line:
Just routes -> M.insert key val:routes map
Function application binds the tightest, so the compiler interprets this as:
Just routes -> (M.insert key val) : (routes map)
Which is presumably not what you meant.
On Thu, Jun 9, 2011 at 11:26 AM, Sean Charles
Here are the snippets of my code currently hurting my coding ulcer...
routes :: [Record] -> IO () routes legodata = do let all = foldl forwardRoutes M.empty legodata -- [Record] return ()
forwardRoutes :: M.Map String [String] -> Record -> M.Map String [String] forwardRoutes map row = let key = row !! 0 in let val = row !! 1 in case lookup key map of Nothing -> M.insert key [val] map Just routes -> M.insert key val:routes map
-- some 'deductions' by me, probably erroneous, to help me try to figure it out -- --if legodata is [Record] -- then row is Record => [Field] -- -- if map is "String [String]" -- then key is Field because row is [Field] -- then val is Field because row is [Field] -- Field is "String" -- -- lookup key map => lookup String M.Map String [String] --
If I am fold-ing over [Record] then I assume that the data that is passed to the callback function is of the type Record, i.e. a single thing from the list of things. Record is defined as [Field] so presumably I could use [Field] or Record in my function 'forwardRoutes'.
When I compile the above I get:
scread.hs:92:18: Couldn't match expected type `[(Field, b)]' against inferred type `M.Map String [String]' In the second argument of `lookup', namely `map' In the expression: lookup key map In the expression: case lookup key map of { Nothing -> M.insert key [val] map Just routes -> M.insert key val : routes map }
I have spent a long time searching and reading and trying to fathom it out from first principles but I cannot for the life of me figure out where '[(Field, b)]' is coming from! I can smell Field in there because Record is typed as [Field], but a tuple? And what is 'b' ?
The 'inferred type' matches what I thought it should be in the error message and I am right (I think) in stating that the 'expected type' is what it actually got from the code at compile time?!
Help! :)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thursday 09 June 2011, 18:26:18, Sean Charles wrote:
Here are the snippets of my code currently hurting my coding ulcer...
routes :: [Record] -> IO () routes legodata = do let all = foldl forwardRoutes M.empty legodata -- [Record] return ()
forwardRoutes :: M.Map String [String] -> Record -> M.Map String [String] forwardRoutes map row = let key = row !! 0 in let val = row !! 1 in case lookup key map of
Ah, that needs to be M.lookup, without qualifying the call, it refers to Prelude.lookup :: Eq a => a -> [(a,b)] -> Maybe b
Nothing -> M.insert key [val] map
Just routes -> M.insert key val:routes map
This needs parentheses, M.insert key (val:routes) map
I have spent a long time searching and reading and trying to fathom it out from first principles but I cannot for the life of me figure out where '[(Field, b)]' is coming from!
Prelude.lookup vs. Data.Map.lookup
I can smell Field in there because Record is typed as [Field], but a tuple? And what is 'b' ?
The 'inferred type' matches what I thought it should be in the error message and I am right (I think) in stating that the 'expected type' is what it actually got from the code at compile time?!
Help!
:)

Thanks every, Daniel, the list at large... I have finally solved my issue and moved on... for the record my function now looks like this: forwardRoutes :: M.Map String [String] -> Record -> M.Map String [String] forwardRoutes map row = let key = row !! 0 in let val = row !! 1 in case M.lookup key map of Nothing -> M.insert key [val] map Just routes -> M.insert key (nub (val:routes)) map and does just what I want! The thing I ha failed to see was using Prelude.lookup instead of M.lookup and some errant (). I know nub is 'potentially inefficient' but the source data set is reasonably small and the script only has to run three to four times a year so "So what!" Just one thing: IF the error message had printed out the Prelude.lookup in the error message, that would have been incredibly useful! Is that a command line switch I haven't come across perhaps ? Thanks again. Sean.
participants (3)
-
Antoine Latter
-
Daniel Fischer
-
Sean Charles