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

国平张 zhangguoping at gmail.com
Wed Mar 17 11:35:08 EDT 2010


Thanks very much. It works!
I just wonder if you can help me to define a Monad to make "do" notion
works :-) ?

I know it is bothering, but I just ever tried to define a Monad,
failed either. What I did to define a Monad was:

instance Monad Parser where
   return v = (\inp->[(v,inp)])
   f >>= g =  = (\inp -> case parse p inp of
                                    [] -> []
                                    [(v,out)]->parse (f v) out)

But it did not compile :-(.

Best Regards,
Guo-ping


2010/3/17 Michael Snoyman <michael at snoyman.com>:
> Hi,
> You can only use do notation if you actually create an instance of Monad,
> which for Parser you haven't done. To continue as is, replace the first line
> with:
> import Prelude hiding (return, fail, (>>=))
> and the p function with
> p = item >>= \x -> item >>= \_ -> item >>= \y -> return (x, y)
> I've basically de-sugared the do-notation you wrote and hid the >>= from
> Prelude so that the one you declared locally is used.
> Michael
> On Tue, Mar 16, 2010 at 9:09 PM, 国平张 <zhangguoping at gmail.com> wrote:
>>
>> Hi,
>>
>> I am a beginner for haskell. I was stuck with a sample of "programming
>> in haskell". Following is my code:
>> ---------------------------------------------------------------------
>> import Prelude hiding (return, fail)
>>
>> type Parser a = (String->[(a,String)])
>>
>> return :: a -> Parser a
>> return v = (\inp->[(v,inp)])
>>
>> item :: Parser Char
>> item = \inp -> case inp of
>>                   [] -> []
>>                   (x:xs) -> [(x,xs)]
>> failure :: Parser a
>> failure = \inp -> []
>>
>> parse :: Parser a->(String->[(a,String)])
>> parse p inp = p inp
>>
>> (>>=) :: Parser a -> (a -> Parser b) -> Parser b
>> p >>= f  = (\inp -> case parse p inp of
>>                                    [] -> []
>>                                    [(v,out)]->parse (f v) out)
>>
>> p :: Parser (Char,Char)
>> p = do x <- item
>>      item
>>      y <- item
>>      return (x,y)
>> ---------------------------------------------------------------------
>>
>> But it cannot be loadded by Hug, saying:
>>
>> Couldn't match expected type `Char'
>>      against inferred type `[(Char, String)]'
>>  Expected type: [((Char, Char), String)]
>>  Inferred type: [(([(Char, String)], [(Char, String)]), String)]
>> In the expression: return (x, y)
>> In the expression:
>>   do x <- item
>>      item
>>      y <- item
>>      return (x, y)
>>
>> -------------------------------------------------------------------
>>
>> I googled and tried a few days still cannot get it compiled, can
>> someone do me a favor to point out what's wrong with it :-) ?
>> _______________________________________________
>> 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