Bind parser returning wrong return type

Hi All, Sorry if this is a very lame question but i am a beginner and much appreciate if some one could correct me? I am reading haskell book and curious why the return type of the bind operator look odd to me For the given definitions * type Parser a = String -> [(a, String)]* * item :: Parser Char* * item = \inp -> case inp of * * [] -> []* * (x:xs) -> [(x,xs)]* * bind :: Parser a -> (a -> Parser b) -> Parser b* * p `bind` f = \inp -> concat [ f x inp' | (x, inp') <- p inp]* when I define z in GHCI as * let z = item `bind` (\x -> (\y -> result (x,y))) "Rohit"* the return type is * >> :t z* * z :: Parser ([Char], Char)* Question: (1) Shouldn't the return type of (Char, [Char])? looking at the list comprehension, "(x, inp') <- p inp" should yield -> "('r', "ohit")". Next f x inp' is left associative, so f x should yield character 'r' and pass to the lambda that should return result tuple ('r', "ohit"), but why is it that z type is ([Char], char) :: (x,y) (2) How can i print the value of z in the above case on the ghci Many thanks, Rohit

Your questions aren't lame. They are common confusions from those who come from a not-so-mathy background. Your first question: Shouldn't the return type be of (Char, [Char])? suggests that you're confusing the type synonym of (Parser a), which is String -> (a, String), with just the right-hand-side, (a, String). Your "z" expression has type Parser ([Char], Char), which means the same thing as String -> ((String, Char), String). How did that happen? Because item `bind` (\x -> (\y -> result (x,y))) "Rohit" is equivalent to item `bind` ( (\x -> (\y -> result (x,y))) "Rohit" ) as those last two expressions go together by the parsing rules. So what you actually have is item `bind` (\y -> result ("Rohit",y)) The first argument to bind has type Parser Char, the second argument (a -> Parser (String,a)). The result is exactly what's expected: Parser (String, Char), i.e. String -> ((String, Char), String). p.s. This might be what you're looking for: Try evaluating item "Rohit" in the repl. -- Kim-Ee

Thanks much Kim, that was very helpful.
On Sat, 15 Nov, 2014 11:09 pm Kim-Ee Yeoh
Your questions aren't lame. They are common confusions from those who come from a not-so-mathy background.
Your first question:
Shouldn't the return type be of (Char, [Char])?
suggests that you're confusing the type synonym of (Parser a), which is String -> (a, String), with just the right-hand-side, (a, String).
Your "z" expression has type Parser ([Char], Char), which means the same thing as String -> ((String, Char), String).
How did that happen?
Because
item `bind` (\x -> (\y -> result (x,y))) "Rohit"
is equivalent to
item `bind` ( (\x -> (\y -> result (x,y))) "Rohit" )
as those last two expressions go together by the parsing rules.
So what you actually have is
item `bind` (\y -> result ("Rohit",y))
The first argument to bind has type Parser Char, the second argument (a -> Parser (String,a)).
The result is exactly what's expected: Parser (String, Char), i.e. String -> ((String, Char), String).
p.s. This might be what you're looking for: Try evaluating
item "Rohit"
in the repl.
-- Kim-Ee _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (2)
-
Kim-Ee Yeoh
-
Rohit Sharma