[Haskell-cafe] Newbie: a parser for a list of objects?

Dmitri O.Kondratiev dokondr at gmail.com
Mon Mar 26 10:43:48 EDT 2007


Please see my questions inside comments {-- --} :
Thanks!

---
module Parser where

import Data.Char

type Parse a b = [a] -> [(b, [a])]

{--
Newbie: a parser for a list of objects?

I am working with the section  17.5 "Case study: parsing expressions" of the
book "Haskell The Craft of Functional Programming", where a parser for a
list of objects is defined.
I called this function pList in order to avoid confusion with 'list' as a
term for data structure.
Please help me to understand how pList works (please, see the rest of the
code at the end of this message):
--}

pList :: Parse a b -> Parse a [b]
pList p = (succeed []) `alt`
         ((p >*> pList p) `build` (uncurry (:)))

{--
First of all, I don't quite understand why there must be a choice ('alt')
between the function ('succeed') that always returns an empty list and the
other part? This results in adding [] to the front, why?

I thought that 'simplified' version of pList should still work fine. Trying
to prove this I wrote :
--}

pL1 :: Parse a b -> Parse a [b]
pL1 p = (p >*> pL1 p) `build` (uncurry (:))

{--
Which, as expected, does not work correctly - just gives an empty list [] -
but I don't understand why:

*Parser> t1 "12345"
[]
*Parser>

Also, I don't understand why the textbook version of pList gives this
result:

*Parser> test "12345"
[("","12345"),("1","2345"),("12","345"),("123","45"),("1234","5"),("12345","")]
*Parser>

In particular, I don't understand where the first element ("","12345") of
the resulting list comes from?

I am trying to figure out how pList recursively unfolds. To my mind
operators in the expression:

(succeed []) `alt`((p >*> pList p) `build` (uncurry (:)))

has the following execution order:
1)  >*>
2) 'build'
3) 'alt'

It seems that operation >*> should be done as many times as many elements
the input list has. Right?

Signature:

(>*>) :: Parse a b -> Parse a c -> Parse a (b, c)

implies that second argument of the expression:

p >*> pList p

should be of type 'Parse a c' but in this application it is of type 'Parse a
b -> Parse a [b]'
How can that be?
How recursion termination conditinon is expressed in pList?
--}

none :: Parse a b
none inp = []

succeed :: b -> Parse a b
succeed val inp = [(val, inp)]

suc:: b -> [a] -> [(b, [a])]
suc val inp = [(val, inp)]

spot :: (a -> Bool) -> Parse a a
spot p [] = []
spot p (x:xs)
     | p x = [(x, xs)]
     | otherwise = []

alt :: Parse a b -> Parse a b -> Parse a b
alt p1 p2 inp = p1 inp ++ p2 inp

bracket = spot (=='(')
dash = spot (== '-')
dig = spot isDigit
alpha = spot isAlpha

infixr 5 >*>

(>*>) :: Parse a b -> Parse a c -> Parse a (b, c)
(>*>) p1 p2 inp = [((x,y), rem2) |(x, rem1) <- p1 inp, (y, rem2) <- p2 rem1]

build :: Parse a b -> (b -> c) -> Parse a c
build p f inp = [ (f x, rem) | (x, rem) <- p inp]

test = pList dig
t1 = pL1 dig
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20070326/d1945776/attachment-0001.htm


More information about the Haskell-Cafe mailing list