[Haskell-cafe] stuck with a sample of "programming in haskell"

国平张 zhangguoping at gmail.com
Fri Mar 19 05:02:43 EDT 2010


Sorry. The same error, This is new stuff.
-----------------------------------------------------------------------------------
newtype Parser a = P { parse :: (String -> [(a,String)]) }

instance Monad Parser where
   return v = P (\s -> [(v,s)])
   p >>= f = P (\s -> case parse p s of
                       []    -> []
                       [(v,str)] -> parse (f v) str)
   fail _ = P (\_ -> [])



item :: Parser Char
item = \inp -> case inp of
                    [] -> []
                    (x:xs) -> [(x,xs)]
p :: Parser (Char,Char)
p = do { x <- item
      ; item
      ; y <- item
      ; return (x,y) }
-----------------------------------------------------------------------------------
I got following:
Prelude> :load c:\b.hs
[1 of 1] Compiling Main             ( C:\b.hs, interpreted )

C:\b.hs:13:7:
    The lambda expression `\ inp -> ...' has one argument,
    but its type `Parser Char' has none
    In the expression:
        \ inp
            -> case inp of {
                 [] -> []
                 (x : xs) -> [...] }
    In the definition of `item':
        item = \ inp
                   -> case inp of {
                        [] -> []
                        (x : xs) -> ... }
Failed, modules loaded: none.
2010/3/19 Stephen Tetley <stephen.tetley at gmail.com>:
> On 19 March 2010 04:35, 国平张 <zhangguoping at gmail.com> wrote:
>> Sorry to bother again. I just cannot figure out how it could compile.
>> I got compile errors.
>> Can someone point out what is right code to use a do notion to make a
>> Parser works.
>
> It looks like the p parser may have the wrong indentation - although
> this might be due to either your mail client or my client formatting
> wrongly:
>
> p :: Parser (Char,Char)
> p = do x <- item
>      item
>      y <- item
>      return (x,y)
>
>
> Try - with white space all aligned to the start character /x/ of the
> first statement in the do:
>
> p :: Parser (Char,Char)
> p = do x <- item
>       item
>       y <- item
>       return (x,y)
>
> Or with braces and semis:
>
> p :: Parser (Char,Char)
> p = do { x <- item
>       ; item
>       ; y <- item
>       ; return (x,y) }
>
> Best wishes
>
> Stephen
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list