On 7 dec 2007, at 23:51, Ryan Bloor wrote:
i am using hugs and the isDigit and anything 'is' doesn't work... they must have forgot to add them in! Does GHC work with them.
Yes, it's in base. Alternatively, you could write the functions yourself, they're not that hard.
p.s... that book looks fantastic... bette than the ones i got from the library; too specific. also... when and where do i use my predetermined types(EBool) and how...?
I think that is explained in the book. It's also not too hard to figure out yourself. A good strategy for writing Haskell programs in general is to think of the types first: what types should your functions have? Often this will help you in thinking of a good implementation.

The first thing you want to do, is parametrize the return-type of your parser. Instead of having type Parser = [(ETerm, String)] you probably want: type Parser a = String -> [(a, String)]. With that type, you could do something like:

parseDigit :: Parser Int
parseMany :: Parser a -> Parser [a]
parseOr :: Parser a -> Parser a -> Parser a

You can use these types to come up with the functions.

-chris



Ryan





> CC: haskell-cafe@haskell.org
> From: [EMAIL PROTECTED]
> To: [EMAIL PROTECTED]
> Subject: Re: [Haskell-cafe] parser
> Date: Fri, 7 Dec 2007 23:31:38 +0100
>
>
> On 7 dec 2007, at 22:55, Ryan Bloor wrote:
>
> > hi
> >
> > The thing is... it will be a simple parser really. The expressions
> > are already defined and we can't use parsec imports. Below is the
> > types I have.
> > I have a function that removes initial spaces from the start of a
> > string. A function that checks if a substring is part of another
> > string, which use the remove space function also.
> > The next function is: which uses the type:
> >
> > type Parser = String -> [(Expr,String)]
> So what does this type really mean? You give it a string, and it will
> return a list of (Expr, String). I would guess that the list is all
> possible outcomes, and the String in (Expr, String) is probably the
> rest of the parsed data. If you want to find a correct parse, you
> probably want to select the first element from that list that has an
> empty rest.
>
> You could write a parser that parses single digits:
>
> parseDigit :: String -> [(Int, String)]
> parseDigit (x:xs) | isDigit x = [read x]
>
> Of course you have to define the other cases for parseDigit. If you
> had a parseMany function that parses many things of the same type, you > could combine that with parseDigit to parse natural numbers. The other
> thing you are really going to need is a choice-operator. In your
> example, you want to parse terms that are either numbers or "term +
> term":
>
> parseTerm = parseNaturalNumber `parseOr` parseAddition
>
> It's probably best to read a good book or tutorial on parsers. There
> is an excellent textbook on grammars and parsing in Haskell [1], it
> probably explains exactly what you want.
>
> -chris
>
> [1] Johan Jeuring, Doaitse Swierstra: Grammars and Parsing: 
http://www.cs.uu.nl/docs/vakken/gont/diktaat.pdf
>
> >
> >
> > readExpression :: String -> Expr
> >
> > e.g. readExpression "True" = EBool True
> > e.g. readExpression "(23 + 67)" = EAdd (EInt 23) (EInt 67)
> >
> >
> > ------------------------
> > Types------------------------------------------
> >
> > data Type = TNone -- badly typed values
> > | TInt -- integer values
> > | TBool -- boolean values
> > deriving Show
> > data Expr = EInt {vInt :: Int} -- integer values
> > | EBool {vBool :: Bool} -- boolean values
> > | EAdd Expr Expr -- (e1 + e2)
> > | EMin Expr Expr -- (e1 - e2)
> > | EMul Expr Expr -- (e1 * e2)
> > | EAnd Expr Expr -- (e1 && e2)
> > | EOr Expr Expr -- (e1 || e2)
> > | ENot Expr -- not e1
> > | EComp Expr Expr -- (e1 == e2)
> > | ETest Expr Expr Expr -- if e1 then e2 else e3
> > | ENone -- badly formed expressions
> >
> >
> >
> >
> >
> >
> > > CC: haskell-cafe@haskell.org
> > > From: [EMAIL PROTECTED]
> > > To: [EMAIL PROTECTED]
> > > Subject: Re: [Haskell-cafe] parser
> > > Date: Fri, 7 Dec 2007 22:17:54 +0100
> > >
> > >
> > > On 6 dec 2007, at 18:06, Ryan Bloor wrote:
> > > > Can anyone advise me on how to check whether a string contains
> > ints,
> > > > chars, bools, etc....
> > > >
> > > > "2345 + 6767" shoudl give IntAdd (2345) (6767)
> > > > "2345" should give IntT 2345
> > > You need to write a parser. There are a lot of libraries that will > > > help you write a parser. One library that is often used for writing
> > > parsers in Haskell is called Parsec [1]. There's good
> > documentation on
> > > that site on how to use it. Parsec is already included in you
> > > distribution. Good luck!
> > >
> > > -chris
> > >
> > > [1]: http://legacy.cs.uu.nl/daan/parsec.html
> >
> >
> > Get closer to the jungleā€¦ I'm a Celebrity Get Me Out Of Here!
>


Can you guess the film? Search Charades!

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

Reply via email to