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

2010-03-19 Thread Stephen Tetley
On 19 March 2010 04:35, 国平张 zhangguop...@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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-19 Thread 国平张
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.tet...@gmail.com:
 On 19 March 2010 04:35, 国平张 zhangguop...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


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

2010-03-19 Thread Stephen Tetley
2010/3/19 国平张 zhangguop...@gmail.com:
 Sorry. The same error, This is new stuff.

Ah indeed - I didn't spot that one as I only read the code rather than ran it.

With the change the parser type to use /newtype/ all the primitive
parsers have to be encoded inside the newtype's constructor
(primitive parsers being ones that have to look directly at the input
stream).

item :: Parser Char
item = Parser $ \inp - case inp of
 [] - []
 (x:xs) - [(x,xs)]

Or in a more prosaic style

item :: Parser Char
item = Parser (\inp - case inp of
[] - []
(x:xs) - [(x,xs)])



This is slightly tiresome. Fortunately once you have defined a small
set of primitive parsers, many more parsers can be derived by
combining the primitives rather than looking at the input stream -
this is the power of the monadic style. The p parser you defined with
the do ... notation is one such derived parser.

Best wishes

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


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

2010-03-19 Thread 国平张
Sorry :-). I am using Hugs, anything I did wrong ?

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 = Parser (\inp - case inp of
   [] - []
   (x:xs) - [(x,xs)])

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

C:\b.hs:12:7: Not in scope: data constructor `Parser'
Failed, modules loaded: none.
Prelude

在 2010年3月19日 下午6:01,Stephen Tetley stephen.tet...@gmail.com 写道:
 2010/3/19 国平张 zhangguop...@gmail.com:
 Sorry. The same error, This is new stuff.

 Ah indeed - I didn't spot that one as I only read the code rather than ran it.

 With the change the parser type to use /newtype/ all the primitive
 parsers have to be encoded inside the newtype's constructor
 (primitive parsers being ones that have to look directly at the input
 stream).

 item :: Parser Char
 item = Parser $ \inp - case inp of
 [] - []
 (x:xs) - [(x,xs)]

 Or in a more prosaic style

 item :: Parser Char
 item = Parser (\inp - case inp of
[] - []
(x:xs) - [(x,xs)])



 This is slightly tiresome. Fortunately once you have defined a small
 set of primitive parsers, many more parsers can be derived by
 combining the primitives rather than looking at the input stream -
 this is the power of the monadic style. The p parser you defined with
 the do ... notation is one such derived parser.

 Best wishes

 Stephen

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


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

2010-03-19 Thread Jochem Berndsen
国平张 wrote:
 Sorry :-). I am using Hugs, anything I did wrong ?
 

 item :: Parser Char
 item = Parser (\inp - case inp of

^^^ the second Parser should be a P, which is a data constructor.

Cheers, Jochem

-- 
Jochem Berndsen | joc...@functor.nl
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-19 Thread Stephen Tetley
Hi

I'm sorry about that, I should have check the last message runs, but I
typed it from a computer that I don't develop on. The code below
should run as I've tested it this time.



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 = P (\inp - case inp of
[] - []
(x:xs) - [(x,xs)])

p :: Parser (Char,Char)
p = do { x - item
  ; item
  ; y - item
  ; return (x,y) }



For the record - the error in the last code I sent was that the
newtype Parser has a different constructor name /P/ to its type name
/Parser/ - I hadn't spotted that in the untested code.

Apologies again

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


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

2010-03-18 Thread 国平张
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.

Thanks in advance.

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)
-
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-17 Thread 国平张
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 mich...@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, 国平张 zhangguop...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


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


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

2010-03-17 Thread Daniel Fischer
Am Mittwoch 17 März 2010 16:35:08 schrieb 国平张:
 Thanks very much. It works!
 I just wonder if you can help me to define a Monad to make do notion
 works :-) ?

To make an instance of Monad, you must create a new datatype, for example

module Parse where

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 (\_ - [])


 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 mich...@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, 国平张 zhangguop...@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@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe

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

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


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

2010-03-16 Thread 国平张
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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2010-03-16 Thread Michael Snoyman
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, 国平张 zhangguop...@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@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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