Daniel,
I am still trying to figure out the order of function applications in the parser returning list of objects (I attached again the code to the end of this message for convenience).

You wrote:
(>*>) associates to the right, hence
p >*> (p >*> (p >*> (... >*> (p >*> succeed [])...)))

I don't understand where (p >*> succeed []) comes from?
 
Yet, if the order is as you describe, everything goes well, for example:

comp1 = dig >*> dig   has type  - Parser char (char, char)
comp2 = dig >*> (succeed [])  has type  - Parser char (char, [a])
pl1 = comp2 `build` (uncurry (:)) has type - Parser char (char, [char])

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

should be:
[] ++  ((p >*> pList p) `build` (uncurry (:)))

so how we get:
(p >*> succeed []) ?
 
Thanks,
Dima

---
module MyParser where
 
import Data.Char
 
type Parse a b = [a] -> [(b, [a])]
 
none :: Parse a b
none  = \inp -> []
 
succeed :: b -> Parse a b
succeed val = \inp -> [(val, inp)]
 
spot :: (a -> Bool) -> Parse a a
spot p = \inp -> case inp of
                   [] -> []
                   (x:xs) -> if (p x) then [(x, xs)] else []      
 
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]
 
pList :: Parse a b -> Parse a [b]
pList p = (succeed []) `alt`
         ((p >*> pList p) `build` (uncurry (:)))
 
comp1 = dig >*> dig
comp2 = dig >*> (succeed [])
pl1 = comp `build` (uncurry (:))
 
test = pList dig
 
On 3/28/07, Daniel Fischer <daniel.is.fischer@web.de> wrote:
Am Dienstag, 27. März 2007 12:15 schrieb Dmitri O.Kondratiev:
> Thanks Daniel!
> Things are getting more in shape, yet I still can not fully comprehend the
> expression:
>
> ((p >*> pList p) `build` (uncurry (:)))
>
> where
>
>  (>*>) :: 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]
>
> So in fact recursive application:
>
> p >*> pList p
>
> should unfold in something like:
>
> ((p >*> p) >*> p) >*> p ...

(>*>) associates to the right, hence
p >*> (p >*> (p >*> (... >*> (p >*> succeed [])...)))

>
> and *all*  iterations of
>
> p >*> pList p
>
> will be done *before* 'build' will be applied?
>
> Correct?

Think so. Though it might be conceivable that 'build' would be partially
applied before.
After p has parsed the first item x1, leaving the remainder rem of the input,
we can see that the result will be
[(x1:lst,rem2) | (lst,rem2) <- pList p rem]
and we know that pList p never fails, due to 'succeed []', so that would be
more efficient than constructing and destroying a lot of pairs.
I've no idea whether a compiler would do that transformation, though I'd be
interested to know.
>
> Thanks,
> Dima
>
Cheers,
Daniel