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

2012-08-21 Thread S. Doaitse Swierstra

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,
>>> 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


[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=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


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


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


[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, 20

[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


[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] [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: 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


[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


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
__



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



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



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



RE: Parsing include files

2000-08-22 Thread S. Doaitse Swierstra

At 4:03 AM -0700 8/21/00, Julian Seward (Intl Vendor) wrote:
>| Since compilers are one of the areas where everyone agrees that FPLs
>| are the right tool for the job, there should be a standard pattern to
>| deal with include files. Am I missing something essential?
>
>No.  Parsec is an excellent library, but I think there's a
>design flaw in that you can't write your own lexer.  The
>"traditional" thing to do is write a lexer, which can deal
>with include files, etc, as you want.  Parsec would then
>be presented with a list of tokens, rather than a list of
>chars as at present.  Doing this would also avoid the hassle
>of having to remember to skip whitespace here, there and
>everywhere, which cluttered up a parser I wrote recently
>with parsec.
>
>Daan, what do you say?
>
>Other than that, Parsec is really good.  I particularly liked
>the error reporting stuff.
>
>J

You will find a rather complete lexer at:

  http://www.cs.uu.nl/groups/ST/Software/UU_Parsing/#scanner

which does recursive imports etc. An example of its use can be found 
in the attribute grammar system and the small example compiler in the 
same place.

You may want to adapt the scanner to your own needs. It may be 
tempting to try to combine the scanning and the parsing in one go, 
but you may wonder why there are separate tools like YACC and Lex for 
those different tasks.

The lexer was written to be used in conjunction with the error 
correcting library you will find there too, but is in no way tied to 
it and might be used with other libraries just as well. We are about 
to release a new version of our combinators, with a library of 
scanner constructing combinators. If you are prepared to live without 
some documentation I can make the new files available.

  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
__




propaganda 1: Fast, Error Correcting Parsing Combinators

1999-08-23 Thread S. Doaitse Swierstra

,,Fast, Error Correcting
Parsing Combinators


(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.



,,Why would you like to use these
Combinators?


Have 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]

_______
___

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

__












propaganda 2: Fast, Multi Layout Pretty Printing Combinators

1999-08-19 Thread S. Doaitse Swierstra

,,Fast, Multi Layout Pretty
Printing Combinators


(Updated: Aug-19-1999)


I have placed a completely new version of our parser combinators on the
net at http://www.cs.uu.nl/groups/ST/Software/PP/


Why would you like to use these Combinators?


Have you always been intrigued by Pretty Printing Combinators because
they allow you to:


   specify pretty printers easily 

   create pretty printers  dynamically 


but did you not like:


   the fact that alternative layout were difficult to specify

or

   expensive to compute


then why not use our new pretty printing combinators? 



I hope this software is useful to you. If you have any comments do not
hesitate to contact us.


Doaitse Swierstra mailto:[EMAIL PROTECTED],[EMAIL PROTECTED]

__

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

__











propaganda 3: Advaced Functional Programming 3 Proceedings

1999-08-19 Thread S. Doaitse Swierstra
e introduced.


The last lecture, titled ,,Haskell as
an Automation Controller, 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]

______________

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

__











Re: Int vs Integer

1998-09-10 Thread S. Doaitse Swierstra

At:

http://www.cs.uu.nl/groups/ST/haskell.pdf

you may find a pdf version of the current haskell 1.4 report. You may read
and browse through it with the Acrobat redaer. Some of you might find this
more pleasing than the html version,

  Doaitse Swierstra

--
PLEASE NOTE THAT THE DOMAIN NAME ruu HAS BEEN CHANGED TO uu

I HONESTLY APOLOGIZE FOR THE INCONVENIENCES THIS CAUSES TO YOU, BUT IT HAS
BEEN ENFORCED UPON US BY THE UNIVERSITY BOARD.

The old domain will remain functioning for a long time, but you cannot say
that you have not been warned.
__
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
__






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
__^___^___