status of rebindable syntax for arrows

2014-10-14 Thread S. Doaitse Swierstra


The GHC manual already for quite a number of version states:

• Arrow notation (see Section 7.17, “Arrow notation ”) uses whatever 
arr, (), first, app, (|||) and loop functions are in scope. 
 But unlike the other constructs, the types of these functions must 
match the Prelude types very closely. Details are in flux; if you want to use 
this, ask! 

When using this feature we get the error:

Var/Type length mismatch: 
   [s{tv aVL} [tv]]
   []
ghc: panic! (the 'impossible' happened)
 (GHC version 7.8.3 for x86_64-apple-darwin):
tcTyVarDetails s{tv aVL} [tv]

Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug;

So our question is whether we should really report this as a bug, and/or what 
we can do about this. 

Thanks for your help,

Doaitse





___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


question about GADT's and error messages

2014-05-13 Thread S. Doaitse Swierstra
Given the following code:

{-# LANGUAGE GADTs #-}
data Any a where
AInt :: Int - Any Int

-- demo 1 does not compile
{-
demo1 a = do case a of
(AInt i) - print i

 Couldn't match expected type ‘t’ with actual type ‘IO ()’
   ‘t’ is untouchable
 inside the constraints (t1 ~ Int)
 bound by a pattern with constructor
AInt :: Int - Any Int,
  in a case alternative
 at /Users/doaitse/TryHaskell/TestGADT.hs:6:17-22
   ‘t’ is a rigid type variable bound by
   the inferred type of demo1 :: Any t1 - t
   at /Users/doaitse/TryHaskell/TestGADT.hs:5:1
 Relevant bindings include
   demo1 :: Any t1 - t
 (bound at /Users/doaitse/TryHaskell/TestGADT.hs:5:1)
 In the expression: print i
 In a case alternative: (AInt i) - print i
Failed, modules loaded: none.
-}


-- all the following go through without complaints:

a = AInt 3
demo2 = do case a of
(AInt i) - print i

demo3 :: IO ()
demo3 = do case a of
(AInt i) - print i


demo4 = do case AInt 3 of
(AInt i) - print i

demo5 :: Any Int - IO ()
demo5 a = do case a of
(AInt i) - print i

I do not see why the error message in demo1 arises. It claims it can't match 
some t with the type IO (), but when I tell that the result is IO () it can?
I think at least the error message is confusing, and not very helpful. I would 
have in no way been able to get the clue that add a type signature as in the 
case of demo5 would solve the problem.

What am I overlooking?

Doaitse


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell-cafe] Haddock GSOC project progress

2013-08-05 Thread S. Doaitse Swierstra
Why not use uu-parsinglib, which will tell you what is wrong and nevertheless 
will continue parsing? 

Currently Jacco Krijnen is working on an extensible version of Pandoc, based on 
the AspectAG and the Murder packages, so you can define your own plugins for 
syntax and semantics.

  Doaitse Swierstra


On Aug 1, 2013, at 1:14 , Richard A. O'Keefe o...@cs.otago.ac.nz wrote:

 
 On 31/07/2013, at 8:16 PM, Simon Hengel wrote:
 
 * There is no such thing as a parse error in Markdown, and I think we
  should try to make this true for Haddock markup, too
 
 It is very far from clear that this is a virtue in Markdown.
 In trying to learn Markdown, I found it an excessively tiresome
 defect.  Whenever I was trying to learn how to produce some
 combination of effects, instead of Markdown telling me
 at THIS point you had something I wasn't expecting, it would
 just produce incorrect output, defined as anything other than
 what I intended.  It also meant that two different Markdown
 processors would accept the same text silently but do different
 things with it.
 
 This is one of the reasons I won't use Markdown.
 
 
 ___
 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] simple parsec question

2013-03-05 Thread S. Doaitse Swierstra
Maybe this is something you do not even want to use a parser combinator library 
for. The package

http://hackage.haskell.org/packages/archive/list-grouping/0.1.1/doc/html/Data-List-Grouping.html

contains a function breakBefore, so you can write

main = do inp - readFile ...
 let result = map mkSection . breakBefore ((= ':').last)). 
lines $ inp

mkSection (l:ll) = Section (Top l) (Contents ll)

Doaitse


On Mar 3, 2013, at 16:44 , Immanuel Normann immanuel.norm...@googlemail.com 
wrote:

 Hi,
 
 I am trying to parse a semi structured text with parsec that basically should 
 identify sections. Each section starts with a headline and has an 
 unstructured content - that's all. For instance, consider the following 
 example text (inside the dashed lines):
 
 ---
 
 top 1:
 
 some text ... bla
 
 top 2:
 
 more text ... bla bla
 
 
 ---
 
 This should be parsed into a structure like this:
 
 [Section (Top 1) (Content some text ... bla), Section (Top 1) (Content 
 more text ... bla)]
 
 Say, I have a parser headline, but the content after a headline could be 
 anything that is different from what headline parses.
 How could the section parser making use of headline look like?
 My idea would be to use the manyTill combinator, but I dont find an easy 
 solution.
 
 Many thanks for any hint
 
 Immanuel
 ___
 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] Parser left recursion

2013-02-21 Thread S. Doaitse Swierstra
As mentioned before, the way to handle this specific problem is to use either  
the pChainl or pChainr parser combinators, as e.g. found on:

http://hackage.haskell.org/packages/archive/uu-parsinglib/2.7.4.1/doc/html/Text-ParserCombinators-UU-Derived.html

and many similar libraries. So one can write:

pExpr = pChainl ( (+) $ pSym ' ')) pFactor
pFactor = iI '(' pExpr ')' Ii | pInteger | pIdentifier 

What is even nicer is that one can easily extend this to deal with many 
different operators:

pExpr = foldr nextop [((+),'+'), ((*), '*'))] pGactor
where nextop (sem,sym) = pChainl sem $ pSym sym))

It is obvious how to extend this further into operators with the same priority 
or being right associative. See furthermore:

@inproceedings{Fokker95:0,
  title = {Functional Parsers},
  author = {Jeroen Fokker},
  year = {1995},
  tags = {parsing},
  researchr = {http://dutieq.st.ewi.tudelft.nl/publication/Fokker95%3A0},
  cites = {0},
  citedby = {0},
  pages = {1-23},
  booktitle = {Advanced Functional Programming, First International Spring 
School on Advanced Functional Programming Techniques, Båstad, Sweden, May 
24-30, 1995, Tutorial Text},
  editor = {Johan  Jeuring and Erik Meijer},
  volume = {925},
  series = {Lecture Notes in Computer Science},
  publisher = {Springer},
  isbn = {3-540-59451-5},
}

Most left recursion stems from the fact that conventional CFG notation is 
sufficient, but unfortunately not ideally suited, to express oft occurring 
patterns. This is where parser combinators come in: they allow one to express 
what one wants to say instead of having to encode it using recursion, etc.

If you have a really nasty grammar where left recursion removal by hand would 
ruin your grammar, you may use a transform like the LeftCornerTransform as used 
e.g. in the ChristmasTree package, which removes the problem of exponential 
time behaviour of reading Haskell data types with infix operators. See: 
http://hackage.haskell.org/package/ChristmasTree-0.2, and which has been 
described in:

@article{DBLP
:journals/entcs/BaarsSV10,
  author= {Arthur I. Baars and
   S. Doaitse Swierstra and
   Marcos Viera},
  title = {Typed Transformations of Typed Grammars: The Left Corner
   Transform},
  journal   = {Electr. Notes Theor. Comput. Sci.},
  volume= {253},
  number= {7},
  year  = {2010},
  pages = {51-64},
  ee= {http://dx.doi.org/10.1016/j.entcs.2010.08.031},
  bibsource = {DBLP, http://dblp.uni-trier.de}
}

Doaitse



On Feb 20, 2013, at 8:13 , Martin Drautzburg martin.drautzb...@web.de wrote:

 Hello all,
 
 this was previously asked on haskell-beginners, but only partially answered.
 
 As an exercise I am writing a parser roughly following the expamples in 
 Graham 
 Hutton's book. The language contains things like:
 
 data Exp = Lit Int -- literal integer
 | Plus Exp Exp
 
 My naive parser enters an infinite recursion, when I try to parse 1+2. I do 
 understand why:
 
 hmm, this expression could be a plus, but then it must start with an 
 expression, lets check. 
 
 and it tries to parse expression again and again considers Plus.
 
 Twan van Laarhoven told me that:
 
 Left-recursion is always a problem for recursive-descend parsers.
 
 and suggested to do something like:
 
parseExp = do
  lit - parseLit
  pluses - many (parsePlusToken * parseLit)
  return (combinePlusesWithLit lit pluses)
 
combinePlusesWithLit = foldr Plus -- or foldl
 
 This indeed does the trick, but only when the first token is a Lit (literal 
 integer). 
 
 I then added the possibility to optionally put things in parentheses. But 
 then  
 I cannot parse (1+2)+3. The original code fails, because (1+2) is not a 
 Lit and when I allow an expression as the first argument to + I get 
 infinite 
 recursion again.
 
 I am generally confused, that saying a plus expression is an integer 
 followed 
 by many plus somethings is not what the language says. So this requires a 
 lot of paying attention to get right. I'd much rather say a plus 
 expression 
 is two expressions with a '+' in between.
 
 I do know for sure, that it is possible to parse (1+2)+3 (ghci does it just 
 fine). But I seem to be missing a trick.
 
 Can anyone shed some light on this?
 
 -- 
 Martin
 
 ___
 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: In opposition of Functor as super-class of Monad

2012-10-24 Thread S. Doaitse Swierstra
There are very good reasons for not following this road; indeed everything 
which is a Monad can also be made an instance of Applicative. But more often 
than not we want to have a more specific implementation. Because Applicative is 
less general, there is in general more that you can do with it.

An analogue is the relation between regular grammars and context-free grammars; 
indeed, once we have the latter concept we might argue that we do not need the 
first one any more. But if we know that something is in the first category we 
can do all kins of nice things which we cannot do with conxet-free grammars, 
such as constructing a finite state machine for recognising sentences.

You proposal would introduce overlapping instances is such cases where we want 
to give a ``better'' implementation in case we know we are dealing with the 
more restricted case.

I have explained this phenomenon for the first time in:


@inproceedings{SwieDupo96,
Author = {Swierstra, S. D. and Duponcheel, L.},
Booktitle = {Advanced Functional Programming},
Date-Added = {2009-01-04 17:21:54 +0100},
Date-Modified = {2009-01-04 17:21:54 +0100},
Editor = {Launchbury, John and Meijer, Erik and Sheard, Tim},
Pages = {184-207},
Publisher = {Springer-Verlag},
Series = {LNCS-Tutorial},
Title = {Deterministic, Error-Correcting Combinator Parsers},
Urlpdf = 
{http://www.cs.uu.nl/people/doaitse/Papers/1996/DetErrCorrComPars.pdf},
Volume = {1129},
Year = {1996}}

If you look at the uu-parsinglib library you will see that the Applicative 
instance of the parsers used there is definitely more involved that what you 
can do with the monadic interface. Your proposal would ruin this library.

Unless we have things like e.g. named instances, the possibility to choose 
between overlapping instances, etc. I think we should leave things the way they 
are; the only reason I see for having superclasses is to be able to use 
functions from those classes in the default implementations of functions in the 
new class, and to group functionality coming from several classes.

 Doaitse












On Oct 24, 2012, at 10:01 , Petr P petr@gmail.com
 wrote:

  Hi,
 
 I was thinking lately about the well known problem that Monad is
 neither Functor nor Applicative. As I understand, it is caused by some
 historical issues. What I like about Haskell is that it allows to
 describe very nicely what different objects actually are - something
 that I find very important for programming. And this issue violates
 this principle.
 
 This has been discussed here more than year ago in
 http://www.haskell.org/pipermail/haskell-prime/2011-January/003312.html
 :
 
 On 1/4/11 11:24, oleg at okmij.org wrote:
 I'd like to argue in opposition of making Functor a super-class of
 Monad. I would argue that superclass constraints are not the right
 tool for expressing mathematical relationship such that all monads are
 functors and applicatives.
 
 Then argument is practical. It seems that making Functor a superclass
 of Monad makes defining new monad instances more of a chore, leading
 to code duplication. To me, code duplication is a sign that an
 abstraction is missing or misused.
 ...
 
 The main objections were that it would break existing code and that it
 would lead to code duplication. The former is serious, the second can
 be easily solved by standard Haskell, since one can define
 
 instance Applicative ... where
pure   = return
(*)  = ap
 instance Functor ... where
fmap   = liftM
 
 To address the first objection:
 AFAIK nobody mentioned the Default superclass instances proposal:
 http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
 To give an example how it would work:
 
class Applicative f = Monad f where
  (=) :: f a - (a - f b) - f b
  ...
  instance Applicative f where
ff * fs = ff = \ f - fs = \ s - return (f s)
...
 
 This says that if somebody defines an instance of Monad it
 automatically becomes an instance of Applicative as defined in the
 nested instance block. So there is no need to define
 Applicative/Functor explicitly, making existing code work.
 
 Implementing this proposal would allow making Monad to extend Functor
 and Applicative without breaking existing code. Moreover, this would
 simplify other things, for example it would be possible to define an
 instance of Traversable and the instances for Functor and Foldable
 would be defined implicitly using fmapDefault and foldMapDefault. I'm
 sure there are many other cases where splitting type classes into a
 more fine-grained hierarchy would be beneficial, and the main reason
 against it is simply not to break compatibility with existing code.
 
 IMHO this would be worthwhile to consider for some future revision of Haskell.
 
  Best regards,
  Petr Pudlak
 
 ___
 Haskell-prime mailing list
 

Re: [Haskell] Compositional Compiler Construction, Oberon0 examples available

2012-08-21 Thread S. Doaitse Swierstra

On Aug 21, 2012, at 13:46 , Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 Doaitse Swierstra wrote:
 Heinrich Apfelmus wrote:
 I have a small question: Last I remember, you've mainly been using
 your UUAGC preprocessor to write attribute grammars in Haskell,
 especially for UHC. Now that you have first-class attribute
 grammars in Haskell (achievement unlocked), what do you intend to
 do with the preprocessor? How do these two approaches compare at
 the moment and where would you like to take them?
 On the page http://www.cs.uu.nl/wiki/bin/view/Center/CoCoCo there is
 a link (http://www.fing.edu.uy/~mviera/papers/VSM12.pdf) to a paper
 we presented at LDTA (one of the ETAPS events) this spring. It
 explains how UUAGC can be used to generate first class compiler
 modules.
 We have also a facility for grouping attributes, so one can trade
 flexibility for speed. The first class approach stores list of
 attributes as nested cartesian products, access to which a clever
 compiler might be able to optimize. This however would correspond  a
 form of specialisation, so you can hardly say that we have really
 independent modules; as always global optimisation is never
 compositional). From the point of view of the first class approach
 such grouped non-termionals are seen as a single composite
 non-terminal.
 
 Ah, I see. So the custom syntax offered by UUAGC is still appreciated, but 
 you now intend to compile it to first-class attribute grammars instead of 
 bare metal Haskell. Makes sense. Thanks!

It is not much that it is our intention, but it is an easy way to make an 
existing compiler extensible. The main (fixed) part of the compiler is 
constructed in the old way from an UUAGC description, and those attributes 
are grouped (and quite a bit more efficient). On top of this you can define 
extra attributes and computations, which plug in to the old system.

Notice that there is a main difference between the two approaches is that the 
uuagc route gives you fast compilers, because we can analyse the grammar, and  
generate efficient tree walking evaluators, whereas the first-class approach 
gives you great flexibility and the possibility to abstract from common 
patterns for which others prefer to get lost in stacks of monads, or find out 
that monads do not work at all since they cannot feed back information into a 
computation easily.


 Doaitse






 
 
 Best regards,
 Heinrich Apfelmus
 
 --
 http://apfelmus.nfshost.com
 
 
 ___
 Haskell mailing list
 Haskell@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell


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


Re: [Haskell-cafe] [Haskell] Compositional Compiler Construction, Oberon0 examples available

2012-08-21 Thread S. Doaitse Swierstra

On Aug 21, 2012, at 13:46 , Heinrich Apfelmus apfel...@quantentunnel.de wrote:

 Doaitse Swierstra wrote:
 Heinrich Apfelmus wrote:
 I have a small question: Last I remember, you've mainly been using
 your UUAGC preprocessor to write attribute grammars in Haskell,
 especially for UHC. Now that you have first-class attribute
 grammars in Haskell (achievement unlocked), what do you intend to
 do with the preprocessor? How do these two approaches compare at
 the moment and where would you like to take them?
 On the page http://www.cs.uu.nl/wiki/bin/view/Center/CoCoCo there is
 a link (http://www.fing.edu.uy/~mviera/papers/VSM12.pdf) to a paper
 we presented at LDTA (one of the ETAPS events) this spring. It
 explains how UUAGC can be used to generate first class compiler
 modules.
 We have also a facility for grouping attributes, so one can trade
 flexibility for speed. The first class approach stores list of
 attributes as nested cartesian products, access to which a clever
 compiler might be able to optimize. This however would correspond  a
 form of specialisation, so you can hardly say that we have really
 independent modules; as always global optimisation is never
 compositional). From the point of view of the first class approach
 such grouped non-termionals are seen as a single composite
 non-terminal.
 
 Ah, I see. So the custom syntax offered by UUAGC is still appreciated, but 
 you now intend to compile it to first-class attribute grammars instead of 
 bare metal Haskell. Makes sense. Thanks!

It is not much that it is our intention, but it is an easy way to make an 
existing compiler extensible. The main (fixed) part of the compiler is 
constructed in the old way from an UUAGC description, and those attributes 
are grouped (and quite a bit more efficient). On top of this you can define 
extra attributes and computations, which plug in to the old system.

Notice that there is a main difference between the two approaches is that the 
uuagc route gives you fast compilers, because we can analyse the grammar, and  
generate efficient tree walking evaluators, whereas the first-class approach 
gives you great flexibility and the possibility to abstract from common 
patterns for which others prefer to get lost in stacks of monads, or find out 
that monads do not work at all since they cannot feed back information into a 
computation easily.


 Doaitse






 
 
 Best regards,
 Heinrich Apfelmus
 
 --
 http://apfelmus.nfshost.com
 
 
 ___
 Haskell mailing list
 hask...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell


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


[Haskell] Summer school on Applied Functional Programming at Utrecht University; deadline for registration May 15

2011-04-18 Thread S. Doaitse Swierstra
Again we will teach an Applied Functional Programming Summer in Haskell 
school this year at Utrecht University. In the previous two occasions students 
were all very happy with the school and we plan to repeat this success this 
year.

The intended audience are prospective master students who have been in contact 
with Functional Programming, e.g. by taking a general course on programming 
languages, and want to learn more about Haskell and its typical programming 
patterns. In the previous two years we have taught an introductory part 
(advanced bachelor level), an advanced part (beginning master level) and a 
shared part for both groups. Topics covered are, besides some examples of 
domain specific languages, also monads, monad transformers, arrows, parser 
combinators and self-analysing programs, underlying principles, type 
inferencing, etc. Half of the course time is spent on a larger programming 
exercise; you can also come with a problem of your own if you want, and get 
help from the Utrecht University Software Technology group in finding the 
proper Haskell idioms, tools and libraries, for solving it.

Important links: 
  -- our own page where we supply information based on questions asked 
http://www.cs.uu.nl/wiki/bin/view/USCS2011/WebHome
  -- the poster you can print and hang somewhere (why not your office door): 
http://www.cs.uu.nl/wiki/pub/USCS2011/WebHome/USCSpos11.pdf 
  -- the official summerschool site where you can register: 
http://www.utrechtsummerschool.nl/index.php?type=coursescode=H9

Furthermore we ask for your cooperation to bring this announcement under the 
attention of potential participants.

 Best,
 Doaitse Swierstra

PS: apologies if you get this mail more than once


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


[Haskell-cafe] Summer school on Applied Functional Programming at Utrecht University; deadline for registration May 15

2011-04-18 Thread S. Doaitse Swierstra
Again we will teach an Applied Functional Programming Summer in Haskell 
school this year at Utrecht University. In the previous two occasions students 
were all very happy with the school and we plan to repeat this success this 
year.

The intended audience are prospective master students who have been in contact 
with Functional Programming, e.g. by taking a general course on programming 
languages, and want to learn more about Haskell and its typical programming 
patterns. In the previous two years we have taught an introductory part 
(advanced bachelor level), an advanced part (beginning master level) and a 
shared part for both groups. Topics covered are, besides some examples of 
domain specific languages, also monads, monad transformers, arrows, parser 
combinators and self-analysing programs, underlying principles, type 
inferencing, etc. Half of the course time is spent on a larger programming 
exercise; you can also come with a problem of your own if you want, and get 
help from the Utrecht University Software Technology group in finding the 
proper Haskell idioms, tools and libraries, for solving it.

Important links: 
  -- our own page where we supply information based on questions asked 
http://www.cs.uu.nl/wiki/bin/view/USCS2011/WebHome
  -- the poster you can print and hang somewhere (why not your office door): 
http://www.cs.uu.nl/wiki/pub/USCS2011/WebHome/USCSpos11.pdf 
  -- the official summerschool site where you can register: 
http://www.utrechtsummerschool.nl/index.php?type=coursescode=H9

Furthermore we ask for your cooperation to bring this announcement under the 
attention of potential participants.

 Best,
 Doaitse Swierstra

PS: apologies if you get this mail more than once


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


Re: [Haskell-cafe] DSL for task dependencies

2011-04-07 Thread S. Doaitse Swierstra
Eelco Dolstra has written a thesis about something like that. Unfortunataly not 
in Haskell.

See http://nixos.org/

 Doaitse

On 17 mrt 2011, at 21:00, Serge Le Huitouze wrote:

 Hi Haskellers!
 
 I think I remember reading a blog post or web page describing a
 EDSL to describe tasks and their dependencies a la make.
 
 Can anyone point me to such published material?
 
 Thanks in advance.
 
 --serge
 
 ___
 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] A opportunity to lern (parsing huge binary file)

2011-03-19 Thread S. Doaitse Swierstra
The uu-parsing library support every ata type that is an instance of  
Data.Listlike 
(http://hackage.haskell.org/packages/archive/ListLike/3.0.1/doc/html/Data-ListLike.html#t:ListLike)
 and thus input from Data.Bytestring.Lazy.

A very small starting program can be found below. Note that here we ask for the 
error correction during parsin at the end of the processing; that is probably 
something you do not want to do, unless you only keep a very small part of the 
input in the result. The parsers are online, do not hang on to the input and 
thus you essentially only access and keep the part of the result you are 
interested in.

We find it a great help to have the error correction at hand since it makes it 
a lot easier to debug your parser. Here we just recognise any list of Word8's.

 Doaitse





{-# LANGUAGE MultiParamTypeClasses #-}
module ReadLargeBinaryFile where

import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.BasicInstances
import Data.Word
import Data.ByteString.Lazy (ByteString,readFile)
import Prelude hiding (readFile)


type BS_Parser a = P (Str Word8 ByteString Integer) a

instance IsLocationUpdatedBy Integer Word8 where
   advance pos _ = pos + 1

p:: BS_Parser [Word8]
p =  pList (pSatisfy (const True) (Insertion  0 0) )
main filename = doinp - readFile filename
  let r@(a, errors) =  parse ( (,) $ p * pEnd) 
(createStr 0 inp)
  putStrLn (--  Result:  ++ show a)
  if null errors then  return ()
 else  do putStr (--  Correcting steps: 
\n)
  show_errors errors
  putStrLn -- 
  where show_errors :: (Show a) = [a] - IO ()
show_errors = sequence_ . (map (putStrLn . show))



interface and that exists for Data. 
On 10 mrt 2011, at 16:36, Skeptic . wrote:

 
 
 Hi,
 I finally have an opportunity to learn Haskell (I'm a day-to-day Java 
 programmer, but I'm also at ease with Scheme), parsing a huge (i.e. up to 50 
 go) binary file. The encoding is very stable, but it's not a flat struct 
 array (i.e. it uses flags). 
 Different outputs (i.e. text files) will be needed, some unknown at this 
 time. 
 Sounds to me a perfect real-world task to see what Haskell can offer.
 
 Any suggestions at how to structure the code or on which packages to look at 
 is welcome.
 
 Thanks. 
 ___
 Haskell mailing list
 Haskell@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell


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


Re: [Haskell-cafe] Wanted: composoable parsers from haskell-src-exts

2011-03-18 Thread S. Doaitse Swierstra
Although this may need a bit of work you might take the parsing code form the 
Utrecht Haskell Compiler (http://www.cs.uu.nl/wiki/bin/view/UHC/Download), 
which uses the uulib parser combinators. They are top-down parsers, and thus 
can be used to parse any prefix given a specific parser, i.e. given the 
non-terminal which describes the prefix.

The UHC contains a separate scanner, since the layout rule makes scannerless 
parsing very complicated.

The uulib should be easily replaced with the newer uu-parsing lib, but this may 
again a bit of some work. This latter library is more easily adapted, and has 
less complicated internals.

   Doaitse

 


On 14 mrt 2011, at 18:55, J. Waldmann wrote:

 Hi.
 
 I want to use parsers from haskell-src-exts as sub-parsers,
 which does not seem to work since they insist on consuming the input 
 completely.
 
 I would need them to parse a maximal prefix, 
 and return the (unconsumed) rest of input as well
 (cf.
 http://hackage.haskell.org/packages/archive/parsec/3.1.1/doc/html/Text-Parsec-Prim.html#v:getInput
 )
 
 I figure that happy has the %partial directive for that, but the description
 http://www.haskell.org/happy/doc/html/sec-directives.html#sec-partial-parsers
 does not really tell me how to obtain the rest of the input.
 
 Any hints (or code samples) appreciated. Thanks - J.W.
 
 
 
 ___
 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] [ANN] new version of uu-parsinglib

2011-03-12 Thread S. Doaitse Swierstra
Version 2.7.0 was uploaded to hackage. 

From the CHANGELOG:

Version 2.7.0
Improvement: change of error correction at end of amb (which deals with 
ambiguous parsers) combinator; available lookahead is better taken into account

Relatively large change:
• Change to Data.ListLike inputs, so a general stream input structure 
is possible; hence we can now parse all instances from Data.ListLike
• Simplified and generalised implementation of merging/permuting 
parsers; any kind of parsers can now be merged/permuted
• New class IsParser was introduced which captures the basic properties 
of our parsers, thus simplifying the types
• Inclusion of a module Text.ParserCombinators.UU.Utils containing 
common Char based parsers 
• Removal of the class Provides, and replaced by separate pSym, 
pSatisfy and pRange; this may require some rewriting of existing parsers. 
  Readability is supposed to improve from that. Types become simpler. 
For an example see the module Text.ParserCombinators.UU.Utils.
• Included a Demo directory, with one module for demonstrating normal 
parsers and one aimed at showing merging parsers
• Added the module Text.ParserCombinaors.UU.Idioms, which contains 
specialised version for the idiomatic notation; 
  it infers the sequental composition operators from the types of the 
operands; 
  String-s and Char-s are not supposed to contribute to the result 
(hence *), function parameters are lifted using `pure`, and normal parsers are 
composed with `*`.
• Many other small changes, mostly upwards compatible or invisible 
(code cleanup)

For some examples see: 
http://hackage.haskell.org/packages/archive/uu-parsinglib/2.7.0/doc/html/Text-ParserCombinators-UU-Demo-Examples.html
  and: 
http://hackage.haskell.org/packages/archive/uu-parsinglib/2.7.0/doc/html/Text-ParserCombinators-UU-Demo-MergeAndPermute.html
  and: 
http://hackage.haskell.org/packages/archive/uu-parsinglib/2.7.0/doc/html/Text-ParserCombinators-UU-Idioms.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] GHC timings

2011-01-20 Thread S. Doaitse Swierstra
I have small program UULib which i use for checking some timing information.

When I compile with ghc 7 and profiling information I get the timings which are 
more or less what I expect.
If I however recompile without profiling tome consumed goes up by a factor of 
20!

1) Am I misinterpreting the results?
2) If not, does this look familiar to anyone?
3) If so, whether should I look first to see what is going on here?

 Doaitse



dyn-81-64:ProgramTests doaitse$ ghc --make UULib
[1 of 2] Compiling ParseInputs  ( ParseInputs.hs, ParseInputs.o )
[2 of 2] Compiling Main ( UULib.hs, UULib.o )
Linking UULib ...
dyn-81-64:ProgramTests doaitse$ time ./UULib
138000

real0m9.101s
user0m9.048s
sys 0m0.038s
dyn-81-64:ProgramTests doaitse$ ghc --make -prof -auto-all -rtsopts UULib
[1 of 2] Compiling ParseInputs  ( ParseInputs.hs, ParseInputs.o )
[2 of 2] Compiling Main ( UULib.hs, UULib.o )
Linking UULib ...
dyn-81-64:ProgramTests doaitse$ time ./UULib
138000

real0m0.418s
user0m0.376s
sys 0m0.038s
dyn-81-64:ProgramTests doaitse$ time ./UULib +RTS -h -p
138000

real0m0.457s
user0m0.397s
sys 0m0.034s


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


[Haskell-cafe] GHC timings

2011-01-20 Thread S. Doaitse Swierstra
I have small program UULib which i use for checking some timing information.

When I compile with ghc 7 and profiling information I get the timings which are 
more or less what I expect.
If I however recompile without profiling tome consumed goes up by a factor of 
20!

1) Am I misinterpreting the results?
2) If not, does this look familiar to anyone?
3) If so, whether should I look first to see what is going on here?

Doaitse



dyn-81-64:ProgramTests doaitse$ ghc --make UULib
[1 of 2] Compiling ParseInputs  ( ParseInputs.hs, ParseInputs.o )
[2 of 2] Compiling Main ( UULib.hs, UULib.o )
Linking UULib ...
dyn-81-64:ProgramTests doaitse$ time ./UULib
138000

real0m9.101s
user0m9.048s
sys 0m0.038s
dyn-81-64:ProgramTests doaitse$ ghc --make -prof -auto-all -rtsopts UULib
[1 of 2] Compiling ParseInputs  ( ParseInputs.hs, ParseInputs.o )
[2 of 2] Compiling Main ( UULib.hs, UULib.o )
Linking UULib ...
dyn-81-64:ProgramTests doaitse$ time ./UULib
138000

real0m0.418s
user0m0.376s
sys 0m0.038s
dyn-81-64:ProgramTests doaitse$ time ./UULib +RTS -h -p
138000

real0m0.457s
user0m0.397s
sys 0m0.034s

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


[Haskell-cafe] ANNOUNCE: new version of uu-parsinglib:2.5.6

2010-12-21 Thread S. Doaitse Swierstra

An old problem popped up in the uu-parsinglib. When combining two parsers with 
|, it is checked to see which alternative  accepts the shortest input; this 
is done in order to prevent infinite insertions, which may occur as a result of 
choosing a recursive alternative  when inserting of some recursive non-terminal 
is needed. In such a case we want to choose a non-recursive alternative.

This approach however does not combine well with the permuting parsers: here 
all the alternatives have the same length and we do not want to compute all 
those lengths, since this defeats the whole purpose of building these 
permutations lazily. So I added a non-length-checking version of | to 
ExtApplicative with is used in pPerms.

If you are using the permuting parsers you are strongly advised to upgrade.

Have a nice Christmas and a happy new year,

  Doaitse








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


Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-29 Thread S. Doaitse Swierstra

On 29 sep 2010, at 00:58, o...@cs.otago.ac.nz wrote:

 Avoiding repeated additions:
 
 movingAverage :: Int - [Float] - [Float]
 movingAverage n l = runSums (sum . take n $l) l (drop n l)
 where n' = fromIntegral n
   runSums sum (h:hs) (t:ts) = sum / n' : runSums (sum-h+t) hs ts
   runSums _   _ []  = []
 
 Doaitse
 
 I very very carefully avoided doing any such thing in my example code.
 For each output result, my code does two additions and one division.
 Yours does one addition, one subtraction, and one division, for the
 required case n = 3.  The way I formulated it, each calculation is
 independent.  The way you've formulated it, the error in one
 calculation accumulates into the next.  NOT a good idea.

If this an issue then:

module MovingAverage where

movingAverage :: [Float] - [Float]
movingAverage (x:y:l) = movingAverage' x y l
where movingAverage' x y (z:zs) = (x+y+z)/3:movingAverage' y z zs
  movingAverage' _ _ _  = []
movingAverage _   = []


has far fewer pattern matches,

 Doaitse


 
 

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


Re: [Haskell-cafe] Help to create a function to calculate a n element moving average ??

2010-09-28 Thread S. Doaitse Swierstra
Avoiding repeated additions:

movingAverage :: Int - [Float] - [Float]
movingAverage n l = runSums (sum . take n $l) l (drop n l)
 where n' = fromIntegral n
   runSums sum (h:hs) (t:ts) = sum / n' : runSums (sum-h+t) hs ts
   runSums _   _ []  = []

Doaitse


On 28 sep 2010, at 03:40, Richard O'Keefe wrote:

 
 On 27/09/2010, at 5:20 AM, rgowka1 wrote:
 
 Type signature would be Int - [Double] - [(Double,Double)]
 
 Any thoughts or ideas on how to calculate a n-element moving average
 of a list of Doubles?
 
 Let's say [1..10]::[Double]
 
 what is the function to calculate the average of the 3 elements?
 
 [(1,0),(2,0),(3,2),(4,3)] :: [(Double,Double)]
 
 moving_average3 (xs0 @ (_ : (xs1 @ (_ : xs2 =
  zipWith3 (\x y z - (x+y+z)/3) xs0 xs1 xs2
 
 *Main moving_average3 [1..10]
 [2.0,3.0,4.0,5.0,6.0,7.0,8.0,9.0]
 
 The result is two elements shorter than the original, but that
 _is_ the definition of moving average after all.
 ___
 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] types for parsing a tree

2010-09-17 Thread S. Doaitse Swierstra

On 16 sep 2010, at 05:42, Jared Jennings wrote:

 On Fri, Sep 10, 2010 at 2:00 PM, S. Doaitse Swierstra
 doai...@swierstra.net wrote:
 I show how this can be done using uu-parsinglib. Note that we have sevral 
 parsers, each having its own type:
 
 Thanks for such a complete example, Doaitse! Unfortunately I have a
 requirement I didn't disclose: the simple tags like TRNUID, NAME,
 AMOUNT could come in any order; and some are optional. I tried to
 fix that by making every field in my Transaction record a Maybe, and
 keeping a Transaction as state for my parser. But after so many Maybes
 I began to think this was not the right way. And I had to run a parser
 as part of another parser. And after all that, it wouldn't build
 because it was badly typed.

The good news is that the library has combinators for that too ;-} Just change 
a few lines. If they are optional use the pOpt combinator instead of the pOne. 

  Doaitse

module Transactions where
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Examples
import Data.Char

pTagged tag (pAttr, pPayload) =  pToken ( ++ tag ++ ) * pAttr * spaces 
* pPayload * spaces *
pToken (/ ++ tag ++ )
pTagtag pPayload  =  pToken ( ++ tag ++ ) * pPayload

data OFX = OFX Response deriving Show
data Response = Response [Transaction] deriving Show
data Transaction = Transaction String String Amount deriving Show
data Amount  = Amount Int Int deriving Show

pAmount  = TRNAMT   `pTag` (Amount $ pNatural * pSym '.' * 
pNatural)
pTransaction = STMTTRN  `pTagged` (pAttr, Transaction `pMerge`( pOne 
(TRNUID `pTag` pLine)
|| pOne 
(NAME   `pTag` pLine)
|| pOne  
pAmount
   )
   )
pResponse= STMTRS   `pTagged` (pAttr, Response $ pList 
(pTransaction * spaces))
pOFX = OFX  `pTagged` (pAttr, OFX  $ pResponse )

pAttr :: Parser String
pAttr = pToken [...]

spaces = pMunch (`elem`  \n\t)
pDigitAsInt = digit2Int $ pDigit 
pNatural = foldl (\a b - a * 10 + b ) 0 $ pList1 pDigitAsInt
digit2Int a =  ord a - ord '0'
pDigit :: Parser Char
pDigit = pSym ('0', '9')
pLine  = pMunch (/='\n') * spaces

main = do input - readFile TrInput
 run (pOFX * spaces) input




 
 But in any case, thanks for turning me on to
 Text.ParserCombinators.UU; I'd only tried Parsec before.
 ___
 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: new keyword: infixlr?

2010-09-10 Thread S. Doaitse Swierstra

On 10 sep 2010, at 20:13, Ian Lynagh wrote:

 On Fri, Sep 10, 2010 at 07:51:10PM +0200, S. Doaitse Swierstra wrote:
 
 Currently Haskell has infix, infixl and infixr operators. I see a use for 
 infixlr as well. This indicates that the implemtation may assume the 
 operator to be associative, and thus has the freedom to balance an 
 expression containing several operator occurrences.
 
 Would it be restricted to use with operators with types that are (a - a
 - a) (or more specific)?

This is what I would normally expect from an infix operator. 

 
 Otherwise e.g.
   let (+:) = (:)
   infixlr :+
   in [] +: [] +: []
 could have type [[a]] or [[[a]]].
 
 The reason that I bring up this is that in a new combinator I have added to 
 my parser library (the || in Text.ParserCombinators.UU.Derived) internally 
 uses cartesian products, which are being constructed and updated. If the 
 compiler had the right to interpret  the expressions a || b ||c || d  
 as e.g. (a || b) || (c || d) then the updating time for would go down 
 from O(n) to O(log n). 
 
 How would the compiler work out which parsing to prefer? Or would it
 assume that infixlr expressions are best balanced?

Yes, that is the idea.


 
 When first reading the proposal, I thought the idea was to allow the
 compiler to more easily perform optimisations like
   a+b+c+2+3+d = a+b+c+5+d
 but I guess that wasn't something you were thinking about?

Indeed, but the behaviour would not be forbidden either. If you would expect 
this then I would probably also want to introduce comm for commutative 
operators, so a+2+b+c would get transformed into a+b+c+(2+4). The only suse for 
this is that after inlining  some further optimisations might take place, which 
would be hard for a programmer to achieve otherwise. My intention was however 
not to make things very complicated at this point.

Doaitse

 
 
 Thanks
 Ian
 
 ___
 Haskell-prime mailing list
 Haskell-prime@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-prime
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: [Haskell-cafe] types for parsing a tree

2010-09-10 Thread S. Doaitse Swierstra
I show how this can be done using uu-parsinglib. Note that we have sevral 
parsers, each having its own type:

module Transactions where
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Examples
import Data.Char

pTagged tag (pAttr, pPayload) =  pToken ( ++ tag ++ ) * pAttr * spaces 
* pPayload * spaces *
 pToken (/ ++ tag ++ )
pTagtag pPayload  =  pToken ( ++ tag ++ ) * pPayload

data OFX = OFX Response deriving Show
data Response= Response [Transaction] deriving Show
data Transaction = Transaction String String Amount deriving Show
data Amount  = Amount Int Int deriving Show

pAmount  = TRNAMT   `pTag` (Amount $ pNatural * pSym '.' * 
pNatural)
pTransaction = STMTTRN  `pTagged` (pAttr, Transaction $  TRNUID 
`pTag` pLine
*  NAME   
`pTag` pLine
* pAmount
)
pResponse= STMTRS   `pTagged` (pAttr, Response $ pList 
(pTransaction * spaces))
pOFX = OFX  `pTagged` (pAttr, OFX  $ pResponse )

pAttr :: Parser String
pAttr = pToken [...]

spaces = pMunch (`elem`  \n\t)
pDigitAsInt = digit2Int $ pDigit 
pNatural = foldl (\a b - a * 10 + b ) 0 $ pList1 pDigitAsInt
digit2Int a =  ord a - ord '0'
pDigit :: Parser Char
pDigit = pSym ('0', '9')
pLine  = pMunch (/='\n') * spaces

main = do input - readFile TrInput
  run (pOFX * spaces) input

Running the main function on your code gives:

*Transactions :r
[1 of 1] Compiling Transactions ( Transactions.hs, interpreted )
Ok, modules loaded: Transactions.
*Transactions main
--
--  Result: OFX (Response [Transaction 9223ry29r389 THE GROCERY STORE 
BLABLABLA (Amount 234 99),Transaction 1237tg832t SOME DUDE ON PAYPAL 
4781487 (Amount 2174 27)])
-- 
*Transactions 

It is interesting to what happens if your input is incorrect,

 Doaitse





On 10 sep 2010, at 18:53, Jared Jennings wrote:

 OFX[...]
STMTRS[...]
STMTTRN[...]
TRNUID9223ry29r389
NAMETHE GROCERY STORE BLABLABLA
TRNAMT234.99
/STMTTRN
STMTTRN[...]
TRNUID1237tg832t
NAMESOME DUDE ON PAYPAL 4781487
TRNAMT2174.27
/STMTTRN
/STMTRS
/OFX

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


[Haskell-cafe] problems using macports?

2010-09-09 Thread S. Doaitse Swierstra
I am in my yearly fightto get a working combination of operating system (Snow 
Leopard), compiler version (6.12) , wxWidgets and wxHaskell on my Mac . 
After deleting most of my stuff, starting afresh, hours of building using 
macports etc. I finally get the message:

loeki:Opgave doaitse$ ghc --make Turtle.hs
[1 of 1] Compiling Main ( Turtle.hs, Turtle.o )
Linking Turtle ...
Undefined symbols:
  _iconv_open, referenced from:
  _hs_iconv_open in libHSbase-4.2.0.2.a(iconv.o)
 (maybe you meant: _hs_iconv_open)
  _iconv, referenced from:
  _hs_iconv in libHSbase-4.2.0.2.a(iconv.o)
 (maybe you meant: _hs_iconv_open, _hs_iconv , _hs_iconv_close )
  _iconv_close, referenced from:
  _hs_iconv_close in libHSbase-4.2.0.2.a(iconv.o)
 (maybe you meant: _hs_iconv_close)
ld: symbol(s) not found
collect2: ld returned 1 exit status
loeki:Opgave doaitse$ 


Some Googling showed me that the same problem has shown up with Yi,  The 
solution however is not there. Can someone enlighten me.

 Doaitse


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


[Haskell-cafe] ANNOUNCE: uu-parsinglib version 2.5.3; extended with merging combinators

2010-08-05 Thread S. Doaitse Swierstra
I have uploaded a new version of the uu-parsinglib. It contains, besides the 
extension of the abstract interpretation part and the fixing of some very 
subtle corner cases in that part, some nice new functionality:

The call of the parser:

-- run ((,,,) `pMerge` (pSome pa || pMany pb || pOne pc ||  pNatural 
`pOpt` 5)) babc45a

results in:

--  Result: ([a, a],[b,b],c,45)

and

-- run ((,,,) `pMerge` (pSome pa || pMany pb || pOne pc ||  pNatural 
`pOpt` 5)) bbc

results in

--  Result: ([a],[b,b],c,5)
--  Correcting steps: 
-- Inserted 'a' at position (0,3) expecting one of ['0'..'9', 'b', 'a']
-- 


pSome means that the number of elements occurring in the input should be = 1
pMany= 0
pOne  = 1
pOpt = 1

The implementation can be found in the Derived module, and is remarkably simple.

Doaitse





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


Re: [Haskell-cafe] design question: decision tree from Programming Collective Intelligence

2010-08-04 Thread S. Doaitse Swierstra
I have added the permutation parsers from uulib to uu-parsinglib:

http://hackage.haskell.org/packages/archive/uu-parsinglib/2.5.1.1/doc/html/Text-ParserCombinators-UU-Perms.html,

where you find reference to the paper

Doaitse


On 22 jun 2010, at 09:24, Stephen Tetley wrote:

 Hello
 
 Maybe permutation trees are a viable starting point?
 
 See the paper Parsing Permutation Phrases which appears to be on CiteSeer.
 
 Some slides are also here - the data type definitions and Functor
 instance for permutation trees are on page 18 (pdf index page 19):
 http://www.comlab.ox.ac.uk/jeremy.gibbons/wg21/meeting56/loeh-slides.pdf
 
 An alternative implementation for applicative functors is here:
 http://hackage.haskell.org/package/action-permutations
 
 Note the use of existentials here is pretty cunning, I didn't get very
 far the time I attempted to use the technique for my own purposes.
 
 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


[Haskell-cafe] Re: Fun with uu-parsinglib

2010-07-29 Thread S. Doaitse Swierstra

On 29 jul 2010, at 05:04, David Place wrote:

 Hi, Doaitse.
 
 I am making good progress transcribing my parser to use your library.   I 
 think some ways that I have grown accustomed to working with Parsec will not 
 work, though.   Now, I am getting the run time error:
 
  Result: *** Exception: cannot compute minimal length of right hand side of 
 monadic parser
 
 Is there an explanation of this error in the documentation?  I am trying to 
 combine with alternation some parsers which return the semantic data 
 structures of my program.  Perhaps there are restrictions on the kind of 
 parsers that can be combined with alternation.
 
 Cheers,
 David
 
 David Place   
 Owner, Panpipes Ho! LLC
 http://panpipesho.com
 d...@vidplace.com
 
 
 


Dear David,

I am cc-ing this answer to Haskell-café since the answer may be of a wider 
interest.

Let me first explain a a sequence of design choices I made:

1) my parser combinators perform error correction by trying to insert missing 
tokens into and to delete superfluous tokens from the input
2) of course there are many possibilities to do so 
3) hence I implemented a search process which currently prunes the tree of 
possible corrective choices up to depth three
4) this process may return several solutions with the same overall cost and I 
have to pick one of those
5) in case of a draw I give preference to those alternatives which delete 
something, so progress is guaranteed
6) at the end of the input this does not work, since there is nothing to delete
7) if I pick an arbitrary alternative this may lead to a choice where we get an 
infinite sequence of insertions; suppose e.g. we want to insert an expression, 
and the system picks the if_alternative. If it does so it inserts an if-token 
and then the process starts all over again by trying to insert a conditional 
expression, which in general will be an expression, which will lead to the 
insertion of another if-token, etc.
8) in order to prevent this behaviour internally an abstract interpretation is 
made which computes the minimal number of tokens a parser will recognise (and 
thus can insert). The recursive alternatives will get an infinite length,  and 
will thus never be chosen unless you grammar is well-formed and all choices 
only can lead to an infinite sequence of insertions
9) if a choice has to be made for the correction process always a finite 
alternative is chosen, so the correction process is guaranteed to complete

Now the monads come in; they raise the question how to compute the minimal 
length of a parser WHICH DEPENDS ON A PREVIOUSLY RECOGNISED part of the input. 
In general this is impossible. So I made the decision to generate an error 
message in such cases, since I did not expect many people to run into this.

But now you, and probably many people used to writing parsers in the monadic 
(i.e. Parsec) style turn up, and you continue to use the monadic style bacuse 
you have become accustomed to a different way of writing parsers. Let me give 
an example, based on the following grammar for well-formed nested parentheses: 
S - (S)S ; epsilon. We want to return e.g. the maximal nesting depth. This is 
one of the functions in the Examples.hs file in the uu-parsinglib. The 
prototypical way of writing this in applicative style, without using monads is:

wfp :: Parser Int
wfp =  max . (+1) $ pParens  wfp * wfp 
  `opt` 
   0

Now let us take a look at the monadic formulation:

wfp  = do lt - pParens wfp
  rt - wfp   --  second call to wfp
  return ((lt + 1) `max` rt)
   | return 0

Now we see that the second call to wfp is within the scope of the binding of 
lt, and hence may depend on it. In this case it does not, but unfortunately the 
abstract interpretation cannot see this, and thus cannot do very much.

This shows in my view the bad thing about monadic parser combinators: they 
prohibit the self-analysis of parsers, they inhibit optimisations, and they 
inhibit feedback based on the analysis. More on this below.

Since I assume that the monadic formulation is only used as a last resort, i.e. 
when a parser REALLY depends on previous input, and that this will in general 
not be part of an alternative construct, I have decided to generate the above 
error message.

Another solution I could have chosen is to make the choice in the correction 
process based on the order in which the alternatives occur in the program, but 
this would create the need to explain to users that the order of their 
alternatives matters, and it is one of the nice things that thus far it does 
not. In the old uulib the order even gets completely lost because we internally 
build tables which assist in speeding up the parsing process.

There are several solutions now:

a) I just remove the error message and make an educated guess, leading to 
situations where users might get stuck in an infinite correction process (only 
at the end of the file; normally in 

Re: [Haskell-cafe] Re: ANN: weighted-regexp-0.1.0.0

2010-07-28 Thread S. Doaitse Swierstra

On 27 jul 2010, at 09:30, Eugene Kirpichov wrote:

 Perhaps this might mean that we can get incremental and parallel
 regexp matching by associating each character with a linear operator

This is exactly what is happening in the uu-parsinglib. 

 Doaitse


 (matrix) over this or related semiring, or something, and mixing that
 with two sigfpe's articles:
 http://blog.sigfpe.com/2008/11/approach-to-algorithm-parallelisation.html
 http://blog.sigfpe.com/2009/01/fast-incremental-regular-expression.html
 
 2010/7/27 Sjoerd Visscher sjo...@w3future.com:
 
 On Jul 27, 2010, at 7:09 AM, Sebastian Fischer wrote:
 
 I'll add
 
noMatch :: RegExp c
noMatch = psym [] (const False)
 
 Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a Semiring, 
 but I'm not sure what that would do.
 --
 Sjoerd Visscher
 http://w3future.com
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 -- 
 Eugene Kirpichov
 Senior Software Engineer,
 Grid Dynamics http://www.griddynamics.com/
 ___
 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: ANN: weighted-regexp-0.1.0.0

2010-07-28 Thread S. Doaitse Swierstra

On 28 jul 2010, at 13:17, Eugene Kirpichov wrote:

 This is very interesting!
 Could you provide some more info? T.i. where to look in the source, or
 on the web?

see: file:///Users/doaitse/.cabal/share/doc/uu-parsinglib-2.4.2/html/index.html

The README.hs module contains some further references.

 Doaitse


 
 2010/7/28 S. Doaitse Swierstra doai...@swierstra.net:
 
 On 27 jul 2010, at 09:30, Eugene Kirpichov wrote:
 
 Perhaps this might mean that we can get incremental and parallel
 regexp matching by associating each character with a linear operator
 
 This is exactly what is happening in the uu-parsinglib.
 
  Doaitse
 
 
 (matrix) over this or related semiring, or something, and mixing that
 with two sigfpe's articles:
 http://blog.sigfpe.com/2008/11/approach-to-algorithm-parallelisation.html
 http://blog.sigfpe.com/2009/01/fast-incremental-regular-expression.html
 
 2010/7/27 Sjoerd Visscher sjo...@w3future.com:
 
 On Jul 27, 2010, at 7:09 AM, Sebastian Fischer wrote:
 
 I'll add
 
noMatch :: RegExp c
noMatch = psym [] (const False)
 
 Oh, by the way, with noMatch, eps, alt and seq_ RegExp is itself a 
 Semiring, but I'm not sure what that would do.
 --
 Sjoerd Visscher
 http://w3future.com
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 --
 Eugene Kirpichov
 Senior Software Engineer,
 Grid Dynamics http://www.griddynamics.com/
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
 
 -- 
 Eugene Kirpichov
 Senior Software Engineer,
 Grid Dynamics http://www.griddynamics.com/

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


Re: [Haskell-cafe] Techniques for ensuring parser correctness?

2010-07-26 Thread S. Doaitse Swierstra

On 26 jul 2010, at 03:51, Jason Dagit wrote:

 Hello,
 
 I find that parser correctness is often hard to verify.  Therefore, I'm 
 interested in techniques that others have used successfully, especially with 
 Haskell.

It seems to me that you are not so much trying to verify parsers, but more 
specifically Parsec parsers. Since in Parsec-based parsers you control the 
backtracking explicitly such parsers can get very complicated semantics. Now 
the question arises: what does it mean for a (Parsec) parser to be correct? Do 
you have another description of the  language which is to be recognised, e.g. a 
context-free grammar. Only then can you give meaning to the word correctness.

In general I think that the more your parser combinators deviate from 
context-free grammars in terms of expressiveness, the more problems you will 
encounter. If you make heavy use of the monadic part, you will not only have to 
prove the correctness of static parsers, but even of parsers which are 
generated dynamically. If you use the backtrack-controlling features, your 
proofs will become even more complicated, since it is unlikely that your more 
abstract formalism in which you have specified your language does not have a 
similar construct: here comes in about 50 years on research on parsing 
techniques and grammar analysis. If your grammar is e.g. LL(1) then you can 
verify that some of the back-tracking-controlling features in your Parser 
parser have been used in a sound way, i.e., that you will be able to parse any 
sentence that your grammar describes.

If you have a context-free grammar, and you want to be relatively sure that the 
parser is correct and you do not want to go through large verification efforts 
I suggest you use the uu-parsinglib; the only restriction there is is that your 
grammar should fulfill certain modest well-formedness criteria, such as being 
non-left-recursive and non-ambiguous. Then  the semantics of the combinators 
are exactly what you want, i.e. your parsers and your grammars are isomorphic. 
If you have however an incorrect formal specification, i.e., a specification 
which contains ambiguous non-terminals like p* constructs where p can reduce to 
an empty string   things break. The first problem one is not recognised and 
will lead to a non-terminating parser, whereas the second problem is detected 
by the grammars analysing themselves while being used, and leading to a 
run-time error message once you reach that part of the grammar during parsing.

If you insist on using left-recursive parsers you may use the left-corner 
transform from the 

http://hackage.haskell.org/packages/archive/ChristmasTree/0.2/doc/html/Text-GRead-Transformations-LeftCorner.html

package, or use a parser generator like happy; parser generators usually do 
some form of analysis (i.e. proving properties), which captures many mistakes 
in the design of a language.

Furthermore you may take a look at: 
@inproceedings{DBLP:conf/mpc/BrinkHL10,
  author= {Kasper Brink and
   Stefan Holdermans and
   Andres L{\o}h},
  title = {Dependently Typed Grammars},
  booktitle = {MPC},
  year  = {2010},
  pages = {58-79},
  ee= {http://dx.doi.org/10.1007/978-3-642-13321-3_6},
  crossref  = {DBLP:conf/mpc/2010},
  bibsource = {DBLP, http://dblp.uni-trier.de}

Doaitse Swierstra










 
 Techniques I'm aware of:
   * Round trip checks: Generate a datastructure, render as a string, parse 
 back, and compare.  Quickcheck can be used to automate this.
   * Fuzz testing:  What tools exist to help me?
   * Formal verification: Has anyone been using this with Haskell parsers?  
 Other than general theorem provers, say Isabelle, what tools exist?
 
 My specific need:
 The immediate challenge I have is that I'm modifying the parser that Darcs 
 uses and we would like to improve the parser's test suite as well.  The 
 parser abstraction used in this case follows parsec's API.  Left to my own 
 devices I would use round trip checks, written with quickcheck, for this 
 exercise.  Because we're using a parsec style parser, I don't have a nice 
 neat grammar handy.
 
 Thanks in advance for any advice you have!
 
 Thanks,
 Jason
 ___
 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] Techniques for ensuring parser correctness?

2010-07-26 Thread S. Doaitse Swierstra
I took a quick look at this file. To me it seems a mixture of a lexer and a 
parser built on top of a home brewn parser library. I see function like 
maybeWork which 
(if I interpret correctly) test whether specific conditions hold for the input, 
etc.

Indeed it would be nice to have a grammatical description of the input format. 
An important question is whether you can be assured that all input is indeed 
correct, or whether any checking has to be done.

 Doaitse


On 26 jul 2010, at 12:38, Eric Kow wrote:

 On Mon, Jul 26, 2010 at 03:01:54 +, Jason Dagit wrote:
 I think the grammar is fairly simple, although I'm not confident classifying
 it.  I know it can be parsed with just a simple pass over the data.  The
 only uses of backtracking are just to figure out what is next, like a peek
 at the next token.  Let me give you some samples of what the input looks
 like.
 
 For the interested, I think you can view
 
 http://darcs.net/src/Darcs/Patch/Read.hs
 
 or better yet darcs get --lazy http://darcs.net
 
 Here are three entries from the inventory they correspond to PatchInfos:
 [TAG 2.4
 Reinier Lamers tux_roc...@reinier.de**20100226180900
 Ignore-this: 36ce0456c214345f55a7bc5fc142e985
 ]
 
 If it turns out to be a sufficiently low-powered grammar, we should
 probably write it up formally and stick it in the source code for
 documentation.
 
 Eric
 
 PS. We've been making little bits of progress trying to document Darcs
on a technical high level, eg.
 
- http://wiki.darcs.net/DarcsInternals/Record
- http://wiki.darcs.net/DarcsInternals/CacheSystem
 
Such a grammar would be a nice addition to the
good-enough-that-you-could-rewrite-Darcs-in-Fortran aspiration.
 
 -- 
 Eric Kow http://www.nltg.brighton.ac.uk/home/Eric.Kow
 For a faster response, please try +44 (0)1273 64 2905.
 ___
 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] Typeclasses question in Real World Haskell book

2010-07-26 Thread S. Doaitse Swierstra
How about:

*Main fromJValue (JBool True) :: Either JSONError Bool
Right True
*Main 

Doaitse


On 26 jul 2010, at 15:16, Angel de Vicente wrote:

 data JValue = JString String
| JNumber Double
| JBool Bool
| JNull
| JObject [(String, JValue)]
| JArray [JValue]
  deriving (Eq, Ord, Show)
 
 type JSONError = String
 
 class JSON a where
toJValue :: a - JValue
fromJValue :: JValue - Either JSONError a
 
 instance JSON JValue where
toJValue = id
fromJValue = Right
 
 instance JSON Bool where
toJValue = JBool
fromJValue (JBool b) = Right b
fromJValue _ = Left not a JSON boolean

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


Re: [Haskell-cafe] Regular Expression to Determinate Finite Automata translator

2010-07-22 Thread S. Doaitse Swierstra
The simplest way to make a recogniser out of a RE is to use one of the 
available parsing libraries:

module RE where
import Text.ParserCombinators.UU
import Text.ParserCombinators.UU.Examples

data RE = Epsilon | Leaf Char | Selection RE RE | Sequence RE RE | Kleene RE | 
Optional RE | End


re_to_fsm :: RE - Parser String
re_to_fsm re = case re of 
Leaf c- lift $ pSym c
Selection re1 re2 - re_to_fsm re1 | re_to_fsm re2
Sequence re1 re2  - (++) $ re_to_fsm re1 * re_to_fsm re2
Kleene re - concat $ pList (re_to_fsm re)
Optional re   - re_to_fsm re `opt` 
End   - pure 

t = re_to_fsm ((Kleene (Leaf 'a') `Sequence` Kleene (Leaf 'b')) `Selection` 
(Kleene (Leaf 'a') `Sequence` (Kleene (Leaf 'c') )))

t1 = run t aaabbb
t2 = run t ccc
t3 = run t aaddcc
test = run (re_to_fsm (Kleene (Leaf 'a') `Sequence` Kleen (Left 'b')) aaabbb

*RE t1
--
--  Result: aaabbb
-- 
*RE t2
--
--  Result: ccc
-- 
*RE t3
--
--  Result: aacc
--  Correcting steps: 
-- Deleted  'd' at position 2 expecting one of ['a', 'c', 'a', 'b']
-- Deleted  'd' at position 3 expecting 'c'
-- 
*RE 


On 22 jul 2010, at 20:51, Aaron Gray wrote:

 Hi,
 
 I am a Haskell newbie. I have coded a Regular Expression to Determinate 
 Finite Automata translator. Algorithm from the Dragon Book.
 
 Would someone eyeball the code and give me suggestions please. 
 
 I have not done anything on character classes yet though. And the parsing is 
 a bit of a hack.
 
 What I am not sure about is having to have multiple versions of similar 
 datatype, each with variations in order to enumerate and generate followPos 
 set.
 
 Is there a better way of implementing this ?
 
 Many thanks in advance,
 
 Aaron
 
 RE2DFA.hs___
 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] Haddock question

2010-07-21 Thread S. Doaitse Swierstra
I am trying to document my parser library. In order to do so I should like to 
include some example output in my haddock documentation. I fail to see however 
how to get a block of output into the haddock part.

E.g.

-- | We can now run the parser @`pa`@ on input \a\, which succeeds: 
-- @ Result: \a\
-- @

does not put the Result ... on a separate line, and if I have several lines of 
output they are concatenated.

 How to proceed,

 Doaitse


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


[Haskell-cafe] Haddock question

2010-07-21 Thread S. Doaitse Swierstra
I am trying to document my parser library. In order to do so I should like to 
include some example output in my haddock documentation. I fail to see however 
how to get a block of output into the haddock part.

E.g.

-- | We can now run the parser @`pa`@ on input \a\, which succeeds: 
-- @ Result: \a\
-- @

does not put the Result ... on a separate line, and if I have several lines of 
output they are concatenated.

How to proceed,

Doaitse

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


Re: [Haskell-cafe] Tiger compiler in Haskell: annotating abstract syntax tree

2010-07-21 Thread S. Doaitse Swierstra
Despite the interesting discussing which has followed this question I think 
that in orde to approach this specific problem the use of a specific 
compiler-writers toolset such as the uuagc 
(http://hackage.haskell.org/package/uuagc-0.9.29)) system is to be preferred; 
it provides aneffiicent and modular way of constructing sch complicated 
compositions.  The complete Utrecht haskell compiler is constructed in this way.

 Doaitse

1) If you are brave hearted you may try to use the 
http://hackage.haskell.org/package/AspectAG road ;-}
2) If you are interested in an (albeit old) Tiger compiler built using uuagc 
see: http://hackage.haskell.org/package/tiger


On 19 jul 2010, at 18:51, José Romildo Malaquias wrote:

 Hello.
 
 In his book Modern Compilder Implementation in ML, Appel presents a
 compiler project for the Tiger programming language where type checking
 and intermediate code generation are intrinsically coupled.
 
 There is a function
 
  transExp :: Absyn.Exp - (Tree.Exp,Types.Type)
 
 that do semantic analysis, translating an expression to the Tree
 intermediate representation language and also do type checking,
 calculating the type of the expression.
 
 Maybe the compiler can be made more didatic if these phases are separate
 phases of compilation.
 
 The type checker would annotate the abstract syntax tree (ast) with type
 annotations, that could be used later by the translater to intermediate
 representation.
 
 In an imperative language probably each relevant ast node would have a
 field for the type annotation, and the type checker would assign the
 type of the node to this field after computing it.
 
 I am writing here to ask suggestions on how to annotate an ast with
 types (or any other information that would be relevant in a compiler
 phase) in Haskell.
 
 As an example, consider the simplified ast types:
 
  data Exp
= IntExp Integer
| VarExp Symbol
| AssignExp Symbol Exp
| IfExp Exp Exp (Maybe Exp)
| CallExp Symbol [Exp]
| LetExp [Dec] Exp
 
  data Dec
 = TypeDec Symbol Ty
 | FunctionDec Symbol [(Symbol,Symbol)] (Mybe Symbol) Exp
 | VarDec Symbol (Maybe Symbol) Exp
 
 Expressions can have type annotations, but declarations can not.
 
 Comments?
 
 
 Regards,
 
 Romildo
 --
 Computer Science Department
 Universidade Federal de Ouro Preto, Brasil
 ___
 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] Haddock question

2010-07-21 Thread S. Doaitse Swierstra
Unfortunately I get for input:

-- | We can now run the parser @`pa`@ on input \a\, which succeeds: 
-- @ 
--   Result: \a\
--   Second line
-- @

the output

We can now run the parser pa on input a, which succeeds: Result: a Second 
line

Doaitse






On 21 jul 2010, at 16:17, Daniel Fischer wrote:

 On Wednesday 21 July 2010 16:09:37, S. Doaitse Swierstra wrote:
 I am trying to document my parser library. In order to do so I should
 like to include some example output in my haddock documentation. I fail
 to see however how to get a block of output into the haddock part.
 
 E.g.
 
 -- | We can now run the parser @`pa`@ on input \a\, which succeeds:
 -- @ Result: \a\
 -- @
 
 -- | We can now ...
 --
 -- @
 --   Result: \a\
 -- @
 --
 --  In further news, ...
 
 
 does not put the Result ... on a separate line, and if I have several
 lines of output they are concatenated.
 
 How to proceed,
 
 Doaitse
 
 
 ___
 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] [Ann] New version of parser combinator library uu-parsinglib-2.4.0

2010-07-21 Thread S. Doaitse Swierstra
I have uploaded a new version of the package uu-parsinglib, te collection of 
online, error-correcting parser combinators, with both an applicative and a 
monadic interface.

* The new version behaves better when more than three corrective steps have to 
be taken at a specific position. In order ro do so we have added a form of 
abstract interpretation which computes the minimal length of each alternative, 
so the shortest one can be chosen (and not one of the recursive alternatives!).

* Furthermore we compute for each parser whether it can recognise the empty 
string. This is used to provide error messages when such parsers are used in 
list-like constructs, on of the most commonly made mistakes by innocent parser 
writers.

* a combinator ? was added which can be used to label productions, and which 
label is used to report what was expected

* some further overloadings of pSym have been added which function at a lower 
level, thus leading to much faster parsers, especially when using the 
combinator  to construct scanner like parsers: e.g.

   spaces = pMunch (==' ')

makes sure that all spaces are skipped in a single go, instead of dealing with 
each recognised ' ' by itself.

I hope you like the extensions, and would be happy to hear from you, both if 
you use them successfully, or if you have any reason for not using them.

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


Re: [Haskell-cafe] Parsec combinator like Prolog's cut operator?

2010-07-03 Thread S. Doaitse Swierstra
If you use the uu-parsing libraries you will get a breadth-first search, 
instead of a non-backtrcaking depth-first search of Parsec; furthermore you do 
not suffer from space leaks and get your results online. In addition you get 
error correction, with high-quality error messages.

The principles of the library are explained in 


@inproceedings{uuparsing:piriapolis,
Author = {Swierstra, S.~Doaitse},
Booktitle = {Language Engineering and Rigorous Software Development},
Date-Added = {2009-05-23 11:08:01 +0200},
Date-Modified = {2009-05-31 22:35:25 +0200},
Editor = {Bove, A. and Barbosa, L. and Pardo, A. and and Sousa Pinto, 
J.},
Pages = {252-300},
Place = {Piriapolis},
Publisher = {Spinger},
Series = {{LNCS}},
Title = {Combinator Parsers: a short tutorial},
Volume = {5520},
Year = {2009}}

which is also available as a technical report:


@techreport{UUCS2008044,
Author = {Swierstra, S. Doaitse},
Date-Added = {2009-01-07 13:47:34 +0100},
Date-Modified = {2009-01-16 17:36:52 +0100},
Institution = {Department of Information and Computing Sciences, 
Utrecht University},
Number = {UU-CS-2008-044},
Pubcat = {techreport},
Title = {Combinator Parsing: A Short Tutorial},
Urlpdf = 
{{http://www.cs.uu.nl/research/techreps/repo/CS-2008/2008-044.pdf}}

Follow the link to the pdf in this last Bibtex record.

In the uu-parsing package you will find a file with examples, which you can 
just run to see the different constructs at work. Because te library is doing 
the hard work, writing parsers becomes simpler.

 Doaitse

On 30 jun 2010, at 05:26, Erik de Castro Lopo wrote:

 Hi all,
 
 I'm reading John Hughes' paper Generalizing Monads to Arrows and found
 the statement regarding parser combinators:
 
   ... depend on the programmer using an additional combinator similar
   to Prolog's 'cut' operator do declare that a parser need never
   backtrack beyond a certain point.
 
 Does something like this already exist in Parsec? If not is there a way
 to write it?
 
 Having this would really help with a parsing problem I have.
 
 Cheers,
 Erik
 -- 
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/
 ___
 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] Parselib sample

2010-06-02 Thread S. Doaitse Swierstra
If you want to use the easier long-standing libraries from Utrecht, we can provide you with a parser for full Haskell, which you can find in the Utrecht Haskell Compiler (UHC) distribution.In 2002 Alexey Rodriguez produced a C fron-end, using the UUlibs combinators. I am attaching the file with the parser so you can take a look. If you want to have access to the full compiler, which was not maintained, I can make the full code available on a website. I think it is also instructive to start with looking at simpler parsers, e.g. for the bibtex format, which is available from:https://subversion.cs.uu.nl/repos/project.STEC.uulib/uulib/trunk/examples/DoaitseOn 1 jun 2010, at 13:06, C K Kashyap wrote:Hi,Is there a not-so-trivial parser implementation with Parselib? Parser for a "C" like language would be good.I searched and found Haskell++ - http://www.cs.chalmers.se/~rjmh/Software/h++.html
However, I'd prefer to look at a parser for a "C" like language.-- Regards,Kashyap
___Haskell-Cafe mailing listHaskell-Cafe@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

CParser.hs
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lazy Parsing (ANN: vcd-0.1.4)

2010-04-28 Thread S. Doaitse Swierstra

On 27 apr 2010, at 22:12, Jason Dusek wrote:

  So UU parsers can construct input?

The perform an editing action on the input so it becomes a sentence of the 
language recognised. 

 The presence of an
  empty list in the 2nd slot of the tuple is the only
  indicator of errors?

The parser wants to see a natural number, whch is a non-empty list of digits. 
So it inserts a single digit, which is any character from the range '0'-'9'. 
Since no default value is given here, it takes the first one from the range: 
'0'. Furthermore you get a list of errors, which tell you which correcting 
steps were taken. There is a special combinator with which you can ask for the 
errors produced since the last time you asked, and which you can use to control 
further parsing.

 
  For parsing datatypes without a sensible default value,
  what happens?

If you do nothing you get a less sensible default value; 
you may however provide (lower costs) extra alternatives which will be taken by 
the correcting process. There is a cost model which can be used to control the 
correction process. Tokens have a specific insertion cost and a specific 
deletion cost with which you can play. Usually this is not necessary. The 
typical process is that at first you do not pay attention to the correction 
process, and once you see things you really do not want, you provide an extra 
alternative, or rule out some alternatives by increasuig costs. 

In the UHC token like if have a high cost, since we think there is very 
little chance that people will forget to write them. A ')' can have a lower 
insertion and deletion cost, since people are more likely to have too many or 
not enough of them.



 Doaitse




 
 --
 Jason Dusek

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


Re: [Haskell-cafe] Lazy Parsing (ANN: vcd-0.1.4)

2010-04-27 Thread S. Doaitse Swierstra
How about:

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


pDate :: Pars (Int,Int,Int)
pDate = (,,) $ pNatural * pDot * pNatural * pDot * pNatural
where pDot = pSym '.'

and then:

*Main test pDate 3.4.5
Loading package syb-0.1.0.2 ... linking ... done.
Loading package base-3.0.3.2 ... linking ... done.
Loading package array-0.3.0.0 ... linking ... done.
Loading package filepath-1.1.0.3 ... linking ... done.
Loading package old-locale-1.0.0.2 ... linking ... done.
Loading package old-time-1.0.0.3 ... linking ... done.
Loading package unix-2.4.0.0 ... linking ... done.
Loading package directory-1.0.1.0 ... linking ... done.
Loading package process-1.0.1.2 ... linking ... done.
Loading package time-1.1.4 ... linking ... done.
Loading package random-1.0.0.2 ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package uu-parsinglib-2.3.1 ... linking ... done.
((3,4,5),[])
*Main test pDate 3..7
((3,0,7),[
Inserted '0' at position 2 expecting '0'..'9'])
*Main test pDate 
((0,0,0),[
Inserted '0' at position 0 expecting '0'..'9',
Inserted '.' at position 0 expecting one of ['0'..'9', '.'],
Inserted '0' at position 0 expecting '0'..'9',
Inserted '.' at position 0 expecting one of ['0'..'9', '.'],
Inserted '0' at position 0 expecting '0'..'9'])
*Main test pDate 3.4.2010
((3,4,2010),[])
*Main

Doaitse


On 27 apr 2010, at 13:23, Tom Hawkins wrote:

 I had been using Parsec to parse VCD files, but needed to lazily parse
 streaming data.  After stumbling on this thread below, I switch to
 polyparse.
 
 What a great library!  I was able to migrate from a strict to a
 semi-lazy parser and many of my parse reductions didn't even need to
 change.  Thanks Malcolm!
 
 In addition to lazy VCD parsing, this version of vcd [1] also includes
 step', which forces a step regardless if variables have changed or not
 -- helpful for realtime simulation.
 
 (BTW, parsec is a great library too.)
 
 -Tom
 
 [1] http://hackage.haskell.org/package/vcd-0.1.4
 
 
 
 On Sun, May 31, 2009 at 6:41 AM, Malcolm Wallace
 malcolm.wall...@cs.york.ac.uk wrote:
 
 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] which version is in the platform

2010-03-22 Thread S. Doaitse Swierstra
On the page:

http://hackage.haskell.org/platform/

I am told that the platform includes ghc-6.10.4, but if I click there on the 
Haskell:batteries included link to get to the page:

http://hackage.haskell.org/platform/contents.html

its states there that I get 6.12.1?

 Doaitse


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


Re: [Haskell-cafe] which version is in the platform

2010-03-22 Thread S. Doaitse Swierstra
It seems that I am being served old pages by my web browser from the cache on 
my machine. By reloading the platform page, I suddenly am asked what system I 
do have, from weher I am referred to the 6.12 version of the platform,

 Doaitse

On 22 mrt 2010, at 14:25, Don Stewart wrote:

 doaitse:
 On the page:
 
 http://hackage.haskell.org/platform/
 
 I am told that the platform includes ghc-6.10.4, but if I click there
 on the Haskell:batteries included link to get to the page:
 
 http://hackage.haskell.org/platform/contents.html
 
 its states there that I get 6.12.1?
 
 
 The beta of the 2010.2.0.0 release is now up, which is based on GHC 6.12.
 
 The last stable Haskell Platform release is 2009.2.0.0, which used GHC
 6.10.4. (And the windows installer currently up provides this version).
 
 -- Don

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


Re: [Haskell-cafe] First time haskell - parse error!

2010-03-09 Thread S. Doaitse Swierstra

On 9 mrt 2010, at 20:04, boblettoj wrote:

 
 Hi, i am getting an error when trying to compile this part of my program, its
 my first time using haskell and as lovely as it is it didn't give me very
 much to go on in the error message!
 
 codescore :: String - String - String
 score [s] [] = false
 score [s] [g] = 
   if valid 4 g
   then (s1 ++ s2 ++ s3 ++ s4) where
   s1 = Golds 
   s2 = show (gold s g)
   s3 = , Silvers 
   s4 = show (silver s g)
   else Bad Guess/code

If you want to keep the definitions local to the expression you should write

 then let s1 = ..
  s2 = ...
  ...
  in (s1++s2++s3++s4)
 else ...

Doaitse


 
 when i try to compile it says: test.hs 63:29: parse error on input 'where'
 (its the line beginning with 'then')
 Anybody got any ideas whats going on?
 thanks!
 -- 
 View this message in context: 
 http://old.nabble.com/First-time-haskell---parse-error%21-tp27839657p27839657.html
 Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
 
 ___
 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: Negation

2010-02-14 Thread S. Doaitse Swierstra


On 14 feb 2010, at 09:32, Simon Marlow wrote:


On 14/02/10 02:21, Lennart Augustsson wrote:

I agree, I don't think this is a bug.  If the grammar actually says
that this is legal, then I think the grammar is wrong.


As far as I can tell Doitse is correct in that GHC does not  
implement the grammar, so it's either a bug in GHC or the grammar.   
To fix it in the grammar would no doubt involve quite a bit of  
refactoring, I can't immediately see how to do it easily.


This is indeed not easy, and probably one more situation where some  
extra text has to exclude this since I actually think it should not be  
accepted from a language design point of view. How would you explain  
that


weird :: Int - Int
weird = (if True then 3 else 5+)

is perfectly correct Haskell?

Doaitse





Cheers,
Simon



On Sun, Feb 14, 2010 at 1:48 AM, John Launchburyj...@galois.com   
wrote:
I don't think this is a bug. I do not expect to be able to unfold  
a definition without some syntactic issues. For example,


two = 1+1
four = 2 * two

but unfolding fails (four = 2 * 1 + 1). In general, we expect to  
have to parenthesize things when unfolding them.


John


On Feb 13, 2010, at 11:56 AM, Simon Marlow wrote:


On 09/02/10 21:43, S. Doaitse Swierstra wrote:
One we start discussing syntax again it might be a good occasion  
to

reformulate/make more precise a few points.

The following program is accepted by the Utrecht Haskell  
Compiler (here

we took great effort to follow the report closely ;-} instead of
spending our time on n+k patterns), but not by the GHC and Hugs.

module Main where

-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x

-- this is a definition of the successor function using section  
notation

increment = ( one + )

-- but if we now unfold the definition of one we get a parser  
error in GHC

increment' = ( let x=1 in x + )


Now that *is* an interesting example.  I had no idea we had a bug  
in that area. Seems to me that it ought to be possible to fix it  
by refactoring the grammar, but I haven't tried yet.


Are there any more of these that you know about?

Cheers,
 Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


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


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


Re: Negation

2010-02-09 Thread S. Doaitse Swierstra
One we start discussing syntax again it might be a good occasion to  
reformulate/make more precise a few points.


The following program is accepted by the Utrecht Haskell Compiler  
(here we took great effort to follow the report closely ;-} instead of  
spending our time on n+k patterns), but not by the GHC and Hugs.


module Main where

-- this is a (rather elaborate) definition of the number 1
one = let x=1 in x

-- this is a definition of the successor function using section notation
increment = ( one + )

-- but if we now unfold the definition of one we get a parser error in  
GHC

increment' = ( let x=1 in x  +  )

The GHC and Hugs parsers are trying so hard to adhere to the meta rule  
that bodies of let-expressions
extend as far as possible when needed in order to avoid ambiguity,  
that they even apply that rule when there is no ambiguity;
here we have  only a single possible parse, i.e. interpreting the  
offending expression as ((let x = 1 in ) +).


Yes, Haskell is both a difficult language to parse and to describe  
precisely.


Doaitse


On 8 feb 2010, at 17:18, Simon Peyton-Jones wrote:


Folks

Which of these definitions are correct Haskell?

x1 = 4 + -5
x2 = -4 + 5
x3 = 4 - -5
x4 = -4 - 5
x5 = 4 * -5
x6 = -4 * 5

Ghc accepts x2, x4, x6 and rejects the others with a message like
Foo.hs:4:7:
  Precedence parsing error
  cannot mix `+' [infixl 6] and prefix `-' [infixl 6] in the  
same infix expression


Hugs accepts them all.

I believe that the language specifies that all should be rejected.  
http://haskell.org/onlinereport/syntax-iso.html


I think that Hugs is right here.  After all, there is no ambiguity  
in any of these expressions.  And an application-domain user found  
this behaviour very surprising.


I'm inclined to start a Haskell Prime ticket to fix this language  
definition bug.  But first, can anyone think of a reason *not* to  
allow all the above?


Simon


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

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


Re: [Haskell-cafe] Parsers for Text Adventures

2010-01-19 Thread S. Doaitse Swierstra
How about using one of the existing libraries, in this case uu- 
parsinglib:


module Parse where

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

data Verb = Go | Get | Jump | Climb | Give deriving (Show)

pCommand :: Pars String
pCommand = foldr (|) pFail (map str2com [(Go, G0), (Get, Get),  
(Jump, Jump), (Give, Climb), (Climb, Give)])


str2com (comm, str) = show comm $ pToken str


and then (the show is for demonstration purposes only; not the swap in  
the last two elements in the list)


*Parse :load ../Test.hs
[1 of 1] Compiling Parse( ../Test.hs, interpreted )
Ok, modules loaded: Parse.
*Parse test pCommand Go
(Go,[])
*Parse test pCommand G0
(Go,[
Deleted  '0' at position 1 expecting 'o',
Inserted 'o' at position 2 expecting 'o'])
*Parse test pCommand o
(Go,[
Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C', 'G']])
*Parse test pCommand Clim
(Give,[
Inserted 'b' at position 4 expecting 'b'])
*Parse


On 17 jan 2010, at 14:30, Mark Spezzano wrote:


Hi,

I am writing a Text Adventure game in Haskell (like Zork)

I have all of the basic parser stuff written as described in  
Hutton's Programming in Haskell and his associated papers. (I'm  
trying to avoid using 3rd party libraries, so that I can learn this  
myself)


Everything that I have works (so far...) except for the following  
problem:


I want to define a grammar using a series of Verbs like this:

data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show,  
Read)


and then have my parser get one of these Verb tokens if possible;  
otherwise it should do something (?) else like give an error message  
stating I don't know that command


Now, Hutton gives examples of parsing strings into string whereas I  
want to parse Strings into my Verbs


So, if the user types get sword then it will tokenise get as  
type Verb's data constructor Get and perhaps sword into a Noun  
called Sword


My parser is defined like this:

newtype Parser a = Parser (String - [(a, String)])

So I CAN give it a Verb type

but this is where I run into a problem

I've written a Parser called keyword

keyword :: Parser Verb
keyword = do x - many1 letter
return (read x)

(read this as take-at-least-one-alphabetic-letter-and-convert-to-a- 
Verb-type)


which DOES work provided that the user types in one of my Verbs. If  
they don't, well, the whole thing fails with an Exception and halts  
processing, returning to GHCi prompt.


Question: Am I going about this the right way? I want to put  
together lots of data types like Verb and Noun etc so that I can  
build a kind of BNF grammar.


Question: If I am going about this the right way then what do I  
about the read x bit failing when the user stops typing in a  
recognised keyword. I could catch the exception, but typing an  
incorrect sentence is just a typo, not really appropriate for an  
exception, I shouldn't think. If it IS appropriate to do this in  
Haskell, then how do I catch this exception and continue processing.


I thought that exceptions should be for exceptional circumstances,  
and it would seem that I might be misusing them in this context.


Thanks

Mark Spezzano

___
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] Parsers for Text Adventures; small typo corrected in example

2010-01-19 Thread S . Doaitse Swierstra
How about using one of the existing libraries, in this case uu- 
parsinglib:


module Parse where

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

data Verb = Go | Get | Jump | Climb | Give deriving (Show)

pCommand :: Pars String
pCommand = foldr (|) pFail (map str2com [(Go, Go), (Get, Get),  
(Jump, Jump), (Give, Climb), (Climb, Give)])


str2com (comm, str) = show comm $ pToken str


and then (the show is for demonstration purposes only; not the swap in  
the last two elements in the list)


*Parse :load ../Test.hs
[1 of 1] Compiling Parse( ../Test.hs, interpreted )
Ok, modules loaded: Parse.
*Parse test pCommand Go
(Go,[])
*Parse test pCommand G0
(Go,[
Deleted  '0' at position 1 expecting 'o',
Inserted 'o' at position 2 expecting 'o'])
*Parse test pCommand o
(Go,[
Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C', 'G']])
*Parse test pCommand Clim
(Give,[
Inserted 'b' at position 4 expecting 'b'])
*Parse


On 17 jan 2010, at 14:30, Mark Spezzano wrote:


Hi,

I am writing a Text Adventure game in Haskell (like Zork)

I have all of the basic parser stuff written as described in  
Hutton's Programming in Haskell and his associated papers. (I'm  
trying to avoid using 3rd party libraries, so that I can learn this  
myself)


Everything that I have works (so far...) except for the following  
problem:


I want to define a grammar using a series of Verbs like this:

data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show,  
Read)


and then have my parser get one of these Verb tokens if possible;  
otherwise it should do something (?) else like give an error message  
stating I don't know that command


Now, Hutton gives examples of parsing strings into string whereas I  
want to parse Strings into my Verbs


So, if the user types get sword then it will tokenise get as  
type Verb's data constructor Get and perhaps sword into a Noun  
called Sword


My parser is defined like this:

newtype Parser a = Parser (String - [(a, String)])

So I CAN give it a Verb type

but this is where I run into a problem

I've written a Parser called keyword

keyword :: Parser Verb
keyword = do x - many1 letter
return (read x)

(read this as take-at-least-one-alphabetic-letter-and-convert-to-a- 
Verb-type)


which DOES work provided that the user types in one of my Verbs. If  
they don't, well, the whole thing fails with an Exception and halts  
processing, returning to GHCi prompt.


Question: Am I going about this the right way? I want to put  
together lots of data types like Verb and Noun etc so that I can  
build a kind of BNF grammar.


Question: If I am going about this the right way then what do I  
about the read x bit failing when the user stops typing in a  
recognised keyword. I could catch the exception, but typing an  
incorrect sentence is just a typo, not really appropriate for an  
exception, I shouldn't think. If it IS appropriate to do this in  
Haskell, then how do I catch this exception and continue processing.


I thought that exceptions should be for exceptional circumstances,  
and it would seem that I might be misusing them in this context.


Thanks

Mark Spezzano

___
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


Re: [Haskell-cafe] Parsers for Text Adventures; in one line

2010-01-19 Thread S. Doaitse Swierstra

When cycling home I realised it could even be shorter:

module Parse where

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

data Verb = Go | Get | Jump | Climb | Give deriving (Show)

pCommand :: Pars Verb
pCommand = foldr (\ c r - c $ pToken (show c) | r)  pFail [Go ,  
Get , Jump , Climb , Give]



*Parse test pCommand Go
Loading package syb ... linking ... done.
Loading package base-3.0.3.1 ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package filepath-1.1.0.2 ... linking ... done.
Loading package old-locale-1.0.0.1 ... linking ... done.
Loading package old-time-1.0.0.2 ... linking ... done.
Loading package unix-2.3.2.0 ... linking ... done.
Loading package directory-1.0.0.3 ... linking ... done.
Loading package process-1.0.1.1 ... linking ... done.
Loading package random-1.0.0.1 ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package uu-parsinglib-2.3.1 ... linking ... done.
(Go,[])
se *Parse test pCommand Clim
(Climb,[
Inserted 'b' at position 4 expecting 'b'])
*Parse



On 19 jan 2010, at 17:31, S.Doaitse Swierstra wrote:

How about using one of the existing libraries, in this case uu- 
parsinglib:


module Parse where

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

data Verb = Go | Get | Jump | Climb | Give deriving (Show)

pCommand :: Pars String
pCommand = foldr (|) pFail (map str2com [(Go, Go), (Get, Get),  
(Jump, Jump), (Give, Climb), (Climb, Give)])


str2com (comm, str) = show comm $ pToken str


and then (the show is for demonstration purposes only; not the swap  
in the last two elements in the list)


*Parse :load ../Test.hs
[1 of 1] Compiling Parse( ../Test.hs, interpreted )
Ok, modules loaded: Parse.
*Parse test pCommand Go
(Go,[])
*Parse test pCommand G0
(Go,[
Deleted  '0' at position 1 expecting 'o',
Inserted 'o' at position 2 expecting 'o'])
*Parse test pCommand o
(Go,[
Inserted 'G' at position 0 expecting one of ['G', 'G', 'J', 'C',  
'G']])

*Parse test pCommand Clim
(Give,[
Inserted 'b' at position 4 expecting 'b'])
*Parse


On 17 jan 2010, at 14:30, Mark Spezzano wrote:


Hi,

I am writing a Text Adventure game in Haskell (like Zork)

I have all of the basic parser stuff written as described in  
Hutton's Programming in Haskell and his associated papers. (I'm  
trying to avoid using 3rd party libraries, so that I can learn this  
myself)


Everything that I have works (so far...) except for the following  
problem:


I want to define a grammar using a series of Verbs like this:

data Verb = Go | Get | Jump | Climb | Give etc, etc deriving (Show,  
Read)


and then have my parser get one of these Verb tokens if possible;  
otherwise it should do something (?) else like give an error  
message stating I don't know that command


Now, Hutton gives examples of parsing strings into string whereas I  
want to parse Strings into my Verbs


So, if the user types get sword then it will tokenise get as  
type Verb's data constructor Get and perhaps sword into a Noun  
called Sword


My parser is defined like this:

newtype Parser a = Parser (String - [(a, String)])

So I CAN give it a Verb type

but this is where I run into a problem

I've written a Parser called keyword

keyword :: Parser Verb
keyword = do x - many1 letter
return (read x)

(read this as take-at-least-one-alphabetic-letter-and-convert-to-a- 
Verb-type)


which DOES work provided that the user types in one of my Verbs. If  
they don't, well, the whole thing fails with an Exception and halts  
processing, returning to GHCi prompt.


Question: Am I going about this the right way? I want to put  
together lots of data types like Verb and Noun etc so that I can  
build a kind of BNF grammar.


Question: If I am going about this the right way then what do I  
about the read x bit failing when the user stops typing in a  
recognised keyword. I could catch the exception, but typing an  
incorrect sentence is just a typo, not really appropriate for an  
exception, I shouldn't think. If it IS appropriate to do this in  
Haskell, then how do I catch this exception and continue processing.


I thought that exceptions should be for exceptional circumstances,  
and it would seem that I might be misusing them in this context.


Thanks

Mark Spezzano

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


Re: [Haskell-cafe] Parsers (Parsec and Iteratee-based Parsers)

2010-01-19 Thread S. Doaitse Swierstra


On 12 jan 2010, at 00:09, Günther Schmidt wrote:


Hi John,

thanks for responding. As I said I've been using Parsec quite a lot,  
but wonder if there is a different approach possible/feasible to  
parsing. Parsec (2x) isn't an online parser, ie, it doesn't  
produce a result before the whole parse is completed.


There is AFAIK one alternative, the uulib, but at first glance it  
seemed very elaborate, so I wonder if Oleg's Iteratee offers  
something simpler.


There is the new uu-parsinglib package, which is simpler and  
documented (and being worked upon).


 Doaitse



I am not in particular looking for some sort of parsec-iteratee- 
hybrid, I'd be quite happy with something entirely based on  
Iteratee. In the Iteratee package there are 2 sample parsers, one  
for TIFF and one for WAVE files. I wish I could say that the  
accompanying documentation is sufficient for me to get the idea,  
alas it's not.


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


nomination for Haskell 2011

2009-12-23 Thread S. Doaitse Swierstra
Herewith I propose Atze Dijkstra as a member of the Haskell 2011  
committee.


Atze is the main architect/implementor of the Utrecht Haskell Compiler  
(see http://www.cs.uu.nl/wiki/UHC, and last year Haskell Symposium),  
and has as a result of that a very good insight in the implementation  
issues involved with new features/extensions/changes. He furthermore  
co-supervises Arie Middelkoop who is working on the Ruler system,  
which aims to be a tool for describing (the implementations of) type  
systems, and Jeroen Fokker who is working on a Grin-based whole- 
program analysis


The compiler itself is currently about 100.000 lines of Haskell. A  
second release is planned for the beginning of next year, which will  
contain a completely new garbage collector, a cabal based installation  
scheme, and the beginning of some global optimisations.


I think Atze primarily covers the following categories: Implementors,  
Academic users, Teachers.


If you have any questions I am more than willing to answer them,

Doaitse



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


Re: [Haskell-cafe] Wiki software?

2009-11-18 Thread S. Doaitse Swierstra

How about:

http://hackage.haskell.org/package/orchid

a simple, but nice wiki produced by one of our students Sebastiaan  
Visser,


 Doaitse Swierstra


On 18 nov 2009, at 18:14, Günther Schmidt wrote:


Hi,

I'm finally about to organize myself, somewhat.

And am going to use a wiki for it. Does there a good one exist  
that's written in Haskell?


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


[Haskell-cafe] Re: uu-parsinglib pKeyword

2009-10-28 Thread S. Doaitse Swierstra

pToken [] = pSucceed []
pToken (x:xs) = (:) $ pSym x * pToken xs

pKeyword_Float = pToken Float
etc

Doaitse

PS: this function has been defined in the module  
Text.ParserCombinators.UU.Derived




On 28 okt 2009, at 17:39, Ozgur wrote:


Hi everybody,

I am using the uu-parsinglib to parse a structured language and map
the results to some proper data structures. Thanks to Prof Doaitse
Swierstra (and other authors if any), it is fun to write a parser
using this library.

I've been sending private mails to Doaitse about my questions, who
kindly gives nice replies everytime. But this time I thought I can ask
my question to the community, and give everyone the chance to benefit
from the answers.

[After the intro, here comes my real question]

I am trying to capture the following pattern.

pKeyword_Int = ( \ _ _ _ - int ) $ pSym 'i' * pSym 'n' * pSym
't'
pKeyword_Float = ( \ _ _ _ _ _ - float ) $ pSym 'f' * pSym 'l'
* pSym 'o' * pSym 'a' * pSym 't'

As you can see there is an obvious pattern if you try to capture a
keyword. If there were a function called pKeyword taking a string as
an argument and producing the necessary parser, things would be
easier.

What I mean is,

pKeyword_Int = pKeyword int
pKeyword_Float = pKeyword float

I tried to create this pKeyword function myself but I couldn't manage
to do it.

I can feel that, one can simply add a * pReturn [] to the ends of
every parser and write a recursion with this base condition.

Any suggestions?

PS: Actually I'm a little bit uncomfortable since there may be such a
function in the library already :)


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


Re: [Haskell-cafe] What *is* a DSL?

2009-10-28 Thread S. Doaitse Swierstra


On 22 okt 2009, at 15:56, Robert Atkey wrote:




Previously parsed input /can/ determine what the parser will accept  
in
the future (as pointed out by Peter Ljunglöf in his licentiate  
thesis).

Consider the following grammar for the context-sensitive language
{aⁿbⁿcⁿ| n ∈ ℕ}:


Yes, sorry, I was sloppy in what I said there. Do you know of a
characterisation of what languages having a possibly infinite amount  
of

nonterminals gives you. Is it all context-sensitive languages or a
subset?


The answer is: all context-sensitive languages. This is a very old  
insight which has come back in various forms in computer science. The  
earliest conception in CS terms is the concept of an affix-grammar, in  
which the infinite number of nonterminals is generated by  
parameterising non-terminals by trees. They were invented by Kees  
koster and Lambert Meertens (who applied them to generate music: http://en.wikipedia.org/wiki/index.html?curid=5314967) 
 in the beginning of the sixties of the last century. There is a long  
follow up on this idea, of which the two most well-known versions are  
the so-called two-level grammars which were used in the Algol68 report  
and the attribute grammar formalism first described by Knuth. The full  
Algol68 language is defined in terms of a two-level grammar. Key  
publications/starting points if you want to learn more about these are:


 - the Algol68 report: 
http://burks.brighton.ac.uk/burks/language/other/a68rr/rrtoc.htm
 - the wikipedia paper on affix grammars: 
http://en.wikipedia.org/wiki/Affix_grammar
 - a nice book about the basics od two-level grammars is the  
Cleaveland  Uzgalis book, Grammars for programming languages, which  
may be hard to get,

 but there is hope: 
http://www.amazon.com/Grammars-Programming-Languages-languages/dp/0444001875
 - http://www.agfl.cs.ru.nl/papers/agpl.ps
 - http://comjnl.oxfordjournals.org/cgi/content/abstract/32/1/36

 Doaitse Swierstra





And a general definition for parsing single-digit numbers. This  
works
for any set of non-terminals, so it is a reusable component that  
works

for any grammar:


Things become more complicated if the reusable component is defined
using non-terminals which take rules (defined using an arbitrary
non-terminal type) as arguments. Exercise: Define a reusable  
variant of

the Kleene star, without using grammars of infinite depth.


I see that you have an answer in the paper you linked to above.  
Another

possible answer is to consider open sets of rules in a grammar:


data OpenRuleSet inp exp =
  forall hidden. OpenRuleSet (forall a. (exp :+: hidden) a -
  Rule (exp :+: hidden :+: inp) a)



data (f :+: g) a = Left2 (f a) | Right2 (g a)


So OpenRuleSet inp exp, exports definitions of the nonterminals in
'exp', imports definitions of nonterminals in 'inp' (and has a
collection of hidden nonterminals).

It is then possible to combine them with a function of type:


combineG :: (inp1 := exp1 :+: inp) -
   (inp2 := exp2 :+: inp) -
   OpenRuleSet inp1 exp1 -
   OpenRuleSet inp2 exp2 -
   OpenRuleSet inp (exp1 :+: exp2)


One can then give a reusable Kleene star by stating it as an open rule
set:


star :: forall a nt. Rule nt a - OpenRuleSet nt (Equal [a])


where Equal is the usual equality GADT.

Obviously, this would be a bit clunky to use in practice, but maybe  
more

specialised versions combineG could be given.

Bob


--
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

___
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] simple parsing

2009-10-28 Thread S. Doaitse Swierstra

Ok,

I think this is a weird problem, but let us start. You want to parse a  
sequence of operands separated by an operator (we assume the ops are  
left associative):


import Text.ParserCombinators.UU.Parsing

pWeird = pChainl pOperator pOperand

An operand is apparently a non-empty list of digits, and the result  
should be the last of these digits:


pOperand = toList.last $ pList1 (pSym ('0', '9'))
toList x = [x]

An operator is a sequence of +-/* symbols, and it is the first  
element in which you are interested:


pOperator = intoOp.head $ pList1 (pSym '+' | pSym '-' ...)

The function intoOp now builds the function which constructs the final  
list given the operator and the left and right operands:


intoOp op = \leftop rightop - leftop ++ [op] ++ rightop

 Doaitse






On 27 okt 2009, at 23:38, satorisanitarium wrote:


I'm trying to parse a list of numbers plus four diferent signs (+-*/)
in this way:

Lets say the list is 32+5/46 result would be 2+5/4
I get:

2+5/4*** Exception: geneticSimple.hs:(55,0)-(65,35): Non-exhaustive
patterns in function chromoResult

If the list is 32+5**6 result would be 2+5*6
I get:
2+5/*** Exception: geneticSimple.hs:(55,0)-(65,35): Non-exhaustive
patterns in function chromoResult

If the list is 32+-72 resoult would be 2+7
I get:
2+*** Exception: geneticSimple.hs:(55,0)-(65,35): Non-exhaustive
patterns in function chromoResult

code:

chromoResult [] = []
chromoResult (a:b:c:xs)
| elem a 0123456789  elem b 0123456789  elem c 0123456789 =
chromoResult (c:xs)
| elem a 0123456789  elem b 0123456789  elem c +-*/ = b:c:
chromoResult xs
| elem a 0123456789  elem b +-*/  elem c 0123456789 =
a:b:c : chromoResult xs
| elem a 0123456789  elem b +-*/  elem c +-*/ = a:b :
chromoResult (c:xs)
| elem a +-*/  elem b 0123456789  elem c 0123456789 =
chromoResult (b:c:xs)
| elem a +-*/  elem b 0123456789  elem c +-*/ = b:c :
chromoResult xs
| elem a +-*/  elem b +-*/  elem c 0123456789 =
chromoResult (c:xs)
| elem a +-*/  elem b +-*/  elem c +-*/ = chromoResult xs
| otherwise = chromoResult (b:c:xs)

I suspect my approach is flawed but i have exausted my ideas.
I need  a fresh approach so if anybody would be kind enough and just
give me a hint how to approach the problem.
Thx in advance.
___
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] Parsec bug, or...?

2009-10-20 Thread S . Doaitse Swierstra
After some private exchange of info between Uwe and me it became clear  
that it may not have been immediately clear that the error messages in  
my original posting where actually part of a more involved process.


By removing the optional part in the pCommand (i.e. making the part  
starting with `opt` invisible, we can show the full power of the built- 
in error correction.


import Text.ParserCombinators.UU.Parsing

pCommand [] = pure []
pCommand (x:xs) = ((:) $ pSym x * pCommand xs) -- `opt` (x:xs)

pCommands = amb . foldr (|) pFail . map pCommand $ [banana,  
chocolate, frito, fromage]


t :: String - ([String], [Error Char Char Int])
t input = parse ( (,) $ pCommands * pEnd)  (listToStr input)

Now one also gets error messages like:

*Main t frxi
([frito],[
Deleted  'x' at position 2 expecting one of ['i', 'o'],
Inserted 't' at position 4 expecting 't',
Inserted 'o' at position 4 expecting 'o'])

for free.

However, since the decision what element to take is based on a limited  
look-ahead, one also gets:


*Main t xfxrxix
([fromage],[
Deleted  'x' at position 0 expecting one of ['b', 'c', 'f', 'f'],
Deleted  'x' at position 2 expecting 'r',
Deleted  'x' at position 4 expecting 'o',
Deleted  'i' at position 5 expecting 'o',
Deleted  'x' at position 6 expecting 'o',
Inserted 'o' at position 7 expecting 'o',
Inserted 'm' at position 7 expecting 'm',
Inserted 'a' at position 7 expecting 'a',
Inserted 'g' at position 7 expecting 'g',
Inserted 'e' at position 7 expecting 'e'])
*Main

which is something not completely expected; the current look-ahead is  
however three symbols ahead, and once a decision is taken this is not  
reconsidered (for cost reasons). This is currently a consequence of  
the rather simplistic inner organisation of the intermediate library.  
In the next version we hope to have gotten rid of this artefact.


Best,
Doaitse











Yes, for my particular problem the complexity is very limited. I
wouldn't even have used parsec for this, in spite of the comment I had
made earlier about this, if I were not already using it in a different
part of the project to parse individual records (buy security foo
for this price on this date, etc), so it was natural to add a bit
more parsec code to also deal with the commands saying what I want to
see from the data. It's all still pretty trivial, but starting already
to be useful to me... it's really quite gratifying what a small amount
of haskell code suffices to make a useful and flexible program.

best regards,
Uwe

On 10/15/09, S. Doaitse Swierstra doai...@swierstra.net wrote:


On 15 okt 2009, at 16:58, Uwe Hollerbach wrote:


Hi, all, thanks for the further inputs, all good stuff to think
about... although it's going to be a little while before I can
appreciate the inner beauty of Doaitse's version! :-)


The nice thing is that you do not have to understand the inner
workings ;-} I basically builds a greedy parser for each word to be
recognised which can stop and assume the rest is there if it can no
longer proceed (the `opt` is greedy in its left alternative) . Hence
it recognises the longest possible prefix.
Since my parsers pursue all alternatives in parallel you  
automatically
get what you want, without having to indicate prefix lengths, calls  
to

try, etc.

The amb combinator has type

amb :: Parser a - Parser [a]

and collects the result from all alternatives its argument parser is
constructed from; you might say it convert an ambiguous parser to a
parser with a list as result, hence preventing the rest of the input
being parsed over and over again. I am currently working on bringing
back more abstract interpretation in the implementation (i.e. what we
have had for almost 10 years in the uulib library), but I do not
expect you to see a lot of that from the outside.

If you want to work with left-recursive parsers (which does not seem
to be the case), you may revert to more complicated solutions such as
found in the christmastree (Changing Haskell's Read Implementation
Such That by Manipulationg Abstract Syntax Trees Read Evaluates
Efficiently) package if you need to generate parsers online, or to
happy-based solutions in case your grammar is fixed.


If you have any questions do not hesitate to ask,
Doaitse



I had considered
the approach of doing a post-parsec verification, but decided I  
wanted

to keep it all inside the parser, hence the desire to match prefixes
there (and lack of desire to write 'string p | string pr |
string pre ...'.

By way of background, the actual stuff I'm wanting to match is not
food names, but some commands for a small ledger program I'm working
on. I needed something like that and was tired of losing data to
quicken every so often. I realize of course that there are other
excellent ledger-type programs out there, but hey, I also needed
another hacking project. I'll put this onto hackage in a while, once
it does most of the basics of what I need. No doubt the main
differentiator between mine

[Haskell-cafe] Lecture Notes Advanced Functional programming available

2009-10-16 Thread S. Doaitse Swierstra
I am happy to announce that the rworked lecture notes for the 6th  
Advance Functional programming summer school have become available.


For further information about the lecture notes:

 
http://www.springer.com/computer/programming/book/978-3-642-04651-3?cm_mmc=NBA-_-Oct-09_EAST_4063641-_-product-_-978-3-642-04651-3

Contents:
	• Umut Acar (Toyota Technological Institute, University of Chicago,  
USA): Self-Adjusting Computation

• Richard Bird (University of Oxford, UK): Spider Spinning
	• Olivier Danvy (University of Aarhus, DK): On deriving abstract  
machines from interpreters and calculi
	• Johan Jeuring (Utrecht University, NL): Libraries for Generic  
Programming in Haskell
	• Ulf Norell (Chalmers University, SE): Dependently Typed Programming  
in Agda
	• Simon Peyton Jones and Satnam Singh (update) (Microsoft Research,  
UK): Parallel Functional Programming
	• Rinus Plasmeijer (Radboud University Nijmegen, NL): Specifying  
Interactive Workflows for the Web


Doaitse


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


Re: [Haskell-cafe] Parsec bug, or...?

2009-10-15 Thread S. Doaitse Swierstra


On 15 okt 2009, at 16:58, Uwe Hollerbach wrote:


Hi, all, thanks for the further inputs, all good stuff to think
about... although it's going to be a little while before I can
appreciate the inner beauty of Doaitse's version! :-)


The nice thing is that you do not have to understand the inner  
workings ;-} I basically builds a greedy parser for each word to be  
recognised which can stop and assume the rest is there if it can no  
longer proceed (the `opt` is greedy in its left alternative) . Hence  
it recognises the longest possible prefix.
Since my parsers pursue all alternatives in parallel you automatically  
get what you want, without having to indicate prefix lengths, calls to  
try, etc.


The amb combinator has type

amb :: Parser a - Parser [a]

and collects the result from all alternatives its argument parser is  
constructed from; you might say it convert an ambiguous parser to a  
parser with a list as result, hence preventing the rest of the input  
being parsed over and over again. I am currently working on bringing  
back more abstract interpretation in the implementation (i.e. what we  
have had for almost 10 years in the uulib library), but I do not  
expect you to see a lot of that from the outside.


If you want to work with left-recursive parsers (which does not seem  
to be the case), you may revert to more complicated solutions such as  
found in the christmastree (Changing Haskell's Read Implementation  
Such That by Manipulationg Abstract Syntax Trees Read Evaluates  
Efficiently) package if you need to generate parsers online, or to  
happy-based solutions in case your grammar is fixed.



 If you have any questions do not hesitate to ask,
 Doaitse



I had considered
the approach of doing a post-parsec verification, but decided I wanted
to keep it all inside the parser, hence the desire to match prefixes
there (and lack of desire to write 'string p | string pr |
string pre ...'.

By way of background, the actual stuff I'm wanting to match is not
food names, but some commands for a small ledger program I'm working
on. I needed something like that and was tired of losing data to
quicken every so often. I realize of course that there are other
excellent ledger-type programs out there, but hey, I also needed
another hacking project. I'll put this onto hackage in a while, once
it does most of the basics of what I need. No doubt the main
differentiator between mine and those other excellent ledger programs
out there will be that mine has fewer features and more bugs...

thanks again, all!

Uwe


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


Re: [Haskell-cafe] Parsec bug, or...?

2009-10-14 Thread S. Doaitse Swierstra

I could not resist this. The code

import Text.ParserCombinators.UU.Parsing

pCommand [] = pure []
pCommand xxs@(x:xs) = ((:) $ pSym x * pCommand xs) `opt` xxs

pCommands = amb . foldr (|) pFail . map pCommand $ [banana,  
chocolate, frito, fromage]


t :: String - ([String], [Error Char Char Int])
t input = parse ( (,) $ pCommands * pEnd)  (listToStr input)

gives the following results:

*Main t 
([banana,chocolate,frito,fromage],[])
*Main t b
([banana],[])
*Main t fr
([frito,fromage],[])
*Main t x
([banana,chocolate,frito,fromage],[
The token 'x'was not consumed by the parsing process.])
*Main t frox
([fromage],[
The token 'x'was not consumed by the parsing process.])
*Main t frx
([frito,fromage],[
The token 'x'was not consumed by the parsing process.])
*Main

I think it is less clumsy and far less confusing than the Parsec code.  
Note that the function amb tells that its parameter parser can be  
ambiguous


 Doaitse



On 13 okt 2009, at 17:10, Uwe Hollerbach wrote:

On 10/12/09, Martijn van Steenbergen mart...@van.steenbergen.nl  
wrote:

Brandon S. Allbery KF8NH wrote:
My fix would be to have myPrefixOf require the prefix be  
terminated in

whatever way is appropriate (end of input, white space, operator?)
instead of simply accepting as soon as it gets a prefix match  
regardless

of what follows.


Maybe you can use notFollowedBy for this.

HTH,

Martijn.




Yes, I've looked at that and am thinking about it. I'm not quite
certain it's needed in my real program... I seem to have convinced
myself that if I actually specify a proper set of unique prefixes, ie,
set the required lengths for both frito and fromage to 3 in the
test program, I won't get into this situation. Assuming I haven't
committed another brain-fart there, that would be sufficient;
presumably, in a real program one would want to actually specify the
unique prefix, rather than a non-unique pre-prefix. It seems to work
fine in my real program, anyway.

Uwe
___
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: What *is* a DSL?

2009-10-12 Thread S. Doaitse Swierstra
This problem of dynamically transforming grammars and bulding parsers  
out of it is addressed in:


@inproceedings{1411296,
 author = {Viera, Marcos and Swierstra, S. Doaitse and Lempsink,  
Eelco},
 title = {Haskell, do you read me?: constructing and composing  
efficient top-down parsers at runtime},
 booktitle = {Haskell '08: Proceedings of the first ACM SIGPLAN  
symposium on Haskell},

 year = {2008},
 isbn = {978-1-60558-064-7},
 pages = {63--74},
 location = {Victoria, BC, Canada},
 doi = {http://doi.acm.org/10.1145/1411286.1411296},
 publisher = {ACM},
 address = {New York, NY, USA},
 }

and the code can be found on hackage under the name ChristmasTree
The left-factorisation is explained in a paper we presented at the  
last LDTA and which will appear in ENTCS. Since we have signed some  
copyright form I do notthink I can attach it here, but if you send me  
a mail, I can definitely send you the paper.


Doaitse


On 11 okt 2009, at 21:54, Ben Franksen wrote:


Ben Franksen wrote:

Next thing I'll try is to transform such a grammar into an actual
parser...


Which I also managed to get working. However, this exposed yet another
problem I am not sure how to solve.

The problem manifests itself with non-left-factored rules like

 Number ::= Digit Number | Digit

Translating such a grammar directly into a Parsec parser leads to  
parse
errors because Parsec's choice operator is predictive: if a  
production has
consumed any input the whole choice fails, even if alternative  
productions

would not:

*Main P.parseTest (parseGrammar myGrm) 2
parse error at (line 1, column 2):
unexpected end of input
expecting Number

Of course, one solution is to apply Parsec's try combinator to all  
choices

in a rule. But this rather defeats the purpose of using a (by default)
predictive parser in the first place which is to avoid unnecessary
backtracking.

So, a better solution is to left-factor the grammar before  
translating to

Parsec. Since we have a data representation of the grammar that we can
readily analyse and transform, this should be possible given some  
suitable

algorithm. But how is this transformation to be typed?

My first naive attempt was to define (recap: nt :: * - * is the  
type of
nonterminals, t :: * is the type of terminals a.k.a. tokens, and a  
is the

result type):


leftFactor :: Grammar nt t a - Grammar nt t a


Of course, this is wrong:  Left-factoring is expected to introduce new
nonterminals, so on the right-hand side of the type we should not  
have the

same 'nt' as on the left. Instead we shoudl have some other type that
is 'nt' extended with new constructors. Moreover, we cannot  
statically
know how many new nonterminals are added, so we cannot simply apply  
a type

function to nt. Is this solvable at all in Haskell or do I need proper
dependent types to express this?

I have very vague ideas that revolve around setting up some  
recursive type
function that on each level adds one constructor, define a common  
interface
with a (multiparam) type class and then use existential  
quantification in

the result type to hide the resulting type of nonterminals.

The next question is: Even if this turns out to be possible, isn't it
overkill? Maybe it is better to use an infinite type for the  
nonterminals
in the first place and let the grammar be a partial function? OTOH,  
the

formulation of the grammar as a function that pattern matches on the
nonterminals is very elegant.

Cheers
Ben

___
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] Designing a DSL?

2009-10-05 Thread S. Doaitse Swierstra



On 2 okt 2009, at 20:37, Jake McArthur wrote:


Günther Schmidt wrote:
And that I find to be the really tricky part, how do I *design* a  
DSL?


I once wrote a tutorial on this subject in which I explain that  
designing a DSL is not so much different from an ordinary programming  
language; the only difference is that you do not have to think about  
type systems and abstraction mechanisms. The tutorial can be found in:



@inproceedings{SwieAzSar98Braga,
	Author = {Swierstra, S. Doaitse and Azero~Alcocer, Pablo R. and  
Saraiva, Jo{\~a}o A.},
	Booktitle = {Advanced Functional Programming, Third International  
School, AFP'98},

Date-Added = {2008-07-15 17:22:15 +0200},
Date-Modified = {2009-01-16 17:35:05 +0100},
	Editor = {Swierstra, S. D. and Henriques, Pedro and Oliveira, Jos 
\'{e}},

Pages = {150-206},
Publisher = {Springer-Verlag},
Series = {LNCS},
Title = {Designing and Implementing Combinator Languages},
Volume = {1608},
Year = {1999}}

It basically describes the origins of the Utrecht Attribute Grammar  
System, uuagc, available from hackage; the basic message is that when  
you implement a language you use compiler construction tools! An  
example of this can be found in a paper Olaf Chitil and I recently  
published in the JFP:



@article{CambridgeJournals:2837460,
Author = {SWIERSTRA, S. DOAITSE and CHITIL, OLAF},
Date-Added = {2009-02-13 10:17:23 +0100},
Date-Modified = {2009-02-13 10:17:23 +0100},
Doi = {10.1017/S0956796808006990},
Eprint = {http://journals.cambridge.org/article_S0956796808006990},
Journal = {Journal of Functional Programming},
Number = {01},
Pages = {1-16},
Title = {Linear, bounded, functional pretty-printing},
	Url = {http://journals.cambridge.org/action/displayAbstract?fromPage=onlineaid=2837460fulltextType=RCfileId=S0956796808006990 
},

Volume = {19},
Year = {2009},
	Abstract = { ABSTRACT We present two implementations of Oppen's  
pretty-printing algorithm in Haskell that meet the efficiency of  
Oppen's imperative solution but have a simpler and a clear structure.  
We start with an implementation that uses lazy evaluation to simulate  
two co-operating processes. Then we present an implementation that  
uses higher-order functions for delimited continuations to simulate co- 
routines with explicit scheduling. },
	Bdsk-Url-1 = {http://journals.cambridge.org/action/displayAbstract?fromPage=onlineaid=2837460fulltextType=RCfileId=S0956796808006990 
},

Bdsk-Url-2 = {http://dx.doi.org/10.1017/S0956796808006990}}

This paper describes two implementation of a functional pretty  
printing, finally solving the problem how to do so with limited alook- 
ahead, as in Oppen's orginal paper. One of the solutions was created  
using an attribute grammar way of thinking and the attribute grammar  
can be found at the end of the technical report, and I hope that this  
example convinces you of the elegance of this approach:



@techreport{PPTr2004,
Author = {Swierstra, S.D.},
Date-Added = {2009-01-04 17:21:54 +0100},
Date-Modified = {2009-01-04 17:21:54 +0100},
Institution = {Inst. of Information and Comp. Science, Utrecht Univ.},
Note = {submitted for publication},
Number = {UU-CS-2004-025a},
Pubcat = {techreport},
	Title = {Linear, Online, Functional Pretty printing (extended and  
corrected version)},
	Urlpdf = {{http://archive.cs.uu.nl/pub/RUU/CS/techreps/CS-2004/2004-025a.pdf 
}},

Year = 2004}

In a more abstract setting your question is also How do I design a  
library, How do I design a consistent theory, and How do I model  
something. These questions are harder to answer ;-}


 Doaitse Swierstra





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


[Haskell-cafe] help with cabal; trying to escape from configuration hell

2009-09-22 Thread S. Doaitse Swierstra
I am trying to run happstack on my Mac, but unfortunately I am getting  
error messages as described in:


http://code.google.com/p/happstack/issues/detail?id=88

The cure seems to be to downgrade to network-2.2.0.1, but  
unfortunately my installed cabal depends on network-2.2.1.4.


I tried to re-install happstack using:

cabal install happstack --reinstall --constraint=network==2.2.0.2

but unfortunately the ghc happily reports to link against  
network-2.2.1.4:


...
Loading package parsec-2.1.0.1 ... linking ... done.
Loading package hsemail-1.3 ... linking ... done.
Loading package network-2.2.1.4 ... linking ... done.
Loading package SMTPClient-1.0.1 ... linking ... done.
Loading package time-1.1.4 ... linking ... done.
...

Can someone rescue me?

 Doaitse





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


[Haskell] Ph.D position, Utrecht University, the Netherlands

2009-09-08 Thread S . Doaitse Swierstra

===
Vacancy PhD student on Realizing Optimal Sharing in the Functional  
Language Implementations

Utrecht University,
The Netherlands.
===

Within the Software Technology group of the Information and Computing  
Sciences department of Utrecht University there is a vacancy for a PhD  
student to work on  the efficient implementation of functional  
languages. The position is funded by NWO, the Netherlands Organization  
for Scientific Research.


-
Project summary:

Lambda-calculus and term rewriting are models of computation lying at  
the basis of functional programming languages. Both possess syntactic  
meta-theories based on analyzing rewrite steps. Unfortunately, naive  
implementations are inefficient, since subterms are frequently copied.


To overcome this problem in both theoretical systems and actual  
implementations, duplicate work is avoided by using graph-based term  
representations, in which identical subterms can be (but not always  
are) shared. The question arises whether graph-representations and  
their reductions that are optimal in a theoretical sense can also be  
practical from an implementer's point of view. However, so far it is  
unclear whether nice theoretical ideas combine well with existing  
implementation methods. The overall-goal of this project is to answer  
this question in a back-and-forth communication between theoretical  
concepts and practical realizations. Starting points are the recent  
work on the optimal Lambdascope implementation based on context  
sharing, and the Haskell implementation developed at Utrecht University.


One of the open problems is whether the Lambdascope framework can be  
extended to efficiently represent  sets of mutually recursive  
definitions. Another, whether global program analysis can discover  
where Lambdascope-based approaches solve problems due to insufficient  
sharing. If both questions can be solved, we want to combine  
Lambdascope-based implementations with conventional frameworks, and  
investigate how efficient the resulting implementations become. The  
unique combination of the theoretical depth from the Logic department  
and the implementation skills and compiler infrastructure from the  
Computer Science department make Utrecht University the optimal  
surroundings for such a project.


-
Project leaders are Prof.dr. Doaitse Swierstra and
dr. Vincent van Oostrom (principal investigator).

The project will be executed in close cooperation between
   * the Software Technology group (http://www.cs.uu.nl/wiki/Center)  
of the Information and Computing Sciences department (http://www.cs.uu.nl/ 
)

   * and the Theoretical Philosophy group
(http://www.uu.nl/EN/faculties/Humanities/research/researchinstitutes/zeno/research/theoreticalphilosophy/Pages/default.aspx 
) of the Philosophy department (http://www.phil.uu.nl/),


and between
   * the more practically oriented PhD student and
   * the more theory oriented postdoc.
-

Requirements: Master degree in Computer Science, Logic, or equivalent.  
Good knowledge of functional programming, and several advanced  
computer science techniques. Knowledge of lambda-calculus  
implementations, Haskell, and compiler construction will be useful.  
Both theory and software development based on this should appeal to you.


Terms of employment: the PhD student should start as soon as possible,  
but no later than January 1, 2010.  The position is for four years  
(after one year there will be an evaluation), full-time. Gross salary  
starts with € 2042,-- per month in the first year and increases to €  
2612,-- in the fourth year of employment.  The salary is supplemented  
with a holiday bonus of 8% and an end-of-year bonus of 3%.  In  
addition we offer: a pension scheme, partially paid parental leave,  
facilities for child care, flexible employment conditions in which you  
may trade salary for vacation days or vice versa. Conditions are based  
on the Collective Employment Agreement of the Dutch Universities: http://www.vsnu.nl/Workstudy/Universities-as-employers-/Collective-Labour-Agreement.htm


More information:
  * about the project can be found on 
http://www.cs.uu.nl/wiki/bin/view/Center/OptimalSharing
  * about the Software Technology group on http://www.cs.uu.nl/wiki/Center
  * about the Information and Computing Sciences department on 
http://www.cs.uu.nl/
  * about this vacancy can be obtained from Doaitse Swierstra (doai...@cs.uu.nl 
,  +31 6 4613 6929).


Send your application in pdf (or another non-proprietary format)  to mailto:sciencep...@uu.nl 
	


with a cc to mailto:doai...@cs.uu.nl. on or before Sept 31, 

[Haskell-cafe] Ph.D position, Utrecht University, the Netherlands

2009-09-08 Thread S. Doaitse Swierstra

Subject: Ph.D position, Utrecht University, the Netherlands


===
Vacancy PhD student on Realizing Optimal Sharing in the Functional  
Language Implementations

Utrecht University,
The Netherlands.
===

Within the Software Technology group of the Information and Computing  
Sciences department of Utrecht University there is a vacancy for a PhD  
student to work on  the efficient implementation of functional  
languages. The position is funded by NWO, the Netherlands Organization  
for Scientific Research.


-
Project summary:

Lambda-calculus and term rewriting are models of computation lying at  
the basis of functional programming languages. Both possess syntactic  
meta-theories based on analyzing rewrite steps. Unfortunately, naive  
implementations are inefficient, since subterms are frequently copied.


To overcome this problem in both theoretical systems and actual  
implementations, duplicate work is avoided by using graph-based term  
representations, in which identical subterms can be (but not always  
are) shared. The question arises whether graph-representations and  
their reductions that are optimal in a theoretical sense can also be  
practical from an implementer's point of view. However, so far it is  
unclear whether nice theoretical ideas combine well with existing  
implementation methods. The overall-goal of this project is to answer  
this question in a back-and-forth communication between theoretical  
concepts and practical realizations. Starting points are the recent  
work on the optimal Lambdascope implementation based on context  
sharing, and the Haskell implementation developed at Utrecht University.


One of the open problems is whether the Lambdascope framework can be  
extended to efficiently represent  sets of mutually recursive  
definitions. Another, whether global program analysis can discover  
where Lambdascope-based approaches solve problems due to insufficient  
sharing. If both questions can be solved, we want to combine  
Lambdascope-based implementations with conventional frameworks, and  
investigate how efficient the resulting implementations become. The  
unique combination of the theoretical depth from the Logic department  
and the implementation skills and compiler infrastructure from the  
Computer Science department make Utrecht University the optimal  
surroundings for such a project.


-
Project leaders are Prof.dr. Doaitse Swierstra and
dr. Vincent van Oostrom (principal investigator).

The project will be executed in close cooperation between
   * the Software Technology group (http://www.cs.uu.nl/wiki/Center)  
of the Information and Computing Sciences department (http://www.cs.uu.nl/ 
)

   * and the Theoretical Philosophy group
(http://www.uu.nl/EN/faculties/Humanities/research/researchinstitutes/zeno/research/theoreticalphilosophy/Pages/default.aspx 
) of the Philosophy department (http://www.phil.uu.nl/),


and between
   * the more practically oriented PhD student and
   * the more theory oriented postdoc.
-

Requirements: Master degree in Computer Science, Logic, or equivalent.  
Good knowledge of functional programming, and several advanced  
computer science techniques. Knowledge of lambda-calculus  
implementations, Haskell, and compiler construction will be useful.  
Both theory and software development based on this should appeal to you.


Terms of employment: the PhD student should start as soon as possible,  
but no later than January 1, 2010.  The position is for four years  
(after one year there will be an evaluation), full-time. Gross salary  
starts with € 2042,-- per month in the first year and increases to €  
2612,-- in the fourth year of employment.  The salary is supplemented  
with a holiday bonus of 8% and an end-of-year bonus of 3%.  In  
addition we offer: a pension scheme, partially paid parental leave,  
facilities for child care, flexible employment conditions in which you  
may trade salary for vacation days or vice versa. Conditions are based  
on the Collective Employment Agreement of the Dutch Universities: http://www.vsnu.nl/Workstudy/Universities-as-employers-/Collective-Labour-Agreement.htm


More information:
  * about the project can be found on 
http://www.cs.uu.nl/wiki/bin/view/Center/OptimalSharing
  * about the Software Technology group on http://www.cs.uu.nl/wiki/Center
  * about the Information and Computing Sciences department on 
http://www.cs.uu.nl/
  * about this vacancy can be obtained from Doaitse Swierstra (doai...@cs.uu.nl 
,  +31 6 4613 6929).


Send your application in pdf (or another non-proprietary format)  to mailto:sciencep...@uu.nl 
	



Re: [Haskell-cafe] ANN: moe html combinator

2009-08-30 Thread S . Doaitse Swierstra


On 28 aug 2009, at 08:11, Jason Dusek wrote:


2009/08/27 Bulat Ziganshin bulat.zigans...@gmail.com:

...stop reusing Prelude operators, in particular, replace -
with $?


I have to say, the `$ do` construct is an eyesore and `- do` is a
lot easier on the eyes.

Would it introduce ambiguity in the Haskell grammar if

  foo do...

  foo case...

  foo if...

were always parsed as:

  foo (do...)

  foo (case...)

  foo (if...)


For the first two it would not make a difference, since they are  
essentially closed constructs, following the offside rule which  
inserts a } at the place where they end, so this cannot give rise to  
an ambiguous interpretetation. One might even argue that their current  
precedence level in the Haskell definition is suboptimal.
The if is a different thing, due to the absence of offside rules for  
if.


Doaitse




This is what is usually meant.

--
Jason Dusek
___
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] Parsec: using two different parser for the same string

2009-08-10 Thread S. Doaitse Swierstra
Since the uu-parsinglib also provides a monadic interface it should  
not be too difficult to provide  a Parsec interface on top of the uu- 
parsinglib combinators. so you can re-use large parts of your code. I  
expect that your parsers eventually will become simpler, since you do  
not have to add explicit control to the parsing process with try-like  
constructs.


This being said I still think that the applicative interface is to be  
preferred over the monadic interface, since it does not prohibit all  
kind of static analases of your parser (as is done in the older  
parsing library which is part of the uulib package); using the monadic  
interface for building new parsers based on results recognised thus  
far is fine, but using it just to construct a parsing result is  
overkill.


If you have any questions please let me know.

 Doaitse





On 10 aug 2009, at 00:30, Paul Sujkov wrote:


Hi Doaitse,

that is very interesting, and I'll take a precise look at the uu- 
parsinglib. Regarding my original question there exist (I believe)  
one serious problem: existing code is written exclusively using  
Parsec and it's already quite complex. At first glimpse I don't see  
an obvious way to use both libraries in one parsing module  
simulatiously. However, these are a very good news indeed, thank you


2009/8/9 S. Doaitse Swierstra doai...@swierstra.net
The uu-parsinglib:

http://hackage.haskell.org/packages/archive/uu-parsinglib/2.2.0/doc/html/Text-ParserCombinators-UU-Core.html

contains a combinator to achieve just this:

-- parsing two alternatives and returning both rsults
pAscii =  pSym ('\000', '\254')
pIntList   =  pParens ((pSym ';') `pListSep` (read $ pList  
(pSym ('0', '9'

parseIntString =  pList (pAscii)

parseBoth = pPair pIntList parseIntString

pPair p q =  amb (Left $ p | Right $ q)


The amb combinator tells you that it's parser parameter is  
ambiguous, and returns you all the possible results. Amazingly it  
still maintains its online behaviour. The only problem is that if  
either one of the parsers fails then you will get only a single  
result.


I have added the code above to the Examples.hs contained in the uu- 
parsinglib (so it will show up in due time when I release a new  
version) which I am attaching. Just load this file, and call the  
function main to see what are the results of the different parsers  
and correction strategies. The only problem is that if either one of  
the parsers  fails you will only get one of the results. If both  
fail you will get the result which fails latest and if both fail at  
the same place, the one which fails with the least repair costs.


If you really want both results, even if the input is erroneaous,  
things become more complicated, especially if you want to embed this  
parser in a larger one, since then we have to check whether both  
parse the same prefix. If needed I could put some work into this, by  
making a slightly different version of the amb combinator.


 Doaitse




On 6 aug 2009, at 21:03, Dan Weston wrote:

Paul,

Arrows (and category theory in general) are interesting, but you  
certainly don't need to understand them for this.
The only arrow in this code is the lowly function arrow (-). ()  
and (|||) are duals of each other and mean, respectively, both and  
either (though for some bizarre reason, both is usually called  
fanout!)


This style of pointfree (or pointless) code is clearer to me  
because I don't have a bunch of variable names to invent and have  
lying around.


Anyway, if you prefer, don't import Control.Arrow at all, and just  
use:


-- |Both: Apply two functions to same argument and tuple the results
infixr 3 
() :: (a - b) - (a - c) - a - (b,c)
(f  g) x = (f x, g x)

-- |Either: If argument is Left, apply Left function, else apply  
Right function

infixr 2 |||
(|||) :: (a - c) - (b - c) - Either a b - c
(|||) = either

either is implicitly imported from the Prelude and is defined as:

-- | Case analysis for the 'Either' type.
-- If the value is @'Left' a@, apply the first function to @a@;
-- if it is @'Right' b@, apply the second function to @b...@.
either  :: (a - c) - (b - c) - Either a b - c
either f _ (Left x) =  f x
either _ g (Right y)=  g y

Dan

Paul Sujkov wrote:
Hi Dan,
thank you for the solution. It looks pretty interesting and usable,  
however I'll have to spend some time understanding arrows: I never  
had an opportunity to use them before. Anyway, it looks very close  
to what I actually need, and in any case much less ugly than  
breaking the GenParser encapsulation
2009/8/6 Dan Weston weston...@imageworks.com mailto:weston...@imageworks.com 


  Of course, since ParsecT s u m is a functor, feel free to use fmap
  instead of parsecMap. Then you don't need to import from
  Text.Parsec.Prim.
  And in hindsight, I might prefer the name (:) or cons to () for
  the first function, but now I'm just obsessing. :)
  Dan
  Dan Weston wrote:
  I

Re: [Haskell-cafe] Parsec: using two different parser for the same string

2009-08-09 Thread S. Doaitse Swierstra

The uu-parsinglib:

http://hackage.haskell.org/packages/archive/uu-parsinglib/2.2.0/doc/html/Text-ParserCombinators-UU-Core.html

contains a combinator to achieve just this:

-- parsing two alternatives and returning both rsults
pAscii =  pSym ('\000', '\254')
pIntList   =  pParens ((pSym ';') `pListSep` (read $ pList (pSym  
('0', '9'

parseIntString =  pList (pAscii)

parseBoth = pPair pIntList parseIntString

pPair p q =  amb (Left $ p | Right $ q)


The amb combinator tells you that it's parser parameter is ambiguous,  
and returns you all the possible results. Amazingly it still maintains  
its online behaviour. The only problem is that if either one of the  
parsers fails then you will get only a single result.


I have added the code above to the Examples.hs contained in the uu- 
parsinglib (so it will show up in due time when I release a new  
version) which I am attaching. Just load this file, and call the  
function main to see what are the results of the different parsers and  
correction strategies. The only problem is that if either one of the  
parsers  fails you will only get one of the results. If both fail you  
will get the result which fails latest and if both fail at the same  
place, the one which fails with the least repair costs.


If you really want both results, even if the input is erroneaous,  
things become more complicated, especially if you want to embed this  
parser in a larger one, since then we have to check whether both parse  
the same prefix. If needed I could put some work into this, by making  
a slightly different version of the amb combinator.


 Doaitse



On 6 aug 2009, at 21:03, Dan Weston wrote:


Paul,

Arrows (and category theory in general) are interesting, but you  
certainly don't need to understand them for this.
The only arrow in this code is the lowly function arrow (-). ()  
and (|||) are duals of each other and mean, respectively, both and  
either (though for some bizarre reason, both is usually called  
fanout!)


This style of pointfree (or pointless) code is clearer to me  
because I don't have a bunch of variable names to invent and have  
lying around.


Anyway, if you prefer, don't import Control.Arrow at all, and just  
use:


-- |Both: Apply two functions to same argument and tuple the results
infixr 3 
() :: (a - b) - (a - c) - a - (b,c)
(f  g) x = (f x, g x)

-- |Either: If argument is Left, apply Left function, else apply  
Right function

infixr 2 |||
(|||) :: (a - c) - (b - c) - Either a b - c
(|||) = either

either is implicitly imported from the Prelude and is defined as:

-- | Case analysis for the 'Either' type.
-- If the value is @'Left' a@, apply the first function to @a@;
-- if it is @'Right' b@, apply the second function to @b...@.
either  :: (a - c) - (b - c) - Either a b - c
either f _ (Left x) =  f x
either _ g (Right y)=  g y

Dan

Paul Sujkov wrote:

Hi Dan,
thank you for the solution. It looks pretty interesting and usable,  
however I'll have to spend some time understanding arrows: I never  
had an opportunity to use them before. Anyway, it looks very close  
to what I actually need, and in any case much less ugly than  
breaking the GenParser encapsulation
2009/8/6 Dan Weston weston...@imageworks.com mailto:weston...@imageworks.com 


   Of course, since ParsecT s u m is a functor, feel free to use fmap
   instead of parsecMap. Then you don't need to import from
   Text.Parsec.Prim.
   And in hindsight, I might prefer the name (:) or cons to ()  
for

   the first function, but now I'm just obsessing. :)
   Dan
   Dan Weston wrote:
   I think parsecMap does the job here:
   ---
   import Text.ParserCombinators.Parsec hiding ((|))
   import Text.Parsec.Prim(parsecMap)
   import Control.Applicative((|))
   import Control.Arrow((|||),())
   -- Tagged (:)
   () :: Either Char Char - Either String String - Either
   String String
   Left  a  Left  b = Left  (a:b)
   Left  a  Right b = Left  (a:b)
   Right a  Left  b = Left  (a:b)
   Right a  Right b = Right (a:b)
   -- Tagged concat
   stringParser :: [Either Char Char] - Either String String
   stringParser = foldr () (Right )
   -- Parse Integer if properly tagged, keeping unparsed string
   maybeToInteger :: Either String String - (Maybe Integer,  
String)
   maybeToInteger = (const Nothing ||| Just . read)  (id |||  
id)

   -- Tagged-choice parser
   intOrStringParser = parsecMap (maybeToInteger . stringParser)
 $ many1 (parsecMap Right digit | parsecMap Left (noneOf  
;)))

   -- Parse between parentheses
   intOrStringListParser = between (char '(')
   (char ')')
   (sepBy1 intOrStringParser  
(char

   ';'))
   ---
   Then you get a tagged version of each string, along with the
   string itself:
   

Re: [Haskell-cafe] Possible Haskell Project

2009-06-02 Thread S. Doaitse Swierstra
The Dutch government has been trying to get something like this for  
years; parliament is asking every new minister why the promised heaven  
has not yet arrived, only to hear that more consultants are needed. I  
have been to hearings of our parliament and I can tell you such events  
are extremely informative and make you loose any hope that something  
good will come out of this soon; there are just too many stakeholders,  
and no so-called problem-owners except you. Simple questions asked,  
for which there often is no answer is:


 - who owns the information?
 - are you allowed to change information which you own?
 - should docters pay for the right to enter information in this  
system, or be paid for the service they provide if they enter  
information?


Instead of trying to change the world you may run a small wiki (I run  
Twiki) server on your home machine where you just store the  
information you collect, and enter your information while you are  
having a consult through your iPhone! When you leave the room you ask  
your docter whether what you have entered is a correct view of this  
situation ;-}I think this will solve the major part of your problem,  
and maybe it opens the eyes of the medical establishment.


 Doaitse Swierstra




On 2 jun 2009, at 11:18, wren ng thornton wrote:


Tom Hawkins wrote:

At the core, the fundamental problem is not that complicated.  It's
just storing and retrieving a person's various health events:
checkups, prescriptions, procedures, test results, etc.  The main
technical challenges are database distribution and patient security.
Both are fun problems, and our friends at Galios continue to show how
effective Haskell is at building secure systems.
Any thoughts?  Ideas?


Actually, it's a lot more complicated than that, albeit not for  
technical reasons. There's a great deal of legislation about what  
can and cannot be done with medical records: who can have access to  
them, under what circumstances, how they can be transmitted, stored,  
etc. This is more than just boilerplate code--- clinics can be  
audited to prove proper handling and can loose their licenses or  
worse for improper handling of records. Additionally, the requisite  
formats do require a lot of boilerplate code since the protocols  
were defined back in the paper age and medical legislation moves at  
the speed of mountains.


I worked briefly on an open-source database project for managing a  
medical clinic's records (so, not even for dealing with the public  
in any way). The technical feat isn't that difficult, as you say,  
but the human engineering involved can be quite complex--- and the  
human programming will have major effects on the design, in order to  
forbid invalid or unacceptable behavior. It's not a project to  
undertake lightly or without corporate funding.


Medical record management is a market that has very low penetration  
from the F/OSS movement, which in turn places a burden on smaller  
clinics, so I'm all for anyone who's willing to invest in an open  
solution :)


--
Live well,
~wren
___
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] ANN: new version of uu-parsinglib

2009-06-01 Thread S. Doaitse Swierstra
And rename empty to fail? You managed to confuse me since I always  
use pSucceed to recognise the empty string.


 Doaitse


On 1 jun 2009, at 01:21, Ross Paterson wrote:


On Sun, May 31, 2009 at 09:40:38PM +0200, S. Doaitse Swierstra wrote:
A new version of the uu-parsinglib has been uploaded to hackage. It  
is

now based on Control.Applicative where possible.

Be warned that functions like some and many will be redefined in the
future.


Perhaps we should make some and many methods of Alternative, * and *
methods of Applicative and $ a method of Functor, all with the  
current

definitions as defaults.  (John Meacham was also asking for the first
of these.)
___
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] ANN: new version of uu-parsinglib

2009-05-31 Thread S. Doaitse Swierstra
A new version of the uu-parsinglib has been uploaded to hackage. It is  
now based on Control.Applicative where possible.


Be warned that functions like some and many will be redefined in the  
future.


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


[Haskell-cafe] Re: Lazy Parsing

2009-05-31 Thread S . Doaitse Swierstra

Dear Gunther,


I am providing my solution, on which one can of course specialise in  
making sure that a valid date is parsed, which would be a bit more  
cumbersome; how should e.g. error correction be done. I prefer to test  
afterwards in such situations.


Best,
Doaitse



module Guenther where
import Text.ParserCombinators.UU.Parsing
import Text.ParserCombinators.UU.BasicInstances
import Text.ParserCombinators.UU.Examples hiding (main)
import Control.Applicative hiding ((*), (*), ($))

{- The first decision we have to make is what kind of input we are  
providing. The simplest case is just to assume simple characters,  
hence for our input type we will use the standard provided stream of  
Characters: Str Char, so we use the type of our parsers to be the type  
used  in the Examples module; since we do not know whether we wil be  
using the parsers in a monadic mode too we stay on the safe side ans  
use the type P_m -}


type GP a = P_m (Str Char) a  -- GP stands for GuenterParser

{- Once we know that our input contains characters, but that in our  
output we what to have integer values, we start out by building a  
parser for a single integer , for which we use the function pNatural  
form the examples-}


pDate = (,,) $ pNatural * pDot * pNatural * pDot *  
(pNatural ::GP Int)

pDot  = pSym '.'
{-
main = do print (test pDate 3.4.1900)
  print (test pDate 3 4 1900)
  print (test pDate ..1900)-}

-- end of Module Guenther

By playing with insertion and deletion costs (e.g. by building a more  
picky pNatural) one can control the error recovery. Another option to  
get better error recovery would be to define a specialised instance of  
Provides which removes spaces. You might even temporarily pSwitch to  
the use of this state





Period.

I do not even manage to write a parser for even a mere digit or a  
simple character. I have read the tutorial from a to a to z and from  
z to a and there were a few words I recognized.


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 :).


I am guessing here that when one does define a parsing function,  
since all the parser combinators aren't function but methods, one  
*must* also provide a type signature so that the compiler knows the  
actual *instance* method?



Günther


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


Re: [Haskell-cafe] Lazy Parsing

2009-05-29 Thread S. Doaitse Swierstra
Lazy parsing has been the default for the last ten years in uulib, and  
is now available in the simple uu-parsinglib (http://hackage.haskell.org/cgi-bin/hackage-scripts/package/uu-parsinglib 
). The whole design of the latter in described in a technical report  
to which references are given on the web page. It provides also error  
correction, the ability to use several different kinds of input  
tokens, and (with some help) ambiguities. If speed is an issue you can  
insert extra hints which locally change the breadth-first parsing  
process locally into a somewhat more depth-first form. When compared  
with Parsec the good news is that usually you do not have to put  
annotations to get nice results.


The older uulib version also performs an abstract interpretation which  
basically changes the search for which alternative to take from a  
linear to a logarithmic complexity, but does not provide a monadic  
structure, in which you use results recognised thus far to construct  
new parsers.


Both the old uulib version and the new version have always had an  
applicative interface.


In the near future elements of the abstract interpretation of the old  
uulib version will migrate into the new version. It is the advent of  
GADT's which made this new version feasable.


An example of the error correction at work at the following example  
code:


pa, pb, paz :: P_m (Str  Char) [Char]
pa = lift $ pSym 'a'
pb = lift $ pSym 'b'
p ++ q = (++) $ p * q
pa2 =   pa ++ pa
pa3 =   pa ++ pa2

pCount p = (\ a b - b+1) $ p * pCount p | pReturn 0
pExact 0 p = pReturn []
pExact n p = (:) $ p * pExact (n-1) p

paz = pMany (pSym ('a', 'z'))

paz' = pSym (\t - 'a' = t  t = 'z', a .. z, 'k')

main :: IO ()
main = do print (test pa a)
  print (test pa b)
  print (test pa2 bbab)
  print (test pa ba)
  print (test pa aa)
  print (test  (do  l - pCount pa
pExact l pb) aaacabbb)
  print (test (amb ( (++) $ pa2 * pa3 | (++) $ pa3  
* pa2))  aaabaa)

  print (test paz ab1z7)
  print (test paz' m)
  print (test paz' )


is

loeki:~ doaitse$ ghci -package uu-parsinglib
GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer ... linking ... done.
Loading package base ... linking ... done.
Loading package syb ... linking ... done.
Loading package array-0.2.0.0 ... linking ... done.
Loading package filepath-1.1.0.1 ... linking ... done.
Loading package old-locale-1.0.0.1 ... linking ... done.
Loading package old-time-1.0.0.1 ... linking ... done.
Loading package unix-2.3.1.0 ... linking ... done.
Loading package directory-1.0.0.2 ... linking ... done.
Loading package process-1.0.1.1 ... linking ... done.
Loading package random-1.0.0.1 ... linking ... done.
Loading package haskell98 ... linking ... done.
Loading package uu-parsinglib-2.0.0 ... linking ... done.
Prelude :m Text.ParserCombinators.UU.Examples
Prelude Text.ParserCombinators.UU.Examples main
(a,[])
(a,[
Deleted  'b' at position 0 expecting one of ['a'],
Inserted 'a' at position 1 expecting one of ['a']])
(aa,[
Deleted  'b' at position 0 expecting one of ['a'],
Deleted  'b' at position 1 expecting one of ['a'],
Deleted  'b' at position 3 expecting one of ['a'],
Inserted 'a' at position 4 expecting one of ['a']])
(a,[
Deleted  'b' at position 0 expecting one of ['a']])
(a,[
The token 'a'was not consumed by the parsing process.])
([b,b,b,b],[
Deleted  'c' at position 3 expecting one of ['a','b'],
Inserted 'b' at position 8 expecting one of ['b']])
([a],[
Deleted  'b' at position 3 expecting one of ['a','a']])
(abz,[
Deleted  '1' at position 2 expecting one of ['a'..'z'],
The token '7'was not consumed by the parsing process.])
('m',[])
('k',[
Inserted 'k' at position 0 expecting one of [a .. z]])
Prelude Text.ParserCombinators.UU.Examples

Doaitse Swierstra





On 27 mei 2009, at 01:52, GüŸnther Schmidt wrote:


Hi all,

is it possible to do lazy parsing with Parsec? I understand that one  
can do that with polyparse, don't know about uulib, but I happen to  
be already somewhat familiar with Parsec, so before I do switch to  
polyparse I rather make sure I actually have to.


The files it has to parse is anywhere from 500 MB to 5 GB.


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] Lazy Parsing

2009-05-29 Thread S. Doaitse Swierstra
In the uu-parsinglib we actually have two versions of parsers: lazy  
ones and strict ones, which have different types. So by giving a type  
annotation you can select the one you want. Notice that in the left- 
hand side of a monadic construct it does not make sense to use a lazy  
parser, since its result will be used as a parameter to the right-hand  
side operator, so in case of a monad our library system automagically  
selects the strict version for the left hand side. For the right hand  
side it depends on the type of the overall expression. Unfortunately  
in Haskell both the left and right hand side of a bind need the to be  
elements of the same monad, whereas in the case of a lazy oevrall  
parser this is not the case.  We solve this problem by tupling the two  
parsers (NOT the parsing results), so still the do-notation can be used.


The use of the library is free of any trickery!

Doaitse Swierstra


On 28 mei 2009, at 11:41, Malcolm Wallace wrote:


Henning Thielemann schlepp...@henning-thielemann.de wrote:


I don't think that it is in general possible to use the same parser
for lazy and strict parsing, just because of the handling of parser
failure.


Polyparse demonstrates that you can mix-and-match lazy parsers with
strict parsers in the different parts of a grammar (by choosing  
whether
to use applicative or monadic style).  You can also switch between  
lazy

or strict interpretations of the applicative parts of your grammar (by
changing the import that decides which version of the parser  
primitives

is in scope).

I also used polyparse for lazy parsing, but I found it unintuitive  
how

to make a parser lazy.


It can certainly be tricky, and requires a certain amount of
experimentation.  I think the difficulties are mainly due to the mix  
of

lazy (applicative) and strict (monadic) styles in different
non-terminals.  A parser that you intend to be lazy, may turn out to  
be
stricter than you hope, because of the strictness of another parser  
that

it depends upon.

Regards,
   Malcolm
___
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] Writing a compiler in Hakell

2009-05-06 Thread S. Doaitse Swierstra

Dear Rouan,

on

http://www.cs.uu.nl/wiki/HUT/WebHome

you will find a collection of tools which may help you to construct a  
compiler. As an example you will find a Tiger compiler constructed  
with the uulib tools and the uuagc attribute grammar system. Tiger is  
the language used in the book series by Andrew Apple. Not that Tiger  
is a great language, but the compiler contains an instance of all the  
things that have to be done when writing a compiler.


Once you like these tools you may take a look at the UHC compiler,  
which actually is a series of compilers, starting from a small  
language, which is than gradually extended, both with new language  
concepts and with new aspects, such as code generation, new forms of  
types etc. Here you will also see that writing a compiler for a  
language like Haskell is not a small endeavour.


You said you wanted to write a compiler in Haskell, but you did not  
say what language you want to compile? This sounds a bit strange: I  
have chosen my tool, but now I am going to decide what to use it for?


With respect to your question about the + operator. There are many  
answers to this question; but it depends on what language you are  
compiling, with which goal in mind etc. It makes a big difference  
whether you are compiling a language like Perl into some byte-code  
language which is to be interpreted in which case your aproach looks  
reasaonable, or a special purpose language describing finite state  
machines into code for an embedded system in which case your approach  
does not work out.


 Doaitse Swierstra







On 6 mei 2009, at 08:07, Rouan van Dalen wrote:



Hi everyone.

I am designing my own programming language.

I would like to know what is the best way to go about writing my  
compiler in haskell.
What are the tools available in haskell that can help with compiler  
construction?


I know about Happy.  Is that a good tool to use?

The compiler is intended for serious use and I would like it to be  
very efficient, maybe competing
with compilers written in C.  It should also be very easy to extend  
as the languoge grows.


Are there any good books that you can recommend on compiler  
construction in general and specific to haskell?



On another note, how is the operator + implemented in haskell?

is there a primitve (say #+) that is wrapped by the haskell operator  
+?

Maybe something like:

(+) :: a - a - a
v1 + v2 = #+ v1 v2




Thanks in advance

Rouan.




___
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] ANNOUNCE: uu-parsinglib-2.0.0

2009-04-28 Thread S. Doaitse Swierstra
The new uu-parsinglib package is the first version of the new parsing  
combinator library package from Utrecht University.


Features:
  - online result construction
  - much simpler internals than the combinators in the uulib package,  
because of the availabilty of GADT's and other extensions

which have become available over the last ten years
  - error correction
  - parsing ambiguous grammars (even with online result  
construction), provided one is willing to label a non-terminal as  
ambiguous
  - monadic interface. We solve a problem in the Polish parsing  
monadic construct, which could lead to a black hole in combination with

error correction
  - instead of trying to make everything a parameter we rely a bit  
more on the user to provide some basic functions, based on given

canonical implementations
  - no abstract interpretation yet, as found in the original uulib  
package. So if you have large grammars with many alternatives

the uulib package is to be preferred
  - extensive motivation and documentation found in a technical  
report  available from the web page


Cons:
  - the package is likely to change and be extended in the near  
future as we incorprorate more of the uulib library into the new package


Pros:
  - suggestions are welcome

 Doaitse Swierstra





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


Re: [Haskell-cafe] Question about implementing an off-side rule in Parsec 2

2009-04-28 Thread S. Doaitse Swierstra
As Lennart said, the complete offside rule as found in Haskell is  
almost impossible to get right. This is mainly due to the way in which  
it is formulated: in terms of error correction. This makes it very  
difficult to build a parser for such rules which have error correction  
built into them. We need to do a kind of open brain surgery to get  
this working. Note that the GHC treats the offside rule even a bit  
different in case it is caused by the do notation, in which case the  
indentation does not have to be greater, but has to be just at least  
as great as the previous indentation.


In the uulib package you will find a module which handles the offside  
parsing as we understand it; you may take it as an object of study. We  
use it in the UHC and we managed to compile almost all the basic  
libraries with it (with the exception of the do's mention above, which  
we had to give some extra indentation).  It basically follows the  
suggestion made by Lennart in this thread, by redefining the input  
state which is being maintained.


I understand that you try to build an Occam compiler. Fortunately the  
offside rule for Occam is much simpler, and resembles closely the  
Miranda rule.


I uploaded a new version of our parser combinators (uu-parisnglib) to  
Hackage, which is well documented in an associated tutorial. I think  
it could give you a good starting point. Note however that the library  
is far from stable, and will be extended in the near future. E.g. with  
a pBlock as we have in the uulib library to deal with the offside  
rule ;-}


 Hope you enjoy jumping into the deep,

 Doaitse Swierstra






On 28 apr 2009, at 22:03, Bas van Gijzel wrote:


Hey,

Thanks for the help thusfar. These are interesting suggestions, and  
I think the occam-pi compiler would help a bit as example. I'll  
force myself to learn some more about the state monad, but I haven't  
found really good examples except in Real World Haskell until now so  
I hope I'll manage. I'll keep you posted about my further progress.


Cheers,

Bas

On Tue, Apr 28, 2009 at 2:04 PM, Neil Brown nc...@kent.ac.uk wrote:
Bas van Gijzel wrote:
Hello everyone,

I'm doing a bachelor project focused on comparing parsers. One of  
the parser libraries I'm using is Parsec (2) and I'm going to  
implement a very small subset of haskell with it, with as most  
important feature the off-side rule (indentation based parsing) used  
in function definitions and possibly in where clauses.


But I'm still a bit stuck on how to implement this cleanly. I tried  
to search for some examples on blogs but I haven't found anything  
yet. As far as I can see the way to go would be using getState and  
updateState methods defined in Parsec.Prim and to use the methods in  
Parsec.Pos to compare the difference in indendation for tokens.


But I haven't completely wrapped my head around any state monad yet  
and I don't understand Parsec enough yet to see how to use the  
methods Parsec.Pos and state easily. Some examples or pointers to  
something to read would really be helpful.

Hi,

I work on a compiler for occam-pi, which has indentation-based  
syntax.  It's regular (two-spaces per indent) rather than different- 
number-of-spaces, and line continuations can only follow certain  
tokens, but perhaps our code might help you.


We use alex for tokenising and parsec for parsing.  We tokenise the  
file, and then use the source positions to create indent/outdent  
tokens in the token stream, and after that the parser parses things  
like a PAR block as: do {reserved PAR; indent; many1 subItem;  
outdent}.  Our code can be found at:


http://offog.org/darcs/tock/

Look in the frontends subdirectory, particularly at  
StructureOccam.hs, but also LexOccam.x and ParseOccam.hs.  It may  
not be the most elegant way to do things (occam has all sorts of  
oddities that make parsing a pain), but it does work :-)


Thanks,

Neil.

___
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: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-24 Thread S. Doaitse Swierstra
Unfortunately I think 4 man years is definitely below the minimum of  
the guesses I would get if I would ask the people in my group ;-}


 Doaitse

On 23 apr 2009, at 16:13, John A. De Goes wrote:



Let's turn this around. You invest 4 months of your life coming out  
with your own experimental Haskell compiler designed to easily test  
new language features. Then a bunch of ungrateful wretches on  
Haskell Cafe demand that you stop distributing your compiler until  
you have full support for Haskell 98. :-)


Do you think that's fair?

Regards,

John A. De Goes
N-BRAIN, Inc.
The Evolution of Collaboration

http://www.n-brain.net|877-376-2724 x 101

On Apr 23, 2009, at 3:18 AM, Jon Fairbairn wrote:


John A. De Goes j...@n-brain.net writes:


That's absurd. You have no way to access private source
code, so any  decision on what features to exclude from
future versions of Haskell  must necessarily look at
publicly accessible source code.


This is all entirely beside the point. The question is not
whether n+k patterns should be in the language, it's whether
an implementation of Haskell 98 should include them.


The only alternative is to continuously add, and never
remove, features from Haskell, even if no one (that we
know) uses them.


But we can remove them in future language versions. The
point I was trying to make at the beginning of this
subthread was that implementations should follow the
definition, because having a core language (Haskell 98) that
can be relied on is simpler and wastes less time than the
alternative.

--
Jón Fairbairn jon.fairba...@cl.cam.ac.uk
http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html  (updated  
2009-01-31)


___
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


Re: [Haskell-cafe] Re: ANNOUNCE: Utrecht Haskell Compiler (UHC) -- first release

2009-04-21 Thread S. Doaitse Swierstra
Maybe it has gone unnoticed, but the main reason we made the compiler  
available, was to make it possible for others to experiment with its  
type extensions, its Grin based back-end and  to show the advantages  
(and disadvantages?) of generating large part of the compiler from an  
attribute grammar based descriptions.


If we had been interested in raising fierce discussions about n+k  
patterns or how and where cabal installs things, we could have easily  
achieved the same effect with much less effort.


 Doaitse Swierstra








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


Re: [Haskell-cafe] Re: Haskell and C++ program

2009-01-19 Thread S. Doaitse Swierstra


On 17 jan 2009, at 22:22, Derek Elkins wrote:


On Thu, 2009-01-15 at 13:40 +0100, Apfelmus, Heinrich wrote:

Eugene Kirpichov wrote:

Well, your program is not equivalent to the C++ version, since it
doesn't bail on incorrect input.


Oops. That's because my assertion

  show . read = id

is wrong. We only have

  read . show  = id
  show . read = id  (in the less defined than sense)


No, you only have
read . show = id which often doesn't hold in practice.
show . read /= id


You do not even have that; the read may remove surplus parentheses  
which will not be reinserted by the show.


 Doaitse





Assuming the first identity holds, you do of course have show . read .
show = show and this probably holds even in most cases where read .  
show

= id does not hold.


___
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] [Announce] TTTAS (with excuse for second attempt to post)

2008-12-07 Thread S. Doaitse Swierstra


We are pleased to announce the availability of the package TTTAS,  
which contains the code associated with our paper at the coming TLDI  
workshop:


[EMAIL PROTECTED] BSV09,
author = {Arthur Baars and S. Doaitse Swierstra and Marcos Viera},
title  = {Typed Transformations of Typed Abstract Syntax},
booktitle = {TLDI '09: fourth ACM SIGPLAN Workshop on Types in  
Language Design and Implementation},

year = {2009},
location = {Savannah, Georgia, USA},
publisher = {ACM},
address = {New York, NY, USA},
}

For more information see: http://www.cs.uu.nl/wiki/bin/view/Center/TTTAS

  Arthur Baars
  Marcos Viera
  Doaitse Swierstra


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


[Haskell] ANNOUNCE: ChristmasTree 0.1 (excuses for second attempt)

2008-12-07 Thread S . Doaitse Swierstra
We are pleased to announce the availability of the package  
ChristmasTree, which contains the code associated with our paper at  
the last Haskell symposium:


@inproceedings{1411296,
author = {Marcos Viera and S. Doaitse Swierstra and Eelco Lempsink},
title = {Haskell, do you read me?: constructing and composing  
efficient top-down parsers at runtime},
booktitle = {Haskell '08: Proceedings of the first ACM SIGPLAN  
symposium on Haskell},

year = {2008},
isbn = {978-1-60558-064-7},
pages = {63--74},
location = {Victoria, BC, Canada},
doi = {http://doi.acm.org/10.1145/1411286.1411296},
publisher = {ACM},
address = {New York, NY, USA},
}
The name of the package stands for:
   Changing Haskell's Read Implementation Such That by Manipulating  
Abstract Syntax Trees it Reads Expressions Efficiently

which, given the time of year, seems appropriate.

Feel free to download and unpack this present at what for the Dutch  
is called Sinterklaasavond (http://en.wikipedia.org/wiki/Sinterklaas),


  Arthur Baars
  Marcos Viera
  Eelco Lempsink
  Doaitse Swierstra

PS: the package uses our library supporting transformation of typed  
abstract syntax, which we placed in a separate package TTTAS

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


[Haskell-cafe] [Announce] TTTAS (with excuse for second attempt to post)

2008-12-07 Thread S. Doaitse Swierstra


We are pleased to announce the availability of the package TTTAS,  
which contains the code associated with our paper at the coming TLDI  
workshop:


[EMAIL PROTECTED] BSV09,
author = {Arthur Baars and S. Doaitse Swierstra and Marcos Viera},
title  = {Typed Transformations of Typed Abstract Syntax},
booktitle = {TLDI '09: fourth ACM SIGPLAN Workshop on Types in  
Language Design and Implementation},

year = {2009},
location = {Savannah, Georgia, USA},
publisher = {ACM},
address = {New York, NY, USA},
}

For more information see: http://www.cs.uu.nl/wiki/bin/view/Center/TTTAS

  Arthur Baars
  Marcos Viera
  Doaitse Swierstra


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


[Haskell-cafe] [Haskell] ANNOUNCE: ChristmasTree 0.1 (excuses for second attempt)

2008-12-07 Thread S . Doaitse Swierstra
We are pleased to announce the availability of the package  
ChristmasTree, which contains the code associated with our paper at  
the last Haskell symposium:


@inproceedings{1411296,
author = {Marcos Viera and S. Doaitse Swierstra and Eelco Lempsink},
title = {Haskell, do you read me?: constructing and composing  
efficient top-down parsers at runtime},
booktitle = {Haskell '08: Proceedings of the first ACM SIGPLAN  
symposium on Haskell},

year = {2008},
isbn = {978-1-60558-064-7},
pages = {63--74},
location = {Victoria, BC, Canada},
doi = {http://doi.acm.org/10.1145/1411286.1411296},
publisher = {ACM},
address = {New York, NY, USA},
}
The name of the package stands for:
   Changing Haskell's Read Implementation Such That by Manipulating  
Abstract Syntax Trees it Reads Expressions Efficiently

which, given the time of year, seems appropriate.

Feel free to download and unpack this present at what for the Dutch  
is called Sinterklaasavond (http://en.wikipedia.org/wiki/Sinterklaas),


  Arthur Baars
  Marcos Viera
  Eelco Lempsink
  Doaitse Swierstra

PS: the package uses our library supporting transformation of typed  
abstract syntax, which we placed in a separate package TTTAS

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


[Haskell] ANNOUNCE: ChristmasTree 0.1

2008-12-05 Thread S. Doaitse Swierstra
We are pleased to announce the availability of the package  
ChristmasTree, which contains the code associated with our paper at  
the last Haskell symposium:


@inproceedings{1411296,
 author = {Marcos Viera and S. Doaitse Swierstra and Eelco Lempsink},
 title = {Haskell, do you read me?: constructing and composing  
efficient top-down parsers at runtime},
 booktitle = {Haskell '08: Proceedings of the first ACM SIGPLAN  
symposium on Haskell},

 year = {2008},
 isbn = {978-1-60558-064-7},
 pages = {63--74},
 location = {Victoria, BC, Canada},
 doi = {http://doi.acm.org/10.1145/1411286.1411296},
 publisher = {ACM},
 address = {New York, NY, USA},
 }

The name of the package stands for:
 Changing Haskell's Read Implementation Such That by  
Manipulating Abstract Syntax Trees it Reads Expressions Efficiently

which, given the time of year, seems appropriate.
Feel free to download and unpack your present at what for the Dutch is  
called Sinterklaasavond (http://en.wikipedia.org/wiki/Sinterklaas),


Arthur Baars
Marcos Viera
Eelco Lempsink
Doaitse Swierstra

PS: the package uses our library supporting transformation of typed  
abstract syntax, which we placed in a separate package TTTAS







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


[Haskell] Announce: TTTAS

2008-12-05 Thread S. Doaitse Swierstra
We are pleased to announce the availability of the package TTTAS,  
which contains the code associated with our paper at the coming TLDI  
workshop:


[EMAIL PROTECTED] BSV09,
author = {Arthur Baars and S. Doaitse Swierstra and Marcos Viera},
title  = {Typed Transformations of Typed Abstract Syntax},
booktitle = {TLDI '09: fourth ACM SIGPLAN Workshop on Types in  
Language Design and Implementation},

year = {2009},
location = {Savannah, Georgia, USA},
publisher = {ACM},
address = {New York, NY, USA},
}

For more information see: http://www.cs.uu.nl/wiki/bin/view/Center/TTTAS

   Arthur Baars
   Marcos Viera
   Doaitse Swierstra
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


new version of Parser Combinators and Syntax Macros's (beta)

2002-03-07 Thread S. Doaitse Swierstra
Title: new version of Parser Combinators and Syntax
Macros's


At:

http://www.cs.uu.nl/groups/ST/Software/UU_Parsing

you will find the latest/greatest version of our combinators,
that are:

- faster (faster than Parsec)
- correct much faster
- compute results lazily, and produce error messages online in
the IO monad while parsing
 (using unsafeInterleavedIO)
- are compatible with the syntax macro mechanism we have
implemented (beta):
 http://www.cs.uu.nl/~arthurb/index.html

Doaitse
-- 

-- 

__
S. Doaitse Swierstra, Department of Computer Science, Utrecht
University

P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands

Mail:
mailto:[EMAIL PROTECTED]

WWW: http://www.cs.uu.nl/


tel: +31 30 253 3962

fax: +31 30 251 3791

mobile: +31 6 2880 1680
__



type definition with strict products

2002-01-30 Thread S. Doaitse Swierstra
Title: type definition with strict
products


I a file that is too large to post here completely, I have
used:

type Result val s = (# val, Steps s
#)

and I get the error message:

UU_Parsing.hs:391:
 Illegal unboxed tuple
type as function argument: (# val, Steps s #)
 In the type: (# val, Steps s #)
 While checking the RHS of a type synonym
declaration `Result'
 In the type synonym declaration for
`Result'

using version The Glorious Glasgow Haskell Compilation
System, version 5.02.2.

Runningan earlier version of the compiler I get on the same file
the following error message:
ghc-5.00.2: panic! (the `impossible'
happened, GHC version 5.00.2):
 dsExpr: tuple pattern:
let {
 fail_d9jc
 = PrelErr.patError
 @ (b r,

UU_Parsing.Steps a,

UU_Parsing.Steps a,

UU_Parsing.Exp a,

UU_Parsing.Steps a)
 (PrelBase.unpackCString#
UU_Parsing.hs:735|case)
} in
 case ds_d9iL of wild_B1 { (# v, ds_d9iR #) -
 case ds_d9iR of wild_B1 {
 UU_Parsing.Best l m f r - (v, l, m, f, r);
__DEFAULT - fail_d9jc
 }
 }

Please report it as a compiler bug to
[EMAIL PROTECTED],
or http://sourceforge.net/projects/ghc/.

which is not very informative either.

My questions are:

- is this type definition really forbidden, and what does the
phrase function argument  in the error message refer
to?

- was there a restriction introduced about what one may write at
the rhs of a type defintion between version 5.00.2 and
5.02.2?

Thanks for looking into this,
Doaitse Swierstra





-- 

__
S. Doaitse Swierstra, Department of Computer Science, Utrecht
University

P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands

Mail:
mailto:[EMAIL PROTECTED]

WWW: http://www.cs.uu.nl/


tel: +31 30 253 3962

fax: +31 30 251 3791

mobile: +31 6 2880 1680
__



new version of parser combinators

2001-06-23 Thread S. Doaitse Swierstra

We have been working hard on new versions of the Parser Combinators 
and AG system, with the following improvements:

  even better error repairs
  much faster and simpler basic parsing machine
  permutation (of different types) and list combinators
  extensive reporting about repairs made and what was expected
  the possibility to manipulate your own state during parsing
   and result construction, using classed based (like monads) interfaces

As an example of the permutation combinators we parse a permutation 
of three elements:

   1) a list of 'a's
   2) a 'b'
   3) an optional 'c'

which is described by:

permtest :: Parser Char (String, Char, Char)
permtest = permute $ (,,) ~$~ pList (pSym 'a') ~*~ pSym 'b' ~*~ pOptSym 'c'

pOptSym :: Char - Parser Char Char
pOptSym x = pSym x | pSucceed '_'


which we try on several inputs resulting in:

t permtest acb
Result:
(a,'b','c')

t permtest cdaa
Errors:
Symbol 'd' before 'a' was deleted, because 'b' or ('a')* was expected.
Symbol 'b' was inserted  at end of file, because 'a' or 'b' was expected.
Result:
(aa,'b','c')

t permtest abd
Errors:
Symbol 'd' at end of file was deleted, because 'c' or eof was expected.
Result:
(a,'b','_')

t permtest 
Errors:
Symbol 'b' was inserted  at end of file, because 'c' or 'b' or ('a')* 
was expected.
Result:
(,'b','_')

The manual is still of an earlier version and will be adapted soon. 
As an example of the combinators we provide a parser for bibtex 
files, that returns the repairs made to the erroneous  entries (as 
far as we understand the bibtex format).


   I hope this is useful to you,
Doaitse Swierstra

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



strictness question

2001-03-02 Thread S. Doaitse Swierstra

I ran into a difference between GHC and Hugs. The following code:

f  (P p) ~(P q)   = P (\ k - \inp - let (((pv, (qv, r)), m), st) = 
p (q k) inp
   in  (((pv qv  , r ), m), st))

runs fine with Hugs but blows up with GHC, whereas:

f  (P p) ~(P q)   = P (\ k - \inp - let ~(~(~(pv, ~(qv, r)), m), 
st) = p (q k) inp
   in  (((pv qv  , r ), m), st))

runs fine with GHC too.

 From the Haskell manual I understand that pattern matching in "let"'s 
should be done lazily, so the addition of a collection of ~'s should 
not make a difference. Am I right with  this interpretation?

A possible source of this problem may be origination from the smarter 
GHC optimiser, but in that case the optimiser is not doing its work 
well.

Doaitse Swierstra




-- 
______
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



RE: strictness question

2001-03-02 Thread S. Doaitse Swierstra

Thanks for the prompt reply. Hugs apparently is more lazy and 
performs all the matching lazily, and that really makes a difference 
in my case.

  Doaitse

At 8:11 AM -0800 3/2/01, Simon Peyton-Jones wrote:
Strange.  You don't supply a complete program, so it's hard to
test. 

Nevertheless, the Haskell Report (Sect 3.12) specifies that
a let adds a single twiddle.  Thus

   let (x, (y,z)) = e in b

means

   let x = case e of (x,(y,z)) - x
y = case e of (x,(y,z)) - y
z = case e of (x,(y,z)) - z
   in b

And that is what GHC implements.  You get something different if you
add twiddles inside:

   let (x, ~(y,z)) = e in b

means
   let x = case e of (x,_) - x
y = case e of (_,(y,_)) - y
   etc

Adding more twiddles means less eager matching.  I don't know whether
Hugs implements this.

Simon

| -Original Message-
| From: S. Doaitse Swierstra [mailto:[EMAIL PROTECTED]]
| Sent: 01 March 2001 11:26
| To: [EMAIL PROTECTED]
| Subject: strictness question
|
|
| I ran into a difference between GHC and Hugs. The following code:
|
| f  (P p) ~(P q)   = P (\ k - \inp - let (((pv, (qv, r)), m), st) =
| p (q k) inp
|in  (((pv qv  , r ), m), st))
|
| runs fine with Hugs but blows up with GHC, whereas:
|
| f  (P p) ~(P q)   = P (\ k - \inp - let ~(~(~(pv, ~(qv, r)), m),
| st) = p (q k) inp
|in  (((pv qv  , r ), m), st))
|
| runs fine with GHC too.
|
|  From the Haskell manual I understand that pattern matching
| in "let"'s
| should be done lazily, so the addition of a collection of ~'s should
| not make a difference. Am I right with  this interpretation?
|
| A possible source of this problem may be origination from the smarter
| GHC optimiser, but in that case the optimiser is not doing its work
| well.
|
| Doaitse Swierstra
|
|
|
|
| --
| __
| ____
| S. Doaitse Swierstra, Department of Computer Science, Utrecht
| University
|P.O.Box 80.089, 3508 TB UTRECHT,   the
| Netherlands
|Mail:  mailto:[EMAIL PROTECTED]
|WWW:   http://www.cs.uu.nl/
|PGP Public Key:
http://www.cs.uu.nl/people/doaitse/
tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

-- 
______
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: GHC for Darwin?

2000-12-21 Thread S. Doaitse Swierstra

At 3:59 PM -0800 12/20/00, Ashley Yakeley wrote:
Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant
that runs on the PowerPC processor.
http://www.opensource.apple.com/projects/darwin/.

I was going to compile it myself before I remembered that compilers do
platform-specific code-generation. Duh.

--
Ashley Yakeley, Seattle WA


___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

Atze Dijkstra (mailto:[EMAIL PROTECTED]) is working on a port of the GHC 
to MacOS X. He has reached the state where he managed to compile some 
programs (e.g. our attribute grammar system and combinator libraries).

  Doaitse Swierstra
-- 
__
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Re: Extensible data types?

2000-10-20 Thread S. Doaitse Swierstra

It is exactly for reasons like these that we developped our small
attribute grammar system:

http://www.cs.uu.nl/groups/ST/Software/UU_AG/index.html

Doaitse Swiesrtra

At 7:21 AM -0200 10/20/00, José Romildo Malaquias wrote:
Hello.

I am back with the issue of extensible union types. Basically
I want to extend a data type with new value constructors.
Some members of the list pointed me to the paper

"Monad Transformers and Modular Interpreters"
Sheng Liang, Paul Hudak and Mark Jones

The authors suggest using a type constructor to express
the disjoint union of two other types:

data Either a b = Left a | Right b

which indeed is part of the Haskell 98 Prelude. Then they introduce
a subtype relationship using multiparameter type classes:

class SubType sub sup where
   inj :: sub - sup   -- injection
   prj :: sup - Maybe sub -- projection

The Either data type consructor is then used to express
the desired subtype relationshipe:

instance SubType a (Either a b) where
   inj   = Left
   prj (Left x)  = Just x
   prj _ = Nothing

instance SubType a b = SubType a (Either c b) where
   inj   = Right . inj
   prj (Right x) = prj x
   prj _ = Nothing

The authors implemented their system in Gofer, due to
restrictions in the type class system of Haskell.
But now that there are Haskell extensions to support
multiparametric type classes, that could be implemented
in Haskell.

The above code fails to type check due to instances
overlapping. Hugs gives the following error message:

ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType"
*** This instance   : SubType a (Either b c)
*** Overlaps with   : SubType a (Either a b)
*** Common instance : SubType a (Either a b)

(I did not check Gofer, but is there a way to solve these
overlapping of instances in it?)

So this is scheme is not going to work with Haskell (extended
with multiparameter type classes).

I would like hear any comments from the Haskell comunity on
this subject. Is there a workaround for the overlapping instances?

Regards.

Romildo
--
Prof. José Romildo Malaquias [EMAIL PROTECTED]
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell

--
__________
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
   P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
   Mail:  mailto:[EMAIL PROTECTED]
   WWW:   http://www.cs.uu.nl/
   PGP Public Key: http://www.cs.uu.nl/people/doaitse/
   tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



propaganda 1: Fast, Error Correcting Parsing Combinators

1999-08-23 Thread S. Doaitse Swierstra

x-richcolorparam,,/parambiggerFast, Error Correcting
Parsing Combinators


/bigger/color(Updated: Aug-19-1999)


I have placed a completely new set of parser combinators on the net at
http://www.cs.uu.nl/groups/ST/Software/Parse/.


I consider my old LL(1) combinators obsolete by now.



colorparam,,/paramWhy would you like to use these
Combinators?


/colorHave you always been intrigued by Combinator Parsers because
they allow you to:


   use the abstraction, typing and naming mechanism of Haskell

   create parsers dynamically

   keep life simple by not having to run a separate program in
order to generate a parser

   work with (limited forms of) infinite grammars


but did you not like:


   expensive backtracking implementations

   bad error reporting and error recovery properties

   my previous combinators because they required the grammar to be
LL(1)

   spurious shift-reduce conflicts reported by other parser
generating tools


then why not use my new parsing combinators? (Provided you have access
to the universal type extensions, as present in e.g. Hugs)


My parser combinators perform (without the programmer having to worry)
left-factorisation of the underlying grammar. The only restriction on
the grammar is that it should not be (neither

directly nor indirectly) left-recursive! If it is, you will soon find
out by running out of stack space. A paper describing the combinators
is in the works. Although the title above uses the word

"deterministic", this may be a bit misleading, since it is well known
fact that not all context free languages can be parsed
deterministically.


I hope this software is useful to you. If you have any comments do not
hesitate to contact me.


Doaitse Swierstra mailto:[EMAIL PROTECTED]

smaller_______
___

S. Doaitse Swierstra, Department of Computer Science, Utrecht
University

(Prof. Dr)P.O.Box 80.089, 3508 TB UTRECHT,   the
Netherlands

  Mail:  mailto:[EMAIL PROTECTED]

  WWW:   http://www.cs.uu.nl/

  PGP Public Key:
http://www.cs.uu.nl/people/doaitse/

  tel:   +31 (30) 253 3962, fax: +31 (30) 2513791

__

/smaller


/x-rich







propaganda 3: Advaced Functional Programming 3 Proceedings

1999-08-19 Thread S. Doaitse Swierstra
 Types/color it is shown in what direction functional
languages are 

most likely to develop, and what may be expected of the new type
systems to 

be introduced.


The last lecture, titled colorparam,,/paramHaskell as
an Automation Controller/color, shows 

that writing functional programs does not have to imply that one is 

bound to remain isolated from the rest of the world.  Being able to 

communicate with software written by others in a uniform way, is 

probably one of the most interesting new developments in current 

computer science.  It appears that the concept of a monad together 

with the Haskell typing rules, are quite adequate to describe the 

interface between Haskell programs and the outer world.




Doaitse Swierstra, Utrecht

Pedro Henriques, Minho

Jos\'{e} Oliveira, Minho 


Doaitse Swierstra mailto:[EMAIL PROTECTED],[EMAIL PROTECTED]

smaller__

S. Doaitse Swierstra, Department of Computer Science, Utrecht
University

(Prof. Dr)P.O.Box 80.089, 3508 TB UTRECHT,   the
Netherlands

  Mail:  mailto:[EMAIL PROTECTED]   

  WWW:   http://www.cs.uu.nl/

  PGP Public Key:
http://www.cs.uu.nl/people/doaitse/

  tel:   +31 (30) 253 3962, fax: +31 (30) 2513791

__




/smaller






Re: Monads and Linear Logic

1997-09-09 Thread S. Doaitse Swierstra

At 8:08 PM 9/3/97, Patrick Logan wrote:
I am stretching my imperative brain cells to comprehend(!) monads, and
now their relationship to linear ("unique" in Clean) objects. I have
glanced at Philip Wadler's paper, but the semantics are impenetrable
to me at this point, and I am looking at the issue from a more
"practical" point of view ("practical" in the sense of "practice",
"practitioner", not that theory is impractical!).

My impression is that monads and linear objects are used in
essentially the same way. I have explicitly read how linear objects
allow the compiler to "garbage collect" them at compile time because
the compiler knows exactly how they are used. I assume the same can be
done for monads? Is this done in the good Haskell compilers?

It has gone unnoticed by many that an assignment not only assigns a new
value to a variable, but is at the same time a form of static garbage
collection. The programmer implicitely states explicitely that the old
value is no longer of interest. This is were state-monads and
uniqueness-types coincide.

  Doaitse Swierstra


In general laymen's terms, what are the performance and expressiveness
issues in comparing monads with linear objects?

Thanks
--
Patrick Logan mailto:[EMAIL PROTECTED]
Voice 503-533-3365Fax   503-629-8556
Gemstone Systems, Inc http://www.gemstone.com

______________
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
(Prof. Dr)P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
  email: [EMAIL PROTECTED]
  WWW:   http://www.cs.ruu.nl/
  PGP Public Key: http://www.cs.ruu.nl/people/doaitse/
  tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__^___^___