Re: Pattern Match Success Changes Types

1998-05-12 Thread Fergus Henderson

On 11-May-1998, Simon L Peyton Jones <[EMAIL PROTECTED]> wrote:
> 
> 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.

A simpler way of doing this is for the CSE pass to just insert a call
to a compiler builtin function `$unsafe_cast' if the types don't
match.  At the very end when you finally discard type information you
can then optimize away the call to `$unsafe_cast'.  This provides the
same benefits without the need for an extra pass. 

It probably doesn't buy a lot, but IMHO it's easy enough that it's worth
doing anyway.

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

I agree, this code should be disallowed.

Note that the different types can lead to different semantics.
Consider the following code, which is similar to the code above:

foo :: (Int -> Float) -> Either Int Char -> Either Float Char
foo f (Left  a)   = Left (f a)
foo _ r@(Right c) = classmethod r

class Demo t where
classmethod :: t -> Either Float Char

instance Demo Either Int Char where
classmethod = m1

instance Demo Either Float Char where
classmethod = m2

Here `r' has type `Either Int Char', not `Either a Char',
and this determines which class method is called.
Note that writing

foo _ r@(Right c) = classmethod (Right c)

would result in compile error (or worse) due to an uninstantiated
type variable.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





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-12 Thread Frank A. Christoph

>> 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.
>
>I don't think you can say this. Granted in this trivial example
>we are only talking about wasting constructor record per
>'demo expression'. But in other more complex examples we could be
>talking several. Also the total heap space that gets wasted this way
>is not an intrinsic property of the demo function. It depends on
>the number of 'demo expressions' (or similar) which get reduced.
>I don't think you can predict how many this will be with any generality.
>In some programs it could conceivably be huge Nos. Couldn't it?.
>It would be nice to re-use the existing constructors, even if the
>type checker says thats illegal.


I'm experiencing a little bout of deja vu here, so excuse me if it turns out
that I'm repeating myself.  (I could swear I already posted this, but it's
not in my "Messages Sent" folder...)

With regard to merging Either instances, I agree with Simon that for most
programs this will not buy you much, but there are two common kinds of
programs where one could expect a significant effect on performance, just
because of sheer scale.  The first is any program which uses an
error/exception monad on a program-wide scale.  The second is a program that
uses Chalmers' fudgets library since, as I recall, the type Either plays a
prominent role in the "messaging" system.

--FC






RE: Pattern Match Success Changes Types

1998-05-12 Thread Koen Claessen

Frank A. Christoph wrote:

 | With regard to merging Either instances, I agree with Simon that for most
 | programs this will not buy you much, but there are two common kinds of
 | programs where one could expect a significant effect on performance, just
 | because of sheer scale.

It is not only Either instances who suffer from this. Consider the
following definition of "map", which could be made by a naive user:

  map :: (a -> b) -> [a] -> [b]
  map f (x:xs) = f x : map f xs
  map f xs = xs

Same problem here.

Stefan Kahrs <[EMAIL PROTECTED]> wrote:

 | >  demo1 :: (a -> b) -> Either a c -> Either b c
 | >  demo1 f (Left  a)   = Left (f a)
 | >  demo1 _ r@(Right c) = r
 | 
 | Well, one could argue that the type of r is
 | forall a.Either a c
 | in which case there is no problem.

This should indeed do the trick, but I think it is way too difficult, if
not impossible. There is a reason that lambda-bound variables are not
generalized: because of decidability of type checking. But maybe it is
different with patterns, I don't know.

Regards,
Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.






Re: Pattern Match Success Changes Types

1998-05-12 Thread Adrian Hey

Hello,

Thanks to everybody who replied on this thread. I'm afraid I've got
to go away for a couple of weeks, so I can't join in any more :-(

Here are my views on the most recent postings...


On Mon 11 May, Jon Mountjoy wrote:
--
> I would guess 'sometimes'.  In some cases of course is it, but in
> other cases you might increase the scope of an expression and thereby
> worsen the space behaviour.  Have there been any attempts to
> identify/quantify this?

My first reaction to this was to wonder how it could ever be advantageous
to reduce the same expression several times instead of just once. Then,
on reflection I thought Gosh!, I see what you mean, thats never occured
to me before. Lazyness seems so blooming complicated in practice,
perhaps I'd better revert back to ML :-)


On Mon 11 May, Olaf Chitil wrote:
-
> See my paper:
> Common Subexpressions are Uncommon in Lazy Functional Languages

I think I will to, looks interesting.


On Mon 11 May, Simon L Peyton Jones wrote:
--
> My advice would be: write clear code, and let the compiler do the
> CSE.

I take it you mean avoid using 'as patterns'. I don't suppose there's any
possibility of expunging them from the language in due course.
No? I thought not.

If I remember right, David Turners Miranda seemed to be able to live without
'as patterns', didn't it?. I never got to use Miranda, I only read about
it.

> If it doesn't, complain to the compiler writers.   You have
> good reason to believe that it should.

Do you think they will take any notice of me :-)

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

Just for the record, I use _ as a 'wildcard' instead of a type variable
which occurs only once. Perhaps this is ambiguous wrt quantification?

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

I don't think you can say this. Granted in this trivial example
we are only talking about wasting constructor record per
'demo expression'. But in other more complex examples we could be
talking several. Also the total heap space that gets wasted this way
is not an intrinsic property of the demo function. It depends on
the number of 'demo expressions' (or similar) which get reduced.
I don't think you can predict how many this will be with any generality.
In some programs it could conceivably be huge Nos. Couldn't it?.
It would be nice to re-use the existing constructors, even if the
type checker says thats illegal.

I think its reasonable to assume that this is _operationally_ safe in most
Haskell implementations, even if the Type Checker does reject it.
I imagine that there isn't a single Haskell implemention where the
representation of (Right c) is in any way dependent on the type of the
argument of the 'Left' constructor. Its difficult to see how it can be,
because the type of the 'Left' constructors argument may not be known
at compile time. Also, such dependency implies compliation of numerous
different versions of 'demo' in order to cope with the multitude
of possibilities. If I'm wrong, please correct me. (After all, I've
had nothing to do with any Haskell implementation so it is quite
possible that my assumptions are invalid.)

Also, I note that the problem Jon Mountjoy mentioned is not relevant to
this particular optimisation. This optimisation will have no effect
on the sharing of expressions which are bound to the 'terminal' pattern
variables (Is that correct terminology? Anyway, you know what I mean.)
The only issue is do existing constructor records get re-used, or are new
ones created. I think the first option has to be more efficient, in
both time & space.

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

I don't think I agree, thats the whole point of my argument.
Either a c is the type of the second argument of demo1.
Things are different for 'r' because it it bound to the pattern/expression
(Right c), so we have more information, and may (subject to
certain constraints) 'take liberties' with the type assigned to 'r'.

I would say that, for all practical purposes, (r == Right c). Its seems
to me that an important feature of Haskell is that constructors are supposed
to behave like functions, are they not? So, given that Right is a (hopefully
well behaved) function, the 'value' of (Right c) is dependent only on the
'value' of c. It seems to be absurd to suggest that the type of (Right c) is,
in some way, also dependent on the type of an expression which is not
referenced at all. This smells strongly of 'side effects' to me,
type wise at least. 

> What type does the result of the fn have?  Either b c.
> Diffe

Re: Pattern Match Success Changes Types

1998-05-12 Thread Fergus Henderson

On 12-May-1998, Frank A. Christoph <[EMAIL PROTECTED]> wrote:
> 
> With regard to merging Either instances, I agree with Simon that for most
> programs this will not buy you much, but there are two common kinds of
> programs where one could expect a significant effect on performance, just
> because of sheer scale.  The first is any program which uses an
> error/exception monad on a program-wide scale.

Another common example, or perhaps an instance of your example, is parsers.
Parsers often use something similar to an error/exception monad for
propagating parse errors.

Parsing applications are very common, so it's probably worth optimizing
these cases.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
WWW:   |  of excellence is a lethal habit"
PGP: finger [EMAIL PROTECTED]| -- the last words of T. S. Garp.





Re: C to Haskell

1998-05-12 Thread Malcolm Wallace

Alex asked:
> > Greencard allows Haskell to call C (or Corba).  Is there a way to give C
> > code access to Haskell functions?
 
Simon writes:
> 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.

Calling Haskell from C is also possible now with nhc13, although, as
with Hugs, the mechanism is currently a little convoluted.  We at York
are working on YASTGC (yet another successor to GreenCard!) which will
make it all rather cleaner - although I suspect this design is somewhat
less advanced than Simon's.

Regards,
Malcolm





RE: Pattern Match Success Changes Types

1998-05-12 Thread Mariano Suarez Alvarez

On Tue, 12 May 1998, Koen Claessen wrote:

> Frank A. Christoph wrote:
> 
>  | With regard to merging Either instances, I agree with Simon that for most
>  | programs this will not buy you much, but there are two common kinds of
>  | programs where one could expect a significant effect on performance, just
>  | because of sheer scale.
> 
> It is not only Either instances who suffer from this. Consider the
> following definition of "map", which could be made by a naive user:
> 
>   map :: (a -> b) -> [a] -> [b]
>   map f (x:xs) = f x : map f xs
>   map f xs = xs
> 
> Same problem here.

Where is the CSE in theis def of map? Why is it naive? (Hugs & ghc define
map on lists exactly like that.) Maybe I'm naive...

-- m

---
Mariano Suarez Alvarez  The introduction of
Departamento de Matematica   numbers as coordinates
Universidad Nacional de Rosario [...] is an act of violence
Pellegrini 250  A. Weyl
2000 Rosario - Argentina
e-mail: [EMAIL PROTECTED]
---






3 AFP

1998-05-12 Thread Luis Soares Barbosa


--
 THIRD  INTERNATIONAL  SUMMER  SCHOOL  ON

 A D V A N C E D   F U N C T I O N A L   P R O G R A M M I N G
--

  12 - 19, September, 1998
University of Minho
   Braga
  Portugal



INVITED LECTURERS:  SCIENTIFIC EDITORS

Lex Augusteijn, Philips ResearchPedro Henriques, Minho
Lennart Augustsson, ChalmersDoaitse Swierstra, Utrecht
Roland Backhouse, Eindhoven Jose Oliveira, Minho
Johan Jeuring, Utrecht
Daan Leijen, Utrecht
Rafael Lins, Recife
Erik Meijer, Utrecht +---+
Oege de Moor, Oxford |PROGRAM & REGISTRATION AT: |
Jose Oliveira, Minho |   |
Joao Saraiva, Minho  |http://www.di.uminho.pt/~afp   |
Tim Sheard, Oregon   +---+
Doaitse Swierstra, Utrecht


--
OVERVIEW
--

After two successful schools on Advanced Functional Programming, which
were held in Bastad (Springer LNCS 925) and Portland (Springer LNCS 1129),
a third school will be organized in Braga, Portugal, by the Department of
Computer Science of the University of Minho, from 12th to 19th September,
1998. 

The primary aim of this series of schools is to make the participants
acquainted with recent developments in the area of Functional Programming.
Lectures are aimed especially at showing new programming techniques,
introducing new language constructs, and presenting interesting application
areas. Another important goal is to provide that kind of information which
enables participants to use functional programming in their daily life, 
after returning from the school.

The school emphasizes LEARNING BY DOING.  Thus a substantial amount of time
is reserved for actually using the ideas presented in the lectures in
programming exercises. During the course students will be challenged to solve 
a number of exercises in generic program construction by interaction with the
lecturer, and by working together on problems.


Most of the lectures in this Summer School are aimed at some aspect of

 GENERIC PROGRAMMING

i.e., programming in a "data-type independent" way.  Generic programming has
a number of advantages. It makes it possible to write programs that solve a 
class of problems once and for all, instead  of writing new code over and over
again for each different instance.

The School will integrate 7 regular courses, 2 invited lectures and a Haskell
tutorial. A detailed schedule is available form the School's homepage.
A WORKSHOP for PhD Students is also planned for Friday, 18th.  Everyone 
intending to make a presentation should submit an extended abstract along 
with the registration form.


--
VENUE
--

The Summer School will be held in Braga, an ancient town in the 
north-west corner of Portugal, located 50 km from Oporto and 30 km
from the seaside.  A parallel cultural program will enable participants to
get in touch with the region and the local academic traditions.

Both the scientific sessions, meals and accommodation will be located at
Casa do Espirito Santo, on the top of a hill surrounding the town.
This self-contained and quiet environment will hopefully provide for maximal
interaction between the participants and a good working atmosphere.

Braga has fast train and motorway connections to Lisbon, the city which is
hosting the celebrations of the 5th centenary of Vasco da Gama's arrival
in India.  A world exhibition --- Expo'98 --- will be held until the end 
of September on the theme "The oceans: a heritage for the future".


--
REGISTRATION
--

Registration can be made directly from the School's homepage or by
electronic mail to the address below, until 25th JULY.

The School fee, including accommodation in double room, full boarding
and documentation, is PTE 75 000. Late registrations will be
accepted until September, the 1st, but charged with an additional
fee of PTE 25 000 (1 USD = 184 PTE). 

For additional information contact:

 +-+
 | AFP |
 | Carla Oliveira  |
 | Univ. Minho, CIUM   |
 | Campus de Gualtar -- 4710 Brag

let succ be an Enum class member

1998-05-12 Thread Christian Sievers

Hello, this is about a change in the prelude I'd like to suggest.

The following is obviously not what one would expect:

  Prelude> succ 100::Integer

  Program error: {primIntegerToInt 100}


However, with the prelude defining succ to be

  succ,:: Enum a => a -> a
  succ =  toEnum . (+1) . fromEnum

we can't hope for anything better.

My suggestion is to make succ a member function of class Enum, with
the old definition as default, so that the instance Enum Integer
can define it to be simply (+1).

Another example is
  data Nat = Zero | Succ Nat
where succ=Succ is not only more natural, but also much more
efficient.

Of course the same holds for pred.

What do you think?
Are there any drawbacks?
Could it be like this in standard haskell?


Christian Sievers





RE: Pattern Match Success Changes Types

1998-05-12 Thread Koen Claessen

On Tue, 12 May 1998, Mariano Suarez Alvarez wrote:

 | On Tue, 12 May 1998, Koen Claessen wrote:
 | 
 | >   map :: (a -> b) -> [a] -> [b]
 | >   map f (x:xs) = f x : map f xs
 | >   map f xs = xs
 | 
 | Where is the CSE in theis def of map? Why is it naive? (Hugs & ghc define
 | map on lists exactly like that.) Maybe I'm naive...

Sorry, I was too brief. I meant this: the third line

  map f xs = xs

does not type check. It should be:

  map f [] = []

Regards,
Koen.

--
Koen Claessen,
[EMAIL PROTECTED],
http://www.cs.chalmers.se/~koen,
Chalmers University of Technology.





Re: let succ be an Enum class member

1998-05-12 Thread Jeffrey R. Lewis

Christian Sievers wrote:

> Hello, this is about a change in the prelude I'd like to suggest.
>
> The following is obviously not what one would expect:
>
>   Prelude> succ 100::Integer
>
>   Program error: {primIntegerToInt 100}
>
> However, with the prelude defining succ to be
>
>   succ,:: Enum a => a -> a
>   succ =  toEnum . (+1) . fromEnum
>
> we can't hope for anything better.
>
> My suggestion is to make succ a member function of class Enum, with
> the old definition as default, so that the instance Enum Integer
> can define it to be simply (+1).
>
> Another example is
>   data Nat = Zero | Succ Nat
> where succ=Succ is not only more natural, but also much more
> efficient.
>
> Of course the same holds for pred.
>
> What do you think?
> Are there any drawbacks?
> Could it be like this in standard haskell?

I agree, in fact, I'd go one stronger.  I'll propose that `fromEnum' and
`toEnum' be taken out, since clearly not all enumerable types are
subtypes of Int (as you point out, Integer leaps immediately to mind).

As an experiment, a little while back,I modified the Prelude to use an
Enum class that included `succ' and `pred', but eliminated `fromEnum'
and `toEnum'.   I then had to eliminate all uses of `fromEnum' and
`toEnum'.  I found that, in every case, `fromEnum' and `toEnum' were
used at specific types (mostly Char), and popped in the suitable
type-specific replacement.  I also had to change hugs to `derive' `succ'
and `pred' instead of `fromEnum' and `toEnum', but this wasn't
difficult.

This certainly makes the Enum class cleaner conceptually, and I can't
think of any drawbacks, except for concern about legacy code (I love
that concept for a young language like Haskell ;-).

--Jeff





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 S. Alexander Jacobson

On Mon, 11 May 1998, Alastair Reid wrote:
> Hugs' "server interface" provides a very limited ability for C functions
> to call Haskell.  Have a look at
> 
>   http://haskell.org/hugs/docs/server.html
> 
> Needless to say, it'll all be better in the new Hugs-GHC system
> we're working on.  

I have gotten a few emails on this new system and it sounds exciting, but
I am a little confused.  The HugServer effectively provides a way to
call use Hugs from within a C program.  I am looking for something
somewhat different (maybe this is H/Direct or not?).

The York system seems to be somewhat better, but still seems to require a
substantial amount of manual labor.

Ideally there would be a system which takes a Haskell project and exports
enumerated functions into a header file and set of C files.  This would
allow C code like:

#include "myHaskellProg.h" //functions prototypes + Haskell fun data structures

void main(int argc,char **argv) {
  printf(myHaskellFunction(argv[1]));
}

If the Haskell file contained its own main, then it would be a standalone
executable.

I could use this to write an adapter to the Apache module API.
It would also allow the use of Haskell code in C and Java libraries.
It would also run a lot faster than Hugs interpreted Haskell.
If you are also required to execute some initialization function,
that would not be soo bad either.

(yes, this begs the question of translating C arguments to Haskell, but 
 if export was restricted to basic types that would cover 80% of needs.
 it would be nice to write Haskell code to process C structs, but that is 
 really just bonus.)

If this is what H/Direct is about, that is great.  If not, I guess I will
just have to cope.

-Alex-

PS Erik, I have made a new version of the CGI library that is somewhat
   easier for newer Haskell users. I will forward once I've finished
   testing (if you are interested).  

___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax






Re: let succ be an Enum class member

1998-05-12 Thread Jon . Fairbairn

On 12 May, Jeffrey R. Lewis wrote:
> I agree, in fact, I'd go one stronger.  I'll propose that `fromEnum' and
> `toEnum' be taken out, since clearly not all enumerable types are
> subtypes of Int (as you point out, Integer leaps immediately to mind).

An alternative would be to return fromEnum and toEnum to their
overloaded types:

toEnum   :: Integral i => i -> a
fromEnum :: Integral i => a -> i

would that suit?

-- 
Jon Fairbairn [EMAIL PROTECTED]







RE: Pattern Match Success Changes Types

1998-05-12 Thread Adrian Hey

On Tue 12 May, Frank A. Christoph wrote:
> I'm experiencing a little bout of deja vu here, so excuse me if it turns out
> that I'm repeating myself.  (I could swear I already posted this, but it's
> not in my "Messages Sent" folder...)
> 
> With regard to merging Either instances, I agree with Simon that for most
> programs this will not buy you much, but there are two common kinds of
> programs where one could expect a significant effect on performance, just
> because of sheer scale.  The first is any program which uses an
> error/exception monad on a program-wide scale.  The second is a program that
> uses Chalmers' fudgets library since, as I recall, the type Either plays a
> prominent role in the "messaging" system.

I just caught this one...

Precisely, I myself have written a parser in which functions similar to
'demo' appear all over the place. Either is a common data type to use to
represent Success or Failure/Exceptions.

The same problem is also apparent with the use of Maybe. In fact, just
about every algebraic type I can think of will have some constructors
that don't reference every type argument, and can therefore be regarded
as 'more polymorphic' when they appear in patterns.

Regards
-- 
Adrian Hey