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
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
I ran into the problem that for the packages which I install using
cabal install
The generated html does not contain links to the sources. This issue was raised
before in:
http://stackoverflow.com/questions/1587635/haddock-for-cabal-installed-modules
I have been looking into the documentation
en
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
At
https://gist.github.com/ckirkendall/2934374
you find solutions in many languages to a simple programming problem: the
evaluation of an expression in an environment.
I want to point your attention to the currently last three entries:
- one using the UUAGC compiler to solve the problem in
On Jan 31, 2013, at 10:47 , Jan Stolarek wrote:
> Thanks for replies guys. I indeed didn't notice that there are monads and
> applicatives used in
> this parser. My thought that monadic parsers are more verbose came from
> Hutton's paper where the
> code is definitely less readable than in e
From the conclusion that both programs compute the same result it can be
concluded that the fact that you have made use of a list comprehension has
forced you to make a choice which should not matter, i.e. the order in which
to place the generators. This should be apparent from your code.
My
use the UUAGC nowadays to generate this code form uuagc input.
http://www.cs.uu.nl/wiki/bin/view/Center/PhDs
Doaitse Swierstra
On Jan 26, 2013, at 23:03 , Petr P wrote:
> Dear Haskellers,
>
> I read some stuff about attribute grammars recently [1] and how UUAGC [2] can
> be used
tion based on questions asked
http://www.cs.uu.nl/wiki/USCS/
-- on this page you can find the poster you can print and hang somewhere (why
not your office door):
Furthermore we ask for your cooperation to bring this announcement under the
attention of potential participants.
Best,
Doaitse
On Aug 19, 2012, at 5:29 , wren ng thornton wrote:
> On 8/17/12 5:35 AM, TP wrote:
>> Hi,
>>
>> I am currently reading documentation on Generalized Algebraic Data Types:
>>
>> http://en.wikibooks.org/wiki/Haskell/GADT
>>
>> I have a question concerning this page. Let us consider the following
On Aug 21, 2012, at 13:46 , Heinrich Apfelmus 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,
>>> es
On Aug 19, 2012, at 10:40 , Heinrich Apfelmus wrote:
> Doaitse Swierstra wrote:
>> Over the years we have been constructing a collection of Embedded
>> Domain Specific Languages for describing compilers which are
>> assembled from fragments which can be compiled individuall
On Aug 19, 2012, at 10:40 , Heinrich Apfelmus wrote:
> Doaitse Swierstra wrote:
>> Over the years we have been constructing a collection of Embedded
>> Domain Specific Languages for describing compilers which are
>> assembled from fragments which can be compiled individuall
s Sem modules to see how we use our first class
attribute grammars to implement the static semantics associated with the
various tasks of the challenge.
We hope you like it, and comments are welcome,
Marcos Viera
Doaitse Swierstra
___
Haske
ter:
http://www.utrechtsummerschool.nl/index.php?type=courses&code=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
__
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
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. give
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, s
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
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
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 r
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 (su
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
On 16 sep 2010, at 05:42, Jared Jennings wrote:
> On Fri, Sep 10, 2010 at 2:00 PM, S. Doaitse Swierstra
> 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,
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
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 --ma
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
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 "
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: *** Ex
e further references.
Doaitse
>
> 2010/7/28 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 linea
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 semirin
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)]
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
p://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. Quickchec
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
27; ' 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
ht
e
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 s
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 m
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:
-- @ Resul
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:
-- @ Resul
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
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
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 wa
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 ... linkin
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?
Doaitse
___
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!
>
> score :: String -> String -> String
> score [s] [] =
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
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)
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 (ma
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 (ma
useful in removing left recursion
and even make your parsers look nicer and more intuitive,
Doaitse Swierstra
On 8 dec 2009, at 16:10, Adam Cigánek wrote:
Hello there,
Is there some other parser library, with similar nice API than Parsec,
but which somehow handles left-recursive
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 f
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 digi
rs-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 reus
g 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
mited. 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
for this price on this date", etc), so it was natural to add a bit
m
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-_-produc
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
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
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 runt
s.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 ;-}
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
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, 2009.
Mention vacancy nr
On 28 aug 2009, at 08:11, Jason Dusek wrote:
2009/08/27 Bulat Ziganshin :
...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
#x27;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
The uu-parsinglib:
http://hackage.haskell.org/packages/archive/uu-parsinglib/2.2.0/doc/html/Text-ParserCombinators-UU-Core.h
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 ((p
lem,
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:
che
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
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 whe
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
trickery!
Doaitse Swierstra
On 28 mei 2009, at 11:41, Malcolm Wallace wrote:
Henning Thielemann 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 ca
["'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.])
([
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
. 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 occ
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 H
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
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 wro
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 y
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 Type
may have offline,
Doaitse Swierstra
On Feb 5, 2007, at 1:39 PM, Thomas Hartman wrote:
haskellers, I'm contemplating returning to school after a decade as a
worker bee, and almost that long as a worker bee doing computer
consulting / miscelaneous tech stuff.
Ideally I'd like to get
expression:
digest.chew.eat.serve.cook.chop.pluck.kill $ chicken
we all have a definite feeling that after applying the functions, the
original object is no longer available, and the FP view does not feel
entirely natural.
Doaitse Swierstra
__
On Jan 29, 2007, at 9:53 AM, Yitzchak Gale wrote:
After many years of OO Perl, I looked at Python.
Within fifteen minutes I had switched, and I never
looked back at Perl.
A few years later, I had a need to hack into the
Python interpreter. While reading up on that,
I came across references to
; invisible (pp "}")
and try render (res_word "let") 3.
Doaitse
On Dec 14, 2006, at 9:57 AM, Christian Maeder wrote:
Doaitse Swierstra schrieb:
The Prettyprint library you can download from:
http://www.cs.uu.nl/wiki/HUT/Download
I've looked into your module UU.
= Text 0 l <|> text t <|> Text 0 r
you should be set and done,
Doaitse Swierstra
On Dec 13, 2006, at 10:31 PM, Tomasz Zielonka wrote:
On Wed, Dec 13, 2006 at 08:58:25PM +, Neil Mitchell wrote:
I've been using the HughesPJ pretty printing library, but I need a
new
comb
/vacatures/en/62612.html
Doaitse Swierstra
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org
king
transitions from Java and C as smooth and surprise-free as possible
(and this is already hard enough).
So I strongly suggest to leave this to the next major redesign of the
language.
Doaitse Swierstra
___
Haskell-Cafe mailing list
Haskell-Cafe
Jeroen Fokker has made Haskell syntax diagrams, which are part of
lecture notes for first-year students. Maybe they are helpful to
others too,
Doaitse
http://abaris.zoo.cs.uu.nl:8080/wiki/pub/FP/CourseLiterature/
haskellsyntax-main.pdf
On Jul 11, 2006, at 4:30 PM, Thiago Arrais wrote:
One might want to take a look at:
http://www.cs.uu.nl/research/projects/proxima/
where we have built (a.o.) an editing environment for Helium programs
(a subset of Haskell),
Doaitse
On 2006 jun 02, at 10:57, Brian Hulley wrote:
Simon Marlow wrote:
Malcolm Wallace wrote:
"Brian Hul
ser with this parser, and that worked (contact [EMAIL PROTECTED] to
get a copy of his code)
- did you think about how to handle the offside rule? If not, the
good news is that we have combinators for that too.
Doaitse Swierstra
Haskell already seems so very close to having this property -
We have all the machinery available. See:
http://www.cs.uu.nl/groups/ST/Center/SyntaxMacros
It will be part of the UtrechtHaskellCompiler (UHC), that is being
constructed with our toolset, and which recently strated to produce
running code. You get the syntax macros "almost" for free if you build
in (x:r):rr
else []:munch p weight
main = print (splitList 18 [1,5,3,17,8,9])
Doaitse Swierstra
PS: note that your problem is a bit underspecified:
-- what to return for an empty list
-- what to do if a number is larger than the weight
On 2004 apr 21, at 15:42, St
int (splitList 18 [1,5,3,17,8,9])
Doaitse Swierstra
PS: note that your problem is a bit underspecified:
-- what to return for an empty list
-- what to do if a number is larger than the weight
On 2004 apr 21, at 15:42, Steve Schafer wrote:
I have a list of integers, e.g.:
[1,5,3,17,8,9]
I want
ng.
See:
http://www.cs.uu.nl/groups/ST/twiki/bin/view/Center/
SoftwareDistributions
and the follow the attribute grammar link.
Best,
Doaitse Swierstra
On vrijdag, nov 7, 2003, at 16:09 Europe/Zurich, Marta Isabel Oliveira
wrote:
Ok, i read the page but i'm still stuck.
I'm reading some pa
in the tree,
Doaitse Swierstra
On woensdag, september 10, 2003, at 12:33 PM, Peter Robinson wrote:
Hello!
Does anyone know a reasonable standalone Parser for the Haskell
Grammar? The
only one i found was hsparser but it's still an alpha release and i
get a few
errors during compili
-> p b -> p a
( *>) :: Parser p => p b -> p a -> p a
etc
Now one can combine parsers as in:
pVal = (+) <$> pInteger <* pSymbol '+' <*> pInteger
<|> (*) <$> pInteger <* pSymbol '*' <*> pInteger
etc
Should I change
mble better what one wants express than
left recursive formulations.
Doaitse
--
______
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
P.O.Box 80.089, 3508 TB UTRECHT, the
rs you can find there. This new version
will also allow you to write scanners with the same set of
combinators.
We are working on a version that will also generate parsers.
Off to ICFP now,
Doaitse Swierstra
At 3:27 PM +1100 9/15/00, Manuel M. T. Chakravarty wrote:
>Doug Ransom <
98 matches
Mail list logo