Apply parser n times vs on the first n characters (Haskell) - parsing

I am studying parsers in Haskell following definitions from G. Hutton, E. Meijer - Monadic Parsing in Haskell.
data Parser a = Parser { parseWith :: String -> [(a, String)] }
instance Functor Parser where
fmap f (Parser p) = Parser $ \s -> [(f a, rest) | (a, rest) <- p s]
instance Applicative Parser where
pure x = Parser $ \s -> [(x, s)]
(Parser p1) <*> (Parser p2) = Parser $ \s -> [(f x, r2) | (f, r1) <- p1 s, (x, r2) <- p2 r1]
instance Monad Parser where
return = pure
p >>= f = Parser $ \s -> concatMap (\(x, r) -> parseWith (f x) r) $ parseWith p s
instance Alternative Parser where
empty = failure
p1 <|> p2 = Parser $ \s ->
case parseWith p1 s of
[] -> parseWith p2 s
res -> res
Essentially I have a (parsed :: a, remaining :: String) context.
As a simple application, I defined the following ADT to parse:
data Arr = Arr Int [Int] -- len [values]
and a parser that can construct Array values from strings, e.g.:
"5|12345" -> Arr 5 [1,2,3,4,5]
First, in order to parse n such Array values (the string input contains n on the first position), e.g.:
"2 3|123 4|9876 2|55" -> [Arr 3 [1,2,3], Arr 4 [9,8,7,6]]
I can do the following:
arrayParse :: Parser Arr
arrayParse = do
len <- digitParse
vals <- exactly len digitParse
return $ Arr len vals
nArraysParse :: Parser [Arr]
nArraysParse = do
n <- digitParse
exactly n arrayParse
where exactly n p constructs a new parser by applying p n times.
Next, I want to parse a different scheme.
Suppose the first character denotes the length of the sub-string defining the arrays, e.g.:
"9 3|123 4|9876 2|55" -> [Arr 3 [1,2,3], Arr 4 [9,8,7,6]]
Meaning that I have to apply arrayParse on the first n chars (excluding | and whitespace) to get the first 2 arrays:
3|123 -> 4 chars (excluding | and whitespace)
4|9876 -> 5 chars (excluding | and whitespace)
So, it's straightforward to apply a parser n times:
exactly :: Int -> Parser a -> Parser [a]
exactly 0 _ = pure []
exactly n p = do
v <- p -- apply parser p once
v' <- exactly (n-1) p -- apply parser p n-1 times
return (v:v')
but how can I express the intent of applying a parser on the first n characters?
My initial approach was something like this:
foo :: Parser [Arr]
foo = do
n <- digitParse
substring <- consume n
-- what to do with substring?
-- can I apply arrayParse on it?
How should I approach this?

Following #jlwoodwa's advice, I managed to achieve the following:
innerParse :: Parser a -> String -> Parser a
innerParse p s = case parseWith p s of
[(arr, "")] -> return arr
_ -> failure
substringParse :: Parser [Arr]
substringParse = do
n <- digitParse
substring <- consume n
innerParse (zeroOrMore arrayParse) substring
which works for my use-case.

Related

Combining parsers in Haskell

I'm given the following parsers
newtype Parser a = Parser { parse :: String -> Maybe (a,String) }
instance Functor Parser where
fmap f p = Parser $ \s -> (\(a,c) -> (f a, c)) <$> parse p s
instance Applicative Parser where
pure a = Parser $ \s -> Just (a,s)
f <*> a = Parser $ \s ->
case parse f s of
Just (g,s') -> parse (fmap g a) s'
Nothing -> Nothing
instance Alternative Parser where
empty = Parser $ \s -> Nothing
l <|> r = Parser $ \s -> parse l s <|> parse r s
ensure :: (a -> Bool) -> Parser a -> Parser a
ensure p parser = Parser $ \s ->
case parse parser s of
Nothing -> Nothing
Just (a,s') -> if p a then Just (a,s') else Nothing
lookahead :: Parser (Maybe Char)
lookahead = Parser f
where f [] = Just (Nothing,[])
f (c:s) = Just (Just c,c:s)
satisfy :: (Char -> Bool) -> Parser Char
satisfy p = Parser f
where f [] = Nothing
f (x:xs) = if p x then Just (x,xs) else Nothing
eof :: Parser ()
eof = Parser $ \s -> if null s then Just ((),[]) else Nothing
eof' :: Parser ()
eof' = ???
I need to write a new parser eof' that does exactly what eof does but is built only using the given parsers and the
Functor/Applicative/Alternative instances above. I'm stuck on this as I don't have experience in combining parsers. Can anyone help me out ?
To understand it easier, we can write it in an equational pseudocode, while we substitute and simplify the definitions, using Monad Comprehensions for clarity and succinctness.
Monad Comprehensions are just like List Comprehensions, only working for any MonadPlus type, not just []; while corresponding closely to do notation, e.g. [ (f a, s') | (a, s') <- parse p s ] === do { (a, s') <- parse p s ; return (f a, s') }.
This gets us:
newtype Parser a = Parser { parse :: String -> Maybe (a,String) }
instance Functor Parser where
parse (fmap f p) s = [ (f a, s') | (a, s') <- parse p s ]
instance Applicative Parser where
parse (pure a) s = pure (a, s)
parse (pf <*> pa) s = [ (g a, s'') | (g, s') <- parse pf s
, (a, s'') <- parse pa s' ]
instance Alternative Parser where
parse empty s = empty
parse (l <|> r) s = parse l s <|> parse r s
ensure :: (a -> Bool) -> Parser a -> Parser a
parse (ensure pred p) s = [ (a, s') | (a, s') <- parse p s, pred a ]
lookahead :: Parser (Maybe Char)
parse lookahead [] = pure (Nothing, [])
parse lookahead s#(c:_) = pure (Just c, s )
satisfy :: (Char -> Bool) -> Parser Char
parse (satisfy p) [] = mzero
parse (satisfy p) (x:xs) = [ (x, xs) | p x ]
eof :: Parser ()
parse eof s = [ ((), []) | null s ]
eof' :: Parser ()
eof' = ???
By the way thanks to the use of Monad Comprehensions and the more abstract pure, empty and mzero instead of their concrete representations in terms of the Maybe type, this same (pseudo-)code will work with a different type, like [] in place of Maybe, viz. newtype Parser a = Parser { parse :: String -> [(a,String)] }.
So we have
ensure :: (a -> Bool) -> Parser a -> Parser a
lookahead :: Parser (Maybe Char)
(satisfy is no good for us here .... why?)
Using that, we can have
ensure ....... ...... :: Parser (Maybe Char)
(... what does ensure id (pure False) do? ...)
but we'll have a useless Nothing result in case the input string was in fact empty, whereas the eof parser given to use produces the () as its result in such case (and otherwise it produces nothing).
No fear, we also have
fmap :: ( a -> b ) -> Parser a -> Parser b
which can transform the Nothing into () for us. We'll need a function that will always do this for us,
alwaysUnit nothing = ()
which we can use now to arrive at the solution:
eof' = fmap ..... (..... ..... ......)

Stack overflow with two functions calling each other in Applicative parser

I'm doing data61's course: https://github.com/data61/fp-course. In the parser one, the following implementation will cause parse (list1 (character *> valueParser 'v')) "abc" stack overflow.
Existing code:
data List t =
Nil
| t :. List t
deriving (Eq, Ord)
-- Right-associative
infixr 5 :.
type Input = Chars
data ParseResult a =
UnexpectedEof
| ExpectedEof Input
| UnexpectedChar Char
| UnexpectedString Chars
| Result Input a
deriving Eq
instance Show a => Show (ParseResult a) where
show UnexpectedEof =
"Unexpected end of stream"
show (ExpectedEof i) =
stringconcat ["Expected end of stream, but got >", show i, "<"]
show (UnexpectedChar c) =
stringconcat ["Unexpected character: ", show [c]]
show (UnexpectedString s) =
stringconcat ["Unexpected string: ", show s]
show (Result i a) =
stringconcat ["Result >", hlist i, "< ", show a]
instance Functor ParseResult where
_ <$> UnexpectedEof =
UnexpectedEof
_ <$> ExpectedEof i =
ExpectedEof i
_ <$> UnexpectedChar c =
UnexpectedChar c
_ <$> UnexpectedString s =
UnexpectedString s
f <$> Result i a =
Result i (f a)
-- Function to determine is a parse result is an error.
isErrorResult ::
ParseResult a
-> Bool
isErrorResult (Result _ _) =
False
isErrorResult UnexpectedEof =
True
isErrorResult (ExpectedEof _) =
True
isErrorResult (UnexpectedChar _) =
True
isErrorResult (UnexpectedString _) =
True
-- | Runs the given function on a successful parse result. Otherwise return the same failing parse result.
onResult ::
ParseResult a
-> (Input -> a -> ParseResult b)
-> ParseResult b
onResult UnexpectedEof _ =
UnexpectedEof
onResult (ExpectedEof i) _ =
ExpectedEof i
onResult (UnexpectedChar c) _ =
UnexpectedChar c
onResult (UnexpectedString s) _ =
UnexpectedString s
onResult (Result i a) k =
k i a
data Parser a = P (Input -> ParseResult a)
parse ::
Parser a
-> Input
-> ParseResult a
parse (P p) =
p
-- | Produces a parser that always fails with #UnexpectedChar# using the given character.
unexpectedCharParser ::
Char
-> Parser a
unexpectedCharParser c =
P (\_ -> UnexpectedChar c)
--- | Return a parser that always returns the given parse result.
---
--- >>> isErrorResult (parse (constantParser UnexpectedEof) "abc")
--- True
constantParser ::
ParseResult a
-> Parser a
constantParser =
P . const
-- | Return a parser that succeeds with a character off the input or fails with an error if the input is empty.
--
-- >>> parse character "abc"
-- Result >bc< 'a'
--
-- >>> isErrorResult (parse character "")
-- True
character ::
Parser Char
character = P p
where p Nil = UnexpectedString Nil
p (a :. as) = Result as a
-- | Parsers can map.
-- Write a Functor instance for a #Parser#.
--
-- >>> parse (toUpper <$> character) "amz"
-- Result >mz< 'A'
instance Functor Parser where
(<$>) ::
(a -> b)
-> Parser a
-> Parser b
f <$> P p = P p'
where p' input = f <$> p input
-- | Return a parser that always succeeds with the given value and consumes no input.
--
-- >>> parse (valueParser 3) "abc"
-- Result >abc< 3
valueParser ::
a
-> Parser a
valueParser a = P p
where p input = Result input a
-- | Return a parser that tries the first parser for a successful value.
--
-- * If the first parser succeeds then use this parser.
--
-- * If the first parser fails, try the second parser.
--
-- >>> parse (character ||| valueParser 'v') ""
-- Result >< 'v'
--
-- >>> parse (constantParser UnexpectedEof ||| valueParser 'v') ""
-- Result >< 'v'
--
-- >>> parse (character ||| valueParser 'v') "abc"
-- Result >bc< 'a'
--
-- >>> parse (constantParser UnexpectedEof ||| valueParser 'v') "abc"
-- Result >abc< 'v'
(|||) ::
Parser a
-> Parser a
-> Parser a
P a ||| P b = P c
where c input
| isErrorResult resultA = b input
| otherwise = resultA
where resultA = a input
infixl 3 |||
My code:
instance Monad Parser where
(=<<) ::
(a -> Parser b)
-> Parser a
-> Parser b
f =<< P a = P p
where p input = onResult (a input) (\i r -> parse (f r) i)
instance Applicative Parser where
(<*>) ::
Parser (a -> b)
-> Parser a
-> Parser b
P f <*> P a = P b
where b input = onResult (f input) (\i f' -> f' <$> a i)
list ::
Parser a
-> Parser (List a)
list p = list1 p ||| pure Nil
list1 ::
Parser a
-> Parser (List a)
list1 p = (:.) <$> p <*> list p
However, if I change list to not use list1, or use =<< in list1, it works fine. It also works if <*> uses =<<. I feel like it might be an issue with tail recursion.
UPDATE:
If I use lazy pattern matching here
P f <*> ~(P a) = P b
where b input = onResult (f input) (\i f' -> f' <$> a i)
It works fine. Pattern matching here is the problem. I don't understand this... Please help!
If I use lazy pattern matching P f <*> ~(P a) = ... then it works fine. Why?
This very issue was discussed recently. You could also fix it by using newtype instead of data: newtype Parser a = P (Input -> ParseResult a).(*)
The definition of list1 wants to know both parser arguments to <*>, but actually when the first will fail (when input is exhausted) we don't need to know the second! But since we force it, it will force its second argument, and that one will force its second parser, ad infinitum.(**) That is, p will fail when input is exhausted, but we have list1 p = (:.) <$> p <*> list p which forces list p even though it won't run when the preceding p fails. That's the reason for the infinite looping, and why your fix with the lazy pattern works.
What is the difference between data and newtype in terms of laziness?
(*)newtype'd type always has only one data constructor, and pattern matching on it does not actually force the value, so it is implicitly like a lazy pattern. Try newtype P = P Int, let foo (P i) = 42 in foo undefined and see that it works.
(**) This happens when the parser is still prepared, composed; before the combined, composed parser even gets to run on the actual input. This means there's yet another, third way to fix the problem: define
list1 p = (:.) <$> p <*> P (\s -> parse (list p) s)
This should work regardless of the laziness of <*> and whether data or newtype was used.
Intriguingly, the above definition means that the parser will be actually created during run time, depending on the input, which is the defining characteristic of Monad, not Applicative which is supposed to be known statically, in advance. But the difference here is that the Applicative depends on the hidden state of input, and not on the "returned" value.

Haskell: Graham Hutton Book Parsing (Ch-8): What does `parse (f v) out` do, and how does it do it?

My question is about Graham Hutton's book Programming in Haskell 1st Ed.
There is a parser created in section 8.4, and I am assuming anyone answering has the book or can see the link to slide 8 in the link above.
A basic parser called item is described as:
type Parser a = String -> [(a, String)]
item :: Parser Char
item = \inp -> case inp of
[] -> []
(x:xs) -> [(x,xs)]
which is used with do to define another parser p (the do parser)
p :: Parser (Char, Char)
p = do x <- item
item
y <- item
return (x,y)
the relevant bind definition is:
(>>=) :: Parser a -> (a -> Parser b) -> Parser b
p >>= f = \inp -> case parse p inp of
[] -> []
[(v,out)] -> parse (f v) out
return is defined as:
return :: a -> Parser a
return v = \inp -> [(v,inp)]
parse is defined as:
parse :: Parser a -> String -> [(a,String)]
parse p inp = p inp
The program (the do parser) takes a string and selects the 1st and 3rd characters and returns them in a tuple with the remainder of the string in a list, e.g., "abcdef" produces [('a','c'), "def"].
I want to know how the
(f v) out
in
[(v,out)] -> parse (f v) out
returns a parser which is then applied to out.
f in the do parser is item and item taking a character 'c' returns [('c',[])]?
How can that be a parser and how can it take out as an argument?
Perhaps I am just not understanding what (f v) does.
Also how does the do parser 'drop' the returned values each time to operate on the rest of the input string when item is called again?
What is the object that works its way through the do parser, and how is it altered at each step, and by what means is it altered?
f v produces a Parser b because f is a function of type a -> Parser b and v is a value of type a. So then you're calling parse with this Parser b and the string out as arguments.
F in the 'do' parser is item
No, it's not. Let's consider a simplified (albeit now somewhat pointless) version of your parser:
p = do x <- item
return x
This will desugar to:
p = item >>= \x -> return x
So the right operand of >>=, i.e. f, is \x -> return x, not item.
Also how does the 'do' parser 'drop' the returned values each time to operate on the rest of the input string when item is called again? What is the object that works its way through the 'do' parser and how is it altered and each step and by what means is it altered?
When you apply a parser it returns a tuple containing the parsed value and a string representing the rest of the input. If you look at item for example, the second element of the tuple will be xs which is the tail of the input string (i.e. a string containing all characters of the input string except the first). This second part of the tuple will be what's fed as the new input to subsequent parsers (as per [(v,out)] -> parse (f v) out), so that way each successive parser will take as input the string that the previous parser produced as the second part of its output tuple (which will be a suffix of its input).
In response to your comments:
When you write "p = item >>= \x -> return x", is that the equivalent of just the first line "p = do x <- item"?
No, it's equivalent to the entire do-block (i.e. do {x <- item; return x}). You can't translate do-blocks line-by-line like that. do { x <- foo; rest } is equivalent to foo >>= \x -> do {rest}, so you'll always have the rest of the do-block as part of the right operand of >>=.
but not how that reduces to simply making 'out' available as the input for the next line. What is parse doing if the next line of the 'do' parser is a the item parser?
Let's walk through an example where we invoke item twice (this is like your p, but without the middle item). In the below I'll use === to denote that the expressions above and below the === are equivalent.
do x <- item
y <- item
return (x, y)
=== -- Desugaring do
item >>= \x -> item >>= \y -> return (x, y)
=== -- Inserting the definition of >>= for outer >>=
\inp -> case parse item inp of
[] -> []
[(v,out)] -> parse (item >>= \y -> return (v, y)) out
Now let's apply this to the input "ab":
case parse item "ab" of
[] -> []
[(v,out)] -> parse (item >>= \y -> return (v, y)) out
=== Insert defintiion of `parse`
case item "ab" of
[] -> []
[(v,out)] -> parse (item >>= \y -> return (v, y)) out
=== Insert definition of item
case ('a', "b") of
[] -> []
[(v,out)] -> parse (item >>= \y -> return (v, y)) out
===
parse (item >>= \y -> return ('a', y)) out
Now we can expand the second >>= the same we did the fist and eventually end up with ('a', 'b').
The relevant advice is, Don't panic (meaning, don't rush it; or, take it slow), and, Follow the types.
First of all, Parsers
type Parser a = String -> [(a,String)]
are functions from String to lists of pairings of result values of type a and the leftover Strings (because type defines type synonyms, not new types like data or newtype do).
That leftovers string will be used as input for the next parsing step. That's the main thing about it here.
You are asking, in
p >>= f = \inp -> case (parse p inp) of
[] -> []
[(v,out)] -> parse (f v) out
how the (f v) in [(v,out)] -> parse (f v) out returns a parser which is then applied to out?
The answer is, f's type says that it does so:
(>>=) :: Parser a -> (a -> Parser b) -> Parser b -- or, the equivalent
(>>=) :: Parser a -> (a -> Parser b) -> (String -> [(b,String)])
-- p f inp
We have f :: a -> Parser b, so that's just what it does: applied to a value of type a it returns a value of type Parser b. Or equivalently,
f :: a -> (String -> [(b,String)]) -- so that
f (v :: a) :: String -> [(b,String)] -- and,
f (v :: a) (out :: String) :: [(b,String)]
So whatever is the value that parse p inp produces, it must be what f is waiting for to proceed. The types must "fit":
p :: Parser a -- m a
f :: a -> Parser b -- a -> m b
f <$> p :: Parser ( Parser b ) -- m ( m b )
f =<< p :: Parser b -- m b
or, equivalently,
p :: String -> [(a, String)]
-- inp v out
f :: a -> String -> [(b, String)]
-- v out
p >>= f :: String -> [(b, String)] -- a combined Parser
-- inp v2 out2
So this also answers your second question,
How can that be a parser and how can it take out as an argument?
The real question is, what kind of f is it, that does such a thing? Where does it come from? And that's your fourth question.
And the answer is, your example in do-notation,
p :: Parser (Char, Char)
p = do x <- item
_ <- item
y <- item
return (x,y)
by Monad laws is equivalent to the nested chain
p = do { x <- item
; do { _ <- item
; do { y <- item
; return (x,y) }}}
which is a syntactic sugar for the nested chain of Parser bind applications,
p :: Parser (Char, Char) -- ~ String -> [((Char,Char), String)]
p = item >>= (\ x -> -- item :: Parser Char ~ String -> [(Char,String)]
item >>= (\ _ -> -- x :: Char
item >>= (\ y -> -- y :: Char
return (x,y) )))
and it is because the functions are nested that the final return has access to both y and x there; and it is precisely the Parser bind that arranges for the output leftovers string to be used as input to the next parsing step:
p = item >>= f -- :: String -> [((Char,Char), String)]
where
{ f x = item >>= f2
where { f2 _ = item >>= f3
where { f3 y = return (x,y) }}}
i.e. (under the assumption that inp is a string of length two or longer),
parse p inp -- assume that `inp`'s
= (item >>= f) inp -- length is at least 2 NB.
=
let [(v, left)] = item inp -- by the def of >>=
in
(f v) left
=
let [(v, left)] = item inp
in
let x = v -- inline the definition of `f`
in (item >>= f2) left
=
let [(v, left)] = item inp
in let x = v
in let [(v2, left2)] = item left -- by the def of >>=, again
in (f2 v2) left2
=
..........
=
let [(x,left1)] = item inp -- x <- item
[(_,left2)] = item left1 -- _ <- item
[(y,left3)] = item left2 -- y <- item
in
[((x,y), left3)]
=
let (x:left1) = inp -- inline the definition
(_:left2) = left1 -- of `item`
(y:left3) = left2
in
[((x,y), left3)]
=
let (x:_:y:left3) = inp
in
[((x,y), left3)]
after few simplifications.
And this answers your third question.
I am having similar problems reading the syntax, because it's not what we are used to.
(>>=) :: Parser a -> (a -> Parser b) -> Parser b
p >>= f = \inp -> case parse p inp of
[] -> []
[(v,out)] -> parse (f v) out
so for the question:
I want to know how the (f v) out in [(v,out)] -> parse (f v) out returns a parser which is then applied to out.
It does because that's the signature of the 2nd arg (the f): (>>=) :: Parser a -> (a -> Parser b) -> Parser b .... f takes an a and produces a Parser b . a Parser b takes a String which is the out ... (f v) out.
But the output of this should not be mixed up with the output of the function we are writing: >>=
We are outputting a parser ... (>>=) :: Parser a -> (a -> Parser b) ->
Parser b .
The Parser we are outputting has the job of wrapping and chaining the first 2 args
A parser is a function that takes 1 arg. This is constructed right after the first = ... i.e. by returning an (anonymous) function: p >>= f = \inp -> ... so inp refers to the input string of the Parser we are building
so what is left is to define what that constructed function should do ... NOTE: we are not implementing any of the input parsers just chaining them together ... so the output Parser function should:
apply the input parser (p) to the its input (inp): p >>= f = \inp -> case parse p inp of
take the output of that parse [(v, out)] -- v is the result, out is what remains of the input
apply the input function (f is (a -> Parser b)) to the parsed result (v)
(f v) produces a Parser b (a function that takes 1 arg)
so apply that output parser to the remainder of the input after the first parser (out)
For me the understanding lies in the use of destructuring and the realization that we are constructing a function that glues together the execution of other functions together simply considering their interface.
Hope that helps ... it helped me to write it :-)

applicative functor: <*> and partial application, how it works

I am reading the book Programming in Haskell by Graham Hutton and I have some problem to understand how <*> and partial application can be used to parse a string.
I know that pure (+1) <*> Just 2
produces Just 3
because pure (+1) produces Just (+1) and then Just (+1) <*> Just 2
produces Just (2+1) and then Just 3
But in more complex case like this:
-- Define a new type containing a parser function
newtype Parser a = P (String -> [(a,String)])
-- This function apply the parser p on inp
parse :: Parser a -> String -> [(a,String)]
parse (P p) inp = p inp
-- A parser which return a tuple with the first char and the remaining string
item :: Parser Char
item = P (\inp -> case inp of
[] -> []
(x:xs) -> [(x,xs)])
-- A parser is a functor
instance Functor Parser where
fmap g p = P (\inp -> case parse p inp of
[] -> []
[(v, out)] -> [(g v, out)])
-- A parser is also an applicative functor
instance Applicative Parser where
pure v = P (\inp -> [(v, inp)])
pg <*> px = P (\inp -> case parse pg inp of
[] -> []
[(g, out)] -> parse (fmap g px) out)
So, when I do:
parse (pure (\x y -> (x,y)) <*> item <*> item) "abc"
The answer is:
[(('a','b'),"c")]
But I don't understand what exactly happens.
First:
pure (\x y -> (x,y)) => P (\inp1 -> [(\x y -> (x,y), inp1)])
I have now a parser with one parameter.
Then:
P (\inp1 -> [(\x y -> (x,y), inp1)]) <*> item
=> P (\inp2 -> case parse (\inp1 -> [(\x y -> (x,y), inp1)]) inp2 of ???
I really don't understand what happens here.
Can someone explain, step by step, what's happens now until the end please.
Let's evaluate pure (\x y -> (x,y)) <*> item. The second application of <*> will be easy once we've seen the first:
P (\inp1 -> [(\x y -> (x,y), inp1)]) <*> item
We replace the <*> expression with its definition, substituting the expression's operands for the definition's parameters.
P (\inp2 -> case parse P (\inp1 -> [(\x y -> (x,y), inp1)]) inp2 of
[] -> []
[(g, out)] -> parse (fmap g item) out)
Then we do the same for the fmap expression.
P (\inp2 -> case parse P (\inp1 -> [(\x y -> (x,y), inp1)]) inp2 of
[] -> []
[(g, out)] -> parse P (\inp -> case parse item inp of
[] -> []
[(v, out)] -> [(g v, out)]) out)
Now we can reduce the first two parse expressions (we'll leave parse item out for later since it's basically primitive).
P (\inp2 -> case [(\x y -> (x,y), inp2)] of
[] -> []
[(g, out)] -> case parse item out of
[] -> []
[(v, out)] -> [(g v, out)])
So much for pure (\x y -> (x,y)) <*> item. Since you created the first parser by lifting a binary function of type a -> b -> (a, b), the single application to a parser of type Parser Char represents a parser of type Parser (b -> (Char, b)).
We can run this parser through the parse function with input "abc". Since the parser has type Parser (b -> (Char, b)), this should reduce to a value of type [(b -> (Char, b), String)]. Let's evaluate that expression now.
parse P (\inp2 -> case [(\x y -> (x,y), inp2)] of
[] -> []
[(g, out)] -> case parse item out of
[] -> []
[(v, out)] -> [(g v, out)]) "abc"
By the definition of parse this reduces to
case [(\x y -> (x,y), "abc")] of
[] -> []
[(g, out)] -> case parse item out of
[] -> []
[(v, out)] -> [(g v, out)]
Clearly, the patterns don't match in the first case, but they do in the second case. We substitute the matches for the patterns in the second expression.
case parse item "abc" of
[] -> []
[(v, out)] -> [((\x y -> (x,y)) v, out)]
Now we finally evaluate that last parse expression. parse item "abc" clearly reduces to [('a', "bc")] from the definition of item.
case [('a', "bc")] of
[] -> []
[(v, out)] -> [((\x y -> (x,y)) v, out)]
Again, the second pattern matches and we do substitution
[((\x y -> (x,y)) 'a', "bc")]
which reduces to
[(\y -> ('a', y), "bc")] :: [(b -> (Char, b), String)] -- the expected type
If you apply this same process to evaluate a second <*> application, and put the result in the parse (result) "abc" expression, you'll see that the expression indeed reduces to[(('a','b'),"c")].
What helped me a lot while learning these things was to focus on the types of the values and functions involved. It's all about applying a function to a value (or in your case applying a function to two values).
($) :: (a -> b) -> a -> b
fmap :: Functor f => (a -> b) -> f a -> f b
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
So with a Functor we apply a function on a value inside a "container/context" (i.e. Maybe, List, . .), and with an Applicative the function we want to apply is itself inside a "container/context".
The function you want to apply is (,), and the values you want to apply the function to are inside a container/context (in your case Parser a).
Using pure we lift the function (,) into the same "context/container" our values are in (note, that we can use pure to lift the function into any Applicative (Maybe, List, Parser, . . ):
(,) :: a -> b -> (a, b)
pure (,) :: Parser (a -> b -> (a, b))
Using <*> we can apply the function (,) that is now inside the Parser context to a value that is also inside the Parser context. One difference to the example you provided with +1 is that (,) has two arguments. Therefore we have to use <*> twice:
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
x :: Parser Int
y :: Parser Char
let p1 = pure (,) <*> x :: Parser (b -> (Int, b))
let v1 = (,) 1 :: b -> (Int, b)
let p2 = p1 <*> y :: Parser (Int, Char)
let v2 = v1 'a' :: (Int, Char)
We have now created a new parser (p2) that we can use just like any other parser!
. . and then there is more!
Have a look at this convenience function:
(<$>) :: Functor f => (a -> b) -> f a -> f b
<$> is just fmap but you can use it to write the combinators more beautifully:
data User = User {name :: String, year :: Int}
nameParser :: Parser String
yearParser :: Parser Int
let userParser = User <$> nameParser <*> yearParser -- :: Parser User
Ok, this answer got longer than I expected! Well, I hope it helps. Maybe also have a look at Typeclassopedia which I found invaluable while learning Haskell which is an endless beautiful process . . :)
TL;DR: When you said you "[now] have a parser with one parameter" inp1, you got confused: inp1 is an input string to a parser, but the function (\x y -> (x,y)) - which is just (,) - is being applied to the output value(s), produced by parsing the input string. The sequence of values produced by your interim parsers is:
-- by (pure (,)):
(,) -- a function expecting two arguments
-- by the first <*> combination with (item):
(,) x -- a partially applied (,) function expecting one more argument
-- by the final <*> combination with another (item):
((,) x) y == (x,y) -- the final result, a pair of `Char`s taken off the
-- input string, first (`x`) by an `item`,
-- and the second (`y`) by another `item` parser
Working by equational reasoning can oftentimes be easier:
-- pseudocode definition of `fmap`:
parse (fmap g p) inp = case (parse p inp) of -- g :: a -> b , p :: Parser a
[] -> [] -- fmap g p :: Parser b
[(v, out)] -> [(g v, out)] -- v :: a , g v :: b
(apparently this assumes any parser can only produce 0 or 1 results, as the case of a longer list isn't handled at all -- which is usually frowned upon, and with good reason);
-- pseudocode definition of `pure`:
parse (pure v) inp = [(v, inp)] -- v :: a , pure v :: Parser a
(parsing with pure v produces the v without consuming the input);
-- pseudocode definition of `item`:
parse (item) inp = case inp of -- inp :: ['Char']
[] -> []
(x:xs) -> [(x,xs)] -- item :: Parser 'Char'
(parsing with item means taking one Char off the head of the input String, if possible); and,
-- pseudocode definition of `(<*>)`:
parse (pg <*> px) inp = case (parse pg inp) of -- px :: Parser a
[] -> []
[(g, out)] -> parse (fmap g px) out -- g :: a -> b
(<*> combines two parsers with types of results that fit, producing a new, combined parser which uses the first parse to parse the input, then uses the second parser to parse the leftover string, combining the two results to produce the result of the new, combined parser);
Now, <*> associates to the left, so what you ask about is
parse ( pure (\x y -> (x,y)) <*> item <*> item ) "abc"
= parse ( (pure (,) <*> item1) <*> item2 ) "abc" -- item_i = item
the rightmost <*> is the topmost, so we expand it first, leaving the nested expression as is for now,
= case (parse (pure (,) <*> item1) "abc") of -- by definition of <*>
[] -> []
[(g2, out2)] -> parse (fmap g2 item2) out2
= case (parse item out2) of -- by definition of fmap
[] -> []
[(v, out)] -> [(g2 v, out)]
= case out2 of -- by definition of item
[] -> []
(y:ys) -> [(g2 y, ys)]
Similarly, the nested expression is simplified as
parse (pure (,) <*> item1) "abc"
= case (parse (pure (\x y -> (x,y))) "abc") of -- by definition of <*>
[] -> []
[(g1, out1)] -> parse (fmap g1 item1) out1
= case (parse item out1) of ....
= case out1 of
[] -> []
(x:xs) -> [(g1 x, xs)]
= case [((,), "abc")] of -- by definition of pure
[(g1, out1)] -> case out1 of
[] -> []
(x:xs) -> [(g1 x, xs)]
= let { out1 = "abc"
; g1 = (,)
; (x:xs) = out1
}
in [(g1 x, xs)]
= [( (,) 'a', "bc")]
and thus we get
= case [( (,) 'a', "bc")] of
[(g2, out2)] -> case out2 of
[] -> []
(y:ys) -> [(g2 y, ys)]
I think you can see now why the result will be [( ((,) 'a') 'b', "c")].
First, I want to emphasize one thing. I found that the crux of understanding lies in noticing the separation between the Parser itself and running the parser with parse.
In running the parser you give the Parser and input string to parse and it will give you the list of possible parses. I think that's probably easy to understand.
You will pass parse a Parser, which may be built using glue, <*>. Try to understand that when you pass parse the Parser, a, or the Parser, f <*> a <*> b, you will be passing it the same type of thing, i.e. something equivalent to (String -> [(a,String)]). I think this is probably easy to understand as well, but still it takes a while to "click".
That said, I'll talk a little about the nature of this applicative glue, <*>. An applicative, F a is a computation that yields data of type a. You can think of a term such as
... f <*> g <*> h
as a series of computations which return some data, say a then b then c. In the context of Parser, the computation involve f looking for a in the current string, then passing the remainder of the string to g, etc. If any of the computations/parses fails, then so does the whole term.
Its interesting to note that any applicative can be written with a pure function at the beginning to collect all those emitted values, so we can generally write,
pure3ArgFunction <$> f <*> g <*> h
I personally find the mental model of emitting and collecting helpful.
So, with that long preamble over, onto the actual explanation. What does
parse (pure (\x y -> (x,y)) <*> item <*> item) "abc"
do? Well, parse (p::Parser (Char,Char) "abc" applies the parser, (which I renamed p) to "abc", yielding [(('a','b'),"c")]. This is a successful parse with the return value of ('a','b') and the leftover string, "c".
Ok, that's not the question though. Why does the parser work this way? Starting with:
.. <*> item <*> item
item takes the next character from the string, yields it as a result and passes the unconsumed input. The next item does the same. The beginning can be rewritten as:
fmap (\x y -> (x,y)) $ item <*> item
or
(\x y -> (x,y)) <$> item <*> item
which is my way of showing that the pure function does not do anything to the input string, it just collects the results. When looked at in this light I think the parser should be easy to understand. Very easy. Too easy. I mean that in all seriousness. Its not that the concept is so hard, but our normal frame of looking at programming is just too foreign for it to make much sense at first.
Some people below did great jobs on "step-by-step" guides for you to easily understand the progress of computation to create the final result. So I don't replicate it here.
What I think is that, you really need to deeply understand about Functor and Applicative Functor. Once you understand these topics, the others will be easy as one two three (I means most of them ^^).
So: what is Functor, Applicative Functor and their applications in your problem?
Best tutorials on these:
Chapter 11 of "Learn You a Haskell for a great good": http://learnyouahaskell.com/functors-applicative-functors-and-monoids.
More visual "Functors, Applicatives, And Monads in Pictures": http://adit.io/posts/2013-04-17-functors,_applicatives,_and_monads_in_pictures.html.
First, when you think about Functor, Applicative Functor, think about "values in contexts": the values are important, and the computational contexts are important too. You have to deal with both of them.
The definitions of the types:
-- Define a new type containing a parser function
newtype Parser a = P (String -> [(a,String)])
-- This function apply the parser p on inp
parse :: Parser a -> String -> [(a,String)]
parse (P p) inp = p inp
The value here is the value of type a, the first element of the tuple in the list.
The context here is the function, or the eventual value. You have to supply an input to get the final value.
Parser is a function wrapped in a P data constructor. So if you got a value b :: Parser Char, and you want to apply it to some input, you have to unwrap the inner function in b. That's why we have the function parse, it unwraps the inner function and applies it to the input value.
And, if you want to create Parser value, you have to use P data constructor wraps around a function.
Second, Functor: something that can be "mapped" over, specified by the function fmap:
fmap :: (a -> b) -> f a -> f b
I often call the function g :: (a -> b) is a normal function because as you see no context wraps around it. So, to be able to apply g to f a, we have to extract the a from f a somehow, so that g can be apply to a alone. That "somehow" depends on the specific Functor and is the context you are working in:
instance Functor Parser where
fmap g p = P (\inp -> case parse p inp of
[] -> []
[(v, out)] -> [(g v, out)])
g is the function of type (a -> b), p is of type f a.
To unwrap p, to get the value of of context, we have to pass some input value in: parse p inp, then the value is the 1st element of the tuple. Apply g to that value, get a value of type b.
The result of fmap is of type f b, so we have to wrap all the result in the same context, that why we have: fmap g p = P (\inp -> ...).
At this time, you might be wonder you could have an implementation of fmap in which the result, instead of [(g v, out)], is [(g v, inp)]. And the answer is Yes. You can implement fmap in any way you like, but the important thing is to be an appropriate Functor, the implementation must obey Functor laws. The laws are they way we deriving the implementation of those functions (http://mvanier.livejournal.com/4586.html). The implementation must satisfy at least 2 Functor laws:
fmap id = id.
fmap (f . g) = fmap f . fmap g.
fmap is often written as infix operator: <$>. When you see this, look at the 2nd operand to determine which Functor you are working with.
Third, Applicative Functor: you apply a wrapped function to a wrapped value to get another wrapped value:
<*> :: f (a -> b) -> f a -> f b
Unwrap the inner function.
Unwrap 1st value.
Apply the function and wrap the result.
In your case:
instance Applicative Parser where
pure v = P (\inp -> [(v, inp)])
pg <*> px = P (\inp -> case parse pg inp of
[] -> []
[(g, out)] -> parse (fmap g px) out)
pg is of type f (a -> b), px is of type f a.
Unwrap g from pg by parse pg inp, g is the 1st of the tuple.
Unwrap px and apply g to the value by using fmap g px. Attention, the result function only applies to out, in some case that is "bc" not "abc".
Wrap the whole result: P (\inp -> ...).
Like Functor, an implementation of Applicative Functor must obey Applicative Functor laws (in the tutorials above).
Fourth, apply to your problem:
parse (pure (\x y -> (x,y)) <*> item <*> item) "abc"
| f1 | |f2| |f3|
Unwrap f1 <*> f2 by passing "abc" to it:
Unwrap f1 by passing "abc" to it, we get [(g, "abc")].
Then fmap g on f2 and passing out="abc" to it:
Unwrap f2 get [('a', "bc")].
Apply g on 'a' get a result: [(\y -> ('a', y), "bc")].
Then fmap 1st element of the result on f3 and passing out="bc" to it:
Unwrap f3 get [('b', "c")].
Apply the function on 'b' get final result: [(('a', 'b'), "c")].
In conclusion:
Take some time for the ideas to "dive" into you. Especially, the laws derives the implementations.
Next time, design your data structure to easier understand.
Haskell is one of my favorite languages and I thing it will be yours soon, so be patient, it needs a learning curve and then you go!
Happy Haskell hacking!
Hmm I am not experienced with Haskell but my attempt on generating Functor and Applicative instances of the Parser type would be as follows;
-- Define a new type containing a parser function
newtype Parser a = P (String -> [(a,String)])
-- This function apply the parser p on inp
parse :: Parser a -> String -> [(a,String)]
parse (P p) inp = p inp
-- A parser which return a tuple with the first char and the remaining string
item :: Parser Char
item = P (\inp -> case inp of
[] -> []
(x:xs) -> [(x,xs)])
-- A parser is a functor
instance Functor Parser where
fmap g (P f) = P (\str -> map (\(x,y) -> (g x, y)) $ f str)
-- A parser is also an applicative functor
instance Applicative Parser where
pure v = P (\str -> [(v, str)])
(P g) <*> (P f) = P (\str -> [(g' v, s) | (g',s) <- g str, (v,_) <- f str])
(P g) <*> (P f) = P (\str -> f str >>= \(v,s1) -> g s1 >>= \(g',s2) -> [(g' v,s2)])
(10x very much for the helping of #Will Ness on <*>)
Accordingly...
*Main> parse (P (\s -> [((+3), s)]) <*> pure 2) "test"
[(5,"test")]
*Main> parse (P (\s -> [((,), s ++ " altered")]) <*> pure 2 <*> pure 4) "test"
[((2,4),"test altered")]

Monadic parsing functional pearl - gluing multiple parsers together

I am working my way through the functional pearl paper Monadic parsing in Haskell (after recommendation at haskellforall.com to read that paper to understand parsing). I wrote an implementation until section 4 on page 3 as below:
newtype Parser a = Parser (String -> [(a,String)])
parse (Parser p) = p
instance Monad Parser where
return a = Parser (\cs -> [(a,cs)])
p >>= f = Parser (\cs -> concat [parse (f a) cs' | (a,cs') <- parse p cs])
item :: Parser Char
item = Parser (\cs -> case cs of
"" -> []
(c:cs) -> [(c,cs)])
p :: Parser (Char,Char)
p = do { a <- item; item; b <- item; return (a,b)}
According to the paper, p is a parser that consumes three characters, skips middle one, and returns a pair of first and second. What I can't figure out is how the modified input string is passed to 2nd and 3rd definitions of item in p. We are not passing the result of first parser to second parser, and so on (because ;, syntactic sugar for >> is used which discards the result as shown by type signature (>>) :: Monad m => m a -> m b -> m b). I will appreciate explanation of how the modified function is being passed in last two invocations of item in p.
Another thing that confuses me is the handling of cs in item - it doesn't return (head,tail) pair. Shouldn't it be redefined as follow since the item parser consumes one character according to the paper:
item :: Parser Char
item = Parser (\cs -> case cs of
"" -> []
(c:cs') -> [(c,cs')]) -- redefinition - use cs' to denote tail
The syntax ; is not always syntactic sugar for >>.
Rather, we have:
do m ; n = m >> n
do x<-m ; n = m >>= \x -> n
(The above translation is simplified, the full gory details can be found in the Haskell Report)
So, your definition for p is equivalent to:
p = item >>= \a -> ( item >> (item >>= \b -> return (a,b) ))
Here, you can see that the first and third items do not have their results discarded (because >>= binds them to a and b respectively), while the middle item does.
Also note that the code
\cs -> case cs of
"" -> []
(c:cs) -> [(c,cs)]
is misleading since it is defining variable cs twice: once in the \cs and once in the
pattern (c:cs). It is equivalent to
\cs -> case cs of
"" -> []
(x:xs) -> [(x,xs)]
This clarifies that the final String is the output is not the original cs one, but rather its tail xs.
In a comment, the poster wondered why the three uses of item do not return the same result, i.e., why in return (a,b) the character a is not equal to b. This is due to the >>= monadic operator, which in this Parser monad automatically feeds the output string xs of each item occurence to the next one. Indeed, the whole point of this monad is to help feeding the "leftover" output of each parser as the "to-be-consumed" input in the next one. This has two advantages: it frees the programmer from having to write code to pass this string around, and it ensures that the string is not accidentally "rewound" to a previous state. To illustrate the latter point, here's some wrong code:
let [(c1,s1)] = someParser someInitialString
[(c2,s2)] = anotherParser1 s1
[(c3,s3)] = anotherParser2 s2
[(c4,s4)] = anotherParser3 s3
[(c5,s5)] = anotherParser4 s2 -- Whoops! Should have been s4
in [c1,c2,c3,c4,c5]
In the last step the string, after having been consumed multiple times, is wrongly rolled back to a previous state, as if the parsers anotherParser2 and anotherParser3 did not consume anything at all. This error is prevented by composing parsers through >>= instead.
I'll try shedding some more light regarding >>.
As you see in the other answer, you should desugar the do's into >>= to better understand what's going on.
Let's for example write a parser that parses two chars and returns them.
twoChars :: Parser (Char,Char)
twoChars = do
i <- item
j <- item
return (i,j)
Now, desugar the do syntax:
twoChars :: Parser (Char,Char)
twoChars =
item >>= (\i ->
item >>= (\j ->
return (i,j) ) )
I put brackets for clarity. As you see, the second item receives the result of the first item parser in the anonymous function, with the result bound to i. The >>= function takes a parser, a function, and returns a parser. Best way to understand it would be to plug it into the definition:
f = \i → item »= \j → return (i,j)
twoChars = item >>= f
twoChars = Parser (\cs -> concat [parse (f a) cs' | (a,cs') <- parse item cs])
So we got back a new Parser. Try to imagine what it will do on an input "abc". cs is bound to "abc", and the item Parser is used to get back [('a',"bc")]. Now, we apply f to 'a', to get back the new parser:
item >>= \j -> return ('a',j)
This parser will be passed the rest of our string left to process ("bc"), and it will use the item parser to get out the b when the \j above is bound to b. We then get a return ('a','b') statement, which puts ('a','b') into a parser that just return ('a','b').
I hope this clears up how the information flow happens. Now, suppose that you want to ignore a character. You could do it like this.
twoChars :: Parser (Char,Char)
twoChars =
item >>= \i ->
item >>= \j ->
item >>= \k ->
return (i,k)
It's ok that the j is bound to 'b' for the example "abc", you never use it. We can so replace j by _.
twoChars :: Parser (Char,Char)
twoChars =
item >>= \i ->
item >>= \_ ->
item >>= \k ->
return (i,k)
But we also know that >> :: m a -> m b -> m b can be defined as:
p >> q = p >>= \_ -> q
So we are left with
twoChars :: Parser (Char,Char)
twoChars =
item >>= \i ->
item >>
item >>= \k ->
return (i,k)
Finally, you can sugar this back into do. The application of >> simply sugars into a single-line statement with no bounding. It results in:
twoChars :: Parser (Char,Char)
twoChars = do
i <- item
item
j <- item
return (i,j)
Hope this cleared some things up.
The more uniform translation of your
p3 = do { a <- item; item; b <- item; return (a,b)}
-- do { a <- item; z <- item; b <- item; return (a,b)} -- z is ignored
is
p3 = item >>= (\a ->
item >>= (\z ->
item >>= (\b ->
return (a,b)))) -- z is unused
(the key observation here is that the functions are nested). Which means that
-- parse (return a) cs = [(a,cs)]
-- parse (p >>= f) cs = [r | (a,cs1) <- parse p cs, -- concat
-- r <- parse (f a) cs1] ) -- inlined !
parse p3 cs
= [ r | (a,cs1) <- parse item cs,
r <- [ r | (z,cs2) <- parse item cs1,
r <- [ r | (b,cs3) <- parse item cs2,
r <- -- parse (return (a,b)) cs3
[((a,b),cs3)]]]] -- z is unused
= [ ((a,b),cs3) | (a,cs1) <- parse item cs,
(_,cs2) <- parse item cs1,
(b,cs3) <- parse item cs2]
So you see, "the input string" does change: first it's cs, then cs1, then cs2.
That is the simple real computation behind all the Parser tags and do syntax. It's all just about the chaining of inputs and outputs in the nested loops, in the end:
parse p3 cs =
for each (a,cs1) in (parse item cs):
for each (z,cs2) in (parse item cs1):
for each (b,cs3) in (parse item cs2):
yield ((a,b),cs3)

Resources