Re: some Standard Haskell issues

1998-08-19 Thread Simon L Peyton Jones

> Yes, I think it's a fine idea to loosen up the syntax and allow import and
> infix anywhere.  But could someone clarify what the intent is with regards to
> the scoping of liberally sprinkled imports/infixes?

I've added a clarification; my intent was that all import and 
fixity declarations would scope over the whole module, just like any other
declaration.

Simon






Standard Haskell

1998-08-04 Thread Simon L Peyton Jones


Folks,

I'm writing to say how I hope to progress the Standard Haskell
process.   I have updated the 'State of play' page

http://www.dcs.gla.ac.uk/~simonpj/std-haskell.html

It now lists every change that I propose to make for Standard
Haskell.  I now propose the following plan:

* Between now and ICFP'98 we discuss these proposals.  By 'we'
  I mean anyone interested: you can post mail to the Haskell
  mailing list.  If anyone finds that an onerous burden on 
  the list I suppose I can start another, but since it is
  a shortlived thing I hope I don't have to.

* At ICFP I'll hold an open meeting of some kind to try to 
  resolve any remaining issues.

* After ICFP I'll publish a draft revised report for debugging

* A month or two later I'll freeze it


On the state-of-play page you'll find a few issues marked
'New'.  These are ones I've come across in my tidying up phase,
and are either brand new or have been little discussed.  I 
highlight them for particular attention.  

Please also pay attention to omissions: what have I missed?

Thanks for your help.

Simon






Re: Felleisen on Standard Haskell

1998-08-04 Thread Simon L Peyton Jones

> In any case, I hope that Simon will follow his urge to get Standard
> Haskell done with Real Soon Now, even if there is no overwhelming
> consensus on certain issues, so that we can then concentrate on Haskell
> 2.

That's just what I intend to do.  I don't see Std Haskell as a big
deal, but even little deals are worth completing rather than
leaving as loose ends... and I'm more optimistic than Paul about
the usefulness of Std Haskell.  I would be happy to find a name
that was less grand and final-sounding than 'Standard Haskell' though;
but more final sounding than 'Haskell 1.5'.

Matthias's points are good ones, but premature for Haskell I think,
which is still moving pretty fast.  Indeed, for some reason, faster
of late.

Simon





Re: Rambling on numbers in Haskell

1998-08-04 Thread Simon L Peyton Jones


I think all this discussion about numerics in Haskell is great. I'm convinced
that designing good libraries is a major creative act, not just an add-on to a
language; and that the existence of good libraries has a big effect on how much
use a language gets.  ('Good' means both having a well-designed signature, and
at least one efficient implementation. Sometimes these two conflict.)  Library
design is sadly under-valued: people who design and implement good libraries
should get at least as much credit as people who design good languages.

The trouble is that it's easier to identify flaws in current libraries
than to figure out better ones. Certainly in the numeric area there sems
to be a big tension between completeness and simplicity.

Bottom line: Haskell 2 is pretty wide open.  If some group of you
out there get excited about this and design and implement a coherent
set of numeric libraries then I think you'd be welcomed with open
arms, even if it wasn't compatible with Haskell's current numeric
class structure.   Sergey's work is moving in that direction, which
is great. 

Above all don't leave it to us compiler hackers!  We aren't 
numeric experts like some of you are, and are most unlikely to do a
good job of revising Haskell's numeric libraries.

Simon







Re: instances in Haskell-2

1998-07-29 Thread Simon L Peyton Jones

> I cannot find there the subject. Could you citate?

Sorry, it turns out I missed your point entirely.  

  class (Ring r,AddGroup (m r)) => RightModule m r where  
cMul :: m r -> r -> m r

So here, m :: *->*

What you really want is to say

  instance Ring r => RightModule (\t->t) r where
 cMul = mul

so that now you can use cMul at type

cMul :: Foo -> Foo -> Foo

(provided Foo is an instance of Ring).



The '(\t->t)::*->*' is your 'transparent newtype' function.  It makes
perfect sense to have lambda abstractions at the type level;
indeed type synonyms define such things.  I've seen quite a few
other occasions in which I wanted a (\t->t) type constructor 
in particular.

What I don't know how to do is to perform type inference on such systems.  (The
restriction that type synonyms must be fully applied is to avoid lambdas in
type inference.)  There is some work on it, but I believe the story is "It's
complicated".


So, yes it's a reasonable question, but I for one don't know
a tractable design.  And it's known swampy territory.

sorry for missing the point the first time.

Simon





Re: suggestions for Haskell-2

1998-07-28 Thread Simon L Peyton Jones

>   class (Ring r,AddGroup (m r)) => RightModule m r  
> where  
> cMul :: m r -> r -> m r
>  -- "vector" (m r) multiplied by "coefficient"  r'
>
> Haskell rejects this (m r) in the context.  Could Haskell-2 allow it?

Yes.  See http://www.dcs.gla.ac.uk/~simonpj/multi-param.html

>   instance Ring r => RightModule r r  where  cMul = mul
>
> Haskell rejects this  `=> RightModule r r'

This is fine too (for Haskell 2). See the same URL.


> `newtype' cannot derive all the instances automatically.
> 
> Thus, in our case,  add (Id 1) (Id 2)  is illegal.
> 
> This may occur a stupid question, but 
>   why Haskell allows the `newtype' derivation only for the standard 
>   classes?
> Why not support declarations like
> 
>  newtype N a b =  N (T a b)  deriving(Eq,Ord,AddGroup,Ring)
> or   newtype N a b =  N (T a b)  deriving( all )

That would indeed be possible for newtype; but my guess is
that if you want 'all' then you ought to be able to get away without
a newtype at all.  But I might well be wrong about this.
Anyway, it's not an unreasonable suggestion.

Simon





International Symposium on Memory Management: call for participation

1998-07-26 Thread Simon L Peyton Jones


Dear colleague

We'd like to invite you to join us at the International Symposium on
Memory Management 1998, immediately preceding OOPSLA in Vacouver.

Memory management is becomming more and more important these
days, and the meeting should be a good chance to find out where
it's at, and to meet other researchers in the field. As well as the
formal programme there will be several informal sessions, led
(we hope) by you.

Details below.

Simon Peyton Jones, General Chair
Richard Jones, Program Chair


---
  Call for participation

   International Symposium on Memory Management 1998

Sat 17th - Mon 19th October 1998, Vancouver

Sponsored by ACM SIGPLAN
Co-located with OOPSLA

Full details at:
http://www.sfu.ca/~burton/ismm98.html

*
* YOU CAN REGISTER NOW ON THIS URL  *
*

The International Symposium on Memory Management is a forum for
research in memory management, especially garbage collection and
dynamic storage allocators. Areas of interest include but are not
limited to: garbage collection, dynamic storage allocation, storage
managemeent implementation techniques and their interactions with
language and OS implementation, and empirical studies of programs'
memory allocation and referencing behavior.


Accepted papers

A Compacting Incremental Collector and its Performance in a Production
Quality Compiler, Martin Larose and Marc Feeley, Universite de
Montreal

Combining Card Marking with Remembered Sets: How to Save Scanning
Time, Alain Azagury, Eliot Kolodner, Erez Petrank and Zvi Yehudai, IBM
Haifa Research Laboratory

Barrier techniques for Incremental Tracing, Pekka P. Pirinen,
Harlequin

The Memory Fragmentation Problem: Solved?, Mark S. Johnstone and Paul
R.Wilson, University of Texas at Austin

Using Generational Garbage Collection to Implement Cache-Conscious
Data Placement, Trishul M. Chilimbi and James R. Larus, University of
Wisconsin-Madison

One-bit Counts between Unique and Sticky, David J. Roth and David
S. Wise, Indiana University

Hierarchical Distributed Reference Counting, Luc Moreau, University of
Southampton

Comparing Mostly-Copying and Mark-Sweep Conservative Collection,
Frederick Smith and Greg Morrisett, Cornell University

A Non-Fragmenting Non-Copying Garbage Collector, Gustavo
Rodriguez-Rivera, Michael Spertus and Charles Fiterman, Geodesic
Systems

Garbage Collection in Generic Libraries, Gor V. Nishanov and Sibylle
Schupp, Rensselaer Polytechnic Institute

Memory Management for Prolog with Tabling, Bart Demoen and
Konstantinos Sagonas, Katholieke Universiteit Leuven

The Bits Between the Lambdas - Binary Data in a Lazy Functional
Language, Malcolm Wallace and Colin Runciman, University of York

A Memory-Efficient Real-Time Non-Copying Garbage Collector, Tian
F. Lim, Prsemyslaw Pardyak and Brian N. Bershad, University of
Washington

Guaranteeing Non-Disruptiveness and Real-Time Deadlines in an
Incremental Garbage Collector, Fridtjof Siebert

A Study of Large Object Spaces, Michael W. Hicks, Luke Hornof,
Jonathan T. Moore and Scott M. Nettles, University of Pennsylvania

Portable Run-Time Type Description for Conventional Compilers, Sheetal
V. Kakkad, Mark S. Johnstone and Paul R. Wilson, University of Texas
at Austin and Somerset Design Center, Motorola Inc.

Compiler Support to Customize the Mark and Sweep Algorithm, Dominique
Colnet, Philippe Coucaud and Olivier Zendra, INRIA-CNRS-Universite
Henri Poincare

Very Concurrent Mark-&-Sweep Garbage Collection without Fine-Grain
Synchronization, Lorenz Huelsbergen and Phil Winterbottom, Bell
Laboratories

Memory Allocation for Long-Running Server Applications, Per-Ake Larson
and Murali Krishnan, Microsoft










Re: Scoped typed variables.

1998-07-22 Thread Simon L Peyton Jones

> I think the way that Hugs 1.3c handles it would meet your goals.  All that
> it requires is a strict extension to the syntax for patterns to allow type
> annotations.  These can be useful in their own right, but also can be
> applied
> to problems like the one that you gave:
> 
>   f :: [a] -> a -> [a]
>   f ((x::a):xs) y = g y
>  where
>g :: a -> [a]
>g q = [x,q]
> 
> The only change I've made here is to replace "x" on the left hand side of
> the definition for f with "(x::a)".  As a result, the type variable "a"
> will be in scope when the signature of g is encountered, and so will not
> be subjected to the usual, implicit universal quantification.

The monomorphism discussion highlighted a disadvantage with
the pattern notation for scoped type variables that I hadn't realised
before.  Michael suggested

  
 f :: [a] -> c
 f xs = if len > fromInteger 3 then len else 0
  where
  len :: c
  len = length xs

This relies on the 'c' from the type signature scoping over
the definition, which is on alternative notation for scoped
type variables.  On the whole I think the 'put signatures in patternss'
approach is nicer, but I don't think it can express this example,
because the relevant type is (only) in the result.  Maybe it's
Just Too Bad, but it is a pity.


Simon





Re: avoiding repeated use of show

1998-07-22 Thread Simon L Peyton Jones

> I would like to avoid using show all the time for printing strings e.g.
> 
> > val = "the sum of 2 and 2 is "++(show $ 2 + 2)++" whenever."
> 
> I would prefer to type something like:
> 
> > val = "the sum of 2 and 2 is "./(2+2)./" whenever." 
> > -- i can' find a better haskell compatible operator

Let me advertise Olivier Danvy's very cunning idea to implement
printf in Haskell/ML.

http://www.brics.dk/RS/98/5/index.html


> So I tried creating my own Stringable class:
> > class Stringable a where
> >  toString::a -> String
> 
> > (./) :: (Stringable a,Stringable b)=> a->b->String
> > x./y = (toString x)++(toString y)
> 
> The trouble is that when I try doing things like:
> 
> > res = (2+2) ./ " hello"
> 
> I get an "Unresolved top-level overloading" error.
>
> Is there any way to convince Haskell to just resolve these numbers to
> SOMETHING by default?  Then I can just declare that type an instance of
> Stringable.

What's going on is this.  You've got the context

(Stringable a, Num a)

arising from the RHS of res, and no further info about what "a" is.
Under extremely restricted circumstances Haskell will choose 
particular type for you, namely

when the classes involved are all standard prelude classes
and at least one is numeric.

Why so restrictive?  Because it it *might* make a massive difference
which type is chosen.  Suppose you had

instance Stringable Int where
   toString n = "Urk!"

instance Srringable Integer where
   toString n = ".Ha ha."

Now whether your program yields "Urk" or "...Ha ha" depends on
which type Haskell chooses.

There's no technical issue here. One could relax the defaulting
restriction, at the cost of (perhaps) sometimes unexpected behaviour.
Or, as you show, you can just tell it which type to use:

res = (2+2)::Int ./ "hello"

Simon 






Re: instances of types

1998-07-22 Thread Simon L Peyton Jones

> Haskell doesn't seem to allow
> 
> > instance Num (Int->Int) where ...
> 
>  or
> 
> > instance Stringable String where ...

Haskell requires you to write instances of the form

instance context => T a1..an where ...

where T is a type constructor and a1..an are type variables.

This is a conservative, but sound, design choice.  Haskell 2,
some versions of Hugs, and GHC 3.02 and later, all accept more
instance declarations.

There's extensive discussion in
http://www.dcs.gla.ac.uk/~simonpj/multi.ps.gz

and a summary of the state of play in
http://www.dcs.gla.ac.uk/~simonpj/multi-param.html

Simon






Re: Monomorphism

1998-07-21 Thread Simon L Peyton Jones

> 
> I'm going to ask a very stupid question.
> 
> Why on earth is len computed twice in this example?  I really don't   
> understand this!

I have to confess that I mischievously hoped that someone
would say this: it demonstates the point nicely that
lifting the monomorphism restriction would cause at least
some people to be surprised.

Let me add the type signatures [I'm a bit puzzled why length used
to have type Integral b => ... but that's a side issue.]


   length :: forall a b. Num b => [a] -> b


   f :: forall a c. Num c => [a] -> c
   f xs = if len > (3::Integer) then len else 0
   where
 len :: forall d. Num d => d
 len = length xs


The first use of len returns an Integer, so we must compute
the length at type Integer.

The second use of len returns a value of type c, so we must
compute length at type c.  (Someone *might* call f wanting an Integer
back, they might not.)

And there you have it.

Simon





Re: GHC licence (was Could Haskell be taken over by Microsoft?)

1998-07-21 Thread Simon L Peyton Jones

> Simon L Peyton Jones wrote:
> > So far as GHC is concerned, I wrote on this list a month ago:
> > "More specifically, I plan to continue beavering away on GHC.
> > GHC is public domain software, and Microsoft are happy for it to 
> > remain so, source code and all.  If anything, I'll have quite a bit
> > more time to work on it than before."
> 
> Do you mean "public domain" literally, i.e. are you renouncing all
> copyright?  (The source code contains copyright notices, but no
> licence, as far as I can see.)

No I am not renouncing all copyright.  By "public domain" I mean freely
available for anyone to use for any purpose other than making money
by selling the compiler itself.  That isn't a formal definition,
but I'm sure you see the intent.

I have carefully avoided getting tangled up in legal red tape, which
is why there is no formal license.  It may be that my move to Microsoft
will force me to spend time sorting this out.  But it's never been
a problem so far, and I doubt it will in the future, so I'm reluctant
to invest the time until pressed to do so.

Simon





Re: Monomorphism

1998-07-21 Thread Simon L Peyton Jones


Olaf suggests

> Hence I suggest that part (b) of rule 1 of the MR should
> be deleted, i.e. simple
> pattern bindings are just treated as function bindings. As I have said in a
> previous email, the recomputation issue could be handled by warnings from the
> compiler.

That would indeed not fall foul of the ambiguity problem, but
it doesn't deal with the unexpected efficiency problem.

Consider:

f xs = if len > 3 then len else 0
 where
len = length xs

You are a first year undergraduate.  Quick, how many times is the
length of xs computed?

Correct!  Twice!  I'm assuming here that we've made the change
to length to give it the sensible type

length :: Num b => [a] -> b

(And it's not length's fault; it's easy to write functions with
similar types.)

Here the effect is arguably minor: taking the length of a list
twice.  But it's not hard to come up with examples that are
exponentially worse.

Some people say "of course len is computed twice", but many find
it puzzling.  We have debated this point endlessly.  Frankly, I'm
very reluctant to make incremental changes to the MR.  Let's either
fix it or leave it alone.  Since we don't know how to fix it, let's
leave it alone.

Simon





Re: Could Haskell be taken over by Microsoft?

1998-07-21 Thread Simon L Peyton Jones

> It seems that many prominent Haskell people are more or less associated
> with Microsoft. It has just been announced that Hugs may go into
> Microsoft Developers Studio and Simon Peyton-Jones is about to move to
> Microsoft. Is there a risk (or change, if you like) that Microsoft will
> eventually take over the Haskell language? In my opinion it is very
> important that this doesn't happen. If Haskell is to have a future it
> must remain free and not dominated by a single company.

Haskell is a public domain language.  Microsoft, like any other company, are at
liberty to build and sell a commercial implementation of Haskell.  It would be
wrong to suggest that they could not or should not; indeed, I think that would
be a wonderful thing if they did. However, I have absolutely no reason to
believe that they are planning any such thing.

So far as GHC is concerned, I wrote on this list a month ago:
"More specifically, I plan to continue beavering away on GHC.
GHC is public domain software, and Microsoft are happy for it to 
remain so, source code and all.  If anything, I'll have quite a bit
more time to work on it than before."

So, sleep easy.

Simon






Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-17 Thread Simon L Peyton Jones


> But if there are too many things missing, no one will use Standard
> Haskell - it already seems as if most of the people on this list are
> going to go straight to Haskell 2, which would mean that Standard
> Haskell might only be used for teaching.

Indeed, I do expect that most of the people on this list will
go straight to (the moving target of) Haskell 2.  The purpose of
Std Haskell is to address the needs of people who don't need the
latest greatest, but do need something stable.  For example,
the fact that Haskell keeps moving (which in many ways is good)
discourages people from writing books, which in turn makes it
less attractive for people who aren't already converted.

> thought this could be specified pretty easily), but I really think
> that the tidying up of the relationship between the prelude and the
> standard libraries is vital. For example, I can see no reason why
> PreludeIO and IO should be separate.  Surely it wouldn't be much work
> to put it all in the IO library? As it stands, the prelude has to
> refer to the library, which, I think, underlines the inconsistency:

I agree that the Prelude could do with tidying up, but I think
it is no small task, and (worse) it is a task with no clear finish.

I do propose (unless people yell) to move back to the generic
take/drop/length operators, but if it's left to me not much else
will happen. On the other hand, if someone is keen to work on the
Prelude and standard libraries, in the next two or three months
(no longer) then I'd be delighted to hear from them.

Simon "desparately trying to keep the lid on the can of worms" PJ






Re: Monomorphism

1998-07-16 Thread Simon L Peyton Jones


> > read :: Read a => String -> a
> > read s = let [(r,s')] = reads s in r
> >
> > This *won't compile* if you don't treat the let binding definition
> > monomorphicly.  Without monomorphism, the types of r and s' are
> >
> > r  :: Read a => a
> > s' :: Read a => String
> >
> > This leads to an ambiguity error for s'.
> 
> I'm not buying it (the DMR being responsible for resolving overloading
> ambiguity).
> 
> There's nothing ambiguous in that definition, because s' is not used.
> There's nothing even ambiguous about the meaning of s' (we can apply the
> dictionary translation just fine).  The problem is with uses of things
> like s'.  Haskell takes the stance that you can't declare something you
> can't use (something with a type that would lead to ambiguity in use),
> but I say this example shows us how that stance may well be shortsighted.

What worries me is that a programmer might write this:

read2 :: (Read a, Read b) => String -> (a,b)
read2 2 = let [(r1,s1)] = read s
  [(r2,s2)] = read s1
  in
  (r1,r2)

Here, s1 is indeed used, so the ambiguity problem does bite.
The troubling thing is that "read" works (at least if the MR
is lifted) but "read2" does not.

I am concerned too about the efficiency problem.  Suppose that
the ambiguity problem was resolved by choosing some arbitrary
type.  (A bad idea, but still.)  And suppose that we continued
"read2" so that it read, say, 10 things.  Reading the 10th would
re-parse all previous 9, which is surely not what a programmer
might expect.  The redexes (read sn) certainly look like thunks,
which we are accustomed to being shared.  But actually it will
be evaluated once for each used variable in the LHS pattern.

Simon





Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-15 Thread Simon L Peyton Jones

> More generally, regardless of the standards process, it feels like the
> GHC, Hugs define the de facto Haskell standard (it doesn't look like HBC
> is still in progress but I could be wrong).  As such, it seems tough to
> write libraries right now as the upcoming GHC/Hugs release will contain
> features that strongly affect library design:
> 
> So I guess my question is how close is this new release? 

For these

> * multi-parameter type classes
> * existential types
> * exceptions
> * mutually recursive import [GHC does this ok]

we'll have a shiny new GHC beta release before ICFP (end Sept).
(I.e. it's pretty much working now.)  Don't know about Hugs.

For these

> * require/ensure/invariant assertions (my optimism)

We need an agreed design first.  Your point about putting
asertions in type signatures makes me think that maybe assertions
would be premature for Std Haskell.

> * module signatures/dynamic linking
> * dynamic linking (serialization/persistence?)

I'm hazy about what you have in mind here.

Simon






Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-15 Thread Simon L Peyton Jones

> etc... all seem to be things that are waiting 'till Haskell 2.  My
> point was that _something_ should be in Standard Haskell.  The features
> you mention are likely to help when writing a better network library,
> but let's not get distracted from the option of including something
> straightforward in the standard.

I hadn't realised that your suggestion was a propos of Standard
Haskell.

I'm pretty leery about trying to agree any new libraries at this
stage, unless someone comes up with a worked-out, and implemented,
specification pretty quickly.  The name of the Std Haskell game
is rapid closure.  There are just tons of things that 'ought'
to be in it that aren't going to be.

Simon





Re: Instance contexts.

1998-07-13 Thread Simon L Peyton Jones


[I'm taking the liberty of broadening this to the Haskell
mailing list.  I doubt anyone is on glasgow-haskell-users, where
it started, but not on the haskell list.]

> > I think this has been discussed before, but I've just run into it myself.
> > I have a MPC 'Set', in the usual bog-standard fashion, and I want to
> > define interval arithmetic over sequences of such sets.  This requires
> > they also be partially ordered, and of a numeric type themselves, so
> > I end up with something like:
> > 
> > 
> > instance (Set s n, Num (s n), POrd (s n)) => Num [s n] where
> >   n + m
> > = bigunion [ overlaps [n1 + m1 | m1 <- m] | n1 <- n]
> > 
> > 
> > This works in 3.01, but not in 3.02.  Is this restriction a sensible
> > one?  Come to that, are my classes?  It seems to me that the nature of
> > the MPC forces me to use non-variable contexts, which I think looks
> > a bit uglky, but I don't know of another way to get the same effect.
> 
> I'd like to support Alex here: it is absolutely necessary to relax
> condition 10 of SPJ's list. 

http://www.dcs.gla.ac.uk/~simonpj/multi-param.html

> Idioms like the one above (`Ord (s a)' or
> `Show (s a)') arise too often and are completely natural.


One of the great merits of imposing restrictions is that
you hear about when they are irritating :-). (The reverse does
not hold.)  Examples like this are jolly useful.

Alex: can you flesh out your example any more? I was expecting
Num (s n) not Num [s n], for example.

Ralf: can you supply other examples?

Ditto others.


One possible choice would be to insist that the context of 
an instance decl constrained only proper sub-expressions of
the type on the RHS.  Alex's example would be fine then, but
perhaps others might not?

Simon





Re: type synonyms

1998-07-09 Thread Simon L Peyton Jones


> That's basically newtype with the data constructor omitted (I would
> prefer data to record). Unfortunately, this seems to be incompatible
> with the class system. (There was a long discussion on the Standard
> Haskell discussion list, unfortunately the entry vanished).

No, it just moved over to decisions:

http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Decisions.cgi

the particular one is this:

http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Decision.cgi?id=443

Simon





Re: MPTC: class type variables

1998-07-08 Thread Simon L Peyton Jones

> Well, I have a convincing example (at least it convinces me ;-).
> There are several ways to define a type class for finite maps (aka
> dictionaries, aka lookup tables). Here is one taken from Chris Okasaki's
> book on purely functional data structures (p. 204):

I saw Mark yesterday, and have made quite a few changes
as a result.  I've tried to address your points, and those
made by others, but you'll have to judge how successfully!

http://www.dcs.gla.ac.uk/~simonpj/multi-param.html

Anyway, you might want to take another look.

Simon





Standard Haskell

1998-07-08 Thread Simon L Peyton Jones


Folks

This message is to update you on the state of play so far
as Standard Haskell is concerned.  I'm circulating to three
Haskell-related mailing lists; in future I'll mail only
the "haskell" list, so pls subscribe to it if you want to
see anything more.

You may remember that John Hughes has been running the
Standard Haskell process, but he's been unable to devote much
time to it lately, so I've agreed to take on that role.

I've summarised the current state of play at

http://www.dcs.gla.ac.uk/~simonpj/std-haskell.html

The introductory paragraphs from that page appear below,
but the details don't.   As you'll see, the idea is that 
Standard Haskell should be a rather small increment (or decrement)
from Haskell 1.4, and I'm keen to get the thing done fairly
quickly.  (I'd be more precise, only my summer is a bit uncertain
because of my move to Cambridge.)

The summary page says what's decided, what's about to be decided,
and what isn't decided.  I'd be interested in your opinions about
any of these things.  Please send them to me or any other member
of the Std Haskell committee (below).  You're also free to send
messages to the Haskell mailing list, of course.

Simon


==

Standard Haskell: State of Play

Following the 1997 Haskell Workshop, much intervening work by the
Standard Haskell committee, and then an informal meeting at
Working Group 2.8 (Oregon, April 1998), 
there are now two separate Haskell language-design efforts:
Standard Haskell, and Haskell 2.

* Standard Haskell is, as was originally agreed at the 1997 Haskell
Workshop, a minor revision of Haskell 1.4, cleaning up traps but NOT adding
major new functionality. and thereby give Haskell the stability that has so far
been lacking.

* Over the past year it has become clear that there are a large number
of interesting proposed developments to Haskell: multi-parameter type
classes, pattern guard, scoped type variable, local universal and
existential quantification, and so on.  John Launchbury is
leading the development of Haskell 2, which will embody
these extensions.  Much of the discussion among the Standard Haskell committee
will transfer into the Haskell 2 effort.



Standard Haskell will therefore by no means be the last revision of Haskell. On
the contrary, we design it knowing that it will be superceded within one or two
years. But it will have a special status: the intention is that Haskell
compilers will continue to support Standard Haskell (given an appropriate flag)
even after later versions of the language have been defined, and in that
sense the name `Standard Haskell' won't refer to a moving target.

It's clear that those of us who want to keep up with the latest developments
will soon move to Haskell 2, but it also seems clear that there is a
substantial user community who will not. This strategy serves both. I think
another advantage is that the `dusty deck' problem will be much less of an
issue in the design of Haskell 2.0, because the dusty decks will remain in
Standard Haskell. So this strategy also gives a once-only opportunity to make
language changes (in the step to Haskell 2) which do break a lot of old
code. Strict pattern matching may yet raise its ugly head again...!



==
John Hughes, [EMAIL PROTECTED]
Lennart Augustsson , [EMAIL PROTECTED] 
David Barton , [EMAIL PROTECTED] 
Richard Bird , [EMAIL PROTECTED] 
Ralf Hinze , [EMAIL PROTECTED] 
Paul Hudak , [EMAIL PROTECTED] 
John Launchbury, [EMAIL PROTECTED] 
David Lester , [EMAIL PROTECTED] 
Jeff Lewis, [EMAIL PROTECTED] 
Erik Meijer , [EMAIL PROTECTED] 
John Peterson , [EMAIL PROTECTED] 
Simon Peyton-Jones , [EMAIL PROTECTED] 
Colin Runciman , [EMAIL PROTECTED] 
Simon Thompson , [EMAIL PROTECTED] 
Phil Wadler , [EMAIL PROTECTED] 






Re: Multi-parameter type classes

1998-07-01 Thread Simon L Peyton Jones

>  |5. In the signature of a class operation, every constraint must
>  |   mention at least one type variable that is not a class type
>  |   variable. Thus:
>  ...
>  |   > class C a where
>  |   >op :: Eq a => (a,b) -> (a,b)
>  |
>  |   is not OK because the constraint (Eq a) mentions on the class type
>  |   variable a, and no others.
> 
> What's the rationale for this rule?

It's hard to explain (which may well mean my head is on backwards).
In the 5 mins I have today here's what I added to the document


The reason it's awkward to implement is this. Supose you
are type checking the RHS of op in an instance declaration for C 
[c],
and suppose you have found that you need the constraint (C (S c)).
Should we reduce the constraint, in the hope being able to
"use" the Eq [c] we have available?  Or should we just
postpone this reduction for the top level of the class decl. 
Usually I make this decision based on whether the constraint mentions any
of the universally quantified type variables (b in this case),
which it doesn't.  Without this convenient test I have to either
to eager context reduction (which I don't want to do), or some sort
of search strategy.

Simon





Re: type errors

1998-07-01 Thread Simon L Peyton Jones

> | > > class (Eq key, Ord key) => Dictionary dict key dat where
> | > >  delete :: key -> dict -> dict
> | ...
> | > the first error:
> | > 
> | > Class type variable `dat' does not appear in method signature
> | > delete :: key -> dict -> dict
> | > 
> | > Why does ghc expect that I use all of the type variables?
> | > Obviously I only need
> | > the key to remove an entry of a dictionary.
> | 
> | You're right.  The restriction is excessive.  Thanks for pointing
> | this out.  Probably we should only require that at least one
> | of the class variables is constrained.
> 
> I don't see this.  The fact is that, if any of the variables in the
> class header don't appear in the type of a method, then that method
> will always have an ambiguous type.  In this case, that would be:
> 
>delete :: (Dictionary dict key dat) => key -> dict -> dict

It would not *always* result in ambiguity. For example, consider

instance Dictionary (MyDict dat) Int dat where ...

f :: MyDict dat -> MyDit dat
f d = delete (3::Int) d

Here, the polymorphism in 'dat' doesn't affect which instance
is chosen.

However, on further reflection, I now think:

in any case where ambiguity would not result
the original class declaration should be re-formulated

So, I now think that the existing rule (all class variables
must appear in each class-operation type signature) is probably
the right one, but on stylistic rather than technical grounds.

> I don't see how Simon's suggestion of replacing "all" with "at least one"
> could be made to work in general.  Such an approach is however possible
> if you are working with multiple parameter classes where the variables in
> one parameter are determined directly by the parameters in another.
> For example, consider the following class:
> 
>class Collection elem col where
>empty :: col
>add   :: elem -> col -> col
>del   :: elem -> col -> col
>enum  :: col -> [elem]
> 
> By the argument above, one should expect empty to be rejected as having
> an ambiguous type:  Collection elem col => col.   However, we could also
> imagine modifying the definition of ambiguity to take account of the fact
> that, in practice, the value of elem would probably be uniquely determined
> by the value of col, and hence the context in which empty is used could
> still provide enough information to allow the overloading to be resolved.

Indeed. Consider

instance Collection a MyColl where
   empty = MyEmpty
   ...

But this would be nearly useless, since we then know nothing
about the type elem.

So, again, nothing seems to be gained by relaxing the restriction
(unlike what I said yesterday).

Simon





Re: type errors

1998-07-01 Thread Simon L Peyton Jones

> > Actually I think you would be better off with a class like
> > this:
> > 
> >   class (Eq key, Ord key) => Dictionary dict key where
> >  delete :: key -> dict dat -> dict dat
> >  search :: key -> dict dat -> (key, SearchResult dat, dict dat)
> >  searchList :: [key] -> dict dat -> ([(key,SearchResult dat)],dict dat)
> 
> Ok, I did not reconize this solution, it seems to me the (nearly) proper one.
> But why not write:
> 
>class => Dictionary dict where
>delete :: (Eq key, Ord key) => key -> dict key dat -> dict key dat
>...
> 
> So one could avoid multiparamter classes at all. The two types key and dat
> should be inferred by the type of dict (which is expressed by 'dict key dat'). I
> can't think about a dictionary where key or dat are not associated with dict.

Yes, that's ok too.  You might find my paper "Bulk types with class"
somewhat relevant.

http://www.dcs.gla.ac.uk/~simonpj/papers.html

Simon





Multi-parameter type classes

1998-06-30 Thread Simon L Peyton Jones


Folks,

GHC 3.02 supports multi-parameter type classes, but I have been
guilty of not documenting precisely what that means.

I've now summarised the extensions, informally but I hope
precisely, at

http://www.dcs.gla.ac.uk/multi-param.html

This includes some changes that aren't in 3.02, based on 
people's experiences with 3.02.

I'd be very glad of feedback.  In effect, this is a straw-man
proposal for Haskell 2.

Simon






Re: type errors

1998-06-30 Thread Simon L Peyton Jones

> The ghc compiler complains about 2 type errors in the following code:
> 
> > data SearchResult a = Found a | Fail
> >
> > class (Eq key, Ord key) => Dictionary dict key dat where
> >  delete :: key -> dict -> dict
> >  search :: key -> dict -> (key,SearchResult dat,dict)
> >  searchList :: [key] -> dict -> ([(key,SearchResult dat)],dict)
> >
> >  searchList [] d = ([],d)
> >  searchList (x:xs) d = let (sresults,d') = searchList xs d
> >(x',sresult,d'') = search x d'
> >new_sres = (x',sresult):sresults
> >in (new_sres,d'')
> 
> the first error:
> 
> Class type variable `dat' does not appear in method signature
> delete :: key -> dict -> dict
> 
> Why does ghc expect that I use all of the type variables?
> Obviously I only need
> the key to remove an entry of a dictionary.

You're right.  The restriction is excessive.  Thanks for pointing
this out.  Probably we should only require that at least one
of the class variables is constrained.

Actually I think you would be better off with a class like 
this:

  class (Eq key, Ord key) => Dictionary dict key where
 delete :: key -> dict dat -> dict dat
 search :: key -> dict dat -> (key, SearchResult dat, dict dat)
 searchList :: [key] -> dict dat -> ([(key,SearchResult dat)],dict dat)

That is, you don't need the 'dat' type variable the class at all.

> Ambiguous type variable(s)
> `key', `dict'
> in the constraint `Dictionary dict key a10v'
> arising from use of `searchList' at Dtest2.hs:11
> In an equation for function `searchList':
> searchList (x : xs) d
>= let
>(sresults, d') = searchList xs d
>(x', sresult, d'') = search x d'
>new_sres = (x', (sresult)) : sresults
>  in (new_sres, (d''))
> In the definition for method `searchList'

You don't say which version of the compiler you are using,
but I think this a palpable bug in 3.01 that is fixed in 3.02.
So you are right to be confused by it!

Simon





Re: laziness and functional middleware

1998-06-19 Thread Simon L Peyton Jones


> The paper says:
> "We are working on a distributed implementation of Concurrent Haskell.
> Once nice property of MVars is that they seem relatively easy to implement
> in a distributed setting..."
> I assume that they are not referring to GPH here. 
> (I was surprised that at this statement given what I presume are the
> substantial difficulties of defining a wire format for lazy
> datastructures).
> 
> I would assume that the distributed implementation gives the programmer
> some access to whether a machine is "up" or I suppose that you could use
> distributed mvars to design your own ping (cool!)

OK, here's the current story.

* Concurrent Haskell works on uniprocessors only.  It's intended for
  programs that need explicitly-forked, concurrent, I/O-performing
  threads.  Processes are explicitly forked with forkIO, which is
  in the IO monad.

  Results are necessarily non-deterministic -- that's part
  of the point!  There is no attempt to use parallelism to gain
  performance.

* GpH (Glasgow Parallel Haskell) works on a variety of multiprocessors.
  It's specifically intended to harness parallelism to gain performance.

  Parallelism is explicitly sparked with `par`, but the RTS is free to
  ignore such sparks.  `par` is not in the IO monad: it has type
par :: a -> b -> b

  Results remain completely deterministic even on a multiprocessor.


I'd like to implement a sort of integrated system.  Certainly it
would be nice to be able to make Concurrent Haskell into Distributed
Haskell. To to this MVars would need to work across processors
(not hard), and forkIO would need a variant that said "fork this
process on this other host".  The goal would still not be performance-through-
parallelism; rather, it is part of the *specification* of a distributed
program that it different parts should execute in different places.

Perhaps one could also have some combination of DH and GpH; after
all they use similar underlying mechanisms.

I believe that Kevin Hammond, Phil Trinder and Rita Loogen are planning
to do something like this, but I'm afraid it's not directly in my 
sights!

Einar Karlsson ([EMAIL PROTECTED]) has been doing a 
huge application in Concurrent Haskell so he may have other comments.


I hope that helps to clarify where things are at from the implementation
point of view.  One way to get us hackers to do things is to 
say loud and clear what would actually be useful to you.

Best wishes

Simon





Re: Garbage Collection in GreenCard/RedCard/HaskellCOM

1998-06-17 Thread Simon L Peyton Jones

> I just reread Dima's answer to my query about the database access in
> particular and am confused.  Dima says that he can't allow queries
> outside the IOMonad because he has to worry about freeing memory (query
> output).  
> 
> However, Haskell/Com (built on top of Greencard?) seems to be able to
> propagate garbage collection information from Haskell to C so that
> when a Haskell/COM Object is no longer in use, there is some functionality
> decrements its reference counter automatically.
> 
> How does this work?  and can dima use this mechamism to free queries
> when they are no longer needed? ..allowing database queries outside
> the IOMonad?  

I think all you need is something like this:

query :: String -- The query
  -> [Result]   -- The result

query q = unsafePerformIO (do {
server <- connect "foo.bax.com";
result <- sendQuery server q;
disconnect server;
return result
  })

A use of unsafePerformIO :: IO a -> a   is a promise that the
enclosed action is indeed a function.  I.e. the proof obligation
is yours.  That's what you say you want here.

And, yes, the garbage collection should be OK.

Simon







Re: laziness and functional middleware

1998-06-17 Thread Simon L Peyton Jones


Alex,

> > main = do  input <- getContents
> >  putStr $ addTwo $ makeLines input
> 
> > addTwo lines = ask1++(ask2 (Strict x)) ++ (result (Strict y))
> > where   x:y:xs = map read lines
> > ask1   = "Enter an Integer: "
> > ask2 _ = "Enter another Integer: "
> > result _ = "Theis sum is "++show (x+y)++"\n"
> 
> > data (Eval a) => Strict a = Strict !a
> > makeLines text = 
> >  (takeWhile ('\n'/=) text): (makeLines $ tail (dropWhile ('\n'/=) text))
> 
> But this code doesn't work.  It prints all the text and then waits for
> input.  Shouldn't laziness guarantee that addTwo doesn't print "Enter
> another integer" until the user enters the first integer?  (that is what
> the file copy example in the tutorial implies) 

What is "Strict".  If you said (x `seq` ask2) instead 
of (ask2 (Strict x)) then you should get the behaviour you expect.
There's a critique of various I/O models in 

%A P Hudak
%A RS Sundaresh
%T On the expressiveness of purely-functional I/O systems
%R YALEU/DCS/RR-665, |DCS|, Yale University
%D March 1989

I don't know whether it got published anywhere.


> For example I am writing an application that handles HTTP transactions 
> and uses a database backend.
> Ideally, I would like to write cgifunctions of type:
> 
> myCGIFunction:: [HTTPRequest]->[DatabaseVersion]->
>   ([HTTPResponse],[DatabaseChanges])
> 
> HTTPRequests come from _middleware_ that recieves http requests from the
> httpd and append them to a list. Attempts to get the next item in the
> HTTPRequest list block until requests come in to fill the list.
> 
> DatabaseVersions come from a driver that appends a new txnBegin object
> to a list.
> 
> The program would look something like:
> main = do 
>   (dbSource,dbSink) <- dbConnect "ODBC: someodbcurl"
>   (httpSource,httpSink) <- apacheConnect "urlToListenOn"
>   (httpResponses,dbUpdates) <- return $ myCGIFunction httpSource dbSource
>   dbSink dbUpdates
>   httpSink httpResponses

I gather that HTTPRequests and DataBaseVersions arrive 
asynchronously and unpredictably.  So how does myCGIFunction know
which list to probe first?  Whichever it chooses it may block on
one while there is data on the other. Unless I'm misunderstanding.

You need to be able to say "wait until there's input available
on one of these two ports, and tell me which".  Something like
the Unix select call.  GHC's Posix library has such a thing,
but you can't use it in the way you describe because myCGIFunction
is a pure function on lists.


So far as your dbSink is concerneds, presumably what you have in mind is that
(dbSink dbUpdates) spins off a concurrent process that pulls on dbUpdates and
sends them to the database.  Concurently, httpSink is doing the same.


In short, lots of concurrency and non-determinism.  Fine!  That's
what Concurrent Haskell is for.  You can find a paper saying what
Concurrent Haskell is intended for.
http://www.dcs.gla.ac.uk/~simonpj/papers.html
(under "monads, state, and concurrency").

I hope this helps somewhat.

Simon





Re: FW: Exceptions are too return values!

1998-06-16 Thread Simon L Peyton Jones


> Simon, I'm sure that a really thorough programmer such as yourself
> would never forget to insert such a test.  But, as was recently
> demonstrated on this mailing list ;-), I'm quite fallible.
> I'm sure there are many other fallible Haskell programmers around.

Don't worry, I'm fallible all right, as much GHC bug mail demonstrates!

> Now, we can certainly debate the likely frequency of such bugs, and
> their cost, and compare this with the advantages and disadvantages
> of exception handling.  In fact, it does seem likely that such
> bugs would be very rare.  The cost of each such bug may be high,
> but if they occur infrequently enough, then the overall cost will be small.
> So maybe you just meant that it wasn't likely to be a significant problem
> in practice.  If that was what you meant, then I'm inclined to agree
> with you.

Yes, that's what I meant.  I'm probably guilty of overstatement.
I do strongly feel that the cost/benefit equation comes down strongly
on the side of the NDSet story.

> > I simply don't think it's reasonable to comletely prescribe
> > the evaluation order of a lazy functional program.
> 
> Why not?  Because it would inhibit optimization?

Not just that; it also places extra side conditions
on reasoning about programs: now any reasoning steps
have to preserve evaluation order.  

Incidentally, if you *do* want to preserve evaluation order
then you can always use "seq".  GHC guarantees not to move
evaluations past "seq".

Simon





Re: FW: Exceptions are too return values!

1998-06-16 Thread Simon L Peyton Jones


> I thought about this problem some more, and I have realized that the
> problem of nondeterminacy for Haskell exceptions would in fact be
> considerably worse that I had previously considered.  The trouble is
> that in the general case the problem is not just that the choice of
> which exception is raised is nondeterministic -- instead, it would be
> much worse: the choice of whether you raise an exception or loop
> forever can be also be nondeterministic.  This occurs because of
> expressions such as `0/0 + loop'.  Or, to take a more realistic (and
> nasty) example, `f 0' where `f x = 1/x + g x' where `g x' happens to
> loop if `x' is zero.

I don't agree that this is a problem.  If (g x) loops when x is zero
then you should jolly well test for that:

f x | x == 0= raise "x is zero"
| otherwise = 1/x + g x


I simply don't think it's reasonable to comletely prescribe
the evaluation order of a lazy functional program.

At the moment, Haskell has the fiction that a divide-by-zero
exception and non-termination are the same value, i.e. bottom.
That allows us to say that the behaviour of

f x = 1/x + g x

is identical regardless of whether "+" evaluates its first
argument first or second.  But we all know that the behaviour
in these two cases is quite different: one prints a message and
halts, and the other fails to terminate.  So in this sense
the behaviour of Haskell programs is already non-deterministic.

The nice thing about the NDSet story is that it makes clear
precisely where the non-determinism occurs.  Equational reasoning
is not impaired, nor is the implementation penalised.  I think
it's a great idea.

So I appear to be in disagreement here with Alex, Amr, and Fergus about
the importance of being able to say precisely which exception is raised.
I'm quite content with knowing which *set* of exceptions can be raised.
Ha!

Simon






Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones

> I was keeping quiet myself, because I am planning to write
> a paper touching on this topic.  But the cat seems to be
> mostly out of the bag now, so I might as well pipe up.

I'm glad you did.  That's a neat idea.  I'm familiar
with the NDSet idea -- that's in the Hughes/O'Donnell
paper that Kevin cited.  The new thing you add is
using the NDSet for the *exceptions*, rather than
for the "main value".  (It would be hopeless for every function
that could raise an exception to get an NDSet in its result
type, and hence required NDSet ops to manipulate.)  

I'll need to think more about this.  Have you got a paper on
the way?

Simon





Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones


> Just to reiterate.  I strongly urge you to ensure consistent exception
> behavior.  As a matter of course, two different compiles should not result
> in two different programs. 

One of the wonderful things about functional languages is that they
do not prescribe the order of evaluation.  To achieve the effect you
want would require us to completely prescribe that order, with
very bad effects on efficiency.  For example, consider

f :: [Int] -> Int

Suppose that an analyser figures out that f evaluates every
element of its argument list to produce its result.  Then it
is OK for the producer of the list to evaluate those thunks
right away, rather than building thunks for f to evaluate.

But if we are required to ensure consistent choice of exception
values then we can't do that any more, because the producer
might evaluate the thunks in a different order to f.

This is a big issue for a lazy language.

I really think that the thing to do is leave it unspecified
which exception is chosen.  In practice, only changing the
compiler's optimisation level is likely to change the program's
exception behaviour.

Simon


> As a matter of course, should we assume that these extensions
> (exceptions, existentials) will become part of Haskell or are they just
> part GHC?  Will they be part of Hugs?

Hugs and GHC will be consistent.  Whether it's a feature deemed
worthy of being Officially Incorporated into Haskell is not
something we'll know for a while.  It's much more likely
to be so incorporated if its implemented and found useful, though.








Re: FW: Exceptions are too return values!

1998-06-11 Thread Simon L Peyton Jones

> Another question: Is "handle" strict in the following argument:
> 
>   handle :: (IOError -> IO a) -> IO a -> IO a
> ^
> (meaning: will "handle f (return bottom)" be bottom?)

Good question.  No, it's not strict in that sense.

Simon





Re: FW: Exceptions are too return values!

1998-06-10 Thread Simon L Peyton Jones


Alastair Reid has been very quiet, so I'll pipe up for him.

Here's a reasonable design for exceptions in Haskell:

* A value of Haskell type T can be
EITHER one of the values we know and love 
   (bottom, or constructor, or function,
depending on T),

OR it can be a set of exceptional values.

* raise :: String -> a
  (raise s) returns a single exceptional value, named by string s

* All strict operations (case, +, etc) return the union of
  the exceptional values returned by their strict arguments
  For example, if both arguments to "+" return an exceptional value
  then "+" returns both. Similarly, any strict context.  

* handle :: (String -> IO a) -> IO a -> IO a
  (handle h a) tries to perform the action a.
  If doing so delivers a set of exceptional values then
  apply the exception handler h to the string that names
  one of them.  It is not defined which of the exceptional 
  values is picked.


The neat thing about this is that the exceptions can
be *raised* in arbitrary purely functional code, without
violating referential transparency.  The question of
which exception is chosen is done in the IO monad, where
of course it is allowed to be non-deterministic.
The implementation does not keep sets of exceptional values,
of course.  It simply propagates the first one it trips
over to the nearest enclosing handler.

(It is likely that successive runs will actually give
the same behaviour, but recompiling the program with
(say) different optimisation levels might change the order
of evaluation, and hence change which exception is tripped
over first.)

We're implementing an experimental version of this
in GHC, integrated with the IO monad exceptions, so that

handle :: (IOError -> IO a) -> IO a -> IO a

and we add an extra constructor (UserError String) to the
IOError type for exceptions raised by raise.

Calls to "error" also show up as an exceptional value, of
course.

One merit of the system is that it chops out a tremendous
number of run-time error checks in the IO monad, since
we are now free to implement the mechanism with standard
stack-unwinding techniques.  Result: much better I/O performance.


I'd be interested to know what people think of this.

Simon






Re: circular module imports

1998-06-09 Thread Simon L Peyton Jones


Alex,

If I were you I'd dispense with "deriving(Read,Show)" in module Publisher,
and add an explicit instance for Read/Show on Publisher in PublisherDB.
That would solve your circularity problem.

Haskell does permit mutually recursive modules, but Hugs does not support
them, and GHC requires some help (described in the user manual; basically
you need to give it an "interface file" to get started).

Simon

> I wanted to represent a reasonably small list of Publishers.
> So I created:
> 
> > module Publisher where
> > data Publisher = Publisher { name::String, func::Registration->Bool}
> > data Registration = 
> > Registration { data::String, pub::Publisher} deriving (Read,Show)
> 
> Notice that the Publisher data type includes functions so I can't just
> store these publishers as tuples in a database.  Instead I store
> information on each publisher in a file e.g. Yahoo.lhs CNN.lhs
> DoubleClick.lhs
> 
> > module Yahoo where
> > import Publisher
> > Yahoo = Publisher "Yahoo" (\x -> x)
> 
> Another file, PublisherDB.lhs, imports each of these 
> 
> > module PublisherDB where
> > import Yahoo
> > import DoubleClick
> > publishers = [("Yahoo",Yahoo),("DoubleClick",DoubleClick)]
> > getPublishers::String -> Publisher
> > getPublisher name = lookup publishers name
> 
> The trouble I have is that Registration requires me to define
> read/show for Publisher and read/show requires access to getPublisher
> which leads to a circular import problem:
> * getPublisher needs to be defined in PublisherDB because it requires a
> complete list of Publishers.  
> * PublisherDB imports each individual publisher (e.g. Yahoo, DoubleClick)
> Individual publishers import Publisher
> 
> For literate programming reasons, as well as general program modularity
> reasons, I would prefer not to merge all of these into a single large
> file.
> 
> Is there another way?
> 
> 
> -Alex-
> 
> ___
> S. Alexander Jacobson i2x Media  
> 1-212-697-0184 voice  1-212-697-1427 fax






Re: classes and instances

1998-06-08 Thread Simon L Peyton Jones


> data Weirder a b = Weirdest a b
> 
> class Weird c where
> f1 :: c -> c
> f2 :: Weirder a b -> c -> Weirder a b
> f3 :: Weirder a c -> Weirder c a
> f4 :: c -> c -> Bool
> 
> instance Weird (d,e) where
> f1 (x,y) = (x,y)
> f2 w (x,y) = Weirdest x y
> f3 (Weirdest x y) = Weirdest y x
> f4 (x,y) z = True
> 
> The complaint is:
> 
> ERROR "x.hs" (line 11): Declared type too general
> *** Expression: f2
> *** Declared type : Weirder a b -> (c,d) -> Weirder a b
> *** Inferred type : Weirder a b -> (a,b) -> Weirder a b
> 
> It is complaining that in the class, the type of the second
> parameter to function f2 has a simple type "(c,d)", which is unrelated
> to the type of the arguments to the constructor Weirdest, namely a and b.

That's exactly the complaint.  

> In the instance, the type of the second argument to f2 must be the same
> types as the arguments to the constructor Weirdest. But this is exactly what
> I want, I want the function in the instance to be valid over a more specific
> type than in the class. This seems to have worked for f1, f3 and f4, but
> not for f2. What am I missing here? Is there a way to define this?

In f1, f3, f4, the way in which the instance is "more specific" is that a type
variable (c, in the class decl) is instantiated by a type.  So for f1, the 
class decl
said
f1 :: c -> c
and the instance decl instantiated c to (d,e), giving the type
f1 :: (d,e) -> (d,e)
And that is indeed the type of the f1 you give in the instance decl.  Ditto 
f3, f4.
But for f2, if we instantiate "c" we get

f2 :: Weirder a b -> (d,e) -> Wierder a b

You correctly say that you want a still more specific type.   Without
understanding your application better I am nervous about recommending
this, but you *can* get what you say you want by using a multi-parameter class

class Weird a b c where
   ...
  f2 :: Weirder a b -> c -> Wierder a b
  ...

and now use the instance

instance Weird d e  (d,e) where
 f2 w (x,y) = Weirdest x y

But multi-parameter type classes aren't a panacea.  It may be that there's a 
more direct
way to achieve what you really want.

Simon







Re: data or class inheritance

1998-06-05 Thread Simon L Peyton Jones


> I have a base class,Organization, with name and address functions.
> I want classes Buyer and Seller from Organization.
> 
> Now if I want to create an 2 instances of Seller
> > data Yahoo = Yahoo
> > instance Organization Yahoo where
> >  name _= "Yahoo"
> >  addreess = ...
> 
> > data DoubleClick= DoubleClick
> > instance Organization DoubleClick where
> >  name _ = "DoubleClick"
>   ...
> 
> Why is [Yahoo,DoubleClick] illegal?  

It's illegal because we can't give it a type.  It hasn't got
type [Yahoo], nor [DoubleClick].  What you want is to say 
"it's a list of things in class Organization, and that's all I will
ever ask of them.  In hbc (and soon in GHC) you can say:

data OrganizationThing = forall a. Organisation a => MkOrg a

(Some people would write "exists" instead of "forall", and that's
reasonable.  But the type of MkOrg really is

MkOrg :: forall a. Organization a => a -> OrganizationThing
)

Notice that OrganizationThing isn't parameterised.

Now you can say

foo :: [OrganizationThing]
foo = [MkOrg Yahoo, MkOrg DoubleClick]

Further, you can say, for example

toName :: OrganizationThing -> String
toName (MkOrg o) = name o

In effect, an OrganizationThing is anything that in in class 
Organization. The MkOrg constructor is a bit annoying (like newtype)
but no more.


Does that help?  I'm about to put existentials into GHC.  It's
been delayed while I ripped its entrails out; adding existentials
and then keeping types throughout the compiler caused a non-trivial
change that I took advantage of to perform a heart-liver-and-lung
transplant.

Simon






Re: order of evalutation of ||

1998-05-29 Thread Simon L Peyton Jones

> 
> If you have a statement like:
> 
> result= a || b || c 
> 
> does Haskell guarantee that a gets evaluated before b?
> If it does then I only have to protect against pattern match failure in
> one place, a.

Yes; if a is true, b and c won't be evaluated.  That's part of
the defn of ||

Simon





Re: SLPJ Moving to Microsoft

1998-05-22 Thread Simon L Peyton Jones


> I was a little surprised to read this too.  You make it sound as if GHC's
> free status was in jeopardy.  Should we all go running for the hills if
> Microsoft decides to crook its little finger in our direction?  I'm glad
> that you will continue to contribute to GHC, but it scares me to think that
> GHC's continued existence depends on Microsoft's "happiness."

That is not the case.  GHC's free status is not in jeopardy.  I'm sorry
if I made it sound like that.

GHC as it now is does not depend in any way on Microsoft's attitude;
how could it?

In principle, my own *future* contribution to GHC do depend on MS's attitude.
I have taken care to check that it is one I am happy with; i.e. they
are delighted for me to continue work on GHC, and publish that source
code publicly.

I know that you've all added smileys, but this is important to me!

Simon






Moving to Microsoft

1998-05-21 Thread Simon L Peyton Jones


Folks,

As some of you will by now know, I am leaving Glasgow.  I'm going
to move to the Microsoft Research lab in Cambridge (England), 
in September 1998.

This is a big upheaval for me, but it's one I'm pretty excited about.
[Lest you should wonder, my reasons for moving are personal and 
family ones, not dissatisfaction with the department here, which I 
still think is terrific.]

Anyway, I plan to continue to do functional programming research, at 
least for the forseeable future (which is as much as has ever been the 
case).  More specifically, I plan to continue beavering away on GHC.
GHC is public domain software, and Microsoft are happy for it to 
remain so, source code and all.  If anything, I'll have quite a bit
more time to work on it than before.

Of course, I hope that being at Microsoft will expose me to all sorts
of new ideas and challenges, too. The Cambridge lab is growing into 
an exciting place to be; for example, Luca Cardelli and Andy Gordon 
are there.

But meanwhile I wanted to reassure those of you who use
GHC that it is still very dear to my heart.  I will continue to 
burn your CPU cycles in new and exicting ways for a while yet!

Simon







Re: doubles-troubles

1998-05-12 Thread Simon L Peyton Jones


> rigid and I belong to the small legion of amateurs who implemented their
> own math. domain system, Rings, Fields, Modules, etc. This apparently
> has no chance to be included into the Haskell standard, nobody cares.

Standards develop because people who care about particular aspects
of them push them forward.  It is not true that nobody cares.  It may well
be true that nobody has time to make a well-documeted and well-implemented
library.  You could change that.  [I mean you plural; readers of this list.]

To be specific, why don't you package it all up as a documented Haskell
library? We'd be happy to distribute it along with GHC, and I bet the 
Hugs team would too.  

After a while, if people liked it, it would become so popular it
would become part of the standard.

I'm serious.  We are busily developing libraries shared between GHC
and Hugs that aren't part of the official standard, but are at least
common between our two impls, and available to all other impls too.
ftp://haskell.org/pub/reid/libs980219/libs.html

Send us your code!

Simon





Re: C to Haskell

1998-05-12 Thread Simon L Peyton Jones

> Greencard allows Haskell to call C (or Corba).  Is there a way to give C
> code access to Haskell functions?

GHC does not yet allow this, but we are working hard on H/Direct,
a successor to Greencard, that will.  It'll also allow you to
seal up Haskell programs inside COM objects.  Timescale: a month
or two rather than a day or two.

Simon





Re: Pattern Match Success Changes Types

1998-05-11 Thread Simon L Peyton Jones


Yes, GHC does some CSE stuff, but not very much. I don't think it has a large
performance impact, but (as luck would have it) but I plan to work on it a bit
in the newt few months.

My advice would be: write clear code, and let the compiler do the
CSE.  If it doesn't, complain to the compiler writers.   You have
good reason to believe that it should.

The exception is the case you've been discussing.  The type of Right
is not

   Right :: b -> Either _ b

(I don't know what "_" is) but rather

   Right :: forall a,b. b -> Either a b

Since GHC keeps the types right through the compiler, it
really can't do CSE on two terms of type

Either Int  Int
Either Bool Int

even if they are both applications of Right.

Actually, GHC does finally discard type information right at the
end, so we could do an extra bit of CSE there, but frankly I doubt
it would buy very much.  But I'm willing to stand corrected.

Incidentally, I don't think it would be sensible to change
the type system to allow the 

 demo1 :: (a -> b) -> Either a c -> Either b c
 demo1 f (Left  a)   = Left (f a)
 demo1 _ r@(Right c) = r

What type does r have?  Either a c.
What type does the result of the fn have?  Either b c.
Different types.  It would be hard (I believe) to specify crisply
when it was legitimate for two terms with different types to
be as'd together.

Simon





Re: Binary, Conversions, and CGI

1998-05-06 Thread Simon L Peyton Jones


> To the newcomer who is not part of the FP academic community, this all
> makes life sort of difficult.   These differences seem larger than the
> differences among C compilers and are MUCH larger than the differences
> among Java compilers.   I have been trying to learn Haskell and have been
> impressed with both its elegance and the way it allows me to write code
> that works on the first try (or two).

These are fair comments.  In my view the things that are holding back
Haskell are not language issues at all.  They are

- foreign language interfaces
- libraries
- programming environments

There are a bunch of people working on all of these, but the results
are not yet stable.  In particular

* On foreign language interfaces, we have now been through several iterations
  of Green Card, and are poised for what I hope is our final "take",
  currently called H/Direct.  There's a paper on my Web page, and an
  implementation on the way.  http://www.dcs.gla.ac.uk/~simonpj
  [I say "we" meaning "Glasgow plus many
  colleagues", notably Yale, York, Utrecht.]

  Foreign language interface implementations have certainly been a 
  moving target.  It would be better to get it "right" first time,
  but worse to have "standardised" prematurely.

* On libraries, there is quite a lot going on.  GHC and Hugs have some
  more or less standardised libraries going well beyond the Haskell 1.4
  set.  The Binary library is a hot topic.  E.g. Glasgow and York had
  a full-day meeting on this very topic two weeks ago; that should lead
  to a library proposal (based on the current York story) 
http://www.cs.york.ac.uk/fp/nhc13/binary.html
  for the world to discuss/critique, and thence to implementations
  for GHC and Hugs as well as NHC.

  As ever, these things take time.

* On programming environments, we are working hard on integrating GHC
  and Hugs.  It's coming, promise.


Of course, all this just describes stuff I know about.  There are probably
other people beavering away on good stuff; please sing out!


> However, I am not a researcher.  I do commercial software development and
> need some documentation and stability.  I understand that everything here
> is fairly new, but it would be really usefl if someone would post a
> summary of the FP community politics for those of us outside the research
> community:
> * What verions of Haskell should someone outside the research community be
> using.  e.g. is GHC ver x particularly experimental?  Is Haskell as a
> whole really a research language and not ready for commercial
>   (e.g. high intensity server based) applications?

Hmm.  GHC 2.10 is rather solid.  GHC 3.01 is more experimental.
http://www.dcs.gla.ac.uk/fp/software/ghc/

I would love for Haskell to be used for high-intensity applications,
but before betting my company on it I'd protype my application.
Our research priorities these days are heavily influenced by
what people say they need; so talk to us.

> * Any particular language features that we should avoid or that are
> likely to change?

In Haskell 1.4 the main proposed simplification is that [x | x<-xs]
will mean a *list* comprehension rather than a *monad* comprehension.
I think the libraries are much more volatile than the language.

> * Who "owns" haskell?  How are decisions made about what goes in/out of
> the language? Who controls the content of Haskell.org?

The whole thing is pretty informal.  There no "official" standardisation
body etc. Instead, there is a working group chaired by John Hughes,
which is trying to develop "Standard Haskell".  More info at
http://www.cs.chalmers.se/~rjmh/Haskell

The discussion is readable by all, but only writable by the working
group.  This is admittedly only semi-democratic; but it is a way 
of making progress.

As Will says, I think the whole scene is pretty exciting. The Haskell community
works together well; and the focus is increasingly on making a *usable*
language. The main difficulty is simple lack of available effort: anyone who
wants to contribute to any of these things, speak up!

All of this reflects my own personal views; I don't claim to speak
for anyone else.

I hope this helps.

Simon






Re: binary search

1998-04-17 Thread Simon L Peyton Jones


> Not to reject assertions (they would be welcome), but I think that you
> need something slightly different in a functional programming language.
> 
> Assertions in procedural languages typically define system state before
> and after a particular function gets executed.
> 
> State assertions are less appropriate to functional programming languages
> (except in the context of the content of monads but that is a separate
> issue).  As I understand it, Haskell programmers should use the type system to 
>prevent
> functions from getting called w/ operands outside their domain.
> For example, a very careful programmer would specify that division is only
> allowed on a type that has already filtered out 0 
> e.g.  
> > newType NonZero :: MakeNonZero Num
> > toNonZero:: Num -> NonZero
> > toNonZero x | x==0 = error "Shouldn't be zero"  
> > | otherwise = MakeNonZero x

Using the type system is often entirely impractical, because
the things you want to check may not be statically checkable, at
least not within the computational language the type system provides.

Inside GHC we make extensive use of assertions.  In the example you give
we might say

divide :: Int -> Int -> Int
divide a b = ASSERT( b /= 0 ) a/b

The ASSERT expands to

if not (b /= 0) then error "Assertion failed on line 27 of Foo.hs"
else a/b

In Haskell 2 I think assertions will be standard.  (So far we have
used the C preprocessor to add them, but they should jolly well be
in the language.)

It's *very* important to be able to turn all assertion-checking off, easily.
Then programmers will write expensive assertion checks 
ASSERT( length xs < 100 )
ASSERT( isBalanced tree )
which they would never write if they thought these checks formed
a permanent part of their code.

In our experience assertions are quite a potent debugging tool.
Note that they can check post-conditions as well as pre-conditions:

f x y = ASSERT( pre x y && post x y r ) r
  where
r = ...body of f...

Simon





Re: binary search

1998-04-16 Thread Simon L Peyton Jones


> 2. how would I have found/fixed such an error in a more complex function
>   w/o assertions and w/o print statements?

Good questions

There was a proposal to put assertions into Std Haskell, which we
have implemented in GHC.  (I'm not sure we've yet put that version out
though.)  So assertions are definitely coming. You are right that they
are important.

Finding infinite loops in functional programs is quite hard.  Colin
Runciman and Jan Sparud have been working on "redex trails".  We
plan to help at least identify where the loop is by putting out
cost-centre-stack information... but that's still in the works.

Simon





Re: Multiple Parameter Class in Hugs -- Please!

1998-04-06 Thread Simon L Peyton Jones


> > infixl 7 *$
> > infixl 6 +$, -$
> > class Ring a where
> >  (+$), (-$), (*$) :: a -> a -> a
> >  negateR :: a -> a
> >  fromIntegerR :: Integer -> a
> >  zeroR, oneR :: a
> 
> It's particularly irritating having to use many of the Num methods and   
> therefore having to give them different names.

Suggestion: use qualified imports:

module Structures where
import Prelude hiding( Num(..) )

  class Ring a where
(+) :: a -> a -> a 
...etc...

  instance Ring Integer where
(+) = (Prelude.+)
...etc...

When you import Structures elsewhere you must either import it
qualified, or else hide Num(..) from the Prelude, so that "+"
always means exactly one thing.

I'n not sure whether this module jiggery pokery works in Hugs,
but it does in GHC.

Simon





Re: Binary files in Haskell

1998-03-11 Thread Simon L Peyton Jones


> Real world example: development tools process a large geometric data set to
> build a run-time optimized BSP tree with precalculated lighting and
> collision information.  The user application will not modify this data, but
> it will have to load it dynamically without slowing down a 30Hz
> graphics/interaction loop. (Apologies to Quake and Mario 64 :)
> 
> Solution in C: load the data as contiguous raw bytes and cast pointers into
> the block to the appropriate structure types.
> 
> Solution in Haskell?

Malcolm Wallace and Colin Runciman at York have been working
on this kind of thing.  They had a paper at the Haskell workshop
last year (which is on Malcolm's home page 
http://www.cs.york.ac.uk/~malcolm/).  I believe they are near to
releasing a revised version.  

It only works for nhc at the moment, but if enough people like you yell loudly
enough (construe this positively!) then we'll put it into GHC/Hugs too.
Our priorities are largely driven by what people ask for.

Simon






Multi-parameter type classes in GHC 3.01

1998-02-25 Thread Simon L Peyton Jones


> PS. Could somebody inform me what is the current status of
> multi-parametric classes?


GHC 3.01 supports multi-parameter type classes
in more or less the form described in the last section of
"Type classes: an exploration of the design space"
(http://www.dcs.gla.ac.uk/~simonpj/multi.ps.gz)


We only mentioned this eliptically in the announcement, but
it should really have been a headline!  (The reason is that
we'd previously released 3.0 to friends, so we'd forgotten
that not everyone knew..)

It now seems very likely that Standard Haskell will support
multi-parameter type classes, and GHC 3.01 is our attempt
to gather feedback about whether we are moving towards
the right set of design choices.

The main limitation at the moment is

no overlapping instance declarations

There are ways to lift this restriction, but it's a conservative
first choice.

Please try it out, and let us know if you trip over
(a) bugs
(b) obscure error messages
(c) design restrictions that cramp your programming style

The URL is

http://www.dcs.gla.ac.uk/fp/software/ghc/

Simon





Want a job?

1998-02-24 Thread Simon L Peyton Jones


I'd be delighted if a programming-language-aware person applied for this
(tenured) post.  Deadline 13 March.

Simon

Lectureship in Computing Science
University of Glasgow

The University invites applications for a permanent lectureship in the
Department of Computing Science.

The Department has demonstrated the highest standards in both teaching and
research.  We are actively developing new courses, at both undergraduate
and postgraduate levels, and have a thriving research community.
Applicants must possess the experience, enthusiasm and ability to enhance a
vigorous research environment, together with the creativity and energy to
contribute to our educational excellence.

Applicants will be considered from any area of computing science, but
preference will be given to those who match our teaching commitments and
who complement or strengthen our research interests.

The appointment will be on the Lecturer A or B scale (?16,045??27,985
p.a.), at a point determined by age, experience, and ability.

Informal enquiries may be made to the Head of Department, Mr Ray Welland,
e-mail [EMAIL PROTECTED]  Information about the Department and further
information about this post may be found on WWW at
http://www.dcs.gla.ac.uk/announce/.

Further particulars may be obtained from the Personnel Office, University
of Glasgow, Glasgow G12 8QQ, Scotland (tel. 0141 330 6094, fax 0141 330
4921).  Applications (eight copies from UK applicants, one copy from
overseas applicants) must be sent to this address by 13 March 1998.  Each
application must consist of: a curriculum vitae, including a list of
publications and a covering letter explaining why you wish to be considered
for the position, a brief statement on the state of your health and details
of any period of probation served elsewhere and any relevant training.  You
should also submit a personal information form (available from our Web
site) including the names and addresses of three referees.  In all
correspondence please quote reference number 060/98AL.








Re: Binary files in Haskell

1998-02-23 Thread Simon L Peyton Jones


> I would like to use Haskell for several larger scale projects, but I
> can't figure out how to read and write binary data.  It does not appear
> that the language supports binary files.  Am I missing something?

Colin Runciman and his Merrie Men are working on writing
Haskell values into binary files with the additional feature
that the files are compressed.  There was a paper in the '97 Haskell
workshop and I know he's been working on it since; but I don't
think a "product" has emerged for general use.  But with encouragement
perhaps it will!

Simon





Re: No field labels?

1998-02-04 Thread Simon L Peyton Jones

> Is there any reason for not allowing:
> 
> > data Test = Test {}
> 
> in Haskell? 

I can't think of one.  Maybe Std Haskell should allow it.
I'll put it on the Std-Haskell board.

Simon





Re: Ambiguous Type Error

1998-01-05 Thread Simon L Peyton Jones

> I have enclosed below a test file that causes an error that puzzles
> me.  Both GHC and Hugs kick it out, so at least they agree; however, I
> must admit that I don't understand it.

Yes, it is a bit confusing, and it took me a few minutes
to see what is going on.

Here's your problem:

> data (Physical indep, Physical dep) => BasicSignal indep dep = 
> Pulse {start_time::indep,
>pulse_width::indep,
>amplitude::dep}
>
> pulse:: (Physical a, Physical b) => BasicSignal a b
> pulse = Pulse{start_time = toPhysical 0.0}
> 
> example2:: BasicSignal Time Voltage
> example2 = pulse {start_time = (Sec 1.0),
>   pulse_width = (Sec 3.0),
>   amplitude = (V 2.0) }

The RHS of example2 is (by definition in the Report) equivalent to

  example2:: BasicSignal Time Voltage
  example2 = case pulse of
Pulse _ _ _ -> Pulse (Sec 1.0) (Sec 3.0) (V 2.0)

The trouble is that "pulse" is overloaded, and the compiler
has no clue which overloading to use.  The fact that example2 has
a type signature doesn't help it, because none of the components
of "pulse" make it through to the output.  So it's ambiguous.

The solution is to say:

   example2 = (pulse :: BasicSignal Time Voltage) {
start_time = Sec 1.0,
pulse_width = Sec 3.0,
amplitude = V 2.0
}

Now the type signature on "pulse" tells it what overloading to use.

You may think it's silly that "pulse" needs to know what overloading
to use, even though the fields concerned (start_time in this case)
are immediately overwritten... but there's nothing to stop "pulse" 
returning two quite different records based on operations from the
Physical class, so you're asking the type system tp do something it
just can't.

Incidentally, the context on your data type declaration adds nothing 
useful.  (We're thinking of nuking them in Std Haskell.)

Simon






Re: Xmas fun

1997-12-20 Thread Simon L Peyton Jones


> This bug could have been caught by a very simple static analysis that
> is very popular in the logic programming community: singleton variable
> warnings.  In the code above, the variable `v2' occurs only once.
> Singleton variables such as this are often bugs.  For cases where the
> programmer really does want a singleton variable, the warning can be
> suppressed by using a different naming convention (in Prolog, it
> would be `_v2'; since Haskell doesn't allow leading underscores,
> I suppose you could use `v2_').

OK, OK, the next release of GHC will (if you ask it) report
unused imports and bindings, and report shadowed bindings too.

Simon






Xmas fun

1997-12-19 Thread Simon L Peyton Jones


Folks,

I thought you might find the following bug I've just
found in GHC entertaining.

In the strictness analyser we need to compare abstract values
so that the fixpoint finder knows when to stop.  In the
middle of this code was the following:

sameVal :: AbsVal -> AbsVal -> Bool

...equations for sameVal...

sameVal (AbsApproxFun str1 v1) (AbsApproxFun str2 v2) 
= str1 == str2 && sameVal v1 v1

...more equations...

That "sameVal v1 v1" should of course be "sameVal v1 v2".

Because sameVal reports equality more often that it should,
the fixpoint finder stops sooner than it should, so the strictness
analyser finds that things are strict when they aren't.  But
this only occurs in slightly obscure situations... and somehow
this bug has gone un-noticed for I dread to think how long!

It showed up in a nofib test -- sing ho for regression tests.

Happy xmas

Simon






Re: Overlapping instance declarations.

1997-12-10 Thread Simon L Peyton Jones


> "A type may not be declared as an instance of a particular class more than
> once in the program."
> 
> Doesn't it really mean that a type _constructor_ may not appear in more
> than one instance declaration for a particular class?  That (stronger)
> condition seems to be what ghc and hugs implement, and probably makes more
> sense, given the rationale of the overlapping instance rule in the first
> place.

Yes, that's right.  In Std Haskell, though, the situation is likely to be
that "two instance decls may not overlap", where "overlap" means that
the two instance heads are unifiable.  The instance head is the bit
after the "=>".


> Specifically, I'm thinking of situations such as:
> 
> instance A a => C [a]
> 
> instance B a => C [a]

Here the instance heads overlap.  The fact that A and B are different
is neither here nor there.  (One could imagine allowing overlapping
inst decls where the type was an instance of only one of A or B, but
that's quite a bit more complicated.)

Simon









Re: Call for parsers

1997-11-13 Thread Simon L Peyton Jones


> So here is my call for contribution:
> 
>Send an abstract syntax and/or a parser specification!
> 
> It doesn't matter if a parser generator is used or recursive descent
> techniques are applied.
> 
> If there is enough echo, I'd like to setup a web page for this
> project, containing things to download, documentation, and giving a
> forum for discussions and applications of the parsers. Ideas range
> from simple formatting tools to library browsers ("I know there is a
> function with a similar type signature somewhere...") or computer
> aided source-to-source transformations.


Good for you!  

I believe that Happy is either very nearly capable of supporting
a full Haskell parser, or is so capable (but nobody has built one).
Simon Marlow can doubtless advise.

In any case, a Happy-based Haskell parser would be a wonderful
thing, along with (as you say) an abstract syntax.

One point: in GHC we are very careful to keep the full Haskell
syntax present in the abstract syntax tree.  So, 

x:[]

is represented differently from

[x]

in the algebraic data type representing a Haskell program.
That makes the data type quite a lot bigger, but it does mean
that you can print out exactly the program that was read in,
rather than an equivalent but bastardised version.


Keeping source-location info is also important.  

You might find GHC's HsSyn data types were a good start.  I don't
propose them as the Right Thing.

(And I definitely don't propose GHC's current parser.  Let's 
do it all in Haskell.)

Simon






Re: evil laziness in iteration

1997-11-05 Thread Simon L Peyton Jones

Sergey

Thanks for your various messages. I've explained your results below. 
You are right to say that
it's hard to be sure what optimisations will happen when; arguably
that's a bad shortcoming of functional programming (especially the lazy sort).
Profiling tools help a bit.
I think, though, that you have found some particularly bad cases.
I'd be very interested in other people's war stories.

It would be great to make a "performance debugging manual" for
GHC, but it's hard to find the time to do so.  Any volunteers?

Simon



You have clearly understood why

foldl1 max [1..n] 

takes lots of both heap and stack... first it builds up a huge
chain of suspended calls to max in the heap; and then when it finds
that it does need to evaluate them it takes a lot of stack to do so.

foldl_strict solves both problems by evaluating the accumulating
parameter as it goes:

foldl_strict k z [] = z
foldl_strict k z (x:xs) = let z1 = k z x
  in seq z1 (foldl_strict k z1 xs)

(I prefer "seq" to "strict", but its a matter of taste. Haskell provides
both.)  The seq forces z1 to be evaluated before the recursive call.

* Why isn't maximum in the Prelude defined using foldl_strict?  No
  reason: it should be.

* Why do sum2 and sum3 behave differently?

sum2 xs = sum' 0 xs
where
   sum' s [] = s
   sum' s (x:xs) = sum' (s+x) xs

sum3 xs = foldl (+) 0 xs

Well, sum3 behaves badly for the same reason as before.  sum2 behaves
well because the compiler can see that sum' is strict in its first
argument; that is, it can see that sum' will eventually evaluate s.
That's what the strictness analyser does.  Having figured out that
the first argument of sum' is sure to be evaluated in the end, 
the compiler arranges to evaluate the first argument of sum' before
the call --- which gives us back something rather like foldl_strict,
and thus good performance.

Why can't the compiler spot that for sum3?  Because in general
foldl does not necessarily evaluate its second argument.

How can we get the good behaviour for sum3?  By defining foldl like
this:

{-# INLINE foldl #-}
foldl k z xs = f z xs 
  where
f z [] = z
f z (x:xs) = f (k z x) xs

Now sum3's right-hand side will turn into sum2's right-hand side
(after inlining foldl) and all will be fine.  (If you use -O.)
The only down side is that some calls to foldl won't benefit
from the inlining and for those cases the code size might go up
a bit.  We should probably make this change to the Prelude.


* Why did you get different behaviour for sum1/sum2/sum3 etc
when you split the program over two modules?  I think it's 
because you didn't put in any type signatures.   When separately
compiled, ghc generated overloaded functions, which weren't
even sure that "+" is strict.  When compiled as one, it could
see that there was only one call to sumx, inline it at the
call site, and thereby discover which "+" you meant.

* Why does your call
foldStrict addR (R 0 b) ss
take lots of space?

foldlStrict  _ z [] =  z
foldlStrict  f z (x:xs) =  let  y = f z x  in 
  y `seq` (foldlStrict f y xs)


data  R = R Int Int

addR (R x b) (R y _) =  R (x+y) b 


Reason: R is a lazy constructor.  So the addR calls get done 
strictly (by foldStrict), but the (x+y) expressions don't get
evaluated because R is lazy.  You can fix this (as you did) by
declaring R to be strict, or by putting a seq in addR:

addR (R x b) (R y _) =  let z = x+y in
z `seq` R z b 

That, in fact, is what happens when you put an "!" in R's declaration.







Re: Importing Prelude

1997-10-14 Thread Simon L Peyton Jones

 
>   The Prelude module is imported automatically into all modules as if
>   by the statement `import Prelude', if and only if it is not imported
>   with an explicit import declaration. This provision for explicit
>   import allows values defined in the Prelude to be hidden from the
>   unqualified name space.

I've always taken "if it [the Prelude] is not imported with
an explicit import decl" to mean "if the Prelude is not imported with an
explicit import decl [of any form]".  So 

> > import qualified Prelude
> > 
> > main :: IO ()
> > main = print Prelude.True

is invalid.  The Prelude is imported with an explicit import decl.
The fact that it's a qualified import decl doesn't matter.  Certainly,
the Report doesn't restrict its words to unqualified import.

Simon






Re: Numeric conversions

1997-10-01 Thread Simon L Peyton Jones


> > real2frac :: (Real a, Fractional b) => a -> b
> > real2frac = fromRational . toRational
> 
> The composition of fromRational and toRational seems to be the
> only way to convert a Double or an Int to a Double.
> 
> There is a function in the prelude, fromRealFrac, with exactly
> the same definition, but in the type signature, in place of Real
> it has RealFrac. This renders it useless as a replacement for
> my real2frac, as Int and Integer aren't instances of RealFrac.

That is odd.  It looks like a bug to me.  I'll suggest that
we change this in Standard Haskell.

Simon






Re: Deriving newtype ADTs from type ADTs

1997-10-01 Thread Simon L Peyton Jones


> However, if the transforming program took into account the information in the
> type signature (for unionMany, it would notice that the user used the type
> synonym for the inner list only), it could make pretty good guesses about which
> arguments and results to unpack or pack.

> Since the additional constructor applications and pattern matches in "newtype"
> ADTs makes them harder to read and write, I think it is useful to be able to
> generate them automatically from simpler, "type" ADTs.  Assuming that there
> are no other problems, maybe one could define some sort of derivation
> mechanism for such ADTs so that they would be imported abstractly:
> 
>   import Set'(newtype Set', union', unionMany')
>  = abstract Set(type Set, union, unionMany)

There's some disucussion about the shortcomings of newtype on the 
Standard Haskell web page.  The difficulty with the proposal you make
is that I no of no precise definition for "some sort of derivation
mechanism".A language definition can't "make pretty good guesses".
It has to precisely specify the meaning of every program.

The dilemma here is that we know that newtype has deficiencies for defining
ADTs, but we don't know a well defined and clearly superior alternative.  The
one that comes closest is Gofer's restricted type synonyms.  Newtype has the
important advantage that it's quite clear what a program means, and what
its type is.

Simon






Re: Another question about monads and linearity

1997-09-04 Thread Simon L Peyton Jones


> There are few formal connections between monads and
> single-threaded state... For any state-transformer monad... there
> is a trivial operation... that will instantly destroy any hope for
> single-threadedness: getState s = (s, s)
> 
> In day-to-day Haskell 1.3 programming what is the solution to this
> problem? If a program is using a C interface to create a mutable
> state, say an external database, what is the simplest way of
> encapsulating the state so that this "trivial operation" cannot be
> defined except by the original author?

A monad is an abstract data type.  The implementation of an ADT is
hidden, so that the client of the ADT can't invalidate its invariants.

Its the same for state-transformer monads.  The programmer can't define
this trivial operaion, because all s/he has is an ADT with an
interface like

newVar :: a -> ST (MutVar a)
readVar :: MutVar a -> ST a
writeVar :: MutVar a -> a -> ST ()
thenST :: ST a -> (a -> ST b) -> ST b
returnST :: a -> ST a

With those operations you simply can't define getState.

You might find "State in Haskell" useful (from my Web page).

Haskell 1.3 doesn't define any state-transformer monads, but both GHC
and Hugs do.

Simon






Re: Evaluating Haskell

1997-08-27 Thread Simon L Peyton Jones


David

> 1) JAVA -- Are there any plans to compile Haskell into byte codes for
> execution on the Java Virtual Machine? The Java issue is very important.

I know of a couple of prototypes of such a thing, one at Yale, and one at
Nottingham.  It is clearly do-able.  It's pretty heavyweight, though: every
thunk (i.e. nearly every sub-expression) tuns into a new class.  I doubt it
would be fast.

I don't know of anyone who has seriously committed to doing this "for real";
i.e. a full-scale, supported, implementation.

> 2) CORBA --How does the concept of objects or agents play in the Haskell
> community? Here I am (loosely) referring to an agent as a free running
> process that does things including receiving messages (or method
> invocations) from others. My interest here is trying to see how Haskell
> programs fit or can be fit into the Corba model.

I'm *much* more gung-ho about this.  I've been working with Erik Meijer
to allow Haskell programs to interact with COM objects, and CORBA is the
same basic idea.  COM/CORBA inter-work gracefully with Java too.
So far we can write Haskell programs that "script" COM objects.  We are
working on encapsulating Haskell programs as COM objects.  I don't know
enough about CORBA to know how much work it would be to do the same exercise
for CORBA, but I bet that once it's done for COM it'd be 90% done for CORBA.

> 3) Scripting language -- We bumped into Haskell while looking for a
> scripting tool in which it was "easy" to write expressions and "high" level
> statements that one would like to make "outside" of a programming
> environment. Scripting languages like Perl, Basic, etc. look just like
> programming languages to me; Perl is undisciplined and Basic is weak. Will
> engineers be able to deal with Haskell? Is there a strategy in which an
> engineer can learn a useful subset of Haskell, and grow into it as need be?
> I am unconvinced by arguments such as "this perfectly ordinary Yale
> graduate student learned Haskell in just 8 days." 

Yes, the biggest obstacle is one of education.  I believe that it's more
that Haskell is simply unfamiliar, and requires a different way of thinking,
rather than that it's hard.  But it should be a good scripting language.

> 4) Concurrency -- I saw that one of the compilers supported Concurrent
> Haskell. I don't recall seeing any mention of it in any of the material I
> have. Have I missed it?

Yes, the Glasow Haskell Compiler supports concurrency.  There's a paper
that describes how and why
"Concurrent Haskell" at
http://www.dcs.gla.ac.uk/~simonpj/papers.html

> If anyone has time, I would love to talk about this over the phone. I'm
> perfectly happy to carry on an email dialog. In the meantime I will learn
> more about Haskell on my own.

By all means phone me: +44-141-330-4500.   

Simon Peyton Jones






Re: Standard Haskell

1997-08-25 Thread Simon L Peyton Jones


> In fact, I would like to hear what all the major implementors have as their
> picture of a final version of Haskell.  You've all been pretty quiet.
> I assume you've all already aired your opinions at the workshop, but it would
> be nice to see them here as well.

Reasonable request.
I hope that my contributions to the Std Haskell Web page pretty much
say what I think.  I'm happy to fill in any gaps if someone identifies them.

Simon






Re: what's wrong with instance C a => D a

1997-08-22 Thread Simon L Peyton Jones

> The report says explicit that instance declarations like
> instance C (a,a) where ...,  or for (Int,a) or for [[a]] are not

> I now only would like to know why this design decission was made,
> are there any problems with the instance declarations I have in mind?

You might find "Type classes - exploring the design space" useful.

http://www.dcs.gla.ac.uk/~simonpj/multi.ps.gz

Simon






GHC status

1997-07-24 Thread Simon L Peyton Jones


[I originally sent this message to glasgow-haskell-users and
glasgow-haskell-bugs, but it occurred to me that it might be of more general
interest, so I'm sending it to the Haskell mailing list too.]


Dear GHC users and co-implementors

We are about to return from sabbatical in Oregon back to Glasgow, so
now seems a good time to let you know the current state of GHC affairs, and
something about our future plans.

Simon and Sigbjorn

Who's doing what


Things have been a bit slow this year, because I have been between grants,
so there have been no research assistants working on GHC. Sigbjorn has
heroically done wonders, but he's really working on his thesis, so I only
let him out to play with GHC one day a week these days.

Because I've been on sabbatical I have personally had more time to spend on
GHC, but I usually cause untold chaos when let loose to play, so you may not
have noticed a great improvement.  GHC *is* much more beautiful inside, I
promise.  It's some 10k lines shorter than GHC 0.29 in spite of growing to
accommodate Haskell 1.4.

and Simon Marlow (of Erlang type-system fame -- ICFP'97) will join up. And
there'll be several research students joining the fun.

And there's you!  Several of you have been extraordinarily helpful this
year, identifying bugs, suggesting fixes, and putting up builds that we
didn't get around to producing.  Thank you Alex, Marc, Sven, Einar, Stefan,
Meurig, Jon, Ralf, Tomasz, Andre...  GHC is much better because of your help.

I read a nice paper recently "The cathedral and the bazaar" by Eric Raymond,
reflecting on his experience Linux, and in particular of developing
"fetchmail".  You can find it at
http://locke.ccil.org/~esr/writings/cathedral.html

It's really worth reading.  One particular thing he suggests is making very
frequent releases, even if they are buggy (like daily when in intense
development mode).  I've been brought up to think that releasing buggy
software is likely to discourage one's users, but perhaps not if the
non-buggy versions (ha!) are prominently so flagged, so that "users" can
stick to them, while "developers" can pull in the latest one.  Comments? 
(Read the Raymond paper first.)

Incidentally, we have always intended that others can use GHC as a substrate
into which to "plug" new passes.  I'm painfully aware that it's a daunting
monster.  However, things have got a bit better this year. The "make" system
is vastly improved, and HAS A MANUAL that describes how it all works and how
to use it.  The internals of the compiler are simpler and cleaner.  So have
a go!

We are also always very interested in programs to add to our nofib test
suite, especially if they stress or break the current comiler. Send your
programs! If they're in our suite then we'll discover when the next release
doesn't run them, rather than you having to...

So much for who's doing what.  Now for


What's cooking
~~

* We're actively working with Erik Meijer, Daan Leijen, Alastair Reid, Colin
Runciman and Malcolm Wallace to continue the Green-Card idea.  The
currently-released Green Card allows Haskell to call C, and there are now
back ends for GHC, Hugs and nhc.  We have a not-yet-released tool that
allows Haskell to call COM (Microsoft's Common Object Model).  We are
designing ways of letting C, and then COM, call Haskell.  All this is
crucial to making Haskell something that Real People can use for Real
Projects.

* During this year we've been working on a successor to GHC's Core
intermediate language.  There are two papers that describe this work:

Henk: a typed intermediate language
Bridging the gulf: a common intermediate langauge for ML and Haskell

Both are attached to my OGI web page http://www.cse.ogi.edu/~simonpj.  If
you are using Core, don't worry. Actually implementing a new IL will be a
heart-liver-and-lung transplant operation, and I don't expect to undertake
it for at least a year.  But the design is interesting!

* I have grown increasingly dissatisified with using C as a portable
assembler, so have been working with others at OGI (Dino Oliva, Thomas
Nordin, Andrew Tolmach) and elsewhere to develop a purpose-designed portable
assembly language, called C--.  We're still refining the design, but I think
we'll put out a public straw man for you to shoot at fairly soon; meanwhile
if the idea grabs you, get in touch and I'll send you a copy.

* As you know, we plan to integrate GHC and Hugs, so that Hugs can run
GHC-compiled binaries.  That involves giving GHC and Hugs a common run-time
system, so that Hugs byte-codes manipulate exactly the same run-time
structures as GHC-compiled code expects.  This work is collaborative with
Yale (esp Alastair Reid) and Nottingham (Mark Jones), and has been moving
rather slowly.  We have a draft RTS design document, and I hope things will
move faster when we get back to 

Re: Haskell 1.4 Prelude bug

1997-07-24 Thread Simon L Peyton Jones


There's a Haskell 1.4 report bug list at

http://haskell.systemsz.cs.yale.edu/report/bugs.html

John Peterson puts the entries in, but it's really up to others to write
the entry.  

Would you like to document the bugs you've found along with the fixes
and send an entry to John?  It would be a great service to human kind.

Simon

| From: Justin Cormack <[EMAIL PROTECTED]>
| Date: Wed, 23 Jul 97 18:59 BST
| Is there an official place to send bug reports to?
| 
| There are several bugs in the lex function specified in the PreludeText
| section of the Standard Prelude for Haskell 1.4. To start with the subsidiary
| function lexLitChar is not defined. Also there is a typo isAlphaNum instead
| of isAlphanum (this typo also appears on page 34 of the Standard Libraries
| report). There are I suspect some further bugs too. Also Hugs does not lex
| the backquote character as specified in the definition.
| 
| More generally, I wonder why this is in the Prelude rather than a library
| where it would seem more appropriate?
| 
| Justin Cormack
| 






Re: Using `newtype' efficiently

1997-06-25 Thread Simon L Peyton Jones



| My question is: how much is this redundancy going to cost? Clearly the
| lambda abstraction is just id, but less obviously (pEmbed (\x->LABEL
| x))is now also id. Presumably none of the Haskell compilers can figure
| this out though? 

It should cost you practically nothing with a compiler at least.  Given 
the decl
newtype Foo a = MkFoo a

then the expression

(MkFoo e)

should be exactly as efficient as plain

e

Similarly, pattern-matching on MkFoo costs nothing.  

We can't guarantee to spot all identities, though.  For example

map MkFoo xs

still does a "map" and traverses the list, even though (map MkFoo) is
the identity function.

GHC tries fairly hard to make newtype cost very little, but because
it's a new feature I don't have many programs that make heavy use of
newtype, nor comparative measurements of the sort you give.  If you
make the same comparisons with GHC I'd be interested in the results.

Simon






Re: Working with newtype

1997-05-29 Thread Simon L Peyton Jones


| I have a small question about defining functions over types declared
| with "newtype".  Consider the following:
| 
|newtype MyList a = MyList [a]
| 
|myMap1 :: (a -> b) -> MyList a -> MyList b

I would say

myMap f (MyList xs) = MyList (map f xs)

| Perhaps there is no elegant solution to this, but as long as I can
| rely on the above code generating no more work than necessary, I am
| content.

Yes it's a bit cumbersome at times, but it is clear what it means,
including what happens with overloading.  It is often useful to
define unMyList :: MyList a -> [a], as you do.

You should get no code for the extra constructors, but I am not confident
that GHC always does a good job.

Simon






No Subject

1997-05-20 Thread Simon L Peyton Jones



| 1.- In the version 1.2 there is a restriction that a C-T instance declaration
|  may only appear either in the module where C or T are declared, but in
|  the version 1.3 this restriction does not appear. What is the reason for 
|  the change? Why is the restriction in 1.2 at all?

We were conservative in 1.2 and less conservative in 1.4, that's all.
The point is that we want to ensure that there's only one C-T instance for a
given type.   The 1.2 restriction made that a bit easier to check, but
it was Really Tiresome in practice.  So we lifted it.


| 2.- In the declaration of the Eq class, (/=) has a default declaration, 
|  but (==) has not. Why?
|  If (==) has also a default declaration (ie: not (x/=y)) you could choose
|  whether to define (==) or (/=) or both when declaring an instance.
|  The same applies to Ord and (<=).

I don't know.  It would be sensible for it to have one.

| 3.- The 1.2 class Text was separated in the 1.3 Show and Read, and then, 1.2
|  programs that uses Text are not 1.3 compatibles, and make them work  
|  requires a lot of changes. But if one adds the following declarations:
|class (Show a, Read a) => Text a
|  and the appropriate instance declarations for predefined types, the only
|  changes needed are in the user-defined instance declarations for Text, 
|  thus reducing the amount of work to be done.
|  Can these things be added to the PreludeText module? 
|  Are they worth considering?

The reason for separating them
was that people mostly want "Show", but they were getting a whole
wad of code for "Read" linked in because the compiler couldn't tell that it
wasn't going to be called. 

I think it's worth the pain of making the changes.  Or, if you want,
there's nothing to stop you adding the class decl you describe.  It does not
have to be in the prelude.

Simon






Re: Pattern guards

1997-05-15 Thread Simon L Peyton Jones


| > f c | (i,j) <- Just (toRect c) = ...
| 
| I'm afraid this example suffers from the same problem as my "simplify"
| example did: It does not perform a test and can thus be replaced by
| 
|   f c = ...
| where (i,j) = toRect c

True.  I can think of two non-contrived ways in which this would
not work so well.  First, "c" might be got from another pattern match:

f d | Just c <- h d,
  (i,j)  <- toRect c
= ...

Then you couldn't use a where clause.  Second, the view might often 
be the maybe-like kind:

data SnocView a = Snoc [a] a
| SNil

snocView :: [a] -> SnocView a

f xs | Snoc ys y <- snocView xs
 = ...

You could instead give snocView the type 

snocView :: [a] -> Maybe ([a], a)

but I find that less appealing somehow.  But as we keep saying, you certainly
can code up everything in terms of everything else.

Simon






Re: pattern guards + monads

1997-05-15 Thread Simon L Peyton Jones



| On pattern guards, Simon PJ writes:
| >  f (x:xs) | x<0 = e1
| >   | x>0 = e2
| >   | otherwise = e3
| 
| then
| >   g a | (x:xs) <- h a, x<0 = e1
| >   | (x:xs) <- h a, x>0 = e1
| >   | otherwise = e3
| 
| Am i right in thinking that f [] is bottom, whilst g [] is e3?

Not quite.  Certainly f [] is bottom.  But g matches (x:xs) against (h a),
not against a.  So a might not be of type list.  What is certainly true
is that if (h a) == [], then g a is e3.

| Later, another definition of g (intended to be equivalent?) is given in
| which g [] appears to be bottom:
| >  g a | (x:xs) <- h a
| > | x<0 = e1
| > | x>0 = e2
| > | otherwise = e3
|
| To match the semantics of the earlier definition of g, shouldn't this
| read as follows?
|g a | (x:xs) <- h a
|   | x<0 = e1
|   | x>0 = e2
|| otherwise = e3

You're dead right.  Nested guards are a bit tricky, eh?

Simon






Re: Deriving class instances

1997-05-14 Thread Simon L Peyton Jones


Olaf

Noel Winstanley has a Haskell preprocessor that does more or less what
you want.

[EMAIL PROTECTED]

Simon

| From: Olaf Chitil <[EMAIL PROTECTED]>
| Date: Wed, 14 May 1997 16:24:59 +0200
| Why is the automatic derivation of instances for some standard classes
| linked to data and newtype declarations?
| It happened already several times to me that I needed a standard
| instance of a data type that I imported from a module that did not
| provide that instance and which I did not want to change (a library;
| GHC, which I mainly want to extend by further modules, not spread
| changes over 250 modules).
| When declaring a new data type one normally avoids deriving (currently)
| unneeded instances, because it costs program code (and maybe one even
| wants to enable the user of the module to define his own instances).
| 
| 
| Hence I suggest to introduce a new top level declaration like
| 
| deriving  (, ..., )
| 
| e.g.
| 
| data Tree a = Leaf a | (Tree a) :^: (Tree a)
| ...
| deriving Tree (Eq, Ord, Show)
| deriving Tree (Read)
| 
| 
| The current syntax would just be an abbreviation.
| I'm not quite sure if the syntax shouldn't be
| 
| deriving (Tree a) (Eq, Ord, Show)
| 
| because it is an instance for the type, not the type constructor.
| The type variable is, however, superfluous.
| 
| 
| Naturally all data constructors of a data type need to be in scope to
| permit derivation of instances.
| For separate compilation a module's interface file needs to include
| information about the order of constructors in the type declaration.
| GHC already does that.
| 
| 
| I know that attaching the order of data constructors to data types is
| not purely declarative. However, this is already the case for the
| current deriving construct, and attaching it to `data' and `newtype'
| just makes the construct less useful.
| 
| Olaf 
| 
| -- 
| OLAF CHITIL, Lehrstuhl fuer Informatik II, RWTH Aachen, 52056 Aachen,
| Germany
|  Tel: (+49/0)241/80-21212; Fax: (+49/0)241/-217
|  URL: http://www-i2.informatik.rwth-aachen.de/~chitil/
| 






Re: Pattern guards

1997-05-14 Thread Simon L Peyton Jones


| >  For example, in this case we could write (rather less elegantly)
| >  
| >  g2 a | (x:xs) <- h a, (y:ys) <- h x = if y<0 then e1
| >else if y>0 then e2
| >else e3
| >
| > To avoid this difficulty with functions like g2...
| 
| Why does the Haskell community have such an antipathy to if...then...else...?
| Tony said that choice of construct is a matter of personal style. Nonetheless,
| I think that this whole debate crystalises a consensus that guards are
| prefereable to conditional expressions.

Thas's easily explained.  The reason I might not want to use if-then-else is
because there might be a subsequent equation I want to try if this one
fails.  Like this:

  g2 a | (x:xs) <- h a, (y:ys) <- h x, y<0 = e1
  g2 a | (x:xs) <- h a, (y:ys) <- h x, y>0 = e2
  g2 a | not (foo a)   = e3
  g2 a | otherwise = e4

Does that help?  (Of course one can compile all pattern matching into
case and if-then-else; that's what the semantics in the report does.  But
then your functions definitions tend to trail off to the right of the page
and can get hard to read.)

Simon
   






Pattern guards

1997-05-13 Thread Simon L Peyton Jones


The discussion about pattern guards has raised two interesting and 
(I think) independent questions:

- Nested guards
- Maybes and monads

Here are my thoughts on these things, typed 30,000 feet above Utah!

Simon


Nested guards
~~
Several people have pointed out that one might want to 
nest guards.  For example, in Haskell we can say

  f (x:xs) | x<0 = e1
   | x>0 = e2
   | otherwise = e3

But now suppose that the pattern (x:xs) was the result of
an auxiliary call to h.  Trying to use pattern guards (as I proposed them)
we might say:

  g a | (x:xs) <- h a, x<0 = e1
  | (x:xs) <- h a, x>0 = e1
  | otherwise = e3

Here we repeat the call to the auxiliary function, h, in the
two guards, which is 
(a) a nuisance, and 
(b) an efficiency worry, because h might be expensive.

In this case (and in fact, I believe,
in most cases) we can deal with (b) using a where clause:

  g a | (x:xs) <- h_a, x<0 = e1
  | (x:xs) <- h_a, x>0 = e1
  | otherwise = e3
  where
h_a = h a

But (a) remains.  Furthermore, it isn't always possible to
use a where clause:

  g2 a | (x:xs) <- h a, (y:ys) <- h x, y<0 = e1
   | (x:xs) <- h a, (y:ys) <- h x, y>0 = e1
   | otherwise = e3

Here, we can't use a where clause to share the calls to (h x).

One might argue that a compiler should spot the common calls to
(h a) and (h x) and common them up.  Indeed I think I argued this
earlier, drawing the analogy with the way we expect a compiler to
avoid unnecessary pattern matching where possible.  But there's a BIG
difference between this and avoiding pattern-matching: pattern-matching
is a small constant cost, whereas making two calls to "h" instead of
one could conceivably have a dramatic effect on efficiency, or even 
change the complexity of the algorithm.  So I certainly agree that
the programmer should be able explicitly to share calls to "h".
In the case of "g" that's possible using a where clause.  In the
case of "g2" it is not.  To share the call (h x) in "g2" we are
pretty much reduced to the clunkiness I objected to in my initial
proposal.  This is a definite shortcoming of my proposal, though
I would like to argue that really bad cases seldom occur.  For
example, in this case we could write (rather less elegantly)

  g2 a | (x:xs) <- h a, (y:ys) <- h x = if y<0 then e1
else if y>0 then e2
else e3


To avoid this difficulty with functions like g2,
Heribert Schuetz suggests having nested guards, something
like this:

  g a | (x:xs) <- h a
  | x<0 = e1
  | x>0 = e2
  | otherwise = e3

The second column of "|" guards is nested inside the first
guard, so that if one of the inner guards fail we simply try
the next without backtracking to the top-level guard.  He points
out, quite correctly, that Haskell already allows a form of nested
choice by having a set of guards for a single set of patterns
and associated where clause.

Haskell doesn't currently allow nesting within pattern matches
either.  In the equations

f (x1:x2:xs) [] = e1
f (x1:x2:xs) (y:ys) = e2

one has to write out the pattern (x1:x2:xs) twice, even though what
we have in mind is presumably to match the pattern (x1:x2:xs) first,
and then choose among the right hand sides based on the second argument.
Phil Wadler suggests that we might want to revisit that choice too.

These are all good points.  Nested choices are somewhat natural (although
they run counter to the general idea of independent equations), but Haskell
permits only a certain particular sort of nested choice (patterns, then
muultiple guarded RHSs).  It would be nice to find a syntax that neatly
incorporated nested choice at any level, among patterns or among guards
(indeed we can see patterns as a particular sort of guard).  Nevertheless,
this would be a more far-reaching proposal.  My proposal is a modest one:
it aims to deal with a large number of commonly occurring and very irritating
cases.  There remain cases (such as g2 above) that it does not handle well.
But, given the smallness of the change required, I think it's a good deal.



Maybes and monads
~~
Heribert also suggests that the typing rule for a
pattern guard "p <- e" should have p::t, e::Maybe t.
Thus

f :: Int -> Int
f x | (y:ys) <- h x = e1
| otherwise = e2

h :: Int -> Maybe [Int]
h x = ...

Here, the guard would fail either if h returns Nothing, or
if it returns (Just []).

I must say that I don't find this convincing:

* The e::Maybe t proposal is equivalent in expressive power
  to mine (e::t).  Each can express precisely the programs
  that the other can, by adding a few "Justs".

* I positively like that with e::t I would write

f x | Just (y:ys) <- h x = e1
| otherwise  = e2

  This is a bit longer than e::Maybe t, but it does mean

Re: Monads, Functors and typeclasses

1997-05-12 Thread Simon L Peyton Jones


Koen suggests:

| The solution is real easy: To express the necessity of a Monad to be a
| Functor, change the definition of the class Monad as follows: 
| 
|   class Functor m => Monad m where
| ...

When to make one class into a superclass of another is a rather tricky
matter of judgement:

  (a) If Functor is a superclass of Monad, then every instance
  of Monad must also be made an instance of Functor, whether
  or not one uses "map".  This can be tiresome.

  (b) On the other hand, it is never *necessary* to make one 
  class a superclass of another; it just makes contexts smaller.
  In Koen's example, he'd have to say:
  class MonadTrans t where
lift :: (Functor m, Monad m) => m a -> t m a
  These extra contexts can be tiresome to write, too.

I don't think there's anything deeper to the Haskell 1.4 decision than that.

Simon






Re: pattern guards and guarded patterns

1997-04-30 Thread Simon L Peyton Jones


Thanks for feedback about pattern guards.  Here are some quick responses.

1.  Several people have suggested something along the lines of being
able to backtrack half way through a pattern guard.  I considered this
but (a) I couldn't see a nice syntax for it and
(b) it's against the spirit of independent guarded equations

Re (b) we write

f (x:xs) [] = e1
f (x:xs) (y:ys) = e2

when you might think we should find a syntax to allow

f (x:xs) [] = e1
 (y:ys) = e2

But we write out the common prefix and expect the compiler to spot the
common pattern.  Similarly I think we should rely on the compiler to spot
common prefixes of guards.

f x y | (x:xs) <- xs,
[] <- ys
  = e1

  | (x:xs) <- xs,
(y:ys) <- ys
  = e2

The only extra difficulty is that the RHS of the pattern guard can be an
expression.


2.  Chris Dornan suggests a second change, adding guarded conditionals.
This makes some sense to me, but it has a lower power-to-weight ratio
(less gain for similar pain) so I think we should consider them separately.
I've not found myself really hating if-then-else enough to want to change it.


3.  I think it's quite important to use "<-" rather than "=".
a) it means that the syntax is precisely that of list comprehensions
b) there's an "=" in the definition already, as Andy points out:
simplify (Plus e e') | let (Val 0) = s  = s'
 | let (Val 0) = s' = s
 | otherwise= Plus s s'
 where
 s  = simplify e
 s' = simplify e'

now there are too many "=" signs to parse easily.  

c) Furthermore, "let" can introduce multiple 
   mutually-recursive bindings,
   and that leads to all the "which order to test" problems 
   that I outlined earlier.

   Point (b) might even suggest disallowing the let form. Under my proposal
   I can write this:

foo x | let y = x+1 = y+1

   It's a bit silly, because I can also use let or where in this 
   situation, but it's not ambiguous so I don't see any particularly
   good reason to disallow it.

   CONCLUSION: "let" should be allowed, but should introduce multiple,
   mutually-recursive bindings.  If any are pattern bindings then they
   are matched lazily, and failure to match is a program error.  Exactly
   as for ordinary let/where bindings, and let bindings in list
   comprehensions.

4. Some people have suggested some monadic generalisations, so that
f g xs | y <- xs = g y
   could mean "map g xs".  Such generalisations *might* be possible,
   but I'm pretty dubious about them.  Keep it simple!

Simon







Re: A new view of guards

1997-04-29 Thread Simon L Peyton Jones



| We can avoid both the case expressions and the helper function by Simon
| Peyton Jones' guard syntax
| 
|   -- version 3
|   simplify (Plus e e') | s  <- simplify e ,
|s' <- simplify e',
|(Val 0) <- s   
|  = s'
|| s  <- simplify e ,
|s' <- simplify e',
|(Val 0) <- s' 
|  = s
|| s  <- simplify e ,
|s' <- simplify e'
|  = (Plus s s')
|   simplify e   = e

I agree with the general thrust of your message (though I was unable to
think of a good syntax for it), but in this particular case there's no
problem.  A where clause will do nicely:

   simplify (Plus e e') | (Val 0) <- s  = s'
| (Val 0) <- s' = s
| otherwise = Plus s s'
where
  s  = simplify e
  s' = simplify e'

simplify e  = e






A new view of guards

1997-04-28 Thread Simon L Peyton Jones


A new view of guards

Simon Peyton Jones, April 1997

This note proposes an extension to the guards that form part of function
definitions in Haskell.  The increased expressive power is known (by me
anyway!) to be useful.  The general aim is similar to that of views [1,2],
but the expressive power of this proposal is a little different, in places
more expressive than views, and in places less so.  The proposal can be
implemented with very modest syntactic and implementation cost.  It is
upward compatible with Haskell; all existing programs will continue to work.

I'd welcome feedback and improvements to this proposal.


What's the problem?
~~~
Consider the following Haskell function definition

filter p [] = []
filter p (y:ys) | p y   = y : filter p ys
| otherwise = filter p ys

The decision of which right-hand side to choose is made in
two stages: first, pattern matching selects a guarded group,
and second, the boolean-valued guards select among the right-hand
sides of the group.  In these two stages, only the pattern-matching
stage can bind variables.  A guard is simply a boolean valued expression.

So pattern-matching combines selection with binding, whereas guards simply
perform selection.  Sometimes this is a tremendous nuisance.  For example,
suppose we have an abstract data type of finite maps, with a lookup
operation:

lookup :: FinteMap -> Int -> Maybe Int

The lookup returns Nothing if the supplied key is not in the
domain of the mapping, and (Just v) otherwise, where v is
the value that the key maps to.  Now consider the following
definition:

   clunky env var1 var2 | ok1 && ok2 = val1 + val2
| otherwise  = var1 + var2
where
  m1 = lookup env var1
  m2 = lookup env var2
  ok1 = maybeToBool m1
  ok2 = maybeToBool m2
  val1 = expectJust m1
  val2 = expectJust m2

The auxiliary functions are
maybeToBool :: Maybe a -> Bool  
maybeToBool (Just x) = True
maybeToBool Nothing  = False

expectJust :: Maybe a -> a
expectJust (Just x) = x
expectJust Nothing  = error "Unexpected Nothing"

What is "clunky" doing?  The guard "ok1 && ok2" checks that both
lookups succeed, using maybeToBool to convert the maybe types to
booleans.  The (lazily evaluated) expectJust calls extract the values
from the results of the lookups, and binds the returned values to
val1 and val2 respectively.  If either lookup fails, then clunky
takes the "otherwise" case and returns the sum of its arguments.

This is certainly legal Haskell, but it is a tremendously verbose
and un-obvious way to achieve the desired effect.  Arguably, a more
direct way to write "clunky" would be to use case expressions:

  clunky env var1 var1 = case lookup env var1 of
   Nothing -> fail
   Just val1 -> case lookup env var2 of
  Nothing -> fail
  Just val2 -> val1 + val2
 where
  fail = val1 + val2

This is a bit shorter, but hardly better.  Of course, we can rewrite
any set of pattern-matching, guarded equations as case expressions;
that is precisely what the compiler does when compiling equations!
The reason that Haskell provides guarded equations is because they
allow us to write down the cases we want to consider, one at a time,
independently of each other.  This structure is hidden in the case 
version.  Two of the right-hand sides are really the same ("fail"),
and the whole expression tends to become more and more indented.  

Worse, if this was just one equation of "clunky", with others that
follow, then the thing wouldn't work at all.  That is, suppose we have

  clunky' env (var1:var2:vars) | ok1 && ok2 = val1 + val2
   where
m1 = lookup env var1
...as before...

  clunky' env [var1]   = ...some stuff...
  clunky' env []   = ...more stuff...

Now, if either the lookups fail we want to fall through to the second
and third equations for clunky'.  If we write the definition in the 
form of a case expression we are forced to make the latter two
equations for clunky' into a separate definition and call it in
the right hand side of "fail".  Ugh.  Ugh.  Ugh.  This is precisely
why Haskell provides guards at all, rather than relying on if-then-else
expressions: if the guard fails we fall through to the next equation,
whereas we can't do that with a conditional.


What is frustrating about this is that the solution is so tantalisingly
near at hand!  What we want to do is to pattern-matc

A pretty-printing library

1997-04-25 Thread Simon L Peyton Jones


Folks,

Many of you will know of John Hughes pretty printing library [1].
I recently extended it with two new features:

* An "empty document" which is a unit for all the composition
  operators.  In practice this is tremendously useful.

* A "paragraph fill" combinator.

There are a number of other new features, summarised below.  

You can find the library on my OGI web page
http://www.cse.ogi.edu/~simonpj

Please tell me of any bugs you find, or suggestions you have for improving
it.  Incidentally, I've fixed a rather subtle bug since I first put the
library on my Web page, so grab the new copy even if you've come across it
already.

Simon

[1]  RJM Hughes "The Design of a Pretty-printing Library", 
 in Advanced Functional Programming, Johan Jeuring and 
 Erik Meijer (eds), LNCS 925


==
Relative to John's original paper, there are the following new features:

1.  There's an empty document, "empty".  It's a left and right unit for 
both <> and $$, and anywhere in the argument list for
sep, hcat, hsep, vcat, fcat etc.

It is Really Useful in practice.

2.  There is a paragraph-fill combinator, fsep, that's much like sep,
only it keeps fitting things on one line until itc can't fit any more.

3.  Some random useful extra combinators are provided.  
<+> puts its arguments beside each other with a space between them,
unless either argument is empty in which case it returns the other

hcat is a list version of <>
hsep is a list version of <+>
vcat is a list version of $$

cat  is behaves like sep,  but it uses <+> for horizontal conposition
fcat is behaves like fsep, but it uses <+> for horizontal conposition

These new ones do the obvious things:
char, semi, comma, colon, space,
parens, brackets, braces, 
quotes, doubleQuotes

4.  The "above" combinator, $$, now overlaps its two arguments if the
last line of the top argument stops before the first line of the second begins.
For example:  text "hi" $$ nest 5 "there"
lays out as
hi   there
rather than
hi
 there

There are two places this is really useful

a) When making labelled blocks, like this:
Left ->   code for left
Right ->  code for right
LongLongLongLabel ->
  code for longlonglonglabel
   The block is on the same line as the label if the label is
   short, but on the next line otherwise.

b) When laying out lists like this:
[ first
, second
, third
]
   which some people like.  But if the list fits on one line
   you want [first, second, third].  You can't do this with
   John's original combinators, but it's quite easy with the
   new $$.

The combinator $+$ gives the original "never-overlap" behaviour.

5.  Several different renderers are provided:
* a standard one
* one that uses cut-marks to avoid deeply-nested documents 
simply piling up in the right-hand margin
* one that ignores indentation (fewer chars output; good for machines)
* one that ignores indentation and newlines (ditto, only more so)

6.  Numerous implementation tidy-ups
Use of unboxed data types to speed up the implementation






Type classes

1997-04-09 Thread Simon L Peyton Jones


Folks,

There's often been quite a bit of discussion on the Haskell mailing list
about extensions of type classes.  Erik Meijer, Mark Jones and I have
written a draft paper that explores the type-class design space, discussing
the various design decisions one must make, and their consequences. 
(Location below.)

One thing the paper needs is more concrete examples.  This message is to
encourage you to grab the paper, and 

a) Check which design choices would permit or prohibit the
   programs you wish you could write in Haskell but can't.
   (For example, many people have asked for multi-parameter
   type classes... but as the paper discusses there are numerous
   other aspects of the type-class system that affect which
   programs are expressible.)

b) Tell us your conclusions, preferably in concrete form. For
   example "The following program requires that we make
   design choice 3b, and not 3a".  (The paper identifies
   9 decisions, and several choices for each decision.)

Of course, any other feedback about the paper would be most gratefully
received too.

The paper will appear in the (informal) proceedings of the Haskell workshop
(7 June in Amsterdam).  We have to produce camera ready copy by 1 May.
So feedback before end April would be most useful.

Simon
===

Type classes: an exploration of the design space
Peyton Jones, Jones, Meijer
http://www.cse.ogi.edu/~simonpj/multi.ps.gz


When type classes were first introduced in Haskell they were regarded as a
fairly experimental language feature, and therefore warranted a fairly
conservative design.  Since that time, practical experience has convinced
many programmers of the benefits and convenience of type classes.  However,
on occasion, these same programmers have discovered examples where seemingly
natural applications for type class overloading are prevented by the
restrictions imposed by the Haskell design.

It is possible to extend the type class mechanisms of Haskell in various
ways to overcome these limitations, but such proposals must be designed with
great care.  For example, several different extensions have been implemented
in Gofer.  Some of these, particularly the support for multi-parameter
classes, have proved to be very useful, but interactions between other
aspects of the design have resulted in a type system that is both unsound
and undecidable.  Another illustration is the introduction of constructor
classes in Haskell 1.3, which came without the proper generalization of the
notion of a context.  As a consequence, certain quite reasonable programs
are not typable.

In this paper we review the rationale behind the design of Haskell's class
system, we identify some of the weaknesses in the current situation, and we
explain the choices that we face in attempting to remove them.






The Glasgow Haskell Compiler -- version 2.02

1997-03-26 Thread Simon L Peyton Jones


 The Glasgow Haskell Compiler -- version 2.02
 

We are pleased to announce the first release of the Glasgow Haskell
Compiler (GHC, version 2.02) for *Haskell 1.4*.  Sources and binaries
are freely available by anonymous FTP and on the World-Wide Web;
details below.

Haskell is "the" standard lazy functional programming language; the
current language version is 1.4, agreed in March, 1997.  The Haskell
Report is online at

http://haskell.org/report/

GHC 2.02 is a beta-quality release:

  * It is reliable.
It has been extensively tested against a large suite of Haskell 1.2 
programs, but not so extensively tested against Haskell 1.4 programs 
because we don't have a comprehensive set (Donations of Haskell 1.4
programs to our test suite are most welcome).

  * It should generate reasonably good code.
All the optimisations that GHC 0.29 used to do are back in, with 
the exception of specialisation.  It ought to be the case that
GHC 2.02 outperforms GHC 0.29, because it has a much better
handle on cross-module inlining, but we know for certain that
this isn't always the case.  We have yet to make a systematic 
comparison.  In short, this is not the moment to switch from 0.29
if you Really Care about performance.  2.02 does, however,
generate much better code than 2.01.

(Please send us programs where 2.02 does noticeably worse than 0.29.)  

  * It is more expensive than it should be.
GHC 2.02 has received even less attention to its own performance.
At present it eats more space and time than GHC 0.29, especially
for very small programs.  We'll work on this.

  * A couple of Haskell 1.4 features are incompletely supported,
notably polymorphic strictness annotations, and Unicode.

If you want to use Haskell 1.4, this is a good moment to switch.  If
you don't need the Haskell 1.4 extensions, then stay with GHC 0.29.
If you want to hack on GHC itself, then 2.02 is definitely for you.
The release notes comment further on this point.

GHC 2.02 is substantially changed from 2.01.  Changes worth noting
include:

  * The whole front end, which deals with the module system, has 
been rewritten. The interface file format has changed.

  * GHC 2.02 is released together with Green Card, a C foreign language 
interface for GHC.  Green card is a pre-processor that
scans Haskell source files for Green Card directives, which
it expands into tons of "ccall" boilerplate that marshalls
your arguments to and from C.

  * GHC 2.02 is available for Win32 platforms, which, from now on,
is a fully supported platform for GHC.

  * GHC 2.02 supports full cross module inlining.  Unlike 0.29 and
its predecessors, inlining can happen even if the inlined body
mentions a function or type that is not itself exported.  This is
one place Haskell 1.4's new module system really pays off.

  * Like 2.01, GHC 2.02 aborts a compilation if it decides that
nothing that the module imports *and acually uses* has changed.
This decision is now taken by the compiler itself, rather than
by a Perl script (as in 2.01) which sometimes got it wrong.

  * The ghc/lib libraries are much more systematically organised.

  * There's a completely new "make" system.  This will mainly affect people
who want the source distribution, who will hopefully find it much, much,
easier than grappling with the old Jmakefiles.  Even for binary
installation, the procedure is a little simpler, though.

Please see the release notes for a complete discussion of What's New.

To run this release, you need a machine with 16+MB memory (more if
building from sources), GNU C (`gcc'), and `perl'.  We have seen GHC
2.01 work on these platforms: alpha-dec-osf2, hppa1.1-hp-hpux9,
sparc-sun-{sunos4,solaris2}, mips-sgi-irix5, and
i386-unknown-{linux,solaris2,freebsd,cygwin32}.  Similar platforms
should work with minimal hacking effort.  The installer's guide
give a full what-ports-work report.

Binaries are distributed in `bundles', e.g. a "profiling bundle" or a
"concurrency bundle" for your platform.  Just grab the ones you need.

Once you have the distribution, please follow the pointers in
ghc/README to find all of the documentation about this release.  NB:
preserve modification times when un-tarring the files (no `m' option
for tar, please)!

We run mailing lists for GHC users and bug reports; to subscribe, send
mail to [EMAIL PROTECTED]; the msg body should be:

subscribe glasgow-haskell- Your Name <[EMAIL PROTECTED]>

Please send bug reports about GHC to [EMAIL PROTECTED]

Simon Peyton Jones

Dated: March 1997

Relevant URLs on the World-Wide Web:

GHC home page http://www.dcs.gla.ac.uk/fp/software/ghc/
Glasgow FP group page http://www.dcs.gla.ac.uk/fp/
comp.lang.functional FAQ  http://www.cs.nott.ac.uk/Department/Staff/mpj/faq.html


Re: reading numbers

1997-03-20 Thread Simon L Peyton Jones


This is a bug in GHC 2.01 (and 0.29 I think).  We'll fix it in 2.02.
(But that means taking a few more hours to rebuild the 2.02 builds that are
about to go out of the door :-).

Simon

| A couple of my colleagues are using Haskell to implement a simple desk
| calculator but they have run into a problem reading in numbers.  Essentially
| they need something that will convert a String to a Float.  The first attempt
| 
| > atof:: String -> Float
| > atof s = read s
| 
| works fine except that it fails for some reasonable inputs like "2" and there
| is no way of detecting and handling failures.  I am just about to code an
| `atof' for them but was wondering if there is a better way.






Re: haskell operator precedence

1997-03-18 Thread Simon L Peyton Jones


| However, in return, perhaps somebody can supply me with parse trees for
| the following:
| 
| - - 1(accepted by nhc and hbc)
| (- 1 `n6` 1)   where infix  6 `n6`   (accepted by nhc, hbc, ghc)
| (- 1 `r6` 1)   where infixr 6 `r6`   (accepted by nhc, hbc, ghc)
| 
| As I read the grammar (for 1.3), all of these should be illegal.  In
| fact, the compilers don't even give consistent answers for the last
| example:  ghc and nhc treat it as (-(1 `r6` 1)) while hbc treats it
| as ((-1) `r6` 1).

Good point!  I've fixed this in GHC.  It might or might not make it into
2.02 which is in build-and-tar mode at the moment.

Simon






Re: polymorphic higher-order terms

1997-03-13 Thread Simon L Peyton Jones



| > data F = MkF t -> t -- did I get the syntax right?
| Almost
| data F = MkF (t -> t)
| > 
| > foo :: (Int, String, F) -> (Int, String)
| > foo (i, s, MkF f) = (f i, f s)
| 
| In fact, this extension has been implemented in Hugs
| and ghc as well as I understand it, but neither of these
| implementations have been made publically available.

Actually it still isn't in GHC, but it Will Be.  I'm planning to do a bit
more, in fact, and allow:

foo :: (forall t. t->t) -> (Int, String) -> (Int,String)
foo f (a,b) = (f a, f b)

So I plan to permit universal quantification at the top level
of a function argument.  The main motivation is to allow us to
write user versions of runST, such as

myRunST :: Int -> (forall s. ST s Int) -> Int
myRunST n st = n + runST st

At present, only "runST" itself has the magic type required.

Implementing this is no more difficult than doing it for constructors.
Of course, a type signature is *required*.  All inferred types will be
as now.

It won't happen overnight though.  Still trying to get 2.02 out of the door!

Simon






Advance programme: ICFP'97 and PEPM'97

1997-02-27 Thread Simon L Peyton Jones



|   |
| International Conference on Functional Programming (ICFP97)   |
|  Symposium on Partial Evaluation and Program Manipulation (PEPM97)|
|   |
|  Haskell Workshop |
|   Types in Compilation Workshop   |
|   |
|  Amsterdam, 7-13 June 1997|
|   |


ADVANCE PROGRAMME

We are happy to announce the advance programme for ICFP'97, PEPM'97,
with the associated workshops on Haskell, and Types in Compilation.
The timetable of events is this:

7 June 1997 Haskell Workshop
8 June 1997 Types in Compilation Workshop
9-11 June 1997  ICFP'97
12-13 June 1997 PEPM'97

You can find the full advance programme, including details of how
to register, at

http://www.cs.kun.nl/fpl/icfp-pepm97/

Attached to this message is are the conference programmes for ICFP and PEPM,
in case you want to scan them right away.

There is also a poster session for ICFP, whose submission deadline is 15 March.
http://www.cse.ogi.edu/PacSoft/icfp-poster.html


We look forward to seeing you at ICFP and PEPM.

Simon Peyton Jones (General Chair, ICFP'97)
John Gallagher (General Chair, PEPM'97)



=   
   ICFP'97

   Second ACM SIGPLAN International Conference on
Functional Programming, in association with IFIP Working Group 2.8.
   June 9-11 1997

The International Conference on Functional Programming (ICFP) combines the
established LISP and Functional Programming (LFP) and Functional Programming
and Computer Architecture (FPCA) conferences into a unified annual meeting
devoted to the design, analysis, implementation, and application of
functional programming languages. The scope is inclusive, encompassing
languages that are typed or untyped, strict or lazy, sequential or parallel,
pure or stateful. Languages of interest include established languages such
as LISP, Scheme, Sisal, ML, Clean, Haskell, and Id, as well as novel designs
in the functional programming tradition.

Twenty five papers spanning a broad range of topics will be presented. In
addition there will be two invited speakers, Joe Armstrong of Ericsson, and
Greg Morrisset from Cornell University.

General Chair Program Chair

SIMON PEYTON JONES,   MADS TOFTE,
Glasgow UniversityUniversity of Copenhagen
Program Committee

ALEX AIKEN,   ANDREW APPEL,
University of California  Berkeley Princeton University
ZENA ARIOLA,  MARC FEELEY,
University of Oregon  University of Montreal
SHAIL ADITYA GUPTA,   PETER LEE,
HP LaboratorieCarnegie Mellon University
XAVIER LEROY, MARTIN ODERSKY,
INRIA University of Karlsruhe
RINUS PLASMEIJER, COLIN RUNCIMAN,
Katholieke Universiteit Nijmegen  University of York
AMR SABRY,GUY STEELE,
University of Oregon  Sun Microsystems Laboratories
PHILIP WADLER,PAUL WILSON,
Bell Labs, Lucent TechnologiesThe University of Texas at Austin

Full information about ICFP can be found at
http://www.fwi.uva.nl/research/func/icfp.html

ICFP Monday, June 9

8:00
 REGISTRATION

8:35-8:45
 WELCOME

8:45-9:45
 INVITED TALK: TYPES IN COMPILATION
 Greg Morrisett (Cornell University)

9:45-10:30
 BREAK

Session 1 chair: Martin Odersky (University of Karlsruhe)

10:30-11:00
 A MODULAR, POLYVARIANT AND TYPE-BASED CLOSURE ANALYSIS
 Anindya Banerjee (Xinotech Research)

11:00-11:30
 STRONGLY TYPED FLOW-DIRECTED REPRESENTATION TRANSFORMATIONS
 Allyn Dimock (Harvard University), Robert Muller (Boston College),
 Franklyn Turbak (Wellesley College) and Joe Wells (Boston University)

11:30-12:00
 TYPE-DRIVEN DEFUNCTIONALIZATION
 Jeffrey M. Bell (Oregon Graduate Institute), Frangoise Bellegarde
 (Universiti de Franche-Comti) and James Hook (Oregon Graduate
 Institute)

12:00-12:30
 SYSTEMATIC REALISATION OF CONTROL FLOW ANALYSES FOR CML
 Kirsten L. Solberg Gasser, Flemming Nielson and Hanne Riis Nielson
 (Aarhus University)

12:30-14:00
 LUNCH

Session 2 chair: Colin Runciman (University

Re: global type inference

1997-02-25 Thread Simon L Peyton Jones


| Why muddle implementation with language design?  Pick a design that
| we know everyone can implement -- e.g., exported functions must have
| type declarations -- and stick to that.  When the state of implementations
| improve, the specification for Haskell 1.5 can change accordingly.  -- P

Actually, we don't know that everyone can implement the design you suggest.
To make sense of the type signature you have to do a completely separate
scope analysis of the source code of the imported module, so that you know
what "T", say, in the type signature of an exported function means.

GHC will do that but it doesn't yet.  Currently you have to fiddle with
GHC-specific interface files. I don't know what Hugs does, nor hbc.

That is why I suggested the form of words I did.  If you like, we could be
more specific, but then there won't be any conforming implementations for a
while!

This isn't muddling implemenation with language design.  The language design
says mutual recursion is OK. A particular implementation supporting separate
compilation will typically require a variety of "help", such as a Makefile
with accurate dependencies.  Requiring type signatures, or interface files,
or whatever is just another implementation specific thing to support
separate compilation.

Simon






Re: Making argv a constant

1997-01-28 Thread Simon L Peyton Jones


Claus writes:

| Let me see if I understand the rules of this firestorm game: You have
| to repeat your ideas some times to push them through the competition?-)

Actually I think that is a poor way to proceed.  That is why I have stopped
sending on this topic --- I have already said what I think and nothing is
gained by repeating it.

Still, your summary was helpful.


The general rule is that unless a consensus emerges about a new feature then
it doesn't get in.   (Unless a consensus emerges that something *has* to be
done in which case everyone has to start compromising about *what*.)

In the case of argv, I don't think a consensus has emerged about either of
these matters.  So what should probably happen is that it stays out of the
language, but that GHC and HBC both (continue to) provide it anyway, as a
non-standard extension (as they do now).

Simon







Re: Making argv a constant

1997-01-17 Thread Simon L Peyton Jones


My, what a firestorm!  The Haskell mailing list springs to life.

Frank writes

|   First, Simon, I think you're a little biased on this issue.  I'm sure that
| making argv a global constant would be a practical benefit for programs like
| GHC.

You're probably right.  I am certainly biased towards large programs.
But I really want Haskell to scale to large programs, rather than become
unreasonably inconvenient to use when the program becomes big.

| nooks and crannies of a program.  Most applications are not nearly so
| configurable, 

I disagree!  Most "real" programs (i.e. products) are highly configurable.

|   Suppose, for example, as Sverker suggested that instead of setting the
| arguments via the command-line, you set them by reading in a file of argument
| settings, one per module.  Then you would be stuck with implementing the
| argument-passing plumbing anyway.

I think this is a really good point, and I don't have a good answer for it.
(see below)

|   Third, I could say that choosing to use a functional language is in some
| sense also accepting the fact that you are "forced to accept some benefits"
| which you could do without.

I don't agree.  In exchange for the costs of higher-order functions, or
laziness, or the lack of side effects, I get some benefits.  In exchange for
making argv accessible only via an IO action I get nothing at all.

|   Fourth, the advantage you claim to get from global flags could also be
| gotten from using a reader monad: not only does it hide the plumbing, but it
| also explicitly indicates that the value is constant.  And last time I looked,
| GHC was overflowing with monads

The outer structure is heavily monadised but there are hundreds and hundreds
of non-monadic functions.  It is *not* a routine matter to get the
arguments to a randomly chosen place.

Lennart writes, of Frank's idea

| > timeStarted :: performOnceBeforeMain (getCurrentTime)
| >
| > Just like that one would do with unsafePerformIO, but with
| > safer semantics (hopefully) and blessed by Standard Haskell.
|
| I agree.  Even if this particular mechanism needs some extra
| restrictions to be safe I would prefer this to the hack of
| just making argv a global constant.  This is a hack too, but
| at least it's generalized.

This would solve the "read options from a file" problem, which I like.
But, it's not clear what the "restrictions" would need to be.  Any ideas
anyone?

| I've sinced changed my mind, maybe it is "a functional programmers
| deathwish", but I find the case where you are explicit about what a
| function depends on to be more honest and true to the FP spirit.
| I've also found it practically useful since you can then change the
| values of the given flags locally (which you couldn't do with a global
| argv).

When I need that benefit, then I'm willing to pay the cost.  What bugs me is
paying the cost simply to be true to the spirit of FP without getting any
benefit.  Maybe I'm just getting old an cynical.  But I still believe in
lazy evaluation so you can't dispose of me altogether. :-)

Simon






Re: Making argv a constant

1997-01-17 Thread Simon L Peyton Jones


Fergus

| I would find Simon's arguments more convincing if he showed
| a convenient idiom that did things properly, rather than a
| convenient way to write broken programs.
| 
| (Doing it properly is probably not too hard, but I'll leave it up to
| the proponents of this proposal to demonstrate this...)

It's hard for me to respond to this since I don't know what you have in mind
when you say "properly".  If you mean proper error reporting, then that's
not difficult:

main = checkArgForErrors argv   >>
   rest of prog...

I'm not sure what else you had in mind.

Simon






Re: Making argv a constant

1997-01-17 Thread Simon L Peyton Jones


Lennart, Fergus, 

re this stdin issue you're missing the point I was trying to make.  It
really only bites badly when you have concurrency.  I enclose the relevant
message, which gives an example of the extra expressiveness non-constant
stdin etc buys you -- I don't know which bit you disagree with, so the best
I can do is simply repeat it.

Simon

| > > I don't honestly see what having these handles as constant *gain* you,
| > > so why then have them as such, if not having them constant gives you
| > > extra expressiveness?
| > 
| > But, unless I'm missing something, making them non-constant doesn't
| > give you any extra expressiveness.
| > 
| > Remember that the fact they are constant does not imply that the
| > file they are connected to is constant.  Even if they are effectively
| > thread-local, i.e if the file that stdin and stdout are connected to
| > depends on which thread you're in, stdin and stdout themselves can
| > still be constants, can't they?
| Exactly!
| 
| I regard stdin, stdout, and stderr as names for abstract versions of
| 0, 1, and 2 (does my background in C programming on Unix show? :-).
| These are just handles, the can be reconnected to anything.  If you
| argue that you should be able to change the meaning of stdin I could
| argue "This piece of code I've got uses the constant 5, this is not
| what I want, I need to change the value of 5 locally when that code
| runs.  Give me the machinery to do that!"


To: [EMAIL PROTECTED] (Kevin Hammond)
cc: [EMAIL PROTECTED], simonpj
Subject: Re: stdin as a constant 
Date: Thu, 16 Jan 1997 11:07:19 -0800
From: Simon L Peyton Jones 
Content-Type: text
Content-Length: 1859


| What you want is allowed.  Although stdin *is* a constant, it's simply a
| constant that refers to a handle.  The handle information (file pointer,
| attached device etc.) needn't be constant.  It's entirely consistent to
| provide, say:
| 
| reconnect :: Handle -> Handle -> IO Handle
| 
| to connect one handle to the same device as another (as long as you're
| careful in the impl. about duplicating file pointers, which can get you into
| trouble -- new files are much easier to deal with!).  This was actually one
| of the extensions that was considered fairly carefully in the I/O design.

This doesn't do what Sigbjorn is suggesting.

Suppose I import a module written by someone else which exports
the function toUpper:

-- toUpper reads stdin, converts all characters to upper
-- case, and sends them to stdout
toUpper :: IO ()

Now I import another module which exports sort:

-- sort reads stdin, divides it into lines, sorts the lines
-- and sends them to stdout
sort :: IO ()

Now suppose I want to arrange to connect toUpper and sort together.
I might hope to do it like this:

module Main where
import M1( toUpper )
import M2( sort )

main = do 
  (in,out) <- pipe;
  forkIO (withStdOut in toUpper);
  withStdIn out sort

The new functions are

pipe :: IO (Handle,Handle)
withStdOut, withStdIn :: Handle -> IO () -> IO ()

The point here is that toUpper and sort each work with *different* mappings
of stdin, stdout.


This example uses concurrency, which Haskell doesn't have.
In the absence of concurrency you can hack it like this:

main = do 
  (in,out) <- pipe;
  old_stdout <- setStdOut in;
  toUpper;
  setStdOut old_stdout;
  setStdIn out;
  sort

But it's a hack, isn't it.  And it doesn't extend to concurrency.

But this may help explain why I'm not so steamed up as I am about argv!

Simon






Re: Making argv a constant

1997-01-16 Thread Simon L Peyton Jones



| Maybe the symbol table isn't passed around to all dark corners though.

Dead right it ain't. There are plenty of places you don't need a symbol
table.

| Anyway, what it seems to me you lose by doing it the way you described
| is that you are stuck again if some day you want to set those flags
| some other way than from the environment variables. For example with
| pragmas. You can't compile several modules with different settings
| either, without restarting all of the compiler, it seems to me.

I regard this as an *advantage*.  If I see

import CmdLineOpts( myFlag )

f x = if myFlag then 
  else 

then I *know* that every call to f will behave like , or
every call will behave like .  No chance that some may behave like
one and some like the other.

If I pass the flags as an argument, thus:

f flags x = if (lookup "myFlag" flags) then  
else 

then I can draw no such conclusion.

The point is, if I *want* to have several behaviours in one run I can
always use this second technique.  But Haskell as it now stands prevents
me from using the first, even when I *don't* want several behaviours in one
run.  I'd be prepared to pay the pain if I wanted the benefit.  Since I
don't want the "benefit" I don't want the pain.  

This message has clarified that there are three (not two) reasons
that argv should be constant

1.  Easier programming
2.  Faster running
3.  Extra reasoning ability (this the new one; every call to
f will behave the same way)

Simon






Re: stdin as a constant

1997-01-16 Thread Simon L Peyton Jones


| What you want is allowed.  Although stdin *is* a constant, it's simply a
| constant that refers to a handle.  The handle information (file pointer,
| attached device etc.) needn't be constant.  It's entirely consistent to
| provide, say:
| 
| reconnect :: Handle -> Handle -> IO Handle
| 
| to connect one handle to the same device as another (as long as you're
| careful in the impl. about duplicating file pointers, which can get you into
| trouble -- new files are much easier to deal with!).  This was actually one
| of the extensions that was considered fairly carefully in the I/O design.

This doesn't do what Sigbjorn is suggesting.

Suppose I import a module written by someone else which exports
the function toUpper:

-- toUpper reads stdin, converts all characters to upper
-- case, and sends them to stdout
toUpper :: IO ()

Now I import another module which exports sort:

-- sort reads stdin, divides it into lines, sorts the lines
-- and sends them to stdout
sort :: IO ()

Now suppose I want to arrange to connect toUpper and sort together.
I might hope to do it like this:

module Main where
import M1( toUpper )
import M2( sort )

main = do 
  (in,out) <- pipe;
  forkIO (withStdOut in toUpper);
  withStdIn out sort

The new functions are

pipe :: IO (Handle,Handle)
withStdOut, withStdIn :: Handle -> IO () -> IO ()

The point here is that toUpper and sort each work with *different* mappings
of stdin, stdout.


This example uses concurrency, which Haskell doesn't have.
In the absence of concurrency you can hack it like this:

main = do 
  (in,out) <- pipe;
  old_stdout <- setStdOut in;
  toUpper;
  setStdOut old_stdout;
  setStdIn out;
  sort

But it's a hack, isn't it.  And it doesn't extend to concurrency.

But this may help explain why I'm not so steamed up as I am about argv!

Simon






Re: Making argv a constant

1997-01-16 Thread Simon L Peyton Jones


Folks

I agree with Sigbjorn about argv, rather strongly, though apparently nobody
else does.

The Glasgow Haskell Compiler used to deal with command-line arguments in the
way mandated by Haskell 1.3; that is, we did a getArgs at the beginning and
then passed the arguments everywhere.

I recently undid all that.  Instead I now go

module CmdLineOpts where

argv = unsafePerformIO getArgs

unfoldSize :: Int
unfoldSize = lookupInt "-funfold-size" argv

useCleverFiniteMap :: Bool
useCleverFiniteMap = lookup "-fclever" argv

...etc..

That is, all the flags are unswizzled and turned into global
constants.

It was Just Too Painful to pass the flags everywhere.  For example, deep in
some dark corner of the transformation system there's a constant that
says how big a function body can be before GHC inlines it.  Threading
the command-line arguments all the way to that site is desperately painful. 
It's even worse if you discover that you'd like a command-line-controllable
thing in a dark corner that doesn't yet have the plumbing... you have to add
an extra argument to a chain of functions all the way to the top.

Passing the flags around costs extra instructions (not many each time, but a
lot of times).  Furthermore, even the flag test is expensive.  You can't
pass 100 flags individually, so you pass a single value and do a lookup each
time you want to test the flag.  Contrast that with a global thunk that
gets updated to a boolean the first time you use it.


I would put up with this pain (programming inconvenience, execution time
cost) if it bought me anything.  For example, you could make some of the
same complaints about the IO monad (it has to be propagated down to where
you use it), but there is a payoff: the order of IO operations is precisely
specified.

But in the case of argv, THERE IS NO BENEFIT WHATSOEVER.  None.  Zero.  Nix.
Nil.  Null.  Not even a little bit.   Will Partain calls this sort of thing
"functional programmer's death wish".  

argv really is a constant for any particular run of the program (I'm
excluding the ability that C programmers have to modify argv; I'll take a
copy at the start of the run, and that's what you get as the constant).  No
program transformations are restricted if argv is a constant.  No reasoning
principles are lost.


Well that's my rant for today.  I havn't said this before because there's an
easy workaround using unsafePerformIO; but unsafePerformIO isn't standard
Haskell, and it's a bit unsatisfactory that GHC is therefore not standard
Haskell in a way that would be very hard to fix.  I'd certainly prefer it if
argv was a standard-Haskell constant.

Simon

PS. I'm less steamed up about the stdin issue; but I think you missed
Sigbjorn's point.  Yes stdin is a constant now, but he'd like stdin *not* to
be a constant, so that he could take a value of type IO () that used stdin,
and reconnect its stdin to (say) a file.









Re: ICFP'97: update and final call for papers

1996-10-23 Thread Simon L Peyton Jones


Of course this should be 14 Feb '97!

Simon

| > Deadline [URLs below]
| > ~
| 
| > Haskell workshop14 February 1996
| 
| '97?  Or is this a Very Dead Line?






ICFP'97: update and final call for papers

1996-10-22 Thread Simon L Peyton Jones




International Conference on Functional Programming (ICFP'97)

  9-11 June 1997, Amsterdam
 http://www.fwi.uva.nl/research/func/icfp97.html

 
|  Final call for papers, and draft programme  |



This message is a brief round-up of the current state of play
for the International Conference on Functional Programming 1997.

 Only 27 writing days left before   
  the main conference submission deadline!  
(Deadline 18 Nov 1996)  

ICFP'97 will be an exciting conference, with two associated
workshops, a poster session, and opportunties to demonstrate
your software.  ICFP'97 is co-located with PEPM'97, which
follows immediately afterwards.

Call for submissions
~~~
Please consider submitting a paper to ICFP'97, or submitting a paper
to one of the associated workshops and poster session.  Their
deadlines are as follows:

Deadline [URLs below]
~
ICFP'97 main conference 18 November 1996
Haskell workshop14 February 1996
Types in Compilation workshop   10 January 1997
Poster session  1  February 1997


** For the main conference there are only 27 days left before 
   the submission deadline! Full details of the call for papers is at
http://www.diku.dk/events/conferences/icfp97/


** Professors, lecturers: please bring the poster session to the
  attention of your students, both graduate 
  and undergraduate.

Draft programme -- June 1997
~~~

Sat 7th Haskell workshop
John Launchbury
http://www.cse.ogi/~jl/ACM/Haskell.html
[ACM approval pending]

Sun 8th Types in Compilation workshop 
Bob Muller & Bob Harper
http://www.cs.bc.edu/~muller/TIC97/

Mon 9th - Weds 11th Main conference
http://www.fwi.uva.nl/research/func/icfp97.html

Tues 10th   Poster session
Walid Taha
http://www.cse.ogi.edu/PacSoft/icfp-poster.html

Thurs 12th - Fri 13th   Partial Evaluation and Program Manipulation
Charles Consel
http://www.irisa.fr/pepm97/








Re: Type inference bug?

1996-10-21 Thread Simon L Peyton Jones


This type error comes up such a lot that I'm copying this message
to the Haskell mailing list.

| The following program does not typecheck under ghc-2.01 unless you
| uncomment the type signature for test.  (ghc-0.29 seems to propagate
| the equality attribute correctly, and doesn't require the annotation.)
| 
|   module Test (test) where
|   -- test :: Eq a => [[a]] -> [a] -> [[a]]
|   test l xs = [ys | ys <- l, ys == map id xs]

The problem here is that there isn't a most general type for test; this is a
shortcoming in the language, not the implementation.  Consider:  map has type

map :: Monad m => (a->b) -> m a -> m b

Now, you are taking equality over those ys's, that equality over things 
of type (m b).  So the "right" type for test is:

test :: (Monad m, Eq (m a)) => [m a] -> m a -> [m a]

But alas, Haskell doesn't like the Eq (m a) constraint, so it complains
of a type error.

The solution is presumably to generalise the type system a bit, so that we
recover the principal-type property.

But we want to do the *right* generalisation.  I know Mark Jones is thinking
about this; others are welcome to do so too!

Simon






ANNOUNCE: Glasgow Haskell 2.01 release (for Haskell 1.3)

1996-07-26 Thread Simon L Peyton Jones


 The Glasgow Haskell Compiler -- version 2.01
 

We are pleased to announce the first release of the Glasgow Haskell
Compiler (GHC, version 2.01) for *Haskell 1.3*.  Sources and binaries
are freely available by anonymous FTP and on the World-Wide Web;
details below.

Haskell is "the" standard lazy functional programming language; the
current language version is 1.3, agreed in May, 1996.  The Haskell
Report is online at
http://haskell.cs.yale.edu/haskell-report/haskell-report.html.

GHC 2.01 is a test-quality release, worth trying if you are a gung-ho
Haskell user or if you are keen to try the new Haskell 1.3 features.
We advise *AGAINST* relying on this compiler (2.01) in any way.  We
are releasing our current Haskell 1.2 compiler (GHC 0.29) at the same
time; it should be pretty solid.

If you want to hack on GHC itself, then 2.01 is for you.  The release
notes comment further on this point.

What happens next?  I'm on sabbatical for a year, and Will Partain
(the one who really makes GHC go) is leaving at the end of July 96 for
a Real Job.  So you shouldn't expect rapid progress on 2.01 over the
next 6-12 months.  

The Glasgow Haskell project seeks to bring the power and elegance of
functional programming to bear on real-world problems.  To that end,
GHC lets you call C (including cross-system garbage collection),
provides good profiling tools, and concurrency and parallelism.  Our
goal is to make it the "tool of choice for real-world applications".

GHC 2.01 is substantially changed from 0.26 (July 1995), as the new
version number suggests.  (The 1.xx numbers are reserved for further
spinoffs from the Haskell-1.2 compiler.)  Changes worth noting
include:

  * GHC is now a Haskell 1.3 compiler (only).  Virtually all Haskell
1.2 modules need changing to go through GHC 2.01; the GHC
documentation includes a ``crib sheet'' of conversion advice.

  * The Haskell compiler proper (ghc/compiler/ in the sources) has
been substantially rewritten and is, of course, Much, Much,
Better.  The typechecker and the "renamer" (module-system support)
are new.

  * Sadly, GHC 2.01 is currently slower than 0.26.  It has taken
all our cycles to get it correct.  We fondly believe that the
architectural changes we have made will end up making 2.0x
*faster* than 0.2x, but we have yet to substantiate this belief;
sorry.  Still, 2.01 (built with 0.29) is quite usable.

  * GHC 2.01's optimisation (-O) is not nearly as good as 0.2x, mostly
because we haven't taught it about cross-module information
(arities, inlinings, etc.).  For this reason, a
2.01-built-with-2.01 (bootstrapped) is no fun to use (too slow),
and, sadly, that is where we would normally get .hc (intermediate
C; used for porting) files from... (hence: none provided).

  * GHC 2.01 is much smarter than 0.26 about when to recompile.  It
will abort a compilation that "make" thought was necessary at a
very early stage, if none of the imported types/classes/functions
*that are actually used* have changed.  This "recompilation
checker" uses a completely different interface-file format than
0.26.  (Interface files are a matter for the compilation system in
Haskell 1.3, not part of the language.)

  * The 2.01 libraries are not "split" (yet), meaning you will end up
with much larger binaries...

  * The not-mandated-by-the-language system libraries are now separate
from GHC (though usually distributed with it).  We hope they can
take on a "life of their own", independent of GHC.

  * All the same cool extensions (e.g., unboxed values), system
libraries (e.g., Posix), profiling, Concurrent Haskell, Parallel
Haskell,...

  * New ports: Linux ELF (same as distributed as GHC 0.28).

Please see the release notes for a complete discussion of What's New.

To run this release, you need a machine with 16+MB memory (more if
building from sources), GNU C (`gcc'), and `perl'.  We have seen GHC
2.01 work on these platforms: alpha-dec-osf2, hppa1.1-hp-hpux9,
sparc-sun-{sunos4,solaris2}, mips-sgi-irix5, and
i386-unknown-{linux,solaris2,freebsd}.  Similar platforms should work
with minimal hacking effort.  The installer's guide give a full
what-ports-work report.

Binaries are distributed in `bundles', e.g. a "profiling bundle" or a
"concurrency bundle" for your platform.  Just grab the ones you need.

Once you have the distribution, please follow the pointers in
ghc/README to find all of the documentation about this release.  NB:
preserve modification times when un-tarring the files (no `m' option
for tar, please)!

We run mailing lists for GHC users and bug reports; to subscribe, send
mail to [EMAIL PROTECTED]; the msg body should be:

subscribe glasgow-haskell- Your Name <[EMAIL PROTECTED]>

Please send bug reports about GHC to [EMAIL PROTECTED]

Simon Peyton Jones

Dated: July '96

Relevant URLs on the World-Wide We

  1   2   >