Re: [Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread Stephen Tetley
Hi Günther


I suspect the problem you were having is that there are various
'parsers' (more correctly 'parser types') defined in
Text.ParserCombinators.UU.Parsing and the code you had in your running
example didn't always have enough information to allow GHC to pick a
particular one.

The /test/ function in Examples demands the parser to be of type 'P_m
state a' [1], so if you were running your parsers with /test/ in your
main function this would be give the parsers a concrete, inferable
type (if you hadn't given then a type signature). Once you comment out
main, the parsers have a more general type than 'P_m state a', which
can't be inferred due to class constraints.

Maybe the 'haskeller's inituition' in this instance is to define the
type signatures and the functions at the same time, admittedly this
can be difficult for functions with heavy use of type classes.

Best wishes

Stephen


[1] I'm afraid I don't know the intricacies of the particular types in
the new UU parsing library, until this morning I'd only used the
previous version in uulib.


2009/5/31 Guenther Schmidt :
> Dear Doaitse,
>
> thank you very much for your help.
>
>>
>> I am curious to know what made you go wrong with the tutorial, and caused
>> that you could not find the solution below?
>>
> Well let's first agree that I'm not very bright. I hate to admit it, but
> it's a simple fact ;-).
>
> Second let's agree that the uu-parsinglib is a *very* sophisticated beast, I
> have not seen anything else like it out there, my sincere congratulations
> for it. Thirdly the tutorial is also a very sophisticated beast, and
> forthly, well just see point 1 :-).
>
> And I just figured out why I was unable to write even that simple parser.
>
> The code you sent me works just fine, I copied and pasted it, no problems.
>
> But, as soon as I comment out the "main" function the type checker
> complains, because now the ghci's type checker can no longer infer the types
> of pDate or pDot. And this is exactly what happened. I kept getting error
> messages from ghci, eventhough I had defined my parsers possible correctly,
> but, *minus* the type signatures *and* minus any main function that called
> it.
>
> In hindsight I realize that this is a trap I have walked into many times
> before, I guess I still have not acquired a Haskellers intuition.
>
> I promise to do better next time :)
>
> Günther
>
>
> ___
> 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] Re: Lazy Parsing

2009-05-31 Thread Malcolm Wallace
It is my pleasure to announce that after 5 days of experimenting  
with uu-parsinglib I have absolutely no clue, whatsoever, on how to  
use it.


I do not even manage to write a parser for even a mere digit or a  
simple character.


I don't know whether you will be willing to change over to polyparse  
library, but here are some hints about how you might use it.


Given that you want the input to be a simple character stream, rather  
than use a more elaborate lexer, the first thing to do is to  
specialise the parser type for your purposes:


> type TextParser a = Parser Char a

Now, to recognise a "mere digit",

> digit :: TextParser Char
> digit = satisfy Char.isDigit

and for a sequence of digits forming an unsigned integer:

> integer :: TextParser Integer
> integer = do ds <- many1 digit
>  return (foldl1 (\n d-> n*10+d)
> (map (fromIntegral.digitToInt) ds))
>   `adjustErr` (++("expected one or more digits"))

I mean I'd like to be able to turn "12.05.2009" into something like  
(12, 5, 2009) and got no clue what the code would have to look like.  
I do know almost every variation what the code must not look like :).


> date = do a <- integer
>   satisfy (=='.')
>   b <- integer
>   satisfy (=='.')
>   c <- integer
>   return (a,b,c)

Of course, that is just the standard (strict) monadic interface used  
by many combinator libraries.  Your original desire was for lazy  
parsing, and to achieve that, you must move over to the applicative  
interface.  The key difference is that you cannot name intermediate  
values, but must construct larger values directly from smaller ones by  
something like function application.


> lazydate = return (,,) `apply` integer `discard` dot
>`apply` integer `discard` dot
>`apply` integer
>where dot = satisfy (=='.')

The (,,) is the constructor function for triples.  The `discard`  
combinator ensures that its second argument parses OK, but throws away  
its result, keeping only the result of its first argument.


Apart from lazy space behaviour, the main observable difference  
between "date" and "lazydate" is when errors are reported on incorrect  
input.  For instance:


  > fst $ runParser date "12.05..2009"
  *** Exception: In a sequence:
  Parse.satisfy: failed
  expected one or more digits

  > fst $ runParser lazydate "12.05..2009"
  (12,5,*** Exception: In a sequence:
  Parse.satisfy: failed
  expected one or more digits

Notice how the lazy parser managed to build the first two elements of  
the triple, whilst the strict parser gave no value at all.


I know that the error messages shown here are not entirely  
satisfactory, but they can be improved significantly just by making  
greater use of the `adjustErr` combinator in lots more places (it is  
rather like Parsec's ).  Errors containing positional information  
about the input can be constructed by introducing a separate lexical  
tokenizer, which is also not difficult.


Regards,
Malcolm

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


Re: [Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread Stephen Tetley
Hi Günther

The code below should work for your simple example, provided it hasn't
lost formatting when I pasted it in to the email.

I was a bit surprised that there is no pSatisfy in this library, but
there are parsers for digits, lower case, upper case letters etc. in
the Examples module that would otherwise be achieved with pSatisfy.

Best wishes

Stephen



{-# LANGUAGE FlexibleContexts   #-}

module Demo1 where

import Text.ParserCombinators.UU.Examples
import Text.ParserCombinators.UU.Parsing


-- here's a simple character '@' parser
pAtSym :: Symbol p Char Char => p Char
pAtSym = pSym '@'

test_simple_char  = test pAtSym "@"
test_simple_char2 = test pAtSym "@"


-- pDigit is supplied in Text.ParserCombinators.UU.Examples
test_any_digit= test pDigit "6"

-- pNatural is supplied in Text.ParserCombinators.UU.Examples
-- It looks like the most likely candidate to parse a
-- sequence of digits...

test_natural   = test pNatural "1234"

--  ... and it is!

-- parse a date "12.05.2009" as a triple (Int,Int,Int)
pDateTriple :: (Symbol p (Char,Char) Char, Applicative p, ExtApplicative p st,
Provides st Char Char)
=> p (Int,Int,Int)
pDateTriple = (,,) <$> pNatural <* pDot <*> pNatural <* pDot <*> pNatural

pDot :: (Symbol p Char Char, Applicative p) => p [Char]
pDot = lift <$> pSym '.'

test_date = test pDateTriple "12.05.2009"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe