On Sat, Mar 8, 2008 at 9:56 AM, Johan Tibell <[EMAIL PROTECTED]> wrote:
>  My current implementation of the parser type is
>
>  newtype Parser r a = Parser
>     { unParser :: S -> (a -> S -> Result r) -> (S -> Result r) -> Result r }
>
>  where the first parameter is the parse state, the second a success
>  continuation, and the third a failure continuation. The only tricky
>  part (except for the above mentioned problem) is to implement the
>  choice operator. I implement mine as
>
>  instance Applicative (Parser r) where
>     pure a = ...
>     p <*> p' = Parser $ \s succ fail ->
>                flip (unParser p s) fail $ \f s' ->
>                    unParser p' s' (succ . f) fail

Copied the wrong code, here's the implementation of <|>

instance Alternative (Parser r) where
    empty = ...
    p <|> p' = Parser $ \s@(S _ pos) succ fail ->
               unParser p s succ $ \s'@(S _ pos') ->
                   if pos == pos'
                   then unParser p' s' succ fail
                   else fail s'

-- Johan
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to