From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 11:03:58 2000 Date: Fri, 1 Dec 2000 11:03:58 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: a trap for the unwary
Today, I thought I had discovered a bug in ghc.  Then I tried hbc
and Hugs, and they also rejected my program with the same error.
nhc98 alone accepts it without complaint.  I looked up the Report,
and it seems that the program is indeed incorrect.

Quick quiz:  without running this through a compiler, who can spot
the mistake?  :-)

> module Main where
> import Char
> f x = y
>   where
>     y | isSpace x = True
>     y | otherwise = False
> main = print (f 'x')

Regards,
    Malcolm


From wimjan@xs4all.nl Fri Dec 1 14:49:13 2000 Date: Fri, 01 Dec 2000 15:49:13 +0100 From: Wim-Jan Hilgenbos wimjan@xs4all.nl Subject: Beginner: error when using multiple where stmts in hugs98
This is a multi-part message in MIME format.
--------------F1E92FD1F075259053A3C4BA
Content-Type: text/plain; charset=us-ascii
Content-Transfer-Encoding: 7bit

Hi,

I've been trying some examples in functional programming. Most things
work fine,
but I have trouble with expressions with 'where' clauses that define
more then one
local definition.
(I work with hugs98 version september 1999 under Linux)

For example:

----------[ Mydiff.hs ]----------------------
module Mydiff where

mydiff f = f'
        where f' x = ( f (x+h) - f x) / h
                    h = 0.0001

----------[ end Mydiff.hs ]-------------------

When I try to load this module I get
    ERROR "Mydiff.hs" (line 5): Syntax error in input (unexpected `=')
line 5 is the line h = 0.0001

I tried other examples like this one, played around with line-breaks
white-space etc.
Rewriting the f' line to f' x = (f (x+0.0001) - f x) / 0.0001 does the
trick, but is not very
satisfying.

Can anyone help?
WJ

PS. I attached above example


-- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
Disclaimer:
"These opinions are my own, though for a small fee they be
 yours too."
 -- Dave Haynie



--------------F1E92FD1F075259053A3C4BA
Content-Type: text/plain; charset=us-ascii;
 name="Mydiff.hs"
Content-Transfer-Encoding: 7bit
Content-Disposition: inline;
 filename="Mydiff.hs"

module Mydiff where

mydiff f = f'
	where f' x = ( f (x+h) - f x) / h
			 h = 0.0001

--------------F1E92FD1F075259053A3C4BA--



From jmaessen@mit.edu Fri Dec 1 15:41:32 2000 Date: Fri, 1 Dec 2000 10:41:32 -0500 From: Jan-Willem Maessen jmaessen@mit.edu Subject: a trap for the unwary
Malcolm Wallace writes:
> Quick quiz:  without running this through a compiler, who can spot
> the mistake?  :-)
> 
> > module Main where
> > import Char
> > f x = y
> >   where
> >     y | isSpace x = True
> >     y | otherwise = False    --  ** The problem line?
> > main = print (f 'x')

Without running this through the compiler, but based on similar
problems I've had recently, I'd assume the problem is the marked
line.  Two outer-level patterns are each presented with guards.  This
would be correct for a function definition:

> f x = y ()
>   where
>     y _ | isSpace x = True
>     y _ | otherwise = False    --  ** Does this work?


This is a tricky issue.  I'd like the original program to be all
right.  We end up sowing confusion with erroneous programs like this
one:

> f x = y
>   where
>     y | otherwise = False    --  ** Now this pattern overlaps!
>     y | isSpace x = True

But of course an analogous problem occurs in the function definition,
and I think can be caught by turning on warnings in ghc.

-Jan-Willem Maessen
jmaessen@mit.edu


From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 15:44:16 2000 Date: Fri, 1 Dec 2000 15:44:16 +0000 From: Malcolm Wallace Malcolm.Wallace@cs.york.ac.uk Subject: a trap for the unwary
> > > f x = y
> > >   where
> > >     y | isSpace x = True
> > >     y | otherwise = False    --  ** The problem line?

Correct.  Here y is a pattern binding, and multiple pattern bindings of
the same variable are not permitted.

> f x = y ()
>   where
>     y _ | isSpace x = True
>     y _ | otherwise = False    --  ** Does this work?

Correct. Here y is a function binding instead, and multiple clauses
*are* permitted.

> I'd like the original program to be all right. 

Me too.  I wrote 'y' as a 0-arity function, knowing that because
it used a free variable bound at an outer scope, it would probably
be lambda-lifted to a greater arity by the compiler.  But only one
compiler saw it in the same way as I did. :-)

Of course, if the pattern binding is more complex than a single
variable name, I still want the no-multiple-bindings rule to apply
as usual:

> f x = y ()
>   where
>     (y:_) | isSpace x = [True]
>     (y:_) | otherwise = [False]    --  ** Definitely wrong

and indeed all compilers reject this, as they should.

Regards,
    Malcolm


From schulzs@uni-freiburg.de Fri Dec 1 17:23:57 2000 Date: Fri, 01 Dec 2000 17:23:57 +0000 From: Sebastian Schulz schulzs@uni-freiburg.de Subject: Beginner: error when using multiple where stmts in hugs98
Wim-Jan Hilgenbos wrote:
> 
> Hi,
> 
> I've been trying some examples in functional programming. Most things
> work fine,
> but I have trouble with expressions with 'where' clauses that define
> more then one
> local definition.
> (I work with hugs98 version september 1999 under Linux)
> 
> For example:
> 
> ----------[ Mydiff.hs ]----------------------
> module Mydiff where
> 
> mydiff f = f'
>         where f' x = ( f (x+h) - f x) / h
>                     h = 0.0001
> 
> ----------[ end Mydiff.hs ]-------------------
> 

Try this:

 mydiff f = f'
     where 
     f' x = ( f (x+h) - f x) / h
     h = 0.0001
 
It works fine with Hugs98 (feb2000).

regards
seb


From ron4ld@pacific.net.au Fri Dec 1 21:08:56 2000 Date: Sat, 02 Dec 2000 08:08:56 +1100 From: Ronald Kuwawi ron4ld@pacific.net.au Subject: old easter egg
open text editor, type
hash :: [Char] -> Int
hash = (foldl (+) 0) . (map ord)

save as hash.hs

load script, type:
hash "MSDOS 6.000"

or 

hash "SYSTEM 7.0"


:-)
Ronald


From zhanyong.wan@yale.edu Fri Dec 1 21:55:06 2000 Date: Fri, 01 Dec 2000 16:55:06 -0500 From: Zhanyong Wan zhanyong.wan@yale.edu Subject: old easter egg
Ronald Kuwawi wrote:
> 
> open text editor, type
> hash :: [Char] -> Int
> hash = (foldl (+) 0) . (map ord)
> 
> save as hash.hs
> 
> load script, type:
> hash "MSDOS 6.000"
> 
> or
> 
> hash "SYSTEM 7.0"

or

hash "HASKELL%98"

:-)

-- Zhanyong Wan


From peterson-john@cs.yale.edu Fri Dec 1 22:14:41 2000 Date: Fri, 1 Dec 2000 17:14:41 -0500 From: John Peterson peterson-john@cs.yale.edu Subject: The Haskell store is open ....
Head to http://www.cafepress.com/haskell for your holiday shopping.
Thanks to Conal Elliott and Fritz Ruehr for their artwork.  Conal's
design was produced by Pan so this shirt is in fact powered by
Haskell!

I'll be glad to add more designs in the future.  Once cafepress lets
me put more than one design in a store I'll consolidate everything.
Meanwhile, if you want to set up a separate store I can link it into
haskell.org for you.

  John


From jf15@hermes.cam.ac.uk Sat Dec 2 00:03:30 2000 Date: Sat, 2 Dec 2000 00:03:30 +0000 (GMT) From: Jon Fairbairn jf15@hermes.cam.ac.uk Subject: old easter egg
On Fri, 1 Dec 2000, Zhanyong Wan wrote:

>=20
> Ronald Kuwawi wrote:
> >=20
> > open text editor, type
> > hash :: [Char] -> Int
> > hash =3D (foldl (+) 0) . (map ord)

> hash "HASKELL%98"


hash "Haskell Ninety Eight !!"=20

surely?
--=20
J=F3n Fairbairn                                 Jon.Fairbairn@cl.cam.ac.uk



From kili@outback.escape.de Sat Dec 2 02:31:05 2000 Date: Sat, 2 Dec 2000 03:31:05 +0100 (CET) From: Matthias Kilian kili@outback.escape.de Subject: old easter egg
On Sat, 2 Dec 2000, Jon Fairbairn wrote:

> > hash "HASKELL%98"
>
>
> hash "Haskell Ninety Eight !!"

Here's the who;e truth:

hash "Turing!"

Kili

--=20
Nunja! Wenn man erst einmal anf=E4ngt zu denken, dann ist es wie
eine Sucht. Man kommt nicht mehr los davon.
[WoKo in dag=B0, 28.11.2000]



From ashley@semantic.org Sat Dec 2 19:08:53 2000 Date: Sat, 2 Dec 2000 11:08:53 -0800 From: Ashley Yakeley ashley@semantic.org Subject: old easter egg
At 2000-12-01 13:08, Ronald Kuwawi wrote:

>open text editor, type
>hash :: [Char] -> Int
>hash = (foldl (+) 0) . (map ord)
>
>save as hash.hs
>
>load script, type:
>hash "MSDOS 6.000"
>
>or 
>
>hash "SYSTEM 7.0"

It's not really an easter egg, is it? It's more a modern form of 
numerology. I was hoping to see the hugs environment show me a little 
dancing bunny animation or something.

letter c | ord c <= 64 = 0
letter c | ord c <= 90 = ord c - 64
letter c | ord c <= 96 = 0
letter c | ord c <= 122 = ord c - 96
letter c | otherwise = 0

renum n | n == 0 = 0
renum n | otherwise = (mod ((n - 1) * 19) 26) + 1

engql c = renum (letter c)

engq = (foldl (+) 0) . (map engql)


-- 
Ashley Yakeley, Seattle WA



From gmh@marian.cs.nott.ac.uk Mon Dec 4 08:54:00 2000 Date: Mon, 4 Dec 2000 8:54:00 GMT From: gmh@marian.cs.nott.ac.uk gmh@marian.cs.nott.ac.uk Subject: JFP Special Issue on Haskell
Dear all,

Please note that the deadline for submission to the JFP Special Issue
on Haskell is in two months time --- 1st February 2001.

Graham Hutton

----------------------------------------------------------------------

			   CALL FOR PAPERS

		  Journal of Functional Programming

		       Special Issue on Haskell
  

Since its  inception in 1987, Haskell  has provided a  focal point for
research  in  lazy  functional  programming.   During  this  time  the
language  has continually  evolved, as  a result  of  both theoretical
advances  and  practical  experience.   Haskell  has proved  to  be  a
powerful tool for many kinds of programming tasks, and applications in
industry are beginning to emerge.  The recent definition of Haskell 98
provides a long-awaited stable version  of the language, but there are
many exciting possibilities for future versions of Haskell.

The  fourth  Haskell  Workshop  was  held  as part  of  the  PLI  2000
colloquium  on Principles, Logics,  and Implementations  of high-level
programming  languages  in Montreal,  17th  September 2000.   Previous
Haskell Workshops have been held in Paris (1999), Amsterdam (1997) and
La Jolla (1995).   Following on from these workshops,  a special issue
of the Journal  of Functional Programming will be  devoted to Haskell.
Possible topics include, but are not limited to:

   Critiques of Haskell 98;
   New proposals for Haskell;
   Applications or case studies;
   Programming techniques;
   Reasoning about programs;
   Semantic issues;
   Pedagogical issues;
   Implementation.

Contributors to  any of  the Haskell workshops  are invited  to submit
full papers to the special issue on Haskell, but submission is open to
everyone.   Submissions should be  sent to  the guest  editor (address
below),  with   a  copy  to   Nasreen  Ahmad  (nasreen@dcs.gla.ac.uk).
Submitted  articles should  be sent  in postscript  format, preferably
gzipped and uuencoded. In addition, please send, as plain text, title,
abstract,  and contact  information.  The  submission deadline  is 1st
February 2001.  For other  submission details, please consult an issue
of JFP or see the Journal's web pages.

Guest Editor:

   Graham Hutton
   School of Computer Science and IT
   The University of Nottingham
   Nottingham NG8 1BB
   United Kingdom
   gmh@cs.nott.ac.uk

Useful Links:

   2000 Haskell Workshop          www.cs.nott.ac.uk/~gmh/hw00.html
   JFP Special Issue on Haskell   www.cs.nott.ac.uk/~gmh/jfp.html
   JFP Home Page                  www.dcs.gla.ac.uk/jfp

----------------------------------------------------------------------


From zhanyong.wan@yale.edu Mon Dec 4 16:04:24 2000 Date: Mon, 04 Dec 2000 11:04:24 -0500 From: Zhanyong Wan zhanyong.wan@yale.edu Subject: Rank-2 polymorphism & type inference
Hello,

I'm playing with Haskell's rank-2 polymorphism extension and am puzzled
by the following example:

-----------------------------------------------------------
module R2Test where

class SubType a b where
  super :: a -> b

data Sub c a = Sub
data Super c a = Super

instance SubType (Sub c a) (Super c a)

f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b
f g x = undefined

x :: Sub c Int
x = undefined

y :: Super c Int
y = f (\a -> super a) x
----------------------------------------------------------

I though the definition of y should type-check because (roughly):

1. We know x :: Sub c Int, y :: Super c Int
2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c
b, we know a is Int and b is Int.
3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we
are all set.

However, Hugs 98 Feb 2000 (with the -98 switch) gives me:

ERROR "R2Test.hs" (line 19): Cannot justify constraints in application
*** Expression    : \a -> super a
*** Type          : Sub b _1 -> Super b _2
*** Given context : ()
*** Constraints   : SubType (Sub b _1) (Super b _2)

and GHC 4.08.1 (with the -fglasgow-exts switch) gives:

R2Test.hs:19:
    Could not deduce `SubType (Sub c a) (Super c Int)'
        from the context: ()
    Probable cause: missing `SubType (Sub c a) (Super c Int)'
                    in the type signature of an expression
                    or missing instance declaration for `SubType (Sub c
a) (Super
 c Int)'
    arising from use of `super' at R2Test.hs:16
    In the right-hand side of a lambda abstraction: super a

If I remove the "forall c." from the type signature for f, then both
compilers accept my code.

My question is: how does the type inference algorithm work in the
presence of rank-2 types?  Does anyone know of any documentation on
this?  Thanks!

-- Zhanyong

# Zhanyong Wan     http://pantheon.yale.edu/~zw23/ ____
# Yale University, Dept of Computer Science       /\___\
# P.O.Box 208285, New Haven, CT 06520-8285        ||___|


From zhanyong.wan@yale.edu Mon Dec 4 21:30:46 2000 Date: Mon, 04 Dec 2000 16:30:46 -0500 From: Zhanyong Wan zhanyong.wan@yale.edu Subject: Rank-2 polymorphism & type inference
Hi,

After sending out my question, I noticed that hugs and ghc understood my
code differently: from the error messages, we can see that hugs view (\a
-> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it
is Sub c a -> Super c Int.  To verify it, I changed my code s.t. y is
defined as

  y = f (\(a :: Sub c Int) -> super a) x

instead of

  y = f (\a -> super a) x

Guess what happened: ghc *accepted* the code, and hugs *rejected* it
with message:

ERROR "R2Test.hs" (line 19): Cannot justify constraints in application
*** Expression    : \a -> super a
*** Type          : Sub b Int -> Super b _2
*** Given context : ()
*** Constraints   : SubType (Sub b Int) (Super b _2)

Aha, this is something interesting!  Either there is no standard for the
Haskell rank-2 type inference algorithm (which is a sad thing), or one
of hugs and ghc is wrong here.  Now the hugs/ghc guys on the list can no
longer remain silent -- you got to defend yourselves! :-)  Could anyone
explain to me what the right behavior is supposed to be here?  Thanks.

-- Zhanyong

Zhanyong Wan wrote:
> 
> Hello,
> 
> I'm playing with Haskell's rank-2 polymorphism extension and am puzzled
> by the following example:
> 
> -----------------------------------------------------------
> module R2Test where
> 
> class SubType a b where
>   super :: a -> b
> 
> data Sub c a = Sub
> data Super c a = Super
> 
> instance SubType (Sub c a) (Super c a)
> 
> f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b
> f g x = undefined
> 
> x :: Sub c Int
> x = undefined
> 
> y :: Super c Int
> y = f (\a -> super a) x
> ----------------------------------------------------------
> 
> I though the definition of y should type-check because (roughly):
> 
> 1. We know x :: Sub c Int, y :: Super c Int
> 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c
> b, we know a is Int and b is Int.
> 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we
> are all set.
> 
> However, Hugs 98 Feb 2000 (with the -98 switch) gives me:
> 
> ERROR "R2Test.hs" (line 19): Cannot justify constraints in application
> *** Expression    : \a -> super a
> *** Type          : Sub b _1 -> Super b _2
> *** Given context : ()
> *** Constraints   : SubType (Sub b _1) (Super b _2)
> 
> and GHC 4.08.1 (with the -fglasgow-exts switch) gives:
> 
> R2Test.hs:19:
>     Could not deduce `SubType (Sub c a) (Super c Int)'
>         from the context: ()
>     Probable cause: missing `SubType (Sub c a) (Super c Int)'
>                     in the type signature of an expression
>                     or missing instance declaration for `SubType (Sub c
> a) (Super
>  c Int)'
>     arising from use of `super' at R2Test.hs:16
>     In the right-hand side of a lambda abstraction: super a
> 
> If I remove the "forall c." from the type signature for f, then both
> compilers accept my code.
> 
> My question is: how does the type inference algorithm work in the
> presence of rank-2 types?  Does anyone know of any documentation on
> this?  Thanks!


From simonpj@microsoft.com Tue Dec 5 13:12:20 2000 Date: Tue, 5 Dec 2000 05:12:20 -0800 From: Simon Peyton-Jones simonpj@microsoft.com Subject: Rank-2 polymorphism & type inference
| > My question is: how does the type inference algorithm work in the
| > presence of rank-2 types?  Does anyone know of any documentation on
| > this?  Thanks!

I had a look at this.  Actually it turns out to be only loosely related
to rank-2 polymorphism.  I've been able to reproduce your problem using
only Haskell 98.  It looks like a problem with incomplete type inference
Consider this:

	module MP where

	class C t where
  	  op :: t -> Bool

	instance C [t] where
	  op x = True

	test :: [Int] -> Bool	-- REQUIRED!
	test y = let f :: c -> Bool
		      f x = op (y >> return x)
		 in
		 f (y::[Int])

Both GHC and Hugs reject this module if the type signature for
test is omitted.  NHC (v1.00, 2000-09-15) falls over completely, with
	Fail: Prelude.chr: bad argument
All three succeed if the signature is in, or if the signature for f is
omitted.

This was unexpected, to me at least.  You may need to add a type 
signature if polymorphic recursion is being used, but here it isn't!

The problem is this: the compiler learns that y::[Int] "too late" to make
use of it when solving the constraints arising from the RHS of f.

In more detail, here's what happens.  First we typecheck the RHS of
f, deducing the types

	x :: a					where a is fresh
	y :: k a					where k is fresh
	y >> return x :: k a
	op (y >> return x) :: Bool		with constraint C (k a)
	\x -> op (y >> return x) :: a -> Bool	with constraint C (k a)

Now we try to generalise over a.  We need to discharge the contraint
C (k a).  Later we will find that y::[Int], so k=[], but we don't know that
yet.  So we can't solve the constraint.

Adding the type signature to 'f' lets both GHC and Hugs figure out
that y::[Int] in advance, so we need to solve the constraint C ([] a),
which is fine.


So I think you have uncovered a genuine problem, and one I don't
know how to solve.  It can always be "solved" by adding more
type information, such as the type sig for 'test'.  In you case you said:

| After sending out my question, I noticed that hugs and ghc understood my
| code differently: from the error messages, we can see that hugs view (\a
| -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it
| is Sub c a -> Super c Int.  To verify it, I changed my code s.t. y is
| defined as
| 
|   y = f (\(a :: Sub c Int) -> super a) x

This is exactly right, and GHC is happy now. I can't account for Hugs'
behaviour.


The "right" solution is presumably to defer all constraint checking until we
know what 'k' is.  But that's a bit tricky because the constraint checking
generates bindings that must appear in f's RHS.  A full solution looks a
bit over-kill-ish.  But it's unsettling that the inference algorithm is
incomplete.

Simon


From johanj@cs.uu.nl Tue Dec 5 14:22:06 2000 Date: Tue, 05 Dec 2000 15:22:06 +0100 From: Johan Jeuring johanj@cs.uu.nl Subject: Call for papers: Haskell Workshop 2001
============================================================================

                              CALL FOR PAPERS

                           2001 Haskell Workshop

                               Firenze, Italy

        The Haskell Workshop forms part of the PLI 2001 colloquium
        on Principles, Logics, and Implementations of high-level
        programming languages, which comprises the ICFP/PPDP conferences
        and associated workshops. Previous Haskell Workshops have been
        held in La Jolla (1995), Amsterdam (1997), Paris (1999), and
        Montreal (2000).

        http://www.cs.uu.nl/people/ralf/hw2001.{html,pdf,ps,txt}

============================================================================

Scope
-----

The purpose of the Haskell Workshop is to discuss experience with
Haskell, and possible future developments for the language.  The scope
of the workshop includes all aspects of the design, semantics, theory,
application, implementation, and teaching of Haskell.  Submissions that
discuss limitations of Haskell at present and/or propose new ideas for
future versions of Haskell are particularly encouraged.  Adopting an
idea from ICFP 2000, the workshop also solicits two special classes of
submissions, application letters and functional pearls, described
below.

Application Letters
-------------------

An application letter describes experience using Haskell to solve
real-world problems. Such a paper might typically be about six pages,
and may be judged by interest of the application and novel use of
Haskell.

Functional Pearls
-----------------

A functional pearl presents - using Haskell as a vehicle - an idea that
is small, rounded, and glows with its own light. Such a paper might
typically be about six pages, and may be judged by elegance of
development and clarity of expression.

Submission details
------------------

Deadline for submission:        1st June 2001
Notification of acceptance:     1st July 2001
Final submission due:           1st August 2001
Haskell Workshop:               to be announced

Authors should submit papers of at most 12 pages, in postscript format,
formatted for A4 paper, to Ralf Hinze (ralf@cs.uu.nl) by 1st June
2001.  The use of the ENTCS style files is strongly recommended.
Application letters and functional pearls should be labeled as such on
the first page. They may be any length up to twelve pages, though
shorter submissions are welcome.  The accepted papers will be published
as a University of Utrecht technical report.

Programme committee
-------------------

Manuel Chakravarty      University of New South Wales
Jeremy Gibbons          University of Oxford
Ralf Hinze (chair)      University of Utrecht
Patrik Jansson          Chalmers University
Mark Jones              Oregon Graduate Institute
Ross Paterson           City University, London
Simon Peyton Jones      Microsoft Research
Stephanie Weirich       Cornell University

============================================================================


From simonpj@microsoft.com Tue Dec 5 17:18:18 2000 Date: Tue, 5 Dec 2000 09:18:18 -0800 From: Simon Peyton-Jones simonpj@microsoft.com Subject: Rank-2 polymorphism & type inference
Musing on Zhanyong's problem some more, a solution occurs to me.
Curiously, it's exactly the solution required for another useful
extension to type classes.  Here is is, so people can shoot holes in it.

| In more detail, here's what happens.  First we typecheck the RHS of
| f, deducing the types
| 
| 	x :: a					where a is fresh
| 	y :: k a					where k is fresh
| 	y >> return x :: k a
| 	op (y >> return x) :: Bool		with constraint C (k a)
| 	\x -> op (y >> return x) :: a -> Bool	with constraint C (k a)
| 
| Now we try to generalise over a.  We need to discharge the contraint
| C (k a).  Later we will find that y::[Int], so k=[], but we 
| don't know that yet.  So we can't solve the constraint.

One bad solution I thought of was to give f the type
	
	f :: forall a. C (k a) => a -> Bool

This is bad because it's not the type signature the programmer
specified.  (It's also bad operationally because we'll pass a
dictionary at runtime, which isn't necessary.)

The good solution is to say this:

	\x -> op (y >> return x) :: a -> Bool	
					with constraint C (k a)
		(just as before)

	/\a \x -> op (y>>return x) :: forall a. a -> Bool
					with constraint (forall a. C (k a))

This requires us to permit constraints with for-alls in them.
As luck would have it, Ralf Hinze and I propose just such a thing in
our paper "Derivable Type Classes" (Section 7)
http://research.microsoft.com/~simonpj/#derive

The motivation there is this: how can you write an equality instance for

	data T k a = MkT (k (T k a))

We can try:

	instance ... => Eq (T k a) where
	  (MkT a) == (MkT b) = a == b

But what is the "..."?  We need that "k" is an equality type
constructor.  The right context is

	instance (forall a. Eq a => Eq (k a)) => Eq (T k a) where
	  ...as before...

Aha!  A constraint with a for-all.

There are some more details in the paper.

So perhaps there's a reason for adding this extension in the implementation
(to solve Zhanyong's problem) even for a Haskell 98 compiler.

Simon


From francois.xavier.bodin@winealley.com Wed Dec 6 19:52:00 2000 Date: Wed, 6 Dec 2000 20:52 +0100 From: francois.xavier.bodin@winealley.com francois.xavier.bodin@winealley.com Subject: Meet us on Wine Alley
Hello!

I found your address on a site about wine, food and good living. I thought =
that you will be interested by the services that our site offers.

www.wine-alley.com is a virtual Club for all those interested in wine in bo=
th a professional and personal capacity.

We now have more than 3900 members, both amateur and in the trade who use o=
ur site to discuss wine, buy and sell it and tell us about the best sources.

Club members use the Newsgroup of www.wine-alley.com to exchange informatio=
n and experiences.  Only the other day someone asked how much a certain rar=
e wine was worth, I asked for more information about the grape variety, whi=
ch doesn't grow in France. Currently there have been more than 717 question=
s and replies.

There is also the small ads. column.

Among the 7 adverts placed this week there have been some really good deals=
 including a magnum of 1945 Pichon Lalande and a 1947 Cheval blanc!

Let me make it clear - www.wine-alley.com itself does not sell or buy wine:=
 we simply offer our members the facilites for making their own arrangement=
s.

www.wine-alley.com is also a site supplying information in real time, parti=
cularly the latest news from winegrowers and makers via the French Press Ag=
ency (AFP).  We also have a database of more than 21,000 wines with informa=
tion supplied directly to the site by winegrowers co-operatives and special=
ist magazines.

I should be delighted if you would come and join us.  At www.wine-alley.com=
 you will find similarly-minded people who just want to share their love of=
 wine.

Kind regards

Fran=E7ois Xavier Bodin, Manager of the Online Club
fx.bodin@winealley.com



PS.  Registering with the www.wine-alley.com club is absolutely free and co=
mmits you to nothing.

If you are not interested in my offer, please excuse this letter; I am sorr=
y to have bothered you.  To prevent further unwanted intrusions please clic=
k on the following link, your email will be automatically removed from our =
list.

http://www.wine-alley.com/wines/desmail.asp?id=3D307392&l=3Duk


From harald@cs.mu.OZ.AU Mon Dec 11 13:13:58 2000 Date: Tue, 12 Dec 2000 00:13:58 +1100 From: Harald Sondergaard harald@cs.mu.OZ.AU Subject: PPDP 2001: Call for Papers
                   Third International Conference on

          PRINCIPLES AND PRACTICE OF DECLARATIVE PROGRAMMING

                  Firenze, Italy, 5-7 September 2001


                           CALL FOR PAPERS


PPDP 2001 aims to stimulate research on the use of declarative methods
in programming  and on the design,  implementation  and application of
programming languages  that support such methods.   Topics of interest
include any aspect related to understanding, integrating and extending
programming paradigms such as those for functional, logic,  constraint
and  object-oriented  programming;  concurrent extensions  and  mobile
computing; type theory; support for modularity; use of logical methods
in the design of  program  development  tools;  program  analysis  and
verification;  abstract interpretation;  development of implementation
methods;  application of the relevant paradigms and associated methods
in industry and education.   This list is not exhaustive:  submissions
describing new and interesting ideas  relating broadly to  declarative
programming are encouraged.   The technical program  of the conference
will combine presentations  of the accepted papers  with invited talks
and advanced tutorials.

PPDP 2001  is part of a federation of colloquia  known as  Principles,
Logics  and  Implementations  of  high-level   programming   languages
(PLI 2001) which includes the ACM SIGPLAN International Conference on
Functional Programming (ICFP 2001).  The colloquia will run from 2 to
8 September, 2001. The venue for the conference is Firenze (Florence),
one  of  Europe's  most  attractive  cities,  famous for its churches,
galleries and museums.

For more details, see the conference web site.

Important Dates:
   Submission     15 March 2001
   Notification    7 May   2001
   Final Version  11 June  2001

Affiliated Workshops:
   Proposals are being solicited for PLI 2001 affiliated workshops.
   Details about the submission of proposals are available at
   http://music.dsi.unifi.it/pli01/wkshops.

Web Sites and Email Contact:
   PPDP 2001: http://music.dsi.unifi.it/pli01/ppdp
   PLI 2001:  http://music.dsi.unifi.it/pli01
   mailto:ppdp01@cs.mu.oz.au

Conference Chair:
   Rocco De Nicola, Universita di Firenze
   http://www.dsi.unifi.it/~denicola/
   mailto:denicola@dsi.unifi.it

Program Chair:
   Harald Sondergaard, The University of Melbourne
   http://www.cs.mu.oz.au/~harald/
   mailto:harald@cs.mu.oz.au

Program Committee:
   Maria Alpuente, Univ. Politecnica de Valencia, ES
   Yves Caseau, Bouygues, FR
   Michael Codish, Ben-Gurion Univ. of the Negev, IL
   Saumya Debray, Univ. of Arizona, US
   Conal Elliott, Microsoft Research, US
   Sandro Etalle, Univ. Maastricht, NL
   Roberto Giacobazzi, Univ. di Verona, IT
   Michael Leuschel, Univ. of Southampton, GB
   John Lloyd, Australian National Univ., AU
   Torben Mogensen, Kobenhavns Univ., DK
   Alan Mycroft, Cambridge Univ., GB
   Gopalan Nadathur, Univ. of Minnesota, US
   Martin Odersky, Ecole Polyt. Fed. Lausanne, CH
   Catuscia Palamidessi, Penn State Univ., US
   Andreas Podelski, Max-Planck-Inst. Informatik, DE
   Kostis Sagonas, Uppsala Univ., SE
   Christian Schulte, Univ. des Saarlandes, DE
   Michael Schwartzbach, Aarhus Univ., DK
   Harald Sondergaard, Univ. of Melbourne, AU
   Peter J. Stuckey, Univ. of Melbourne, AU 



From venneri@dsi.unifi.it Wed Dec 13 20:06:41 2000 Date: Wed, 13 Dec 2000 16:06:41 -0400 From: b.venneri venneri@dsi.unifi.it Subject: PLI 2001: call for workshop proposals
                    CALL FOR WORKSHOP PROPOSALS
               Principles, Logics and Implementations
            of high-level programming languages (PLI 2001)
			 Firenze, Italy

                      	September 3 - 7, 2001
               	http://music.dsi.unifi.it/pli01




PLI 2001, a federation of colloquia which includes ICFP 2001 (ACM-SIGPLAN
International Conference on Functional Programming) and PPDP 2001
(ACM-SIGPLAN International Conference on Principles and Practice of
Declarative Programming), will be held in Firenze, Italy, September 3-7 2001.
Workshops affiliated to PLI 2001 will be held before, after or
in parallel with the main conferences.
Researchers and practitioners are invited to submit workshop proposals,
that should be sent to the PLI 2001 Workshop Chair
Betti Venneri mailto:venneri@dsi.unifi.it
with "PLI01 Workshop Submission" in the subject header.


Proposals should include
* a short scientific justification of the proposed topic
(somehow related to the colloquia),
* names and contact information of the organizers,
* expected number of participants and duration
(the preference is for one day-long workshops),
* estimated dates for paper submissions, notification of acceptance and
final versions and any other relevant information (e.g., invited speakers,
publication policy, etc.).


THE DEADLINE FOR RECEIPT OF PROPOSALS IS JANUARY 8, 2001.
Proposals will be evaluated by the PLI 2001 Workshop Chair, the ICFP and
PPDP Program Chairs and Conference Chairs.
Notification of acceptance will be made by February 2, 2001.

The titles and brief information related to accepted workshop proposals
will be included in the conference program and advertised in the call for
participation. Workshop organizers will be responsible for producing a Call
for papers and a Web site, for reviewing and making acceptance decisions on
submitted papers, and for scheduling workshop activities in consultation
with the local organizers.

Workshop selection committee:
Xavier Leroy (INRIA, France), ICFP 2001 Program Chair
Benjamin C. Pierce (Univ. of Pennsylvania), ICFP 2001 Conference Chair
Harald Sondergaard (Univ. of Melbourne), PPDP 2001 Program Chair
Rocco De Nicola (Univ. of Firenze), PPDP 2001 Conference Chair
Betti Venneri (Univ. of Firenze), PLI 2001 Workshop Chair.


we




From shlomif@vipe.technion.ac.il Fri Dec 15 19:47:27 2000 Date: Fri, 15 Dec 2000 21:47:27 +0200 (IST) From: Shlomi Fish shlomif@vipe.technion.ac.il Subject: Finding primes using a primes map with Haskell and Hugs98
Hi!

As some of you may know, a Haskell program that prints all the primes can be 
as short as the following:

primes = sieve [2.. ] where
         sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]

Now, this program roughly corresponds to the following perl program:

###### SNIP SNIP #####
#!/usr/bin/perl

use strict;

my (@primes, $a, $p);
@primes = (2);
MAIN_LOOP: 
for($a = 3; $a < 1000; $a++)
{
    foreach $p (@primes)
    {
        if ($a % $p == 0)
        {
            next MAIN_LOOP;
        }
    }
    push @primes, $a;
}
print join(", ", @primes);
####### SNIP SNIP #####

The program can be more optimized for both speed and code size, but I wanted
to make it as verbose as possible.

The algorithm keeps a list of the primes, and for each new number checks if it
is divisable by any of them and if not it adds it to the list.

There is a different algorithm which keeps a boolean map which tells whether
the number at that position is prime or not. At start it is initialized to all
trues. The algorithm iterates over all the numbers from 2 to the square root
of the desired bound, and if it encounters a prime number it marks all the
numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally
considered a better algorithm than the previous one, because it uses less
costier operations (multiplications and additions instead of modulos.)

The perl program that implements that algorithm is this:

#### SNIP SNIP #####
#!/usr/bin/perl

use strict;

sub primes
{
    my $how_much = shift;

    my (@array, $bound, $a, $b, @primes);

    @array = (1) x $how_much;

    $bound = int(sqrt($how_much))+1;

    for($a=2;$a<=$bound;$a++)
    {
        if ($array[$a])
        {
            for($b=$a*$a;$b<$how_much;$b+=$a)
            {
                $array[$b] = 0;
            }
            push @primes, $a;
        }
    }
    for(;$a<$how_much;$a++)
    {
        if ($array[$a])
        {
            push @primes, $a;
        }
    }

    return @primes;
}

print join(", ", primes(1000));
##### SNIP SNIP ######

Now, I tried writing an equivalent Haskell program and the best I could do was
the following:

---- SNIP SNIP -----
module Primes where

import Prelude
import Array

how_much :: Int
how_much = 1000 

initial_primes_map :: Array Int Bool 
initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ]

mybound :: Int
mybound = ceiling(sqrt(fromInteger(toInteger(how_much))))

next_primes_map :: Int -> Array Int Bool -> Array Int Bool
next_primes_map a primes_map = 
    if (a == mybound) 
    then primes_map 
    else next_primes_map (a+1) (
        if primes_map!a
        then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ]
        else primes_map
        )
    
prime_bound :: Int -> Int
prime_bound a = (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a))))

get_primes_map :: Array Int Bool
get_primes_map = (next_primes_map 2 initial_primes_map)

list_primes :: Array Int Bool -> Int -> [Int]
list_primes primes_map n = 
    if (n > how_much) 
    then [] 
    else 
    (
        if primes_map!n 
        then n:(list_primes primes_map (n+1)) 
        else list_primes primes_map (n+1)
    )

show_primes = show (list_primes get_primes_map 2)
---- SNIP SNIP -----


The problem is that when running it on hugs98 on a Windows98 computer with
64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When
entering how_much as 50,000 I get the following message:

ERROR: Garbage collection fails to reclaim sufficient space

In perl I can scale beyond 100,000, and if I modify the code to use a bit
vector (using vec) to much more. So my question is what am I or hugs are doing
wrong and how I can write better code that implements this specific algorithm.

>From what I saw I used tail recursion, (and hugs98 has proper tail recursion,
right?), and there's only one primes_map present at each iteration (and thus,
at all), so it shouldn't be too problematic. Does it have to do with the way
hugs98 implements and Int to Bool array?

Regards,

    Shlomi Fish

----------------------------------------------------------------------
Shlomi Fish        shlomif@vipe.technion.ac.il 
Home Page:         http://t2.technion.ac.il/~shlomif/
Home E-mail:       shlomif@techie.com

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.



From jenglish@flightlab.com Sat Dec 16 23:21:48 2000 Date: Sat, 16 Dec 2000 15:21:48 -0800 From: Joe English jenglish@flightlab.com Subject: Finding primes using a primes map with Haskell and Hugs98
Shlomi Fish wrote:

> As some of you may know, a Haskell program that prints all the primes can be
> as short as the following:
>
> primes = sieve [2.. ] where
>          sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]
>
> Now, this program roughly corresponds to the following perl program:

[ ~20 line Perl program snipped ]

> The program can be more optimized for both speed and code size, but I wanted
> to make it as verbose as possible.
>
> There is a different algorithm which keeps a boolean map [...]
> The algorithm iterates over all the numbers from 2 to the square root
> of the desired bound, and if it encounters a prime number it marks all the
> numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime.

[~40 line Perl implementation snipped]

> Now, I tried writing an equivalent Haskell program and the best I
> could do was the following:

[ ~45 line Haskell implementation snipped ]

Another way to do this is to compute the final array directly,
instead of computing successive versions of the array:

    import Array
    primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
	primesMap   = accumArray (||) False (2,n) multList
	multList    = [(m,True) | j <- [2 .. n `div` 2], m <- multiples j]
	multiples j = takeWhile (n>=) [k*j | k <- [2..]]

Now this version does a lot more work than the algorithm
described above -- it computes multiples of *all* the integers
less than n/2, not just the primes less than sqrt(n) -- but
it has the virtue of being short enough to reason about effectively
and is probably a better starting point for further optimization.

> The problem is that when running it on hugs98 on a Windows98 computer with
> 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When
> entering how_much as 50,000 I get the following message:
>
> ERROR: Garbage collection fails to reclaim sufficient space

My implementation fares even worse under Hugs -- it runs out
of space around n = 4500 (Linux box, 64M RAM).  With GHC
it has no problem for n = 100,000, although the space usage
is still extremely poor.  It grows to consume all
available RAM at around n = 200,000.  (On the other hand,
it's considerably faster than the traditional 2-liner
listed above, up to the point where it starts paging).

I suspect the poor memory usage is due to the way accumArray
works -- it's building up a huge array of suspensions of the form

	(False && (False && ( ... && True)))

that aren't reduced until an array element is requested.

(A strict version of accumArray, analogous to "foldl_strict"
defined below, would solve this problem, but I don't
see any way to implement it in Standard Haskell).

> In perl I can scale beyond 100,000, and if I modify the code to use a bit
> vector (using vec) to much more. So my question is what am I or hugs are
> doing wrong and how I can write better code that implements this specific
> algorithm.
>
> From what I saw I used tail recursion, (and hugs98 has proper tail recursion
> right?), and there's only one primes_map present at each iteration (and thus,
> at all), so it shouldn't be too problematic.

Actually no; this is a common misconception.  In a strict
language like Scheme, tail call optimization works because
a tail call is the last thing a function does.  In Haskell
though the tail call is the *first* thing that gets evaluated
(more or less), leaving all the "earlier" work as an unevaluated
suspension.  Code that is space-efficient in a strict language
frequently suffers from awful space leaks in a lazy language.
For example:

sum_first_n_integers n = f n 0 where
	f 0 a = a
	f n a = f (n-1) (n+a)

quickly leads to a "Control Stack Overflow" error in Hugs.
BTW, the trick to fix it is to change the last line to:

	f n acc = f (n-1) $! (n+acc)

or to replace the whole thing with:

    foldl_strict (+) 0 [1..n]

where

    foldl_strict f a []     = a
    foldl_strict f a (x:xs) = (foldl_strict f $! f a x) xs


> Does it have to do with the way hugs98 implements and Int to Bool array?

Most likely yes.  Hugs is optimized for interactive use and quick
compilation, not for space usage.  Try it with GHC or HBC and
see how it does.


--Joe English

  jenglish@flightlab.com


From ahey@iee.org Sun Dec 17 11:59:43 2000 Date: Sun, 17 Dec 2000 11:59:43 +0000 (GMT) From: Adrian Hey ahey@iee.org Subject: Finding primes using a primes map with Haskell and Hugs98
On Fri 15 Dec, Shlomi Fish wrote:
> There is a different algorithm which keeps a boolean map which tells whether
> the number at that position is prime or not. At start it is initialized to all
> trues. The algorithm iterates over all the numbers from 2 to the square root
> of the desired bound, and if it encounters a prime number it marks all the
> numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally
> considered a better algorithm than the previous one, because it uses less
> costier operations (multiplications and additions instead of modulos.)

Functional programming languages are notoriously ineffecient at array
handling (though I'm not sure exactly what the various Haskell
implementations actually do).

You can use a variation of this algorithm with lazy lists..

primes = 2:(get_primes [3,5..])
get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs))

strike step x_now (x:xs) = 
 case (compare x_now x) of
 LT -> strike step (x_now+step) (x:xs)
 EQ -> strike step (x_now+step) xs
 GT -> x:(strike step x_now xs)

The equivalent program in Clean (on a MAC) gets upto 877783 before giving a
stack overflow error (1000K of stack, 4000K of Heap allocated). (I haven't
actually tried this in Haskell 'cos I don't have a Windoze or 'nix box.)

Regards
-- 
Adrian Hey



From qrczak@knm.org.pl Sun Dec 17 19:29:32 2000 Date: 17 Dec 2000 19:29:32 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Problem with functional dependencies
The following module is rejected by both
    ghc -fglasgow-exts -fallow-undecidable-instances
and
    hugs -98

------------------------------------------------------------------------
class HasFoo a foo | a -> foo where
    foo :: a -> foo

data A = A Int
data B = B A

instance HasFoo A Int where
    foo (A x) = x

instance HasFoo A foo => HasFoo B foo where
    foo (B a) = foo a
------------------------------------------------------------------------

The error messsage says that the type inferred for foo in B's instance
is not general enough: the rhs has type "HasFoo B Int => B -> Int", but
"HasFoo B foo => B -> foo" was expected.

Should it really be wrong? I don't know the details of type inference
with fundeps, but intuitively it should work, yielding an instance
HasFoo B Int. Could it be made legal please?

With the fundep removed, it works.

I need it for a preprocessor which generates instances like that for B
without knowing the type to put as the second class argument. Fundeps
aren't essential, but...

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From elke.kasimir@catmint.de Sun Dec 17 18:56:46 2000 Date: Sun, 17 Dec 2000 19:56:46 +0100 (CET) From: Elke Kasimir elke.kasimir@catmint.de Subject: Finding primes using a primes map with Haskell and Hugs98
This message is in MIME format
--_=XFMail.1.3.p0.Linux:001217195636:327=_
Content-Type: text/plain; charset=iso-8859-1

Your algorithm seems to be based on the following idea: 
calculate the non-primes and derive the primes from 
them by calculating the set difference of the natural numbers 
and the non-primes.

A naive implementation of this idea can be found as 

primes' 

in the attachached file. The function uses no multiplication 
or division and though performs 6 times worse than the sieve
in calculating the first 30000 primes.

The complexity for finding the next i'th prime with this naive
implementation is about O(i). In comparison to this, the sieve 
provides a good optimization because only those natural numbers 
are tested against the i'th prime which have run through all other
sieves.

Nevertheless, your algorithm is promising when the non-primes are 
merged efficiently enough into a single sorted list which can be easily
subtracted from the natural numbers.

I think the deployment of an array is basically a way to efficiently merge the 
multiples of the primaries into a sorted list (where even duplicates 
are removed), thus hoping to reduce the number of  the operations better 
than the optimization that is provided by the sieve.

However, to use arrays this way, you probably need destructive array updates, 
because the array must be incrementally updated when new primes are
found. I think that standard haskell arrays don't do the job very well. 

An implementation of the "merging" idea in Haskell is

primes''

in the attached file. It is 15% faster then the  sieve in calculating the 30000 
first primes.

The algorithm is realized as two mutually recursive functions 
noprimes and primes'', the latter  calculating the set difference between 
the non-primes  and the natural numbers, the former merging
the all multiples of all primes into a sorted list. It should be possible 
to substantially optimize the merging operation.

primes'''

is an efficient variant of primes'. Instead of a list it uses a binary tree 
for the management of the lists of multiples of the already found
primes, and thus requires some additional programming effort.

The complexity is reduced from O(i) to something
like O(Log(i)).

Compared with the sieve, primes''' needs only half 
the time to calculate the first 30000 primes.

(Tests with ghc 4.08, 64m heap)

Best,
Elke.


On 15-Dec-00 Shlomi Fish wrote:
> 
> Hi!
> 
> As some of you may know, a Haskell program that prints all the primes can be 
> as short as the following:
> 
> primes = sieve [2.. ] where
>          sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]
> 
> Now, this program roughly corresponds to the following perl program:
> 
>###### SNIP SNIP #####
>#!/usr/bin/perl
> 
> use strict;
> 
> my (@primes, $a, $p);
> @primes = (2);
> MAIN_LOOP: 
> for($a = 3; $a < 1000; $a++)
> {
>     foreach $p (@primes)
>     {
>         if ($a % $p == 0)
>         {
>             next MAIN_LOOP;
>         }
>     }
>     push @primes, $a;
> }
> print join(", ", @primes);
>####### SNIP SNIP #####
> 
> The program can be more optimized for both speed and code size, but I wanted
> to make it as verbose as possible.
> 
> The algorithm keeps a list of the primes, and for each new number checks if
> it
> is divisable by any of them and if not it adds it to the list.
> 
> There is a different algorithm which keeps a boolean map which tells whether
> the number at that position is prime or not. At start it is initialized to
> all
> trues. The algorithm iterates over all the numbers from 2 to the square root
> of the desired bound, and if it encounters a prime number it marks all the
> numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally
> considered a better algorithm than the previous one, because it uses less
> costier operations (multiplications and additions instead of modulos.)
> 
> The perl program that implements that algorithm is this:
> 
>#### SNIP SNIP #####
>#!/usr/bin/perl
> 
> use strict;
> 
> sub primes
> {
>     my $how_much = shift;
> 
>     my (@array, $bound, $a, $b, @primes);
> 
>     @array = (1) x $how_much;
> 
>     $bound = int(sqrt($how_much))+1;
> 
>     for($a=2;$a<=$bound;$a++)
>     {
>         if ($array[$a])
>         {
>             for($b=$a*$a;$b<$how_much;$b+=$a)
>             {
>                 $array[$b] = 0;
>             }
>             push @primes, $a;
>         }
>     }
>     for(;$a<$how_much;$a++)
>     {
>         if ($array[$a])
>         {
>             push @primes, $a;
>         }
>     }
> 
>     return @primes;
> }
> 
> print join(", ", primes(1000));
>##### SNIP SNIP ######
> 
> Now, I tried writing an equivalent Haskell program and the best I could do
> was
> the following:
> 
> ---- SNIP SNIP -----
> module Primes where
> 
> import Prelude
> import Array
> 
> how_much :: Int
> how_much = 1000 
> 
> initial_primes_map :: Array Int Bool 
> initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ]
> 
> mybound :: Int
> mybound = ceiling(sqrt(fromInteger(toInteger(how_much))))
> 
> next_primes_map :: Int -> Array Int Bool -> Array Int Bool
> next_primes_map a primes_map = 
>     if (a == mybound) 
>     then primes_map 
>     else next_primes_map (a+1) (
>         if primes_map!a
>         then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ]
>         else primes_map
>         )
>     
> prime_bound :: Int -> Int
> prime_bound a =
> (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a))))
> 
> get_primes_map :: Array Int Bool
> get_primes_map = (next_primes_map 2 initial_primes_map)
> 
> list_primes :: Array Int Bool -> Int -> [Int]
> list_primes primes_map n = 
>     if (n > how_much) 
>     then [] 
>     else 
>     (
>         if primes_map!n 
>         then n:(list_primes primes_map (n+1)) 
>         else list_primes primes_map (n+1)
>     )
> 
> show_primes = show (list_primes get_primes_map 2)
> ---- SNIP SNIP -----
> 
> 
> The problem is that when running it on hugs98 on a Windows98 computer with
> 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When
> entering how_much as 50,000 I get the following message:
> 
> ERROR: Garbage collection fails to reclaim sufficient space
> 
> In perl I can scale beyond 100,000, and if I modify the code to use a bit
> vector (using vec) to much more. So my question is what am I or hugs are
> doing
> wrong and how I can write better code that implements this specific
> algorithm.
> 
>>From what I saw I used tail recursion, (and hugs98 has proper tail recursion,
> right?), and there's only one primes_map present at each iteration (and thus,
> at all), so it shouldn't be too problematic. Does it have to do with the way
> hugs98 implements and Int to Bool array?
> 
> Regards,
> 
>     Shlomi Fish
> 
> ----------------------------------------------------------------------
> Shlomi Fish        shlomif@vipe.technion.ac.il 
> Home Page:         http://t2.technion.ac.il/~shlomif/
> Home E-mail:       shlomif@techie.com
> 
> The prefix "God Said" has the extraordinary logical property of 
> converting any statement that follows it into a true one.
> 
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell

---
Elke Kasimir
Skalitzer Str. 79
10997 Berlin (Germany)
fon:  +49 (030) 612 852 16
mail: elke.kasimir@catmint.de>  
see: <http://www.catmint.de/elke>

for pgp public key see:
<http://www.catmint.de/elke/pgp_signature.html>

--_=XFMail.1.3.p0.Linux:001217195636:327=_
Content-Disposition: attachment; filename="Primes.hs"
Content-Transfer-Encoding: base64
Content-Description: Primes.hs
Content-Type: application/octet-stream; name=Primes.hs; SizeOnDisk=3056

bW9kdWxlIFByaW1lcwp3aGVyZQoKaW1wb3J0IExpc3QKCi0tIDEuIHZlcnNpb24sIHNpZXZlCgpw
cmltZXMgCiAgICA9IHNpZXZlIFsyLi5dIAogICAgICAgd2hlcmUgc2lldmUgKHg6eHMpID0geCA6
IHNpZXZlIFsgbiB8IG4gPC0geHMgLCBuIGBtb2RgIHggPiAwIF0gCgoKLS0gMi4gdmVyc2lvbjog
a2VlcCBhbiAidXB0by1kYXRlIiBsaXN0IG9mIHRoZSBub24tcHJpbWVzIAotLSAgICAgICAgICAg
ICAoYSBmaW5pdGUgbGlzdCBvZiBpbmlmaW5pdGUgbGlzdHMpCi0tICAgICAgICAgICAgIGFuZCBj
YWxjdWxhdGUgdGhlIHByaW1lcyBmcm9tIHRoZW0uCgpwcmltZXMnCiAgICA9IG1rUHJpbWVzIFtd
IFsyLi5dIAogICAgICB3aGVyZQogICAgICAgbWtQcmltZXMgbm9uX3ByaW1lcyAoeDp4cykgCgkg
ICB8IG51bGwgd2l0aFggPSB4IDogbWtQcmltZXMgKG11bHQgeCA6IG5vbl9wcmltZXMpICAgICAg
ICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChtYXAgdGFpbCB3aXRoWCArKyB3
aXRob3V0WCkgeHMKCSAgIHdoZXJlCgkgICAod2l0aFgsd2l0aG91dFgpID0gcGFydGl0aW9uICgo
PT14KS4gaGVhZCkgbm9uX3ByaW1lcwoJICAgbXVsdCB4ICAgICAgICAgICA9IGl0ZXJhdGUgKCt4
KSAoeCt4KQoKCi0tIDMuIHZlcnNpb246IHByaW1lcyBhbmQgbm9uLXByaW1lcyBhcmUgbXV0dWFs
bHkgcmVjdXJzaXZlLgoKcHJpbWVzJycKICAgID0gMiA6IGRpZmYgWzMuLl0gbm9uX3ByaW1lcwoK
bm9uX3ByaW1lcyAKICAgID0gbWVyZ2UgKG1hcCBtdWx0IHByaW1lcycnKSAKICAgICAgd2hlcmUg
CiAgICAgIG11bHQgeCAgID0gaXRlcmF0ZSAoK3gpICh4K3gpICAgICAgCgptZXJnZSAoKHg6eHMp
OnJlc3QpCiAgICA9IHggOiBtZXJnZSAocmVhcnJhbmdlICh4czpyZXN0KSkKCnJlYXJyYW5nZSBs
QCh4bEAoeDp4cyk6KHk6eXMpOnJlc3QpIAogICAgfCB4IDw9IHkgICAgID0gbAogICAgfCBvdGhl
cndpc2UgID0gKHk6eGwpIDogcmVhcnJhbmdlICh5czpyZXN0KSAKCi0tIHNldCBkaWZmZXJlbmNl
IGZvciBvcmRlcmVkIGxpc3RzIC0gcmVzdWx0IGlzIGFsc28gb3JkZXJlZDoKZGlmZiA6OiBPcmQg
YSA9PiBbYV0gLT4gW2FdIC0+IFthXQpkaWZmIHhsQCh4OnhzKSB5bEAoeTp5cykgCiAgICB8IHgg
PCAgeSA9IHggOiBkaWZmIHhzIHlsCiAgICB8IHggPT0geSA9ICAgICBkaWZmIHhzIHlsCiAgICB8
IHggPiAgeSA9ICAgICBkaWZmIHhsIHlzCgoKLS0gNC4gdmVyc2lvbiwgbGlrZSAyLiwgYnV0IHVz
ZXMgYSB0cmVlIHRvIG1hbmFnZSBub24tcHJpbXNlOgoKcHJpbWVzJycnCiAgICA9IG1rUHJpbWVz
IEwgWzIuLl0gCiAgICAgIHdoZXJlCiAgICAgICBta1ByaW1lcyBub25fcHJpbWVzICh4OnhzKSAK
CSAgIHwgbnVsbCB3aXRoWCA9IHggOiBta1ByaW1lcyAodGluc2VydCAobXVsdCB4KSBub25fcHJp
bWVzKSAgICAgICAgICAgICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChmb2xk
ciB0aW5zZXJ0IHdpdGhvdXRYIChtYXAgdGFpbCB3aXRoWCkpIHhzCgkgICB3aGVyZQoJICAgKHdp
dGhYLHdpdGhvdXRYKSA9IHRwYXJ0aXRpb24gW3hdIG5vbl9wcmltZXMgCgkgICBtdWx0IHggICAg
ICAgICAgID0gaXRlcmF0ZSAoK3gpICh4K3gpCgotLSBhIGJpbmFyeSB0cmVlOgoKZGF0YSBUcmVl
ID0gTiBbSW50ZWdlcl0gVHJlZSBUcmVlIHwgTCBkZXJpdmluZyBTaG93CgotLSBydWxlcyBmb3Ig
cGxhY2luZyBpbnRlZ2VyIGxpc3RzOgoKbGVmdG9mLCByaWdodG9mIDo6IFtJbnRlZ2VyXSAtPiBU
cmVlIC0+IEJvb2wKCmxlZnRvZiAgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA8PSB5CnJpZ2h0
b2YgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA+IHkKCi0tIHJ1bGUgZm9yIG1hdGNoaW5nIGlu
dGVnZXIgbGlzdHM6CgptYXRjaGVzIDo6IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IEJvb2wKbWF0Y2hl
cyAoeDp4cykgKE4gKHk6eXMpIF8gXykgPSB4ID09IHkKCi0tIGluc2VydGlvbjoKCnRpbnNlcnQg
OjogW0ludGVnZXJdIC0+IFRyZWUgLT4gVHJlZQp0aW5zZXJ0IHhsICAgTCA9IE4geGwgTCBMCnRp
bnNlcnQgeGwgdEAoTiB5bCB0MSB0MikgCiAgICB8IHhsIGBsZWZ0b2ZgICB0ID0gTiB5bCAodGlu
c2VydCB4bCB0MSkgdDIKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgPSBOIHlsIHQxICh0aW5zZXJ0IHhs
IHQyKQoKLS0gZXh0cmFjdGlvbiAmIHJlbW92YWwgaW4gb25lIHN0ZXA6Cgp0cGFydGl0aW9uIDo6
IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IChbW0ludGVnZXJdXSxUcmVlKQp0cGFydGl0aW9uIHhsIEwg
PSAoW10sTCkKdHBhcnRpdGlvbiB4bCB0QChOIHlsIHQxIHQyKSAKICAgIHwgeGwgYG1hdGNoZXNg
IHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24nIHhsIHQxIGluICh5bDphLCByZW1vdmUgYiB0
MikKICAgIHwgeGwgYGxlZnRvZmAgIHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24geGwgdDEg
aW4gKGEsIE4geWwgYiB0MikKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgID0gIGxldCAoYSxiKSA9IHRw
YXJ0aXRpb24geGwgdDIgaW4gKGEsIE4geWwgdDEgYikKCnRwYXJ0aXRpb24nIHhsIEwgPSAoW10s
TCkgICAgICAtLSBjaGVjayBmb3IgbW9yZSBtYXRjaGVzCnRwYXJ0aXRpb24nIHhsIHRAKE4geWwg
dDEgdDIpIAogICAgfCB4bCBgbWF0Y2hlc2AgdCAgPSAgbGV0IChhLGIpID0gdHBhcnRpdGlvbicg
eGwgdDEgaW4gKHlsOmEsIHJlbW92ZSBiIHQyKQogICAgfCBvdGhlcndpc2UgICAgICAgPSAoW10s
dCkKCnJlbW92ZSBMICB0MiAgPSB0MgpyZW1vdmUgdDEgdDIgPSBsZXQgKGEsYikgPSByaWdodG1v
c3QgdDEgaW4gTiBhIGIgdDIKCnJpZ2h0bW9zdCAoTiB5bCB0MSAgTCkgPSAoeWwsdDEpCnJpZ2h0
bW9zdCAoTiB5bCB0MSB0MikgPSBsZXQgKGEsYik9cmlnaHRtb3N0IHQyIGluIChhLCBOIHlsIHQx
IGIpCiAgCgotLSB0ZXN0IGNvcnJlY3RuZXNzCgpwZGlmZiA9IFsgKGEsYixjLGQpIHwgCgkgKGEs
YixjLGQpPC16aXA0IHByaW1lcyBwcmltZXMnIHByaW1lcycnIHByaW1lcycnJywgCgkgYSAvPSBi
IHx8IGIgLz0gYyB8fCBjIC89IGQgCgkgXQoKCgoKCgoKCgo=

--_=XFMail.1.3.p0.Linux:001217195636:327=_--
End of MIME message


From ahey@iee.org Mon Dec 18 00:24:12 2000 Date: Mon, 18 Dec 2000 00:24:12 +0000 (GMT) From: Adrian Hey ahey@iee.org Subject: Finding primes using a primes map with Haskell and Hugs98
On Sun 17 Dec, Adrian Hey wrote:
> You can use a variation of this algorithm with lazy lists..
>
> primes = 2:(get_primes [3,5..])
> get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs))
                                                   ^^^
Whoops,_____________________________________________|

32 bit Ints may cause trouble here :-)

Regards
-- 
Adrian Hey



From Xavier.Leroy@inria.fr Mon Dec 18 09:30:07 2000 Date: Mon, 18 Dec 2000 10:30:07 +0100 From: Xavier Leroy Xavier.Leroy@inria.fr Subject: call for papers ICFP 2001
                         ICFP 2001: Call for Papers

       ICFP 2001: International Conference on Functional Programming
                Firenze (Florence), Italy; 3-5 September 2001
         associated with PLI 2001: Colloquium on Principles, Logics,
          and Implementations of High-Level Programming Languages

Important dates:

      Submission deadline                     15 March 2001, 18:00 UTC
      Notification of acceptance or rejection 11 May 2001
      Final paper due                         29 June 2001
      Conference                              3-5 September 2001

Scope:

ICFP 2001 seeks original papers on the full spectrum of the art, science,
and practice of functional programming. The conference invites submissions
on all topics ranging from principles to practice, from foundations to
features, and from abstraction to application. The scope covers all
languages that encourage programming with functions, including both purely
applicative and imperative languages, as well as languages that support
objects and concurrency. Papers setting new directions in functional
programming, or describing novel or exemplary applications of functional
programming, are particularly encouraged. Topics of interest include, but
are not limited to, the following:

   * Foundations: formal semantics, lambda calculus, type theory, monads,
     continuations, control, state, effects.
   * Design: modules and type systems, concurrency and distribution,
     components and composition, relations to object-oriented and logic
     programming, multiparadigm programming.
   * Implementation: abstract machines, compile-time and run-time
     optimization, just-in-time compilers, memory management,
     foreign-function and component interfaces.
   * Transformation and Analysis: abstract interpretation, partial
     evaluation, program transformation, theorem proving, specification and
     verification.
   * Applications: scientific and numerical computing, symbolic computing
     and artificial intelligence, systems programming, databases, graphic
     user interfaces, multimedia programming, web programming.
   * Experience: FP in education and industry, ramifications on other
     paradigms and computing disciplines.
   * Functional pearls: elegant, instructive examples of functional
     programming.

Submission guidelines:

Please refer to the submission Web site  http://cristal.inria.fr/ICFP2001/

Program committee:

 General chair                     Program committee
                               
 Benjamin Pierce                   Karl Crary, Carnegie Mellon University
 University of Pennsylvania        Marc Feeley, University of Montréal
                                   Giorgio Ghelli, University of Pisa
 Program chair                     Simon Peyton Jones, Microsoft Research
                                   John Hughes, Chalmers University
 Xavier Leroy                      Naoki Kobayashi, University of Tokyo
 INRIA Rocquencourt                Julia Lawall, DIKU, U. Copenhagen
 Domaine de Voluceau, B.P. 105     Sheng Liang, Stratum8
 78153 Le Chesnay, France          John Reppy, Bell Labs, Lucent Technologies
 E-mail: Xavier.Leroy@inria.fr     Scott Smith, John Hopkins University
 Fax: + 33 - 1 - 39 63 56 84       Carolyn Talcott, Stanford University
 Phone: + 33 - 1 - 39 63 55 61     Kwangkeun Yi, KAIST


From sebastien@posse42.net Tue Dec 19 14:15:16 2000 Date: Tue, 19 Dec 2000 15:15:16 +0100 From: Sebastien Carlier sebastien@posse42.net Subject: Excessive restriction in ghc ?
Hello.

I am getting an error message from ghc 4.08.1 with
the following code:

> class Collection e ce | ce -> e where
>     empty :: ce
>     insert :: e -> ce -> ce
>
> class (Eq e, Collection e ce) => Set e ce where
>     member :: e -> ce -> Bool
>     union :: ce -> ce -> ce

Main.lhs:7:
    Class type variable `e' does not appear in method signature
        union :: {- implicit forall -} ce -> ce -> ce

Since `ce' uniquely determines `e', I would expect the
compiler to assume that `e' appears in the method signature.
Either I am misunderstanding something, or something may be
missing in the compiler around rename/RnSource.lhs:249.

Regards,
Sebastien Carlier




From zhanyong.wan@yale.edu Tue Dec 19 15:43:28 2000 Date: Tue, 19 Dec 2000 10:43:28 -0500 From: Zhanyong Wan zhanyong.wan@yale.edu Subject: Excessive restriction in ghc ?
Hi Sebastien,

Sebastien Carlier wrote:
 
> I am getting an error message from ghc 4.08.1 with
> the following code:
> 
> > class Collection e ce | ce -> e where
> >     empty :: ce
> >     insert :: e -> ce -> ce
> >
> > class (Eq e, Collection e ce) => Set e ce where
> >     member :: e -> ce -> Bool
> >     union :: ce -> ce -> ce
> 
> Main.lhs:7:
>     Class type variable `e' does not appear in method signature
>         union :: {- implicit forall -} ce -> ce -> ce
> 
> Since `ce' uniquely determines `e', I would expect the
> compiler to assume that `e' appears in the method signature.
> Either I am misunderstanding something, or something may be
> missing in the compiler around rename/RnSource.lhs:249.

I encountered the same problem this summer and wrote to Simon PJ and
Jeff Lewis.  Here's Jeff's answer:

> I'm glad to find examples where they are indispensible.  The implementation of
> FDs in GHC is pretty much complete WRT Mark's writeup (but it doesn't complain
> about instances inconsistent with FDs).  I'm using them in a current project,
> but in a fairly conservative manner.  In hugs, I implemented several
> extensions to do with derived instances and superclasses - pretty much
> necessary as you've found.  Unfortunately, in hugs I implemented it in rather
> the wrong way.  Based on dicsussions at the Hugs/GHC meeting w/ Simon, I have
> a cunning plan for finishing the implementation properly in GHC, but just
> haven't had the chance to do it.  What I need to do is write it up, so that
> either Simon or myself can finish the job.

So the short answer to your question is: FD in derived instances is not
implemented in GHC yet.

I'm still eagerly waiting to use this feature in my project.  Jeff,
could you give us an update on the progress?  Thanks!

-- 
# Zhanyong Wan     http://pantheon.yale.edu/~zw23/ ____
# Yale University, Dept of Computer Science       /\___\
# P.O.Box 208285, New Haven, CT 06520-8285        ||___|


From mk167280@zodiac.mimuw.edu.pl Tue Dec 19 15:56:40 2000 Date: Tue, 19 Dec 2000 16:56:40 +0100 From: Marcin Kowalczyk mk167280@zodiac.mimuw.edu.pl Subject: Excessive restriction in ghc ?
On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote:

> > class Collection e ce | ce -> e where
> >     empty :: ce
> >     insert :: e -> ce -> ce
> >
> > class (Eq e, Collection e ce) => Set e ce where

Doesn't adding the fundep to Set's definition as well help?

-- 
Marcin 'Qrczak' Kowalczyk


From zhanyong.wan@yale.edu Tue Dec 19 16:04:31 2000 Date: Tue, 19 Dec 2000 11:04:31 -0500 From: Zhanyong Wan zhanyong.wan@yale.edu Subject: Excessive restriction in ghc ?
Marcin Kowalczyk wrote:
> 
> On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote:
> 
> > > class Collection e ce | ce -> e where
> > >     empty :: ce
> > >     insert :: e -> ce -> ce
> > >
> > > class (Eq e, Collection e ce) => Set e ce where
> 
> Doesn't adding the fundep to Set's definition as well help?

It might help in this particular case, but if we want something like

  class Collection e ce => Foo ce where ...

then your trick does not apply, and I indeed need something like the
above in my project.

-- Zhanyong Wan


From simonpj@microsoft.com Tue Dec 19 14:47:41 2000 Date: Tue, 19 Dec 2000 06:47:41 -0800 From: Simon Peyton-Jones simonpj@microsoft.com Subject: Excessive restriction in ghc ?
Functional dependencies aren't fully implemented in 4.08 I'm afraid,
and won't ever be. It'll be significantly better in 5.0, but we won't
release that for a while yet.  (Unless you care to build from the
CVS tree.)

Simon

| -----Original Message-----
| From: Sebastien Carlier [mailto:sebastien@posse42.net]
| Sent: 19 December 2000 14:15
| To: haskell@haskell.org
| Subject: Excessive restriction in ghc ?
| 
| 
| Hello.
| 
| I am getting an error message from ghc 4.08.1 with
| the following code:
| 
| > class Collection e ce | ce -> e where
| >     empty :: ce
| >     insert :: e -> ce -> ce
| >
| > class (Eq e, Collection e ce) => Set e ce where
| >     member :: e -> ce -> Bool
| >     union :: ce -> ce -> ce
| 
| Main.lhs:7:
|     Class type variable `e' does not appear in method signature
|         union :: {- implicit forall -} ce -> ce -> ce
| 
| Since `ce' uniquely determines `e', I would expect the
| compiler to assume that `e' appears in the method signature.
| Either I am misunderstanding something, or something may be
| missing in the compiler around rename/RnSource.lhs:249.
| 
| Regards,
| Sebastien Carlier
| 
| 
| 
| _______________________________________________
| Haskell mailing list
| Haskell@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell
| 


From simonpj@microsoft.com Tue Dec 19 14:58:41 2000 Date: Tue, 19 Dec 2000 06:58:41 -0800 From: Simon Peyton-Jones simonpj@microsoft.com Subject: Finding primes using a primes map with Haskell and Hugs98
| Another way to do this is to compute the final array directly,
| instead of computing successive versions of the array:
| 
|     import Array
|     primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
| 	primesMap   = accumArray (||) False (2,n) multList
| 	multList    = [(m,True) | j <- [2 .. n `div` 2], m <- 
| multiples j]
| 	multiples j = takeWhile (n>=) [k*j | k <- [2..]]

This style is definitely the way to go.  Haskell does badly
if you update an array one index at a time.  

Remember that arrays can be recursive.  Here's a definition
of Fibonacci for example; you can probably adapt it for primes

fibs :: Int -> Array Int Int
-- If a = fibs n, then a!i is fib(i), for i<=n.
fibs n = a
          where
	 a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <-
[3..n]])
		-- Notice that a is recursive

Simon


From shlomif@vipe.technion.ac.il Wed Dec 20 14:02:23 2000 Date: Wed, 20 Dec 2000 16:02:23 +0200 (IST) From: Shlomi Fish shlomif@vipe.technion.ac.il Subject: Finding primes using a primes map with Haskell and Hugs98
On Tue, 19 Dec 2000, Simon Peyton-Jones wrote:

> | Another way to do this is to compute the final array directly,
> | instead of computing successive versions of the array:
> | 
> |     import Array
> |     primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where
> | 	primesMap   = accumArray (||) False (2,n) multList
> | 	multList    = [(m,True) | j <- [2 .. n `div` 2], m <- 
> | multiples j]
> | 	multiples j = takeWhile (n>=) [k*j | k <- [2..]]
> 
> This style is definitely the way to go.  Haskell does badly
> if you update an array one index at a time.  
> 

Unfortunately, it seems that this style is not the way to go. This program
cannot scale beyond 5000 while my second program scales beyond 30000. I'm
not saying 30000 is a good limit, but 5000 is much worse.

Anyway, somebody who contacted me in private suggested the following
method. It is a similiar algorithm which uses a list instead of an array.


primes :: Int -> [Int]

primes how_much = sieve [2..how_much] where
         sieve (p:x) = 
             p : (if p <= mybound
                 then sieve (remove (p*p) x)
                 else x) where
             remove what (a:as) | what > how_much = (a:as)
                                | a < what = a:(remove what as)
                                | a == what = (remove (what+step) as)
                                | a > what = a:(remove (what+step) as)
             remove what [] = []
             step = (if (p == 2) then p else (2*p)) 
         sieve [] = []
         mybound = ceiling(sqrt(fromIntegral how_much))

I optimized it quite a bit, but the concept remained the same. 

Anyway, this code can scale very well to 100000 and beyond. But it's not
exactly the same algorithm.

I also implemented this algorithm in perl, and I can send it in person if
anybody requests it.

I'll try to see how the two programs run in GHC and HBC.

Regards,

	Shlomi Fish




> Remember that arrays can be recursive.  Here's a definition
> of Fibonacci for example; you can probably adapt it for primes
> 
> fibs :: Int -> Array Int Int
> -- If a = fibs n, then a!i is fib(i), for i<=n.
> fibs n = a
>           where
> 	 a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <-
> [3..n]])
> 		-- Notice that a is recursive
> 
> Simon
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 



----------------------------------------------------------------------
Shlomi Fish        shlomif@vipe.technion.ac.il 
Home Page:         http://t2.technion.ac.il/~shlomif/
Home E-mail:       shlomif@techie.com

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.




From ger@tzi.de Wed Dec 20 14:12:46 2000 Date: Wed, 20 Dec 2000 15:12:46 +0100 From: George Russell ger@tzi.de Subject: Finding primes using a primes map with Haskell and Hugs98
There are numerous ways of optimising sieving for primes, none of which have much
to do with this list.  For example, two suggestions:
(1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise
    sieve separately for this k on higher primes.  (Or you might use products of
    more or less primes, depending on memory and how high you were going.)
(2) use bitwise arithmetic.
If you look in the literature I think you'll find plenty more possibilities.
I don't really see why any of this has anything to do with Haskell though.
When it comes to seriously icky bit-twiddling algorithms I don't think Haskell
has much to offer over C, especially as you'd have to make everything unboxed if
you want comparable speed.


From Colin.Runciman@cs.york.ac.uk Wed Dec 20 14:49:30 2000 Date: Wed, 20 Dec 2000 14:49:30 GMT From: Colin.Runciman@cs.york.ac.uk Colin.Runciman@cs.york.ac.uk Subject: Finding primes using a primes map with Haskell and Hugs98
> There are numerous ways of optimising sieving for primes, none of which
> have much to do with this list.  For example, two suggestions:
> (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise
>     sieve separately for this k on higher primes.  (Or you might use products of
>     more or less primes, depending on memory and how high you were going.)
> ...
> I don't really see why any of this has anything to do with Haskell though.
> When it comes to seriously icky bit-twiddling algorithms I don't think Haskell
> has much to offer over C, especially as you'd have to make everything unboxed if
> you want comparable speed.

Forgive the self-reference, but the following short article is
all about this very topic:

C. Runciman,
Lazy wheel sieves and spirals of primes,
Journal of Functional Programming, v7, n2, pp219--226,
March 1997.



From Dominic.J.Steinitz@BritishAirways.com Wed Dec 20 16:12:16 2000 Date: 20 Dec 2000 16:12:16 Z From: Steinitz, Dominic J Dominic.J.Steinitz@BritishAirways.com Subject: Haskell Productivity
The Haskell website claims that

"Ericsson measured an improvement factor of between 9 and 25 in one set of experiments on telephony software".

Presumably this is with Erlang not with Haskell. I have searched for the reference that substantiates this claim but I've only been able to find:

http://set.gmd.de/~ap/femsys/wiger.html 

which talks about a productivity factor of 4

and

http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haskell-vs-ada-abstract.html

which suggests that Haskell is about 2-3 times as productive as imperative languages.

Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25?

Thanks, Dominic.

-------------------------------------------------------------------------------------------------
21st century air travel     http://www.britishairways.com


From simonpj@microsoft.com Wed Dec 20 11:11:44 2000 Date: Wed, 20 Dec 2000 03:11:44 -0800 From: Simon Peyton-Jones simonpj@microsoft.com Subject: Problem with functional dependencies
I think you can simplify the example.  Given

	class HasFoo a b | a -> b where
	  foo :: a -> b

	instance HasFoo Int Bool where ...

Is this legal?

	f :: HasFoo Int b => Int -> b
	f x = foo x

You might think so, since 
	HasFoo Int b => Int -> b
is a substitution instance of
	HasFoo a b => a -> b

but if we infer the type (HasFoo Int b => Int -> b)
for f's RHS, we can then "improve" it using the instance
decl to (HasFoo Int Bool => Int -> Bool), and now the signature
isn't a substitution insance of the type of the RHS.  Indeed,
this is just what will happen if you try with GHC, because
GHC takes advantage of type signatures when typechecking a 
function defn, rather than first typechecking the defn and only
then comparing with the signature.

I don't know what the answers are here, but there's more to this
functional dependency stuff than meets the eye.  Even whether
one type is more general than another has changed!

Simon

| -----Original Message-----
| From: qrczak@knm.org.pl [mailto:qrczak@knm.org.pl]
| Sent: 17 December 2000 19:30
| To: haskell@haskell.org
| Subject: Problem with functional dependencies
| 
| 
| The following module is rejected by both
|     ghc -fglasgow-exts -fallow-undecidable-instances
| and
|     hugs -98
| 
| --------------------------------------------------------------
| ----------
| class HasFoo a foo | a -> foo where
|     foo :: a -> foo
| 
| data A = A Int
| data B = B A
| 
| instance HasFoo A Int where
|     foo (A x) = x
| 
| instance HasFoo A foo => HasFoo B foo where
|     foo (B a) = foo a
| --------------------------------------------------------------
| ----------
| 
| The error messsage says that the type inferred for foo in B's instance
| is not general enough: the rhs has type "HasFoo B Int => B -> 
| Int", but
| "HasFoo B foo => B -> foo" was expected.


From paul.hudak@yale.edu Wed Dec 20 16:28:10 2000 Date: Wed, 20 Dec 2000 11:28:10 -0500 From: Paul Hudak paul.hudak@yale.edu Subject: Haskell Productivity
> Can someone point me at some more references?

See http://haskell.org/papers/NSWC/jfp.ps.

  -Paul


From peterd@availant.com Wed Dec 20 16:45:35 2000 Date: Wed, 20 Dec 2000 11:45:35 -0500 From: Peter Douglass peterd@availant.com Subject: Haskell Productivity
There is a thread on comp.lang.functional which may be of interest.
Here is a link that might work for you.

http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh
8ss$6le$1@bird.wu-wien.ac.at%3e%231/1

> -----Original Message-----
> From: Steinitz, Dominic J 
> [mailto:Dominic.J.Steinitz@BritishAirways.com]
> Sent: Wednesday, December 20, 2000 11:12 AM
> To: haskell
> Subject: Haskell Productivity
> 
> 
> The Haskell website claims that
> 
> "Ericsson measured an improvement factor of between 9 and 25 
> in one set of experiments on telephony software".
> 
> Presumably this is with Erlang not with Haskell. I have 
> searched for the reference that substantiates this claim but 
> I've only been able to find:
> 
> http://set.gmd.de/~ap/femsys/wiger.html 
> 
> which talks about a productivity factor of 4
> 
> and
> 
> http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haske
ll-vs-ada-abstract.html

which suggests that Haskell is about 2-3 times as productive as imperative
languages.

Can someone point me at some more references? Especially the one that talks
about a productivity improvement of 9-25?

Thanks, Dominic.

----------------------------------------------------------------------------
---------------------
21st century air travel     http://www.britishairways.com

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


From peterd@availant.com Wed Dec 20 16:50:50 2000 Date: Wed, 20 Dec 2000 11:50:50 -0500 From: Peter Douglass peterd@availant.com Subject: Haskell Productivity
Hello all,
  You will need to manually reconnect the link I sent into a single line
for it to work.

> There is a thread on comp.lang.functional which may be of interest.
> Here is a link that might work for you.
> 
>
http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh
8ss$6le$1@bird.wu-wien.ac.at%3e%231/1
 


From ashley@semantic.org Wed Dec 20 23:59:50 2000 Date: Wed, 20 Dec 2000 15:59:50 -0800 From: Ashley Yakeley ashley@semantic.org Subject: GHC for Darwin?
Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant 
that runs on the PowerPC processor.
<http://www.opensource.apple.com/projects/darwin/>.

I was going to compile it myself before I remembered that compilers do 
platform-specific code-generation. Duh.

-- 
Ashley Yakeley, Seattle WA



From simonmar@microsoft.com Wed Dec 20 17:46:25 2000 Date: Wed, 20 Dec 2000 09:46:25 -0800 From: Simon Marlow simonmar@microsoft.com Subject: ANNOUNCE: Happy version 1.9
ANNOUNCING  Happy 1.9  - The LALR(1) Parser Generator for Haskell
-----------------------------------------------------------------

I'm pleased to announce version 1.9 of Happy, the parser generator
system for Haskell.  Changes in this version, relative to version 1.8
(the previous full release):

        * A grammar may now contain several entry points, allowing
          several parsers to share parts of the grammar.

        * Some bugfixes.

Happy is available in source form, which can be compiled with GHC
version 4.xx (4.08.1 recommended), and we also provide binaries for
some architectures.  The Happy homepage with links to the various
distributions lives at:

        http://www.haskell.org/happy/

Please send any bug reports and comments to simonmar@microsoft.com.


From doaitse@cs.uu.nl Thu Dec 21 08:22:27 2000 Date: Thu, 21 Dec 2000 10:22:27 +0200 From: S. Doaitse Swierstra doaitse@cs.uu.nl Subject: GHC for Darwin?
At 3:59 PM -0800 12/20/00, Ashley Yakeley wrote:
>Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant
>that runs on the PowerPC processor.
><http://www.opensource.apple.com/projects/darwin/>.
>
>I was going to compile it myself before I remembered that compilers do
>platform-specific code-generation. Duh.
>
>--
>Ashley Yakeley, Seattle WA
>
>
>_______________________________________________
>Haskell mailing list
>Haskell@haskell.org
>http://www.haskell.org/mailman/listinfo/haskell

Atze Dijkstra (mailto:atze@cs.uu.nl) is working on a port of the GHC 
to MacOS X. He has reached the state where he managed to compile some 
programs (e.g. our attribute grammar system and combinator libraries).

      Doaitse Swierstra
-- 
__________________________________________________________________________
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
                       P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
                       Mail:  mailto:doaitse@cs.uu.nl
                       WWW:   http://www.cs.uu.nl/
                       PGP Public Key: http://www.cs.uu.nl/people/doaitse/
                       tel:   +31 (30) 253 3962, fax: +31 (30) 2513791
__________________________________________________________________________


From jeff@galconn.com Thu Dec 21 08:59:29 2000 Date: Thu, 21 Dec 2000 00:59:29 -0800 From: Jeffrey R. Lewis jeff@galconn.com Subject: Problem with functional dependencies
Simon Peyton-Jones wrote:

> I think you can simplify the example.  Given
>
>         class HasFoo a b | a -> b where
>           foo :: a -> b
>
>         instance HasFoo Int Bool where ...
>
> Is this legal?
>
>         f :: HasFoo Int b => Int -> b
>         f x = foo x
>
> You might think so, since
>         HasFoo Int b => Int -> b
> is a substitution instance of
>         HasFoo a b => a -> b

This is the step where the reasoning goes wrong.  The functional dependency tells you that `b' isn't really a free variable, since it is dependent on `a'.  If you substitute for `a', you can't expect `b' to remain unconstrained.

Hugs complains that the inferred type for `f' is not general enough.  It's right to complain, but the real problem is that the signature is too general.  Asimilar situation arises if you try to declare an instance `HasFoo Int b', but in this case, hugs complains that the instance is more general than the dependency allows.  A useful thing to do would be to check for this sort of thing in signatures as well, so that the more appropriate error message can be given.

--Jeff



From qrczak@knm.org.pl Thu Dec 21 10:05:14 2000 Date: 21 Dec 2000 10:05:14 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Problem with functional dependencies
Thu, 21 Dec 2000 00:59:29 -0800, Jeffrey R. Lewis <jeff@galconn.com> pisze:

> >         class HasFoo a b | a -> b where

> >         f :: HasFoo Int b => Int -> b
> >         f x = foo x

> This is the step where the reasoning goes wrong.  The functional
> dependency tells you that `b' isn't really a free variable, since
> it is dependent on `a'.  If you substitute for `a', you can't expect
> `b' to remain unconstrained.

It's not unconstrained: the constraint is "HasFoo Int b", as written.
IMHO it should not matter that the constraint fully determines b.

> Asimilar situation arises if you try to declare an instance `HasFoo
> Int b', but in this case, hugs complains that the instance is more
> general than the dependency allows.

ghc does not complain. How would I express "the instance can be chosen
basing on 'a' alone, and the instance found will tell what constraints
are on 'b'"?

Aren't fundeps a too general mechanism which is not able to express
simpler statements? :-(

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From chak@cse.unsw.edu.au Thu Dec 21 11:40:02 2000 Date: Thu, 21 Dec 2000 22:40:02 +1100 From: Manuel M. T. Chakravarty chak@cse.unsw.edu.au Subject: ANNOUNCE: Happy version 1.9
Simon Marlow <simonmar@microsoft.com> wrote,

> ANNOUNCING  Happy 1.9  - The LALR(1) Parser Generator for Haskell
> -----------------------------------------------------------------

A RedHat 7.0/i386 rpm package is available at

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/happy-1.9-1.i386.rpm

and the matching source rpm at

  ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/happy-1.9-1.src.rpm

Happy Hacking,
Manuel


From rrt1001@cam.ac.uk Thu Dec 21 11:58:42 2000 Date: Thu, 21 Dec 2000 11:58:42 +0000 (GMT) From: Reuben Thomas rrt1001@cam.ac.uk Subject: ANNOUNCE: Happy version 1.9
> ANNOUNCING  Happy 1.9  - The LALR(1) Parser Generator for Haskell
> -----------------------------------------------------------------

A Windows InstallShield package is available at

  http://www.haskell.org/happy/dist/1.9/happy-1-9.exe

-- 
http://sc3d.org/rrt/ | egrep, n.  a bird that debugs bison




From lennart@augustsson.net Thu Dec 21 12:11:33 2000 Date: Thu, 21 Dec 2000 13:11:33 +0100 From: Lennart Augustsson lennart@augustsson.net Subject: Problem with functional dependencies
Simon Peyton-Jones wrote:

> I think you can simplify the example.  Given
>
>         class HasFoo a b | a -> b where
>           foo :: a -> b
>
>         instance HasFoo Int Bool where ...
>
> Is this legal?
>
>         f :: HasFoo Int b => Int -> b
>         f x = foo x
>
> You might think so, since
>         HasFoo Int b => Int -> b
> is a substitution instance of
>         HasFoo a b => a -> b
>
> but if we infer the type (HasFoo Int b => Int -> b)
> for f's RHS, we can then "improve" it using the instance
> decl to (HasFoo Int Bool => Int -> Bool), and now the signature
> isn't a substitution insance of the type of the RHS.

I definitely want it to be legal.  I have examples where this is immensly useful.


--

        -- Lennart





From qrczak@knm.org.pl Thu Dec 21 18:32:59 2000 Date: 21 Dec 2000 18:32:59 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Are fundeps the right model at all?
Could somebody show an example which requires fundeps and cannot be
expressed using a simpler model explained below - a model that I can
even understand? Is the model self-consistent at all?

Each class is associated with a set of subsets of type variables in
its head. Let's call it the set of keys. The intuitive meaning of a
key is that types corresponding to these variables are sufficient to
determine which instance to choose. They correspond to lhss of some
fundeps.

Plain classes without explicitly written keys correspond to having
a single key consisting of all type variables. Keys influence the
typechecking thus:

- A type is unambiguous if for every class constraint in it there
  exists its key such that types in the constraint corresponding to
  type variables from the key contain no type variables which are
  absent in the type itself.

- All class methods must have unambiguous types, i.e. for each method
  there must be a key whose all type variables are present in the
  method's type.

- For each key, there must be no pair of instances whose heads
  projected to the class parameters from the key overlap.

- For each class constraint of an unambiguous type an each its key
  there must be an instance found basing on this key, or the type is
  incorrect because of missing instances. Moreover, instances found
  basing on all keys must be identical.

- Perhaps something must be said about class contexts and instance
  contexts. I'm not sure what yet.


Examples:

class Collection c e | c where
    empty  :: c
    insert :: c -> e -> c

class Monad m => MonadState s m | m where
    get :: m s
    put :: s -> m ()

newtype State s a = State {runState :: s -> (a,s)}
instance Monad (State s)
instance MonadState s (State s)
test1:: Int -> Int
test1 x = snd (runState get x) -- Not ambiguous.

class IOvsST io st | io, st where
    -- Two single-element keys.
    ioToST :: io -> st
    stToIO :: st -> io

instance IOvsST (IORef a) (STRef s a) where
    ioToST = unsafeCoerce#
    stToIO = unsafeCoerce#

test2:: IORef a -> IORef a
test2 = ioToST . stToIO -- Not ambiguous.

class Foo a b | a
instance Foo Int [a]
-- This is rejected by Hugs (with fundep a->b) but I would definitely
-- accept it.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From ger@tzi.de Thu Dec 21 20:20:46 2000 Date: Thu, 21 Dec 2000 21:20:46 +0100 From: George Russell ger@tzi.de Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
Alternatively, I wonder whether the current system of type classes is the right
model at all.

Although I prefer the Haskell system, I think it is instructive to compare it
with the Standard ML (SML) system of structures and functors.  My point is that
both Haskell and SML impose one of two possible extremes on the user, and
suffer for it.

With SML, it is as if all instances are explicitly named.  SML does not permit
user-defined overloading, and so SML is not capable of understanding 
something such as a "type class of things we can compare", and has a horrible
set of kludges to cope with implementing the equality operator.

With Haskell, on the other hand, there is no way of referring to a particular
instance when you want to.  We see a particular consequence of that here, in
that (unlike SML), it is not possible to associate an internal type with a 
given instance.  Another problem is that no-one has any control over what
instances get exported, because since instances are anonymous there is no way 
of referring to them.  Hence the current procedure is to expose everything to
the importer, which is surely a mistake.

So if you agree with me up to here, perhaps you are agreed that it is worth
while trying to find a middle way, in which we try to combine both approaches.
Well I'm not an expert language designer, and I'm doing this off the top of my
head late on Thursday evening, so please don't nitpick about syntax; I'm aware
that parsing will probably be difficult in all sorts of ways with exactly what
I'm writing, but that shouldn't be too hard to tweak.  In particular I have
followed SML in using "." to express qualification by something, even though
Haskell already used "." for something else, because I can't be bothered right
now to dig up a better symbol.

On the other hand if my whole approach is a pile of elephant dung I apologise
for wasting your time, and wish you a happy Christmas/holidays, but do try to
find a better way of combining the best of SML functors and Haskell classes.

Anyway here is my proposal.
(1) We extend type classes to allow them to introduce types.  Thus for example
    I would replace Marcin's first example by
       class Collectible e where
          type c -- or we could just omit the "type" keyword, trading clarity
                 -- for conciseness.
                 --  note also that we need a way of expressing a context for
                 -- "c", EG that it's an instance of Eq.
          empty :: c
          insert :: c -> e -> c
    As usual, you can refer to "empty" and "insert" right away, but you 
    can't refer to "c" without extra syntax.  We need a way of referring to 
    the particular instance of Collectible.  So I suggest something like:

    singleton :: (method | Collectible e) => e -> method.c
    singleton el = insert empty el
(2) We extend instance declarations in two ways.  Firstly and obviously, we 
    need a way of declaring the type c in the instance second declaration.  
    The second thing is to introduce named instance declarations, like this:

    instance IntList | Collectible Int where
       type c = [Int]
       empty = []
       insert = (flip(:)) 

    To actually _refer_ to a specific instance, you would qualify with IntList.
    So you could refer to IntList.c,  IntList.empty, IntList.insert, just like
    you would with SML.  But as with Haskell, "empty" and "insert" would
    continue to be available implicitly.

    A more complicated example arises when you have instances depending on 
    other instances.  EG

    instance SetCollection | Ord el => Collectible el where
       type c = Set el
       empty = emptySet
       insert = addToSet -- new function, thank Simon Marlow

    Then, in this case, you would refer to SetCollection.c when you wanted to
    refer to the type c.   However note that in this case we are implicitly
    using an anonymous use of Ord.  Supposing you had previously defined
    (ignoring questions about overlapping instances for now . . .)

    instance EccentricOrd | Ord Int where
       ...
    and you wanted to define Sets in terms of EccentricOrd.  Then I suggest 
    that you use instead SetCollection(EccentricOrd).c and likewise 
    SetCollection(EccentricOrd).empty and Sets(EccentricOrd).insert, 
    though I hope that such monstrous constructions will not often 
    be necessary.   When they are, maybe it would be a good idea to allow the
    user to abbreviate, as in
       instance EccentricSet | Collectible Int = SetCollection(EccentricOrd)
    just as you can do in SML.
(3) Finally it would be nice to extend the module syntax to allow named
    instances to be selectively exported and imported, just like variables.  
    If I could ignore all pre-existing Haskell code I would specify that
    whenever a module has a specific import list, no instances are imported
    unless specified.  However this is politically impossible, so instead I
    suggest that all anonymous instances continue to be implicitly imported, 
    as now, but that named instances are only imported when named in the 
    import list.  EG "import File(instance SetCollection)".  Also, I think it 
    would be nice to have something similar to the "qualified" operator, by 
    which class membership is NOT automatically inherited, and would have to 
    be explicitly specified by referring to "SetCollection.insert" or indeed 
    "SetCollection.singleton"; in particular this would provide a clean way 
    of handling overlapping classes.
OK, so I realise this is probably not the final answer, but wouldn't it be 
nice if something along these lines could be got to work?


From ger@tzi.de Fri Dec 22 15:56:41 2000 Date: Fri, 22 Dec 2000 16:56:41 +0100 From: George Russell ger@tzi.de Subject: List.partition a bit too eager
I think the following program

import List
main = putStr . show . fst . (partition id) . cycle $ [True,False]

should display [True,True,True,...].  But instead, for both GHC and Hugs,
you get a stack overflow.  Is this a bug, or could someone explain it to me?


From qrczak@knm.org.pl Sun Dec 24 20:25:12 2000 Date: 24 Dec 2000 20:25:12 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
Thu, 21 Dec 2000 21:20:46 +0100, George Russell <ger@tzi.de> pisze:

> So if you agree with me up to here, perhaps you are agreed that it is worth
> while trying to find a middle way, in which we try to combine both approaches.

I am thinking about a yet different approach. Leave classes and SML
structures as they are, and make *records* more flexible, to be used
instead of classes if instances are to be manipulated explicitly,
and instead of structures if we are using Haskell rather than SML
or OCaml, and instead of objects if we are using Haskell rather than
some OO language, and as a general way of expressing things behaving
like fixed dictionaries of values.

I have yet to play more with it. I already have some thoughts and
a working preprocessor which translates my extensions to Haskell
(with multi-parameter classes and fundeps).

-------- GOALS --------

* Replace the current record mechanism with a better one.

* Don't require sets of fields of different record types disjoint. It's
  not only to avoid inventing unique field names, but also to have
  functions polymorphic over all records containing specific fields
  of specific types.

* Provide a way to specialize existing record types to new types that
  behave similarly except of small changes. I.e. kind of inheritance.

* Since Haskell does not have subtyping, have coercions up the
  inheritance tree. Overloading functions on record types is not
  always enough, e.g. to put records in a heterogeneous collection
  they must be coerced to a common type.

* Don't constrain the implementation of field access for different
  record types. As long as it behaves like a record, it is a record.

* Don't constrain the implementation of methods even for the same
  record type. Since Haskell does not have subtyping, records which
  would have different types in other languages can have the same
  type in Haskell, as long as the same interface suffices.

* Express keyword parameters of functions. A function might use many
  parameters refining its behavior which usually have some default
  values. Old code using that function must not break when more
  parameters are added.

* A piece of code should be understandable locally, independently
  of definitions and instances present elsewhere.

* Have a nice syntax.

* Keep it simple and easily translatable to the core language.

Fields and methods are really the same thing. Moreover, inheritance is
really delegation and coercions are the same things as field accesses
as well.

Record types are not anonymous, unlike TREX. Field names are born
implicitly and live in a separate namespace. Each field name is
associated with a class of record types having that field. Instances
of these classes are defined implicitly for types defined as records,
but can also be given explicitly for any type.

-------- FIELD SELECTION --------

A field selection expression of the form
        expr.label
is equivalent to
        (.label) expr
where
        (.label) :: (r.label :: a) => r -> a
is an overloaded selector function.

(rec.label:: a) is a syntax for Has_label rec a, where Has_label is
the implicitly defined class for this label. Such class would look
like this if it were defined as normal classes:
        class Has_label r a | r -> a where
            (.label)  :: r -> a
            set_label :: r -> a -> r
except that there are no real names Has_label nor set_label.

-------- DEFINITION OF RECORD TYPES --------

The definition of a record type:
        data Monoid e = record
            zero :: e
            plus :: e -> e -> e
defines the appropriate single-constructor algebraic type and
obvious instances:
        instance (Monoid e).zero :: e           where ...
        instance (Monoid e).plus :: e -> e -> e where ...

We can construct values of this type thus:
        numAddMonoid :: Num e => Monoid e
        numAddMonoid = record
            zero = 0
            plus = (+)

The meaning of such overloaded record creation expressions will be
specified later.

-------- INHERITANCE --------

Here is another example of a record type definition:
        data Group e = record
            monoid :: Monoid e
            minus  :: e -> e -> e
            neg    :: e -> e
            monoid (zero, plus)
            x `minus` y = x `plus` neg y
            neg y       = zero `minus` y

This record type has three direct members: monoid, minus, and neg.
monoid holds its zero and plus.

We want to be able to extract zero and plus of a group directly,
instead of going through the underlying monoid. We could define
appropriate instances:
        instance (Group e).zero :: e           where ...
        instance (Group e).plus :: e -> e -> e where ...
and this is what the inheritance declaration
        monoid (zero, plus)
does automatically for us.

So groups too have zero and plus, which are deleagated to the monoid.
Seen from outside, these fields are indistinguishable from proper
Group's fields.

-------- DEFAULT DEFINITIONS --------

minus and neg in Group have default definitions expressed in terms
of each other. When making a Group we can provide the definition of
either one or both, otherwise both will diverge.

We could provide default definitions of inherited methods too. If they
had default definition in the supertype, they would be overridden.
This is how the system expresses OO methods belonging to a type: by
default definitions. They can be overridden in subtypes or at object
creation time.

How is it done that the default definition of minus refers to the
definition of neg which will be supplied later? It is not known yet
which fields will be specified at creation time. OTOH at the creation
time it is not known which fields have default definitions, because
the creation expression is polymorphic over record types containing
specific fields and will be instantiated based on the context.

There is a standard class defined as follows:
        class Record r where
            bless :: r -> r

A record creation expression, say:
        record
            zero = 0
            plus = (+)
is a syntactic sugar for a recursively defined object:
        let this = bless this `set_zero` 0 `set_plus` (+)
        in this

The bless function, named after Perl's mechanism used in a similar
context, returns a record with all fields initialized using their
default definitions, or bottoms for fields with no defaults. Default
definitions refer to other fields through the parameter of bless.
As seen above, bless is applied to the record to be constructed, and
then fields with values specified at creation time are overridden.

That way all field definitions can find right versions of other fields,
no matter which were defined together with the type and which were
supplied at the creation time.

The type of the above record creation expression is
        (Record r, Num a, Num b, r.zero :: a, r.plus :: b -> b -> b) => r

-------- DEFINITION OF BLESS --------

Definition of a record type automatically makes it an instance of
the class Record.

A field from which some other fields are inherited is initialized to
blessed value of the same field taken from the parameter of bless,
modified by setting those fields which have default defintions.
It sounds complicated but this is what yields right bindings of
all definitions.

If a type behaves like a record, it is a record. You can make Record
instances of arbitrary types, making them constructible using the
record syntax.

bless should be lazy. Field setters can be strict.

-------- UPDATING FIELDS --------

If fields represent state changing over time, they can be mutable
references. Fields can also be updated in a functional style, but
this is really construction of new objects basing on old ones.

Field update syntax is as follows:
        expr.record
            label1 = value1
            label2 = value2
It is equivalent to simple nested set_label applications.

Fields initialized with default definitions will not switch to refer
to updated values of other fields! All magic already happened at
record creation time.

This can be changed in at least two ways. First, you can define
instances of appropriate Has_label classes yourself and associate
arbitrary magic with field updates. Second, you can make such instance
for the field that you want to be a function of other fields instead of
putting the field in the record directly.

Definitions of two methods of Has_label classes have special syntax:
        instance (a,b).fst :: a where
            (a,_).fst              = a
            (_,b).record {fst = a} = (a,b)

        instance (a,b).snd :: b where
            (_,b).snd              = b
            (a,_).record {snd = b} = (a,b)

I.e. pattern.label is equivalent to (.label) pattern and defines the
getter function, and pattern1.record {label = pattern2} defines the
setter when applied to the record matching pattern1 and field value
matching pattern2. Braces can be omitted, but they make the syntax
more clear.

-------- SYNTAX DETAILS --------

The record keyword triggers the layout rules. Value definitions after
the record keyword look like let bindings. They can be defined by
cases with argument patterns on the left of the equal sign.

In record type definitions, record creations and record updates
definitions of fields can refer to all fields mentioned in those
constructs in an unqualified form. They can also refer to a special
variable called this, which holds the whole record after construction
or update.

-------- EXAMPLE --------

This example introduces a feature of renaming fields while inheriting.

> data Monoid e = record
>     zero :: e
>     plus :: e -> e -> e
> 
> numAddMonoid :: Num e => Monoid e
> numAddMonoid = record
>     zero = 0
>     plus = (+)
> 
> numMulMonoid :: Num e => Monoid e
> numMulMonoid = record
>     zero = 1
>     plus = (*)
> 
> data Group e = record
>     monoid :: Monoid e
>     minus  :: e -> e -> e
>     neg    :: e -> e
>     monoid (zero, plus)
>     x `minus` y = x `plus` neg y
>     neg y       = zero `minus` y
> 
> numAddGroup :: Num e => Group e
> numAddGroup = record
>     monoid  = numAddMonoid
>     minus   = (-)
>     neg     = negate
> 
> numMulGroup :: Fractional e => Group e
> numMulGroup = record
>     monoid  = numMulMonoid
>     minus   = (/)
>     neg     = recip
> 
> data Ring e = record
>     addGroup  :: Group e
>     mulMonoid :: Monoid e
>     addGroup  (monoid as addMonoid, zero, plus, minus, neg)
>     mulMonoid (zero as one, plus as times)
> 
> numRing :: Num e => Ring e
> numRing = record
>     addGroup  = numAddGroup
>     mulMonoid = numMulMonoid
> 
> data Field e = record
>     addGroup :: Group e
>     mulGroup :: Group e
>     addGroup (monoid as addMonoid, zero, plus, minus, neg)
>     mulGroup (monoid as mulMonoid, zero as one, plus as times,
>                                    minus as div, neg as recip)
> 
> instance (Field e).ring :: Ring e where
>     f.ring = record
>         addGroup  = f.addGroup
>         mulMonoid = f.mulMonoid
>     f.record {ring = r} = f.record
>         addGroup  = r.addGroup
>         mulMonoid = r.mulMonoid
> 
> -- Alternatively a Field could consist of a Ring and div + recip.
> -- The difference is an implementation detail not visible outside.
> -- The following definition will work with either variant:
> 
> numField :: Fractional e => Field e
> numField = record
>     addGroup = numAddGroup
>     mulGroup = numMulGroup

-------- PROBLEMS --------

If those records are to simulate classes, they should be able to have
polymorphic fields. Unfortunately it does not work to have overloaded
setters in this case. I don't know a good solution.

Similarly we would want to have records with existentially quantified
types. Again it does not work to have overloaded getters and setters.

Listing all inherited fields can be annoying. It would not really
work otherwise, as arbitrary instances for sypertypes can be added
at any time. It is not necessary to list all fields: other fields
are available through the field we inherit from anyway.

It would be desirable to selectively export instances.

-------- PROTOTYPE IMPLEMENTATION --------

I have an implementation of this in the form of a preprocessor,
based on hssource from ghc-4.11's hslibs. I will polish it and put
for downloading to let people play with my records. I hope to have
more interesting examples.

The difference between this implementation and the above proposal
is that types of inherited fields must be given explicitly. This
is because delegation instances would otherwise have to have
types which are not accepted by ghc, and they would require
-fallow-undecidable-instances if they were legal (which is not a
surprise because cyclic inheritance makes it impossible to determine
the type of the field).

I reported the problem under the subject "Problem with functional
dependencies" on December 17th. I believe that both problems can
be fixed, especially if handling those constructs were inside the
compiler.

-------- THE REST OF MY REPLY TO GEORGE RUSSELL --------

> (1) We extend type classes to allow them to introduce types.

If your classes were expressed as my records, it would roughly
correspond to existential quantification. But there are big problems
with typechecking in this approach.

I hope somebody will invent a solution.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From fjh@cs.mu.oz.au Tue Dec 26 01:10:55 2000 Date: Tue, 26 Dec 2000 12:10:55 +1100 From: Fergus Henderson fjh@cs.mu.oz.au Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
On 21-Dec-2000, George Russell <ger@tzi.de> wrote:
> (3) Finally it would be nice to extend the module syntax to allow named
>     instances to be selectively exported and imported, just like variables.  

Mercury's module system allows instance declarations (which, as in
Haskell 98, are unnamed) to be selectively exported.

	:- module foo.
	:- interface.

	    :- import_module enum.

	    :- type t.
	    :- instance enum(t).

	:- implementation.

	    :- instance enum(t) where [ ... ].

Mercury doesn't directly support selective import -- you can only
import a whole module, not part of it.  But if you really want that
you can achieve it by putting each instance declaration in its own
nested module.

	:- module foo.
	:- interface.
	:- import_module enum.

	   :- type t.

	   :- module enum_t.
	   :- interface.
	   :- instance enum(t).
	   :- end_module enum_t.

	:- implementation.

	   :- module enum_t.
	   :- implementation.
	   :- instance enum(t) where [ ... ].
	   :- end_module enum_t.

-- 
Fergus Henderson <fjh@cs.mu.oz.au>  |  "I have always known that the pursuit
                                    |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.


From qrczak@knm.org.pl Tue Dec 26 08:46:44 2000 Date: 26 Dec 2000 08:46:44 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
Tue, 26 Dec 2000 12:10:55 +1100, Fergus Henderson <fjh@cs.mu.oz.au> pisze:

> Mercury's module system allows instance declarations (which, as in
> Haskell 98, are unnamed) to be selectively exported.

If they could be selectively exported in Haskell, how to make it
compatible with the current assumption that they are exported by
default? Selective hiding would be weird.

Perhaps there should be a separate section for exporting instances.
If not present, then everything is exported (as with plain module
contents).

I hope selective export would help with resolving conflicting
instances. There might be a confusion if a function does indeed
get a sorted list of objects of type T but it expected a different
ordering, but the danger of inability of linking two independent
libraries due to an innocent overlapping instance might be worse.

As we are at it, it would be nice to be able to specify signatures and
other interface details where they belong - in the export list. With
a different syntax of the export list; there would be an ambiguity if
    ..., var1, var2 :: Type, ...
gives Type to both variables or only one, and items should be
separated by layoutable semicolons.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From Doug_Ransom@pml.com Wed Dec 27 18:33:42 2000 Date: Wed, 27 Dec 2000 10:33:42 -0800 From: Doug Ransom Doug_Ransom@pml.com Subject: ANNOUNCE: HaXml 1.00
I think it is important that a good haskell XML library be included as part
of the haskell runtime library given XML's relevance.





> -----Original Message-----
> From: Malcolm Wallace [mailto:Malcolm.Wallace@cs.york.ac.uk]
> Sent: Thursday, November 16, 2000 8:42 AM
> To: haskell@haskell.org
> Subject: ANNOUNCE: HaXml 1.00
> 
> 
> We are pleased to announce
> 
>                           HaXml   release 1.00
>                           --------------------
> 
> HaXml is a library enabling the use of Haskell and XML together,
> together with several auxiliary tools for useful XML jobs.  Fuller
> details are on the web page.
> 
> 
> What's new since 0.9?
> ---------------------
> The main addition is a full treatment of the external subset for DTDs.
> The DtdToHaskell tool can now slurp in a single DTD from multiple
> files, and also now treats conditional sections (INCLUDE and IGNORE)
> correctly.
> 
> There is improved error-reporting: lexing and parsing errors 
> now report
> the relevant filename, and the line/column positions are more 
> accurate.
> 
> 
> Where do I get it?
> ------------------
> Web pages:	http://www.cs.york.ac.uk/fp/HaXml/
> FTP site:	ftp://ftp.cs.york.ac.uk/pub/haskell/HaXml/
> 
> An older version of HaXml is also included in GHC's hslibs, in package
> "text".  This will probably be updated to 1.00 at some time.
> 
> Regards,
>     Malcolm
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 


From Doug_Ransom@pml.com Thu Dec 28 01:30:19 2000 Date: Wed, 27 Dec 2000 17:30:19 -0800 From: Doug Ransom Doug_Ransom@pml.com Subject: Learning Haskell and FP
I have read "The Craft of Functional Programming" by Simon Thompson and a
few paper on the web.  "The Craft" is a good book, but it is an introduction
to FP.


It seems to me it there are a lot of books on OO design I can pick up at the
bookstore, but in the FP world, one must worm their way through all sorts of
papers.  I have seen papers on Catamorphisms, Monads, Programming with
Barbed Wire, folds, etc.  I think these papers are hard to understand if you
don't have the acadademic/mathematical background -- being papers and not
textbooks these papers assume a fair bit of base knowledge. I know I can
design a fold function to use in place of primitive recursion for most data
structures -- I just don't know if I should. It is pretty easy to get
through "The Craft of Functional Programming" without understanding what
Category Theory  , a Catamorphism , or a Kleisli Composition is.  I can see
lots of real Software Engineering oppurtunities for these various techniques
if I could just put them together.

Is there a good textbook on Functional Programming which starts from a base
point similar to "The craft of Functional Programming" but more advanced in
terms of introducing necessary topics like Category theory, catamorphisms,
monads, etc?  I would find such a book very useful, especially if it
concentrated on lazy functional programming.


Doug Ransom
Systems Engineer
Power Measurement Ltd.
http://www.pml.com
250-652-7100 office
250-652-0411 fax
mailto:doug_ransom@pml.com


From israelt@optushome.com.au Thu Dec 28 02:50:50 2000 Date: Thu, 28 Dec 2000 12:50:50 +1000 From: i r thomas israelt@optushome.com.au Subject: Learning Haskell and FP
>I have read "The Craft of Functional Programming" by Simon Thompson and a
>few paper on the web.  "The Craft" is a good book, but it is an=
 introduction
>to FP.
>It seems to me it there are a lot of books on OO design I can pick up at=
 the
>bookstore, but in the FP world, one must worm their way through all sorts=
 of
>papers.  I have seen papers on Catamorphisms, Monads, Programming with
>Barbed Wire, folds, etc.  I think these papers are hard to understand if=
 you
>don't have the acadademic/mathematical background -- being papers and not
>textbooks these papers assume a fair bit of base knowledge.

I agree with this completely.
The CFP book is a good introduction.
Unforunately, the " Gentle Introduction To Haskell" that haskell.org links=
 to is not a very useful introduction.
I am getting  more out of  Rex Paige's Two Dozen Short Lessons in Haskell.=
 ( I am studying Haskell and C# on my own in my spare time as break from my=
 medical practice ). 



From russell@brainlink.com Thu Dec 28 06:14:54 2000 Date: Thu, 28 Dec 2000 01:14:54 -0500 From: Benjamin L. Russell russell@brainlink.com Subject: Learning Haskell and FP
While it may not be advanced or mathematical enough for your needs, you may wish to read _The Haskell School of Expression: Learning Functional Programming through Multimedia,_ by Paul Hudak.  This is also an introductory book on functional programming, with a special focus on Haskell, although the examples used are mainly from multimedia.

I compared the first few chapters of both _The Craft of Functional Programming_ and _The Haskell School of Expression,_ and personally found Hudak's book (the latter) much more interesting.  The exercises are designed to teach the reader to think in terms of functional, as opposed to imperative or object-oriented, programming--hence the phrase in the title "School of Expression."

--Ben
--
Benjamin L. Russell
russell@brainlink.com
benjamin.russell.es.94@aya.yale.edu
"Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho

On Wed, 27 Dec 2000 17:30:19 -0800
 Doug Ransom <Doug_Ransom@pml.com> wrote:
> I have read "The Craft of Functional Programming" by
> Simon Thompson and a
> few paper on the web.  "The Craft" is a good book, but it
> is an introduction
> to FP.
> 
> 
> It seems to me it there are a lot of books on OO design I
> can pick up at the
> bookstore, but in the FP world, one must worm their way
> through all sorts of
> papers.  I have seen papers on Catamorphisms, Monads,
> Programming with
> Barbed Wire, folds, etc.  I think these papers are hard
> to understand if you
> don't have the acadademic/mathematical background --
> being papers and not
> textbooks these papers assume a fair bit of base
> knowledge. I know I can
> design a fold function to use in place of primitive
> recursion for most data
> structures -- I just don't know if I should. It is pretty
> easy to get
> through "The Craft of Functional Programming" without
> understanding what
> Category Theory  , a Catamorphism , or a Kleisli
> Composition is.  I can see
> lots of real Software Engineering oppurtunities for these
> various techniques
> if I could just put them together.
> 
> Is there a good textbook on Functional Programming which
> starts from a base
> point similar to "The craft of Functional Programming"
> but more advanced in
> terms of introducing necessary topics like Category
> theory, catamorphisms,
> monads, etc?  I would find such a book very useful,
> especially if it
> concentrated on lazy functional programming.
> 
> 
> Doug Ransom
> Systems Engineer
> Power Measurement Ltd.
> http://www.pml.com
> 250-652-7100 office
> 250-652-0411 fax
> mailto:doug_ransom@pml.com
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell


From israelt@optushome.com.au Thu Dec 28 08:52:03 2000 Date: Thu, 28 Dec 2000 18:52:03 +1000 From: i r thomas israelt@optushome.com.au Subject: Learning Haskell and FP
>While it may not be advanced or mathematical enough for your needs, you=
 may wish to read _The Haskell School of Expression:=A0Learning Functional=
 Programming through Multimedia,_ by Paul Hudak.  This is also an=
 introductory book on functional programming, with a special focus on=
 Haskell, although the examples used are mainly from multimedia.

Is there an online version of Hudak's book ?
( For example Bruce Eckel has online versions of all his books available=
 online as well as in print )

>"Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho

Translation please ! 
Basho is my favorite Japanese poet.
Unfortunately my Japanese is at the Ohio level..
(  ohiogozaimazu)





From israelt@optushome.com.au Thu Dec 28 08:53:08 2000 Date: Thu, 28 Dec 2000 18:53:08 +1000 From: i r thomas israelt@optushome.com.au Subject: Haskell newsgroup
How about starting a Haskell newsgroup ?
The closest seems to be comp.lang.functional.



From johanj@cs.uu.nl Thu Dec 28 14:06:26 2000 Date: Thu, 28 Dec 2000 15:06:26 +0100 From: Johan Jeuring johanj@cs.uu.nl Subject: Learning Haskell and FP
>Is there a good textbook on Functional Programming which starts from a base
>point similar to "The craft of Functional Programming" but more advanced in
>terms of introducing necessary topics like Category theory, catamorphisms,
>monads, etc?  I would find such a book very useful, especially if it
>concentrated on lazy functional programming.

You might want to have a look at the series of three books on Advanced
Functional 
Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would 
probably start with 925, which introduces monads, parser & pretty-printing 
combinators, monadic catamorphisms, constructor classes, etc.

-- Johan Jeuring



From franka@cs.uu.nl Thu Dec 28 15:48:57 2000 Date: Thu, 28 Dec 2000 16:48:57 +0100 From: Frank Atanassow franka@cs.uu.nl Subject: Learning Haskell and FP
i r thomas wrote (on 28-12-00 12:50 +1000):
> Unforunately, the " Gentle Introduction To Haskell" that haskell.org links to is not a very useful introduction.
> I am getting  more out of  Rex Paige's Two Dozen Short Lessons in Haskell. ( I am studying Haskell and C# on my own in my spare time as break from my medical practice ). 

What did you find unuseful about GITH? How could it be improved? What were
your expectations for it? What was more useful about Rex Paige's notes?

>> "Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho
>
> Translation please !

Is it OK if I show off and steal some thunder? :)

  "(It's) An old pond! The sound of water steadily dripping in..."

-- 
Frank Atanassow, Information & Computing Sciences, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-3261 Fax +31 (030) 251-379


From Doug_Ransom@pml.com Thu Dec 28 17:34:18 2000 Date: Thu, 28 Dec 2000 09:34:18 -0800 From: Doug Ransom Doug_Ransom@pml.com Subject: Haskell newsgroup
That would only work if the haskell mailing list was either delete or
mirrored onto a newsgroup.  I would prefer a newsgroup myself for bandwidth
reasons.


> -----Original Message-----
> From: i r thomas [mailto:israelt@optushome.com.au]
> Sent: Thursday, December 28, 2000 12:53 AM
> To: haskell@haskell.org
> Subject: Haskell newsgroup
> 
> 
> How about starting a Haskell newsgroup ?
> The closest seems to be comp.lang.functional.
> 
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell
> 


From Doug_Ransom@pml.com Thu Dec 28 17:36:37 2000 Date: Thu, 28 Dec 2000 09:36:37 -0800 From: Doug Ransom Doug_Ransom@pml.com Subject: Learning Haskell and FP
Who are the audience for  the books on Advanced Functional Programming?
Academics with a theoretical CS background or someone with just a bit of
understanding of FP? Ideally, I would like a course suited for someone who
has completed a basic FP course.



> -----Original Message-----
> From: Johan Jeuring [mailto:johanj@cs.uu.nl]
> Sent: Thursday, December 28, 2000 6:06 AM
> To: Doug Ransom
> Cc: haskell@haskell.org
> Subject: Re: Learning Haskell and FP
> 
> 
> >Is there a good textbook on Functional Programming which 
> starts from a base
> >point similar to "The craft of Functional Programming" but 
> more advanced in
> >terms of introducing necessary topics like Category theory, 
> catamorphisms,
> >monads, etc?  I would find such a book very useful, especially if it
> >concentrated on lazy functional programming.
> 
> You might want to have a look at the series of three books on Advanced
> Functional 
> Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would 
> probably start with 925, which introduces monads, parser & 
> pretty-printing 
> combinators, monadic catamorphisms, constructor classes, etc.
> 
> -- Johan Jeuring
> 


From shlomif@vipe.technion.ac.il Thu Dec 28 19:23:07 2000 Date: Thu, 28 Dec 2000 21:23:07 +0200 (IST) From: Shlomi Fish shlomif@vipe.technion.ac.il Subject: Haskell newsgroup
On Thu, 28 Dec 2000, Doug Ransom wrote:

> That would only work if the haskell mailing list was either delete or
> mirrored onto a newsgroup.  I would prefer a newsgroup myself for bandwidth
> reasons.
>

And I prefer a mailing-list. It's hard to access newsgroups from the
Technion, and Deja-news seems to be little help when it comes to posting
messages.

Regards,

	Shlomi Fish


----------------------------------------------------------------------
Shlomi Fish        shlomif@vipe.technion.ac.il 
Home Page:         http://t2.technion.ac.il/~shlomif/
Home E-mail:       shlomif@techie.com

The prefix "God Said" has the extraordinary logical property of 
converting any statement that follows it into a true one.



From wli@holomorphy.com Thu Dec 28 19:40:38 2000 Date: Thu, 28 Dec 2000 11:40:38 -0800 From: William Lee Irwin III wli@holomorphy.com Subject: Haskell newsgroup
On Thu, Dec 28, 2000 at 06:53:08PM +1000, i r thomas wrote:
> How about starting a Haskell newsgroup ?
> The closest seems to be comp.lang.functional.

There is a Haskell IRC channel on EfNet. I've been fielding Haskell
questions there with Albert Lai and Ada Lim for several months. There
has also been Haskell-related activity on OpenProjects Network #lisp.

comp.lang.functional seems to be inclusive enough to obviate the need
for a dedicated newsgroup.


Cheers,
Bill
-- 
"And who knows, if you try it, maybe you find out that you like SM(L)? ;)"
-- Markus Mottl on comp.lang.functional


From proff@iq.org Thu Dec 28 22:20:13 2000 Date: 29 Dec 2000 09:20:13 +1100 From: Julian Assange proff@iq.org Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
George Russell <ger@tzi.de> writes:

> I'm writing, but that shouldn't be too hard to tweak.  In particular I have
> followed SML in using "." to express qualification by something, even though
> Haskell already used "." for something else, because I can't be bothered right
> now to dig up a better symbol.

This is why all non S-exp like lanaguage are doomed to progressive
syntactic cancer as the useful parts of operator name space and syntax
space become progressively polluted and mutated by one fad after
another.

--
 Julian Assange        |If you want to build a ship, don't drum up people
                       |together to collect wood or assign them tasks
 proff@iq.org          |and work, but rather teach them to long for the endless
 proff@gnu.ai.mit.edu  |immensity of the sea. -- Antoine de Saint Exupery


From russell@brainlink.com Thu Dec 28 22:35:04 2000 Date: Thu, 28 Dec 2000 17:35:04 -0500 From: Benjamin L. Russell russell@brainlink.com Subject: Learning Haskell and FP
On Thu, 28 Dec 2000 16:48:57 +0100
 Frank Atanassow <franka@cs.uu.nl> wrote:
> i r thomas wrote (on 28-12-00 12:50 +1000):
> > Unforunately, the " Gentle Introduction To Haskell"
> that haskell.org links to is not a very useful
> introduction.
> > I am getting  more out of  Rex Paige's Two Dozen Short
> Lessons in Haskell. ( I am studying Haskell and C# on my
> own in my spare time as break from my medical practice ).
> 
> What did you find unuseful about GITH? How could it be
> improved? What were
> your expectations for it? What was more useful about Rex
> Paige's notes?

I read part of _GITH,_ too; while it included information necessary for an introduction, the style seemed rather terse and dry, and rather difficult to follow at times, and read more like a manual with many technical details than a tutorial brimming with motivational material, especially when compared to _The Haskell School of Expression_ ("_HSE_" in the sequel).  In particular, it could have had some more interesting examples or some more commentary, both of which made _HSE_ so fascinating.

> >> "Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo
> Basho
> >
> > Translation please !
> 
> Is it OK if I show off and steal some thunder? :)
> 
>   "(It's) An old pond! The sound of water steadily
> dripping in..."

Actually, if I may add, the translation I remember was the following:

   "[It's] An old pond!  The sound of water as the frog jumps in...."

"Kawazu" means "frog," and "tobikomu" means "(to) jump in."

--Ben
--
Benjamin L. Russell
russell@brainlink.com
benjamin.russell.es.94@aya.yale.edu
"Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho


From jans@numeric-quest.com Thu Dec 28 18:29:46 2000 Date: Thu, 28 Dec 2000 13:29:46 -0500 (EST) From: Jan Skibinski jans@numeric-quest.com Subject: Learning Haskell and FP
On Thu, 28 Dec 2000, Benjamin L. Russell wrote:

> On Thu, 28 Dec 2000 16:48:57 +0100
>  Frank Atanassow <franka@cs.uu.nl> wrote:
> > i r thomas wrote (on 28-12-00 12:50 +1000):
> > >> "Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho
> > >
> >   "(It's) An old pond! The sound of water steadily
> > dripping in..."
> 
>    "[It's] An old pond!  The sound of water as the frog jumps in...."

Keeping with the minimalistic spirit of Haskell:

    pond
        frog
            plop!
		
-- by James Kirkup, an English poet
-- Supposedly from Hiroaki Sato collection of 80 English translations
-- of this haiku.
--  
	3 down 77 to go..

Jan




From fruehr@willamette.edu Fri Dec 29 00:42:32 2000 Date: Thu, 28 Dec 2000 16:42:32 -0800 (PST) From: Fritz K Ruehr fruehr@willamette.edu Subject: Learning Haskell and FP
[ Doug Ransom wrote about wanting a more advanced and design-oriented book
  on FP than "The Craft of Functional Programming" by Simon Thompson.
  In reply, Johan Jeuring recommended the Advanced Schools books (I concur). 
 ]

Let me add a few other recommendations, plus a vision of a book (not
yet written, as far as I know) which might fit Doug's needs; I'll
call it "The Design Patterns Haskell Companion" (see below).

The "actual book" recommendations (all documented on haskell.org):

 * Introduction to Functional Programming using Haskell (second edition)
   by Richard Bird (Prentice Hall, ISBN: 0-13-484346-0)
   
   This book is an introductory text, like CFP, but it ramps up a bit
   faster and addresses design issues from a more advanced perspective
   (IMHO). It's certainly an excellent text, and it builds to a nice
   medium-sized design example (the program calculator of Chapter 12).
   It also leans toward a different style of design and programming,
   influenced by BMF/Squiggol.

 * Algebra of Programming
   by Richard Bird and Oege de Moor (Prentice Hall, ISBN: 0-13-507245-X)
   
   You might think of this as an advanced sequel to IFPH above, 
   although it focuses more on the theory behind program calculation:
   categories and allegories figure prominently, and it leans even 
   further in the direction indicated above. But there is nevertheless 
   a lot of good material here which can serve as a foundation for 
   design work, esp. the final chapters (7-10) on algorithms topics.

 * Algorithms: A Functional Programming Approach
   by Fethi Rabhi and Guy Lapalme (Addison-Wesley, ISBN: 0-201-59604-0)
   
   This is a concise tour through the usual gamut of data structures 
   and algorithms topics typical of a "CS 2" course, but from a 
   functional perspective. It is addressed more to people who are 
   already familiar with programming and with the "standard" approach
   to DSA issues. It works very well as a reference but includes 
   enough discussion to reward a straight reading.

 * Purely Functional Data Structures
   by Chris Okasaki (Cambridge University Press, ISBN: 0-521-66350-4)
   
   This one is similar to AFPA above (in being a tour of DSA topics from
   a functional perspective), but is a bit more advanced: e.g., Ch. 3
   covers leftist heaps, binomial heaps and red-black trees. It also
   addresses issues of analysis in the context of lazy evaluation more
   thoroughly (Banker's method, etc.). The examples are written using
   SML, but an appendix (and a website) give Haskell versions.

Of course, none of these books really answers the needs of the mature
programmer/blossoming functional programmer who seeks advice on
broader design issues in the context of lazy FP, esp. Haskell.
This gap leads me to propose the fanciful book mentioned above:

 * The Design Patterns Haskell Companion
   by [someone(s) reading this list?]

The title may be pandering a bit, but if the Smalltalk people can do it,
why can't we? :) . In fact, the title is based on "The Design Patterns
Smalltalk Companion" by Alpert, Brown and Woolf, a book I came across
while reading up on design patterns. (It was recommended by a customer
review on Amazon as being better than the original "gang of four" book.)

The "Smalltalk Companion" serves an audience of mature programmers and
attempts to document a number of "standard" design patterns in the
specific context of Smalltalk. I'm not sure that the Haskell community
would be comfortable referring to its collective design folklore in
these terms, but I'm sure we would all welcome a good book written at
this level which systematically addressed the motivation, rationale,
trade-offs, etc. of the more advanced techniques of FP (i.e., monads, 
type and constructor classes, Xa-morphisms (for various X), 
higher-order and nested datatypes, etc.).

As Johan mentioned, the "Advanced School" books serve this purpose to an
extent, but they differ from my vision in two respects: first, they are
collections of chapters on particular topics, written by different
authors, and thus don't form a consistent, systematic review. Second,
they are not (all) written from the specific perspective of design, so
that for example they don't provide as much comparison and contrast
*between* techniques.

Of course, another motivation for such a book is that it might lend an
air of credibility and maturity to the language, thus helping to 
promote it in the larger world. Casting it in terms of "design patterns"
would certainly make sense for these purposes (and probably guarantees
a certain audience, too), although I am still ambivalent about the need
for Haskell to become a huge hit with mainstream audiences.

In any case, if anyone is interested to write such a book, I will buy
a copy :) . And if anyone wishes to collabrate on it, I am willing
to help out. (I am not qualified to write it alone, and I think it 
would turn out best as a group effort in any case.)

  --  Fritz Ruehr
      fruehr@willamette.edu


From john@foo.net Fri Dec 29 08:37:45 2000 Date: Fri, 29 Dec 2000 00:37:45 -0800 From: John Meacham john@foo.net Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
I also like the approach of generalizing the record system, although I
have not evaluated your particular proposal. Speaking of record
improvements why is 
	http://www.cse.ogi.edu/~mpj/pubs/lightrec.html
not listed on the future of haskell page? has it already been determined
to not be in the future of haskell or has no one gotten around to it?
Does anyone else read this proposal and drool? 

Speaking of this proposal does anyone else see parallels between the
lightweight modules proposal and the implicit parameters proposal
http://www.cse.ogi.edu/~jlewis/implicit.ps.gz as implemented in ghc.

in particular implicit parameters seem like they would be able to be
implemented as syntatic sugar on the lightweight module system,

one could rewrite implicit parameters as every function taking a record
which we can call 'imp' now '?foo' can be rewritten as 'imp.foo' and the
'with ?foo = 1' construct can be rewritten as nimp = {imp | foo := 1}
and then passing nimp to all called functions. I have not thought this
too far thorough so I could be missing something obvious but I think it
shows potential at least for the unification of two popular extensions. 

and I am pretty sure this was too obvious to mention in the lightweight
records paper but the section of (.foo) being equivalent to 
(\{_|foo=v} -> v) seems appropriate.

	John

-- 
--------------------------------------------------------------
John Meacham   http://www.ugcs.caltech.edu/~john/
California Institute of Technology, Alum.  john@foo.net
--------------------------------------------------------------


From johanj@cs.uu.nl Fri Dec 29 10:48:58 2000 Date: Fri, 29 Dec 2000 11:48:58 +0100 From: Johan Jeuring johanj@cs.uu.nl Subject: Learning Haskell and FP
>Who are the audience for  the books on Advanced Functional Programming?
>Academics with a theoretical CS background or someone with just a bit of
>understanding of FP? Ideally, I would like a course suited for someone who
>has completed a basic FP course.

It varies a bit per school (book) and per article. But certainly LNCS 925
contains a number of chapters that should be interesting for someone with
a general CS background and a basic FP course. I know it has been used
in a couple of undergraduate courses on advanced functional programming.

Topics, Authors, LNCS nr:

- Monads, Wadler, 925
- Parser Combinators, Fokker, 925
- Constructor Classes, Jones, 925
- (Monadic) folds (or catamorphisms), Meijer & Jeuring, 925
- Space leaks and heap profiling, Runciman & Rojemo, 1129
- Algorithms and data structures, Okasaki, 1129
- Graph algorithms, Launchbury, 925
- User Interfaces, Carlsson & Hallgren, 925, Peyton Jones & Finne 1129

etc.

Johan Jeuring

http://www.cs.uu.nl/~johanj/


From franka@cs.uu.nl Fri Dec 29 13:31:01 2000 Date: Fri, 29 Dec 2000 14:31:01 +0100 From: Frank Atanassow franka@cs.uu.nl Subject: Learning Haskell and FP
Benjamin L. Russell wrote (on 28-12-00 17:35 -0500):

> > >> "Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho
> > [..] Is it OK if I show off and steal some thunder? :)

So much for that idea...!

> >   "(It's) An old pond! The sound of water steadily dripping in..."
> 
> Actually, if I may add, the translation I remember was the following:
> 
>    "[It's] An old pond!  The sound of water as the frog jumps in...."
> 
> "Kawazu" means "frog," and "tobikomu" means "(to) jump in."

That makes sense. I was guessing that "kawazu" was the old form of modern
"kawarazu" (`without changing'). Modern `frog' is "kaeru", though, and the
transitive form of "kawaru" (`change') is also "kaeru", so I suppose there is
some linguistic relationship. "tobikomu" makes much more sense this way too. I
thought it was a figurative usage, but it still didn't sound right...

-- 
Frank Atanassow, Information & Computing Sciences, Utrecht University
Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands
Tel +31 (030) 253-3261 Fax +31 (030) 251-379


From Doug_Ransom@pml.com Fri Dec 29 15:52:24 2000 Date: Fri, 29 Dec 2000 07:52:24 -0800 From: Doug Ransom Doug_Ransom@pml.com Subject: Haskell Language Design Questions
1.  Is the lack of dynamic binding of functions by design or because it was
too much effort to be justified at the time the language was designed?  In
object oriented programming there can be several implementations of the same
interface, and they can be stored in the same collection.

2.	It seems to me that the Maybe monad is a poor substitute for
exception handling because the functions that raise errors may not
necessarily support it.

For example, if I use someone elses custom type and a custom map function 

theirmap myApplicator SomeList

and theirmap is not designed to support the Maybe monad, then it becomes
hard to use if SomeFunction might raise an error.  

Am I missing something?





Doug Ransom
Systems Engineer
Power Measurement Ltd.
http://www.pml.com
250-652-7100 office
250-652-0411 fax
mailto:doug_ransom@pml.com


From israelt@optushome.com.au Fri Dec 29 06:50:36 2000 Date: Fri, 29 Dec 2000 16:50:36 +1000 From: i r thomas israelt@optushome.com.au Subject: Learning Haskell and FP
On 12/28/2000 at 7:00 PM Bill Halchin wrote:
>Hello IR,
>    I agree with the OU Haskell Tutorial. It is excellent!! 

Yes, with a bit of editing and more diagrams , it would probably be worth=
 publishing.

>BTW, what is your C# source?

The .NET Framework SDK is freely downloadable from MS ( around 100 megs )
and comes with a C# tutorial, C# reference and a command line C#.
There are also a few chapters online of some C# books that cover issues=
 like namespaces and attributes.
I am using the Antechinus C# editor as an IDE . This comes with a few basic=
 C# examples as well.
( for vi freaks, I have written a C# vim syntax file that will appear on=
 vim.org once it is polished up.)



From fjh@cs.mu.oz.au Sat Dec 30 03:50:04 2000 Date: Sat, 30 Dec 2000 14:50:04 +1100 From: Fergus Henderson fjh@cs.mu.oz.au Subject: Haskell Language Design Questions
On 29-Dec-2000, Doug Ransom <Doug_Ransom@pml.com> wrote:
> 1.  Is the lack of dynamic binding of functions by design or because it was
> too much effort to be justified at the time the language was designed?  In
> object oriented programming there can be several implementations of the same
> interface, and they can be stored in the same collection.

It's just something that didn't make it into Haskell 98.
Hugs and ghc offer a language extension for that.
It will almost certainly be in the next revision of Haskell.  See
<http://www.haskell.org/ghc/docs/latest/set/existential-quantification.html>.

> 2.	It seems to me that the Maybe monad is a poor substitute for
> exception handling because the functions that raise errors may not
> necessarily support it.

Hugs and ghc also have exception handling extensions.
See <http://www.haskell.org/ghc/docs/latest/set/sec-exception.html>.
There's also a paper or two on that.  I hope you'll forgive the
self-citation, but the only one for which I happen to have a reference
on-hand is this one:

	A semantics for imprecise exceptions. Simon Peyton-Jones,
	Alastair Reid, Tony Hoare, Simon Marlow, and Fergus Henderson.
	Proceedings of the 1999 ACM SIGPLAN Conference on Programming
	Language Design and Implementation, May 1999.

-- 
Fergus Henderson <fjh@cs.mu.oz.au>  |  "I have always known that the pursuit
                                    |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.


From qrczak@knm.org.pl Sat Dec 30 09:34:22 2000 Date: 30 Dec 2000 09:34:22 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Haskell Language Design Questions
Sat, 30 Dec 2000 14:50:04 +1100, Fergus Henderson <fjh@cs.mu.oz.au> pisze:

> It's just something that didn't make it into Haskell 98.
> Hugs and ghc offer a language extension for that.
> It will almost certainly be in the next revision of Haskell.  See
> <http://www.haskell.org/ghc/docs/latest/set/existential-quantification.html>.

Existential quantification is not always necessary to obtain an
equivalent of dynamic binding. Dynamic binding is often used instead
of function closures or IO action closures, especially in languages
which lack real closures.

An object of the abstract type "output IO stream" is equivalent to
a record (tuple, whatever) of values of types like
    Char   -> IO () -- write a character
    String -> IO () -- write a string
    IO ()           -- flush
    IO ()           -- close

"Dynamic binding" is a fancy way of saying that the function to be
called will be chosen at runtime. So we have exactly this, expressed
in a simpler way.

OO languages provide subtyping and inheritance. This is harder.
Subtyping done by explicit coercions up can be done, but it's tedious
to write (my new record scheme proposal tries to help here), and it's
impossible to coerce down. Inheritance can be done by delegation.

It does not work to express everything like OO languages usually do,
because they are not typesafe. That's why (IMHO) that OO languages are
usually dynamically typed. OO-like subtyping is usually not able to
accurately express binary methods or the requirement that an argument
must provide several interfaces at once.

Haskell's classes should be left for constraints on types (as opposed
to values). I want to sort a list, I compare elements with each
other. It does not make sense to say that an element is comparable.
Comparable with what? A _type_ can be comparable (i.e. ordered),
or the ordering itself may be expressed as an object, but it does
not belong to objects being compared. It follows that it does not
make sense to have "a heterogeneous collection of comparable objects"
or casting an object up to the type "comparable".

But I might not care if the fact that something is a stream open for
writing is a property of its type which is not statically known (as
when stream is modelled as a class) or a property of all objects of the
given type which is concrete (as when stream is modelled as a record
of functions) - because I usually work with one such object at a time.

When it's expressed as a class, I gain the possibility of extracting
from the same object at different places properties belonging to
different interfaces, without explicit coercions. But it is necessary
to use existential quantification for heterogeneous collections.
When it's expressed as a record of functions, all streams are flattened
to a single interface, it is more convenient to use but the information
about the exact kind of stream is not available.

These approaches can be mixed. With my new record scheme proposal
it is more convenient to introduce a class of types of objects from
which the interface of a stream open for writing (expressed as a
record of functions) can be extracted. This class needs not to be
explicitly defined (only the record of functions). Stream operations
can also be seen as provided by the object itself instead of always
going through the extracted interface.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From R.Daniel@Europe.com Sat Dec 30 15:16:30 2000 Date: Sat, 30 Dec 2000 15:16:30 +0000 From: R.Daniel R.Daniel@Europe.com Subject: The Hanoi Towers
--=====================_12490613==_.ALT
Content-Type: text/plain; charset="us-ascii"; format=flowed

hi, i was looking for the source code for the Hanoi Towers, if anyone has 
that, could you please send it to me?

I apreciate the help , thankx

----->R.Daniel Aka AZONIC
         ICQ           28959546
--=====================_12490613==_.ALT
Content-Type: text/html; charset="us-ascii"

<html>
hi, i was looking for the source code for the Hanoi Towers, if anyone has
that, could you please send it to me? <br>
<br>
I apreciate the help , thankx<br>
<x-sigsep><p></x-sigsep>
-----&gt;R.Daniel Aka AZONIC<br>
&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;
<font color="#0000FF">ICQ&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp;
28959546</font></html>

--=====================_12490613==_.ALT--



From qrczak@knm.org.pl Sat Dec 30 17:53:05 2000 Date: 30 Dec 2000 17:53:05 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)
Fri, 29 Dec 2000 00:37:45 -0800, John Meacham <john@foo.net> pisze:

> http://www.cse.ogi.edu/~mpj/pubs/lightrec.html

I've read it and posted some comments in February 2000. There was no
answer AFAIR. Here are they again, slightly edited and extended:

I don't understand why to separate kinds of rows and record types,
instead of having "a type which is known to be a record type", at
least on the level visible for the programmer. So instead of
    type Point        r = (r | x::Int, y::Int)
    type Colored      r = (r | c::Color)
    type ColoredPoint r = Point (Colored r)
    p :: {ColoredPoint()}
    -- Point, Colored, ColoredPoint :: row -> row
it would be
    type Point        r = {r | x::Int, y::Int}
    type Colored      r = {r | c::Color}
    type ColoredPoint r = Point (Colored r)
    p :: ColoredPoint()
    -- Point, Colored, ColoredPoint :: recordType -> recordType
    -- where recordType is something like a subkind of *.

                                --------

It is bad to require the programmers to think in advance that a type
is going to be subtyped, and write elaborated
    type Point r = (r | x::Int, y::Int)
    ... {Point()} ...
instead of simpler
    type Point = {x::Int, y::Int}
    ... Point ...
which is not extensible.

                                --------

I got used to () as a unit type. It would be a pity to lose it.

                                --------

A minor problem. If tuples are records, field names should be such
that alphabetic order gives the sequential order of fields, or have
a special rule of field ordering for names of tuple fields...

                                --------

In general I don't quite like the fact that records are getting more
anonymous. Magical instances of basic classes? How inelegant.

If I want the record type to have an identity, it will have to be
wrapped in a newtype, so I must think at the beginning if I will ever
want to write specialized insances for it and then all the code will
depend on the decision. Currently a datatype with named fields has
both an identity and convenient syntax of field access. (And why
newtype is not mentioned in section 5.1?)

I like name equivalence where it increases type safety. Extensible
records promote structural equivalence.

Unfortunately the proposal seems to increase the number of
irregularities and inelegant rules...

If expr.Constructor for a multiparameter constructor yields a tuple,
then for an unary constructor it should give a 1-tuple, no? I know
it would be extremely inconvenient, especially as newtypes are more
used, so I don't propose it, but it is getting less regular. What
about nullary constructors - empty tuple? :-)

I don't say that I don't like the proposal at all, or that I never
wanted to have several types with the same field names. But it is
not clean for me, it's a compromise between usability and elegance,
and from the elegance point of view I like current records more.

Maybe it would be helpful to show how to translate a program with
extensible records to a program without them (I guess it's possible
in a quite natural way, but requires global transformation of the
whole program).

                                --------

Extensible records makes a syntactic difference between field access
and function call. So if one wants to export a type abstractly or
simply to provide functions operating on it without fixing the fact
that they are physically fields, he ends in writing functions like

size:: MyRecord -> Int
size x = x.MyRecord.size

which are unnecessary now, even if size is simply a field.

It reminds me of C++ which wants us to provide methods for accessing
data fields (for allowing them to be later redefined as methods,
and for allowing everything to be uniformly used with "()" after the
feature name). Ugh.

                                --------

My new record scheme proposal does not provide such lightweight
extensibility, but fields can be added and deleted in a controlled
way if the right types and instances are made.

The distinction between having a field and having a supertype is
blurred. Similarly between having itself a field called foo and having
a supertype which has a field called foo. Similarly between creating
a record by adding fields to another record and creating a record by
putting another record as one of fields. Similarly between casting
to a supertype by removing some fields and extracting the supertype
represented by a field.

An advantage is that the interface of records does not constrain the
representation in any way. It's up to how instances are defined,
with the provision of natural definitions for records implemented
physically as product types.

For example supplying a color for a colorless point and the reverse
operation can be written thus:
    addColor :: (Record cp, cp.point :: p, cp.color :: Color)
             => p -> Color -> cp
    addColor p c = record point = p; color = c

    removeColor :: (cp.point :: p) => cp -> p
    removeColor = (.point)

When the following definitions are present:
    data Point = record
        x, y :: Int
    data ColoredPoint = record
        point :: Point
        point (x, y)
        color :: Color
these functions can be used as of types
    addColor    :: Point -> Color -> ColoredPoint
    removeColor :: ColoredPoint -> Point

A colored point can be constructed either as in addColor, from a
point and a color, or thus:
    record
        x     = ...
        y     = ...
        color = ...

If ColoredPoint were defined directly as
    data ColoredPoint = record
        x, y  :: Int
        color :: Color
the previous interface could be *retroactively* reconstructed thus:
    instance (ColoredPoint).point :: Point where
        cp.point = record x = cp.x; y = cp.y
        cp.record {point = p} = cp.record x = p.x; y = p.y

Multiple inheritance can be modelled as well. And field renaming
during inheritance.

-- 
 __("<  Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/
 \__/
  ^^                      SYGNATURA ZASTĘPCZA
QRCZAK



From kahl@heraklit.informatik.unibw-muenchen.de Fri Dec 22 16:04:45 2000 Date: 22 Dec 2000 16:04:45 -0000 From: Wolfram Kahl kahl@heraklit.informatik.unibw-muenchen.de Subject: 2nd CFP: RelMiS 2001
[please post.  apologies for multiple copies]


                            SECOND CALL FOR PAPERS


                RelMiS 2001 - Relational Methods in Software
                ============================================

                        7-8 April 2001, Genova, Italy

                     http://ist.unibw-muenchen.de/RelMiS/

                       A Satellite Event to ETAPS 2001


Important Dates
===============

Deadline for submission:    10 January  2001
Notification of acceptance:  9 February 2001
Final version due:          28 February 2001
Workshop dates:            7-8 April    2001


Workshop Topics
===============

* Relational Specifications and Modelling:
     methods and tools, tabular methods, abstract data types
* Relational Software Design and Development Techniques:
     relational refinement, heuristic approaches for derivation, correctness
     considerations, dynamic programming, greedy algorithms, catamorphisms,
     paramorphisms, hylomorphisms and related topics
* Programming with Relations:
     prototyping, testing, fault tolerance, information systems, information
     coding
* Implementing relational algebra with mixed representation of relations
* Handling of Large Relations:
     problems of scale, innovative representations, distributed
     implementation


Submissions
===========

Submissions will be evaluated by the Program Committee for inclusion in the
proceedings, which will be published in the ENTCS series. Papers must
contain original contributions, be clearly written, and include appropriate
reference to and comparison with related work. Papers should be submitted
electronically as uuencoded PostScript files at the address
relmis@ist.unibw-muenchen.de. Preference will be given to papers that are no
shorter than 10 and no longer than 15 pages. A separate message should also
be sent, with a text-only one-page abstract and with mailing addresses (both
postal and electronic), telephone number and fax number of the corresponding
author.

Final versions will have to be submitted as LaTeX source and have to adhere
to the ENTCS style!


Programme Committee
===================

Rudolf Berghammer (Kiel), Jules Desharnais (Quebec), Wolfram Kahl (Munich),
David L. Parnas (Hamilton), Gunther Schmidt (Munich)


-------------

E-Mail: relmis@ist.unibw-muenchen.de
Workshop home page: URL: http://ist.unibw-muenchen.de/RelMiS/



From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 11:03:58 2000 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Fri, 1 Dec 2000 11:03:58 +0000 Subject: a trap for the unwary Message-ID: Today, I thought I had discovered a bug in ghc. Then I tried hbc and Hugs, and they also rejected my program with the same error. nhc98 alone accepts it without complaint. I looked up the Report, and it seems that the program is indeed incorrect. Quick quiz: without running this through a compiler, who can spot the mistake? :-) > module Main where > import Char > f x = y > where > y | isSpace x = True > y | otherwise = False > main = print (f 'x') Regards, Malcolm From wimjan@xs4all.nl Fri Dec 1 14:49:13 2000 From: wimjan@xs4all.nl (Wim-Jan Hilgenbos) Date: Fri, 01 Dec 2000 15:49:13 +0100 Subject: Beginner: error when using multiple where stmts in hugs98 Message-ID: <3A27BA68.4EE70883@xs4all.nl> This is a multi-part message in MIME format. --------------F1E92FD1F075259053A3C4BA Content-Type: text/plain; charset=us-ascii Content-Transfer-Encoding: 7bit Hi, I've been trying some examples in functional programming. Most things work fine, but I have trouble with expressions with 'where' clauses that define more then one local definition. (I work with hugs98 version september 1999 under Linux) For example: ----------[ Mydiff.hs ]---------------------- module Mydiff where mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 ----------[ end Mydiff.hs ]------------------- When I try to load this module I get ERROR "Mydiff.hs" (line 5): Syntax error in input (unexpected `=') line 5 is the line h = 0.0001 I tried other examples like this one, played around with line-breaks white-space etc. Rewriting the f' line to f' x = (f (x+0.0001) - f x) / 0.0001 does the trick, but is not very satisfying. Can anyone help? WJ PS. I attached above example -- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Disclaimer: "These opinions are my own, though for a small fee they be yours too." -- Dave Haynie --------------F1E92FD1F075259053A3C4BA Content-Type: text/plain; charset=us-ascii; name="Mydiff.hs" Content-Transfer-Encoding: 7bit Content-Disposition: inline; filename="Mydiff.hs" module Mydiff where mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 --------------F1E92FD1F075259053A3C4BA-- From jmaessen@mit.edu Fri Dec 1 15:41:32 2000 From: jmaessen@mit.edu (Jan-Willem Maessen) Date: Fri, 1 Dec 2000 10:41:32 -0500 Subject: a trap for the unwary Message-ID: <200012011541.KAA00635@lauzeta.mit.edu> Malcolm Wallace writes: > Quick quiz: without running this through a compiler, who can spot > the mistake? :-) > > > module Main where > > import Char > > f x = y > > where > > y | isSpace x = True > > y | otherwise = False -- ** The problem line? > > main = print (f 'x') Without running this through the compiler, but based on similar problems I've had recently, I'd assume the problem is the marked line. Two outer-level patterns are each presented with guards. This would be correct for a function definition: > f x = y () > where > y _ | isSpace x = True > y _ | otherwise = False -- ** Does this work? This is a tricky issue. I'd like the original program to be all right. We end up sowing confusion with erroneous programs like this one: > f x = y > where > y | otherwise = False -- ** Now this pattern overlaps! > y | isSpace x = True But of course an analogous problem occurs in the function definition, and I think can be caught by turning on warnings in ghc. -Jan-Willem Maessen jmaessen@mit.edu From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 15:44:16 2000 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Fri, 1 Dec 2000 15:44:16 +0000 Subject: a trap for the unwary In-Reply-To: <200012011541.KAA00635@lauzeta.mit.edu> Message-ID: > > > f x = y > > > where > > > y | isSpace x = True > > > y | otherwise = False -- ** The problem line? Correct. Here y is a pattern binding, and multiple pattern bindings of the same variable are not permitted. > f x = y () > where > y _ | isSpace x = True > y _ | otherwise = False -- ** Does this work? Correct. Here y is a function binding instead, and multiple clauses *are* permitted. > I'd like the original program to be all right. Me too. I wrote 'y' as a 0-arity function, knowing that because it used a free variable bound at an outer scope, it would probably be lambda-lifted to a greater arity by the compiler. But only one compiler saw it in the same way as I did. :-) Of course, if the pattern binding is more complex than a single variable name, I still want the no-multiple-bindings rule to apply as usual: > f x = y () > where > (y:_) | isSpace x = [True] > (y:_) | otherwise = [False] -- ** Definitely wrong and indeed all compilers reject this, as they should. Regards, Malcolm From schulzs@uni-freiburg.de Fri Dec 1 17:23:57 2000 From: schulzs@uni-freiburg.de (Sebastian Schulz) Date: Fri, 01 Dec 2000 17:23:57 +0000 Subject: Beginner: error when using multiple where stmts in hugs98 References: <3A27BA68.4EE70883@xs4all.nl> Message-ID: <3A27DEAD.6FED7B7@shamoha.de> Wim-Jan Hilgenbos wrote: > > Hi, > > I've been trying some examples in functional programming. Most things > work fine, > but I have trouble with expressions with 'where' clauses that define > more then one > local definition. > (I work with hugs98 version september 1999 under Linux) > > For example: > > ----------[ Mydiff.hs ]---------------------- > module Mydiff where > > mydiff f = f' > where f' x = ( f (x+h) - f x) / h > h = 0.0001 > > ----------[ end Mydiff.hs ]------------------- > Try this: mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 It works fine with Hugs98 (feb2000). regards seb From ron4ld@pacific.net.au Fri Dec 1 21:08:56 2000 From: ron4ld@pacific.net.au (Ronald Kuwawi) Date: Sat, 02 Dec 2000 08:08:56 +1100 Subject: old easter egg Message-ID: <3A281368.7D24E3DC@pacific.net.au> open text editor, type hash :: [Char] -> Int hash = (foldl (+) 0) . (map ord) save as hash.hs load script, type: hash "MSDOS 6.000" or hash "SYSTEM 7.0" :-) Ronald From zhanyong.wan@yale.edu Fri Dec 1 21:55:06 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Fri, 01 Dec 2000 16:55:06 -0500 Subject: old easter egg References: <3A281368.7D24E3DC@pacific.net.au> Message-ID: <3A281E3A.66187BC7@yale.edu> Ronald Kuwawi wrote: > > open text editor, type > hash :: [Char] -> Int > hash = (foldl (+) 0) . (map ord) > > save as hash.hs > > load script, type: > hash "MSDOS 6.000" > > or > > hash "SYSTEM 7.0" or hash "HASKELL%98" :-) -- Zhanyong Wan From peterson-john@cs.yale.edu Fri Dec 1 22:14:41 2000 From: peterson-john@cs.yale.edu (John Peterson) Date: Fri, 1 Dec 2000 17:14:41 -0500 Subject: The Haskell store is open .... Message-ID: <200012012214.RAA28801@ragged.cs.yale.edu> Head to http://www.cafepress.com/haskell for your holiday shopping. Thanks to Conal Elliott and Fritz Ruehr for their artwork. Conal's design was produced by Pan so this shirt is in fact powered by Haskell! I'll be glad to add more designs in the future. Once cafepress lets me put more than one design in a store I'll consolidate everything. Meanwhile, if you want to set up a separate store I can link it into haskell.org for you. John From jf15@hermes.cam.ac.uk Sat Dec 2 00:03:30 2000 From: jf15@hermes.cam.ac.uk (Jon Fairbairn) Date: Sat, 2 Dec 2000 00:03:30 +0000 (GMT) Subject: old easter egg In-Reply-To: <3A281E3A.66187BC7@yale.edu> Message-ID: On Fri, 1 Dec 2000, Zhanyong Wan wrote: >=20 > Ronald Kuwawi wrote: > >=20 > > open text editor, type > > hash :: [Char] -> Int > > hash =3D (foldl (+) 0) . (map ord) > hash "HASKELL%98" hash "Haskell Ninety Eight !!"=20 surely? --=20 J=F3n Fairbairn Jon.Fairbairn@cl.cam.ac.uk From kili@outback.escape.de Sat Dec 2 02:31:05 2000 From: kili@outback.escape.de (Matthias Kilian) Date: Sat, 2 Dec 2000 03:31:05 +0100 (CET) Subject: old easter egg In-Reply-To: Message-ID: On Sat, 2 Dec 2000, Jon Fairbairn wrote: > > hash "HASKELL%98" > > > hash "Haskell Ninety Eight !!" Here's the who;e truth: hash "Turing!" Kili --=20 Nunja! Wenn man erst einmal anf=E4ngt zu denken, dann ist es wie eine Sucht. Man kommt nicht mehr los davon. [WoKo in dag=B0, 28.11.2000] From ashley@semantic.org Sat Dec 2 19:08:53 2000 From: ashley@semantic.org (Ashley Yakeley) Date: Sat, 2 Dec 2000 11:08:53 -0800 Subject: old easter egg Message-ID: <200012021908.LAA10458@mail4.halcyon.com> At 2000-12-01 13:08, Ronald Kuwawi wrote: >open text editor, type >hash :: [Char] -> Int >hash = (foldl (+) 0) . (map ord) > >save as hash.hs > >load script, type: >hash "MSDOS 6.000" > >or > >hash "SYSTEM 7.0" It's not really an easter egg, is it? It's more a modern form of numerology. I was hoping to see the hugs environment show me a little dancing bunny animation or something. letter c | ord c <= 64 = 0 letter c | ord c <= 90 = ord c - 64 letter c | ord c <= 96 = 0 letter c | ord c <= 122 = ord c - 96 letter c | otherwise = 0 renum n | n == 0 = 0 renum n | otherwise = (mod ((n - 1) * 19) 26) + 1 engql c = renum (letter c) engq = (foldl (+) 0) . (map engql) -- Ashley Yakeley, Seattle WA From gmh@marian.cs.nott.ac.uk Mon Dec 4 08:54:00 2000 From: gmh@marian.cs.nott.ac.uk (gmh@marian.cs.nott.ac.uk) Date: Mon, 4 Dec 2000 8:54:00 GMT Subject: JFP Special Issue on Haskell Message-ID: <20001204085501.0EA3F1016@www.haskell.org> Dear all, Please note that the deadline for submission to the JFP Special Issue on Haskell is in two months time --- 1st February 2001. Graham Hutton ---------------------------------------------------------------------- CALL FOR PAPERS Journal of Functional Programming Special Issue on Haskell Since its inception in 1987, Haskell has provided a focal point for research in lazy functional programming. During this time the language has continually evolved, as a result of both theoretical advances and practical experience. Haskell has proved to be a powerful tool for many kinds of programming tasks, and applications in industry are beginning to emerge. The recent definition of Haskell 98 provides a long-awaited stable version of the language, but there are many exciting possibilities for future versions of Haskell. The fourth Haskell Workshop was held as part of the PLI 2000 colloquium on Principles, Logics, and Implementations of high-level programming languages in Montreal, 17th September 2000. Previous Haskell Workshops have been held in Paris (1999), Amsterdam (1997) and La Jolla (1995). Following on from these workshops, a special issue of the Journal of Functional Programming will be devoted to Haskell. Possible topics include, but are not limited to: Critiques of Haskell 98; New proposals for Haskell; Applications or case studies; Programming techniques; Reasoning about programs; Semantic issues; Pedagogical issues; Implementation. Contributors to any of the Haskell workshops are invited to submit full papers to the special issue on Haskell, but submission is open to everyone. Submissions should be sent to the guest editor (address below), with a copy to Nasreen Ahmad (nasreen@dcs.gla.ac.uk). Submitted articles should be sent in postscript format, preferably gzipped and uuencoded. In addition, please send, as plain text, title, abstract, and contact information. The submission deadline is 1st February 2001. For other submission details, please consult an issue of JFP or see the Journal's web pages. Guest Editor: Graham Hutton School of Computer Science and IT The University of Nottingham Nottingham NG8 1BB United Kingdom gmh@cs.nott.ac.uk Useful Links: 2000 Haskell Workshop www.cs.nott.ac.uk/~gmh/hw00.html JFP Special Issue on Haskell www.cs.nott.ac.uk/~gmh/jfp.html JFP Home Page www.dcs.gla.ac.uk/jfp ---------------------------------------------------------------------- From zhanyong.wan@yale.edu Mon Dec 4 16:04:24 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Mon, 04 Dec 2000 11:04:24 -0500 Subject: Rank-2 polymorphism & type inference Message-ID: <3A2BC088.11497DEA@yale.edu> Hello, I'm playing with Haskell's rank-2 polymorphism extension and am puzzled by the following example: ----------------------------------------------------------- module R2Test where class SubType a b where super :: a -> b data Sub c a = Sub data Super c a = Super instance SubType (Sub c a) (Super c a) f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b f g x = undefined x :: Sub c Int x = undefined y :: Super c Int y = f (\a -> super a) x ---------------------------------------------------------- I though the definition of y should type-check because (roughly): 1. We know x :: Sub c Int, y :: Super c Int 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b, we know a is Int and b is Int. 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we are all set. However, Hugs 98 Feb 2000 (with the -98 switch) gives me: ERROR "R2Test.hs" (line 19): Cannot justify constraints in application *** Expression : \a -> super a *** Type : Sub b _1 -> Super b _2 *** Given context : () *** Constraints : SubType (Sub b _1) (Super b _2) and GHC 4.08.1 (with the -fglasgow-exts switch) gives: R2Test.hs:19: Could not deduce `SubType (Sub c a) (Super c Int)' from the context: () Probable cause: missing `SubType (Sub c a) (Super c Int)' in the type signature of an expression or missing instance declaration for `SubType (Sub c a) (Super c Int)' arising from use of `super' at R2Test.hs:16 In the right-hand side of a lambda abstraction: super a If I remove the "forall c." from the type signature for f, then both compilers accept my code. My question is: how does the type inference algorithm work in the presence of rank-2 types? Does anyone know of any documentation on this? Thanks! -- Zhanyong # Zhanyong Wan http://pantheon.yale.edu/~zw23/ ____ # Yale University, Dept of Computer Science /\___\ # P.O.Box 208285, New Haven, CT 06520-8285 ||___| From zhanyong.wan@yale.edu Mon Dec 4 21:30:46 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Mon, 04 Dec 2000 16:30:46 -0500 Subject: Rank-2 polymorphism & type inference References: <3A2BC088.11497DEA@yale.edu> Message-ID: <3A2C0D06.69F3058D@yale.edu> Hi, After sending out my question, I noticed that hugs and ghc understood my code differently: from the error messages, we can see that hugs view (\a -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it is Sub c a -> Super c Int. To verify it, I changed my code s.t. y is defined as y = f (\(a :: Sub c Int) -> super a) x instead of y = f (\a -> super a) x Guess what happened: ghc *accepted* the code, and hugs *rejected* it with message: ERROR "R2Test.hs" (line 19): Cannot justify constraints in application *** Expression : \a -> super a *** Type : Sub b Int -> Super b _2 *** Given context : () *** Constraints : SubType (Sub b Int) (Super b _2) Aha, this is something interesting! Either there is no standard for the Haskell rank-2 type inference algorithm (which is a sad thing), or one of hugs and ghc is wrong here. Now the hugs/ghc guys on the list can no longer remain silent -- you got to defend yourselves! :-) Could anyone explain to me what the right behavior is supposed to be here? Thanks. -- Zhanyong Zhanyong Wan wrote: > > Hello, > > I'm playing with Haskell's rank-2 polymorphism extension and am puzzled > by the following example: > > ----------------------------------------------------------- > module R2Test where > > class SubType a b where > super :: a -> b > > data Sub c a = Sub > data Super c a = Super > > instance SubType (Sub c a) (Super c a) > > f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b > f g x = undefined > > x :: Sub c Int > x = undefined > > y :: Super c Int > y = f (\a -> super a) x > ---------------------------------------------------------- > > I though the definition of y should type-check because (roughly): > > 1. We know x :: Sub c Int, y :: Super c Int > 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c > b, we know a is Int and b is Int. > 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we > are all set. > > However, Hugs 98 Feb 2000 (with the -98 switch) gives me: > > ERROR "R2Test.hs" (line 19): Cannot justify constraints in application > *** Expression : \a -> super a > *** Type : Sub b _1 -> Super b _2 > *** Given context : () > *** Constraints : SubType (Sub b _1) (Super b _2) > > and GHC 4.08.1 (with the -fglasgow-exts switch) gives: > > R2Test.hs:19: > Could not deduce `SubType (Sub c a) (Super c Int)' > from the context: () > Probable cause: missing `SubType (Sub c a) (Super c Int)' > in the type signature of an expression > or missing instance declaration for `SubType (Sub c > a) (Super > c Int)' > arising from use of `super' at R2Test.hs:16 > In the right-hand side of a lambda abstraction: super a > > If I remove the "forall c." from the type signature for f, then both > compilers accept my code. > > My question is: how does the type inference algorithm work in the > presence of rank-2 types? Does anyone know of any documentation on > this? Thanks! From simonpj@microsoft.com Tue Dec 5 13:12:20 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 5 Dec 2000 05:12:20 -0800 Subject: Rank-2 polymorphism & type inference Message-ID: <74096918BE6FD94B9068105F877C002D013781CA@red-pt-02.redmond.corp.microsoft.com> | > My question is: how does the type inference algorithm work in the | > presence of rank-2 types? Does anyone know of any documentation on | > this? Thanks! I had a look at this. Actually it turns out to be only loosely related to rank-2 polymorphism. I've been able to reproduce your problem using only Haskell 98. It looks like a problem with incomplete type inference Consider this: module MP where class C t where op :: t -> Bool instance C [t] where op x = True test :: [Int] -> Bool -- REQUIRED! test y = let f :: c -> Bool f x = op (y >> return x) in f (y::[Int]) Both GHC and Hugs reject this module if the type signature for test is omitted. NHC (v1.00, 2000-09-15) falls over completely, with Fail: Prelude.chr: bad argument All three succeed if the signature is in, or if the signature for f is omitted. This was unexpected, to me at least. You may need to add a type signature if polymorphic recursion is being used, but here it isn't! The problem is this: the compiler learns that y::[Int] "too late" to make use of it when solving the constraints arising from the RHS of f. In more detail, here's what happens. First we typecheck the RHS of f, deducing the types x :: a where a is fresh y :: k a where k is fresh y >> return x :: k a op (y >> return x) :: Bool with constraint C (k a) \x -> op (y >> return x) :: a -> Bool with constraint C (k a) Now we try to generalise over a. We need to discharge the contraint C (k a). Later we will find that y::[Int], so k=[], but we don't know that yet. So we can't solve the constraint. Adding the type signature to 'f' lets both GHC and Hugs figure out that y::[Int] in advance, so we need to solve the constraint C ([] a), which is fine. So I think you have uncovered a genuine problem, and one I don't know how to solve. It can always be "solved" by adding more type information, such as the type sig for 'test'. In you case you said: | After sending out my question, I noticed that hugs and ghc understood my | code differently: from the error messages, we can see that hugs view (\a | -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it | is Sub c a -> Super c Int. To verify it, I changed my code s.t. y is | defined as | | y = f (\(a :: Sub c Int) -> super a) x This is exactly right, and GHC is happy now. I can't account for Hugs' behaviour. The "right" solution is presumably to defer all constraint checking until we know what 'k' is. But that's a bit tricky because the constraint checking generates bindings that must appear in f's RHS. A full solution looks a bit over-kill-ish. But it's unsettling that the inference algorithm is incomplete. Simon From johanj@cs.uu.nl Tue Dec 5 14:22:06 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Tue, 05 Dec 2000 15:22:06 +0100 Subject: Call for papers: Haskell Workshop 2001 In-Reply-To: Message-ID: <20001205142154.B18FA451B@mail.cs.uu.nl> ============================================================================ CALL FOR PAPERS 2001 Haskell Workshop Firenze, Italy The Haskell Workshop forms part of the PLI 2001 colloquium on Principles, Logics, and Implementations of high-level programming languages, which comprises the ICFP/PPDP conferences and associated workshops. Previous Haskell Workshops have been held in La Jolla (1995), Amsterdam (1997), Paris (1999), and Montreal (2000). http://www.cs.uu.nl/people/ralf/hw2001.{html,pdf,ps,txt} ============================================================================ Scope ----- The purpose of the Haskell Workshop is to discuss experience with Haskell, and possible future developments for the language. The scope of the workshop includes all aspects of the design, semantics, theory, application, implementation, and teaching of Haskell. Submissions that discuss limitations of Haskell at present and/or propose new ideas for future versions of Haskell are particularly encouraged. Adopting an idea from ICFP 2000, the workshop also solicits two special classes of submissions, application letters and functional pearls, described below. Application Letters ------------------- An application letter describes experience using Haskell to solve real-world problems. Such a paper might typically be about six pages, and may be judged by interest of the application and novel use of Haskell. Functional Pearls ----------------- A functional pearl presents - using Haskell as a vehicle - an idea that is small, rounded, and glows with its own light. Such a paper might typically be about six pages, and may be judged by elegance of development and clarity of expression. Submission details ------------------ Deadline for submission: 1st June 2001 Notification of acceptance: 1st July 2001 Final submission due: 1st August 2001 Haskell Workshop: to be announced Authors should submit papers of at most 12 pages, in postscript format, formatted for A4 paper, to Ralf Hinze (ralf@cs.uu.nl) by 1st June 2001. The use of the ENTCS style files is strongly recommended. Application letters and functional pearls should be labeled as such on the first page. They may be any length up to twelve pages, though shorter submissions are welcome. The accepted papers will be published as a University of Utrecht technical report. Programme committee ------------------- Manuel Chakravarty University of New South Wales Jeremy Gibbons University of Oxford Ralf Hinze (chair) University of Utrecht Patrik Jansson Chalmers University Mark Jones Oregon Graduate Institute Ross Paterson City University, London Simon Peyton Jones Microsoft Research Stephanie Weirich Cornell University ============================================================================ From simonpj@microsoft.com Tue Dec 5 17:18:18 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 5 Dec 2000 09:18:18 -0800 Subject: Rank-2 polymorphism & type inference Message-ID: <74096918BE6FD94B9068105F877C002D013781D6@red-pt-02.redmond.corp.microsoft.com> Musing on Zhanyong's problem some more, a solution occurs to me. Curiously, it's exactly the solution required for another useful extension to type classes. Here is is, so people can shoot holes in it. | In more detail, here's what happens. First we typecheck the RHS of | f, deducing the types | | x :: a where a is fresh | y :: k a where k is fresh | y >> return x :: k a | op (y >> return x) :: Bool with constraint C (k a) | \x -> op (y >> return x) :: a -> Bool with constraint C (k a) | | Now we try to generalise over a. We need to discharge the contraint | C (k a). Later we will find that y::[Int], so k=[], but we | don't know that yet. So we can't solve the constraint. One bad solution I thought of was to give f the type f :: forall a. C (k a) => a -> Bool This is bad because it's not the type signature the programmer specified. (It's also bad operationally because we'll pass a dictionary at runtime, which isn't necessary.) The good solution is to say this: \x -> op (y >> return x) :: a -> Bool with constraint C (k a) (just as before) /\a \x -> op (y>>return x) :: forall a. a -> Bool with constraint (forall a. C (k a)) This requires us to permit constraints with for-alls in them. As luck would have it, Ralf Hinze and I propose just such a thing in our paper "Derivable Type Classes" (Section 7) http://research.microsoft.com/~simonpj/#derive The motivation there is this: how can you write an equality instance for data T k a = MkT (k (T k a)) We can try: instance ... => Eq (T k a) where (MkT a) == (MkT b) = a == b But what is the "..."? We need that "k" is an equality type constructor. The right context is instance (forall a. Eq a => Eq (k a)) => Eq (T k a) where ...as before... Aha! A constraint with a for-all. There are some more details in the paper. So perhaps there's a reason for adding this extension in the implementation (to solve Zhanyong's problem) even for a Haskell 98 compiler. Simon From francois.xavier.bodin@winealley.com Wed Dec 6 19:52:00 2000 From: francois.xavier.bodin@winealley.com (francois.xavier.bodin@winealley.com) Date: Wed, 6 Dec 2000 20:52 +0100 Subject: Meet us on Wine Alley Message-ID: <20001206195207.C9A321034@www.haskell.org> Hello! I found your address on a site about wine, food and good living. I thought = that you will be interested by the services that our site offers. www.wine-alley.com is a virtual Club for all those interested in wine in bo= th a professional and personal capacity. We now have more than 3900 members, both amateur and in the trade who use o= ur site to discuss wine, buy and sell it and tell us about the best sources. Club members use the Newsgroup of www.wine-alley.com to exchange informatio= n and experiences. Only the other day someone asked how much a certain rar= e wine was worth, I asked for more information about the grape variety, whi= ch doesn't grow in France. Currently there have been more than 717 question= s and replies. There is also the small ads. column. Among the 7 adverts placed this week there have been some really good deals= including a magnum of 1945 Pichon Lalande and a 1947 Cheval blanc! Let me make it clear - www.wine-alley.com itself does not sell or buy wine:= we simply offer our members the facilites for making their own arrangement= s. www.wine-alley.com is also a site supplying information in real time, parti= cularly the latest news from winegrowers and makers via the French Press Ag= ency (AFP). We also have a database of more than 21,000 wines with informa= tion supplied directly to the site by winegrowers co-operatives and special= ist magazines. I should be delighted if you would come and join us. At www.wine-alley.com= you will find similarly-minded people who just want to share their love of= wine. Kind regards Fran=E7ois Xavier Bodin, Manager of the Online Club fx.bodin@winealley.com PS. Registering with the www.wine-alley.com club is absolutely free and co= mmits you to nothing. If you are not interested in my offer, please excuse this letter; I am sorr= y to have bothered you. To prevent further unwanted intrusions please clic= k on the following link, your email will be automatically removed from our = list. http://www.wine-alley.com/wines/desmail.asp?id=3D307392&l=3Duk From harald@cs.mu.OZ.AU Mon Dec 11 13:13:58 2000 From: harald@cs.mu.OZ.AU (Harald Sondergaard) Date: Tue, 12 Dec 2000 00:13:58 +1100 Subject: PPDP 2001: Call for Papers Message-ID: <200012111314.AAA03065@mundook.cs.mu.OZ.AU> Third International Conference on PRINCIPLES AND PRACTICE OF DECLARATIVE PROGRAMMING Firenze, Italy, 5-7 September 2001 CALL FOR PAPERS PPDP 2001 aims to stimulate research on the use of declarative methods in programming and on the design, implementation and application of programming languages that support such methods. Topics of interest include any aspect related to understanding, integrating and extending programming paradigms such as those for functional, logic, constraint and object-oriented programming; concurrent extensions and mobile computing; type theory; support for modularity; use of logical methods in the design of program development tools; program analysis and verification; abstract interpretation; development of implementation methods; application of the relevant paradigms and associated methods in industry and education. This list is not exhaustive: submissions describing new and interesting ideas relating broadly to declarative programming are encouraged. The technical program of the conference will combine presentations of the accepted papers with invited talks and advanced tutorials. PPDP 2001 is part of a federation of colloquia known as Principles, Logics and Implementations of high-level programming languages (PLI 2001) which includes the ACM SIGPLAN International Conference on Functional Programming (ICFP 2001). The colloquia will run from 2 to 8 September, 2001. The venue for the conference is Firenze (Florence), one of Europe's most attractive cities, famous for its churches, galleries and museums. For more details, see the conference web site. Important Dates: Submission 15 March 2001 Notification 7 May 2001 Final Version 11 June 2001 Affiliated Workshops: Proposals are being solicited for PLI 2001 affiliated workshops. Details about the submission of proposals are available at http://music.dsi.unifi.it/pli01/wkshops. Web Sites and Email Contact: PPDP 2001: http://music.dsi.unifi.it/pli01/ppdp PLI 2001: http://music.dsi.unifi.it/pli01 mailto:ppdp01@cs.mu.oz.au Conference Chair: Rocco De Nicola, Universita di Firenze http://www.dsi.unifi.it/~denicola/ mailto:denicola@dsi.unifi.it Program Chair: Harald Sondergaard, The University of Melbourne http://www.cs.mu.oz.au/~harald/ mailto:harald@cs.mu.oz.au Program Committee: Maria Alpuente, Univ. Politecnica de Valencia, ES Yves Caseau, Bouygues, FR Michael Codish, Ben-Gurion Univ. of the Negev, IL Saumya Debray, Univ. of Arizona, US Conal Elliott, Microsoft Research, US Sandro Etalle, Univ. Maastricht, NL Roberto Giacobazzi, Univ. di Verona, IT Michael Leuschel, Univ. of Southampton, GB John Lloyd, Australian National Univ., AU Torben Mogensen, Kobenhavns Univ., DK Alan Mycroft, Cambridge Univ., GB Gopalan Nadathur, Univ. of Minnesota, US Martin Odersky, Ecole Polyt. Fed. Lausanne, CH Catuscia Palamidessi, Penn State Univ., US Andreas Podelski, Max-Planck-Inst. Informatik, DE Kostis Sagonas, Uppsala Univ., SE Christian Schulte, Univ. des Saarlandes, DE Michael Schwartzbach, Aarhus Univ., DK Harald Sondergaard, Univ. of Melbourne, AU Peter J. Stuckey, Univ. of Melbourne, AU From venneri@dsi.unifi.it Wed Dec 13 20:06:41 2000 From: venneri@dsi.unifi.it (b.venneri) Date: Wed, 13 Dec 2000 16:06:41 -0400 Subject: PLI 2001: call for workshop proposals Message-ID: CALL FOR WORKSHOP PROPOSALS Principles, Logics and Implementations of high-level programming languages (PLI 2001) Firenze, Italy September 3 - 7, 2001 http://music.dsi.unifi.it/pli01 PLI 2001, a federation of colloquia which includes ICFP 2001 (ACM-SIGPLAN International Conference on Functional Programming) and PPDP 2001 (ACM-SIGPLAN International Conference on Principles and Practice of Declarative Programming), will be held in Firenze, Italy, September 3-7 2001. Workshops affiliated to PLI 2001 will be held before, after or in parallel with the main conferences. Researchers and practitioners are invited to submit workshop proposals, that should be sent to the PLI 2001 Workshop Chair Betti Venneri mailto:venneri@dsi.unifi.it with "PLI01 Workshop Submission" in the subject header. Proposals should include * a short scientific justification of the proposed topic (somehow related to the colloquia), * names and contact information of the organizers, * expected number of participants and duration (the preference is for one day-long workshops), * estimated dates for paper submissions, notification of acceptance and final versions and any other relevant information (e.g., invited speakers, publication policy, etc.). THE DEADLINE FOR RECEIPT OF PROPOSALS IS JANUARY 8, 2001. Proposals will be evaluated by the PLI 2001 Workshop Chair, the ICFP and PPDP Program Chairs and Conference Chairs. Notification of acceptance will be made by February 2, 2001. The titles and brief information related to accepted workshop proposals will be included in the conference program and advertised in the call for participation. Workshop organizers will be responsible for producing a Call for papers and a Web site, for reviewing and making acceptance decisions on submitted papers, and for scheduling workshop activities in consultation with the local organizers. Workshop selection committee: Xavier Leroy (INRIA, France), ICFP 2001 Program Chair Benjamin C. Pierce (Univ. of Pennsylvania), ICFP 2001 Conference Chair Harald Sondergaard (Univ. of Melbourne), PPDP 2001 Program Chair Rocco De Nicola (Univ. of Firenze), PPDP 2001 Conference Chair Betti Venneri (Univ. of Firenze), PLI 2001 Workshop Chair. we From shlomif@vipe.technion.ac.il Fri Dec 15 19:47:27 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Fri, 15 Dec 2000 21:47:27 +0200 (IST) Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: Hi! As some of you may know, a Haskell program that prints all the primes can be as short as the following: primes = sieve [2.. ] where sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] Now, this program roughly corresponds to the following perl program: ###### SNIP SNIP ##### #!/usr/bin/perl use strict; my (@primes, $a, $p); @primes = (2); MAIN_LOOP: for($a = 3; $a < 1000; $a++) { foreach $p (@primes) { if ($a % $p == 0) { next MAIN_LOOP; } } push @primes, $a; } print join(", ", @primes); ####### SNIP SNIP ##### The program can be more optimized for both speed and code size, but I wanted to make it as verbose as possible. The algorithm keeps a list of the primes, and for each new number checks if it is divisable by any of them and if not it adds it to the list. There is a different algorithm which keeps a boolean map which tells whether the number at that position is prime or not. At start it is initialized to all trues. The algorithm iterates over all the numbers from 2 to the square root of the desired bound, and if it encounters a prime number it marks all the numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally considered a better algorithm than the previous one, because it uses less costier operations (multiplications and additions instead of modulos.) The perl program that implements that algorithm is this: #### SNIP SNIP ##### #!/usr/bin/perl use strict; sub primes { my $how_much = shift; my (@array, $bound, $a, $b, @primes); @array = (1) x $how_much; $bound = int(sqrt($how_much))+1; for($a=2;$a<=$bound;$a++) { if ($array[$a]) { for($b=$a*$a;$b<$how_much;$b+=$a) { $array[$b] = 0; } push @primes, $a; } } for(;$a<$how_much;$a++) { if ($array[$a]) { push @primes, $a; } } return @primes; } print join(", ", primes(1000)); ##### SNIP SNIP ###### Now, I tried writing an equivalent Haskell program and the best I could do was the following: ---- SNIP SNIP ----- module Primes where import Prelude import Array how_much :: Int how_much = 1000 initial_primes_map :: Array Int Bool initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ] mybound :: Int mybound = ceiling(sqrt(fromInteger(toInteger(how_much)))) next_primes_map :: Int -> Array Int Bool -> Array Int Bool next_primes_map a primes_map = if (a == mybound) then primes_map else next_primes_map (a+1) ( if primes_map!a then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ] else primes_map ) prime_bound :: Int -> Int prime_bound a = (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a)))) get_primes_map :: Array Int Bool get_primes_map = (next_primes_map 2 initial_primes_map) list_primes :: Array Int Bool -> Int -> [Int] list_primes primes_map n = if (n > how_much) then [] else ( if primes_map!n then n:(list_primes primes_map (n+1)) else list_primes primes_map (n+1) ) show_primes = show (list_primes get_primes_map 2) ---- SNIP SNIP ----- The problem is that when running it on hugs98 on a Windows98 computer with 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When entering how_much as 50,000 I get the following message: ERROR: Garbage collection fails to reclaim sufficient space In perl I can scale beyond 100,000, and if I modify the code to use a bit vector (using vec) to much more. So my question is what am I or hugs are doing wrong and how I can write better code that implements this specific algorithm. >From what I saw I used tail recursion, (and hugs98 has proper tail recursion, right?), and there's only one primes_map present at each iteration (and thus, at all), so it shouldn't be too problematic. Does it have to do with the way hugs98 implements and Int to Bool array? Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From jenglish@flightlab.com Sat Dec 16 23:21:48 2000 From: jenglish@flightlab.com (Joe English) Date: Sat, 16 Dec 2000 15:21:48 -0800 Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: References: Message-ID: <200012162321.PAA00918@dragon.flightlab.com> Shlomi Fish wrote: > As some of you may know, a Haskell program that prints all the primes can be > as short as the following: > > primes = sieve [2.. ] where > sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] > > Now, this program roughly corresponds to the following perl program: [ ~20 line Perl program snipped ] > The program can be more optimized for both speed and code size, but I wanted > to make it as verbose as possible. > > There is a different algorithm which keeps a boolean map [...] > The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. [~40 line Perl implementation snipped] > Now, I tried writing an equivalent Haskell program and the best I > could do was the following: [ ~45 line Haskell implementation snipped ] Another way to do this is to compute the final array directly, instead of computing successive versions of the array: import Array primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where primesMap = accumArray (||) False (2,n) multList multList = [(m,True) | j <- [2 .. n `div` 2], m <- multiples j] multiples j = takeWhile (n>=) [k*j | k <- [2..]] Now this version does a lot more work than the algorithm described above -- it computes multiples of *all* the integers less than n/2, not just the primes less than sqrt(n) -- but it has the virtue of being short enough to reason about effectively and is probably a better starting point for further optimization. > The problem is that when running it on hugs98 on a Windows98 computer with > 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When > entering how_much as 50,000 I get the following message: > > ERROR: Garbage collection fails to reclaim sufficient space My implementation fares even worse under Hugs -- it runs out of space around n = 4500 (Linux box, 64M RAM). With GHC it has no problem for n = 100,000, although the space usage is still extremely poor. It grows to consume all available RAM at around n = 200,000. (On the other hand, it's considerably faster than the traditional 2-liner listed above, up to the point where it starts paging). I suspect the poor memory usage is due to the way accumArray works -- it's building up a huge array of suspensions of the form (False && (False && ( ... && True))) that aren't reduced until an array element is requested. (A strict version of accumArray, analogous to "foldl_strict" defined below, would solve this problem, but I don't see any way to implement it in Standard Haskell). > In perl I can scale beyond 100,000, and if I modify the code to use a bit > vector (using vec) to much more. So my question is what am I or hugs are > doing wrong and how I can write better code that implements this specific > algorithm. > > From what I saw I used tail recursion, (and hugs98 has proper tail recursion > right?), and there's only one primes_map present at each iteration (and thus, > at all), so it shouldn't be too problematic. Actually no; this is a common misconception. In a strict language like Scheme, tail call optimization works because a tail call is the last thing a function does. In Haskell though the tail call is the *first* thing that gets evaluated (more or less), leaving all the "earlier" work as an unevaluated suspension. Code that is space-efficient in a strict language frequently suffers from awful space leaks in a lazy language. For example: sum_first_n_integers n = f n 0 where f 0 a = a f n a = f (n-1) (n+a) quickly leads to a "Control Stack Overflow" error in Hugs. BTW, the trick to fix it is to change the last line to: f n acc = f (n-1) $! (n+acc) or to replace the whole thing with: foldl_strict (+) 0 [1..n] where foldl_strict f a [] = a foldl_strict f a (x:xs) = (foldl_strict f $! f a x) xs > Does it have to do with the way hugs98 implements and Int to Bool array? Most likely yes. Hugs is optimized for interactive use and quick compilation, not for space usage. Try it with GHC or HBC and see how it does. --Joe English jenglish@flightlab.com From ahey@iee.org Sun Dec 17 11:59:43 2000 From: ahey@iee.org (Adrian Hey) Date: Sun, 17 Dec 2000 11:59:43 +0000 (GMT) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: On Fri 15 Dec, Shlomi Fish wrote: > There is a different algorithm which keeps a boolean map which tells whether > the number at that position is prime or not. At start it is initialized to all > trues. The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally > considered a better algorithm than the previous one, because it uses less > costier operations (multiplications and additions instead of modulos.) Functional programming languages are notoriously ineffecient at array handling (though I'm not sure exactly what the various Haskell implementations actually do). You can use a variation of this algorithm with lazy lists.. primes = 2:(get_primes [3,5..]) get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs)) strike step x_now (x:xs) = case (compare x_now x) of LT -> strike step (x_now+step) (x:xs) EQ -> strike step (x_now+step) xs GT -> x:(strike step x_now xs) The equivalent program in Clean (on a MAC) gets upto 877783 before giving a stack overflow error (1000K of stack, 4000K of Heap allocated). (I haven't actually tried this in Haskell 'cos I don't have a Windoze or 'nix box.) Regards -- Adrian Hey From qrczak@knm.org.pl Sun Dec 17 19:29:32 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 17 Dec 2000 19:29:32 GMT Subject: Problem with functional dependencies Message-ID: The following module is rejected by both ghc -fglasgow-exts -fallow-undecidable-instances and hugs -98 ------------------------------------------------------------------------ class HasFoo a foo | a -> foo where foo :: a -> foo data A = A Int data B = B A instance HasFoo A Int where foo (A x) = x instance HasFoo A foo => HasFoo B foo where foo (B a) = foo a ------------------------------------------------------------------------ The error messsage says that the type inferred for foo in B's instance is not general enough: the rhs has type "HasFoo B Int => B -> Int", but "HasFoo B foo => B -> foo" was expected. Should it really be wrong? I don't know the details of type inference with fundeps, but intuitively it should work, yielding an instance HasFoo B Int. Could it be made legal please? With the fundep removed, it works. I need it for a preprocessor which generates instances like that for B without knowing the type to put as the second class argument. Fundeps aren't essential, but... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From elke.kasimir@catmint.de Sun Dec 17 18:56:46 2000 From: elke.kasimir@catmint.de (Elke Kasimir) Date: Sun, 17 Dec 2000 19:56:46 +0100 (CET) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: This message is in MIME format --_=XFMail.1.3.p0.Linux:001217195636:327=_ Content-Type: text/plain; charset=iso-8859-1 Your algorithm seems to be based on the following idea: calculate the non-primes and derive the primes from them by calculating the set difference of the natural numbers and the non-primes. A naive implementation of this idea can be found as primes' in the attachached file. The function uses no multiplication or division and though performs 6 times worse than the sieve in calculating the first 30000 primes. The complexity for finding the next i'th prime with this naive implementation is about O(i). In comparison to this, the sieve provides a good optimization because only those natural numbers are tested against the i'th prime which have run through all other sieves. Nevertheless, your algorithm is promising when the non-primes are merged efficiently enough into a single sorted list which can be easily subtracted from the natural numbers. I think the deployment of an array is basically a way to efficiently merge the multiples of the primaries into a sorted list (where even duplicates are removed), thus hoping to reduce the number of the operations better than the optimization that is provided by the sieve. However, to use arrays this way, you probably need destructive array updates, because the array must be incrementally updated when new primes are found. I think that standard haskell arrays don't do the job very well. An implementation of the "merging" idea in Haskell is primes'' in the attached file. It is 15% faster then the sieve in calculating the 30000 first primes. The algorithm is realized as two mutually recursive functions noprimes and primes'', the latter calculating the set difference between the non-primes and the natural numbers, the former merging the all multiples of all primes into a sorted list. It should be possible to substantially optimize the merging operation. primes''' is an efficient variant of primes'. Instead of a list it uses a binary tree for the management of the lists of multiples of the already found primes, and thus requires some additional programming effort. The complexity is reduced from O(i) to something like O(Log(i)). Compared with the sieve, primes''' needs only half the time to calculate the first 30000 primes. (Tests with ghc 4.08, 64m heap) Best, Elke. On 15-Dec-00 Shlomi Fish wrote: > > Hi! > > As some of you may know, a Haskell program that prints all the primes can be > as short as the following: > > primes = sieve [2.. ] where > sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] > > Now, this program roughly corresponds to the following perl program: > >###### SNIP SNIP ##### >#!/usr/bin/perl > > use strict; > > my (@primes, $a, $p); > @primes = (2); > MAIN_LOOP: > for($a = 3; $a < 1000; $a++) > { > foreach $p (@primes) > { > if ($a % $p == 0) > { > next MAIN_LOOP; > } > } > push @primes, $a; > } > print join(", ", @primes); >####### SNIP SNIP ##### > > The program can be more optimized for both speed and code size, but I wanted > to make it as verbose as possible. > > The algorithm keeps a list of the primes, and for each new number checks if > it > is divisable by any of them and if not it adds it to the list. > > There is a different algorithm which keeps a boolean map which tells whether > the number at that position is prime or not. At start it is initialized to > all > trues. The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally > considered a better algorithm than the previous one, because it uses less > costier operations (multiplications and additions instead of modulos.) > > The perl program that implements that algorithm is this: > >#### SNIP SNIP ##### >#!/usr/bin/perl > > use strict; > > sub primes > { > my $how_much = shift; > > my (@array, $bound, $a, $b, @primes); > > @array = (1) x $how_much; > > $bound = int(sqrt($how_much))+1; > > for($a=2;$a<=$bound;$a++) > { > if ($array[$a]) > { > for($b=$a*$a;$b<$how_much;$b+=$a) > { > $array[$b] = 0; > } > push @primes, $a; > } > } > for(;$a<$how_much;$a++) > { > if ($array[$a]) > { > push @primes, $a; > } > } > > return @primes; > } > > print join(", ", primes(1000)); >##### SNIP SNIP ###### > > Now, I tried writing an equivalent Haskell program and the best I could do > was > the following: > > ---- SNIP SNIP ----- > module Primes where > > import Prelude > import Array > > how_much :: Int > how_much = 1000 > > initial_primes_map :: Array Int Bool > initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ] > > mybound :: Int > mybound = ceiling(sqrt(fromInteger(toInteger(how_much)))) > > next_primes_map :: Int -> Array Int Bool -> Array Int Bool > next_primes_map a primes_map = > if (a == mybound) > then primes_map > else next_primes_map (a+1) ( > if primes_map!a > then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ] > else primes_map > ) > > prime_bound :: Int -> Int > prime_bound a = > (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a)))) > > get_primes_map :: Array Int Bool > get_primes_map = (next_primes_map 2 initial_primes_map) > > list_primes :: Array Int Bool -> Int -> [Int] > list_primes primes_map n = > if (n > how_much) > then [] > else > ( > if primes_map!n > then n:(list_primes primes_map (n+1)) > else list_primes primes_map (n+1) > ) > > show_primes = show (list_primes get_primes_map 2) > ---- SNIP SNIP ----- > > > The problem is that when running it on hugs98 on a Windows98 computer with > 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When > entering how_much as 50,000 I get the following message: > > ERROR: Garbage collection fails to reclaim sufficient space > > In perl I can scale beyond 100,000, and if I modify the code to use a bit > vector (using vec) to much more. So my question is what am I or hugs are > doing > wrong and how I can write better code that implements this specific > algorithm. > >>From what I saw I used tail recursion, (and hugs98 has proper tail recursion, > right?), and there's only one primes_map present at each iteration (and thus, > at all), so it shouldn't be too problematic. Does it have to do with the way > hugs98 implements and Int to Bool array? > > Regards, > > Shlomi Fish > > ---------------------------------------------------------------------- > Shlomi Fish shlomif@vipe.technion.ac.il > Home Page: http://t2.technion.ac.il/~shlomif/ > Home E-mail: shlomif@techie.com > > The prefix "God Said" has the extraordinary logical property of > converting any statement that follows it into a true one. > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell --- Elke Kasimir Skalitzer Str. 79 10997 Berlin (Germany) fon: +49 (030) 612 852 16 mail: elke.kasimir@catmint.de> see: for pgp public key see: --_=XFMail.1.3.p0.Linux:001217195636:327=_ Content-Disposition: attachment; filename="Primes.hs" Content-Transfer-Encoding: base64 Content-Description: Primes.hs Content-Type: application/octet-stream; name=Primes.hs; SizeOnDisk=3056 bW9kdWxlIFByaW1lcwp3aGVyZQoKaW1wb3J0IExpc3QKCi0tIDEuIHZlcnNpb24sIHNpZXZlCgpw cmltZXMgCiAgICA9IHNpZXZlIFsyLi5dIAogICAgICAgd2hlcmUgc2lldmUgKHg6eHMpID0geCA6 IHNpZXZlIFsgbiB8IG4gPC0geHMgLCBuIGBtb2RgIHggPiAwIF0gCgoKLS0gMi4gdmVyc2lvbjog a2VlcCBhbiAidXB0by1kYXRlIiBsaXN0IG9mIHRoZSBub24tcHJpbWVzIAotLSAgICAgICAgICAg ICAoYSBmaW5pdGUgbGlzdCBvZiBpbmlmaW5pdGUgbGlzdHMpCi0tICAgICAgICAgICAgIGFuZCBj YWxjdWxhdGUgdGhlIHByaW1lcyBmcm9tIHRoZW0uCgpwcmltZXMnCiAgICA9IG1rUHJpbWVzIFtd IFsyLi5dIAogICAgICB3aGVyZQogICAgICAgbWtQcmltZXMgbm9uX3ByaW1lcyAoeDp4cykgCgkg ICB8IG51bGwgd2l0aFggPSB4IDogbWtQcmltZXMgKG11bHQgeCA6IG5vbl9wcmltZXMpICAgICAg ICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChtYXAgdGFpbCB3aXRoWCArKyB3 aXRob3V0WCkgeHMKCSAgIHdoZXJlCgkgICAod2l0aFgsd2l0aG91dFgpID0gcGFydGl0aW9uICgo PT14KS4gaGVhZCkgbm9uX3ByaW1lcwoJICAgbXVsdCB4ICAgICAgICAgICA9IGl0ZXJhdGUgKCt4 KSAoeCt4KQoKCi0tIDMuIHZlcnNpb246IHByaW1lcyBhbmQgbm9uLXByaW1lcyBhcmUgbXV0dWFs bHkgcmVjdXJzaXZlLgoKcHJpbWVzJycKICAgID0gMiA6IGRpZmYgWzMuLl0gbm9uX3ByaW1lcwoK bm9uX3ByaW1lcyAKICAgID0gbWVyZ2UgKG1hcCBtdWx0IHByaW1lcycnKSAKICAgICAgd2hlcmUg CiAgICAgIG11bHQgeCAgID0gaXRlcmF0ZSAoK3gpICh4K3gpICAgICAgCgptZXJnZSAoKHg6eHMp OnJlc3QpCiAgICA9IHggOiBtZXJnZSAocmVhcnJhbmdlICh4czpyZXN0KSkKCnJlYXJyYW5nZSBs QCh4bEAoeDp4cyk6KHk6eXMpOnJlc3QpIAogICAgfCB4IDw9IHkgICAgID0gbAogICAgfCBvdGhl cndpc2UgID0gKHk6eGwpIDogcmVhcnJhbmdlICh5czpyZXN0KSAKCi0tIHNldCBkaWZmZXJlbmNl IGZvciBvcmRlcmVkIGxpc3RzIC0gcmVzdWx0IGlzIGFsc28gb3JkZXJlZDoKZGlmZiA6OiBPcmQg YSA9PiBbYV0gLT4gW2FdIC0+IFthXQpkaWZmIHhsQCh4OnhzKSB5bEAoeTp5cykgCiAgICB8IHgg PCAgeSA9IHggOiBkaWZmIHhzIHlsCiAgICB8IHggPT0geSA9ICAgICBkaWZmIHhzIHlsCiAgICB8 IHggPiAgeSA9ICAgICBkaWZmIHhsIHlzCgoKLS0gNC4gdmVyc2lvbiwgbGlrZSAyLiwgYnV0IHVz ZXMgYSB0cmVlIHRvIG1hbmFnZSBub24tcHJpbXNlOgoKcHJpbWVzJycnCiAgICA9IG1rUHJpbWVz IEwgWzIuLl0gCiAgICAgIHdoZXJlCiAgICAgICBta1ByaW1lcyBub25fcHJpbWVzICh4OnhzKSAK CSAgIHwgbnVsbCB3aXRoWCA9IHggOiBta1ByaW1lcyAodGluc2VydCAobXVsdCB4KSBub25fcHJp bWVzKSAgICAgICAgICAgICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChmb2xk ciB0aW5zZXJ0IHdpdGhvdXRYIChtYXAgdGFpbCB3aXRoWCkpIHhzCgkgICB3aGVyZQoJICAgKHdp dGhYLHdpdGhvdXRYKSA9IHRwYXJ0aXRpb24gW3hdIG5vbl9wcmltZXMgCgkgICBtdWx0IHggICAg ICAgICAgID0gaXRlcmF0ZSAoK3gpICh4K3gpCgotLSBhIGJpbmFyeSB0cmVlOgoKZGF0YSBUcmVl ID0gTiBbSW50ZWdlcl0gVHJlZSBUcmVlIHwgTCBkZXJpdmluZyBTaG93CgotLSBydWxlcyBmb3Ig cGxhY2luZyBpbnRlZ2VyIGxpc3RzOgoKbGVmdG9mLCByaWdodG9mIDo6IFtJbnRlZ2VyXSAtPiBU cmVlIC0+IEJvb2wKCmxlZnRvZiAgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA8PSB5CnJpZ2h0 b2YgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA+IHkKCi0tIHJ1bGUgZm9yIG1hdGNoaW5nIGlu dGVnZXIgbGlzdHM6CgptYXRjaGVzIDo6IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IEJvb2wKbWF0Y2hl cyAoeDp4cykgKE4gKHk6eXMpIF8gXykgPSB4ID09IHkKCi0tIGluc2VydGlvbjoKCnRpbnNlcnQg OjogW0ludGVnZXJdIC0+IFRyZWUgLT4gVHJlZQp0aW5zZXJ0IHhsICAgTCA9IE4geGwgTCBMCnRp bnNlcnQgeGwgdEAoTiB5bCB0MSB0MikgCiAgICB8IHhsIGBsZWZ0b2ZgICB0ID0gTiB5bCAodGlu c2VydCB4bCB0MSkgdDIKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgPSBOIHlsIHQxICh0aW5zZXJ0IHhs IHQyKQoKLS0gZXh0cmFjdGlvbiAmIHJlbW92YWwgaW4gb25lIHN0ZXA6Cgp0cGFydGl0aW9uIDo6 IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IChbW0ludGVnZXJdXSxUcmVlKQp0cGFydGl0aW9uIHhsIEwg PSAoW10sTCkKdHBhcnRpdGlvbiB4bCB0QChOIHlsIHQxIHQyKSAKICAgIHwgeGwgYG1hdGNoZXNg IHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24nIHhsIHQxIGluICh5bDphLCByZW1vdmUgYiB0 MikKICAgIHwgeGwgYGxlZnRvZmAgIHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24geGwgdDEg aW4gKGEsIE4geWwgYiB0MikKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgID0gIGxldCAoYSxiKSA9IHRw YXJ0aXRpb24geGwgdDIgaW4gKGEsIE4geWwgdDEgYikKCnRwYXJ0aXRpb24nIHhsIEwgPSAoW10s TCkgICAgICAtLSBjaGVjayBmb3IgbW9yZSBtYXRjaGVzCnRwYXJ0aXRpb24nIHhsIHRAKE4geWwg dDEgdDIpIAogICAgfCB4bCBgbWF0Y2hlc2AgdCAgPSAgbGV0IChhLGIpID0gdHBhcnRpdGlvbicg eGwgdDEgaW4gKHlsOmEsIHJlbW92ZSBiIHQyKQogICAgfCBvdGhlcndpc2UgICAgICAgPSAoW10s dCkKCnJlbW92ZSBMICB0MiAgPSB0MgpyZW1vdmUgdDEgdDIgPSBsZXQgKGEsYikgPSByaWdodG1v c3QgdDEgaW4gTiBhIGIgdDIKCnJpZ2h0bW9zdCAoTiB5bCB0MSAgTCkgPSAoeWwsdDEpCnJpZ2h0 bW9zdCAoTiB5bCB0MSB0MikgPSBsZXQgKGEsYik9cmlnaHRtb3N0IHQyIGluIChhLCBOIHlsIHQx IGIpCiAgCgotLSB0ZXN0IGNvcnJlY3RuZXNzCgpwZGlmZiA9IFsgKGEsYixjLGQpIHwgCgkgKGEs YixjLGQpPC16aXA0IHByaW1lcyBwcmltZXMnIHByaW1lcycnIHByaW1lcycnJywgCgkgYSAvPSBi IHx8IGIgLz0gYyB8fCBjIC89IGQgCgkgXQoKCgoKCgoKCgo= --_=XFMail.1.3.p0.Linux:001217195636:327=_-- End of MIME message From ahey@iee.org Mon Dec 18 00:24:12 2000 From: ahey@iee.org (Adrian Hey) Date: Mon, 18 Dec 2000 00:24:12 +0000 (GMT) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: On Sun 17 Dec, Adrian Hey wrote: > You can use a variation of this algorithm with lazy lists.. > > primes = 2:(get_primes [3,5..]) > get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs)) ^^^ Whoops,_____________________________________________| 32 bit Ints may cause trouble here :-) Regards -- Adrian Hey From Xavier.Leroy@inria.fr Mon Dec 18 09:30:07 2000 From: Xavier.Leroy@inria.fr (Xavier Leroy) Date: Mon, 18 Dec 2000 10:30:07 +0100 Subject: call for papers ICFP 2001 Message-ID: <20001218103007.B32378@pauillac.inria.fr> ICFP 2001: Call for Papers ICFP 2001: International Conference on Functional Programming Firenze (Florence), Italy; 3-5 September 2001 associated with PLI 2001: Colloquium on Principles, Logics, and Implementations of High-Level Programming Languages Important dates: Submission deadline 15 March 2001, 18:00 UTC Notification of acceptance or rejection 11 May 2001 Final paper due 29 June 2001 Conference 3-5 September 2001 Scope: ICFP 2001 seeks original papers on the full spectrum of the art, science, and practice of functional programming. The conference invites submissions on all topics ranging from principles to practice, from foundations to features, and from abstraction to application. The scope covers all languages that encourage programming with functions, including both purely applicative and imperative languages, as well as languages that support objects and concurrency. Papers setting new directions in functional programming, or describing novel or exemplary applications of functional programming, are particularly encouraged. Topics of interest include, but are not limited to, the following: * Foundations: formal semantics, lambda calculus, type theory, monads, continuations, control, state, effects. * Design: modules and type systems, concurrency and distribution, components and composition, relations to object-oriented and logic programming, multiparadigm programming. * Implementation: abstract machines, compile-time and run-time optimization, just-in-time compilers, memory management, foreign-function and component interfaces. * Transformation and Analysis: abstract interpretation, partial evaluation, program transformation, theorem proving, specification and verification. * Applications: scientific and numerical computing, symbolic computing and artificial intelligence, systems programming, databases, graphic user interfaces, multimedia programming, web programming. * Experience: FP in education and industry, ramifications on other paradigms and computing disciplines. * Functional pearls: elegant, instructive examples of functional programming. Submission guidelines: Please refer to the submission Web site http://cristal.inria.fr/ICFP2001/ Program committee: General chair Program committee Benjamin Pierce Karl Crary, Carnegie Mellon University University of Pennsylvania Marc Feeley, University of Montréal Giorgio Ghelli, University of Pisa Program chair Simon Peyton Jones, Microsoft Research John Hughes, Chalmers University Xavier Leroy Naoki Kobayashi, University of Tokyo INRIA Rocquencourt Julia Lawall, DIKU, U. Copenhagen Domaine de Voluceau, B.P. 105 Sheng Liang, Stratum8 78153 Le Chesnay, France John Reppy, Bell Labs, Lucent Technologies E-mail: Xavier.Leroy@inria.fr Scott Smith, John Hopkins University Fax: + 33 - 1 - 39 63 56 84 Carolyn Talcott, Stanford University Phone: + 33 - 1 - 39 63 55 61 Kwangkeun Yi, KAIST From sebastien@posse42.net Tue Dec 19 14:15:16 2000 From: sebastien@posse42.net (Sebastien Carlier) Date: Tue, 19 Dec 2000 15:15:16 +0100 Subject: Excessive restriction in ghc ? Message-ID: <006401c069c6$1cdc13c0$d701a8c0@air> Hello. I am getting an error message from ghc 4.08.1 with the following code: > class Collection e ce | ce -> e where > empty :: ce > insert :: e -> ce -> ce > > class (Eq e, Collection e ce) => Set e ce where > member :: e -> ce -> Bool > union :: ce -> ce -> ce Main.lhs:7: Class type variable `e' does not appear in method signature union :: {- implicit forall -} ce -> ce -> ce Since `ce' uniquely determines `e', I would expect the compiler to assume that `e' appears in the method signature. Either I am misunderstanding something, or something may be missing in the compiler around rename/RnSource.lhs:249. Regards, Sebastien Carlier From zhanyong.wan@yale.edu Tue Dec 19 15:43:28 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Tue, 19 Dec 2000 10:43:28 -0500 Subject: Excessive restriction in ghc ? References: <006401c069c6$1cdc13c0$d701a8c0@air> Message-ID: <3A3F8220.3FED720E@yale.edu> Hi Sebastien, Sebastien Carlier wrote: > I am getting an error message from ghc 4.08.1 with > the following code: > > > class Collection e ce | ce -> e where > > empty :: ce > > insert :: e -> ce -> ce > > > > class (Eq e, Collection e ce) => Set e ce where > > member :: e -> ce -> Bool > > union :: ce -> ce -> ce > > Main.lhs:7: > Class type variable `e' does not appear in method signature > union :: {- implicit forall -} ce -> ce -> ce > > Since `ce' uniquely determines `e', I would expect the > compiler to assume that `e' appears in the method signature. > Either I am misunderstanding something, or something may be > missing in the compiler around rename/RnSource.lhs:249. I encountered the same problem this summer and wrote to Simon PJ and Jeff Lewis. Here's Jeff's answer: > I'm glad to find examples where they are indispensible. The implementation of > FDs in GHC is pretty much complete WRT Mark's writeup (but it doesn't complain > about instances inconsistent with FDs). I'm using them in a current project, > but in a fairly conservative manner. In hugs, I implemented several > extensions to do with derived instances and superclasses - pretty much > necessary as you've found. Unfortunately, in hugs I implemented it in rather > the wrong way. Based on dicsussions at the Hugs/GHC meeting w/ Simon, I have > a cunning plan for finishing the implementation properly in GHC, but just > haven't had the chance to do it. What I need to do is write it up, so that > either Simon or myself can finish the job. So the short answer to your question is: FD in derived instances is not implemented in GHC yet. I'm still eagerly waiting to use this feature in my project. Jeff, could you give us an update on the progress? Thanks! -- # Zhanyong Wan http://pantheon.yale.edu/~zw23/ ____ # Yale University, Dept of Computer Science /\___\ # P.O.Box 208285, New Haven, CT 06520-8285 ||___| From mk167280@zodiac.mimuw.edu.pl Tue Dec 19 15:56:40 2000 From: mk167280@zodiac.mimuw.edu.pl (Marcin Kowalczyk) Date: Tue, 19 Dec 2000 16:56:40 +0100 Subject: Excessive restriction in ghc ? In-Reply-To: <006401c069c6$1cdc13c0$d701a8c0@air>; from sebastien@posse42.net on Tue, Dec 19, 2000 at 03:15:16PM +0100 References: <006401c069c6$1cdc13c0$d701a8c0@air> Message-ID: <20001219165640.A9716@zodiac.mimuw.edu.pl> On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote: > > class Collection e ce | ce -> e where > > empty :: ce > > insert :: e -> ce -> ce > > > > class (Eq e, Collection e ce) => Set e ce where Doesn't adding the fundep to Set's definition as well help? -- Marcin 'Qrczak' Kowalczyk From zhanyong.wan@yale.edu Tue Dec 19 16:04:31 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Tue, 19 Dec 2000 11:04:31 -0500 Subject: Excessive restriction in ghc ? References: <006401c069c6$1cdc13c0$d701a8c0@air> <20001219165640.A9716@zodiac.mimuw.edu.pl> Message-ID: <3A3F870F.10CA4BD8@yale.edu> Marcin Kowalczyk wrote: > > On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote: > > > > class Collection e ce | ce -> e where > > > empty :: ce > > > insert :: e -> ce -> ce > > > > > > class (Eq e, Collection e ce) => Set e ce where > > Doesn't adding the fundep to Set's definition as well help? It might help in this particular case, but if we want something like class Collection e ce => Foo ce where ... then your trick does not apply, and I indeed need something like the above in my project. -- Zhanyong Wan From simonpj@microsoft.com Tue Dec 19 14:47:41 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 19 Dec 2000 06:47:41 -0800 Subject: Excessive restriction in ghc ? Message-ID: <74096918BE6FD94B9068105F877C002D0137839A@red-pt-02.redmond.corp.microsoft.com> Functional dependencies aren't fully implemented in 4.08 I'm afraid, and won't ever be. It'll be significantly better in 5.0, but we won't release that for a while yet. (Unless you care to build from the CVS tree.) Simon | -----Original Message----- | From: Sebastien Carlier [mailto:sebastien@posse42.net] | Sent: 19 December 2000 14:15 | To: haskell@haskell.org | Subject: Excessive restriction in ghc ? | | | Hello. | | I am getting an error message from ghc 4.08.1 with | the following code: | | > class Collection e ce | ce -> e where | > empty :: ce | > insert :: e -> ce -> ce | > | > class (Eq e, Collection e ce) => Set e ce where | > member :: e -> ce -> Bool | > union :: ce -> ce -> ce | | Main.lhs:7: | Class type variable `e' does not appear in method signature | union :: {- implicit forall -} ce -> ce -> ce | | Since `ce' uniquely determines `e', I would expect the | compiler to assume that `e' appears in the method signature. | Either I am misunderstanding something, or something may be | missing in the compiler around rename/RnSource.lhs:249. | | Regards, | Sebastien Carlier | | | | _______________________________________________ | Haskell mailing list | Haskell@haskell.org | http://www.haskell.org/mailman/listinfo/haskell | From simonpj@microsoft.com Tue Dec 19 14:58:41 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 19 Dec 2000 06:58:41 -0800 Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: <74096918BE6FD94B9068105F877C002D0137839D@red-pt-02.redmond.corp.microsoft.com> | Another way to do this is to compute the final array directly, | instead of computing successive versions of the array: | | import Array | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where | primesMap = accumArray (||) False (2,n) multList | multList = [(m,True) | j <- [2 .. n `div` 2], m <- | multiples j] | multiples j = takeWhile (n>=) [k*j | k <- [2..]] This style is definitely the way to go. Haskell does badly if you update an array one index at a time. Remember that arrays can be recursive. Here's a definition of Fibonacci for example; you can probably adapt it for primes fibs :: Int -> Array Int Int -- If a = fibs n, then a!i is fib(i), for i<=n. fibs n = a where a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <- [3..n]]) -- Notice that a is recursive Simon From shlomif@vipe.technion.ac.il Wed Dec 20 14:02:23 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Wed, 20 Dec 2000 16:02:23 +0200 (IST) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: <74096918BE6FD94B9068105F877C002D0137839D@red-pt-02.redmond.corp.microsoft.com> Message-ID: On Tue, 19 Dec 2000, Simon Peyton-Jones wrote: > | Another way to do this is to compute the final array directly, > | instead of computing successive versions of the array: > | > | import Array > | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where > | primesMap = accumArray (||) False (2,n) multList > | multList = [(m,True) | j <- [2 .. n `div` 2], m <- > | multiples j] > | multiples j = takeWhile (n>=) [k*j | k <- [2..]] > > This style is definitely the way to go. Haskell does badly > if you update an array one index at a time. > Unfortunately, it seems that this style is not the way to go. This program cannot scale beyond 5000 while my second program scales beyond 30000. I'm not saying 30000 is a good limit, but 5000 is much worse. Anyway, somebody who contacted me in private suggested the following method. It is a similiar algorithm which uses a list instead of an array. primes :: Int -> [Int] primes how_much = sieve [2..how_much] where sieve (p:x) = p : (if p <= mybound then sieve (remove (p*p) x) else x) where remove what (a:as) | what > how_much = (a:as) | a < what = a:(remove what as) | a == what = (remove (what+step) as) | a > what = a:(remove (what+step) as) remove what [] = [] step = (if (p == 2) then p else (2*p)) sieve [] = [] mybound = ceiling(sqrt(fromIntegral how_much)) I optimized it quite a bit, but the concept remained the same. Anyway, this code can scale very well to 100000 and beyond. But it's not exactly the same algorithm. I also implemented this algorithm in perl, and I can send it in person if anybody requests it. I'll try to see how the two programs run in GHC and HBC. Regards, Shlomi Fish > Remember that arrays can be recursive. Here's a definition > of Fibonacci for example; you can probably adapt it for primes > > fibs :: Int -> Array Int Int > -- If a = fibs n, then a!i is fib(i), for i<=n. > fibs n = a > where > a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <- > [3..n]]) > -- Notice that a is recursive > > Simon > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From ger@tzi.de Wed Dec 20 14:12:46 2000 From: ger@tzi.de (George Russell) Date: Wed, 20 Dec 2000 15:12:46 +0100 Subject: Finding primes using a primes map with Haskell and Hugs98 References: Message-ID: <3A40BE5E.13D8D959@tzi.de> There are numerous ways of optimising sieving for primes, none of which have much to do with this list. For example, two suggestions: (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise sieve separately for this k on higher primes. (Or you might use products of more or less primes, depending on memory and how high you were going.) (2) use bitwise arithmetic. If you look in the literature I think you'll find plenty more possibilities. I don't really see why any of this has anything to do with Haskell though. When it comes to seriously icky bit-twiddling algorithms I don't think Haskell has much to offer over C, especially as you'd have to make everything unboxed if you want comparable speed. From Colin.Runciman@cs.york.ac.uk Wed Dec 20 14:49:30 2000 From: Colin.Runciman@cs.york.ac.uk (Colin.Runciman@cs.york.ac.uk) Date: Wed, 20 Dec 2000 14:49:30 GMT Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: <200012201449.OAA01102@pc179.cs.york.ac.uk> > There are numerous ways of optimising sieving for primes, none of which > have much to do with this list. For example, two suggestions: > (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise > sieve separately for this k on higher primes. (Or you might use products of > more or less primes, depending on memory and how high you were going.) > ... > I don't really see why any of this has anything to do with Haskell though. > When it comes to seriously icky bit-twiddling algorithms I don't think Haskell > has much to offer over C, especially as you'd have to make everything unboxed if > you want comparable speed. Forgive the self-reference, but the following short article is all about this very topic: C. Runciman, Lazy wheel sieves and spirals of primes, Journal of Functional Programming, v7, n2, pp219--226, March 1997. From Dominic.J.Steinitz@BritishAirways.com Wed Dec 20 16:12:16 2000 From: Dominic.J.Steinitz@BritishAirways.com (Steinitz, Dominic J) Date: 20 Dec 2000 16:12:16 Z Subject: Haskell Productivity Message-ID: <"032483A40DA600E0*/c=GB/admd=ATTMAIL/prmd=BA/o=British Airways PLC/ou=CORPLN1/s=Steinitz/g=Dominic/i=J/"@MHS> The Haskell website claims that "Ericsson measured an improvement factor of between 9 and 25 in one set of experiments on telephony software". Presumably this is with Erlang not with Haskell. I have searched for the reference that substantiates this claim but I've only been able to find: http://set.gmd.de/~ap/femsys/wiger.html which talks about a productivity factor of 4 and http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haskell-vs-ada-abstract.html which suggests that Haskell is about 2-3 times as productive as imperative languages. Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25? Thanks, Dominic. ------------------------------------------------------------------------------------------------- 21st century air travel http://www.britishairways.com From simonpj@microsoft.com Wed Dec 20 11:11:44 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Wed, 20 Dec 2000 03:11:44 -0800 Subject: Problem with functional dependencies Message-ID: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> I think you can simplify the example. Given class HasFoo a b | a -> b where foo :: a -> b instance HasFoo Int Bool where ... Is this legal? f :: HasFoo Int b => Int -> b f x = foo x You might think so, since HasFoo Int b => Int -> b is a substitution instance of HasFoo a b => a -> b but if we infer the type (HasFoo Int b => Int -> b) for f's RHS, we can then "improve" it using the instance decl to (HasFoo Int Bool => Int -> Bool), and now the signature isn't a substitution insance of the type of the RHS. Indeed, this is just what will happen if you try with GHC, because GHC takes advantage of type signatures when typechecking a function defn, rather than first typechecking the defn and only then comparing with the signature. I don't know what the answers are here, but there's more to this functional dependency stuff than meets the eye. Even whether one type is more general than another has changed! Simon | -----Original Message----- | From: qrczak@knm.org.pl [mailto:qrczak@knm.org.pl] | Sent: 17 December 2000 19:30 | To: haskell@haskell.org | Subject: Problem with functional dependencies | | | The following module is rejected by both | ghc -fglasgow-exts -fallow-undecidable-instances | and | hugs -98 | | -------------------------------------------------------------- | ---------- | class HasFoo a foo | a -> foo where | foo :: a -> foo | | data A = A Int | data B = B A | | instance HasFoo A Int where | foo (A x) = x | | instance HasFoo A foo => HasFoo B foo where | foo (B a) = foo a | -------------------------------------------------------------- | ---------- | | The error messsage says that the type inferred for foo in B's instance | is not general enough: the rhs has type "HasFoo B Int => B -> | Int", but | "HasFoo B foo => B -> foo" was expected. From paul.hudak@yale.edu Wed Dec 20 16:28:10 2000 From: paul.hudak@yale.edu (Paul Hudak) Date: Wed, 20 Dec 2000 11:28:10 -0500 Subject: Haskell Productivity References: <"032483A40DA600E0*/c=GB/admd=ATTMAIL/prmd=BA/o=British Airways PLC/ou=CORPLN1/s=Steinitz/g=Dominic/i=J/"@MHS> Message-ID: <3A40DE1A.1F00B405@yale.edu> > Can someone point me at some more references? See http://haskell.org/papers/NSWC/jfp.ps. -Paul From peterd@availant.com Wed Dec 20 16:45:35 2000 From: peterd@availant.com (Peter Douglass) Date: Wed, 20 Dec 2000 11:45:35 -0500 Subject: Haskell Productivity Message-ID: <8BDAB3CD0E67D411B02400D0B79EA49A5F6CCC@smail01.clam.com> There is a thread on comp.lang.functional which may be of interest. Here is a link that might work for you. http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh 8ss$6le$1@bird.wu-wien.ac.at%3e%231/1 > -----Original Message----- > From: Steinitz, Dominic J > [mailto:Dominic.J.Steinitz@BritishAirways.com] > Sent: Wednesday, December 20, 2000 11:12 AM > To: haskell > Subject: Haskell Productivity > > > The Haskell website claims that > > "Ericsson measured an improvement factor of between 9 and 25 > in one set of experiments on telephony software". > > Presumably this is with Erlang not with Haskell. I have > searched for the reference that substantiates this claim but > I've only been able to find: > > http://set.gmd.de/~ap/femsys/wiger.html > > which talks about a productivity factor of 4 > > and > > http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haske ll-vs-ada-abstract.html which suggests that Haskell is about 2-3 times as productive as imperative languages. Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25? Thanks, Dominic. ---------------------------------------------------------------------------- --------------------- 21st century air travel http://www.britishairways.com _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell From peterd@availant.com Wed Dec 20 16:50:50 2000 From: peterd@availant.com (Peter Douglass) Date: Wed, 20 Dec 2000 11:50:50 -0500 Subject: Haskell Productivity Message-ID: <8BDAB3CD0E67D411B02400D0B79EA49A5F6CCF@smail01.clam.com> Hello all, You will need to manually reconnect the link I sent into a single line for it to work. > There is a thread on comp.lang.functional which may be of interest. > Here is a link that might work for you. > > http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh 8ss$6le$1@bird.wu-wien.ac.at%3e%231/1 From ashley@semantic.org Wed Dec 20 23:59:50 2000 From: ashley@semantic.org (Ashley Yakeley) Date: Wed, 20 Dec 2000 15:59:50 -0800 Subject: GHC for Darwin? Message-ID: <200012202359.PAA26221@mail4.halcyon.com> Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant that runs on the PowerPC processor. . I was going to compile it myself before I remembered that compilers do platform-specific code-generation. Duh. -- Ashley Yakeley, Seattle WA From simonmar@microsoft.com Wed Dec 20 17:46:25 2000 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 20 Dec 2000 09:46:25 -0800 Subject: ANNOUNCE: Happy version 1.9 Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell ----------------------------------------------------------------- I'm pleased to announce version 1.9 of Happy, the parser generator system for Haskell. Changes in this version, relative to version 1.8 (the previous full release): * A grammar may now contain several entry points, allowing several parsers to share parts of the grammar. * Some bugfixes. Happy is available in source form, which can be compiled with GHC version 4.xx (4.08.1 recommended), and we also provide binaries for some architectures. The Happy homepage with links to the various distributions lives at: http://www.haskell.org/happy/ Please send any bug reports and comments to simonmar@microsoft.com. From doaitse@cs.uu.nl Thu Dec 21 08:22:27 2000 From: doaitse@cs.uu.nl (S. Doaitse Swierstra) Date: Thu, 21 Dec 2000 10:22:27 +0200 Subject: GHC for Darwin? In-Reply-To: <200012202359.PAA26221@mail4.halcyon.com> References: <200012202359.PAA26221@mail4.halcyon.com> Message-ID: At 3:59 PM -0800 12/20/00, Ashley Yakeley wrote: >Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant >that runs on the PowerPC processor. >. > >I was going to compile it myself before I remembered that compilers do >platform-specific code-generation. Duh. > >-- >Ashley Yakeley, Seattle WA > > >_______________________________________________ >Haskell mailing list >Haskell@haskell.org >http://www.haskell.org/mailman/listinfo/haskell Atze Dijkstra (mailto:atze@cs.uu.nl) is working on a port of the GHC to MacOS X. He has reached the state where he managed to compile some programs (e.g. our attribute grammar system and combinator libraries). Doaitse Swierstra -- __________________________________________________________________________ S. Doaitse Swierstra, Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands Mail: mailto:doaitse@cs.uu.nl WWW: http://www.cs.uu.nl/ PGP Public Key: http://www.cs.uu.nl/people/doaitse/ tel: +31 (30) 253 3962, fax: +31 (30) 2513791 __________________________________________________________________________ From jeff@galconn.com Thu Dec 21 08:59:29 2000 From: jeff@galconn.com (Jeffrey R. Lewis) Date: Thu, 21 Dec 2000 00:59:29 -0800 Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> Message-ID: <3A41C671.B9EDF2E3@galconn.com> Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so, since > HasFoo Int b => Int -> b > is a substitution instance of > HasFoo a b => a -> b This is the step where the reasoning goes wrong. The functional dependency tells you that `b' isn't really a free variable, since it is dependent on `a'. If you substitute for `a', you can't expect `b' to remain unconstrained. Hugs complains that the inferred type for `f' is not general enough. It's right to complain, but the real problem is that the signature is too general. Asimilar situation arises if you try to declare an instance `HasFoo Int b', but in this case, hugs complains that the instance is more general than the dependency allows. A useful thing to do would be to check for this sort of thing in signatures as well, so that the more appropriate error message can be given. --Jeff From qrczak@knm.org.pl Thu Dec 21 10:05:14 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 21 Dec 2000 10:05:14 GMT Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> <3A41C671.B9EDF2E3@galconn.com> Message-ID: Thu, 21 Dec 2000 00:59:29 -0800, Jeffrey R. Lewis pisze: > > class HasFoo a b | a -> b where > > f :: HasFoo Int b => Int -> b > > f x = foo x > This is the step where the reasoning goes wrong. The functional > dependency tells you that `b' isn't really a free variable, since > it is dependent on `a'. If you substitute for `a', you can't expect > `b' to remain unconstrained. It's not unconstrained: the constraint is "HasFoo Int b", as written. IMHO it should not matter that the constraint fully determines b. > Asimilar situation arises if you try to declare an instance `HasFoo > Int b', but in this case, hugs complains that the instance is more > general than the dependency allows. ghc does not complain. How would I express "the instance can be chosen basing on 'a' alone, and the instance found will tell what constraints are on 'b'"? Aren't fundeps a too general mechanism which is not able to express simpler statements? :-( -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From chak@cse.unsw.edu.au Thu Dec 21 11:40:02 2000 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Thu, 21 Dec 2000 22:40:02 +1100 Subject: ANNOUNCE: Happy version 1.9 In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> References: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> Message-ID: <20001221224002G.chak@cse.unsw.edu.au> Simon Marlow wrote, > ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell > ----------------------------------------------------------------- A RedHat 7.0/i386 rpm package is available at ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/happy-1.9-1.i386.rpm and the matching source rpm at ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/happy-1.9-1.src.rpm Happy Hacking, Manuel From rrt1001@cam.ac.uk Thu Dec 21 11:58:42 2000 From: rrt1001@cam.ac.uk (Reuben Thomas) Date: Thu, 21 Dec 2000 11:58:42 +0000 (GMT) Subject: ANNOUNCE: Happy version 1.9 In-Reply-To: <20001221224002G.chak@cse.unsw.edu.au> Message-ID: > ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell > ----------------------------------------------------------------- A Windows InstallShield package is available at http://www.haskell.org/happy/dist/1.9/happy-1-9.exe -- http://sc3d.org/rrt/ | egrep, n. a bird that debugs bison From lennart@augustsson.net Thu Dec 21 12:11:33 2000 From: lennart@augustsson.net (Lennart Augustsson) Date: Thu, 21 Dec 2000 13:11:33 +0100 Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> Message-ID: <3A41F375.499AEC44@augustsson.net> Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so, since > HasFoo Int b => Int -> b > is a substitution instance of > HasFoo a b => a -> b > > but if we infer the type (HasFoo Int b => Int -> b) > for f's RHS, we can then "improve" it using the instance > decl to (HasFoo Int Bool => Int -> Bool), and now the signature > isn't a substitution insance of the type of the RHS. I definitely want it to be legal. I have examples where this is immensly useful. -- -- Lennart From qrczak@knm.org.pl Thu Dec 21 18:32:59 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 21 Dec 2000 18:32:59 GMT Subject: Are fundeps the right model at all? Message-ID: Could somebody show an example which requires fundeps and cannot be expressed using a simpler model explained below - a model that I can even understand? Is the model self-consistent at all? Each class is associated with a set of subsets of type variables in its head. Let's call it the set of keys. The intuitive meaning of a key is that types corresponding to these variables are sufficient to determine which instance to choose. They correspond to lhss of some fundeps. Plain classes without explicitly written keys correspond to having a single key consisting of all type variables. Keys influence the typechecking thus: - A type is unambiguous if for every class constraint in it there exists its key such that types in the constraint corresponding to type variables from the key contain no type variables which are absent in the type itself. - All class methods must have unambiguous types, i.e. for each method there must be a key whose all type variables are present in the method's type. - For each key, there must be no pair of instances whose heads projected to the class parameters from the key overlap. - For each class constraint of an unambiguous type an each its key there must be an instance found basing on this key, or the type is incorrect because of missing instances. Moreover, instances found basing on all keys must be identical. - Perhaps something must be said about class contexts and instance contexts. I'm not sure what yet. Examples: class Collection c e | c where empty :: c insert :: c -> e -> c class Monad m => MonadState s m | m where get :: m s put :: s -> m () newtype State s a = State {runState :: s -> (a,s)} instance Monad (State s) instance MonadState s (State s) test1:: Int -> Int test1 x = snd (runState get x) -- Not ambiguous. class IOvsST io st | io, st where -- Two single-element keys. ioToST :: io -> st stToIO :: st -> io instance IOvsST (IORef a) (STRef s a) where ioToST = unsafeCoerce# stToIO = unsafeCoerce# test2:: IORef a -> IORef a test2 = ioToST . stToIO -- Not ambiguous. class Foo a b | a instance Foo Int [a] -- This is rejected by Hugs (with fundep a->b) but I would definitely -- accept it. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From ger@tzi.de Thu Dec 21 20:20:46 2000 From: ger@tzi.de (George Russell) Date: Thu, 21 Dec 2000 21:20:46 +0100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: Message-ID: <3A42661E.7FCCAFFA@tzi.de> Alternatively, I wonder whether the current system of type classes is the right model at all. Although I prefer the Haskell system, I think it is instructive to compare it with the Standard ML (SML) system of structures and functors. My point is that both Haskell and SML impose one of two possible extremes on the user, and suffer for it. With SML, it is as if all instances are explicitly named. SML does not permit user-defined overloading, and so SML is not capable of understanding something such as a "type class of things we can compare", and has a horrible set of kludges to cope with implementing the equality operator. With Haskell, on the other hand, there is no way of referring to a particular instance when you want to. We see a particular consequence of that here, in that (unlike SML), it is not possible to associate an internal type with a given instance. Another problem is that no-one has any control over what instances get exported, because since instances are anonymous there is no way of referring to them. Hence the current procedure is to expose everything to the importer, which is surely a mistake. So if you agree with me up to here, perhaps you are agreed that it is worth while trying to find a middle way, in which we try to combine both approaches. Well I'm not an expert language designer, and I'm doing this off the top of my head late on Thursday evening, so please don't nitpick about syntax; I'm aware that parsing will probably be difficult in all sorts of ways with exactly what I'm writing, but that shouldn't be too hard to tweak. In particular I have followed SML in using "." to express qualification by something, even though Haskell already used "." for something else, because I can't be bothered right now to dig up a better symbol. On the other hand if my whole approach is a pile of elephant dung I apologise for wasting your time, and wish you a happy Christmas/holidays, but do try to find a better way of combining the best of SML functors and Haskell classes. Anyway here is my proposal. (1) We extend type classes to allow them to introduce types. Thus for example I would replace Marcin's first example by class Collectible e where type c -- or we could just omit the "type" keyword, trading clarity -- for conciseness. -- note also that we need a way of expressing a context for -- "c", EG that it's an instance of Eq. empty :: c insert :: c -> e -> c As usual, you can refer to "empty" and "insert" right away, but you can't refer to "c" without extra syntax. We need a way of referring to the particular instance of Collectible. So I suggest something like: singleton :: (method | Collectible e) => e -> method.c singleton el = insert empty el (2) We extend instance declarations in two ways. Firstly and obviously, we need a way of declaring the type c in the instance second declaration. The second thing is to introduce named instance declarations, like this: instance IntList | Collectible Int where type c = [Int] empty = [] insert = (flip(:)) To actually _refer_ to a specific instance, you would qualify with IntList. So you could refer to IntList.c, IntList.empty, IntList.insert, just like you would with SML. But as with Haskell, "empty" and "insert" would continue to be available implicitly. A more complicated example arises when you have instances depending on other instances. EG instance SetCollection | Ord el => Collectible el where type c = Set el empty = emptySet insert = addToSet -- new function, thank Simon Marlow Then, in this case, you would refer to SetCollection.c when you wanted to refer to the type c. However note that in this case we are implicitly using an anonymous use of Ord. Supposing you had previously defined (ignoring questions about overlapping instances for now . . .) instance EccentricOrd | Ord Int where ... and you wanted to define Sets in terms of EccentricOrd. Then I suggest that you use instead SetCollection(EccentricOrd).c and likewise SetCollection(EccentricOrd).empty and Sets(EccentricOrd).insert, though I hope that such monstrous constructions will not often be necessary. When they are, maybe it would be a good idea to allow the user to abbreviate, as in instance EccentricSet | Collectible Int = SetCollection(EccentricOrd) just as you can do in SML. (3) Finally it would be nice to extend the module syntax to allow named instances to be selectively exported and imported, just like variables. If I could ignore all pre-existing Haskell code I would specify that whenever a module has a specific import list, no instances are imported unless specified. However this is politically impossible, so instead I suggest that all anonymous instances continue to be implicitly imported, as now, but that named instances are only imported when named in the import list. EG "import File(instance SetCollection)". Also, I think it would be nice to have something similar to the "qualified" operator, by which class membership is NOT automatically inherited, and would have to be explicitly specified by referring to "SetCollection.insert" or indeed "SetCollection.singleton"; in particular this would provide a clean way of handling overlapping classes. OK, so I realise this is probably not the final answer, but wouldn't it be nice if something along these lines could be got to work? From ger@tzi.de Fri Dec 22 15:56:41 2000 From: ger@tzi.de (George Russell) Date: Fri, 22 Dec 2000 16:56:41 +0100 Subject: List.partition a bit too eager Message-ID: <3A4379B9.CBA6D281@tzi.de> I think the following program import List main = putStr . show . fst . (partition id) . cycle $ [True,False] should display [True,True,True,...]. But instead, for both GHC and Hugs, you get a stack overflow. Is this a bug, or could someone explain it to me? From qrczak@knm.org.pl Sun Dec 24 20:25:12 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 24 Dec 2000 20:25:12 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: Thu, 21 Dec 2000 21:20:46 +0100, George Russell pisze: > So if you agree with me up to here, perhaps you are agreed that it is worth > while trying to find a middle way, in which we try to combine both approaches. I am thinking about a yet different approach. Leave classes and SML structures as they are, and make *records* more flexible, to be used instead of classes if instances are to be manipulated explicitly, and instead of structures if we are using Haskell rather than SML or OCaml, and instead of objects if we are using Haskell rather than some OO language, and as a general way of expressing things behaving like fixed dictionaries of values. I have yet to play more with it. I already have some thoughts and a working preprocessor which translates my extensions to Haskell (with multi-parameter classes and fundeps). -------- GOALS -------- * Replace the current record mechanism with a better one. * Don't require sets of fields of different record types disjoint. It's not only to avoid inventing unique field names, but also to have functions polymorphic over all records containing specific fields of specific types. * Provide a way to specialize existing record types to new types that behave similarly except of small changes. I.e. kind of inheritance. * Since Haskell does not have subtyping, have coercions up the inheritance tree. Overloading functions on record types is not always enough, e.g. to put records in a heterogeneous collection they must be coerced to a common type. * Don't constrain the implementation of field access for different record types. As long as it behaves like a record, it is a record. * Don't constrain the implementation of methods even for the same record type. Since Haskell does not have subtyping, records which would have different types in other languages can have the same type in Haskell, as long as the same interface suffices. * Express keyword parameters of functions. A function might use many parameters refining its behavior which usually have some default values. Old code using that function must not break when more parameters are added. * A piece of code should be understandable locally, independently of definitions and instances present elsewhere. * Have a nice syntax. * Keep it simple and easily translatable to the core language. Fields and methods are really the same thing. Moreover, inheritance is really delegation and coercions are the same things as field accesses as well. Record types are not anonymous, unlike TREX. Field names are born implicitly and live in a separate namespace. Each field name is associated with a class of record types having that field. Instances of these classes are defined implicitly for types defined as records, but can also be given explicitly for any type. -------- FIELD SELECTION -------- A field selection expression of the form expr.label is equivalent to (.label) expr where (.label) :: (r.label :: a) => r -> a is an overloaded selector function. (rec.label:: a) is a syntax for Has_label rec a, where Has_label is the implicitly defined class for this label. Such class would look like this if it were defined as normal classes: class Has_label r a | r -> a where (.label) :: r -> a set_label :: r -> a -> r except that there are no real names Has_label nor set_label. -------- DEFINITION OF RECORD TYPES -------- The definition of a record type: data Monoid e = record zero :: e plus :: e -> e -> e defines the appropriate single-constructor algebraic type and obvious instances: instance (Monoid e).zero :: e where ... instance (Monoid e).plus :: e -> e -> e where ... We can construct values of this type thus: numAddMonoid :: Num e => Monoid e numAddMonoid = record zero = 0 plus = (+) The meaning of such overloaded record creation expressions will be specified later. -------- INHERITANCE -------- Here is another example of a record type definition: data Group e = record monoid :: Monoid e minus :: e -> e -> e neg :: e -> e monoid (zero, plus) x `minus` y = x `plus` neg y neg y = zero `minus` y This record type has three direct members: monoid, minus, and neg. monoid holds its zero and plus. We want to be able to extract zero and plus of a group directly, instead of going through the underlying monoid. We could define appropriate instances: instance (Group e).zero :: e where ... instance (Group e).plus :: e -> e -> e where ... and this is what the inheritance declaration monoid (zero, plus) does automatically for us. So groups too have zero and plus, which are deleagated to the monoid. Seen from outside, these fields are indistinguishable from proper Group's fields. -------- DEFAULT DEFINITIONS -------- minus and neg in Group have default definitions expressed in terms of each other. When making a Group we can provide the definition of either one or both, otherwise both will diverge. We could provide default definitions of inherited methods too. If they had default definition in the supertype, they would be overridden. This is how the system expresses OO methods belonging to a type: by default definitions. They can be overridden in subtypes or at object creation time. How is it done that the default definition of minus refers to the definition of neg which will be supplied later? It is not known yet which fields will be specified at creation time. OTOH at the creation time it is not known which fields have default definitions, because the creation expression is polymorphic over record types containing specific fields and will be instantiated based on the context. There is a standard class defined as follows: class Record r where bless :: r -> r A record creation expression, say: record zero = 0 plus = (+) is a syntactic sugar for a recursively defined object: let this = bless this `set_zero` 0 `set_plus` (+) in this The bless function, named after Perl's mechanism used in a similar context, returns a record with all fields initialized using their default definitions, or bottoms for fields with no defaults. Default definitions refer to other fields through the parameter of bless. As seen above, bless is applied to the record to be constructed, and then fields with values specified at creation time are overridden. That way all field definitions can find right versions of other fields, no matter which were defined together with the type and which were supplied at the creation time. The type of the above record creation expression is (Record r, Num a, Num b, r.zero :: a, r.plus :: b -> b -> b) => r -------- DEFINITION OF BLESS -------- Definition of a record type automatically makes it an instance of the class Record. A field from which some other fields are inherited is initialized to blessed value of the same field taken from the parameter of bless, modified by setting those fields which have default defintions. It sounds complicated but this is what yields right bindings of all definitions. If a type behaves like a record, it is a record. You can make Record instances of arbitrary types, making them constructible using the record syntax. bless should be lazy. Field setters can be strict. -------- UPDATING FIELDS -------- If fields represent state changing over time, they can be mutable references. Fields can also be updated in a functional style, but this is really construction of new objects basing on old ones. Field update syntax is as follows: expr.record label1 = value1 label2 = value2 It is equivalent to simple nested set_label applications. Fields initialized with default definitions will not switch to refer to updated values of other fields! All magic already happened at record creation time. This can be changed in at least two ways. First, you can define instances of appropriate Has_label classes yourself and associate arbitrary magic with field updates. Second, you can make such instance for the field that you want to be a function of other fields instead of putting the field in the record directly. Definitions of two methods of Has_label classes have special syntax: instance (a,b).fst :: a where (a,_).fst = a (_,b).record {fst = a} = (a,b) instance (a,b).snd :: b where (_,b).snd = b (a,_).record {snd = b} = (a,b) I.e. pattern.label is equivalent to (.label) pattern and defines the getter function, and pattern1.record {label = pattern2} defines the setter when applied to the record matching pattern1 and field value matching pattern2. Braces can be omitted, but they make the syntax more clear. -------- SYNTAX DETAILS -------- The record keyword triggers the layout rules. Value definitions after the record keyword look like let bindings. They can be defined by cases with argument patterns on the left of the equal sign. In record type definitions, record creations and record updates definitions of fields can refer to all fields mentioned in those constructs in an unqualified form. They can also refer to a special variable called this, which holds the whole record after construction or update. -------- EXAMPLE -------- This example introduces a feature of renaming fields while inheriting. > data Monoid e = record > zero :: e > plus :: e -> e -> e > > numAddMonoid :: Num e => Monoid e > numAddMonoid = record > zero = 0 > plus = (+) > > numMulMonoid :: Num e => Monoid e > numMulMonoid = record > zero = 1 > plus = (*) > > data Group e = record > monoid :: Monoid e > minus :: e -> e -> e > neg :: e -> e > monoid (zero, plus) > x `minus` y = x `plus` neg y > neg y = zero `minus` y > > numAddGroup :: Num e => Group e > numAddGroup = record > monoid = numAddMonoid > minus = (-) > neg = negate > > numMulGroup :: Fractional e => Group e > numMulGroup = record > monoid = numMulMonoid > minus = (/) > neg = recip > > data Ring e = record > addGroup :: Group e > mulMonoid :: Monoid e > addGroup (monoid as addMonoid, zero, plus, minus, neg) > mulMonoid (zero as one, plus as times) > > numRing :: Num e => Ring e > numRing = record > addGroup = numAddGroup > mulMonoid = numMulMonoid > > data Field e = record > addGroup :: Group e > mulGroup :: Group e > addGroup (monoid as addMonoid, zero, plus, minus, neg) > mulGroup (monoid as mulMonoid, zero as one, plus as times, > minus as div, neg as recip) > > instance (Field e).ring :: Ring e where > f.ring = record > addGroup = f.addGroup > mulMonoid = f.mulMonoid > f.record {ring = r} = f.record > addGroup = r.addGroup > mulMonoid = r.mulMonoid > > -- Alternatively a Field could consist of a Ring and div + recip. > -- The difference is an implementation detail not visible outside. > -- The following definition will work with either variant: > > numField :: Fractional e => Field e > numField = record > addGroup = numAddGroup > mulGroup = numMulGroup -------- PROBLEMS -------- If those records are to simulate classes, they should be able to have polymorphic fields. Unfortunately it does not work to have overloaded setters in this case. I don't know a good solution. Similarly we would want to have records with existentially quantified types. Again it does not work to have overloaded getters and setters. Listing all inherited fields can be annoying. It would not really work otherwise, as arbitrary instances for sypertypes can be added at any time. It is not necessary to list all fields: other fields are available through the field we inherit from anyway. It would be desirable to selectively export instances. -------- PROTOTYPE IMPLEMENTATION -------- I have an implementation of this in the form of a preprocessor, based on hssource from ghc-4.11's hslibs. I will polish it and put for downloading to let people play with my records. I hope to have more interesting examples. The difference between this implementation and the above proposal is that types of inherited fields must be given explicitly. This is because delegation instances would otherwise have to have types which are not accepted by ghc, and they would require -fallow-undecidable-instances if they were legal (which is not a surprise because cyclic inheritance makes it impossible to determine the type of the field). I reported the problem under the subject "Problem with functional dependencies" on December 17th. I believe that both problems can be fixed, especially if handling those constructs were inside the compiler. -------- THE REST OF MY REPLY TO GEORGE RUSSELL -------- > (1) We extend type classes to allow them to introduce types. If your classes were expressed as my records, it would roughly correspond to existential quantification. But there are big problems with typechecking in this approach. I hope somebody will invent a solution. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From fjh@cs.mu.oz.au Tue Dec 26 01:10:55 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Tue, 26 Dec 2000 12:10:55 +1100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: <3A42661E.7FCCAFFA@tzi.de> References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: <20001226121054.A20508@hg.cs.mu.oz.au> On 21-Dec-2000, George Russell wrote: > (3) Finally it would be nice to extend the module syntax to allow named > instances to be selectively exported and imported, just like variables. Mercury's module system allows instance declarations (which, as in Haskell 98, are unnamed) to be selectively exported. :- module foo. :- interface. :- import_module enum. :- type t. :- instance enum(t). :- implementation. :- instance enum(t) where [ ... ]. Mercury doesn't directly support selective import -- you can only import a whole module, not part of it. But if you really want that you can achieve it by putting each instance declaration in its own nested module. :- module foo. :- interface. :- import_module enum. :- type t. :- module enum_t. :- interface. :- instance enum(t). :- end_module enum_t. :- implementation. :- module enum_t. :- implementation. :- instance enum(t) where [ ... ]. :- end_module enum_t. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From qrczak@knm.org.pl Tue Dec 26 08:46:44 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 26 Dec 2000 08:46:44 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> <20001226121054.A20508@hg.cs.mu.oz.au> Message-ID: Tue, 26 Dec 2000 12:10:55 +1100, Fergus Henderson pisze: > Mercury's module system allows instance declarations (which, as in > Haskell 98, are unnamed) to be selectively exported. If they could be selectively exported in Haskell, how to make it compatible with the current assumption that they are exported by default? Selective hiding would be weird. Perhaps there should be a separate section for exporting instances. If not present, then everything is exported (as with plain module contents). I hope selective export would help with resolving conflicting instances. There might be a confusion if a function does indeed get a sorted list of objects of type T but it expected a different ordering, but the danger of inability of linking two independent libraries due to an innocent overlapping instance might be worse. As we are at it, it would be nice to be able to specify signatures and other interface details where they belong - in the export list. With a different syntax of the export list; there would be an ambiguity if ..., var1, var2 :: Type, ... gives Type to both variables or only one, and items should be separated by layoutable semicolons. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From Doug_Ransom@pml.com Wed Dec 27 18:33:42 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Wed, 27 Dec 2000 10:33:42 -0800 Subject: ANNOUNCE: HaXml 1.00 Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61DD@hermes.pml.com> I think it is important that a good haskell XML library be included as part of the haskell runtime library given XML's relevance. > -----Original Message----- > From: Malcolm Wallace [mailto:Malcolm.Wallace@cs.york.ac.uk] > Sent: Thursday, November 16, 2000 8:42 AM > To: haskell@haskell.org > Subject: ANNOUNCE: HaXml 1.00 > > > We are pleased to announce > > HaXml release 1.00 > -------------------- > > HaXml is a library enabling the use of Haskell and XML together, > together with several auxiliary tools for useful XML jobs. Fuller > details are on the web page. > > > What's new since 0.9? > --------------------- > The main addition is a full treatment of the external subset for DTDs. > The DtdToHaskell tool can now slurp in a single DTD from multiple > files, and also now treats conditional sections (INCLUDE and IGNORE) > correctly. > > There is improved error-reporting: lexing and parsing errors > now report > the relevant filename, and the line/column positions are more > accurate. > > > Where do I get it? > ------------------ > Web pages: http://www.cs.york.ac.uk/fp/HaXml/ > FTP site: ftp://ftp.cs.york.ac.uk/pub/haskell/HaXml/ > > An older version of HaXml is also included in GHC's hslibs, in package > "text". This will probably be updated to 1.00 at some time. > > Regards, > Malcolm > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > From Doug_Ransom@pml.com Thu Dec 28 01:30:19 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Wed, 27 Dec 2000 17:30:19 -0800 Subject: Learning Haskell and FP Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> I have read "The Craft of Functional Programming" by Simon Thompson and a few paper on the web. "The Craft" is a good book, but it is an introduction to FP. It seems to me it there are a lot of books on OO design I can pick up at the bookstore, but in the FP world, one must worm their way through all sorts of papers. I have seen papers on Catamorphisms, Monads, Programming with Barbed Wire, folds, etc. I think these papers are hard to understand if you don't have the acadademic/mathematical background -- being papers and not textbooks these papers assume a fair bit of base knowledge. I know I can design a fold function to use in place of primitive recursion for most data structures -- I just don't know if I should. It is pretty easy to get through "The Craft of Functional Programming" without understanding what Category Theory , a Catamorphism , or a Kleisli Composition is. I can see lots of real Software Engineering oppurtunities for these various techniques if I could just put them together. Is there a good textbook on Functional Programming which starts from a base point similar to "The craft of Functional Programming" but more advanced in terms of introducing necessary topics like Category theory, catamorphisms, monads, etc? I would find such a book very useful, especially if it concentrated on lazy functional programming. Doug Ransom Systems Engineer Power Measurement Ltd. http://www.pml.com 250-652-7100 office 250-652-0411 fax mailto:doug_ransom@pml.com From israelt@optushome.com.au Thu Dec 28 02:50:50 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 12:50:50 +1000 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> References: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: <200012281250500955.006178FD@mail> >I have read "The Craft of Functional Programming" by Simon Thompson and a >few paper on the web. "The Craft" is a good book, but it is an= introduction >to FP. >It seems to me it there are a lot of books on OO design I can pick up at= the >bookstore, but in the FP world, one must worm their way through all sorts= of >papers. I have seen papers on Catamorphisms, Monads, Programming with >Barbed Wire, folds, etc. I think these papers are hard to understand if= you >don't have the acadademic/mathematical background -- being papers and not >textbooks these papers assume a fair bit of base knowledge. I agree with this completely. The CFP book is a good introduction. Unforunately, the " Gentle Introduction To Haskell" that haskell.org links= to is not a very useful introduction. I am getting more out of Rex Paige's Two Dozen Short Lessons in Haskell.= ( I am studying Haskell and C# on my own in my spare time as break from my= medical practice ). From russell@brainlink.com Thu Dec 28 06:14:54 2000 From: russell@brainlink.com (Benjamin L. Russell) Date: Thu, 28 Dec 2000 01:14:54 -0500 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: While it may not be advanced or mathematical enough for your needs, you may wish to read _The Haskell School of Expression: Learning Functional Programming through Multimedia,_ by Paul Hudak. This is also an introductory book on functional programming, with a special focus on Haskell, although the examples used are mainly from multimedia. I compared the first few chapters of both _The Craft of Functional Programming_ and _The Haskell School of Expression,_ and personally found Hudak's book (the latter) much more interesting. The exercises are designed to teach the reader to think in terms of functional, as opposed to imperative or object-oriented, programming--hence the phrase in the title "School of Expression." --Ben -- Benjamin L. Russell russell@brainlink.com benjamin.russell.es.94@aya.yale.edu "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho On Wed, 27 Dec 2000 17:30:19 -0800 Doug Ransom wrote: > I have read "The Craft of Functional Programming" by > Simon Thompson and a > few paper on the web. "The Craft" is a good book, but it > is an introduction > to FP. > > > It seems to me it there are a lot of books on OO design I > can pick up at the > bookstore, but in the FP world, one must worm their way > through all sorts of > papers. I have seen papers on Catamorphisms, Monads, > Programming with > Barbed Wire, folds, etc. I think these papers are hard > to understand if you > don't have the acadademic/mathematical background -- > being papers and not > textbooks these papers assume a fair bit of base > knowledge. I know I can > design a fold function to use in place of primitive > recursion for most data > structures -- I just don't know if I should. It is pretty > easy to get > through "The Craft of Functional Programming" without > understanding what > Category Theory , a Catamorphism , or a Kleisli > Composition is. I can see > lots of real Software Engineering oppurtunities for these > various techniques > if I could just put them together. > > Is there a good textbook on Functional Programming which > starts from a base > point similar to "The craft of Functional Programming" > but more advanced in > terms of introducing necessary topics like Category > theory, catamorphisms, > monads, etc? I would find such a book very useful, > especially if it > concentrated on lazy functional programming. > > > Doug Ransom > Systems Engineer > Power Measurement Ltd. > http://www.pml.com > 250-652-7100 office > 250-652-0411 fax > mailto:doug_ransom@pml.com > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell From israelt@optushome.com.au Thu Dec 28 08:52:03 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 18:52:03 +1000 Subject: Learning Haskell and FP In-Reply-To: References: Message-ID: <200012281852030258.01AC2A6C@mail> >While it may not be advanced or mathematical enough for your needs, you= may wish to read _The Haskell School of Expression:=A0Learning Functional= Programming through Multimedia,_ by Paul Hudak. This is also an= introductory book on functional programming, with a special focus on= Haskell, although the examples used are mainly from multimedia. Is there an online version of Hudak's book ? ( For example Bruce Eckel has online versions of all his books available= online as well as in print ) >"Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho Translation please ! Basho is my favorite Japanese poet. Unfortunately my Japanese is at the Ohio level.. ( ohiogozaimazu) From israelt@optushome.com.au Thu Dec 28 08:53:08 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 18:53:08 +1000 Subject: Haskell newsgroup Message-ID: <200012281853080001.01AD2753@mail> How about starting a Haskell newsgroup ? The closest seems to be comp.lang.functional. From johanj@cs.uu.nl Thu Dec 28 14:06:26 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Thu, 28 Dec 2000 15:06:26 +0100 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: <20001228140611.B3E3B4536@mail.cs.uu.nl> >Is there a good textbook on Functional Programming which starts from a base >point similar to "The craft of Functional Programming" but more advanced in >terms of introducing necessary topics like Category theory, catamorphisms, >monads, etc? I would find such a book very useful, especially if it >concentrated on lazy functional programming. You might want to have a look at the series of three books on Advanced Functional Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would probably start with 925, which introduces monads, parser & pretty-printing combinators, monadic catamorphisms, constructor classes, etc. -- Johan Jeuring From franka@cs.uu.nl Thu Dec 28 15:48:57 2000 From: franka@cs.uu.nl (Frank Atanassow) Date: Thu, 28 Dec 2000 16:48:57 +0100 Subject: Learning Haskell and FP In-Reply-To: <200012281250500955.006178FD@mail>; from israelt@optushome.com.au on Thu, Dec 28, 2000 at 12:50:50PM +1000 References: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> <200012281250500955.006178FD@mail> Message-ID: <20001228164857.A13674@cs.uu.nl> i r thomas wrote (on 28-12-00 12:50 +1000): > Unforunately, the " Gentle Introduction To Haskell" that haskell.org links to is not a very useful introduction. > I am getting more out of Rex Paige's Two Dozen Short Lessons in Haskell. ( I am studying Haskell and C# on my own in my spare time as break from my medical practice ). What did you find unuseful about GITH? How could it be improved? What were your expectations for it? What was more useful about Rex Paige's notes? >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > Translation please ! Is it OK if I show off and steal some thunder? :) "(It's) An old pond! The sound of water steadily dripping in..." -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Doug_Ransom@pml.com Thu Dec 28 17:34:18 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Thu, 28 Dec 2000 09:34:18 -0800 Subject: Haskell newsgroup Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61ED@hermes.pml.com> That would only work if the haskell mailing list was either delete or mirrored onto a newsgroup. I would prefer a newsgroup myself for bandwidth reasons. > -----Original Message----- > From: i r thomas [mailto:israelt@optushome.com.au] > Sent: Thursday, December 28, 2000 12:53 AM > To: haskell@haskell.org > Subject: Haskell newsgroup > > > How about starting a Haskell newsgroup ? > The closest seems to be comp.lang.functional. > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > From Doug_Ransom@pml.com Thu Dec 28 17:36:37 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Thu, 28 Dec 2000 09:36:37 -0800 Subject: Learning Haskell and FP Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61EE@hermes.pml.com> Who are the audience for the books on Advanced Functional Programming? Academics with a theoretical CS background or someone with just a bit of understanding of FP? Ideally, I would like a course suited for someone who has completed a basic FP course. > -----Original Message----- > From: Johan Jeuring [mailto:johanj@cs.uu.nl] > Sent: Thursday, December 28, 2000 6:06 AM > To: Doug Ransom > Cc: haskell@haskell.org > Subject: Re: Learning Haskell and FP > > > >Is there a good textbook on Functional Programming which > starts from a base > >point similar to "The craft of Functional Programming" but > more advanced in > >terms of introducing necessary topics like Category theory, > catamorphisms, > >monads, etc? I would find such a book very useful, especially if it > >concentrated on lazy functional programming. > > You might want to have a look at the series of three books on Advanced > Functional > Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would > probably start with 925, which introduces monads, parser & > pretty-printing > combinators, monadic catamorphisms, constructor classes, etc. > > -- Johan Jeuring > From shlomif@vipe.technion.ac.il Thu Dec 28 19:23:07 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Thu, 28 Dec 2000 21:23:07 +0200 (IST) Subject: Haskell newsgroup In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61ED@hermes.pml.com> Message-ID: On Thu, 28 Dec 2000, Doug Ransom wrote: > That would only work if the haskell mailing list was either delete or > mirrored onto a newsgroup. I would prefer a newsgroup myself for bandwidth > reasons. > And I prefer a mailing-list. It's hard to access newsgroups from the Technion, and Deja-news seems to be little help when it comes to posting messages. Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From wli@holomorphy.com Thu Dec 28 19:40:38 2000 From: wli@holomorphy.com (William Lee Irwin III) Date: Thu, 28 Dec 2000 11:40:38 -0800 Subject: Haskell newsgroup In-Reply-To: <200012281853080001.01AD2753@mail>; from israelt@optushome.com.au on Thu, Dec 28, 2000 at 06:53:08PM +1000 References: <200012281853080001.01AD2753@mail> Message-ID: <20001228114038.N685@holomorphy.com> On Thu, Dec 28, 2000 at 06:53:08PM +1000, i r thomas wrote: > How about starting a Haskell newsgroup ? > The closest seems to be comp.lang.functional. There is a Haskell IRC channel on EfNet. I've been fielding Haskell questions there with Albert Lai and Ada Lim for several months. There has also been Haskell-related activity on OpenProjects Network #lisp. comp.lang.functional seems to be inclusive enough to obviate the need for a dedicated newsgroup. Cheers, Bill -- "And who knows, if you try it, maybe you find out that you like SM(L)? ;)" -- Markus Mottl on comp.lang.functional From proff@iq.org Thu Dec 28 22:20:13 2000 From: proff@iq.org (Julian Assange) Date: 29 Dec 2000 09:20:13 +1100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: George Russell's message of "Thu, 21 Dec 2000 21:20:46 +0100" References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: George Russell writes: > I'm writing, but that shouldn't be too hard to tweak. In particular I have > followed SML in using "." to express qualification by something, even though > Haskell already used "." for something else, because I can't be bothered right > now to dig up a better symbol. This is why all non S-exp like lanaguage are doomed to progressive syntactic cancer as the useful parts of operator name space and syntax space become progressively polluted and mutated by one fad after another. -- Julian Assange |If you want to build a ship, don't drum up people |together to collect wood or assign them tasks proff@iq.org |and work, but rather teach them to long for the endless proff@gnu.ai.mit.edu |immensity of the sea. -- Antoine de Saint Exupery From russell@brainlink.com Thu Dec 28 22:35:04 2000 From: russell@brainlink.com (Benjamin L. Russell) Date: Thu, 28 Dec 2000 17:35:04 -0500 Subject: Learning Haskell and FP In-Reply-To: <20001228164857.A13674@cs.uu.nl> Message-ID: On Thu, 28 Dec 2000 16:48:57 +0100 Frank Atanassow wrote: > i r thomas wrote (on 28-12-00 12:50 +1000): > > Unforunately, the " Gentle Introduction To Haskell" > that haskell.org links to is not a very useful > introduction. > > I am getting more out of Rex Paige's Two Dozen Short > Lessons in Haskell. ( I am studying Haskell and C# on my > own in my spare time as break from my medical practice ). > > What did you find unuseful about GITH? How could it be > improved? What were > your expectations for it? What was more useful about Rex > Paige's notes? I read part of _GITH,_ too; while it included information necessary for an introduction, the style seemed rather terse and dry, and rather difficult to follow at times, and read more like a manual with many technical details than a tutorial brimming with motivational material, especially when compared to _The Haskell School of Expression_ ("_HSE_" in the sequel). In particular, it could have had some more interesting examples or some more commentary, both of which made _HSE_ so fascinating. > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo > Basho > > > > Translation please ! > > Is it OK if I show off and steal some thunder? :) > > "(It's) An old pond! The sound of water steadily > dripping in..." Actually, if I may add, the translation I remember was the following: "[It's] An old pond! The sound of water as the frog jumps in...." "Kawazu" means "frog," and "tobikomu" means "(to) jump in." --Ben -- Benjamin L. Russell russell@brainlink.com benjamin.russell.es.94@aya.yale.edu "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho From jans@numeric-quest.com Thu Dec 28 18:29:46 2000 From: jans@numeric-quest.com (Jan Skibinski) Date: Thu, 28 Dec 2000 13:29:46 -0500 (EST) Subject: Learning Haskell and FP In-Reply-To: Message-ID: On Thu, 28 Dec 2000, Benjamin L. Russell wrote: > On Thu, 28 Dec 2000 16:48:57 +0100 > Frank Atanassow wrote: > > i r thomas wrote (on 28-12-00 12:50 +1000): > > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > > > > "(It's) An old pond! The sound of water steadily > > dripping in..." > > "[It's] An old pond! The sound of water as the frog jumps in...." Keeping with the minimalistic spirit of Haskell: pond frog plop! -- by James Kirkup, an English poet -- Supposedly from Hiroaki Sato collection of 80 English translations -- of this haiku. -- 3 down 77 to go.. Jan From fruehr@willamette.edu Fri Dec 29 00:42:32 2000 From: fruehr@willamette.edu (Fritz K Ruehr) Date: Thu, 28 Dec 2000 16:42:32 -0800 (PST) Subject: Learning Haskell and FP Message-ID: <200012290042.QAA29740@gemini.willamette.edu> [ Doug Ransom wrote about wanting a more advanced and design-oriented book on FP than "The Craft of Functional Programming" by Simon Thompson. In reply, Johan Jeuring recommended the Advanced Schools books (I concur). ] Let me add a few other recommendations, plus a vision of a book (not yet written, as far as I know) which might fit Doug's needs; I'll call it "The Design Patterns Haskell Companion" (see below). The "actual book" recommendations (all documented on haskell.org): * Introduction to Functional Programming using Haskell (second edition) by Richard Bird (Prentice Hall, ISBN: 0-13-484346-0) This book is an introductory text, like CFP, but it ramps up a bit faster and addresses design issues from a more advanced perspective (IMHO). It's certainly an excellent text, and it builds to a nice medium-sized design example (the program calculator of Chapter 12). It also leans toward a different style of design and programming, influenced by BMF/Squiggol. * Algebra of Programming by Richard Bird and Oege de Moor (Prentice Hall, ISBN: 0-13-507245-X) You might think of this as an advanced sequel to IFPH above, although it focuses more on the theory behind program calculation: categories and allegories figure prominently, and it leans even further in the direction indicated above. But there is nevertheless a lot of good material here which can serve as a foundation for design work, esp. the final chapters (7-10) on algorithms topics. * Algorithms: A Functional Programming Approach by Fethi Rabhi and Guy Lapalme (Addison-Wesley, ISBN: 0-201-59604-0) This is a concise tour through the usual gamut of data structures and algorithms topics typical of a "CS 2" course, but from a functional perspective. It is addressed more to people who are already familiar with programming and with the "standard" approach to DSA issues. It works very well as a reference but includes enough discussion to reward a straight reading. * Purely Functional Data Structures by Chris Okasaki (Cambridge University Press, ISBN: 0-521-66350-4) This one is similar to AFPA above (in being a tour of DSA topics from a functional perspective), but is a bit more advanced: e.g., Ch. 3 covers leftist heaps, binomial heaps and red-black trees. It also addresses issues of analysis in the context of lazy evaluation more thoroughly (Banker's method, etc.). The examples are written using SML, but an appendix (and a website) give Haskell versions. Of course, none of these books really answers the needs of the mature programmer/blossoming functional programmer who seeks advice on broader design issues in the context of lazy FP, esp. Haskell. This gap leads me to propose the fanciful book mentioned above: * The Design Patterns Haskell Companion by [someone(s) reading this list?] The title may be pandering a bit, but if the Smalltalk people can do it, why can't we? :) . In fact, the title is based on "The Design Patterns Smalltalk Companion" by Alpert, Brown and Woolf, a book I came across while reading up on design patterns. (It was recommended by a customer review on Amazon as being better than the original "gang of four" book.) The "Smalltalk Companion" serves an audience of mature programmers and attempts to document a number of "standard" design patterns in the specific context of Smalltalk. I'm not sure that the Haskell community would be comfortable referring to its collective design folklore in these terms, but I'm sure we would all welcome a good book written at this level which systematically addressed the motivation, rationale, trade-offs, etc. of the more advanced techniques of FP (i.e., monads, type and constructor classes, Xa-morphisms (for various X), higher-order and nested datatypes, etc.). As Johan mentioned, the "Advanced School" books serve this purpose to an extent, but they differ from my vision in two respects: first, they are collections of chapters on particular topics, written by different authors, and thus don't form a consistent, systematic review. Second, they are not (all) written from the specific perspective of design, so that for example they don't provide as much comparison and contrast *between* techniques. Of course, another motivation for such a book is that it might lend an air of credibility and maturity to the language, thus helping to promote it in the larger world. Casting it in terms of "design patterns" would certainly make sense for these purposes (and probably guarantees a certain audience, too), although I am still ambivalent about the need for Haskell to become a huge hit with mainstream audiences. In any case, if anyone is interested to write such a book, I will buy a copy :) . And if anyone wishes to collabrate on it, I am willing to help out. (I am not qualified to write it alone, and I think it would turn out best as a group effort in any case.) -- Fritz Ruehr fruehr@willamette.edu From john@foo.net Fri Dec 29 08:37:45 2000 From: john@foo.net (John Meacham) Date: Fri, 29 Dec 2000 00:37:45 -0800 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: ; from qrczak@knm.org.pl on Sun, Dec 24, 2000 at 08:25:12PM +0000 References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: <20001229003745.A11084@mark.ugcs.caltech.edu> I also like the approach of generalizing the record system, although I have not evaluated your particular proposal. Speaking of record improvements why is http://www.cse.ogi.edu/~mpj/pubs/lightrec.html not listed on the future of haskell page? has it already been determined to not be in the future of haskell or has no one gotten around to it? Does anyone else read this proposal and drool? Speaking of this proposal does anyone else see parallels between the lightweight modules proposal and the implicit parameters proposal http://www.cse.ogi.edu/~jlewis/implicit.ps.gz as implemented in ghc. in particular implicit parameters seem like they would be able to be implemented as syntatic sugar on the lightweight module system, one could rewrite implicit parameters as every function taking a record which we can call 'imp' now '?foo' can be rewritten as 'imp.foo' and the 'with ?foo = 1' construct can be rewritten as nimp = {imp | foo := 1} and then passing nimp to all called functions. I have not thought this too far thorough so I could be missing something obvious but I think it shows potential at least for the unification of two popular extensions. and I am pretty sure this was too obvious to mention in the lightweight records paper but the section of (.foo) being equivalent to (\{_|foo=v} -> v) seems appropriate. John -- -------------------------------------------------------------- John Meacham http://www.ugcs.caltech.edu/~john/ California Institute of Technology, Alum. john@foo.net -------------------------------------------------------------- From johanj@cs.uu.nl Fri Dec 29 10:48:58 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Fri, 29 Dec 2000 11:48:58 +0100 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EE@hermes.pml.com> Message-ID: <20001229104844.5C7F94539@mail.cs.uu.nl> >Who are the audience for the books on Advanced Functional Programming? >Academics with a theoretical CS background or someone with just a bit of >understanding of FP? Ideally, I would like a course suited for someone who >has completed a basic FP course. It varies a bit per school (book) and per article. But certainly LNCS 925 contains a number of chapters that should be interesting for someone with a general CS background and a basic FP course. I know it has been used in a couple of undergraduate courses on advanced functional programming. Topics, Authors, LNCS nr: - Monads, Wadler, 925 - Parser Combinators, Fokker, 925 - Constructor Classes, Jones, 925 - (Monadic) folds (or catamorphisms), Meijer & Jeuring, 925 - Space leaks and heap profiling, Runciman & Rojemo, 1129 - Algorithms and data structures, Okasaki, 1129 - Graph algorithms, Launchbury, 925 - User Interfaces, Carlsson & Hallgren, 925, Peyton Jones & Finne 1129 etc. Johan Jeuring http://www.cs.uu.nl/~johanj/ From franka@cs.uu.nl Fri Dec 29 13:31:01 2000 From: franka@cs.uu.nl (Frank Atanassow) Date: Fri, 29 Dec 2000 14:31:01 +0100 Subject: Learning Haskell and FP In-Reply-To: ; from russell@brainlink.com on Thu, Dec 28, 2000 at 05:35:04PM -0500 References: <20001228164857.A13674@cs.uu.nl> Message-ID: <20001229143101.A14014@cs.uu.nl> Benjamin L. Russell wrote (on 28-12-00 17:35 -0500): > > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > [..] Is it OK if I show off and steal some thunder? :) So much for that idea...! > > "(It's) An old pond! The sound of water steadily dripping in..." > > Actually, if I may add, the translation I remember was the following: > > "[It's] An old pond! The sound of water as the frog jumps in...." > > "Kawazu" means "frog," and "tobikomu" means "(to) jump in." That makes sense. I was guessing that "kawazu" was the old form of modern "kawarazu" (`without changing'). Modern `frog' is "kaeru", though, and the transitive form of "kawaru" (`change') is also "kaeru", so I suppose there is some linguistic relationship. "tobikomu" makes much more sense this way too. I thought it was a figurative usage, but it still didn't sound right... -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Doug_Ransom@pml.com Fri Dec 29 15:52:24 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Fri, 29 Dec 2000 07:52:24 -0800 Subject: Haskell Language Design Questions Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> 1. Is the lack of dynamic binding of functions by design or because it was too much effort to be justified at the time the language was designed? In object oriented programming there can be several implementations of the same interface, and they can be stored in the same collection. 2. It seems to me that the Maybe monad is a poor substitute for exception handling because the functions that raise errors may not necessarily support it. For example, if I use someone elses custom type and a custom map function theirmap myApplicator SomeList and theirmap is not designed to support the Maybe monad, then it becomes hard to use if SomeFunction might raise an error. Am I missing something? Doug Ransom Systems Engineer Power Measurement Ltd. http://www.pml.com 250-652-7100 office 250-652-0411 fax mailto:doug_ransom@pml.com From israelt@optushome.com.au Fri Dec 29 06:50:36 2000 From: israelt@optushome.com.au (i r thomas) Date: Fri, 29 Dec 2000 16:50:36 +1000 Subject: Learning Haskell and FP In-Reply-To: <200012290042.QAA29740@gemini.willamette.edu> References: <200012290042.QAA29740@gemini.willamette.edu> Message-ID: <200012291650360884.018BF6C5@mail> On 12/28/2000 at 7:00 PM Bill Halchin wrote: >Hello IR, > I agree with the OU Haskell Tutorial. It is excellent!! Yes, with a bit of editing and more diagrams , it would probably be worth= publishing. >BTW, what is your C# source? The .NET Framework SDK is freely downloadable from MS ( around 100 megs ) and comes with a C# tutorial, C# reference and a command line C#. There are also a few chapters online of some C# books that cover issues= like namespaces and attributes. I am using the Antechinus C# editor as an IDE . This comes with a few basic= C# examples as well. ( for vi freaks, I have written a C# vim syntax file that will appear on= vim.org once it is polished up.) From fjh@cs.mu.oz.au Sat Dec 30 03:50:04 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Sat, 30 Dec 2000 14:50:04 +1100 Subject: Haskell Language Design Questions In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> References: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> Message-ID: <20001230145004.A12063@hg.cs.mu.oz.au> On 29-Dec-2000, Doug Ransom wrote: > 1. Is the lack of dynamic binding of functions by design or because it was > too much effort to be justified at the time the language was designed? In > object oriented programming there can be several implementations of the same > interface, and they can be stored in the same collection. It's just something that didn't make it into Haskell 98. Hugs and ghc offer a language extension for that. It will almost certainly be in the next revision of Haskell. See . > 2. It seems to me that the Maybe monad is a poor substitute for > exception handling because the functions that raise errors may not > necessarily support it. Hugs and ghc also have exception handling extensions. See . There's also a paper or two on that. I hope you'll forgive the self-citation, but the only one for which I happen to have a reference on-hand is this one: A semantics for imprecise exceptions. Simon Peyton-Jones, Alastair Reid, Tony Hoare, Simon Marlow, and Fergus Henderson. Proceedings of the 1999 ACM SIGPLAN Conference on Programming Language Design and Implementation, May 1999. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From qrczak@knm.org.pl Sat Dec 30 09:34:22 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 30 Dec 2000 09:34:22 GMT Subject: Haskell Language Design Questions References: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> <20001230145004.A12063@hg.cs.mu.oz.au> Message-ID: Sat, 30 Dec 2000 14:50:04 +1100, Fergus Henderson pisze: > It's just something that didn't make it into Haskell 98. > Hugs and ghc offer a language extension for that. > It will almost certainly be in the next revision of Haskell. See > . Existential quantification is not always necessary to obtain an equivalent of dynamic binding. Dynamic binding is often used instead of function closures or IO action closures, especially in languages which lack real closures. An object of the abstract type "output IO stream" is equivalent to a record (tuple, whatever) of values of types like Char -> IO () -- write a character String -> IO () -- write a string IO () -- flush IO () -- close "Dynamic binding" is a fancy way of saying that the function to be called will be chosen at runtime. So we have exactly this, expressed in a simpler way. OO languages provide subtyping and inheritance. This is harder. Subtyping done by explicit coercions up can be done, but it's tedious to write (my new record scheme proposal tries to help here), and it's impossible to coerce down. Inheritance can be done by delegation. It does not work to express everything like OO languages usually do, because they are not typesafe. That's why (IMHO) that OO languages are usually dynamically typed. OO-like subtyping is usually not able to accurately express binary methods or the requirement that an argument must provide several interfaces at once. Haskell's classes should be left for constraints on types (as opposed to values). I want to sort a list, I compare elements with each other. It does not make sense to say that an element is comparable. Comparable with what? A _type_ can be comparable (i.e. ordered), or the ordering itself may be expressed as an object, but it does not belong to objects being compared. It follows that it does not make sense to have "a heterogeneous collection of comparable objects" or casting an object up to the type "comparable". But I might not care if the fact that something is a stream open for writing is a property of its type which is not statically known (as when stream is modelled as a class) or a property of all objects of the given type which is concrete (as when stream is modelled as a record of functions) - because I usually work with one such object at a time. When it's expressed as a class, I gain the possibility of extracting from the same object at different places properties belonging to different interfaces, without explicit coercions. But it is necessary to use existential quantification for heterogeneous collections. When it's expressed as a record of functions, all streams are flattened to a single interface, it is more convenient to use but the information about the exact kind of stream is not available. These approaches can be mixed. With my new record scheme proposal it is more convenient to introduce a class of types of objects from which the interface of a stream open for writing (expressed as a record of functions) can be extracted. This class needs not to be explicitly defined (only the record of functions). Stream operations can also be seen as provided by the object itself instead of always going through the extracted interface. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From R.Daniel@Europe.com Sat Dec 30 15:16:30 2000 From: R.Daniel@Europe.com (R.Daniel) Date: Sat, 30 Dec 2000 15:16:30 +0000 Subject: The Hanoi Towers Message-ID: <5.0.0.25.2.20001230151115.009ef3a0@mail.ip.pt> --=====================_12490613==_.ALT Content-Type: text/plain; charset="us-ascii"; format=flowed hi, i was looking for the source code for the Hanoi Towers, if anyone has that, could you please send it to me? I apreciate the help , thankx ----->R.Daniel Aka AZONIC ICQ 28959546 --=====================_12490613==_.ALT Content-Type: text/html; charset="us-ascii" hi, i was looking for the source code for the Hanoi Towers, if anyone has that, could you please send it to me?

I apreciate the help , thankx

----->R.Daniel Aka AZONIC
        ICQ           28959546 --=====================_12490613==_.ALT-- From qrczak@knm.org.pl Sat Dec 30 17:53:05 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 30 Dec 2000 17:53:05 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> <20001229003745.A11084@mark.ugcs.caltech.edu> Message-ID: Fri, 29 Dec 2000 00:37:45 -0800, John Meacham pisze: > http://www.cse.ogi.edu/~mpj/pubs/lightrec.html I've read it and posted some comments in February 2000. There was no answer AFAIR. Here are they again, slightly edited and extended: I don't understand why to separate kinds of rows and record types, instead of having "a type which is known to be a record type", at least on the level visible for the programmer. So instead of type Point r = (r | x::Int, y::Int) type Colored r = (r | c::Color) type ColoredPoint r = Point (Colored r) p :: {ColoredPoint()} -- Point, Colored, ColoredPoint :: row -> row it would be type Point r = {r | x::Int, y::Int} type Colored r = {r | c::Color} type ColoredPoint r = Point (Colored r) p :: ColoredPoint() -- Point, Colored, ColoredPoint :: recordType -> recordType -- where recordType is something like a subkind of *. -------- It is bad to require the programmers to think in advance that a type is going to be subtyped, and write elaborated type Point r = (r | x::Int, y::Int) ... {Point()} ... instead of simpler type Point = {x::Int, y::Int} ... Point ... which is not extensible. -------- I got used to () as a unit type. It would be a pity to lose it. -------- A minor problem. If tuples are records, field names should be such that alphabetic order gives the sequential order of fields, or have a special rule of field ordering for names of tuple fields... -------- In general I don't quite like the fact that records are getting more anonymous. Magical instances of basic classes? How inelegant. If I want the record type to have an identity, it will have to be wrapped in a newtype, so I must think at the beginning if I will ever want to write specialized insances for it and then all the code will depend on the decision. Currently a datatype with named fields has both an identity and convenient syntax of field access. (And why newtype is not mentioned in section 5.1?) I like name equivalence where it increases type safety. Extensible records promote structural equivalence. Unfortunately the proposal seems to increase the number of irregularities and inelegant rules... If expr.Constructor for a multiparameter constructor yields a tuple, then for an unary constructor it should give a 1-tuple, no? I know it would be extremely inconvenient, especially as newtypes are more used, so I don't propose it, but it is getting less regular. What about nullary constructors - empty tuple? :-) I don't say that I don't like the proposal at all, or that I never wanted to have several types with the same field names. But it is not clean for me, it's a compromise between usability and elegance, and from the elegance point of view I like current records more. Maybe it would be helpful to show how to translate a program with extensible records to a program without them (I guess it's possible in a quite natural way, but requires global transformation of the whole program). -------- Extensible records makes a syntactic difference between field access and function call. So if one wants to export a type abstractly or simply to provide functions operating on it without fixing the fact that they are physically fields, he ends in writing functions like size:: MyRecord -> Int size x = x.MyRecord.size which are unnecessary now, even if size is simply a field. It reminds me of C++ which wants us to provide methods for accessing data fields (for allowing them to be later redefined as methods, and for allowing everything to be uniformly used with "()" after the feature name). Ugh. -------- My new record scheme proposal does not provide such lightweight extensibility, but fields can be added and deleted in a controlled way if the right types and instances are made. The distinction between having a field and having a supertype is blurred. Similarly between having itself a field called foo and having a supertype which has a field called foo. Similarly between creating a record by adding fields to another record and creating a record by putting another record as one of fields. Similarly between casting to a supertype by removing some fields and extracting the supertype represented by a field. An advantage is that the interface of records does not constrain the representation in any way. It's up to how instances are defined, with the provision of natural definitions for records implemented physically as product types. For example supplying a color for a colorless point and the reverse operation can be written thus: addColor :: (Record cp, cp.point :: p, cp.color :: Color) => p -> Color -> cp addColor p c = record point = p; color = c removeColor :: (cp.point :: p) => cp -> p removeColor = (.point) When the following definitions are present: data Point = record x, y :: Int data ColoredPoint = record point :: Point point (x, y) color :: Color these functions can be used as of types addColor :: Point -> Color -> ColoredPoint removeColor :: ColoredPoint -> Point A colored point can be constructed either as in addColor, from a point and a color, or thus: record x = ... y = ... color = ... If ColoredPoint were defined directly as data ColoredPoint = record x, y :: Int color :: Color the previous interface could be *retroactively* reconstructed thus: instance (ColoredPoint).point :: Point where cp.point = record x = cp.x; y = cp.y cp.record {point = p} = cp.record x = p.x; y = p.y Multiple inheritance can be modelled as well. And field renaming during inheritance. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From kahl@heraklit.informatik.unibw-muenchen.de Fri Dec 22 16:04:45 2000 From: kahl@heraklit.informatik.unibw-muenchen.de (Wolfram Kahl) Date: 22 Dec 2000 16:04:45 -0000 Subject: 2nd CFP: RelMiS 2001 Message-ID: <20001222160445.29431.qmail@heraklit.informatik.unibw-muenchen.de> [please post. apologies for multiple copies] SECOND CALL FOR PAPERS RelMiS 2001 - Relational Methods in Software ============================================ 7-8 April 2001, Genova, Italy http://ist.unibw-muenchen.de/RelMiS/ A Satellite Event to ETAPS 2001 Important Dates =============== Deadline for submission: 10 January 2001 Notification of acceptance: 9 February 2001 Final version due: 28 February 2001 Workshop dates: 7-8 April 2001 Workshop Topics =============== * Relational Specifications and Modelling: methods and tools, tabular methods, abstract data types * Relational Software Design and Development Techniques: relational refinement, heuristic approaches for derivation, correctness considerations, dynamic programming, greedy algorithms, catamorphisms, paramorphisms, hylomorphisms and related topics * Programming with Relations: prototyping, testing, fault tolerance, information systems, information coding * Implementing relational algebra with mixed representation of relations * Handling of Large Relations: problems of scale, innovative representations, distributed implementation Submissions =========== Submissions will be evaluated by the Program Committee for inclusion in the proceedings, which will be published in the ENTCS series. Papers must contain original contributions, be clearly written, and include appropriate reference to and comparison with related work. Papers should be submitted electronically as uuencoded PostScript files at the address relmis@ist.unibw-muenchen.de. Preference will be given to papers that are no shorter than 10 and no longer than 15 pages. A separate message should also be sent, with a text-only one-page abstract and with mailing addresses (both postal and electronic), telephone number and fax number of the corresponding author. Final versions will have to be submitted as LaTeX source and have to adhere to the ENTCS style! Programme Committee =================== Rudolf Berghammer (Kiel), Jules Desharnais (Quebec), Wolfram Kahl (Munich), David L. Parnas (Hamilton), Gunther Schmidt (Munich) ------------- E-Mail: relmis@ist.unibw-muenchen.de Workshop home page: URL: http://ist.unibw-muenchen.de/RelMiS/ From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 11:03:58 2000 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Fri, 1 Dec 2000 11:03:58 +0000 Subject: a trap for the unwary Message-ID: Today, I thought I had discovered a bug in ghc. Then I tried hbc and Hugs, and they also rejected my program with the same error. nhc98 alone accepts it without complaint. I looked up the Report, and it seems that the program is indeed incorrect. Quick quiz: without running this through a compiler, who can spot the mistake? :-) > module Main where > import Char > f x = y > where > y | isSpace x = True > y | otherwise = False > main = print (f 'x') Regards, Malcolm From wimjan@xs4all.nl Fri Dec 1 14:49:13 2000 From: wimjan@xs4all.nl (Wim-Jan Hilgenbos) Date: Fri, 01 Dec 2000 15:49:13 +0100 Subject: Beginner: error when using multiple where stmts in hugs98 Message-ID: <3A27BA68.4EE70883@xs4all.nl> This is a multi-part message in MIME format. --------------F1E92FD1F075259053A3C4BA Content-Type: text/plain; charset=us-ascii Content-Transfer-Encoding: 7bit Hi, I've been trying some examples in functional programming. Most things work fine, but I have trouble with expressions with 'where' clauses that define more then one local definition. (I work with hugs98 version september 1999 under Linux) For example: ----------[ Mydiff.hs ]---------------------- module Mydiff where mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 ----------[ end Mydiff.hs ]------------------- When I try to load this module I get ERROR "Mydiff.hs" (line 5): Syntax error in input (unexpected `=') line 5 is the line h = 0.0001 I tried other examples like this one, played around with line-breaks white-space etc. Rewriting the f' line to f' x = (f (x+0.0001) - f x) / 0.0001 does the trick, but is not very satisfying. Can anyone help? WJ PS. I attached above example -- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Disclaimer: "These opinions are my own, though for a small fee they be yours too." -- Dave Haynie --------------F1E92FD1F075259053A3C4BA Content-Type: text/plain; charset=us-ascii; name="Mydiff.hs" Content-Transfer-Encoding: 7bit Content-Disposition: inline; filename="Mydiff.hs" module Mydiff where mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 --------------F1E92FD1F075259053A3C4BA-- From jmaessen@mit.edu Fri Dec 1 15:41:32 2000 From: jmaessen@mit.edu (Jan-Willem Maessen) Date: Fri, 1 Dec 2000 10:41:32 -0500 Subject: a trap for the unwary Message-ID: <200012011541.KAA00635@lauzeta.mit.edu> Malcolm Wallace writes: > Quick quiz: without running this through a compiler, who can spot > the mistake? :-) > > > module Main where > > import Char > > f x = y > > where > > y | isSpace x = True > > y | otherwise = False -- ** The problem line? > > main = print (f 'x') Without running this through the compiler, but based on similar problems I've had recently, I'd assume the problem is the marked line. Two outer-level patterns are each presented with guards. This would be correct for a function definition: > f x = y () > where > y _ | isSpace x = True > y _ | otherwise = False -- ** Does this work? This is a tricky issue. I'd like the original program to be all right. We end up sowing confusion with erroneous programs like this one: > f x = y > where > y | otherwise = False -- ** Now this pattern overlaps! > y | isSpace x = True But of course an analogous problem occurs in the function definition, and I think can be caught by turning on warnings in ghc. -Jan-Willem Maessen jmaessen@mit.edu From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 15:44:16 2000 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Fri, 1 Dec 2000 15:44:16 +0000 Subject: a trap for the unwary In-Reply-To: <200012011541.KAA00635@lauzeta.mit.edu> Message-ID: > > > f x = y > > > where > > > y | isSpace x = True > > > y | otherwise = False -- ** The problem line? Correct. Here y is a pattern binding, and multiple pattern bindings of the same variable are not permitted. > f x = y () > where > y _ | isSpace x = True > y _ | otherwise = False -- ** Does this work? Correct. Here y is a function binding instead, and multiple clauses *are* permitted. > I'd like the original program to be all right. Me too. I wrote 'y' as a 0-arity function, knowing that because it used a free variable bound at an outer scope, it would probably be lambda-lifted to a greater arity by the compiler. But only one compiler saw it in the same way as I did. :-) Of course, if the pattern binding is more complex than a single variable name, I still want the no-multiple-bindings rule to apply as usual: > f x = y () > where > (y:_) | isSpace x = [True] > (y:_) | otherwise = [False] -- ** Definitely wrong and indeed all compilers reject this, as they should. Regards, Malcolm From schulzs@uni-freiburg.de Fri Dec 1 17:23:57 2000 From: schulzs@uni-freiburg.de (Sebastian Schulz) Date: Fri, 01 Dec 2000 17:23:57 +0000 Subject: Beginner: error when using multiple where stmts in hugs98 References: <3A27BA68.4EE70883@xs4all.nl> Message-ID: <3A27DEAD.6FED7B7@shamoha.de> Wim-Jan Hilgenbos wrote: > > Hi, > > I've been trying some examples in functional programming. Most things > work fine, > but I have trouble with expressions with 'where' clauses that define > more then one > local definition. > (I work with hugs98 version september 1999 under Linux) > > For example: > > ----------[ Mydiff.hs ]---------------------- > module Mydiff where > > mydiff f = f' > where f' x = ( f (x+h) - f x) / h > h = 0.0001 > > ----------[ end Mydiff.hs ]------------------- > Try this: mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 It works fine with Hugs98 (feb2000). regards seb From ron4ld@pacific.net.au Fri Dec 1 21:08:56 2000 From: ron4ld@pacific.net.au (Ronald Kuwawi) Date: Sat, 02 Dec 2000 08:08:56 +1100 Subject: old easter egg Message-ID: <3A281368.7D24E3DC@pacific.net.au> open text editor, type hash :: [Char] -> Int hash = (foldl (+) 0) . (map ord) save as hash.hs load script, type: hash "MSDOS 6.000" or hash "SYSTEM 7.0" :-) Ronald From zhanyong.wan@yale.edu Fri Dec 1 21:55:06 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Fri, 01 Dec 2000 16:55:06 -0500 Subject: old easter egg References: <3A281368.7D24E3DC@pacific.net.au> Message-ID: <3A281E3A.66187BC7@yale.edu> Ronald Kuwawi wrote: > > open text editor, type > hash :: [Char] -> Int > hash = (foldl (+) 0) . (map ord) > > save as hash.hs > > load script, type: > hash "MSDOS 6.000" > > or > > hash "SYSTEM 7.0" or hash "HASKELL%98" :-) -- Zhanyong Wan From peterson-john@cs.yale.edu Fri Dec 1 22:14:41 2000 From: peterson-john@cs.yale.edu (John Peterson) Date: Fri, 1 Dec 2000 17:14:41 -0500 Subject: The Haskell store is open .... Message-ID: <200012012214.RAA28801@ragged.cs.yale.edu> Head to http://www.cafepress.com/haskell for your holiday shopping. Thanks to Conal Elliott and Fritz Ruehr for their artwork. Conal's design was produced by Pan so this shirt is in fact powered by Haskell! I'll be glad to add more designs in the future. Once cafepress lets me put more than one design in a store I'll consolidate everything. Meanwhile, if you want to set up a separate store I can link it into haskell.org for you. John From jf15@hermes.cam.ac.uk Sat Dec 2 00:03:30 2000 From: jf15@hermes.cam.ac.uk (Jon Fairbairn) Date: Sat, 2 Dec 2000 00:03:30 +0000 (GMT) Subject: old easter egg In-Reply-To: <3A281E3A.66187BC7@yale.edu> Message-ID: On Fri, 1 Dec 2000, Zhanyong Wan wrote: >=20 > Ronald Kuwawi wrote: > >=20 > > open text editor, type > > hash :: [Char] -> Int > > hash =3D (foldl (+) 0) . (map ord) > hash "HASKELL%98" hash "Haskell Ninety Eight !!"=20 surely? --=20 J=F3n Fairbairn Jon.Fairbairn@cl.cam.ac.uk From kili@outback.escape.de Sat Dec 2 02:31:05 2000 From: kili@outback.escape.de (Matthias Kilian) Date: Sat, 2 Dec 2000 03:31:05 +0100 (CET) Subject: old easter egg In-Reply-To: Message-ID: On Sat, 2 Dec 2000, Jon Fairbairn wrote: > > hash "HASKELL%98" > > > hash "Haskell Ninety Eight !!" Here's the who;e truth: hash "Turing!" Kili --=20 Nunja! Wenn man erst einmal anf=E4ngt zu denken, dann ist es wie eine Sucht. Man kommt nicht mehr los davon. [WoKo in dag=B0, 28.11.2000] From ashley@semantic.org Sat Dec 2 19:08:53 2000 From: ashley@semantic.org (Ashley Yakeley) Date: Sat, 2 Dec 2000 11:08:53 -0800 Subject: old easter egg Message-ID: <200012021908.LAA10458@mail4.halcyon.com> At 2000-12-01 13:08, Ronald Kuwawi wrote: >open text editor, type >hash :: [Char] -> Int >hash = (foldl (+) 0) . (map ord) > >save as hash.hs > >load script, type: >hash "MSDOS 6.000" > >or > >hash "SYSTEM 7.0" It's not really an easter egg, is it? It's more a modern form of numerology. I was hoping to see the hugs environment show me a little dancing bunny animation or something. letter c | ord c <= 64 = 0 letter c | ord c <= 90 = ord c - 64 letter c | ord c <= 96 = 0 letter c | ord c <= 122 = ord c - 96 letter c | otherwise = 0 renum n | n == 0 = 0 renum n | otherwise = (mod ((n - 1) * 19) 26) + 1 engql c = renum (letter c) engq = (foldl (+) 0) . (map engql) -- Ashley Yakeley, Seattle WA From gmh@marian.cs.nott.ac.uk Mon Dec 4 08:54:00 2000 From: gmh@marian.cs.nott.ac.uk (gmh@marian.cs.nott.ac.uk) Date: Mon, 4 Dec 2000 8:54:00 GMT Subject: JFP Special Issue on Haskell Message-ID: <20001204085501.0EA3F1016@www.haskell.org> Dear all, Please note that the deadline for submission to the JFP Special Issue on Haskell is in two months time --- 1st February 2001. Graham Hutton ---------------------------------------------------------------------- CALL FOR PAPERS Journal of Functional Programming Special Issue on Haskell Since its inception in 1987, Haskell has provided a focal point for research in lazy functional programming. During this time the language has continually evolved, as a result of both theoretical advances and practical experience. Haskell has proved to be a powerful tool for many kinds of programming tasks, and applications in industry are beginning to emerge. The recent definition of Haskell 98 provides a long-awaited stable version of the language, but there are many exciting possibilities for future versions of Haskell. The fourth Haskell Workshop was held as part of the PLI 2000 colloquium on Principles, Logics, and Implementations of high-level programming languages in Montreal, 17th September 2000. Previous Haskell Workshops have been held in Paris (1999), Amsterdam (1997) and La Jolla (1995). Following on from these workshops, a special issue of the Journal of Functional Programming will be devoted to Haskell. Possible topics include, but are not limited to: Critiques of Haskell 98; New proposals for Haskell; Applications or case studies; Programming techniques; Reasoning about programs; Semantic issues; Pedagogical issues; Implementation. Contributors to any of the Haskell workshops are invited to submit full papers to the special issue on Haskell, but submission is open to everyone. Submissions should be sent to the guest editor (address below), with a copy to Nasreen Ahmad (nasreen@dcs.gla.ac.uk). Submitted articles should be sent in postscript format, preferably gzipped and uuencoded. In addition, please send, as plain text, title, abstract, and contact information. The submission deadline is 1st February 2001. For other submission details, please consult an issue of JFP or see the Journal's web pages. Guest Editor: Graham Hutton School of Computer Science and IT The University of Nottingham Nottingham NG8 1BB United Kingdom gmh@cs.nott.ac.uk Useful Links: 2000 Haskell Workshop www.cs.nott.ac.uk/~gmh/hw00.html JFP Special Issue on Haskell www.cs.nott.ac.uk/~gmh/jfp.html JFP Home Page www.dcs.gla.ac.uk/jfp ---------------------------------------------------------------------- From zhanyong.wan@yale.edu Mon Dec 4 16:04:24 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Mon, 04 Dec 2000 11:04:24 -0500 Subject: Rank-2 polymorphism & type inference Message-ID: <3A2BC088.11497DEA@yale.edu> Hello, I'm playing with Haskell's rank-2 polymorphism extension and am puzzled by the following example: ----------------------------------------------------------- module R2Test where class SubType a b where super :: a -> b data Sub c a = Sub data Super c a = Super instance SubType (Sub c a) (Super c a) f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b f g x = undefined x :: Sub c Int x = undefined y :: Super c Int y = f (\a -> super a) x ---------------------------------------------------------- I though the definition of y should type-check because (roughly): 1. We know x :: Sub c Int, y :: Super c Int 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b, we know a is Int and b is Int. 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we are all set. However, Hugs 98 Feb 2000 (with the -98 switch) gives me: ERROR "R2Test.hs" (line 19): Cannot justify constraints in application *** Expression : \a -> super a *** Type : Sub b _1 -> Super b _2 *** Given context : () *** Constraints : SubType (Sub b _1) (Super b _2) and GHC 4.08.1 (with the -fglasgow-exts switch) gives: R2Test.hs:19: Could not deduce `SubType (Sub c a) (Super c Int)' from the context: () Probable cause: missing `SubType (Sub c a) (Super c Int)' in the type signature of an expression or missing instance declaration for `SubType (Sub c a) (Super c Int)' arising from use of `super' at R2Test.hs:16 In the right-hand side of a lambda abstraction: super a If I remove the "forall c." from the type signature for f, then both compilers accept my code. My question is: how does the type inference algorithm work in the presence of rank-2 types? Does anyone know of any documentation on this? Thanks! -- Zhanyong # Zhanyong Wan http://pantheon.yale.edu/~zw23/ ____ # Yale University, Dept of Computer Science /\___\ # P.O.Box 208285, New Haven, CT 06520-8285 ||___| From zhanyong.wan@yale.edu Mon Dec 4 21:30:46 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Mon, 04 Dec 2000 16:30:46 -0500 Subject: Rank-2 polymorphism & type inference References: <3A2BC088.11497DEA@yale.edu> Message-ID: <3A2C0D06.69F3058D@yale.edu> Hi, After sending out my question, I noticed that hugs and ghc understood my code differently: from the error messages, we can see that hugs view (\a -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it is Sub c a -> Super c Int. To verify it, I changed my code s.t. y is defined as y = f (\(a :: Sub c Int) -> super a) x instead of y = f (\a -> super a) x Guess what happened: ghc *accepted* the code, and hugs *rejected* it with message: ERROR "R2Test.hs" (line 19): Cannot justify constraints in application *** Expression : \a -> super a *** Type : Sub b Int -> Super b _2 *** Given context : () *** Constraints : SubType (Sub b Int) (Super b _2) Aha, this is something interesting! Either there is no standard for the Haskell rank-2 type inference algorithm (which is a sad thing), or one of hugs and ghc is wrong here. Now the hugs/ghc guys on the list can no longer remain silent -- you got to defend yourselves! :-) Could anyone explain to me what the right behavior is supposed to be here? Thanks. -- Zhanyong Zhanyong Wan wrote: > > Hello, > > I'm playing with Haskell's rank-2 polymorphism extension and am puzzled > by the following example: > > ----------------------------------------------------------- > module R2Test where > > class SubType a b where > super :: a -> b > > data Sub c a = Sub > data Super c a = Super > > instance SubType (Sub c a) (Super c a) > > f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b > f g x = undefined > > x :: Sub c Int > x = undefined > > y :: Super c Int > y = f (\a -> super a) x > ---------------------------------------------------------- > > I though the definition of y should type-check because (roughly): > > 1. We know x :: Sub c Int, y :: Super c Int > 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c > b, we know a is Int and b is Int. > 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we > are all set. > > However, Hugs 98 Feb 2000 (with the -98 switch) gives me: > > ERROR "R2Test.hs" (line 19): Cannot justify constraints in application > *** Expression : \a -> super a > *** Type : Sub b _1 -> Super b _2 > *** Given context : () > *** Constraints : SubType (Sub b _1) (Super b _2) > > and GHC 4.08.1 (with the -fglasgow-exts switch) gives: > > R2Test.hs:19: > Could not deduce `SubType (Sub c a) (Super c Int)' > from the context: () > Probable cause: missing `SubType (Sub c a) (Super c Int)' > in the type signature of an expression > or missing instance declaration for `SubType (Sub c > a) (Super > c Int)' > arising from use of `super' at R2Test.hs:16 > In the right-hand side of a lambda abstraction: super a > > If I remove the "forall c." from the type signature for f, then both > compilers accept my code. > > My question is: how does the type inference algorithm work in the > presence of rank-2 types? Does anyone know of any documentation on > this? Thanks! From simonpj@microsoft.com Tue Dec 5 13:12:20 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 5 Dec 2000 05:12:20 -0800 Subject: Rank-2 polymorphism & type inference Message-ID: <74096918BE6FD94B9068105F877C002D013781CA@red-pt-02.redmond.corp.microsoft.com> | > My question is: how does the type inference algorithm work in the | > presence of rank-2 types? Does anyone know of any documentation on | > this? Thanks! I had a look at this. Actually it turns out to be only loosely related to rank-2 polymorphism. I've been able to reproduce your problem using only Haskell 98. It looks like a problem with incomplete type inference Consider this: module MP where class C t where op :: t -> Bool instance C [t] where op x = True test :: [Int] -> Bool -- REQUIRED! test y = let f :: c -> Bool f x = op (y >> return x) in f (y::[Int]) Both GHC and Hugs reject this module if the type signature for test is omitted. NHC (v1.00, 2000-09-15) falls over completely, with Fail: Prelude.chr: bad argument All three succeed if the signature is in, or if the signature for f is omitted. This was unexpected, to me at least. You may need to add a type signature if polymorphic recursion is being used, but here it isn't! The problem is this: the compiler learns that y::[Int] "too late" to make use of it when solving the constraints arising from the RHS of f. In more detail, here's what happens. First we typecheck the RHS of f, deducing the types x :: a where a is fresh y :: k a where k is fresh y >> return x :: k a op (y >> return x) :: Bool with constraint C (k a) \x -> op (y >> return x) :: a -> Bool with constraint C (k a) Now we try to generalise over a. We need to discharge the contraint C (k a). Later we will find that y::[Int], so k=[], but we don't know that yet. So we can't solve the constraint. Adding the type signature to 'f' lets both GHC and Hugs figure out that y::[Int] in advance, so we need to solve the constraint C ([] a), which is fine. So I think you have uncovered a genuine problem, and one I don't know how to solve. It can always be "solved" by adding more type information, such as the type sig for 'test'. In you case you said: | After sending out my question, I noticed that hugs and ghc understood my | code differently: from the error messages, we can see that hugs view (\a | -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it | is Sub c a -> Super c Int. To verify it, I changed my code s.t. y is | defined as | | y = f (\(a :: Sub c Int) -> super a) x This is exactly right, and GHC is happy now. I can't account for Hugs' behaviour. The "right" solution is presumably to defer all constraint checking until we know what 'k' is. But that's a bit tricky because the constraint checking generates bindings that must appear in f's RHS. A full solution looks a bit over-kill-ish. But it's unsettling that the inference algorithm is incomplete. Simon From johanj@cs.uu.nl Tue Dec 5 14:22:06 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Tue, 05 Dec 2000 15:22:06 +0100 Subject: Call for papers: Haskell Workshop 2001 In-Reply-To: Message-ID: <20001205142154.B18FA451B@mail.cs.uu.nl> ============================================================================ CALL FOR PAPERS 2001 Haskell Workshop Firenze, Italy The Haskell Workshop forms part of the PLI 2001 colloquium on Principles, Logics, and Implementations of high-level programming languages, which comprises the ICFP/PPDP conferences and associated workshops. Previous Haskell Workshops have been held in La Jolla (1995), Amsterdam (1997), Paris (1999), and Montreal (2000). http://www.cs.uu.nl/people/ralf/hw2001.{html,pdf,ps,txt} ============================================================================ Scope ----- The purpose of the Haskell Workshop is to discuss experience with Haskell, and possible future developments for the language. The scope of the workshop includes all aspects of the design, semantics, theory, application, implementation, and teaching of Haskell. Submissions that discuss limitations of Haskell at present and/or propose new ideas for future versions of Haskell are particularly encouraged. Adopting an idea from ICFP 2000, the workshop also solicits two special classes of submissions, application letters and functional pearls, described below. Application Letters ------------------- An application letter describes experience using Haskell to solve real-world problems. Such a paper might typically be about six pages, and may be judged by interest of the application and novel use of Haskell. Functional Pearls ----------------- A functional pearl presents - using Haskell as a vehicle - an idea that is small, rounded, and glows with its own light. Such a paper might typically be about six pages, and may be judged by elegance of development and clarity of expression. Submission details ------------------ Deadline for submission: 1st June 2001 Notification of acceptance: 1st July 2001 Final submission due: 1st August 2001 Haskell Workshop: to be announced Authors should submit papers of at most 12 pages, in postscript format, formatted for A4 paper, to Ralf Hinze (ralf@cs.uu.nl) by 1st June 2001. The use of the ENTCS style files is strongly recommended. Application letters and functional pearls should be labeled as such on the first page. They may be any length up to twelve pages, though shorter submissions are welcome. The accepted papers will be published as a University of Utrecht technical report. Programme committee ------------------- Manuel Chakravarty University of New South Wales Jeremy Gibbons University of Oxford Ralf Hinze (chair) University of Utrecht Patrik Jansson Chalmers University Mark Jones Oregon Graduate Institute Ross Paterson City University, London Simon Peyton Jones Microsoft Research Stephanie Weirich Cornell University ============================================================================ From simonpj@microsoft.com Tue Dec 5 17:18:18 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 5 Dec 2000 09:18:18 -0800 Subject: Rank-2 polymorphism & type inference Message-ID: <74096918BE6FD94B9068105F877C002D013781D6@red-pt-02.redmond.corp.microsoft.com> Musing on Zhanyong's problem some more, a solution occurs to me. Curiously, it's exactly the solution required for another useful extension to type classes. Here is is, so people can shoot holes in it. | In more detail, here's what happens. First we typecheck the RHS of | f, deducing the types | | x :: a where a is fresh | y :: k a where k is fresh | y >> return x :: k a | op (y >> return x) :: Bool with constraint C (k a) | \x -> op (y >> return x) :: a -> Bool with constraint C (k a) | | Now we try to generalise over a. We need to discharge the contraint | C (k a). Later we will find that y::[Int], so k=[], but we | don't know that yet. So we can't solve the constraint. One bad solution I thought of was to give f the type f :: forall a. C (k a) => a -> Bool This is bad because it's not the type signature the programmer specified. (It's also bad operationally because we'll pass a dictionary at runtime, which isn't necessary.) The good solution is to say this: \x -> op (y >> return x) :: a -> Bool with constraint C (k a) (just as before) /\a \x -> op (y>>return x) :: forall a. a -> Bool with constraint (forall a. C (k a)) This requires us to permit constraints with for-alls in them. As luck would have it, Ralf Hinze and I propose just such a thing in our paper "Derivable Type Classes" (Section 7) http://research.microsoft.com/~simonpj/#derive The motivation there is this: how can you write an equality instance for data T k a = MkT (k (T k a)) We can try: instance ... => Eq (T k a) where (MkT a) == (MkT b) = a == b But what is the "..."? We need that "k" is an equality type constructor. The right context is instance (forall a. Eq a => Eq (k a)) => Eq (T k a) where ...as before... Aha! A constraint with a for-all. There are some more details in the paper. So perhaps there's a reason for adding this extension in the implementation (to solve Zhanyong's problem) even for a Haskell 98 compiler. Simon From francois.xavier.bodin@winealley.com Wed Dec 6 19:52:00 2000 From: francois.xavier.bodin@winealley.com (francois.xavier.bodin@winealley.com) Date: Wed, 6 Dec 2000 20:52 +0100 Subject: Meet us on Wine Alley Message-ID: <20001206195207.C9A321034@www.haskell.org> Hello! I found your address on a site about wine, food and good living. I thought = that you will be interested by the services that our site offers. www.wine-alley.com is a virtual Club for all those interested in wine in bo= th a professional and personal capacity. We now have more than 3900 members, both amateur and in the trade who use o= ur site to discuss wine, buy and sell it and tell us about the best sources. Club members use the Newsgroup of www.wine-alley.com to exchange informatio= n and experiences. Only the other day someone asked how much a certain rar= e wine was worth, I asked for more information about the grape variety, whi= ch doesn't grow in France. Currently there have been more than 717 question= s and replies. There is also the small ads. column. Among the 7 adverts placed this week there have been some really good deals= including a magnum of 1945 Pichon Lalande and a 1947 Cheval blanc! Let me make it clear - www.wine-alley.com itself does not sell or buy wine:= we simply offer our members the facilites for making their own arrangement= s. www.wine-alley.com is also a site supplying information in real time, parti= cularly the latest news from winegrowers and makers via the French Press Ag= ency (AFP). We also have a database of more than 21,000 wines with informa= tion supplied directly to the site by winegrowers co-operatives and special= ist magazines. I should be delighted if you would come and join us. At www.wine-alley.com= you will find similarly-minded people who just want to share their love of= wine. Kind regards Fran=E7ois Xavier Bodin, Manager of the Online Club fx.bodin@winealley.com PS. Registering with the www.wine-alley.com club is absolutely free and co= mmits you to nothing. If you are not interested in my offer, please excuse this letter; I am sorr= y to have bothered you. To prevent further unwanted intrusions please clic= k on the following link, your email will be automatically removed from our = list. http://www.wine-alley.com/wines/desmail.asp?id=3D307392&l=3Duk From harald@cs.mu.OZ.AU Mon Dec 11 13:13:58 2000 From: harald@cs.mu.OZ.AU (Harald Sondergaard) Date: Tue, 12 Dec 2000 00:13:58 +1100 Subject: PPDP 2001: Call for Papers Message-ID: <200012111314.AAA03065@mundook.cs.mu.OZ.AU> Third International Conference on PRINCIPLES AND PRACTICE OF DECLARATIVE PROGRAMMING Firenze, Italy, 5-7 September 2001 CALL FOR PAPERS PPDP 2001 aims to stimulate research on the use of declarative methods in programming and on the design, implementation and application of programming languages that support such methods. Topics of interest include any aspect related to understanding, integrating and extending programming paradigms such as those for functional, logic, constraint and object-oriented programming; concurrent extensions and mobile computing; type theory; support for modularity; use of logical methods in the design of program development tools; program analysis and verification; abstract interpretation; development of implementation methods; application of the relevant paradigms and associated methods in industry and education. This list is not exhaustive: submissions describing new and interesting ideas relating broadly to declarative programming are encouraged. The technical program of the conference will combine presentations of the accepted papers with invited talks and advanced tutorials. PPDP 2001 is part of a federation of colloquia known as Principles, Logics and Implementations of high-level programming languages (PLI 2001) which includes the ACM SIGPLAN International Conference on Functional Programming (ICFP 2001). The colloquia will run from 2 to 8 September, 2001. The venue for the conference is Firenze (Florence), one of Europe's most attractive cities, famous for its churches, galleries and museums. For more details, see the conference web site. Important Dates: Submission 15 March 2001 Notification 7 May 2001 Final Version 11 June 2001 Affiliated Workshops: Proposals are being solicited for PLI 2001 affiliated workshops. Details about the submission of proposals are available at http://music.dsi.unifi.it/pli01/wkshops. Web Sites and Email Contact: PPDP 2001: http://music.dsi.unifi.it/pli01/ppdp PLI 2001: http://music.dsi.unifi.it/pli01 mailto:ppdp01@cs.mu.oz.au Conference Chair: Rocco De Nicola, Universita di Firenze http://www.dsi.unifi.it/~denicola/ mailto:denicola@dsi.unifi.it Program Chair: Harald Sondergaard, The University of Melbourne http://www.cs.mu.oz.au/~harald/ mailto:harald@cs.mu.oz.au Program Committee: Maria Alpuente, Univ. Politecnica de Valencia, ES Yves Caseau, Bouygues, FR Michael Codish, Ben-Gurion Univ. of the Negev, IL Saumya Debray, Univ. of Arizona, US Conal Elliott, Microsoft Research, US Sandro Etalle, Univ. Maastricht, NL Roberto Giacobazzi, Univ. di Verona, IT Michael Leuschel, Univ. of Southampton, GB John Lloyd, Australian National Univ., AU Torben Mogensen, Kobenhavns Univ., DK Alan Mycroft, Cambridge Univ., GB Gopalan Nadathur, Univ. of Minnesota, US Martin Odersky, Ecole Polyt. Fed. Lausanne, CH Catuscia Palamidessi, Penn State Univ., US Andreas Podelski, Max-Planck-Inst. Informatik, DE Kostis Sagonas, Uppsala Univ., SE Christian Schulte, Univ. des Saarlandes, DE Michael Schwartzbach, Aarhus Univ., DK Harald Sondergaard, Univ. of Melbourne, AU Peter J. Stuckey, Univ. of Melbourne, AU From venneri@dsi.unifi.it Wed Dec 13 20:06:41 2000 From: venneri@dsi.unifi.it (b.venneri) Date: Wed, 13 Dec 2000 16:06:41 -0400 Subject: PLI 2001: call for workshop proposals Message-ID: CALL FOR WORKSHOP PROPOSALS Principles, Logics and Implementations of high-level programming languages (PLI 2001) Firenze, Italy September 3 - 7, 2001 http://music.dsi.unifi.it/pli01 PLI 2001, a federation of colloquia which includes ICFP 2001 (ACM-SIGPLAN International Conference on Functional Programming) and PPDP 2001 (ACM-SIGPLAN International Conference on Principles and Practice of Declarative Programming), will be held in Firenze, Italy, September 3-7 2001. Workshops affiliated to PLI 2001 will be held before, after or in parallel with the main conferences. Researchers and practitioners are invited to submit workshop proposals, that should be sent to the PLI 2001 Workshop Chair Betti Venneri mailto:venneri@dsi.unifi.it with "PLI01 Workshop Submission" in the subject header. Proposals should include * a short scientific justification of the proposed topic (somehow related to the colloquia), * names and contact information of the organizers, * expected number of participants and duration (the preference is for one day-long workshops), * estimated dates for paper submissions, notification of acceptance and final versions and any other relevant information (e.g., invited speakers, publication policy, etc.). THE DEADLINE FOR RECEIPT OF PROPOSALS IS JANUARY 8, 2001. Proposals will be evaluated by the PLI 2001 Workshop Chair, the ICFP and PPDP Program Chairs and Conference Chairs. Notification of acceptance will be made by February 2, 2001. The titles and brief information related to accepted workshop proposals will be included in the conference program and advertised in the call for participation. Workshop organizers will be responsible for producing a Call for papers and a Web site, for reviewing and making acceptance decisions on submitted papers, and for scheduling workshop activities in consultation with the local organizers. Workshop selection committee: Xavier Leroy (INRIA, France), ICFP 2001 Program Chair Benjamin C. Pierce (Univ. of Pennsylvania), ICFP 2001 Conference Chair Harald Sondergaard (Univ. of Melbourne), PPDP 2001 Program Chair Rocco De Nicola (Univ. of Firenze), PPDP 2001 Conference Chair Betti Venneri (Univ. of Firenze), PLI 2001 Workshop Chair. we From shlomif@vipe.technion.ac.il Fri Dec 15 19:47:27 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Fri, 15 Dec 2000 21:47:27 +0200 (IST) Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: Hi! As some of you may know, a Haskell program that prints all the primes can be as short as the following: primes = sieve [2.. ] where sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] Now, this program roughly corresponds to the following perl program: ###### SNIP SNIP ##### #!/usr/bin/perl use strict; my (@primes, $a, $p); @primes = (2); MAIN_LOOP: for($a = 3; $a < 1000; $a++) { foreach $p (@primes) { if ($a % $p == 0) { next MAIN_LOOP; } } push @primes, $a; } print join(", ", @primes); ####### SNIP SNIP ##### The program can be more optimized for both speed and code size, but I wanted to make it as verbose as possible. The algorithm keeps a list of the primes, and for each new number checks if it is divisable by any of them and if not it adds it to the list. There is a different algorithm which keeps a boolean map which tells whether the number at that position is prime or not. At start it is initialized to all trues. The algorithm iterates over all the numbers from 2 to the square root of the desired bound, and if it encounters a prime number it marks all the numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally considered a better algorithm than the previous one, because it uses less costier operations (multiplications and additions instead of modulos.) The perl program that implements that algorithm is this: #### SNIP SNIP ##### #!/usr/bin/perl use strict; sub primes { my $how_much = shift; my (@array, $bound, $a, $b, @primes); @array = (1) x $how_much; $bound = int(sqrt($how_much))+1; for($a=2;$a<=$bound;$a++) { if ($array[$a]) { for($b=$a*$a;$b<$how_much;$b+=$a) { $array[$b] = 0; } push @primes, $a; } } for(;$a<$how_much;$a++) { if ($array[$a]) { push @primes, $a; } } return @primes; } print join(", ", primes(1000)); ##### SNIP SNIP ###### Now, I tried writing an equivalent Haskell program and the best I could do was the following: ---- SNIP SNIP ----- module Primes where import Prelude import Array how_much :: Int how_much = 1000 initial_primes_map :: Array Int Bool initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ] mybound :: Int mybound = ceiling(sqrt(fromInteger(toInteger(how_much)))) next_primes_map :: Int -> Array Int Bool -> Array Int Bool next_primes_map a primes_map = if (a == mybound) then primes_map else next_primes_map (a+1) ( if primes_map!a then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ] else primes_map ) prime_bound :: Int -> Int prime_bound a = (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a)))) get_primes_map :: Array Int Bool get_primes_map = (next_primes_map 2 initial_primes_map) list_primes :: Array Int Bool -> Int -> [Int] list_primes primes_map n = if (n > how_much) then [] else ( if primes_map!n then n:(list_primes primes_map (n+1)) else list_primes primes_map (n+1) ) show_primes = show (list_primes get_primes_map 2) ---- SNIP SNIP ----- The problem is that when running it on hugs98 on a Windows98 computer with 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When entering how_much as 50,000 I get the following message: ERROR: Garbage collection fails to reclaim sufficient space In perl I can scale beyond 100,000, and if I modify the code to use a bit vector (using vec) to much more. So my question is what am I or hugs are doing wrong and how I can write better code that implements this specific algorithm. >From what I saw I used tail recursion, (and hugs98 has proper tail recursion, right?), and there's only one primes_map present at each iteration (and thus, at all), so it shouldn't be too problematic. Does it have to do with the way hugs98 implements and Int to Bool array? Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From jenglish@flightlab.com Sat Dec 16 23:21:48 2000 From: jenglish@flightlab.com (Joe English) Date: Sat, 16 Dec 2000 15:21:48 -0800 Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: References: Message-ID: <200012162321.PAA00918@dragon.flightlab.com> Shlomi Fish wrote: > As some of you may know, a Haskell program that prints all the primes can be > as short as the following: > > primes = sieve [2.. ] where > sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] > > Now, this program roughly corresponds to the following perl program: [ ~20 line Perl program snipped ] > The program can be more optimized for both speed and code size, but I wanted > to make it as verbose as possible. > > There is a different algorithm which keeps a boolean map [...] > The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. [~40 line Perl implementation snipped] > Now, I tried writing an equivalent Haskell program and the best I > could do was the following: [ ~45 line Haskell implementation snipped ] Another way to do this is to compute the final array directly, instead of computing successive versions of the array: import Array primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where primesMap = accumArray (||) False (2,n) multList multList = [(m,True) | j <- [2 .. n `div` 2], m <- multiples j] multiples j = takeWhile (n>=) [k*j | k <- [2..]] Now this version does a lot more work than the algorithm described above -- it computes multiples of *all* the integers less than n/2, not just the primes less than sqrt(n) -- but it has the virtue of being short enough to reason about effectively and is probably a better starting point for further optimization. > The problem is that when running it on hugs98 on a Windows98 computer with > 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When > entering how_much as 50,000 I get the following message: > > ERROR: Garbage collection fails to reclaim sufficient space My implementation fares even worse under Hugs -- it runs out of space around n = 4500 (Linux box, 64M RAM). With GHC it has no problem for n = 100,000, although the space usage is still extremely poor. It grows to consume all available RAM at around n = 200,000. (On the other hand, it's considerably faster than the traditional 2-liner listed above, up to the point where it starts paging). I suspect the poor memory usage is due to the way accumArray works -- it's building up a huge array of suspensions of the form (False && (False && ( ... && True))) that aren't reduced until an array element is requested. (A strict version of accumArray, analogous to "foldl_strict" defined below, would solve this problem, but I don't see any way to implement it in Standard Haskell). > In perl I can scale beyond 100,000, and if I modify the code to use a bit > vector (using vec) to much more. So my question is what am I or hugs are > doing wrong and how I can write better code that implements this specific > algorithm. > > From what I saw I used tail recursion, (and hugs98 has proper tail recursion > right?), and there's only one primes_map present at each iteration (and thus, > at all), so it shouldn't be too problematic. Actually no; this is a common misconception. In a strict language like Scheme, tail call optimization works because a tail call is the last thing a function does. In Haskell though the tail call is the *first* thing that gets evaluated (more or less), leaving all the "earlier" work as an unevaluated suspension. Code that is space-efficient in a strict language frequently suffers from awful space leaks in a lazy language. For example: sum_first_n_integers n = f n 0 where f 0 a = a f n a = f (n-1) (n+a) quickly leads to a "Control Stack Overflow" error in Hugs. BTW, the trick to fix it is to change the last line to: f n acc = f (n-1) $! (n+acc) or to replace the whole thing with: foldl_strict (+) 0 [1..n] where foldl_strict f a [] = a foldl_strict f a (x:xs) = (foldl_strict f $! f a x) xs > Does it have to do with the way hugs98 implements and Int to Bool array? Most likely yes. Hugs is optimized for interactive use and quick compilation, not for space usage. Try it with GHC or HBC and see how it does. --Joe English jenglish@flightlab.com From ahey@iee.org Sun Dec 17 11:59:43 2000 From: ahey@iee.org (Adrian Hey) Date: Sun, 17 Dec 2000 11:59:43 +0000 (GMT) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: On Fri 15 Dec, Shlomi Fish wrote: > There is a different algorithm which keeps a boolean map which tells whether > the number at that position is prime or not. At start it is initialized to all > trues. The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally > considered a better algorithm than the previous one, because it uses less > costier operations (multiplications and additions instead of modulos.) Functional programming languages are notoriously ineffecient at array handling (though I'm not sure exactly what the various Haskell implementations actually do). You can use a variation of this algorithm with lazy lists.. primes = 2:(get_primes [3,5..]) get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs)) strike step x_now (x:xs) = case (compare x_now x) of LT -> strike step (x_now+step) (x:xs) EQ -> strike step (x_now+step) xs GT -> x:(strike step x_now xs) The equivalent program in Clean (on a MAC) gets upto 877783 before giving a stack overflow error (1000K of stack, 4000K of Heap allocated). (I haven't actually tried this in Haskell 'cos I don't have a Windoze or 'nix box.) Regards -- Adrian Hey From qrczak@knm.org.pl Sun Dec 17 19:29:32 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 17 Dec 2000 19:29:32 GMT Subject: Problem with functional dependencies Message-ID: The following module is rejected by both ghc -fglasgow-exts -fallow-undecidable-instances and hugs -98 ------------------------------------------------------------------------ class HasFoo a foo | a -> foo where foo :: a -> foo data A = A Int data B = B A instance HasFoo A Int where foo (A x) = x instance HasFoo A foo => HasFoo B foo where foo (B a) = foo a ------------------------------------------------------------------------ The error messsage says that the type inferred for foo in B's instance is not general enough: the rhs has type "HasFoo B Int => B -> Int", but "HasFoo B foo => B -> foo" was expected. Should it really be wrong? I don't know the details of type inference with fundeps, but intuitively it should work, yielding an instance HasFoo B Int. Could it be made legal please? With the fundep removed, it works. I need it for a preprocessor which generates instances like that for B without knowing the type to put as the second class argument. Fundeps aren't essential, but... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From elke.kasimir@catmint.de Sun Dec 17 18:56:46 2000 From: elke.kasimir@catmint.de (Elke Kasimir) Date: Sun, 17 Dec 2000 19:56:46 +0100 (CET) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: This message is in MIME format --_=XFMail.1.3.p0.Linux:001217195636:327=_ Content-Type: text/plain; charset=iso-8859-1 Your algorithm seems to be based on the following idea: calculate the non-primes and derive the primes from them by calculating the set difference of the natural numbers and the non-primes. A naive implementation of this idea can be found as primes' in the attachached file. The function uses no multiplication or division and though performs 6 times worse than the sieve in calculating the first 30000 primes. The complexity for finding the next i'th prime with this naive implementation is about O(i). In comparison to this, the sieve provides a good optimization because only those natural numbers are tested against the i'th prime which have run through all other sieves. Nevertheless, your algorithm is promising when the non-primes are merged efficiently enough into a single sorted list which can be easily subtracted from the natural numbers. I think the deployment of an array is basically a way to efficiently merge the multiples of the primaries into a sorted list (where even duplicates are removed), thus hoping to reduce the number of the operations better than the optimization that is provided by the sieve. However, to use arrays this way, you probably need destructive array updates, because the array must be incrementally updated when new primes are found. I think that standard haskell arrays don't do the job very well. An implementation of the "merging" idea in Haskell is primes'' in the attached file. It is 15% faster then the sieve in calculating the 30000 first primes. The algorithm is realized as two mutually recursive functions noprimes and primes'', the latter calculating the set difference between the non-primes and the natural numbers, the former merging the all multiples of all primes into a sorted list. It should be possible to substantially optimize the merging operation. primes''' is an efficient variant of primes'. Instead of a list it uses a binary tree for the management of the lists of multiples of the already found primes, and thus requires some additional programming effort. The complexity is reduced from O(i) to something like O(Log(i)). Compared with the sieve, primes''' needs only half the time to calculate the first 30000 primes. (Tests with ghc 4.08, 64m heap) Best, Elke. On 15-Dec-00 Shlomi Fish wrote: > > Hi! > > As some of you may know, a Haskell program that prints all the primes can be > as short as the following: > > primes = sieve [2.. ] where > sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] > > Now, this program roughly corresponds to the following perl program: > >###### SNIP SNIP ##### >#!/usr/bin/perl > > use strict; > > my (@primes, $a, $p); > @primes = (2); > MAIN_LOOP: > for($a = 3; $a < 1000; $a++) > { > foreach $p (@primes) > { > if ($a % $p == 0) > { > next MAIN_LOOP; > } > } > push @primes, $a; > } > print join(", ", @primes); >####### SNIP SNIP ##### > > The program can be more optimized for both speed and code size, but I wanted > to make it as verbose as possible. > > The algorithm keeps a list of the primes, and for each new number checks if > it > is divisable by any of them and if not it adds it to the list. > > There is a different algorithm which keeps a boolean map which tells whether > the number at that position is prime or not. At start it is initialized to > all > trues. The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally > considered a better algorithm than the previous one, because it uses less > costier operations (multiplications and additions instead of modulos.) > > The perl program that implements that algorithm is this: > >#### SNIP SNIP ##### >#!/usr/bin/perl > > use strict; > > sub primes > { > my $how_much = shift; > > my (@array, $bound, $a, $b, @primes); > > @array = (1) x $how_much; > > $bound = int(sqrt($how_much))+1; > > for($a=2;$a<=$bound;$a++) > { > if ($array[$a]) > { > for($b=$a*$a;$b<$how_much;$b+=$a) > { > $array[$b] = 0; > } > push @primes, $a; > } > } > for(;$a<$how_much;$a++) > { > if ($array[$a]) > { > push @primes, $a; > } > } > > return @primes; > } > > print join(", ", primes(1000)); >##### SNIP SNIP ###### > > Now, I tried writing an equivalent Haskell program and the best I could do > was > the following: > > ---- SNIP SNIP ----- > module Primes where > > import Prelude > import Array > > how_much :: Int > how_much = 1000 > > initial_primes_map :: Array Int Bool > initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ] > > mybound :: Int > mybound = ceiling(sqrt(fromInteger(toInteger(how_much)))) > > next_primes_map :: Int -> Array Int Bool -> Array Int Bool > next_primes_map a primes_map = > if (a == mybound) > then primes_map > else next_primes_map (a+1) ( > if primes_map!a > then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ] > else primes_map > ) > > prime_bound :: Int -> Int > prime_bound a = > (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a)))) > > get_primes_map :: Array Int Bool > get_primes_map = (next_primes_map 2 initial_primes_map) > > list_primes :: Array Int Bool -> Int -> [Int] > list_primes primes_map n = > if (n > how_much) > then [] > else > ( > if primes_map!n > then n:(list_primes primes_map (n+1)) > else list_primes primes_map (n+1) > ) > > show_primes = show (list_primes get_primes_map 2) > ---- SNIP SNIP ----- > > > The problem is that when running it on hugs98 on a Windows98 computer with > 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When > entering how_much as 50,000 I get the following message: > > ERROR: Garbage collection fails to reclaim sufficient space > > In perl I can scale beyond 100,000, and if I modify the code to use a bit > vector (using vec) to much more. So my question is what am I or hugs are > doing > wrong and how I can write better code that implements this specific > algorithm. > >>From what I saw I used tail recursion, (and hugs98 has proper tail recursion, > right?), and there's only one primes_map present at each iteration (and thus, > at all), so it shouldn't be too problematic. Does it have to do with the way > hugs98 implements and Int to Bool array? > > Regards, > > Shlomi Fish > > ---------------------------------------------------------------------- > Shlomi Fish shlomif@vipe.technion.ac.il > Home Page: http://t2.technion.ac.il/~shlomif/ > Home E-mail: shlomif@techie.com > > The prefix "God Said" has the extraordinary logical property of > converting any statement that follows it into a true one. > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell --- Elke Kasimir Skalitzer Str. 79 10997 Berlin (Germany) fon: +49 (030) 612 852 16 mail: elke.kasimir@catmint.de> see: for pgp public key see: --_=XFMail.1.3.p0.Linux:001217195636:327=_ Content-Disposition: attachment; filename="Primes.hs" Content-Transfer-Encoding: base64 Content-Description: Primes.hs Content-Type: application/octet-stream; name=Primes.hs; SizeOnDisk=3056 bW9kdWxlIFByaW1lcwp3aGVyZQoKaW1wb3J0IExpc3QKCi0tIDEuIHZlcnNpb24sIHNpZXZlCgpw cmltZXMgCiAgICA9IHNpZXZlIFsyLi5dIAogICAgICAgd2hlcmUgc2lldmUgKHg6eHMpID0geCA6 IHNpZXZlIFsgbiB8IG4gPC0geHMgLCBuIGBtb2RgIHggPiAwIF0gCgoKLS0gMi4gdmVyc2lvbjog a2VlcCBhbiAidXB0by1kYXRlIiBsaXN0IG9mIHRoZSBub24tcHJpbWVzIAotLSAgICAgICAgICAg ICAoYSBmaW5pdGUgbGlzdCBvZiBpbmlmaW5pdGUgbGlzdHMpCi0tICAgICAgICAgICAgIGFuZCBj YWxjdWxhdGUgdGhlIHByaW1lcyBmcm9tIHRoZW0uCgpwcmltZXMnCiAgICA9IG1rUHJpbWVzIFtd IFsyLi5dIAogICAgICB3aGVyZQogICAgICAgbWtQcmltZXMgbm9uX3ByaW1lcyAoeDp4cykgCgkg ICB8IG51bGwgd2l0aFggPSB4IDogbWtQcmltZXMgKG11bHQgeCA6IG5vbl9wcmltZXMpICAgICAg ICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChtYXAgdGFpbCB3aXRoWCArKyB3 aXRob3V0WCkgeHMKCSAgIHdoZXJlCgkgICAod2l0aFgsd2l0aG91dFgpID0gcGFydGl0aW9uICgo PT14KS4gaGVhZCkgbm9uX3ByaW1lcwoJICAgbXVsdCB4ICAgICAgICAgICA9IGl0ZXJhdGUgKCt4 KSAoeCt4KQoKCi0tIDMuIHZlcnNpb246IHByaW1lcyBhbmQgbm9uLXByaW1lcyBhcmUgbXV0dWFs bHkgcmVjdXJzaXZlLgoKcHJpbWVzJycKICAgID0gMiA6IGRpZmYgWzMuLl0gbm9uX3ByaW1lcwoK bm9uX3ByaW1lcyAKICAgID0gbWVyZ2UgKG1hcCBtdWx0IHByaW1lcycnKSAKICAgICAgd2hlcmUg CiAgICAgIG11bHQgeCAgID0gaXRlcmF0ZSAoK3gpICh4K3gpICAgICAgCgptZXJnZSAoKHg6eHMp OnJlc3QpCiAgICA9IHggOiBtZXJnZSAocmVhcnJhbmdlICh4czpyZXN0KSkKCnJlYXJyYW5nZSBs QCh4bEAoeDp4cyk6KHk6eXMpOnJlc3QpIAogICAgfCB4IDw9IHkgICAgID0gbAogICAgfCBvdGhl cndpc2UgID0gKHk6eGwpIDogcmVhcnJhbmdlICh5czpyZXN0KSAKCi0tIHNldCBkaWZmZXJlbmNl IGZvciBvcmRlcmVkIGxpc3RzIC0gcmVzdWx0IGlzIGFsc28gb3JkZXJlZDoKZGlmZiA6OiBPcmQg YSA9PiBbYV0gLT4gW2FdIC0+IFthXQpkaWZmIHhsQCh4OnhzKSB5bEAoeTp5cykgCiAgICB8IHgg PCAgeSA9IHggOiBkaWZmIHhzIHlsCiAgICB8IHggPT0geSA9ICAgICBkaWZmIHhzIHlsCiAgICB8 IHggPiAgeSA9ICAgICBkaWZmIHhsIHlzCgoKLS0gNC4gdmVyc2lvbiwgbGlrZSAyLiwgYnV0IHVz ZXMgYSB0cmVlIHRvIG1hbmFnZSBub24tcHJpbXNlOgoKcHJpbWVzJycnCiAgICA9IG1rUHJpbWVz IEwgWzIuLl0gCiAgICAgIHdoZXJlCiAgICAgICBta1ByaW1lcyBub25fcHJpbWVzICh4OnhzKSAK CSAgIHwgbnVsbCB3aXRoWCA9IHggOiBta1ByaW1lcyAodGluc2VydCAobXVsdCB4KSBub25fcHJp bWVzKSAgICAgICAgICAgICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChmb2xk ciB0aW5zZXJ0IHdpdGhvdXRYIChtYXAgdGFpbCB3aXRoWCkpIHhzCgkgICB3aGVyZQoJICAgKHdp dGhYLHdpdGhvdXRYKSA9IHRwYXJ0aXRpb24gW3hdIG5vbl9wcmltZXMgCgkgICBtdWx0IHggICAg ICAgICAgID0gaXRlcmF0ZSAoK3gpICh4K3gpCgotLSBhIGJpbmFyeSB0cmVlOgoKZGF0YSBUcmVl ID0gTiBbSW50ZWdlcl0gVHJlZSBUcmVlIHwgTCBkZXJpdmluZyBTaG93CgotLSBydWxlcyBmb3Ig cGxhY2luZyBpbnRlZ2VyIGxpc3RzOgoKbGVmdG9mLCByaWdodG9mIDo6IFtJbnRlZ2VyXSAtPiBU cmVlIC0+IEJvb2wKCmxlZnRvZiAgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA8PSB5CnJpZ2h0 b2YgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA+IHkKCi0tIHJ1bGUgZm9yIG1hdGNoaW5nIGlu dGVnZXIgbGlzdHM6CgptYXRjaGVzIDo6IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IEJvb2wKbWF0Y2hl cyAoeDp4cykgKE4gKHk6eXMpIF8gXykgPSB4ID09IHkKCi0tIGluc2VydGlvbjoKCnRpbnNlcnQg OjogW0ludGVnZXJdIC0+IFRyZWUgLT4gVHJlZQp0aW5zZXJ0IHhsICAgTCA9IE4geGwgTCBMCnRp bnNlcnQgeGwgdEAoTiB5bCB0MSB0MikgCiAgICB8IHhsIGBsZWZ0b2ZgICB0ID0gTiB5bCAodGlu c2VydCB4bCB0MSkgdDIKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgPSBOIHlsIHQxICh0aW5zZXJ0IHhs IHQyKQoKLS0gZXh0cmFjdGlvbiAmIHJlbW92YWwgaW4gb25lIHN0ZXA6Cgp0cGFydGl0aW9uIDo6 IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IChbW0ludGVnZXJdXSxUcmVlKQp0cGFydGl0aW9uIHhsIEwg PSAoW10sTCkKdHBhcnRpdGlvbiB4bCB0QChOIHlsIHQxIHQyKSAKICAgIHwgeGwgYG1hdGNoZXNg IHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24nIHhsIHQxIGluICh5bDphLCByZW1vdmUgYiB0 MikKICAgIHwgeGwgYGxlZnRvZmAgIHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24geGwgdDEg aW4gKGEsIE4geWwgYiB0MikKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgID0gIGxldCAoYSxiKSA9IHRw YXJ0aXRpb24geGwgdDIgaW4gKGEsIE4geWwgdDEgYikKCnRwYXJ0aXRpb24nIHhsIEwgPSAoW10s TCkgICAgICAtLSBjaGVjayBmb3IgbW9yZSBtYXRjaGVzCnRwYXJ0aXRpb24nIHhsIHRAKE4geWwg dDEgdDIpIAogICAgfCB4bCBgbWF0Y2hlc2AgdCAgPSAgbGV0IChhLGIpID0gdHBhcnRpdGlvbicg eGwgdDEgaW4gKHlsOmEsIHJlbW92ZSBiIHQyKQogICAgfCBvdGhlcndpc2UgICAgICAgPSAoW10s dCkKCnJlbW92ZSBMICB0MiAgPSB0MgpyZW1vdmUgdDEgdDIgPSBsZXQgKGEsYikgPSByaWdodG1v c3QgdDEgaW4gTiBhIGIgdDIKCnJpZ2h0bW9zdCAoTiB5bCB0MSAgTCkgPSAoeWwsdDEpCnJpZ2h0 bW9zdCAoTiB5bCB0MSB0MikgPSBsZXQgKGEsYik9cmlnaHRtb3N0IHQyIGluIChhLCBOIHlsIHQx IGIpCiAgCgotLSB0ZXN0IGNvcnJlY3RuZXNzCgpwZGlmZiA9IFsgKGEsYixjLGQpIHwgCgkgKGEs YixjLGQpPC16aXA0IHByaW1lcyBwcmltZXMnIHByaW1lcycnIHByaW1lcycnJywgCgkgYSAvPSBi IHx8IGIgLz0gYyB8fCBjIC89IGQgCgkgXQoKCgoKCgoKCgo= --_=XFMail.1.3.p0.Linux:001217195636:327=_-- End of MIME message From ahey@iee.org Mon Dec 18 00:24:12 2000 From: ahey@iee.org (Adrian Hey) Date: Mon, 18 Dec 2000 00:24:12 +0000 (GMT) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: On Sun 17 Dec, Adrian Hey wrote: > You can use a variation of this algorithm with lazy lists.. > > primes = 2:(get_primes [3,5..]) > get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs)) ^^^ Whoops,_____________________________________________| 32 bit Ints may cause trouble here :-) Regards -- Adrian Hey From Xavier.Leroy@inria.fr Mon Dec 18 09:30:07 2000 From: Xavier.Leroy@inria.fr (Xavier Leroy) Date: Mon, 18 Dec 2000 10:30:07 +0100 Subject: call for papers ICFP 2001 Message-ID: <20001218103007.B32378@pauillac.inria.fr> ICFP 2001: Call for Papers ICFP 2001: International Conference on Functional Programming Firenze (Florence), Italy; 3-5 September 2001 associated with PLI 2001: Colloquium on Principles, Logics, and Implementations of High-Level Programming Languages Important dates: Submission deadline 15 March 2001, 18:00 UTC Notification of acceptance or rejection 11 May 2001 Final paper due 29 June 2001 Conference 3-5 September 2001 Scope: ICFP 2001 seeks original papers on the full spectrum of the art, science, and practice of functional programming. The conference invites submissions on all topics ranging from principles to practice, from foundations to features, and from abstraction to application. The scope covers all languages that encourage programming with functions, including both purely applicative and imperative languages, as well as languages that support objects and concurrency. Papers setting new directions in functional programming, or describing novel or exemplary applications of functional programming, are particularly encouraged. Topics of interest include, but are not limited to, the following: * Foundations: formal semantics, lambda calculus, type theory, monads, continuations, control, state, effects. * Design: modules and type systems, concurrency and distribution, components and composition, relations to object-oriented and logic programming, multiparadigm programming. * Implementation: abstract machines, compile-time and run-time optimization, just-in-time compilers, memory management, foreign-function and component interfaces. * Transformation and Analysis: abstract interpretation, partial evaluation, program transformation, theorem proving, specification and verification. * Applications: scientific and numerical computing, symbolic computing and artificial intelligence, systems programming, databases, graphic user interfaces, multimedia programming, web programming. * Experience: FP in education and industry, ramifications on other paradigms and computing disciplines. * Functional pearls: elegant, instructive examples of functional programming. Submission guidelines: Please refer to the submission Web site http://cristal.inria.fr/ICFP2001/ Program committee: General chair Program committee Benjamin Pierce Karl Crary, Carnegie Mellon University University of Pennsylvania Marc Feeley, University of Montréal Giorgio Ghelli, University of Pisa Program chair Simon Peyton Jones, Microsoft Research John Hughes, Chalmers University Xavier Leroy Naoki Kobayashi, University of Tokyo INRIA Rocquencourt Julia Lawall, DIKU, U. Copenhagen Domaine de Voluceau, B.P. 105 Sheng Liang, Stratum8 78153 Le Chesnay, France John Reppy, Bell Labs, Lucent Technologies E-mail: Xavier.Leroy@inria.fr Scott Smith, John Hopkins University Fax: + 33 - 1 - 39 63 56 84 Carolyn Talcott, Stanford University Phone: + 33 - 1 - 39 63 55 61 Kwangkeun Yi, KAIST From sebastien@posse42.net Tue Dec 19 14:15:16 2000 From: sebastien@posse42.net (Sebastien Carlier) Date: Tue, 19 Dec 2000 15:15:16 +0100 Subject: Excessive restriction in ghc ? Message-ID: <006401c069c6$1cdc13c0$d701a8c0@air> Hello. I am getting an error message from ghc 4.08.1 with the following code: > class Collection e ce | ce -> e where > empty :: ce > insert :: e -> ce -> ce > > class (Eq e, Collection e ce) => Set e ce where > member :: e -> ce -> Bool > union :: ce -> ce -> ce Main.lhs:7: Class type variable `e' does not appear in method signature union :: {- implicit forall -} ce -> ce -> ce Since `ce' uniquely determines `e', I would expect the compiler to assume that `e' appears in the method signature. Either I am misunderstanding something, or something may be missing in the compiler around rename/RnSource.lhs:249. Regards, Sebastien Carlier From zhanyong.wan@yale.edu Tue Dec 19 15:43:28 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Tue, 19 Dec 2000 10:43:28 -0500 Subject: Excessive restriction in ghc ? References: <006401c069c6$1cdc13c0$d701a8c0@air> Message-ID: <3A3F8220.3FED720E@yale.edu> Hi Sebastien, Sebastien Carlier wrote: > I am getting an error message from ghc 4.08.1 with > the following code: > > > class Collection e ce | ce -> e where > > empty :: ce > > insert :: e -> ce -> ce > > > > class (Eq e, Collection e ce) => Set e ce where > > member :: e -> ce -> Bool > > union :: ce -> ce -> ce > > Main.lhs:7: > Class type variable `e' does not appear in method signature > union :: {- implicit forall -} ce -> ce -> ce > > Since `ce' uniquely determines `e', I would expect the > compiler to assume that `e' appears in the method signature. > Either I am misunderstanding something, or something may be > missing in the compiler around rename/RnSource.lhs:249. I encountered the same problem this summer and wrote to Simon PJ and Jeff Lewis. Here's Jeff's answer: > I'm glad to find examples where they are indispensible. The implementation of > FDs in GHC is pretty much complete WRT Mark's writeup (but it doesn't complain > about instances inconsistent with FDs). I'm using them in a current project, > but in a fairly conservative manner. In hugs, I implemented several > extensions to do with derived instances and superclasses - pretty much > necessary as you've found. Unfortunately, in hugs I implemented it in rather > the wrong way. Based on dicsussions at the Hugs/GHC meeting w/ Simon, I have > a cunning plan for finishing the implementation properly in GHC, but just > haven't had the chance to do it. What I need to do is write it up, so that > either Simon or myself can finish the job. So the short answer to your question is: FD in derived instances is not implemented in GHC yet. I'm still eagerly waiting to use this feature in my project. Jeff, could you give us an update on the progress? Thanks! -- # Zhanyong Wan http://pantheon.yale.edu/~zw23/ ____ # Yale University, Dept of Computer Science /\___\ # P.O.Box 208285, New Haven, CT 06520-8285 ||___| From mk167280@zodiac.mimuw.edu.pl Tue Dec 19 15:56:40 2000 From: mk167280@zodiac.mimuw.edu.pl (Marcin Kowalczyk) Date: Tue, 19 Dec 2000 16:56:40 +0100 Subject: Excessive restriction in ghc ? In-Reply-To: <006401c069c6$1cdc13c0$d701a8c0@air>; from sebastien@posse42.net on Tue, Dec 19, 2000 at 03:15:16PM +0100 References: <006401c069c6$1cdc13c0$d701a8c0@air> Message-ID: <20001219165640.A9716@zodiac.mimuw.edu.pl> On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote: > > class Collection e ce | ce -> e where > > empty :: ce > > insert :: e -> ce -> ce > > > > class (Eq e, Collection e ce) => Set e ce where Doesn't adding the fundep to Set's definition as well help? -- Marcin 'Qrczak' Kowalczyk From zhanyong.wan@yale.edu Tue Dec 19 16:04:31 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Tue, 19 Dec 2000 11:04:31 -0500 Subject: Excessive restriction in ghc ? References: <006401c069c6$1cdc13c0$d701a8c0@air> <20001219165640.A9716@zodiac.mimuw.edu.pl> Message-ID: <3A3F870F.10CA4BD8@yale.edu> Marcin Kowalczyk wrote: > > On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote: > > > > class Collection e ce | ce -> e where > > > empty :: ce > > > insert :: e -> ce -> ce > > > > > > class (Eq e, Collection e ce) => Set e ce where > > Doesn't adding the fundep to Set's definition as well help? It might help in this particular case, but if we want something like class Collection e ce => Foo ce where ... then your trick does not apply, and I indeed need something like the above in my project. -- Zhanyong Wan From simonpj@microsoft.com Tue Dec 19 14:47:41 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 19 Dec 2000 06:47:41 -0800 Subject: Excessive restriction in ghc ? Message-ID: <74096918BE6FD94B9068105F877C002D0137839A@red-pt-02.redmond.corp.microsoft.com> Functional dependencies aren't fully implemented in 4.08 I'm afraid, and won't ever be. It'll be significantly better in 5.0, but we won't release that for a while yet. (Unless you care to build from the CVS tree.) Simon | -----Original Message----- | From: Sebastien Carlier [mailto:sebastien@posse42.net] | Sent: 19 December 2000 14:15 | To: haskell@haskell.org | Subject: Excessive restriction in ghc ? | | | Hello. | | I am getting an error message from ghc 4.08.1 with | the following code: | | > class Collection e ce | ce -> e where | > empty :: ce | > insert :: e -> ce -> ce | > | > class (Eq e, Collection e ce) => Set e ce where | > member :: e -> ce -> Bool | > union :: ce -> ce -> ce | | Main.lhs:7: | Class type variable `e' does not appear in method signature | union :: {- implicit forall -} ce -> ce -> ce | | Since `ce' uniquely determines `e', I would expect the | compiler to assume that `e' appears in the method signature. | Either I am misunderstanding something, or something may be | missing in the compiler around rename/RnSource.lhs:249. | | Regards, | Sebastien Carlier | | | | _______________________________________________ | Haskell mailing list | Haskell@haskell.org | http://www.haskell.org/mailman/listinfo/haskell | From simonpj@microsoft.com Tue Dec 19 14:58:41 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 19 Dec 2000 06:58:41 -0800 Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: <74096918BE6FD94B9068105F877C002D0137839D@red-pt-02.redmond.corp.microsoft.com> | Another way to do this is to compute the final array directly, | instead of computing successive versions of the array: | | import Array | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where | primesMap = accumArray (||) False (2,n) multList | multList = [(m,True) | j <- [2 .. n `div` 2], m <- | multiples j] | multiples j = takeWhile (n>=) [k*j | k <- [2..]] This style is definitely the way to go. Haskell does badly if you update an array one index at a time. Remember that arrays can be recursive. Here's a definition of Fibonacci for example; you can probably adapt it for primes fibs :: Int -> Array Int Int -- If a = fibs n, then a!i is fib(i), for i<=n. fibs n = a where a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <- [3..n]]) -- Notice that a is recursive Simon From shlomif@vipe.technion.ac.il Wed Dec 20 14:02:23 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Wed, 20 Dec 2000 16:02:23 +0200 (IST) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: <74096918BE6FD94B9068105F877C002D0137839D@red-pt-02.redmond.corp.microsoft.com> Message-ID: On Tue, 19 Dec 2000, Simon Peyton-Jones wrote: > | Another way to do this is to compute the final array directly, > | instead of computing successive versions of the array: > | > | import Array > | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where > | primesMap = accumArray (||) False (2,n) multList > | multList = [(m,True) | j <- [2 .. n `div` 2], m <- > | multiples j] > | multiples j = takeWhile (n>=) [k*j | k <- [2..]] > > This style is definitely the way to go. Haskell does badly > if you update an array one index at a time. > Unfortunately, it seems that this style is not the way to go. This program cannot scale beyond 5000 while my second program scales beyond 30000. I'm not saying 30000 is a good limit, but 5000 is much worse. Anyway, somebody who contacted me in private suggested the following method. It is a similiar algorithm which uses a list instead of an array. primes :: Int -> [Int] primes how_much = sieve [2..how_much] where sieve (p:x) = p : (if p <= mybound then sieve (remove (p*p) x) else x) where remove what (a:as) | what > how_much = (a:as) | a < what = a:(remove what as) | a == what = (remove (what+step) as) | a > what = a:(remove (what+step) as) remove what [] = [] step = (if (p == 2) then p else (2*p)) sieve [] = [] mybound = ceiling(sqrt(fromIntegral how_much)) I optimized it quite a bit, but the concept remained the same. Anyway, this code can scale very well to 100000 and beyond. But it's not exactly the same algorithm. I also implemented this algorithm in perl, and I can send it in person if anybody requests it. I'll try to see how the two programs run in GHC and HBC. Regards, Shlomi Fish > Remember that arrays can be recursive. Here's a definition > of Fibonacci for example; you can probably adapt it for primes > > fibs :: Int -> Array Int Int > -- If a = fibs n, then a!i is fib(i), for i<=n. > fibs n = a > where > a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <- > [3..n]]) > -- Notice that a is recursive > > Simon > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From ger@tzi.de Wed Dec 20 14:12:46 2000 From: ger@tzi.de (George Russell) Date: Wed, 20 Dec 2000 15:12:46 +0100 Subject: Finding primes using a primes map with Haskell and Hugs98 References: Message-ID: <3A40BE5E.13D8D959@tzi.de> There are numerous ways of optimising sieving for primes, none of which have much to do with this list. For example, two suggestions: (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise sieve separately for this k on higher primes. (Or you might use products of more or less primes, depending on memory and how high you were going.) (2) use bitwise arithmetic. If you look in the literature I think you'll find plenty more possibilities. I don't really see why any of this has anything to do with Haskell though. When it comes to seriously icky bit-twiddling algorithms I don't think Haskell has much to offer over C, especially as you'd have to make everything unboxed if you want comparable speed. From Colin.Runciman@cs.york.ac.uk Wed Dec 20 14:49:30 2000 From: Colin.Runciman@cs.york.ac.uk (Colin.Runciman@cs.york.ac.uk) Date: Wed, 20 Dec 2000 14:49:30 GMT Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: <200012201449.OAA01102@pc179.cs.york.ac.uk> > There are numerous ways of optimising sieving for primes, none of which > have much to do with this list. For example, two suggestions: > (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise > sieve separately for this k on higher primes. (Or you might use products of > more or less primes, depending on memory and how high you were going.) > ... > I don't really see why any of this has anything to do with Haskell though. > When it comes to seriously icky bit-twiddling algorithms I don't think Haskell > has much to offer over C, especially as you'd have to make everything unboxed if > you want comparable speed. Forgive the self-reference, but the following short article is all about this very topic: C. Runciman, Lazy wheel sieves and spirals of primes, Journal of Functional Programming, v7, n2, pp219--226, March 1997. From Dominic.J.Steinitz@BritishAirways.com Wed Dec 20 16:12:16 2000 From: Dominic.J.Steinitz@BritishAirways.com (Steinitz, Dominic J) Date: 20 Dec 2000 16:12:16 Z Subject: Haskell Productivity Message-ID: <"032483A40DA600E0*/c=GB/admd=ATTMAIL/prmd=BA/o=British Airways PLC/ou=CORPLN1/s=Steinitz/g=Dominic/i=J/"@MHS> The Haskell website claims that "Ericsson measured an improvement factor of between 9 and 25 in one set of experiments on telephony software". Presumably this is with Erlang not with Haskell. I have searched for the reference that substantiates this claim but I've only been able to find: http://set.gmd.de/~ap/femsys/wiger.html which talks about a productivity factor of 4 and http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haskell-vs-ada-abstract.html which suggests that Haskell is about 2-3 times as productive as imperative languages. Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25? Thanks, Dominic. ------------------------------------------------------------------------------------------------- 21st century air travel http://www.britishairways.com From simonpj@microsoft.com Wed Dec 20 11:11:44 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Wed, 20 Dec 2000 03:11:44 -0800 Subject: Problem with functional dependencies Message-ID: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> I think you can simplify the example. Given class HasFoo a b | a -> b where foo :: a -> b instance HasFoo Int Bool where ... Is this legal? f :: HasFoo Int b => Int -> b f x = foo x You might think so, since HasFoo Int b => Int -> b is a substitution instance of HasFoo a b => a -> b but if we infer the type (HasFoo Int b => Int -> b) for f's RHS, we can then "improve" it using the instance decl to (HasFoo Int Bool => Int -> Bool), and now the signature isn't a substitution insance of the type of the RHS. Indeed, this is just what will happen if you try with GHC, because GHC takes advantage of type signatures when typechecking a function defn, rather than first typechecking the defn and only then comparing with the signature. I don't know what the answers are here, but there's more to this functional dependency stuff than meets the eye. Even whether one type is more general than another has changed! Simon | -----Original Message----- | From: qrczak@knm.org.pl [mailto:qrczak@knm.org.pl] | Sent: 17 December 2000 19:30 | To: haskell@haskell.org | Subject: Problem with functional dependencies | | | The following module is rejected by both | ghc -fglasgow-exts -fallow-undecidable-instances | and | hugs -98 | | -------------------------------------------------------------- | ---------- | class HasFoo a foo | a -> foo where | foo :: a -> foo | | data A = A Int | data B = B A | | instance HasFoo A Int where | foo (A x) = x | | instance HasFoo A foo => HasFoo B foo where | foo (B a) = foo a | -------------------------------------------------------------- | ---------- | | The error messsage says that the type inferred for foo in B's instance | is not general enough: the rhs has type "HasFoo B Int => B -> | Int", but | "HasFoo B foo => B -> foo" was expected. From paul.hudak@yale.edu Wed Dec 20 16:28:10 2000 From: paul.hudak@yale.edu (Paul Hudak) Date: Wed, 20 Dec 2000 11:28:10 -0500 Subject: Haskell Productivity References: <"032483A40DA600E0*/c=GB/admd=ATTMAIL/prmd=BA/o=British Airways PLC/ou=CORPLN1/s=Steinitz/g=Dominic/i=J/"@MHS> Message-ID: <3A40DE1A.1F00B405@yale.edu> > Can someone point me at some more references? See http://haskell.org/papers/NSWC/jfp.ps. -Paul From peterd@availant.com Wed Dec 20 16:45:35 2000 From: peterd@availant.com (Peter Douglass) Date: Wed, 20 Dec 2000 11:45:35 -0500 Subject: Haskell Productivity Message-ID: <8BDAB3CD0E67D411B02400D0B79EA49A5F6CCC@smail01.clam.com> There is a thread on comp.lang.functional which may be of interest. Here is a link that might work for you. http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh 8ss$6le$1@bird.wu-wien.ac.at%3e%231/1 > -----Original Message----- > From: Steinitz, Dominic J > [mailto:Dominic.J.Steinitz@BritishAirways.com] > Sent: Wednesday, December 20, 2000 11:12 AM > To: haskell > Subject: Haskell Productivity > > > The Haskell website claims that > > "Ericsson measured an improvement factor of between 9 and 25 > in one set of experiments on telephony software". > > Presumably this is with Erlang not with Haskell. I have > searched for the reference that substantiates this claim but > I've only been able to find: > > http://set.gmd.de/~ap/femsys/wiger.html > > which talks about a productivity factor of 4 > > and > > http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haske ll-vs-ada-abstract.html which suggests that Haskell is about 2-3 times as productive as imperative languages. Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25? Thanks, Dominic. ---------------------------------------------------------------------------- --------------------- 21st century air travel http://www.britishairways.com _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell From peterd@availant.com Wed Dec 20 16:50:50 2000 From: peterd@availant.com (Peter Douglass) Date: Wed, 20 Dec 2000 11:50:50 -0500 Subject: Haskell Productivity Message-ID: <8BDAB3CD0E67D411B02400D0B79EA49A5F6CCF@smail01.clam.com> Hello all, You will need to manually reconnect the link I sent into a single line for it to work. > There is a thread on comp.lang.functional which may be of interest. > Here is a link that might work for you. > > http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh 8ss$6le$1@bird.wu-wien.ac.at%3e%231/1 From ashley@semantic.org Wed Dec 20 23:59:50 2000 From: ashley@semantic.org (Ashley Yakeley) Date: Wed, 20 Dec 2000 15:59:50 -0800 Subject: GHC for Darwin? Message-ID: <200012202359.PAA26221@mail4.halcyon.com> Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant that runs on the PowerPC processor. . I was going to compile it myself before I remembered that compilers do platform-specific code-generation. Duh. -- Ashley Yakeley, Seattle WA From simonmar@microsoft.com Wed Dec 20 17:46:25 2000 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 20 Dec 2000 09:46:25 -0800 Subject: ANNOUNCE: Happy version 1.9 Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell ----------------------------------------------------------------- I'm pleased to announce version 1.9 of Happy, the parser generator system for Haskell. Changes in this version, relative to version 1.8 (the previous full release): * A grammar may now contain several entry points, allowing several parsers to share parts of the grammar. * Some bugfixes. Happy is available in source form, which can be compiled with GHC version 4.xx (4.08.1 recommended), and we also provide binaries for some architectures. The Happy homepage with links to the various distributions lives at: http://www.haskell.org/happy/ Please send any bug reports and comments to simonmar@microsoft.com. From doaitse@cs.uu.nl Thu Dec 21 08:22:27 2000 From: doaitse@cs.uu.nl (S. Doaitse Swierstra) Date: Thu, 21 Dec 2000 10:22:27 +0200 Subject: GHC for Darwin? In-Reply-To: <200012202359.PAA26221@mail4.halcyon.com> References: <200012202359.PAA26221@mail4.halcyon.com> Message-ID: At 3:59 PM -0800 12/20/00, Ashley Yakeley wrote: >Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant >that runs on the PowerPC processor. >. > >I was going to compile it myself before I remembered that compilers do >platform-specific code-generation. Duh. > >-- >Ashley Yakeley, Seattle WA > > >_______________________________________________ >Haskell mailing list >Haskell@haskell.org >http://www.haskell.org/mailman/listinfo/haskell Atze Dijkstra (mailto:atze@cs.uu.nl) is working on a port of the GHC to MacOS X. He has reached the state where he managed to compile some programs (e.g. our attribute grammar system and combinator libraries). Doaitse Swierstra -- __________________________________________________________________________ S. Doaitse Swierstra, Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands Mail: mailto:doaitse@cs.uu.nl WWW: http://www.cs.uu.nl/ PGP Public Key: http://www.cs.uu.nl/people/doaitse/ tel: +31 (30) 253 3962, fax: +31 (30) 2513791 __________________________________________________________________________ From jeff@galconn.com Thu Dec 21 08:59:29 2000 From: jeff@galconn.com (Jeffrey R. Lewis) Date: Thu, 21 Dec 2000 00:59:29 -0800 Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> Message-ID: <3A41C671.B9EDF2E3@galconn.com> Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so, since > HasFoo Int b => Int -> b > is a substitution instance of > HasFoo a b => a -> b This is the step where the reasoning goes wrong. The functional dependency tells you that `b' isn't really a free variable, since it is dependent on `a'. If you substitute for `a', you can't expect `b' to remain unconstrained. Hugs complains that the inferred type for `f' is not general enough. It's right to complain, but the real problem is that the signature is too general. Asimilar situation arises if you try to declare an instance `HasFoo Int b', but in this case, hugs complains that the instance is more general than the dependency allows. A useful thing to do would be to check for this sort of thing in signatures as well, so that the more appropriate error message can be given. --Jeff From qrczak@knm.org.pl Thu Dec 21 10:05:14 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 21 Dec 2000 10:05:14 GMT Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> <3A41C671.B9EDF2E3@galconn.com> Message-ID: Thu, 21 Dec 2000 00:59:29 -0800, Jeffrey R. Lewis pisze: > > class HasFoo a b | a -> b where > > f :: HasFoo Int b => Int -> b > > f x = foo x > This is the step where the reasoning goes wrong. The functional > dependency tells you that `b' isn't really a free variable, since > it is dependent on `a'. If you substitute for `a', you can't expect > `b' to remain unconstrained. It's not unconstrained: the constraint is "HasFoo Int b", as written. IMHO it should not matter that the constraint fully determines b. > Asimilar situation arises if you try to declare an instance `HasFoo > Int b', but in this case, hugs complains that the instance is more > general than the dependency allows. ghc does not complain. How would I express "the instance can be chosen basing on 'a' alone, and the instance found will tell what constraints are on 'b'"? Aren't fundeps a too general mechanism which is not able to express simpler statements? :-( -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From chak@cse.unsw.edu.au Thu Dec 21 11:40:02 2000 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Thu, 21 Dec 2000 22:40:02 +1100 Subject: ANNOUNCE: Happy version 1.9 In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> References: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> Message-ID: <20001221224002G.chak@cse.unsw.edu.au> Simon Marlow wrote, > ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell > ----------------------------------------------------------------- A RedHat 7.0/i386 rpm package is available at ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/happy-1.9-1.i386.rpm and the matching source rpm at ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/happy-1.9-1.src.rpm Happy Hacking, Manuel From rrt1001@cam.ac.uk Thu Dec 21 11:58:42 2000 From: rrt1001@cam.ac.uk (Reuben Thomas) Date: Thu, 21 Dec 2000 11:58:42 +0000 (GMT) Subject: ANNOUNCE: Happy version 1.9 In-Reply-To: <20001221224002G.chak@cse.unsw.edu.au> Message-ID: > ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell > ----------------------------------------------------------------- A Windows InstallShield package is available at http://www.haskell.org/happy/dist/1.9/happy-1-9.exe -- http://sc3d.org/rrt/ | egrep, n. a bird that debugs bison From lennart@augustsson.net Thu Dec 21 12:11:33 2000 From: lennart@augustsson.net (Lennart Augustsson) Date: Thu, 21 Dec 2000 13:11:33 +0100 Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> Message-ID: <3A41F375.499AEC44@augustsson.net> Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so, since > HasFoo Int b => Int -> b > is a substitution instance of > HasFoo a b => a -> b > > but if we infer the type (HasFoo Int b => Int -> b) > for f's RHS, we can then "improve" it using the instance > decl to (HasFoo Int Bool => Int -> Bool), and now the signature > isn't a substitution insance of the type of the RHS. I definitely want it to be legal. I have examples where this is immensly useful. -- -- Lennart From qrczak@knm.org.pl Thu Dec 21 18:32:59 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 21 Dec 2000 18:32:59 GMT Subject: Are fundeps the right model at all? Message-ID: Could somebody show an example which requires fundeps and cannot be expressed using a simpler model explained below - a model that I can even understand? Is the model self-consistent at all? Each class is associated with a set of subsets of type variables in its head. Let's call it the set of keys. The intuitive meaning of a key is that types corresponding to these variables are sufficient to determine which instance to choose. They correspond to lhss of some fundeps. Plain classes without explicitly written keys correspond to having a single key consisting of all type variables. Keys influence the typechecking thus: - A type is unambiguous if for every class constraint in it there exists its key such that types in the constraint corresponding to type variables from the key contain no type variables which are absent in the type itself. - All class methods must have unambiguous types, i.e. for each method there must be a key whose all type variables are present in the method's type. - For each key, there must be no pair of instances whose heads projected to the class parameters from the key overlap. - For each class constraint of an unambiguous type an each its key there must be an instance found basing on this key, or the type is incorrect because of missing instances. Moreover, instances found basing on all keys must be identical. - Perhaps something must be said about class contexts and instance contexts. I'm not sure what yet. Examples: class Collection c e | c where empty :: c insert :: c -> e -> c class Monad m => MonadState s m | m where get :: m s put :: s -> m () newtype State s a = State {runState :: s -> (a,s)} instance Monad (State s) instance MonadState s (State s) test1:: Int -> Int test1 x = snd (runState get x) -- Not ambiguous. class IOvsST io st | io, st where -- Two single-element keys. ioToST :: io -> st stToIO :: st -> io instance IOvsST (IORef a) (STRef s a) where ioToST = unsafeCoerce# stToIO = unsafeCoerce# test2:: IORef a -> IORef a test2 = ioToST . stToIO -- Not ambiguous. class Foo a b | a instance Foo Int [a] -- This is rejected by Hugs (with fundep a->b) but I would definitely -- accept it. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From ger@tzi.de Thu Dec 21 20:20:46 2000 From: ger@tzi.de (George Russell) Date: Thu, 21 Dec 2000 21:20:46 +0100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: Message-ID: <3A42661E.7FCCAFFA@tzi.de> Alternatively, I wonder whether the current system of type classes is the right model at all. Although I prefer the Haskell system, I think it is instructive to compare it with the Standard ML (SML) system of structures and functors. My point is that both Haskell and SML impose one of two possible extremes on the user, and suffer for it. With SML, it is as if all instances are explicitly named. SML does not permit user-defined overloading, and so SML is not capable of understanding something such as a "type class of things we can compare", and has a horrible set of kludges to cope with implementing the equality operator. With Haskell, on the other hand, there is no way of referring to a particular instance when you want to. We see a particular consequence of that here, in that (unlike SML), it is not possible to associate an internal type with a given instance. Another problem is that no-one has any control over what instances get exported, because since instances are anonymous there is no way of referring to them. Hence the current procedure is to expose everything to the importer, which is surely a mistake. So if you agree with me up to here, perhaps you are agreed that it is worth while trying to find a middle way, in which we try to combine both approaches. Well I'm not an expert language designer, and I'm doing this off the top of my head late on Thursday evening, so please don't nitpick about syntax; I'm aware that parsing will probably be difficult in all sorts of ways with exactly what I'm writing, but that shouldn't be too hard to tweak. In particular I have followed SML in using "." to express qualification by something, even though Haskell already used "." for something else, because I can't be bothered right now to dig up a better symbol. On the other hand if my whole approach is a pile of elephant dung I apologise for wasting your time, and wish you a happy Christmas/holidays, but do try to find a better way of combining the best of SML functors and Haskell classes. Anyway here is my proposal. (1) We extend type classes to allow them to introduce types. Thus for example I would replace Marcin's first example by class Collectible e where type c -- or we could just omit the "type" keyword, trading clarity -- for conciseness. -- note also that we need a way of expressing a context for -- "c", EG that it's an instance of Eq. empty :: c insert :: c -> e -> c As usual, you can refer to "empty" and "insert" right away, but you can't refer to "c" without extra syntax. We need a way of referring to the particular instance of Collectible. So I suggest something like: singleton :: (method | Collectible e) => e -> method.c singleton el = insert empty el (2) We extend instance declarations in two ways. Firstly and obviously, we need a way of declaring the type c in the instance second declaration. The second thing is to introduce named instance declarations, like this: instance IntList | Collectible Int where type c = [Int] empty = [] insert = (flip(:)) To actually _refer_ to a specific instance, you would qualify with IntList. So you could refer to IntList.c, IntList.empty, IntList.insert, just like you would with SML. But as with Haskell, "empty" and "insert" would continue to be available implicitly. A more complicated example arises when you have instances depending on other instances. EG instance SetCollection | Ord el => Collectible el where type c = Set el empty = emptySet insert = addToSet -- new function, thank Simon Marlow Then, in this case, you would refer to SetCollection.c when you wanted to refer to the type c. However note that in this case we are implicitly using an anonymous use of Ord. Supposing you had previously defined (ignoring questions about overlapping instances for now . . .) instance EccentricOrd | Ord Int where ... and you wanted to define Sets in terms of EccentricOrd. Then I suggest that you use instead SetCollection(EccentricOrd).c and likewise SetCollection(EccentricOrd).empty and Sets(EccentricOrd).insert, though I hope that such monstrous constructions will not often be necessary. When they are, maybe it would be a good idea to allow the user to abbreviate, as in instance EccentricSet | Collectible Int = SetCollection(EccentricOrd) just as you can do in SML. (3) Finally it would be nice to extend the module syntax to allow named instances to be selectively exported and imported, just like variables. If I could ignore all pre-existing Haskell code I would specify that whenever a module has a specific import list, no instances are imported unless specified. However this is politically impossible, so instead I suggest that all anonymous instances continue to be implicitly imported, as now, but that named instances are only imported when named in the import list. EG "import File(instance SetCollection)". Also, I think it would be nice to have something similar to the "qualified" operator, by which class membership is NOT automatically inherited, and would have to be explicitly specified by referring to "SetCollection.insert" or indeed "SetCollection.singleton"; in particular this would provide a clean way of handling overlapping classes. OK, so I realise this is probably not the final answer, but wouldn't it be nice if something along these lines could be got to work? From ger@tzi.de Fri Dec 22 15:56:41 2000 From: ger@tzi.de (George Russell) Date: Fri, 22 Dec 2000 16:56:41 +0100 Subject: List.partition a bit too eager Message-ID: <3A4379B9.CBA6D281@tzi.de> I think the following program import List main = putStr . show . fst . (partition id) . cycle $ [True,False] should display [True,True,True,...]. But instead, for both GHC and Hugs, you get a stack overflow. Is this a bug, or could someone explain it to me? From qrczak@knm.org.pl Sun Dec 24 20:25:12 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 24 Dec 2000 20:25:12 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: Thu, 21 Dec 2000 21:20:46 +0100, George Russell pisze: > So if you agree with me up to here, perhaps you are agreed that it is worth > while trying to find a middle way, in which we try to combine both approaches. I am thinking about a yet different approach. Leave classes and SML structures as they are, and make *records* more flexible, to be used instead of classes if instances are to be manipulated explicitly, and instead of structures if we are using Haskell rather than SML or OCaml, and instead of objects if we are using Haskell rather than some OO language, and as a general way of expressing things behaving like fixed dictionaries of values. I have yet to play more with it. I already have some thoughts and a working preprocessor which translates my extensions to Haskell (with multi-parameter classes and fundeps). -------- GOALS -------- * Replace the current record mechanism with a better one. * Don't require sets of fields of different record types disjoint. It's not only to avoid inventing unique field names, but also to have functions polymorphic over all records containing specific fields of specific types. * Provide a way to specialize existing record types to new types that behave similarly except of small changes. I.e. kind of inheritance. * Since Haskell does not have subtyping, have coercions up the inheritance tree. Overloading functions on record types is not always enough, e.g. to put records in a heterogeneous collection they must be coerced to a common type. * Don't constrain the implementation of field access for different record types. As long as it behaves like a record, it is a record. * Don't constrain the implementation of methods even for the same record type. Since Haskell does not have subtyping, records which would have different types in other languages can have the same type in Haskell, as long as the same interface suffices. * Express keyword parameters of functions. A function might use many parameters refining its behavior which usually have some default values. Old code using that function must not break when more parameters are added. * A piece of code should be understandable locally, independently of definitions and instances present elsewhere. * Have a nice syntax. * Keep it simple and easily translatable to the core language. Fields and methods are really the same thing. Moreover, inheritance is really delegation and coercions are the same things as field accesses as well. Record types are not anonymous, unlike TREX. Field names are born implicitly and live in a separate namespace. Each field name is associated with a class of record types having that field. Instances of these classes are defined implicitly for types defined as records, but can also be given explicitly for any type. -------- FIELD SELECTION -------- A field selection expression of the form expr.label is equivalent to (.label) expr where (.label) :: (r.label :: a) => r -> a is an overloaded selector function. (rec.label:: a) is a syntax for Has_label rec a, where Has_label is the implicitly defined class for this label. Such class would look like this if it were defined as normal classes: class Has_label r a | r -> a where (.label) :: r -> a set_label :: r -> a -> r except that there are no real names Has_label nor set_label. -------- DEFINITION OF RECORD TYPES -------- The definition of a record type: data Monoid e = record zero :: e plus :: e -> e -> e defines the appropriate single-constructor algebraic type and obvious instances: instance (Monoid e).zero :: e where ... instance (Monoid e).plus :: e -> e -> e where ... We can construct values of this type thus: numAddMonoid :: Num e => Monoid e numAddMonoid = record zero = 0 plus = (+) The meaning of such overloaded record creation expressions will be specified later. -------- INHERITANCE -------- Here is another example of a record type definition: data Group e = record monoid :: Monoid e minus :: e -> e -> e neg :: e -> e monoid (zero, plus) x `minus` y = x `plus` neg y neg y = zero `minus` y This record type has three direct members: monoid, minus, and neg. monoid holds its zero and plus. We want to be able to extract zero and plus of a group directly, instead of going through the underlying monoid. We could define appropriate instances: instance (Group e).zero :: e where ... instance (Group e).plus :: e -> e -> e where ... and this is what the inheritance declaration monoid (zero, plus) does automatically for us. So groups too have zero and plus, which are deleagated to the monoid. Seen from outside, these fields are indistinguishable from proper Group's fields. -------- DEFAULT DEFINITIONS -------- minus and neg in Group have default definitions expressed in terms of each other. When making a Group we can provide the definition of either one or both, otherwise both will diverge. We could provide default definitions of inherited methods too. If they had default definition in the supertype, they would be overridden. This is how the system expresses OO methods belonging to a type: by default definitions. They can be overridden in subtypes or at object creation time. How is it done that the default definition of minus refers to the definition of neg which will be supplied later? It is not known yet which fields will be specified at creation time. OTOH at the creation time it is not known which fields have default definitions, because the creation expression is polymorphic over record types containing specific fields and will be instantiated based on the context. There is a standard class defined as follows: class Record r where bless :: r -> r A record creation expression, say: record zero = 0 plus = (+) is a syntactic sugar for a recursively defined object: let this = bless this `set_zero` 0 `set_plus` (+) in this The bless function, named after Perl's mechanism used in a similar context, returns a record with all fields initialized using their default definitions, or bottoms for fields with no defaults. Default definitions refer to other fields through the parameter of bless. As seen above, bless is applied to the record to be constructed, and then fields with values specified at creation time are overridden. That way all field definitions can find right versions of other fields, no matter which were defined together with the type and which were supplied at the creation time. The type of the above record creation expression is (Record r, Num a, Num b, r.zero :: a, r.plus :: b -> b -> b) => r -------- DEFINITION OF BLESS -------- Definition of a record type automatically makes it an instance of the class Record. A field from which some other fields are inherited is initialized to blessed value of the same field taken from the parameter of bless, modified by setting those fields which have default defintions. It sounds complicated but this is what yields right bindings of all definitions. If a type behaves like a record, it is a record. You can make Record instances of arbitrary types, making them constructible using the record syntax. bless should be lazy. Field setters can be strict. -------- UPDATING FIELDS -------- If fields represent state changing over time, they can be mutable references. Fields can also be updated in a functional style, but this is really construction of new objects basing on old ones. Field update syntax is as follows: expr.record label1 = value1 label2 = value2 It is equivalent to simple nested set_label applications. Fields initialized with default definitions will not switch to refer to updated values of other fields! All magic already happened at record creation time. This can be changed in at least two ways. First, you can define instances of appropriate Has_label classes yourself and associate arbitrary magic with field updates. Second, you can make such instance for the field that you want to be a function of other fields instead of putting the field in the record directly. Definitions of two methods of Has_label classes have special syntax: instance (a,b).fst :: a where (a,_).fst = a (_,b).record {fst = a} = (a,b) instance (a,b).snd :: b where (_,b).snd = b (a,_).record {snd = b} = (a,b) I.e. pattern.label is equivalent to (.label) pattern and defines the getter function, and pattern1.record {label = pattern2} defines the setter when applied to the record matching pattern1 and field value matching pattern2. Braces can be omitted, but they make the syntax more clear. -------- SYNTAX DETAILS -------- The record keyword triggers the layout rules. Value definitions after the record keyword look like let bindings. They can be defined by cases with argument patterns on the left of the equal sign. In record type definitions, record creations and record updates definitions of fields can refer to all fields mentioned in those constructs in an unqualified form. They can also refer to a special variable called this, which holds the whole record after construction or update. -------- EXAMPLE -------- This example introduces a feature of renaming fields while inheriting. > data Monoid e = record > zero :: e > plus :: e -> e -> e > > numAddMonoid :: Num e => Monoid e > numAddMonoid = record > zero = 0 > plus = (+) > > numMulMonoid :: Num e => Monoid e > numMulMonoid = record > zero = 1 > plus = (*) > > data Group e = record > monoid :: Monoid e > minus :: e -> e -> e > neg :: e -> e > monoid (zero, plus) > x `minus` y = x `plus` neg y > neg y = zero `minus` y > > numAddGroup :: Num e => Group e > numAddGroup = record > monoid = numAddMonoid > minus = (-) > neg = negate > > numMulGroup :: Fractional e => Group e > numMulGroup = record > monoid = numMulMonoid > minus = (/) > neg = recip > > data Ring e = record > addGroup :: Group e > mulMonoid :: Monoid e > addGroup (monoid as addMonoid, zero, plus, minus, neg) > mulMonoid (zero as one, plus as times) > > numRing :: Num e => Ring e > numRing = record > addGroup = numAddGroup > mulMonoid = numMulMonoid > > data Field e = record > addGroup :: Group e > mulGroup :: Group e > addGroup (monoid as addMonoid, zero, plus, minus, neg) > mulGroup (monoid as mulMonoid, zero as one, plus as times, > minus as div, neg as recip) > > instance (Field e).ring :: Ring e where > f.ring = record > addGroup = f.addGroup > mulMonoid = f.mulMonoid > f.record {ring = r} = f.record > addGroup = r.addGroup > mulMonoid = r.mulMonoid > > -- Alternatively a Field could consist of a Ring and div + recip. > -- The difference is an implementation detail not visible outside. > -- The following definition will work with either variant: > > numField :: Fractional e => Field e > numField = record > addGroup = numAddGroup > mulGroup = numMulGroup -------- PROBLEMS -------- If those records are to simulate classes, they should be able to have polymorphic fields. Unfortunately it does not work to have overloaded setters in this case. I don't know a good solution. Similarly we would want to have records with existentially quantified types. Again it does not work to have overloaded getters and setters. Listing all inherited fields can be annoying. It would not really work otherwise, as arbitrary instances for sypertypes can be added at any time. It is not necessary to list all fields: other fields are available through the field we inherit from anyway. It would be desirable to selectively export instances. -------- PROTOTYPE IMPLEMENTATION -------- I have an implementation of this in the form of a preprocessor, based on hssource from ghc-4.11's hslibs. I will polish it and put for downloading to let people play with my records. I hope to have more interesting examples. The difference between this implementation and the above proposal is that types of inherited fields must be given explicitly. This is because delegation instances would otherwise have to have types which are not accepted by ghc, and they would require -fallow-undecidable-instances if they were legal (which is not a surprise because cyclic inheritance makes it impossible to determine the type of the field). I reported the problem under the subject "Problem with functional dependencies" on December 17th. I believe that both problems can be fixed, especially if handling those constructs were inside the compiler. -------- THE REST OF MY REPLY TO GEORGE RUSSELL -------- > (1) We extend type classes to allow them to introduce types. If your classes were expressed as my records, it would roughly correspond to existential quantification. But there are big problems with typechecking in this approach. I hope somebody will invent a solution. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From fjh@cs.mu.oz.au Tue Dec 26 01:10:55 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Tue, 26 Dec 2000 12:10:55 +1100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: <3A42661E.7FCCAFFA@tzi.de> References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: <20001226121054.A20508@hg.cs.mu.oz.au> On 21-Dec-2000, George Russell wrote: > (3) Finally it would be nice to extend the module syntax to allow named > instances to be selectively exported and imported, just like variables. Mercury's module system allows instance declarations (which, as in Haskell 98, are unnamed) to be selectively exported. :- module foo. :- interface. :- import_module enum. :- type t. :- instance enum(t). :- implementation. :- instance enum(t) where [ ... ]. Mercury doesn't directly support selective import -- you can only import a whole module, not part of it. But if you really want that you can achieve it by putting each instance declaration in its own nested module. :- module foo. :- interface. :- import_module enum. :- type t. :- module enum_t. :- interface. :- instance enum(t). :- end_module enum_t. :- implementation. :- module enum_t. :- implementation. :- instance enum(t) where [ ... ]. :- end_module enum_t. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From qrczak@knm.org.pl Tue Dec 26 08:46:44 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 26 Dec 2000 08:46:44 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> <20001226121054.A20508@hg.cs.mu.oz.au> Message-ID: Tue, 26 Dec 2000 12:10:55 +1100, Fergus Henderson pisze: > Mercury's module system allows instance declarations (which, as in > Haskell 98, are unnamed) to be selectively exported. If they could be selectively exported in Haskell, how to make it compatible with the current assumption that they are exported by default? Selective hiding would be weird. Perhaps there should be a separate section for exporting instances. If not present, then everything is exported (as with plain module contents). I hope selective export would help with resolving conflicting instances. There might be a confusion if a function does indeed get a sorted list of objects of type T but it expected a different ordering, but the danger of inability of linking two independent libraries due to an innocent overlapping instance might be worse. As we are at it, it would be nice to be able to specify signatures and other interface details where they belong - in the export list. With a different syntax of the export list; there would be an ambiguity if ..., var1, var2 :: Type, ... gives Type to both variables or only one, and items should be separated by layoutable semicolons. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From Doug_Ransom@pml.com Wed Dec 27 18:33:42 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Wed, 27 Dec 2000 10:33:42 -0800 Subject: ANNOUNCE: HaXml 1.00 Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61DD@hermes.pml.com> I think it is important that a good haskell XML library be included as part of the haskell runtime library given XML's relevance. > -----Original Message----- > From: Malcolm Wallace [mailto:Malcolm.Wallace@cs.york.ac.uk] > Sent: Thursday, November 16, 2000 8:42 AM > To: haskell@haskell.org > Subject: ANNOUNCE: HaXml 1.00 > > > We are pleased to announce > > HaXml release 1.00 > -------------------- > > HaXml is a library enabling the use of Haskell and XML together, > together with several auxiliary tools for useful XML jobs. Fuller > details are on the web page. > > > What's new since 0.9? > --------------------- > The main addition is a full treatment of the external subset for DTDs. > The DtdToHaskell tool can now slurp in a single DTD from multiple > files, and also now treats conditional sections (INCLUDE and IGNORE) > correctly. > > There is improved error-reporting: lexing and parsing errors > now report > the relevant filename, and the line/column positions are more > accurate. > > > Where do I get it? > ------------------ > Web pages: http://www.cs.york.ac.uk/fp/HaXml/ > FTP site: ftp://ftp.cs.york.ac.uk/pub/haskell/HaXml/ > > An older version of HaXml is also included in GHC's hslibs, in package > "text". This will probably be updated to 1.00 at some time. > > Regards, > Malcolm > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > From Doug_Ransom@pml.com Thu Dec 28 01:30:19 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Wed, 27 Dec 2000 17:30:19 -0800 Subject: Learning Haskell and FP Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> I have read "The Craft of Functional Programming" by Simon Thompson and a few paper on the web. "The Craft" is a good book, but it is an introduction to FP. It seems to me it there are a lot of books on OO design I can pick up at the bookstore, but in the FP world, one must worm their way through all sorts of papers. I have seen papers on Catamorphisms, Monads, Programming with Barbed Wire, folds, etc. I think these papers are hard to understand if you don't have the acadademic/mathematical background -- being papers and not textbooks these papers assume a fair bit of base knowledge. I know I can design a fold function to use in place of primitive recursion for most data structures -- I just don't know if I should. It is pretty easy to get through "The Craft of Functional Programming" without understanding what Category Theory , a Catamorphism , or a Kleisli Composition is. I can see lots of real Software Engineering oppurtunities for these various techniques if I could just put them together. Is there a good textbook on Functional Programming which starts from a base point similar to "The craft of Functional Programming" but more advanced in terms of introducing necessary topics like Category theory, catamorphisms, monads, etc? I would find such a book very useful, especially if it concentrated on lazy functional programming. Doug Ransom Systems Engineer Power Measurement Ltd. http://www.pml.com 250-652-7100 office 250-652-0411 fax mailto:doug_ransom@pml.com From israelt@optushome.com.au Thu Dec 28 02:50:50 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 12:50:50 +1000 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> References: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: <200012281250500955.006178FD@mail> >I have read "The Craft of Functional Programming" by Simon Thompson and a >few paper on the web. "The Craft" is a good book, but it is an= introduction >to FP. >It seems to me it there are a lot of books on OO design I can pick up at= the >bookstore, but in the FP world, one must worm their way through all sorts= of >papers. I have seen papers on Catamorphisms, Monads, Programming with >Barbed Wire, folds, etc. I think these papers are hard to understand if= you >don't have the acadademic/mathematical background -- being papers and not >textbooks these papers assume a fair bit of base knowledge. I agree with this completely. The CFP book is a good introduction. Unforunately, the " Gentle Introduction To Haskell" that haskell.org links= to is not a very useful introduction. I am getting more out of Rex Paige's Two Dozen Short Lessons in Haskell.= ( I am studying Haskell and C# on my own in my spare time as break from my= medical practice ). From russell@brainlink.com Thu Dec 28 06:14:54 2000 From: russell@brainlink.com (Benjamin L. Russell) Date: Thu, 28 Dec 2000 01:14:54 -0500 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: While it may not be advanced or mathematical enough for your needs, you may wish to read _The Haskell School of Expression: Learning Functional Programming through Multimedia,_ by Paul Hudak. This is also an introductory book on functional programming, with a special focus on Haskell, although the examples used are mainly from multimedia. I compared the first few chapters of both _The Craft of Functional Programming_ and _The Haskell School of Expression,_ and personally found Hudak's book (the latter) much more interesting. The exercises are designed to teach the reader to think in terms of functional, as opposed to imperative or object-oriented, programming--hence the phrase in the title "School of Expression." --Ben -- Benjamin L. Russell russell@brainlink.com benjamin.russell.es.94@aya.yale.edu "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho On Wed, 27 Dec 2000 17:30:19 -0800 Doug Ransom wrote: > I have read "The Craft of Functional Programming" by > Simon Thompson and a > few paper on the web. "The Craft" is a good book, but it > is an introduction > to FP. > > > It seems to me it there are a lot of books on OO design I > can pick up at the > bookstore, but in the FP world, one must worm their way > through all sorts of > papers. I have seen papers on Catamorphisms, Monads, > Programming with > Barbed Wire, folds, etc. I think these papers are hard > to understand if you > don't have the acadademic/mathematical background -- > being papers and not > textbooks these papers assume a fair bit of base > knowledge. I know I can > design a fold function to use in place of primitive > recursion for most data > structures -- I just don't know if I should. It is pretty > easy to get > through "The Craft of Functional Programming" without > understanding what > Category Theory , a Catamorphism , or a Kleisli > Composition is. I can see > lots of real Software Engineering oppurtunities for these > various techniques > if I could just put them together. > > Is there a good textbook on Functional Programming which > starts from a base > point similar to "The craft of Functional Programming" > but more advanced in > terms of introducing necessary topics like Category > theory, catamorphisms, > monads, etc? I would find such a book very useful, > especially if it > concentrated on lazy functional programming. > > > Doug Ransom > Systems Engineer > Power Measurement Ltd. > http://www.pml.com > 250-652-7100 office > 250-652-0411 fax > mailto:doug_ransom@pml.com > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell From israelt@optushome.com.au Thu Dec 28 08:52:03 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 18:52:03 +1000 Subject: Learning Haskell and FP In-Reply-To: References: Message-ID: <200012281852030258.01AC2A6C@mail> >While it may not be advanced or mathematical enough for your needs, you= may wish to read _The Haskell School of Expression:=A0Learning Functional= Programming through Multimedia,_ by Paul Hudak. This is also an= introductory book on functional programming, with a special focus on= Haskell, although the examples used are mainly from multimedia. Is there an online version of Hudak's book ? ( For example Bruce Eckel has online versions of all his books available= online as well as in print ) >"Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho Translation please ! Basho is my favorite Japanese poet. Unfortunately my Japanese is at the Ohio level.. ( ohiogozaimazu) From israelt@optushome.com.au Thu Dec 28 08:53:08 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 18:53:08 +1000 Subject: Haskell newsgroup Message-ID: <200012281853080001.01AD2753@mail> How about starting a Haskell newsgroup ? The closest seems to be comp.lang.functional. From johanj@cs.uu.nl Thu Dec 28 14:06:26 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Thu, 28 Dec 2000 15:06:26 +0100 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: <20001228140611.B3E3B4536@mail.cs.uu.nl> >Is there a good textbook on Functional Programming which starts from a base >point similar to "The craft of Functional Programming" but more advanced in >terms of introducing necessary topics like Category theory, catamorphisms, >monads, etc? I would find such a book very useful, especially if it >concentrated on lazy functional programming. You might want to have a look at the series of three books on Advanced Functional Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would probably start with 925, which introduces monads, parser & pretty-printing combinators, monadic catamorphisms, constructor classes, etc. -- Johan Jeuring From franka@cs.uu.nl Thu Dec 28 15:48:57 2000 From: franka@cs.uu.nl (Frank Atanassow) Date: Thu, 28 Dec 2000 16:48:57 +0100 Subject: Learning Haskell and FP In-Reply-To: <200012281250500955.006178FD@mail>; from israelt@optushome.com.au on Thu, Dec 28, 2000 at 12:50:50PM +1000 References: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> <200012281250500955.006178FD@mail> Message-ID: <20001228164857.A13674@cs.uu.nl> i r thomas wrote (on 28-12-00 12:50 +1000): > Unforunately, the " Gentle Introduction To Haskell" that haskell.org links to is not a very useful introduction. > I am getting more out of Rex Paige's Two Dozen Short Lessons in Haskell. ( I am studying Haskell and C# on my own in my spare time as break from my medical practice ). What did you find unuseful about GITH? How could it be improved? What were your expectations for it? What was more useful about Rex Paige's notes? >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > Translation please ! Is it OK if I show off and steal some thunder? :) "(It's) An old pond! The sound of water steadily dripping in..." -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Doug_Ransom@pml.com Thu Dec 28 17:34:18 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Thu, 28 Dec 2000 09:34:18 -0800 Subject: Haskell newsgroup Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61ED@hermes.pml.com> That would only work if the haskell mailing list was either delete or mirrored onto a newsgroup. I would prefer a newsgroup myself for bandwidth reasons. > -----Original Message----- > From: i r thomas [mailto:israelt@optushome.com.au] > Sent: Thursday, December 28, 2000 12:53 AM > To: haskell@haskell.org > Subject: Haskell newsgroup > > > How about starting a Haskell newsgroup ? > The closest seems to be comp.lang.functional. > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > From Doug_Ransom@pml.com Thu Dec 28 17:36:37 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Thu, 28 Dec 2000 09:36:37 -0800 Subject: Learning Haskell and FP Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61EE@hermes.pml.com> Who are the audience for the books on Advanced Functional Programming? Academics with a theoretical CS background or someone with just a bit of understanding of FP? Ideally, I would like a course suited for someone who has completed a basic FP course. > -----Original Message----- > From: Johan Jeuring [mailto:johanj@cs.uu.nl] > Sent: Thursday, December 28, 2000 6:06 AM > To: Doug Ransom > Cc: haskell@haskell.org > Subject: Re: Learning Haskell and FP > > > >Is there a good textbook on Functional Programming which > starts from a base > >point similar to "The craft of Functional Programming" but > more advanced in > >terms of introducing necessary topics like Category theory, > catamorphisms, > >monads, etc? I would find such a book very useful, especially if it > >concentrated on lazy functional programming. > > You might want to have a look at the series of three books on Advanced > Functional > Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would > probably start with 925, which introduces monads, parser & > pretty-printing > combinators, monadic catamorphisms, constructor classes, etc. > > -- Johan Jeuring > From shlomif@vipe.technion.ac.il Thu Dec 28 19:23:07 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Thu, 28 Dec 2000 21:23:07 +0200 (IST) Subject: Haskell newsgroup In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61ED@hermes.pml.com> Message-ID: On Thu, 28 Dec 2000, Doug Ransom wrote: > That would only work if the haskell mailing list was either delete or > mirrored onto a newsgroup. I would prefer a newsgroup myself for bandwidth > reasons. > And I prefer a mailing-list. It's hard to access newsgroups from the Technion, and Deja-news seems to be little help when it comes to posting messages. Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From wli@holomorphy.com Thu Dec 28 19:40:38 2000 From: wli@holomorphy.com (William Lee Irwin III) Date: Thu, 28 Dec 2000 11:40:38 -0800 Subject: Haskell newsgroup In-Reply-To: <200012281853080001.01AD2753@mail>; from israelt@optushome.com.au on Thu, Dec 28, 2000 at 06:53:08PM +1000 References: <200012281853080001.01AD2753@mail> Message-ID: <20001228114038.N685@holomorphy.com> On Thu, Dec 28, 2000 at 06:53:08PM +1000, i r thomas wrote: > How about starting a Haskell newsgroup ? > The closest seems to be comp.lang.functional. There is a Haskell IRC channel on EfNet. I've been fielding Haskell questions there with Albert Lai and Ada Lim for several months. There has also been Haskell-related activity on OpenProjects Network #lisp. comp.lang.functional seems to be inclusive enough to obviate the need for a dedicated newsgroup. Cheers, Bill -- "And who knows, if you try it, maybe you find out that you like SM(L)? ;)" -- Markus Mottl on comp.lang.functional From proff@iq.org Thu Dec 28 22:20:13 2000 From: proff@iq.org (Julian Assange) Date: 29 Dec 2000 09:20:13 +1100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: George Russell's message of "Thu, 21 Dec 2000 21:20:46 +0100" References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: George Russell writes: > I'm writing, but that shouldn't be too hard to tweak. In particular I have > followed SML in using "." to express qualification by something, even though > Haskell already used "." for something else, because I can't be bothered right > now to dig up a better symbol. This is why all non S-exp like lanaguage are doomed to progressive syntactic cancer as the useful parts of operator name space and syntax space become progressively polluted and mutated by one fad after another. -- Julian Assange |If you want to build a ship, don't drum up people |together to collect wood or assign them tasks proff@iq.org |and work, but rather teach them to long for the endless proff@gnu.ai.mit.edu |immensity of the sea. -- Antoine de Saint Exupery From russell@brainlink.com Thu Dec 28 22:35:04 2000 From: russell@brainlink.com (Benjamin L. Russell) Date: Thu, 28 Dec 2000 17:35:04 -0500 Subject: Learning Haskell and FP In-Reply-To: <20001228164857.A13674@cs.uu.nl> Message-ID: On Thu, 28 Dec 2000 16:48:57 +0100 Frank Atanassow wrote: > i r thomas wrote (on 28-12-00 12:50 +1000): > > Unforunately, the " Gentle Introduction To Haskell" > that haskell.org links to is not a very useful > introduction. > > I am getting more out of Rex Paige's Two Dozen Short > Lessons in Haskell. ( I am studying Haskell and C# on my > own in my spare time as break from my medical practice ). > > What did you find unuseful about GITH? How could it be > improved? What were > your expectations for it? What was more useful about Rex > Paige's notes? I read part of _GITH,_ too; while it included information necessary for an introduction, the style seemed rather terse and dry, and rather difficult to follow at times, and read more like a manual with many technical details than a tutorial brimming with motivational material, especially when compared to _The Haskell School of Expression_ ("_HSE_" in the sequel). In particular, it could have had some more interesting examples or some more commentary, both of which made _HSE_ so fascinating. > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo > Basho > > > > Translation please ! > > Is it OK if I show off and steal some thunder? :) > > "(It's) An old pond! The sound of water steadily > dripping in..." Actually, if I may add, the translation I remember was the following: "[It's] An old pond! The sound of water as the frog jumps in...." "Kawazu" means "frog," and "tobikomu" means "(to) jump in." --Ben -- Benjamin L. Russell russell@brainlink.com benjamin.russell.es.94@aya.yale.edu "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho From jans@numeric-quest.com Thu Dec 28 18:29:46 2000 From: jans@numeric-quest.com (Jan Skibinski) Date: Thu, 28 Dec 2000 13:29:46 -0500 (EST) Subject: Learning Haskell and FP In-Reply-To: Message-ID: On Thu, 28 Dec 2000, Benjamin L. Russell wrote: > On Thu, 28 Dec 2000 16:48:57 +0100 > Frank Atanassow wrote: > > i r thomas wrote (on 28-12-00 12:50 +1000): > > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > > > > "(It's) An old pond! The sound of water steadily > > dripping in..." > > "[It's] An old pond! The sound of water as the frog jumps in...." Keeping with the minimalistic spirit of Haskell: pond frog plop! -- by James Kirkup, an English poet -- Supposedly from Hiroaki Sato collection of 80 English translations -- of this haiku. -- 3 down 77 to go.. Jan From fruehr@willamette.edu Fri Dec 29 00:42:32 2000 From: fruehr@willamette.edu (Fritz K Ruehr) Date: Thu, 28 Dec 2000 16:42:32 -0800 (PST) Subject: Learning Haskell and FP Message-ID: <200012290042.QAA29740@gemini.willamette.edu> [ Doug Ransom wrote about wanting a more advanced and design-oriented book on FP than "The Craft of Functional Programming" by Simon Thompson. In reply, Johan Jeuring recommended the Advanced Schools books (I concur). ] Let me add a few other recommendations, plus a vision of a book (not yet written, as far as I know) which might fit Doug's needs; I'll call it "The Design Patterns Haskell Companion" (see below). The "actual book" recommendations (all documented on haskell.org): * Introduction to Functional Programming using Haskell (second edition) by Richard Bird (Prentice Hall, ISBN: 0-13-484346-0) This book is an introductory text, like CFP, but it ramps up a bit faster and addresses design issues from a more advanced perspective (IMHO). It's certainly an excellent text, and it builds to a nice medium-sized design example (the program calculator of Chapter 12). It also leans toward a different style of design and programming, influenced by BMF/Squiggol. * Algebra of Programming by Richard Bird and Oege de Moor (Prentice Hall, ISBN: 0-13-507245-X) You might think of this as an advanced sequel to IFPH above, although it focuses more on the theory behind program calculation: categories and allegories figure prominently, and it leans even further in the direction indicated above. But there is nevertheless a lot of good material here which can serve as a foundation for design work, esp. the final chapters (7-10) on algorithms topics. * Algorithms: A Functional Programming Approach by Fethi Rabhi and Guy Lapalme (Addison-Wesley, ISBN: 0-201-59604-0) This is a concise tour through the usual gamut of data structures and algorithms topics typical of a "CS 2" course, but from a functional perspective. It is addressed more to people who are already familiar with programming and with the "standard" approach to DSA issues. It works very well as a reference but includes enough discussion to reward a straight reading. * Purely Functional Data Structures by Chris Okasaki (Cambridge University Press, ISBN: 0-521-66350-4) This one is similar to AFPA above (in being a tour of DSA topics from a functional perspective), but is a bit more advanced: e.g., Ch. 3 covers leftist heaps, binomial heaps and red-black trees. It also addresses issues of analysis in the context of lazy evaluation more thoroughly (Banker's method, etc.). The examples are written using SML, but an appendix (and a website) give Haskell versions. Of course, none of these books really answers the needs of the mature programmer/blossoming functional programmer who seeks advice on broader design issues in the context of lazy FP, esp. Haskell. This gap leads me to propose the fanciful book mentioned above: * The Design Patterns Haskell Companion by [someone(s) reading this list?] The title may be pandering a bit, but if the Smalltalk people can do it, why can't we? :) . In fact, the title is based on "The Design Patterns Smalltalk Companion" by Alpert, Brown and Woolf, a book I came across while reading up on design patterns. (It was recommended by a customer review on Amazon as being better than the original "gang of four" book.) The "Smalltalk Companion" serves an audience of mature programmers and attempts to document a number of "standard" design patterns in the specific context of Smalltalk. I'm not sure that the Haskell community would be comfortable referring to its collective design folklore in these terms, but I'm sure we would all welcome a good book written at this level which systematically addressed the motivation, rationale, trade-offs, etc. of the more advanced techniques of FP (i.e., monads, type and constructor classes, Xa-morphisms (for various X), higher-order and nested datatypes, etc.). As Johan mentioned, the "Advanced School" books serve this purpose to an extent, but they differ from my vision in two respects: first, they are collections of chapters on particular topics, written by different authors, and thus don't form a consistent, systematic review. Second, they are not (all) written from the specific perspective of design, so that for example they don't provide as much comparison and contrast *between* techniques. Of course, another motivation for such a book is that it might lend an air of credibility and maturity to the language, thus helping to promote it in the larger world. Casting it in terms of "design patterns" would certainly make sense for these purposes (and probably guarantees a certain audience, too), although I am still ambivalent about the need for Haskell to become a huge hit with mainstream audiences. In any case, if anyone is interested to write such a book, I will buy a copy :) . And if anyone wishes to collabrate on it, I am willing to help out. (I am not qualified to write it alone, and I think it would turn out best as a group effort in any case.) -- Fritz Ruehr fruehr@willamette.edu From john@foo.net Fri Dec 29 08:37:45 2000 From: john@foo.net (John Meacham) Date: Fri, 29 Dec 2000 00:37:45 -0800 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: ; from qrczak@knm.org.pl on Sun, Dec 24, 2000 at 08:25:12PM +0000 References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: <20001229003745.A11084@mark.ugcs.caltech.edu> I also like the approach of generalizing the record system, although I have not evaluated your particular proposal. Speaking of record improvements why is http://www.cse.ogi.edu/~mpj/pubs/lightrec.html not listed on the future of haskell page? has it already been determined to not be in the future of haskell or has no one gotten around to it? Does anyone else read this proposal and drool? Speaking of this proposal does anyone else see parallels between the lightweight modules proposal and the implicit parameters proposal http://www.cse.ogi.edu/~jlewis/implicit.ps.gz as implemented in ghc. in particular implicit parameters seem like they would be able to be implemented as syntatic sugar on the lightweight module system, one could rewrite implicit parameters as every function taking a record which we can call 'imp' now '?foo' can be rewritten as 'imp.foo' and the 'with ?foo = 1' construct can be rewritten as nimp = {imp | foo := 1} and then passing nimp to all called functions. I have not thought this too far thorough so I could be missing something obvious but I think it shows potential at least for the unification of two popular extensions. and I am pretty sure this was too obvious to mention in the lightweight records paper but the section of (.foo) being equivalent to (\{_|foo=v} -> v) seems appropriate. John -- -------------------------------------------------------------- John Meacham http://www.ugcs.caltech.edu/~john/ California Institute of Technology, Alum. john@foo.net -------------------------------------------------------------- From johanj@cs.uu.nl Fri Dec 29 10:48:58 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Fri, 29 Dec 2000 11:48:58 +0100 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EE@hermes.pml.com> Message-ID: <20001229104844.5C7F94539@mail.cs.uu.nl> >Who are the audience for the books on Advanced Functional Programming? >Academics with a theoretical CS background or someone with just a bit of >understanding of FP? Ideally, I would like a course suited for someone who >has completed a basic FP course. It varies a bit per school (book) and per article. But certainly LNCS 925 contains a number of chapters that should be interesting for someone with a general CS background and a basic FP course. I know it has been used in a couple of undergraduate courses on advanced functional programming. Topics, Authors, LNCS nr: - Monads, Wadler, 925 - Parser Combinators, Fokker, 925 - Constructor Classes, Jones, 925 - (Monadic) folds (or catamorphisms), Meijer & Jeuring, 925 - Space leaks and heap profiling, Runciman & Rojemo, 1129 - Algorithms and data structures, Okasaki, 1129 - Graph algorithms, Launchbury, 925 - User Interfaces, Carlsson & Hallgren, 925, Peyton Jones & Finne 1129 etc. Johan Jeuring http://www.cs.uu.nl/~johanj/ From franka@cs.uu.nl Fri Dec 29 13:31:01 2000 From: franka@cs.uu.nl (Frank Atanassow) Date: Fri, 29 Dec 2000 14:31:01 +0100 Subject: Learning Haskell and FP In-Reply-To: ; from russell@brainlink.com on Thu, Dec 28, 2000 at 05:35:04PM -0500 References: <20001228164857.A13674@cs.uu.nl> Message-ID: <20001229143101.A14014@cs.uu.nl> Benjamin L. Russell wrote (on 28-12-00 17:35 -0500): > > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > [..] Is it OK if I show off and steal some thunder? :) So much for that idea...! > > "(It's) An old pond! The sound of water steadily dripping in..." > > Actually, if I may add, the translation I remember was the following: > > "[It's] An old pond! The sound of water as the frog jumps in...." > > "Kawazu" means "frog," and "tobikomu" means "(to) jump in." That makes sense. I was guessing that "kawazu" was the old form of modern "kawarazu" (`without changing'). Modern `frog' is "kaeru", though, and the transitive form of "kawaru" (`change') is also "kaeru", so I suppose there is some linguistic relationship. "tobikomu" makes much more sense this way too. I thought it was a figurative usage, but it still didn't sound right... -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Doug_Ransom@pml.com Fri Dec 29 15:52:24 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Fri, 29 Dec 2000 07:52:24 -0800 Subject: Haskell Language Design Questions Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> 1. Is the lack of dynamic binding of functions by design or because it was too much effort to be justified at the time the language was designed? In object oriented programming there can be several implementations of the same interface, and they can be stored in the same collection. 2. It seems to me that the Maybe monad is a poor substitute for exception handling because the functions that raise errors may not necessarily support it. For example, if I use someone elses custom type and a custom map function theirmap myApplicator SomeList and theirmap is not designed to support the Maybe monad, then it becomes hard to use if SomeFunction might raise an error. Am I missing something? Doug Ransom Systems Engineer Power Measurement Ltd. http://www.pml.com 250-652-7100 office 250-652-0411 fax mailto:doug_ransom@pml.com From israelt@optushome.com.au Fri Dec 29 06:50:36 2000 From: israelt@optushome.com.au (i r thomas) Date: Fri, 29 Dec 2000 16:50:36 +1000 Subject: Learning Haskell and FP In-Reply-To: <200012290042.QAA29740@gemini.willamette.edu> References: <200012290042.QAA29740@gemini.willamette.edu> Message-ID: <200012291650360884.018BF6C5@mail> On 12/28/2000 at 7:00 PM Bill Halchin wrote: >Hello IR, > I agree with the OU Haskell Tutorial. It is excellent!! Yes, with a bit of editing and more diagrams , it would probably be worth= publishing. >BTW, what is your C# source? The .NET Framework SDK is freely downloadable from MS ( around 100 megs ) and comes with a C# tutorial, C# reference and a command line C#. There are also a few chapters online of some C# books that cover issues= like namespaces and attributes. I am using the Antechinus C# editor as an IDE . This comes with a few basic= C# examples as well. ( for vi freaks, I have written a C# vim syntax file that will appear on= vim.org once it is polished up.) From fjh@cs.mu.oz.au Sat Dec 30 03:50:04 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Sat, 30 Dec 2000 14:50:04 +1100 Subject: Haskell Language Design Questions In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> References: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> Message-ID: <20001230145004.A12063@hg.cs.mu.oz.au> On 29-Dec-2000, Doug Ransom wrote: > 1. Is the lack of dynamic binding of functions by design or because it was > too much effort to be justified at the time the language was designed? In > object oriented programming there can be several implementations of the same > interface, and they can be stored in the same collection. It's just something that didn't make it into Haskell 98. Hugs and ghc offer a language extension for that. It will almost certainly be in the next revision of Haskell. See . > 2. It seems to me that the Maybe monad is a poor substitute for > exception handling because the functions that raise errors may not > necessarily support it. Hugs and ghc also have exception handling extensions. See . There's also a paper or two on that. I hope you'll forgive the self-citation, but the only one for which I happen to have a reference on-hand is this one: A semantics for imprecise exceptions. Simon Peyton-Jones, Alastair Reid, Tony Hoare, Simon Marlow, and Fergus Henderson. Proceedings of the 1999 ACM SIGPLAN Conference on Programming Language Design and Implementation, May 1999. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From qrczak@knm.org.pl Sat Dec 30 09:34:22 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 30 Dec 2000 09:34:22 GMT Subject: Haskell Language Design Questions References: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> <20001230145004.A12063@hg.cs.mu.oz.au> Message-ID: Sat, 30 Dec 2000 14:50:04 +1100, Fergus Henderson pisze: > It's just something that didn't make it into Haskell 98. > Hugs and ghc offer a language extension for that. > It will almost certainly be in the next revision of Haskell. See > . Existential quantification is not always necessary to obtain an equivalent of dynamic binding. Dynamic binding is often used instead of function closures or IO action closures, especially in languages which lack real closures. An object of the abstract type "output IO stream" is equivalent to a record (tuple, whatever) of values of types like Char -> IO () -- write a character String -> IO () -- write a string IO () -- flush IO () -- close "Dynamic binding" is a fancy way of saying that the function to be called will be chosen at runtime. So we have exactly this, expressed in a simpler way. OO languages provide subtyping and inheritance. This is harder. Subtyping done by explicit coercions up can be done, but it's tedious to write (my new record scheme proposal tries to help here), and it's impossible to coerce down. Inheritance can be done by delegation. It does not work to express everything like OO languages usually do, because they are not typesafe. That's why (IMHO) that OO languages are usually dynamically typed. OO-like subtyping is usually not able to accurately express binary methods or the requirement that an argument must provide several interfaces at once. Haskell's classes should be left for constraints on types (as opposed to values). I want to sort a list, I compare elements with each other. It does not make sense to say that an element is comparable. Comparable with what? A _type_ can be comparable (i.e. ordered), or the ordering itself may be expressed as an object, but it does not belong to objects being compared. It follows that it does not make sense to have "a heterogeneous collection of comparable objects" or casting an object up to the type "comparable". But I might not care if the fact that something is a stream open for writing is a property of its type which is not statically known (as when stream is modelled as a class) or a property of all objects of the given type which is concrete (as when stream is modelled as a record of functions) - because I usually work with one such object at a time. When it's expressed as a class, I gain the possibility of extracting from the same object at different places properties belonging to different interfaces, without explicit coercions. But it is necessary to use existential quantification for heterogeneous collections. When it's expressed as a record of functions, all streams are flattened to a single interface, it is more convenient to use but the information about the exact kind of stream is not available. These approaches can be mixed. With my new record scheme proposal it is more convenient to introduce a class of types of objects from which the interface of a stream open for writing (expressed as a record of functions) can be extracted. This class needs not to be explicitly defined (only the record of functions). Stream operations can also be seen as provided by the object itself instead of always going through the extracted interface. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From R.Daniel@Europe.com Sat Dec 30 15:16:30 2000 From: R.Daniel@Europe.com (R.Daniel) Date: Sat, 30 Dec 2000 15:16:30 +0000 Subject: The Hanoi Towers Message-ID: <5.0.0.25.2.20001230151115.009ef3a0@mail.ip.pt> --=====================_12490613==_.ALT Content-Type: text/plain; charset="us-ascii"; format=flowed hi, i was looking for the source code for the Hanoi Towers, if anyone has that, could you please send it to me? I apreciate the help , thankx ----->R.Daniel Aka AZONIC ICQ 28959546 --=====================_12490613==_.ALT Content-Type: text/html; charset="us-ascii" hi, i was looking for the source code for the Hanoi Towers, if anyone has that, could you please send it to me?

I apreciate the help , thankx

----->R.Daniel Aka AZONIC
        ICQ           28959546 --=====================_12490613==_.ALT-- From qrczak@knm.org.pl Sat Dec 30 17:53:05 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 30 Dec 2000 17:53:05 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> <20001229003745.A11084@mark.ugcs.caltech.edu> Message-ID: Fri, 29 Dec 2000 00:37:45 -0800, John Meacham pisze: > http://www.cse.ogi.edu/~mpj/pubs/lightrec.html I've read it and posted some comments in February 2000. There was no answer AFAIR. Here are they again, slightly edited and extended: I don't understand why to separate kinds of rows and record types, instead of having "a type which is known to be a record type", at least on the level visible for the programmer. So instead of type Point r = (r | x::Int, y::Int) type Colored r = (r | c::Color) type ColoredPoint r = Point (Colored r) p :: {ColoredPoint()} -- Point, Colored, ColoredPoint :: row -> row it would be type Point r = {r | x::Int, y::Int} type Colored r = {r | c::Color} type ColoredPoint r = Point (Colored r) p :: ColoredPoint() -- Point, Colored, ColoredPoint :: recordType -> recordType -- where recordType is something like a subkind of *. -------- It is bad to require the programmers to think in advance that a type is going to be subtyped, and write elaborated type Point r = (r | x::Int, y::Int) ... {Point()} ... instead of simpler type Point = {x::Int, y::Int} ... Point ... which is not extensible. -------- I got used to () as a unit type. It would be a pity to lose it. -------- A minor problem. If tuples are records, field names should be such that alphabetic order gives the sequential order of fields, or have a special rule of field ordering for names of tuple fields... -------- In general I don't quite like the fact that records are getting more anonymous. Magical instances of basic classes? How inelegant. If I want the record type to have an identity, it will have to be wrapped in a newtype, so I must think at the beginning if I will ever want to write specialized insances for it and then all the code will depend on the decision. Currently a datatype with named fields has both an identity and convenient syntax of field access. (And why newtype is not mentioned in section 5.1?) I like name equivalence where it increases type safety. Extensible records promote structural equivalence. Unfortunately the proposal seems to increase the number of irregularities and inelegant rules... If expr.Constructor for a multiparameter constructor yields a tuple, then for an unary constructor it should give a 1-tuple, no? I know it would be extremely inconvenient, especially as newtypes are more used, so I don't propose it, but it is getting less regular. What about nullary constructors - empty tuple? :-) I don't say that I don't like the proposal at all, or that I never wanted to have several types with the same field names. But it is not clean for me, it's a compromise between usability and elegance, and from the elegance point of view I like current records more. Maybe it would be helpful to show how to translate a program with extensible records to a program without them (I guess it's possible in a quite natural way, but requires global transformation of the whole program). -------- Extensible records makes a syntactic difference between field access and function call. So if one wants to export a type abstractly or simply to provide functions operating on it without fixing the fact that they are physically fields, he ends in writing functions like size:: MyRecord -> Int size x = x.MyRecord.size which are unnecessary now, even if size is simply a field. It reminds me of C++ which wants us to provide methods for accessing data fields (for allowing them to be later redefined as methods, and for allowing everything to be uniformly used with "()" after the feature name). Ugh. -------- My new record scheme proposal does not provide such lightweight extensibility, but fields can be added and deleted in a controlled way if the right types and instances are made. The distinction between having a field and having a supertype is blurred. Similarly between having itself a field called foo and having a supertype which has a field called foo. Similarly between creating a record by adding fields to another record and creating a record by putting another record as one of fields. Similarly between casting to a supertype by removing some fields and extracting the supertype represented by a field. An advantage is that the interface of records does not constrain the representation in any way. It's up to how instances are defined, with the provision of natural definitions for records implemented physically as product types. For example supplying a color for a colorless point and the reverse operation can be written thus: addColor :: (Record cp, cp.point :: p, cp.color :: Color) => p -> Color -> cp addColor p c = record point = p; color = c removeColor :: (cp.point :: p) => cp -> p removeColor = (.point) When the following definitions are present: data Point = record x, y :: Int data ColoredPoint = record point :: Point point (x, y) color :: Color these functions can be used as of types addColor :: Point -> Color -> ColoredPoint removeColor :: ColoredPoint -> Point A colored point can be constructed either as in addColor, from a point and a color, or thus: record x = ... y = ... color = ... If ColoredPoint were defined directly as data ColoredPoint = record x, y :: Int color :: Color the previous interface could be *retroactively* reconstructed thus: instance (ColoredPoint).point :: Point where cp.point = record x = cp.x; y = cp.y cp.record {point = p} = cp.record x = p.x; y = p.y Multiple inheritance can be modelled as well. And field renaming during inheritance. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From kahl@heraklit.informatik.unibw-muenchen.de Fri Dec 22 16:04:45 2000 From: kahl@heraklit.informatik.unibw-muenchen.de (Wolfram Kahl) Date: 22 Dec 2000 16:04:45 -0000 Subject: 2nd CFP: RelMiS 2001 Message-ID: <20001222160445.29431.qmail@heraklit.informatik.unibw-muenchen.de> [please post. apologies for multiple copies] SECOND CALL FOR PAPERS RelMiS 2001 - Relational Methods in Software ============================================ 7-8 April 2001, Genova, Italy http://ist.unibw-muenchen.de/RelMiS/ A Satellite Event to ETAPS 2001 Important Dates =============== Deadline for submission: 10 January 2001 Notification of acceptance: 9 February 2001 Final version due: 28 February 2001 Workshop dates: 7-8 April 2001 Workshop Topics =============== * Relational Specifications and Modelling: methods and tools, tabular methods, abstract data types * Relational Software Design and Development Techniques: relational refinement, heuristic approaches for derivation, correctness considerations, dynamic programming, greedy algorithms, catamorphisms, paramorphisms, hylomorphisms and related topics * Programming with Relations: prototyping, testing, fault tolerance, information systems, information coding * Implementing relational algebra with mixed representation of relations * Handling of Large Relations: problems of scale, innovative representations, distributed implementation Submissions =========== Submissions will be evaluated by the Program Committee for inclusion in the proceedings, which will be published in the ENTCS series. Papers must contain original contributions, be clearly written, and include appropriate reference to and comparison with related work. Papers should be submitted electronically as uuencoded PostScript files at the address relmis@ist.unibw-muenchen.de. Preference will be given to papers that are no shorter than 10 and no longer than 15 pages. A separate message should also be sent, with a text-only one-page abstract and with mailing addresses (both postal and electronic), telephone number and fax number of the corresponding author. Final versions will have to be submitted as LaTeX source and have to adhere to the ENTCS style! Programme Committee =================== Rudolf Berghammer (Kiel), Jules Desharnais (Quebec), Wolfram Kahl (Munich), David L. Parnas (Hamilton), Gunther Schmidt (Munich) ------------- E-Mail: relmis@ist.unibw-muenchen.de Workshop home page: URL: http://ist.unibw-muenchen.de/RelMiS/ From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 11:03:58 2000 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Fri, 1 Dec 2000 11:03:58 +0000 Subject: a trap for the unwary Message-ID: Today, I thought I had discovered a bug in ghc. Then I tried hbc and Hugs, and they also rejected my program with the same error. nhc98 alone accepts it without complaint. I looked up the Report, and it seems that the program is indeed incorrect. Quick quiz: without running this through a compiler, who can spot the mistake? :-) > module Main where > import Char > f x = y > where > y | isSpace x = True > y | otherwise = False > main = print (f 'x') Regards, Malcolm From wimjan@xs4all.nl Fri Dec 1 14:49:13 2000 From: wimjan@xs4all.nl (Wim-Jan Hilgenbos) Date: Fri, 01 Dec 2000 15:49:13 +0100 Subject: Beginner: error when using multiple where stmts in hugs98 Message-ID: <3A27BA68.4EE70883@xs4all.nl> This is a multi-part message in MIME format. --------------F1E92FD1F075259053A3C4BA Content-Type: text/plain; charset=us-ascii Content-Transfer-Encoding: 7bit Hi, I've been trying some examples in functional programming. Most things work fine, but I have trouble with expressions with 'where' clauses that define more then one local definition. (I work with hugs98 version september 1999 under Linux) For example: ----------[ Mydiff.hs ]---------------------- module Mydiff where mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 ----------[ end Mydiff.hs ]------------------- When I try to load this module I get ERROR "Mydiff.hs" (line 5): Syntax error in input (unexpected `=') line 5 is the line h = 0.0001 I tried other examples like this one, played around with line-breaks white-space etc. Rewriting the f' line to f' x = (f (x+0.0001) - f x) / 0.0001 does the trick, but is not very satisfying. Can anyone help? WJ PS. I attached above example -- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - Disclaimer: "These opinions are my own, though for a small fee they be yours too." -- Dave Haynie --------------F1E92FD1F075259053A3C4BA Content-Type: text/plain; charset=us-ascii; name="Mydiff.hs" Content-Transfer-Encoding: 7bit Content-Disposition: inline; filename="Mydiff.hs" module Mydiff where mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 --------------F1E92FD1F075259053A3C4BA-- From jmaessen@mit.edu Fri Dec 1 15:41:32 2000 From: jmaessen@mit.edu (Jan-Willem Maessen) Date: Fri, 1 Dec 2000 10:41:32 -0500 Subject: a trap for the unwary Message-ID: <200012011541.KAA00635@lauzeta.mit.edu> Malcolm Wallace writes: > Quick quiz: without running this through a compiler, who can spot > the mistake? :-) > > > module Main where > > import Char > > f x = y > > where > > y | isSpace x = True > > y | otherwise = False -- ** The problem line? > > main = print (f 'x') Without running this through the compiler, but based on similar problems I've had recently, I'd assume the problem is the marked line. Two outer-level patterns are each presented with guards. This would be correct for a function definition: > f x = y () > where > y _ | isSpace x = True > y _ | otherwise = False -- ** Does this work? This is a tricky issue. I'd like the original program to be all right. We end up sowing confusion with erroneous programs like this one: > f x = y > where > y | otherwise = False -- ** Now this pattern overlaps! > y | isSpace x = True But of course an analogous problem occurs in the function definition, and I think can be caught by turning on warnings in ghc. -Jan-Willem Maessen jmaessen@mit.edu From Malcolm.Wallace@cs.york.ac.uk Fri Dec 1 15:44:16 2000 From: Malcolm.Wallace@cs.york.ac.uk (Malcolm Wallace) Date: Fri, 1 Dec 2000 15:44:16 +0000 Subject: a trap for the unwary In-Reply-To: <200012011541.KAA00635@lauzeta.mit.edu> Message-ID: > > > f x = y > > > where > > > y | isSpace x = True > > > y | otherwise = False -- ** The problem line? Correct. Here y is a pattern binding, and multiple pattern bindings of the same variable are not permitted. > f x = y () > where > y _ | isSpace x = True > y _ | otherwise = False -- ** Does this work? Correct. Here y is a function binding instead, and multiple clauses *are* permitted. > I'd like the original program to be all right. Me too. I wrote 'y' as a 0-arity function, knowing that because it used a free variable bound at an outer scope, it would probably be lambda-lifted to a greater arity by the compiler. But only one compiler saw it in the same way as I did. :-) Of course, if the pattern binding is more complex than a single variable name, I still want the no-multiple-bindings rule to apply as usual: > f x = y () > where > (y:_) | isSpace x = [True] > (y:_) | otherwise = [False] -- ** Definitely wrong and indeed all compilers reject this, as they should. Regards, Malcolm From schulzs@uni-freiburg.de Fri Dec 1 17:23:57 2000 From: schulzs@uni-freiburg.de (Sebastian Schulz) Date: Fri, 01 Dec 2000 17:23:57 +0000 Subject: Beginner: error when using multiple where stmts in hugs98 References: <3A27BA68.4EE70883@xs4all.nl> Message-ID: <3A27DEAD.6FED7B7@shamoha.de> Wim-Jan Hilgenbos wrote: > > Hi, > > I've been trying some examples in functional programming. Most things > work fine, > but I have trouble with expressions with 'where' clauses that define > more then one > local definition. > (I work with hugs98 version september 1999 under Linux) > > For example: > > ----------[ Mydiff.hs ]---------------------- > module Mydiff where > > mydiff f = f' > where f' x = ( f (x+h) - f x) / h > h = 0.0001 > > ----------[ end Mydiff.hs ]------------------- > Try this: mydiff f = f' where f' x = ( f (x+h) - f x) / h h = 0.0001 It works fine with Hugs98 (feb2000). regards seb From ron4ld@pacific.net.au Fri Dec 1 21:08:56 2000 From: ron4ld@pacific.net.au (Ronald Kuwawi) Date: Sat, 02 Dec 2000 08:08:56 +1100 Subject: old easter egg Message-ID: <3A281368.7D24E3DC@pacific.net.au> open text editor, type hash :: [Char] -> Int hash = (foldl (+) 0) . (map ord) save as hash.hs load script, type: hash "MSDOS 6.000" or hash "SYSTEM 7.0" :-) Ronald From zhanyong.wan@yale.edu Fri Dec 1 21:55:06 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Fri, 01 Dec 2000 16:55:06 -0500 Subject: old easter egg References: <3A281368.7D24E3DC@pacific.net.au> Message-ID: <3A281E3A.66187BC7@yale.edu> Ronald Kuwawi wrote: > > open text editor, type > hash :: [Char] -> Int > hash = (foldl (+) 0) . (map ord) > > save as hash.hs > > load script, type: > hash "MSDOS 6.000" > > or > > hash "SYSTEM 7.0" or hash "HASKELL%98" :-) -- Zhanyong Wan From peterson-john@cs.yale.edu Fri Dec 1 22:14:41 2000 From: peterson-john@cs.yale.edu (John Peterson) Date: Fri, 1 Dec 2000 17:14:41 -0500 Subject: The Haskell store is open .... Message-ID: <200012012214.RAA28801@ragged.cs.yale.edu> Head to http://www.cafepress.com/haskell for your holiday shopping. Thanks to Conal Elliott and Fritz Ruehr for their artwork. Conal's design was produced by Pan so this shirt is in fact powered by Haskell! I'll be glad to add more designs in the future. Once cafepress lets me put more than one design in a store I'll consolidate everything. Meanwhile, if you want to set up a separate store I can link it into haskell.org for you. John From jf15@hermes.cam.ac.uk Sat Dec 2 00:03:30 2000 From: jf15@hermes.cam.ac.uk (Jon Fairbairn) Date: Sat, 2 Dec 2000 00:03:30 +0000 (GMT) Subject: old easter egg In-Reply-To: <3A281E3A.66187BC7@yale.edu> Message-ID: On Fri, 1 Dec 2000, Zhanyong Wan wrote: >=20 > Ronald Kuwawi wrote: > >=20 > > open text editor, type > > hash :: [Char] -> Int > > hash =3D (foldl (+) 0) . (map ord) > hash "HASKELL%98" hash "Haskell Ninety Eight !!"=20 surely? --=20 J=F3n Fairbairn Jon.Fairbairn@cl.cam.ac.uk From kili@outback.escape.de Sat Dec 2 02:31:05 2000 From: kili@outback.escape.de (Matthias Kilian) Date: Sat, 2 Dec 2000 03:31:05 +0100 (CET) Subject: old easter egg In-Reply-To: Message-ID: On Sat, 2 Dec 2000, Jon Fairbairn wrote: > > hash "HASKELL%98" > > > hash "Haskell Ninety Eight !!" Here's the who;e truth: hash "Turing!" Kili --=20 Nunja! Wenn man erst einmal anf=E4ngt zu denken, dann ist es wie eine Sucht. Man kommt nicht mehr los davon. [WoKo in dag=B0, 28.11.2000] From ashley@semantic.org Sat Dec 2 19:08:53 2000 From: ashley@semantic.org (Ashley Yakeley) Date: Sat, 2 Dec 2000 11:08:53 -0800 Subject: old easter egg Message-ID: <200012021908.LAA10458@mail4.halcyon.com> At 2000-12-01 13:08, Ronald Kuwawi wrote: >open text editor, type >hash :: [Char] -> Int >hash = (foldl (+) 0) . (map ord) > >save as hash.hs > >load script, type: >hash "MSDOS 6.000" > >or > >hash "SYSTEM 7.0" It's not really an easter egg, is it? It's more a modern form of numerology. I was hoping to see the hugs environment show me a little dancing bunny animation or something. letter c | ord c <= 64 = 0 letter c | ord c <= 90 = ord c - 64 letter c | ord c <= 96 = 0 letter c | ord c <= 122 = ord c - 96 letter c | otherwise = 0 renum n | n == 0 = 0 renum n | otherwise = (mod ((n - 1) * 19) 26) + 1 engql c = renum (letter c) engq = (foldl (+) 0) . (map engql) -- Ashley Yakeley, Seattle WA From gmh@marian.cs.nott.ac.uk Mon Dec 4 08:54:00 2000 From: gmh@marian.cs.nott.ac.uk (gmh@marian.cs.nott.ac.uk) Date: Mon, 4 Dec 2000 8:54:00 GMT Subject: JFP Special Issue on Haskell Message-ID: <20001204085501.0EA3F1016@www.haskell.org> Dear all, Please note that the deadline for submission to the JFP Special Issue on Haskell is in two months time --- 1st February 2001. Graham Hutton ---------------------------------------------------------------------- CALL FOR PAPERS Journal of Functional Programming Special Issue on Haskell Since its inception in 1987, Haskell has provided a focal point for research in lazy functional programming. During this time the language has continually evolved, as a result of both theoretical advances and practical experience. Haskell has proved to be a powerful tool for many kinds of programming tasks, and applications in industry are beginning to emerge. The recent definition of Haskell 98 provides a long-awaited stable version of the language, but there are many exciting possibilities for future versions of Haskell. The fourth Haskell Workshop was held as part of the PLI 2000 colloquium on Principles, Logics, and Implementations of high-level programming languages in Montreal, 17th September 2000. Previous Haskell Workshops have been held in Paris (1999), Amsterdam (1997) and La Jolla (1995). Following on from these workshops, a special issue of the Journal of Functional Programming will be devoted to Haskell. Possible topics include, but are not limited to: Critiques of Haskell 98; New proposals for Haskell; Applications or case studies; Programming techniques; Reasoning about programs; Semantic issues; Pedagogical issues; Implementation. Contributors to any of the Haskell workshops are invited to submit full papers to the special issue on Haskell, but submission is open to everyone. Submissions should be sent to the guest editor (address below), with a copy to Nasreen Ahmad (nasreen@dcs.gla.ac.uk). Submitted articles should be sent in postscript format, preferably gzipped and uuencoded. In addition, please send, as plain text, title, abstract, and contact information. The submission deadline is 1st February 2001. For other submission details, please consult an issue of JFP or see the Journal's web pages. Guest Editor: Graham Hutton School of Computer Science and IT The University of Nottingham Nottingham NG8 1BB United Kingdom gmh@cs.nott.ac.uk Useful Links: 2000 Haskell Workshop www.cs.nott.ac.uk/~gmh/hw00.html JFP Special Issue on Haskell www.cs.nott.ac.uk/~gmh/jfp.html JFP Home Page www.dcs.gla.ac.uk/jfp ---------------------------------------------------------------------- From zhanyong.wan@yale.edu Mon Dec 4 16:04:24 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Mon, 04 Dec 2000 11:04:24 -0500 Subject: Rank-2 polymorphism & type inference Message-ID: <3A2BC088.11497DEA@yale.edu> Hello, I'm playing with Haskell's rank-2 polymorphism extension and am puzzled by the following example: ----------------------------------------------------------- module R2Test where class SubType a b where super :: a -> b data Sub c a = Sub data Super c a = Super instance SubType (Sub c a) (Super c a) f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b f g x = undefined x :: Sub c Int x = undefined y :: Super c Int y = f (\a -> super a) x ---------------------------------------------------------- I though the definition of y should type-check because (roughly): 1. We know x :: Sub c Int, y :: Super c Int 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b, we know a is Int and b is Int. 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we are all set. However, Hugs 98 Feb 2000 (with the -98 switch) gives me: ERROR "R2Test.hs" (line 19): Cannot justify constraints in application *** Expression : \a -> super a *** Type : Sub b _1 -> Super b _2 *** Given context : () *** Constraints : SubType (Sub b _1) (Super b _2) and GHC 4.08.1 (with the -fglasgow-exts switch) gives: R2Test.hs:19: Could not deduce `SubType (Sub c a) (Super c Int)' from the context: () Probable cause: missing `SubType (Sub c a) (Super c Int)' in the type signature of an expression or missing instance declaration for `SubType (Sub c a) (Super c Int)' arising from use of `super' at R2Test.hs:16 In the right-hand side of a lambda abstraction: super a If I remove the "forall c." from the type signature for f, then both compilers accept my code. My question is: how does the type inference algorithm work in the presence of rank-2 types? Does anyone know of any documentation on this? Thanks! -- Zhanyong # Zhanyong Wan http://pantheon.yale.edu/~zw23/ ____ # Yale University, Dept of Computer Science /\___\ # P.O.Box 208285, New Haven, CT 06520-8285 ||___| From zhanyong.wan@yale.edu Mon Dec 4 21:30:46 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Mon, 04 Dec 2000 16:30:46 -0500 Subject: Rank-2 polymorphism & type inference References: <3A2BC088.11497DEA@yale.edu> Message-ID: <3A2C0D06.69F3058D@yale.edu> Hi, After sending out my question, I noticed that hugs and ghc understood my code differently: from the error messages, we can see that hugs view (\a -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it is Sub c a -> Super c Int. To verify it, I changed my code s.t. y is defined as y = f (\(a :: Sub c Int) -> super a) x instead of y = f (\a -> super a) x Guess what happened: ghc *accepted* the code, and hugs *rejected* it with message: ERROR "R2Test.hs" (line 19): Cannot justify constraints in application *** Expression : \a -> super a *** Type : Sub b Int -> Super b _2 *** Given context : () *** Constraints : SubType (Sub b Int) (Super b _2) Aha, this is something interesting! Either there is no standard for the Haskell rank-2 type inference algorithm (which is a sad thing), or one of hugs and ghc is wrong here. Now the hugs/ghc guys on the list can no longer remain silent -- you got to defend yourselves! :-) Could anyone explain to me what the right behavior is supposed to be here? Thanks. -- Zhanyong Zhanyong Wan wrote: > > Hello, > > I'm playing with Haskell's rank-2 polymorphism extension and am puzzled > by the following example: > > ----------------------------------------------------------- > module R2Test where > > class SubType a b where > super :: a -> b > > data Sub c a = Sub > data Super c a = Super > > instance SubType (Sub c a) (Super c a) > > f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c b > f g x = undefined > > x :: Sub c Int > x = undefined > > y :: Super c Int > y = f (\a -> super a) x > ---------------------------------------------------------- > > I though the definition of y should type-check because (roughly): > > 1. We know x :: Sub c Int, y :: Super c Int > 2. Hence in f :: (forall c. Sub c a -> Super c b) -> Sub c a -> Super c > b, we know a is Int and b is Int. > 3. Hence (\a -> super a) :: (forall c. Sub c Int -> Super c Int), and we > are all set. > > However, Hugs 98 Feb 2000 (with the -98 switch) gives me: > > ERROR "R2Test.hs" (line 19): Cannot justify constraints in application > *** Expression : \a -> super a > *** Type : Sub b _1 -> Super b _2 > *** Given context : () > *** Constraints : SubType (Sub b _1) (Super b _2) > > and GHC 4.08.1 (with the -fglasgow-exts switch) gives: > > R2Test.hs:19: > Could not deduce `SubType (Sub c a) (Super c Int)' > from the context: () > Probable cause: missing `SubType (Sub c a) (Super c Int)' > in the type signature of an expression > or missing instance declaration for `SubType (Sub c > a) (Super > c Int)' > arising from use of `super' at R2Test.hs:16 > In the right-hand side of a lambda abstraction: super a > > If I remove the "forall c." from the type signature for f, then both > compilers accept my code. > > My question is: how does the type inference algorithm work in the > presence of rank-2 types? Does anyone know of any documentation on > this? Thanks! From simonpj@microsoft.com Tue Dec 5 13:12:20 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 5 Dec 2000 05:12:20 -0800 Subject: Rank-2 polymorphism & type inference Message-ID: <74096918BE6FD94B9068105F877C002D013781CA@red-pt-02.redmond.corp.microsoft.com> | > My question is: how does the type inference algorithm work in the | > presence of rank-2 types? Does anyone know of any documentation on | > this? Thanks! I had a look at this. Actually it turns out to be only loosely related to rank-2 polymorphism. I've been able to reproduce your problem using only Haskell 98. It looks like a problem with incomplete type inference Consider this: module MP where class C t where op :: t -> Bool instance C [t] where op x = True test :: [Int] -> Bool -- REQUIRED! test y = let f :: c -> Bool f x = op (y >> return x) in f (y::[Int]) Both GHC and Hugs reject this module if the type signature for test is omitted. NHC (v1.00, 2000-09-15) falls over completely, with Fail: Prelude.chr: bad argument All three succeed if the signature is in, or if the signature for f is omitted. This was unexpected, to me at least. You may need to add a type signature if polymorphic recursion is being used, but here it isn't! The problem is this: the compiler learns that y::[Int] "too late" to make use of it when solving the constraints arising from the RHS of f. In more detail, here's what happens. First we typecheck the RHS of f, deducing the types x :: a where a is fresh y :: k a where k is fresh y >> return x :: k a op (y >> return x) :: Bool with constraint C (k a) \x -> op (y >> return x) :: a -> Bool with constraint C (k a) Now we try to generalise over a. We need to discharge the contraint C (k a). Later we will find that y::[Int], so k=[], but we don't know that yet. So we can't solve the constraint. Adding the type signature to 'f' lets both GHC and Hugs figure out that y::[Int] in advance, so we need to solve the constraint C ([] a), which is fine. So I think you have uncovered a genuine problem, and one I don't know how to solve. It can always be "solved" by adding more type information, such as the type sig for 'test'. In you case you said: | After sending out my question, I noticed that hugs and ghc understood my | code differently: from the error messages, we can see that hugs view (\a | -> super a) as having type Sub b _1 -> Super b _2, while ghc thinks it | is Sub c a -> Super c Int. To verify it, I changed my code s.t. y is | defined as | | y = f (\(a :: Sub c Int) -> super a) x This is exactly right, and GHC is happy now. I can't account for Hugs' behaviour. The "right" solution is presumably to defer all constraint checking until we know what 'k' is. But that's a bit tricky because the constraint checking generates bindings that must appear in f's RHS. A full solution looks a bit over-kill-ish. But it's unsettling that the inference algorithm is incomplete. Simon From johanj@cs.uu.nl Tue Dec 5 14:22:06 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Tue, 05 Dec 2000 15:22:06 +0100 Subject: Call for papers: Haskell Workshop 2001 In-Reply-To: Message-ID: <20001205142154.B18FA451B@mail.cs.uu.nl> ============================================================================ CALL FOR PAPERS 2001 Haskell Workshop Firenze, Italy The Haskell Workshop forms part of the PLI 2001 colloquium on Principles, Logics, and Implementations of high-level programming languages, which comprises the ICFP/PPDP conferences and associated workshops. Previous Haskell Workshops have been held in La Jolla (1995), Amsterdam (1997), Paris (1999), and Montreal (2000). http://www.cs.uu.nl/people/ralf/hw2001.{html,pdf,ps,txt} ============================================================================ Scope ----- The purpose of the Haskell Workshop is to discuss experience with Haskell, and possible future developments for the language. The scope of the workshop includes all aspects of the design, semantics, theory, application, implementation, and teaching of Haskell. Submissions that discuss limitations of Haskell at present and/or propose new ideas for future versions of Haskell are particularly encouraged. Adopting an idea from ICFP 2000, the workshop also solicits two special classes of submissions, application letters and functional pearls, described below. Application Letters ------------------- An application letter describes experience using Haskell to solve real-world problems. Such a paper might typically be about six pages, and may be judged by interest of the application and novel use of Haskell. Functional Pearls ----------------- A functional pearl presents - using Haskell as a vehicle - an idea that is small, rounded, and glows with its own light. Such a paper might typically be about six pages, and may be judged by elegance of development and clarity of expression. Submission details ------------------ Deadline for submission: 1st June 2001 Notification of acceptance: 1st July 2001 Final submission due: 1st August 2001 Haskell Workshop: to be announced Authors should submit papers of at most 12 pages, in postscript format, formatted for A4 paper, to Ralf Hinze (ralf@cs.uu.nl) by 1st June 2001. The use of the ENTCS style files is strongly recommended. Application letters and functional pearls should be labeled as such on the first page. They may be any length up to twelve pages, though shorter submissions are welcome. The accepted papers will be published as a University of Utrecht technical report. Programme committee ------------------- Manuel Chakravarty University of New South Wales Jeremy Gibbons University of Oxford Ralf Hinze (chair) University of Utrecht Patrik Jansson Chalmers University Mark Jones Oregon Graduate Institute Ross Paterson City University, London Simon Peyton Jones Microsoft Research Stephanie Weirich Cornell University ============================================================================ From simonpj@microsoft.com Tue Dec 5 17:18:18 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 5 Dec 2000 09:18:18 -0800 Subject: Rank-2 polymorphism & type inference Message-ID: <74096918BE6FD94B9068105F877C002D013781D6@red-pt-02.redmond.corp.microsoft.com> Musing on Zhanyong's problem some more, a solution occurs to me. Curiously, it's exactly the solution required for another useful extension to type classes. Here is is, so people can shoot holes in it. | In more detail, here's what happens. First we typecheck the RHS of | f, deducing the types | | x :: a where a is fresh | y :: k a where k is fresh | y >> return x :: k a | op (y >> return x) :: Bool with constraint C (k a) | \x -> op (y >> return x) :: a -> Bool with constraint C (k a) | | Now we try to generalise over a. We need to discharge the contraint | C (k a). Later we will find that y::[Int], so k=[], but we | don't know that yet. So we can't solve the constraint. One bad solution I thought of was to give f the type f :: forall a. C (k a) => a -> Bool This is bad because it's not the type signature the programmer specified. (It's also bad operationally because we'll pass a dictionary at runtime, which isn't necessary.) The good solution is to say this: \x -> op (y >> return x) :: a -> Bool with constraint C (k a) (just as before) /\a \x -> op (y>>return x) :: forall a. a -> Bool with constraint (forall a. C (k a)) This requires us to permit constraints with for-alls in them. As luck would have it, Ralf Hinze and I propose just such a thing in our paper "Derivable Type Classes" (Section 7) http://research.microsoft.com/~simonpj/#derive The motivation there is this: how can you write an equality instance for data T k a = MkT (k (T k a)) We can try: instance ... => Eq (T k a) where (MkT a) == (MkT b) = a == b But what is the "..."? We need that "k" is an equality type constructor. The right context is instance (forall a. Eq a => Eq (k a)) => Eq (T k a) where ...as before... Aha! A constraint with a for-all. There are some more details in the paper. So perhaps there's a reason for adding this extension in the implementation (to solve Zhanyong's problem) even for a Haskell 98 compiler. Simon From francois.xavier.bodin@winealley.com Wed Dec 6 19:52:00 2000 From: francois.xavier.bodin@winealley.com (francois.xavier.bodin@winealley.com) Date: Wed, 6 Dec 2000 20:52 +0100 Subject: Meet us on Wine Alley Message-ID: <20001206195207.C9A321034@www.haskell.org> Hello! I found your address on a site about wine, food and good living. I thought = that you will be interested by the services that our site offers. www.wine-alley.com is a virtual Club for all those interested in wine in bo= th a professional and personal capacity. We now have more than 3900 members, both amateur and in the trade who use o= ur site to discuss wine, buy and sell it and tell us about the best sources. Club members use the Newsgroup of www.wine-alley.com to exchange informatio= n and experiences. Only the other day someone asked how much a certain rar= e wine was worth, I asked for more information about the grape variety, whi= ch doesn't grow in France. Currently there have been more than 717 question= s and replies. There is also the small ads. column. Among the 7 adverts placed this week there have been some really good deals= including a magnum of 1945 Pichon Lalande and a 1947 Cheval blanc! Let me make it clear - www.wine-alley.com itself does not sell or buy wine:= we simply offer our members the facilites for making their own arrangement= s. www.wine-alley.com is also a site supplying information in real time, parti= cularly the latest news from winegrowers and makers via the French Press Ag= ency (AFP). We also have a database of more than 21,000 wines with informa= tion supplied directly to the site by winegrowers co-operatives and special= ist magazines. I should be delighted if you would come and join us. At www.wine-alley.com= you will find similarly-minded people who just want to share their love of= wine. Kind regards Fran=E7ois Xavier Bodin, Manager of the Online Club fx.bodin@winealley.com PS. Registering with the www.wine-alley.com club is absolutely free and co= mmits you to nothing. If you are not interested in my offer, please excuse this letter; I am sorr= y to have bothered you. To prevent further unwanted intrusions please clic= k on the following link, your email will be automatically removed from our = list. http://www.wine-alley.com/wines/desmail.asp?id=3D307392&l=3Duk From harald@cs.mu.OZ.AU Mon Dec 11 13:13:58 2000 From: harald@cs.mu.OZ.AU (Harald Sondergaard) Date: Tue, 12 Dec 2000 00:13:58 +1100 Subject: PPDP 2001: Call for Papers Message-ID: <200012111314.AAA03065@mundook.cs.mu.OZ.AU> Third International Conference on PRINCIPLES AND PRACTICE OF DECLARATIVE PROGRAMMING Firenze, Italy, 5-7 September 2001 CALL FOR PAPERS PPDP 2001 aims to stimulate research on the use of declarative methods in programming and on the design, implementation and application of programming languages that support such methods. Topics of interest include any aspect related to understanding, integrating and extending programming paradigms such as those for functional, logic, constraint and object-oriented programming; concurrent extensions and mobile computing; type theory; support for modularity; use of logical methods in the design of program development tools; program analysis and verification; abstract interpretation; development of implementation methods; application of the relevant paradigms and associated methods in industry and education. This list is not exhaustive: submissions describing new and interesting ideas relating broadly to declarative programming are encouraged. The technical program of the conference will combine presentations of the accepted papers with invited talks and advanced tutorials. PPDP 2001 is part of a federation of colloquia known as Principles, Logics and Implementations of high-level programming languages (PLI 2001) which includes the ACM SIGPLAN International Conference on Functional Programming (ICFP 2001). The colloquia will run from 2 to 8 September, 2001. The venue for the conference is Firenze (Florence), one of Europe's most attractive cities, famous for its churches, galleries and museums. For more details, see the conference web site. Important Dates: Submission 15 March 2001 Notification 7 May 2001 Final Version 11 June 2001 Affiliated Workshops: Proposals are being solicited for PLI 2001 affiliated workshops. Details about the submission of proposals are available at http://music.dsi.unifi.it/pli01/wkshops. Web Sites and Email Contact: PPDP 2001: http://music.dsi.unifi.it/pli01/ppdp PLI 2001: http://music.dsi.unifi.it/pli01 mailto:ppdp01@cs.mu.oz.au Conference Chair: Rocco De Nicola, Universita di Firenze http://www.dsi.unifi.it/~denicola/ mailto:denicola@dsi.unifi.it Program Chair: Harald Sondergaard, The University of Melbourne http://www.cs.mu.oz.au/~harald/ mailto:harald@cs.mu.oz.au Program Committee: Maria Alpuente, Univ. Politecnica de Valencia, ES Yves Caseau, Bouygues, FR Michael Codish, Ben-Gurion Univ. of the Negev, IL Saumya Debray, Univ. of Arizona, US Conal Elliott, Microsoft Research, US Sandro Etalle, Univ. Maastricht, NL Roberto Giacobazzi, Univ. di Verona, IT Michael Leuschel, Univ. of Southampton, GB John Lloyd, Australian National Univ., AU Torben Mogensen, Kobenhavns Univ., DK Alan Mycroft, Cambridge Univ., GB Gopalan Nadathur, Univ. of Minnesota, US Martin Odersky, Ecole Polyt. Fed. Lausanne, CH Catuscia Palamidessi, Penn State Univ., US Andreas Podelski, Max-Planck-Inst. Informatik, DE Kostis Sagonas, Uppsala Univ., SE Christian Schulte, Univ. des Saarlandes, DE Michael Schwartzbach, Aarhus Univ., DK Harald Sondergaard, Univ. of Melbourne, AU Peter J. Stuckey, Univ. of Melbourne, AU From venneri@dsi.unifi.it Wed Dec 13 20:06:41 2000 From: venneri@dsi.unifi.it (b.venneri) Date: Wed, 13 Dec 2000 16:06:41 -0400 Subject: PLI 2001: call for workshop proposals Message-ID: CALL FOR WORKSHOP PROPOSALS Principles, Logics and Implementations of high-level programming languages (PLI 2001) Firenze, Italy September 3 - 7, 2001 http://music.dsi.unifi.it/pli01 PLI 2001, a federation of colloquia which includes ICFP 2001 (ACM-SIGPLAN International Conference on Functional Programming) and PPDP 2001 (ACM-SIGPLAN International Conference on Principles and Practice of Declarative Programming), will be held in Firenze, Italy, September 3-7 2001. Workshops affiliated to PLI 2001 will be held before, after or in parallel with the main conferences. Researchers and practitioners are invited to submit workshop proposals, that should be sent to the PLI 2001 Workshop Chair Betti Venneri mailto:venneri@dsi.unifi.it with "PLI01 Workshop Submission" in the subject header. Proposals should include * a short scientific justification of the proposed topic (somehow related to the colloquia), * names and contact information of the organizers, * expected number of participants and duration (the preference is for one day-long workshops), * estimated dates for paper submissions, notification of acceptance and final versions and any other relevant information (e.g., invited speakers, publication policy, etc.). THE DEADLINE FOR RECEIPT OF PROPOSALS IS JANUARY 8, 2001. Proposals will be evaluated by the PLI 2001 Workshop Chair, the ICFP and PPDP Program Chairs and Conference Chairs. Notification of acceptance will be made by February 2, 2001. The titles and brief information related to accepted workshop proposals will be included in the conference program and advertised in the call for participation. Workshop organizers will be responsible for producing a Call for papers and a Web site, for reviewing and making acceptance decisions on submitted papers, and for scheduling workshop activities in consultation with the local organizers. Workshop selection committee: Xavier Leroy (INRIA, France), ICFP 2001 Program Chair Benjamin C. Pierce (Univ. of Pennsylvania), ICFP 2001 Conference Chair Harald Sondergaard (Univ. of Melbourne), PPDP 2001 Program Chair Rocco De Nicola (Univ. of Firenze), PPDP 2001 Conference Chair Betti Venneri (Univ. of Firenze), PLI 2001 Workshop Chair. we From shlomif@vipe.technion.ac.il Fri Dec 15 19:47:27 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Fri, 15 Dec 2000 21:47:27 +0200 (IST) Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: Hi! As some of you may know, a Haskell program that prints all the primes can be as short as the following: primes = sieve [2.. ] where sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] Now, this program roughly corresponds to the following perl program: ###### SNIP SNIP ##### #!/usr/bin/perl use strict; my (@primes, $a, $p); @primes = (2); MAIN_LOOP: for($a = 3; $a < 1000; $a++) { foreach $p (@primes) { if ($a % $p == 0) { next MAIN_LOOP; } } push @primes, $a; } print join(", ", @primes); ####### SNIP SNIP ##### The program can be more optimized for both speed and code size, but I wanted to make it as verbose as possible. The algorithm keeps a list of the primes, and for each new number checks if it is divisable by any of them and if not it adds it to the list. There is a different algorithm which keeps a boolean map which tells whether the number at that position is prime or not. At start it is initialized to all trues. The algorithm iterates over all the numbers from 2 to the square root of the desired bound, and if it encounters a prime number it marks all the numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally considered a better algorithm than the previous one, because it uses less costier operations (multiplications and additions instead of modulos.) The perl program that implements that algorithm is this: #### SNIP SNIP ##### #!/usr/bin/perl use strict; sub primes { my $how_much = shift; my (@array, $bound, $a, $b, @primes); @array = (1) x $how_much; $bound = int(sqrt($how_much))+1; for($a=2;$a<=$bound;$a++) { if ($array[$a]) { for($b=$a*$a;$b<$how_much;$b+=$a) { $array[$b] = 0; } push @primes, $a; } } for(;$a<$how_much;$a++) { if ($array[$a]) { push @primes, $a; } } return @primes; } print join(", ", primes(1000)); ##### SNIP SNIP ###### Now, I tried writing an equivalent Haskell program and the best I could do was the following: ---- SNIP SNIP ----- module Primes where import Prelude import Array how_much :: Int how_much = 1000 initial_primes_map :: Array Int Bool initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ] mybound :: Int mybound = ceiling(sqrt(fromInteger(toInteger(how_much)))) next_primes_map :: Int -> Array Int Bool -> Array Int Bool next_primes_map a primes_map = if (a == mybound) then primes_map else next_primes_map (a+1) ( if primes_map!a then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ] else primes_map ) prime_bound :: Int -> Int prime_bound a = (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a)))) get_primes_map :: Array Int Bool get_primes_map = (next_primes_map 2 initial_primes_map) list_primes :: Array Int Bool -> Int -> [Int] list_primes primes_map n = if (n > how_much) then [] else ( if primes_map!n then n:(list_primes primes_map (n+1)) else list_primes primes_map (n+1) ) show_primes = show (list_primes get_primes_map 2) ---- SNIP SNIP ----- The problem is that when running it on hugs98 on a Windows98 computer with 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When entering how_much as 50,000 I get the following message: ERROR: Garbage collection fails to reclaim sufficient space In perl I can scale beyond 100,000, and if I modify the code to use a bit vector (using vec) to much more. So my question is what am I or hugs are doing wrong and how I can write better code that implements this specific algorithm. >From what I saw I used tail recursion, (and hugs98 has proper tail recursion, right?), and there's only one primes_map present at each iteration (and thus, at all), so it shouldn't be too problematic. Does it have to do with the way hugs98 implements and Int to Bool array? Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From jenglish@flightlab.com Sat Dec 16 23:21:48 2000 From: jenglish@flightlab.com (Joe English) Date: Sat, 16 Dec 2000 15:21:48 -0800 Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: References: Message-ID: <200012162321.PAA00918@dragon.flightlab.com> Shlomi Fish wrote: > As some of you may know, a Haskell program that prints all the primes can be > as short as the following: > > primes = sieve [2.. ] where > sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] > > Now, this program roughly corresponds to the following perl program: [ ~20 line Perl program snipped ] > The program can be more optimized for both speed and code size, but I wanted > to make it as verbose as possible. > > There is a different algorithm which keeps a boolean map [...] > The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. [~40 line Perl implementation snipped] > Now, I tried writing an equivalent Haskell program and the best I > could do was the following: [ ~45 line Haskell implementation snipped ] Another way to do this is to compute the final array directly, instead of computing successive versions of the array: import Array primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where primesMap = accumArray (||) False (2,n) multList multList = [(m,True) | j <- [2 .. n `div` 2], m <- multiples j] multiples j = takeWhile (n>=) [k*j | k <- [2..]] Now this version does a lot more work than the algorithm described above -- it computes multiples of *all* the integers less than n/2, not just the primes less than sqrt(n) -- but it has the virtue of being short enough to reason about effectively and is probably a better starting point for further optimization. > The problem is that when running it on hugs98 on a Windows98 computer with > 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When > entering how_much as 50,000 I get the following message: > > ERROR: Garbage collection fails to reclaim sufficient space My implementation fares even worse under Hugs -- it runs out of space around n = 4500 (Linux box, 64M RAM). With GHC it has no problem for n = 100,000, although the space usage is still extremely poor. It grows to consume all available RAM at around n = 200,000. (On the other hand, it's considerably faster than the traditional 2-liner listed above, up to the point where it starts paging). I suspect the poor memory usage is due to the way accumArray works -- it's building up a huge array of suspensions of the form (False && (False && ( ... && True))) that aren't reduced until an array element is requested. (A strict version of accumArray, analogous to "foldl_strict" defined below, would solve this problem, but I don't see any way to implement it in Standard Haskell). > In perl I can scale beyond 100,000, and if I modify the code to use a bit > vector (using vec) to much more. So my question is what am I or hugs are > doing wrong and how I can write better code that implements this specific > algorithm. > > From what I saw I used tail recursion, (and hugs98 has proper tail recursion > right?), and there's only one primes_map present at each iteration (and thus, > at all), so it shouldn't be too problematic. Actually no; this is a common misconception. In a strict language like Scheme, tail call optimization works because a tail call is the last thing a function does. In Haskell though the tail call is the *first* thing that gets evaluated (more or less), leaving all the "earlier" work as an unevaluated suspension. Code that is space-efficient in a strict language frequently suffers from awful space leaks in a lazy language. For example: sum_first_n_integers n = f n 0 where f 0 a = a f n a = f (n-1) (n+a) quickly leads to a "Control Stack Overflow" error in Hugs. BTW, the trick to fix it is to change the last line to: f n acc = f (n-1) $! (n+acc) or to replace the whole thing with: foldl_strict (+) 0 [1..n] where foldl_strict f a [] = a foldl_strict f a (x:xs) = (foldl_strict f $! f a x) xs > Does it have to do with the way hugs98 implements and Int to Bool array? Most likely yes. Hugs is optimized for interactive use and quick compilation, not for space usage. Try it with GHC or HBC and see how it does. --Joe English jenglish@flightlab.com From ahey@iee.org Sun Dec 17 11:59:43 2000 From: ahey@iee.org (Adrian Hey) Date: Sun, 17 Dec 2000 11:59:43 +0000 (GMT) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: On Fri 15 Dec, Shlomi Fish wrote: > There is a different algorithm which keeps a boolean map which tells whether > the number at that position is prime or not. At start it is initialized to all > trues. The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally > considered a better algorithm than the previous one, because it uses less > costier operations (multiplications and additions instead of modulos.) Functional programming languages are notoriously ineffecient at array handling (though I'm not sure exactly what the various Haskell implementations actually do). You can use a variation of this algorithm with lazy lists.. primes = 2:(get_primes [3,5..]) get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs)) strike step x_now (x:xs) = case (compare x_now x) of LT -> strike step (x_now+step) (x:xs) EQ -> strike step (x_now+step) xs GT -> x:(strike step x_now xs) The equivalent program in Clean (on a MAC) gets upto 877783 before giving a stack overflow error (1000K of stack, 4000K of Heap allocated). (I haven't actually tried this in Haskell 'cos I don't have a Windoze or 'nix box.) Regards -- Adrian Hey From qrczak@knm.org.pl Sun Dec 17 19:29:32 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 17 Dec 2000 19:29:32 GMT Subject: Problem with functional dependencies Message-ID: The following module is rejected by both ghc -fglasgow-exts -fallow-undecidable-instances and hugs -98 ------------------------------------------------------------------------ class HasFoo a foo | a -> foo where foo :: a -> foo data A = A Int data B = B A instance HasFoo A Int where foo (A x) = x instance HasFoo A foo => HasFoo B foo where foo (B a) = foo a ------------------------------------------------------------------------ The error messsage says that the type inferred for foo in B's instance is not general enough: the rhs has type "HasFoo B Int => B -> Int", but "HasFoo B foo => B -> foo" was expected. Should it really be wrong? I don't know the details of type inference with fundeps, but intuitively it should work, yielding an instance HasFoo B Int. Could it be made legal please? With the fundep removed, it works. I need it for a preprocessor which generates instances like that for B without knowing the type to put as the second class argument. Fundeps aren't essential, but... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From elke.kasimir@catmint.de Sun Dec 17 18:56:46 2000 From: elke.kasimir@catmint.de (Elke Kasimir) Date: Sun, 17 Dec 2000 19:56:46 +0100 (CET) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: This message is in MIME format --_=XFMail.1.3.p0.Linux:001217195636:327=_ Content-Type: text/plain; charset=iso-8859-1 Your algorithm seems to be based on the following idea: calculate the non-primes and derive the primes from them by calculating the set difference of the natural numbers and the non-primes. A naive implementation of this idea can be found as primes' in the attachached file. The function uses no multiplication or division and though performs 6 times worse than the sieve in calculating the first 30000 primes. The complexity for finding the next i'th prime with this naive implementation is about O(i). In comparison to this, the sieve provides a good optimization because only those natural numbers are tested against the i'th prime which have run through all other sieves. Nevertheless, your algorithm is promising when the non-primes are merged efficiently enough into a single sorted list which can be easily subtracted from the natural numbers. I think the deployment of an array is basically a way to efficiently merge the multiples of the primaries into a sorted list (where even duplicates are removed), thus hoping to reduce the number of the operations better than the optimization that is provided by the sieve. However, to use arrays this way, you probably need destructive array updates, because the array must be incrementally updated when new primes are found. I think that standard haskell arrays don't do the job very well. An implementation of the "merging" idea in Haskell is primes'' in the attached file. It is 15% faster then the sieve in calculating the 30000 first primes. The algorithm is realized as two mutually recursive functions noprimes and primes'', the latter calculating the set difference between the non-primes and the natural numbers, the former merging the all multiples of all primes into a sorted list. It should be possible to substantially optimize the merging operation. primes''' is an efficient variant of primes'. Instead of a list it uses a binary tree for the management of the lists of multiples of the already found primes, and thus requires some additional programming effort. The complexity is reduced from O(i) to something like O(Log(i)). Compared with the sieve, primes''' needs only half the time to calculate the first 30000 primes. (Tests with ghc 4.08, 64m heap) Best, Elke. On 15-Dec-00 Shlomi Fish wrote: > > Hi! > > As some of you may know, a Haskell program that prints all the primes can be > as short as the following: > > primes = sieve [2.. ] where > sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ] > > Now, this program roughly corresponds to the following perl program: > >###### SNIP SNIP ##### >#!/usr/bin/perl > > use strict; > > my (@primes, $a, $p); > @primes = (2); > MAIN_LOOP: > for($a = 3; $a < 1000; $a++) > { > foreach $p (@primes) > { > if ($a % $p == 0) > { > next MAIN_LOOP; > } > } > push @primes, $a; > } > print join(", ", @primes); >####### SNIP SNIP ##### > > The program can be more optimized for both speed and code size, but I wanted > to make it as verbose as possible. > > The algorithm keeps a list of the primes, and for each new number checks if > it > is divisable by any of them and if not it adds it to the list. > > There is a different algorithm which keeps a boolean map which tells whether > the number at that position is prime or not. At start it is initialized to > all > trues. The algorithm iterates over all the numbers from 2 to the square root > of the desired bound, and if it encounters a prime number it marks all the > numbers p*p, p*p+p, p*p+2*p, p*p+3*p, etc. as not prime. It is generally > considered a better algorithm than the previous one, because it uses less > costier operations (multiplications and additions instead of modulos.) > > The perl program that implements that algorithm is this: > >#### SNIP SNIP ##### >#!/usr/bin/perl > > use strict; > > sub primes > { > my $how_much = shift; > > my (@array, $bound, $a, $b, @primes); > > @array = (1) x $how_much; > > $bound = int(sqrt($how_much))+1; > > for($a=2;$a<=$bound;$a++) > { > if ($array[$a]) > { > for($b=$a*$a;$b<$how_much;$b+=$a) > { > $array[$b] = 0; > } > push @primes, $a; > } > } > for(;$a<$how_much;$a++) > { > if ($array[$a]) > { > push @primes, $a; > } > } > > return @primes; > } > > print join(", ", primes(1000)); >##### SNIP SNIP ###### > > Now, I tried writing an equivalent Haskell program and the best I could do > was > the following: > > ---- SNIP SNIP ----- > module Primes where > > import Prelude > import Array > > how_much :: Int > how_much = 1000 > > initial_primes_map :: Array Int Bool > initial_primes_map = array (1, how_much) [ (i,True) | i <- [1 .. how_much] ] > > mybound :: Int > mybound = ceiling(sqrt(fromInteger(toInteger(how_much)))) > > next_primes_map :: Int -> Array Int Bool -> Array Int Bool > next_primes_map a primes_map = > if (a == mybound) > then primes_map > else next_primes_map (a+1) ( > if primes_map!a > then primes_map // [ (i*a, False) | i <- [a .. (prime_bound a)] ] > else primes_map > ) > > prime_bound :: Int -> Int > prime_bound a = > (floor(fromInteger(toInteger(how_much))/fromInteger(toInteger(a)))) > > get_primes_map :: Array Int Bool > get_primes_map = (next_primes_map 2 initial_primes_map) > > list_primes :: Array Int Bool -> Int -> [Int] > list_primes primes_map n = > if (n > how_much) > then [] > else > ( > if primes_map!n > then n:(list_primes primes_map (n+1)) > else list_primes primes_map (n+1) > ) > > show_primes = show (list_primes get_primes_map 2) > ---- SNIP SNIP ----- > > > The problem is that when running it on hugs98 on a Windows98 computer with > 64MB of RAM, I cannot seem to scale beyond 30,000 or so, as my boundary. When > entering how_much as 50,000 I get the following message: > > ERROR: Garbage collection fails to reclaim sufficient space > > In perl I can scale beyond 100,000, and if I modify the code to use a bit > vector (using vec) to much more. So my question is what am I or hugs are > doing > wrong and how I can write better code that implements this specific > algorithm. > >>From what I saw I used tail recursion, (and hugs98 has proper tail recursion, > right?), and there's only one primes_map present at each iteration (and thus, > at all), so it shouldn't be too problematic. Does it have to do with the way > hugs98 implements and Int to Bool array? > > Regards, > > Shlomi Fish > > ---------------------------------------------------------------------- > Shlomi Fish shlomif@vipe.technion.ac.il > Home Page: http://t2.technion.ac.il/~shlomif/ > Home E-mail: shlomif@techie.com > > The prefix "God Said" has the extraordinary logical property of > converting any statement that follows it into a true one. > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell --- Elke Kasimir Skalitzer Str. 79 10997 Berlin (Germany) fon: +49 (030) 612 852 16 mail: elke.kasimir@catmint.de> see: for pgp public key see: --_=XFMail.1.3.p0.Linux:001217195636:327=_ Content-Disposition: attachment; filename="Primes.hs" Content-Transfer-Encoding: base64 Content-Description: Primes.hs Content-Type: application/octet-stream; name=Primes.hs; SizeOnDisk=3056 bW9kdWxlIFByaW1lcwp3aGVyZQoKaW1wb3J0IExpc3QKCi0tIDEuIHZlcnNpb24sIHNpZXZlCgpw cmltZXMgCiAgICA9IHNpZXZlIFsyLi5dIAogICAgICAgd2hlcmUgc2lldmUgKHg6eHMpID0geCA6 IHNpZXZlIFsgbiB8IG4gPC0geHMgLCBuIGBtb2RgIHggPiAwIF0gCgoKLS0gMi4gdmVyc2lvbjog a2VlcCBhbiAidXB0by1kYXRlIiBsaXN0IG9mIHRoZSBub24tcHJpbWVzIAotLSAgICAgICAgICAg ICAoYSBmaW5pdGUgbGlzdCBvZiBpbmlmaW5pdGUgbGlzdHMpCi0tICAgICAgICAgICAgIGFuZCBj YWxjdWxhdGUgdGhlIHByaW1lcyBmcm9tIHRoZW0uCgpwcmltZXMnCiAgICA9IG1rUHJpbWVzIFtd IFsyLi5dIAogICAgICB3aGVyZQogICAgICAgbWtQcmltZXMgbm9uX3ByaW1lcyAoeDp4cykgCgkg ICB8IG51bGwgd2l0aFggPSB4IDogbWtQcmltZXMgKG11bHQgeCA6IG5vbl9wcmltZXMpICAgICAg ICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChtYXAgdGFpbCB3aXRoWCArKyB3 aXRob3V0WCkgeHMKCSAgIHdoZXJlCgkgICAod2l0aFgsd2l0aG91dFgpID0gcGFydGl0aW9uICgo PT14KS4gaGVhZCkgbm9uX3ByaW1lcwoJICAgbXVsdCB4ICAgICAgICAgICA9IGl0ZXJhdGUgKCt4 KSAoeCt4KQoKCi0tIDMuIHZlcnNpb246IHByaW1lcyBhbmQgbm9uLXByaW1lcyBhcmUgbXV0dWFs bHkgcmVjdXJzaXZlLgoKcHJpbWVzJycKICAgID0gMiA6IGRpZmYgWzMuLl0gbm9uX3ByaW1lcwoK bm9uX3ByaW1lcyAKICAgID0gbWVyZ2UgKG1hcCBtdWx0IHByaW1lcycnKSAKICAgICAgd2hlcmUg CiAgICAgIG11bHQgeCAgID0gaXRlcmF0ZSAoK3gpICh4K3gpICAgICAgCgptZXJnZSAoKHg6eHMp OnJlc3QpCiAgICA9IHggOiBtZXJnZSAocmVhcnJhbmdlICh4czpyZXN0KSkKCnJlYXJyYW5nZSBs QCh4bEAoeDp4cyk6KHk6eXMpOnJlc3QpIAogICAgfCB4IDw9IHkgICAgID0gbAogICAgfCBvdGhl cndpc2UgID0gKHk6eGwpIDogcmVhcnJhbmdlICh5czpyZXN0KSAKCi0tIHNldCBkaWZmZXJlbmNl IGZvciBvcmRlcmVkIGxpc3RzIC0gcmVzdWx0IGlzIGFsc28gb3JkZXJlZDoKZGlmZiA6OiBPcmQg YSA9PiBbYV0gLT4gW2FdIC0+IFthXQpkaWZmIHhsQCh4OnhzKSB5bEAoeTp5cykgCiAgICB8IHgg PCAgeSA9IHggOiBkaWZmIHhzIHlsCiAgICB8IHggPT0geSA9ICAgICBkaWZmIHhzIHlsCiAgICB8 IHggPiAgeSA9ICAgICBkaWZmIHhsIHlzCgoKLS0gNC4gdmVyc2lvbiwgbGlrZSAyLiwgYnV0IHVz ZXMgYSB0cmVlIHRvIG1hbmFnZSBub24tcHJpbXNlOgoKcHJpbWVzJycnCiAgICA9IG1rUHJpbWVz IEwgWzIuLl0gCiAgICAgIHdoZXJlCiAgICAgICBta1ByaW1lcyBub25fcHJpbWVzICh4OnhzKSAK CSAgIHwgbnVsbCB3aXRoWCA9IHggOiBta1ByaW1lcyAodGluc2VydCAobXVsdCB4KSBub25fcHJp bWVzKSAgICAgICAgICAgICB4cwoJICAgfCBvdGhlcndpc2UgID0gICAgIG1rUHJpbWVzIChmb2xk ciB0aW5zZXJ0IHdpdGhvdXRYIChtYXAgdGFpbCB3aXRoWCkpIHhzCgkgICB3aGVyZQoJICAgKHdp dGhYLHdpdGhvdXRYKSA9IHRwYXJ0aXRpb24gW3hdIG5vbl9wcmltZXMgCgkgICBtdWx0IHggICAg ICAgICAgID0gaXRlcmF0ZSAoK3gpICh4K3gpCgotLSBhIGJpbmFyeSB0cmVlOgoKZGF0YSBUcmVl ID0gTiBbSW50ZWdlcl0gVHJlZSBUcmVlIHwgTCBkZXJpdmluZyBTaG93CgotLSBydWxlcyBmb3Ig cGxhY2luZyBpbnRlZ2VyIGxpc3RzOgoKbGVmdG9mLCByaWdodG9mIDo6IFtJbnRlZ2VyXSAtPiBU cmVlIC0+IEJvb2wKCmxlZnRvZiAgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA8PSB5CnJpZ2h0 b2YgKHg6eHMpIChOICh5OnlzKSBfIF8pID0geCA+IHkKCi0tIHJ1bGUgZm9yIG1hdGNoaW5nIGlu dGVnZXIgbGlzdHM6CgptYXRjaGVzIDo6IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IEJvb2wKbWF0Y2hl cyAoeDp4cykgKE4gKHk6eXMpIF8gXykgPSB4ID09IHkKCi0tIGluc2VydGlvbjoKCnRpbnNlcnQg OjogW0ludGVnZXJdIC0+IFRyZWUgLT4gVHJlZQp0aW5zZXJ0IHhsICAgTCA9IE4geGwgTCBMCnRp bnNlcnQgeGwgdEAoTiB5bCB0MSB0MikgCiAgICB8IHhsIGBsZWZ0b2ZgICB0ID0gTiB5bCAodGlu c2VydCB4bCB0MSkgdDIKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgPSBOIHlsIHQxICh0aW5zZXJ0IHhs IHQyKQoKLS0gZXh0cmFjdGlvbiAmIHJlbW92YWwgaW4gb25lIHN0ZXA6Cgp0cGFydGl0aW9uIDo6 IFtJbnRlZ2VyXSAtPiBUcmVlIC0+IChbW0ludGVnZXJdXSxUcmVlKQp0cGFydGl0aW9uIHhsIEwg PSAoW10sTCkKdHBhcnRpdGlvbiB4bCB0QChOIHlsIHQxIHQyKSAKICAgIHwgeGwgYG1hdGNoZXNg IHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24nIHhsIHQxIGluICh5bDphLCByZW1vdmUgYiB0 MikKICAgIHwgeGwgYGxlZnRvZmAgIHQgID0gIGxldCAoYSxiKSA9IHRwYXJ0aXRpb24geGwgdDEg aW4gKGEsIE4geWwgYiB0MikKICAgIHwgeGwgYHJpZ2h0b2ZgIHQgID0gIGxldCAoYSxiKSA9IHRw YXJ0aXRpb24geGwgdDIgaW4gKGEsIE4geWwgdDEgYikKCnRwYXJ0aXRpb24nIHhsIEwgPSAoW10s TCkgICAgICAtLSBjaGVjayBmb3IgbW9yZSBtYXRjaGVzCnRwYXJ0aXRpb24nIHhsIHRAKE4geWwg dDEgdDIpIAogICAgfCB4bCBgbWF0Y2hlc2AgdCAgPSAgbGV0IChhLGIpID0gdHBhcnRpdGlvbicg eGwgdDEgaW4gKHlsOmEsIHJlbW92ZSBiIHQyKQogICAgfCBvdGhlcndpc2UgICAgICAgPSAoW10s dCkKCnJlbW92ZSBMICB0MiAgPSB0MgpyZW1vdmUgdDEgdDIgPSBsZXQgKGEsYikgPSByaWdodG1v c3QgdDEgaW4gTiBhIGIgdDIKCnJpZ2h0bW9zdCAoTiB5bCB0MSAgTCkgPSAoeWwsdDEpCnJpZ2h0 bW9zdCAoTiB5bCB0MSB0MikgPSBsZXQgKGEsYik9cmlnaHRtb3N0IHQyIGluIChhLCBOIHlsIHQx IGIpCiAgCgotLSB0ZXN0IGNvcnJlY3RuZXNzCgpwZGlmZiA9IFsgKGEsYixjLGQpIHwgCgkgKGEs YixjLGQpPC16aXA0IHByaW1lcyBwcmltZXMnIHByaW1lcycnIHByaW1lcycnJywgCgkgYSAvPSBi IHx8IGIgLz0gYyB8fCBjIC89IGQgCgkgXQoKCgoKCgoKCgo= --_=XFMail.1.3.p0.Linux:001217195636:327=_-- End of MIME message From ahey@iee.org Mon Dec 18 00:24:12 2000 From: ahey@iee.org (Adrian Hey) Date: Mon, 18 Dec 2000 00:24:12 +0000 (GMT) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: Message-ID: On Sun 17 Dec, Adrian Hey wrote: > You can use a variation of this algorithm with lazy lists.. > > primes = 2:(get_primes [3,5..]) > get_primes (x:xs) = x:(get_primes (strike (x+x) (x*x) xs)) ^^^ Whoops,_____________________________________________| 32 bit Ints may cause trouble here :-) Regards -- Adrian Hey From Xavier.Leroy@inria.fr Mon Dec 18 09:30:07 2000 From: Xavier.Leroy@inria.fr (Xavier Leroy) Date: Mon, 18 Dec 2000 10:30:07 +0100 Subject: call for papers ICFP 2001 Message-ID: <20001218103007.B32378@pauillac.inria.fr> ICFP 2001: Call for Papers ICFP 2001: International Conference on Functional Programming Firenze (Florence), Italy; 3-5 September 2001 associated with PLI 2001: Colloquium on Principles, Logics, and Implementations of High-Level Programming Languages Important dates: Submission deadline 15 March 2001, 18:00 UTC Notification of acceptance or rejection 11 May 2001 Final paper due 29 June 2001 Conference 3-5 September 2001 Scope: ICFP 2001 seeks original papers on the full spectrum of the art, science, and practice of functional programming. The conference invites submissions on all topics ranging from principles to practice, from foundations to features, and from abstraction to application. The scope covers all languages that encourage programming with functions, including both purely applicative and imperative languages, as well as languages that support objects and concurrency. Papers setting new directions in functional programming, or describing novel or exemplary applications of functional programming, are particularly encouraged. Topics of interest include, but are not limited to, the following: * Foundations: formal semantics, lambda calculus, type theory, monads, continuations, control, state, effects. * Design: modules and type systems, concurrency and distribution, components and composition, relations to object-oriented and logic programming, multiparadigm programming. * Implementation: abstract machines, compile-time and run-time optimization, just-in-time compilers, memory management, foreign-function and component interfaces. * Transformation and Analysis: abstract interpretation, partial evaluation, program transformation, theorem proving, specification and verification. * Applications: scientific and numerical computing, symbolic computing and artificial intelligence, systems programming, databases, graphic user interfaces, multimedia programming, web programming. * Experience: FP in education and industry, ramifications on other paradigms and computing disciplines. * Functional pearls: elegant, instructive examples of functional programming. Submission guidelines: Please refer to the submission Web site http://cristal.inria.fr/ICFP2001/ Program committee: General chair Program committee Benjamin Pierce Karl Crary, Carnegie Mellon University University of Pennsylvania Marc Feeley, University of Montréal Giorgio Ghelli, University of Pisa Program chair Simon Peyton Jones, Microsoft Research John Hughes, Chalmers University Xavier Leroy Naoki Kobayashi, University of Tokyo INRIA Rocquencourt Julia Lawall, DIKU, U. Copenhagen Domaine de Voluceau, B.P. 105 Sheng Liang, Stratum8 78153 Le Chesnay, France John Reppy, Bell Labs, Lucent Technologies E-mail: Xavier.Leroy@inria.fr Scott Smith, John Hopkins University Fax: + 33 - 1 - 39 63 56 84 Carolyn Talcott, Stanford University Phone: + 33 - 1 - 39 63 55 61 Kwangkeun Yi, KAIST From sebastien@posse42.net Tue Dec 19 14:15:16 2000 From: sebastien@posse42.net (Sebastien Carlier) Date: Tue, 19 Dec 2000 15:15:16 +0100 Subject: Excessive restriction in ghc ? Message-ID: <006401c069c6$1cdc13c0$d701a8c0@air> Hello. I am getting an error message from ghc 4.08.1 with the following code: > class Collection e ce | ce -> e where > empty :: ce > insert :: e -> ce -> ce > > class (Eq e, Collection e ce) => Set e ce where > member :: e -> ce -> Bool > union :: ce -> ce -> ce Main.lhs:7: Class type variable `e' does not appear in method signature union :: {- implicit forall -} ce -> ce -> ce Since `ce' uniquely determines `e', I would expect the compiler to assume that `e' appears in the method signature. Either I am misunderstanding something, or something may be missing in the compiler around rename/RnSource.lhs:249. Regards, Sebastien Carlier From zhanyong.wan@yale.edu Tue Dec 19 15:43:28 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Tue, 19 Dec 2000 10:43:28 -0500 Subject: Excessive restriction in ghc ? References: <006401c069c6$1cdc13c0$d701a8c0@air> Message-ID: <3A3F8220.3FED720E@yale.edu> Hi Sebastien, Sebastien Carlier wrote: > I am getting an error message from ghc 4.08.1 with > the following code: > > > class Collection e ce | ce -> e where > > empty :: ce > > insert :: e -> ce -> ce > > > > class (Eq e, Collection e ce) => Set e ce where > > member :: e -> ce -> Bool > > union :: ce -> ce -> ce > > Main.lhs:7: > Class type variable `e' does not appear in method signature > union :: {- implicit forall -} ce -> ce -> ce > > Since `ce' uniquely determines `e', I would expect the > compiler to assume that `e' appears in the method signature. > Either I am misunderstanding something, or something may be > missing in the compiler around rename/RnSource.lhs:249. I encountered the same problem this summer and wrote to Simon PJ and Jeff Lewis. Here's Jeff's answer: > I'm glad to find examples where they are indispensible. The implementation of > FDs in GHC is pretty much complete WRT Mark's writeup (but it doesn't complain > about instances inconsistent with FDs). I'm using them in a current project, > but in a fairly conservative manner. In hugs, I implemented several > extensions to do with derived instances and superclasses - pretty much > necessary as you've found. Unfortunately, in hugs I implemented it in rather > the wrong way. Based on dicsussions at the Hugs/GHC meeting w/ Simon, I have > a cunning plan for finishing the implementation properly in GHC, but just > haven't had the chance to do it. What I need to do is write it up, so that > either Simon or myself can finish the job. So the short answer to your question is: FD in derived instances is not implemented in GHC yet. I'm still eagerly waiting to use this feature in my project. Jeff, could you give us an update on the progress? Thanks! -- # Zhanyong Wan http://pantheon.yale.edu/~zw23/ ____ # Yale University, Dept of Computer Science /\___\ # P.O.Box 208285, New Haven, CT 06520-8285 ||___| From mk167280@zodiac.mimuw.edu.pl Tue Dec 19 15:56:40 2000 From: mk167280@zodiac.mimuw.edu.pl (Marcin Kowalczyk) Date: Tue, 19 Dec 2000 16:56:40 +0100 Subject: Excessive restriction in ghc ? In-Reply-To: <006401c069c6$1cdc13c0$d701a8c0@air>; from sebastien@posse42.net on Tue, Dec 19, 2000 at 03:15:16PM +0100 References: <006401c069c6$1cdc13c0$d701a8c0@air> Message-ID: <20001219165640.A9716@zodiac.mimuw.edu.pl> On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote: > > class Collection e ce | ce -> e where > > empty :: ce > > insert :: e -> ce -> ce > > > > class (Eq e, Collection e ce) => Set e ce where Doesn't adding the fundep to Set's definition as well help? -- Marcin 'Qrczak' Kowalczyk From zhanyong.wan@yale.edu Tue Dec 19 16:04:31 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Tue, 19 Dec 2000 11:04:31 -0500 Subject: Excessive restriction in ghc ? References: <006401c069c6$1cdc13c0$d701a8c0@air> <20001219165640.A9716@zodiac.mimuw.edu.pl> Message-ID: <3A3F870F.10CA4BD8@yale.edu> Marcin Kowalczyk wrote: > > On Tue, Dec 19, 2000 at 03:15:16PM +0100, Sebastien Carlier wrote: > > > > class Collection e ce | ce -> e where > > > empty :: ce > > > insert :: e -> ce -> ce > > > > > > class (Eq e, Collection e ce) => Set e ce where > > Doesn't adding the fundep to Set's definition as well help? It might help in this particular case, but if we want something like class Collection e ce => Foo ce where ... then your trick does not apply, and I indeed need something like the above in my project. -- Zhanyong Wan From simonpj@microsoft.com Tue Dec 19 14:47:41 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 19 Dec 2000 06:47:41 -0800 Subject: Excessive restriction in ghc ? Message-ID: <74096918BE6FD94B9068105F877C002D0137839A@red-pt-02.redmond.corp.microsoft.com> Functional dependencies aren't fully implemented in 4.08 I'm afraid, and won't ever be. It'll be significantly better in 5.0, but we won't release that for a while yet. (Unless you care to build from the CVS tree.) Simon | -----Original Message----- | From: Sebastien Carlier [mailto:sebastien@posse42.net] | Sent: 19 December 2000 14:15 | To: haskell@haskell.org | Subject: Excessive restriction in ghc ? | | | Hello. | | I am getting an error message from ghc 4.08.1 with | the following code: | | > class Collection e ce | ce -> e where | > empty :: ce | > insert :: e -> ce -> ce | > | > class (Eq e, Collection e ce) => Set e ce where | > member :: e -> ce -> Bool | > union :: ce -> ce -> ce | | Main.lhs:7: | Class type variable `e' does not appear in method signature | union :: {- implicit forall -} ce -> ce -> ce | | Since `ce' uniquely determines `e', I would expect the | compiler to assume that `e' appears in the method signature. | Either I am misunderstanding something, or something may be | missing in the compiler around rename/RnSource.lhs:249. | | Regards, | Sebastien Carlier | | | | _______________________________________________ | Haskell mailing list | Haskell@haskell.org | http://www.haskell.org/mailman/listinfo/haskell | From simonpj@microsoft.com Tue Dec 19 14:58:41 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Tue, 19 Dec 2000 06:58:41 -0800 Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: <74096918BE6FD94B9068105F877C002D0137839D@red-pt-02.redmond.corp.microsoft.com> | Another way to do this is to compute the final array directly, | instead of computing successive versions of the array: | | import Array | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where | primesMap = accumArray (||) False (2,n) multList | multList = [(m,True) | j <- [2 .. n `div` 2], m <- | multiples j] | multiples j = takeWhile (n>=) [k*j | k <- [2..]] This style is definitely the way to go. Haskell does badly if you update an array one index at a time. Remember that arrays can be recursive. Here's a definition of Fibonacci for example; you can probably adapt it for primes fibs :: Int -> Array Int Int -- If a = fibs n, then a!i is fib(i), for i<=n. fibs n = a where a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <- [3..n]]) -- Notice that a is recursive Simon From shlomif@vipe.technion.ac.il Wed Dec 20 14:02:23 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Wed, 20 Dec 2000 16:02:23 +0200 (IST) Subject: Finding primes using a primes map with Haskell and Hugs98 In-Reply-To: <74096918BE6FD94B9068105F877C002D0137839D@red-pt-02.redmond.corp.microsoft.com> Message-ID: On Tue, 19 Dec 2000, Simon Peyton-Jones wrote: > | Another way to do this is to compute the final array directly, > | instead of computing successive versions of the array: > | > | import Array > | primes n = [ i | i <- [2 ..n], not (primesMap ! i)] where > | primesMap = accumArray (||) False (2,n) multList > | multList = [(m,True) | j <- [2 .. n `div` 2], m <- > | multiples j] > | multiples j = takeWhile (n>=) [k*j | k <- [2..]] > > This style is definitely the way to go. Haskell does badly > if you update an array one index at a time. > Unfortunately, it seems that this style is not the way to go. This program cannot scale beyond 5000 while my second program scales beyond 30000. I'm not saying 30000 is a good limit, but 5000 is much worse. Anyway, somebody who contacted me in private suggested the following method. It is a similiar algorithm which uses a list instead of an array. primes :: Int -> [Int] primes how_much = sieve [2..how_much] where sieve (p:x) = p : (if p <= mybound then sieve (remove (p*p) x) else x) where remove what (a:as) | what > how_much = (a:as) | a < what = a:(remove what as) | a == what = (remove (what+step) as) | a > what = a:(remove (what+step) as) remove what [] = [] step = (if (p == 2) then p else (2*p)) sieve [] = [] mybound = ceiling(sqrt(fromIntegral how_much)) I optimized it quite a bit, but the concept remained the same. Anyway, this code can scale very well to 100000 and beyond. But it's not exactly the same algorithm. I also implemented this algorithm in perl, and I can send it in person if anybody requests it. I'll try to see how the two programs run in GHC and HBC. Regards, Shlomi Fish > Remember that arrays can be recursive. Here's a definition > of Fibonacci for example; you can probably adapt it for primes > > fibs :: Int -> Array Int Int > -- If a = fibs n, then a!i is fib(i), for i<=n. > fibs n = a > where > a = array (1,n) ([(1,1),(2,1)] ++ [(i,a!(i-1) + a!(i-2) | i <- > [3..n]]) > -- Notice that a is recursive > > Simon > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From ger@tzi.de Wed Dec 20 14:12:46 2000 From: ger@tzi.de (George Russell) Date: Wed, 20 Dec 2000 15:12:46 +0100 Subject: Finding primes using a primes map with Haskell and Hugs98 References: Message-ID: <3A40BE5E.13D8D959@tzi.de> There are numerous ways of optimising sieving for primes, none of which have much to do with this list. For example, two suggestions: (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise sieve separately for this k on higher primes. (Or you might use products of more or less primes, depending on memory and how high you were going.) (2) use bitwise arithmetic. If you look in the literature I think you'll find plenty more possibilities. I don't really see why any of this has anything to do with Haskell though. When it comes to seriously icky bit-twiddling algorithms I don't think Haskell has much to offer over C, especially as you'd have to make everything unboxed if you want comparable speed. From Colin.Runciman@cs.york.ac.uk Wed Dec 20 14:49:30 2000 From: Colin.Runciman@cs.york.ac.uk (Colin.Runciman@cs.york.ac.uk) Date: Wed, 20 Dec 2000 14:49:30 GMT Subject: Finding primes using a primes map with Haskell and Hugs98 Message-ID: <200012201449.OAA01102@pc179.cs.york.ac.uk> > There are numerous ways of optimising sieving for primes, none of which > have much to do with this list. For example, two suggestions: > (1) for each k modulo 2*3*5*7, if k is divisible by 2/3/5 or 7, ignore, otherwise > sieve separately for this k on higher primes. (Or you might use products of > more or less primes, depending on memory and how high you were going.) > ... > I don't really see why any of this has anything to do with Haskell though. > When it comes to seriously icky bit-twiddling algorithms I don't think Haskell > has much to offer over C, especially as you'd have to make everything unboxed if > you want comparable speed. Forgive the self-reference, but the following short article is all about this very topic: C. Runciman, Lazy wheel sieves and spirals of primes, Journal of Functional Programming, v7, n2, pp219--226, March 1997. From Dominic.J.Steinitz@BritishAirways.com Wed Dec 20 16:12:16 2000 From: Dominic.J.Steinitz@BritishAirways.com (Steinitz, Dominic J) Date: 20 Dec 2000 16:12:16 Z Subject: Haskell Productivity Message-ID: <"032483A40DA600E0*/c=GB/admd=ATTMAIL/prmd=BA/o=British Airways PLC/ou=CORPLN1/s=Steinitz/g=Dominic/i=J/"@MHS> The Haskell website claims that "Ericsson measured an improvement factor of between 9 and 25 in one set of experiments on telephony software". Presumably this is with Erlang not with Haskell. I have searched for the reference that substantiates this claim but I've only been able to find: http://set.gmd.de/~ap/femsys/wiger.html which talks about a productivity factor of 4 and http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haskell-vs-ada-abstract.html which suggests that Haskell is about 2-3 times as productive as imperative languages. Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25? Thanks, Dominic. ------------------------------------------------------------------------------------------------- 21st century air travel http://www.britishairways.com From simonpj@microsoft.com Wed Dec 20 11:11:44 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Wed, 20 Dec 2000 03:11:44 -0800 Subject: Problem with functional dependencies Message-ID: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> I think you can simplify the example. Given class HasFoo a b | a -> b where foo :: a -> b instance HasFoo Int Bool where ... Is this legal? f :: HasFoo Int b => Int -> b f x = foo x You might think so, since HasFoo Int b => Int -> b is a substitution instance of HasFoo a b => a -> b but if we infer the type (HasFoo Int b => Int -> b) for f's RHS, we can then "improve" it using the instance decl to (HasFoo Int Bool => Int -> Bool), and now the signature isn't a substitution insance of the type of the RHS. Indeed, this is just what will happen if you try with GHC, because GHC takes advantage of type signatures when typechecking a function defn, rather than first typechecking the defn and only then comparing with the signature. I don't know what the answers are here, but there's more to this functional dependency stuff than meets the eye. Even whether one type is more general than another has changed! Simon | -----Original Message----- | From: qrczak@knm.org.pl [mailto:qrczak@knm.org.pl] | Sent: 17 December 2000 19:30 | To: haskell@haskell.org | Subject: Problem with functional dependencies | | | The following module is rejected by both | ghc -fglasgow-exts -fallow-undecidable-instances | and | hugs -98 | | -------------------------------------------------------------- | ---------- | class HasFoo a foo | a -> foo where | foo :: a -> foo | | data A = A Int | data B = B A | | instance HasFoo A Int where | foo (A x) = x | | instance HasFoo A foo => HasFoo B foo where | foo (B a) = foo a | -------------------------------------------------------------- | ---------- | | The error messsage says that the type inferred for foo in B's instance | is not general enough: the rhs has type "HasFoo B Int => B -> | Int", but | "HasFoo B foo => B -> foo" was expected. From paul.hudak@yale.edu Wed Dec 20 16:28:10 2000 From: paul.hudak@yale.edu (Paul Hudak) Date: Wed, 20 Dec 2000 11:28:10 -0500 Subject: Haskell Productivity References: <"032483A40DA600E0*/c=GB/admd=ATTMAIL/prmd=BA/o=British Airways PLC/ou=CORPLN1/s=Steinitz/g=Dominic/i=J/"@MHS> Message-ID: <3A40DE1A.1F00B405@yale.edu> > Can someone point me at some more references? See http://haskell.org/papers/NSWC/jfp.ps. -Paul From peterd@availant.com Wed Dec 20 16:45:35 2000 From: peterd@availant.com (Peter Douglass) Date: Wed, 20 Dec 2000 11:45:35 -0500 Subject: Haskell Productivity Message-ID: <8BDAB3CD0E67D411B02400D0B79EA49A5F6CCC@smail01.clam.com> There is a thread on comp.lang.functional which may be of interest. Here is a link that might work for you. http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh 8ss$6le$1@bird.wu-wien.ac.at%3e%231/1 > -----Original Message----- > From: Steinitz, Dominic J > [mailto:Dominic.J.Steinitz@BritishAirways.com] > Sent: Wednesday, December 20, 2000 11:12 AM > To: haskell > Subject: Haskell Productivity > > > The Haskell website claims that > > "Ericsson measured an improvement factor of between 9 and 25 > in one set of experiments on telephony software". > > Presumably this is with Erlang not with Haskell. I have > searched for the reference that substantiates this claim but > I've only been able to find: > > http://set.gmd.de/~ap/femsys/wiger.html > > which talks about a productivity factor of 4 > > and > > http://www.md.chalmers.se/Cs/Research/Functional/Fudgets/haske ll-vs-ada-abstract.html which suggests that Haskell is about 2-3 times as productive as imperative languages. Can someone point me at some more references? Especially the one that talks about a productivity improvement of 9-25? Thanks, Dominic. ---------------------------------------------------------------------------- --------------------- 21st century air travel http://www.britishairways.com _______________________________________________ Haskell mailing list Haskell@haskell.org http://www.haskell.org/mailman/listinfo/haskell From peterd@availant.com Wed Dec 20 16:50:50 2000 From: peterd@availant.com (Peter Douglass) Date: Wed, 20 Dec 2000 11:50:50 -0500 Subject: Haskell Productivity Message-ID: <8BDAB3CD0E67D411B02400D0B79EA49A5F6CCF@smail01.clam.com> Hello all, You will need to manually reconnect the link I sent into a single line for it to work. > There is a thread on comp.lang.functional which may be of interest. > Here is a link that might work for you. > > http://www.deja.com/dnquery.xp?search=thread&svcclass=dnserver&recnum=%3c8lh 8ss$6le$1@bird.wu-wien.ac.at%3e%231/1 From ashley@semantic.org Wed Dec 20 23:59:50 2000 From: ashley@semantic.org (Ashley Yakeley) Date: Wed, 20 Dec 2000 15:59:50 -0800 Subject: GHC for Darwin? Message-ID: <200012202359.PAA26221@mail4.halcyon.com> Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant that runs on the PowerPC processor. . I was going to compile it myself before I remembered that compilers do platform-specific code-generation. Duh. -- Ashley Yakeley, Seattle WA From simonmar@microsoft.com Wed Dec 20 17:46:25 2000 From: simonmar@microsoft.com (Simon Marlow) Date: Wed, 20 Dec 2000 09:46:25 -0800 Subject: ANNOUNCE: Happy version 1.9 Message-ID: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell ----------------------------------------------------------------- I'm pleased to announce version 1.9 of Happy, the parser generator system for Haskell. Changes in this version, relative to version 1.8 (the previous full release): * A grammar may now contain several entry points, allowing several parsers to share parts of the grammar. * Some bugfixes. Happy is available in source form, which can be compiled with GHC version 4.xx (4.08.1 recommended), and we also provide binaries for some architectures. The Happy homepage with links to the various distributions lives at: http://www.haskell.org/happy/ Please send any bug reports and comments to simonmar@microsoft.com. From doaitse@cs.uu.nl Thu Dec 21 08:22:27 2000 From: doaitse@cs.uu.nl (S. Doaitse Swierstra) Date: Thu, 21 Dec 2000 10:22:27 +0200 Subject: GHC for Darwin? In-Reply-To: <200012202359.PAA26221@mail4.halcyon.com> References: <200012202359.PAA26221@mail4.halcyon.com> Message-ID: At 3:59 PM -0800 12/20/00, Ashley Yakeley wrote: >Are there any plans to port GHC to Darwin? Darwin is a FreeBSD-variant >that runs on the PowerPC processor. >. > >I was going to compile it myself before I remembered that compilers do >platform-specific code-generation. Duh. > >-- >Ashley Yakeley, Seattle WA > > >_______________________________________________ >Haskell mailing list >Haskell@haskell.org >http://www.haskell.org/mailman/listinfo/haskell Atze Dijkstra (mailto:atze@cs.uu.nl) is working on a port of the GHC to MacOS X. He has reached the state where he managed to compile some programs (e.g. our attribute grammar system and combinator libraries). Doaitse Swierstra -- __________________________________________________________________________ S. Doaitse Swierstra, Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands Mail: mailto:doaitse@cs.uu.nl WWW: http://www.cs.uu.nl/ PGP Public Key: http://www.cs.uu.nl/people/doaitse/ tel: +31 (30) 253 3962, fax: +31 (30) 2513791 __________________________________________________________________________ From jeff@galconn.com Thu Dec 21 08:59:29 2000 From: jeff@galconn.com (Jeffrey R. Lewis) Date: Thu, 21 Dec 2000 00:59:29 -0800 Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> Message-ID: <3A41C671.B9EDF2E3@galconn.com> Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so, since > HasFoo Int b => Int -> b > is a substitution instance of > HasFoo a b => a -> b This is the step where the reasoning goes wrong. The functional dependency tells you that `b' isn't really a free variable, since it is dependent on `a'. If you substitute for `a', you can't expect `b' to remain unconstrained. Hugs complains that the inferred type for `f' is not general enough. It's right to complain, but the real problem is that the signature is too general. Asimilar situation arises if you try to declare an instance `HasFoo Int b', but in this case, hugs complains that the instance is more general than the dependency allows. A useful thing to do would be to check for this sort of thing in signatures as well, so that the more appropriate error message can be given. --Jeff From qrczak@knm.org.pl Thu Dec 21 10:05:14 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 21 Dec 2000 10:05:14 GMT Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> <3A41C671.B9EDF2E3@galconn.com> Message-ID: Thu, 21 Dec 2000 00:59:29 -0800, Jeffrey R. Lewis pisze: > > class HasFoo a b | a -> b where > > f :: HasFoo Int b => Int -> b > > f x = foo x > This is the step where the reasoning goes wrong. The functional > dependency tells you that `b' isn't really a free variable, since > it is dependent on `a'. If you substitute for `a', you can't expect > `b' to remain unconstrained. It's not unconstrained: the constraint is "HasFoo Int b", as written. IMHO it should not matter that the constraint fully determines b. > Asimilar situation arises if you try to declare an instance `HasFoo > Int b', but in this case, hugs complains that the instance is more > general than the dependency allows. ghc does not complain. How would I express "the instance can be chosen basing on 'a' alone, and the instance found will tell what constraints are on 'b'"? Aren't fundeps a too general mechanism which is not able to express simpler statements? :-( -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From chak@cse.unsw.edu.au Thu Dec 21 11:40:02 2000 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Thu, 21 Dec 2000 22:40:02 +1100 Subject: ANNOUNCE: Happy version 1.9 In-Reply-To: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> References: <9584A4A864BD8548932F2F88EB30D1C60171F366@TVP-MSG-01.europe.corp.microsoft.com> Message-ID: <20001221224002G.chak@cse.unsw.edu.au> Simon Marlow wrote, > ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell > ----------------------------------------------------------------- A RedHat 7.0/i386 rpm package is available at ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/i386/happy-1.9-1.i386.rpm and the matching source rpm at ftp://ftp.cse.unsw.edu.au/pub/users/chak/jibunmaki/src/happy-1.9-1.src.rpm Happy Hacking, Manuel From rrt1001@cam.ac.uk Thu Dec 21 11:58:42 2000 From: rrt1001@cam.ac.uk (Reuben Thomas) Date: Thu, 21 Dec 2000 11:58:42 +0000 (GMT) Subject: ANNOUNCE: Happy version 1.9 In-Reply-To: <20001221224002G.chak@cse.unsw.edu.au> Message-ID: > ANNOUNCING Happy 1.9 - The LALR(1) Parser Generator for Haskell > ----------------------------------------------------------------- A Windows InstallShield package is available at http://www.haskell.org/happy/dist/1.9/happy-1-9.exe -- http://sc3d.org/rrt/ | egrep, n. a bird that debugs bison From lennart@augustsson.net Thu Dec 21 12:11:33 2000 From: lennart@augustsson.net (Lennart Augustsson) Date: Thu, 21 Dec 2000 13:11:33 +0100 Subject: Problem with functional dependencies References: <74096918BE6FD94B9068105F877C002D013783CC@red-pt-02.redmond.corp.microsoft.com> Message-ID: <3A41F375.499AEC44@augustsson.net> Simon Peyton-Jones wrote: > I think you can simplify the example. Given > > class HasFoo a b | a -> b where > foo :: a -> b > > instance HasFoo Int Bool where ... > > Is this legal? > > f :: HasFoo Int b => Int -> b > f x = foo x > > You might think so, since > HasFoo Int b => Int -> b > is a substitution instance of > HasFoo a b => a -> b > > but if we infer the type (HasFoo Int b => Int -> b) > for f's RHS, we can then "improve" it using the instance > decl to (HasFoo Int Bool => Int -> Bool), and now the signature > isn't a substitution insance of the type of the RHS. I definitely want it to be legal. I have examples where this is immensly useful. -- -- Lennart From qrczak@knm.org.pl Thu Dec 21 18:32:59 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 21 Dec 2000 18:32:59 GMT Subject: Are fundeps the right model at all? Message-ID: Could somebody show an example which requires fundeps and cannot be expressed using a simpler model explained below - a model that I can even understand? Is the model self-consistent at all? Each class is associated with a set of subsets of type variables in its head. Let's call it the set of keys. The intuitive meaning of a key is that types corresponding to these variables are sufficient to determine which instance to choose. They correspond to lhss of some fundeps. Plain classes without explicitly written keys correspond to having a single key consisting of all type variables. Keys influence the typechecking thus: - A type is unambiguous if for every class constraint in it there exists its key such that types in the constraint corresponding to type variables from the key contain no type variables which are absent in the type itself. - All class methods must have unambiguous types, i.e. for each method there must be a key whose all type variables are present in the method's type. - For each key, there must be no pair of instances whose heads projected to the class parameters from the key overlap. - For each class constraint of an unambiguous type an each its key there must be an instance found basing on this key, or the type is incorrect because of missing instances. Moreover, instances found basing on all keys must be identical. - Perhaps something must be said about class contexts and instance contexts. I'm not sure what yet. Examples: class Collection c e | c where empty :: c insert :: c -> e -> c class Monad m => MonadState s m | m where get :: m s put :: s -> m () newtype State s a = State {runState :: s -> (a,s)} instance Monad (State s) instance MonadState s (State s) test1:: Int -> Int test1 x = snd (runState get x) -- Not ambiguous. class IOvsST io st | io, st where -- Two single-element keys. ioToST :: io -> st stToIO :: st -> io instance IOvsST (IORef a) (STRef s a) where ioToST = unsafeCoerce# stToIO = unsafeCoerce# test2:: IORef a -> IORef a test2 = ioToST . stToIO -- Not ambiguous. class Foo a b | a instance Foo Int [a] -- This is rejected by Hugs (with fundep a->b) but I would definitely -- accept it. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From ger@tzi.de Thu Dec 21 20:20:46 2000 From: ger@tzi.de (George Russell) Date: Thu, 21 Dec 2000 21:20:46 +0100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: Message-ID: <3A42661E.7FCCAFFA@tzi.de> Alternatively, I wonder whether the current system of type classes is the right model at all. Although I prefer the Haskell system, I think it is instructive to compare it with the Standard ML (SML) system of structures and functors. My point is that both Haskell and SML impose one of two possible extremes on the user, and suffer for it. With SML, it is as if all instances are explicitly named. SML does not permit user-defined overloading, and so SML is not capable of understanding something such as a "type class of things we can compare", and has a horrible set of kludges to cope with implementing the equality operator. With Haskell, on the other hand, there is no way of referring to a particular instance when you want to. We see a particular consequence of that here, in that (unlike SML), it is not possible to associate an internal type with a given instance. Another problem is that no-one has any control over what instances get exported, because since instances are anonymous there is no way of referring to them. Hence the current procedure is to expose everything to the importer, which is surely a mistake. So if you agree with me up to here, perhaps you are agreed that it is worth while trying to find a middle way, in which we try to combine both approaches. Well I'm not an expert language designer, and I'm doing this off the top of my head late on Thursday evening, so please don't nitpick about syntax; I'm aware that parsing will probably be difficult in all sorts of ways with exactly what I'm writing, but that shouldn't be too hard to tweak. In particular I have followed SML in using "." to express qualification by something, even though Haskell already used "." for something else, because I can't be bothered right now to dig up a better symbol. On the other hand if my whole approach is a pile of elephant dung I apologise for wasting your time, and wish you a happy Christmas/holidays, but do try to find a better way of combining the best of SML functors and Haskell classes. Anyway here is my proposal. (1) We extend type classes to allow them to introduce types. Thus for example I would replace Marcin's first example by class Collectible e where type c -- or we could just omit the "type" keyword, trading clarity -- for conciseness. -- note also that we need a way of expressing a context for -- "c", EG that it's an instance of Eq. empty :: c insert :: c -> e -> c As usual, you can refer to "empty" and "insert" right away, but you can't refer to "c" without extra syntax. We need a way of referring to the particular instance of Collectible. So I suggest something like: singleton :: (method | Collectible e) => e -> method.c singleton el = insert empty el (2) We extend instance declarations in two ways. Firstly and obviously, we need a way of declaring the type c in the instance second declaration. The second thing is to introduce named instance declarations, like this: instance IntList | Collectible Int where type c = [Int] empty = [] insert = (flip(:)) To actually _refer_ to a specific instance, you would qualify with IntList. So you could refer to IntList.c, IntList.empty, IntList.insert, just like you would with SML. But as with Haskell, "empty" and "insert" would continue to be available implicitly. A more complicated example arises when you have instances depending on other instances. EG instance SetCollection | Ord el => Collectible el where type c = Set el empty = emptySet insert = addToSet -- new function, thank Simon Marlow Then, in this case, you would refer to SetCollection.c when you wanted to refer to the type c. However note that in this case we are implicitly using an anonymous use of Ord. Supposing you had previously defined (ignoring questions about overlapping instances for now . . .) instance EccentricOrd | Ord Int where ... and you wanted to define Sets in terms of EccentricOrd. Then I suggest that you use instead SetCollection(EccentricOrd).c and likewise SetCollection(EccentricOrd).empty and Sets(EccentricOrd).insert, though I hope that such monstrous constructions will not often be necessary. When they are, maybe it would be a good idea to allow the user to abbreviate, as in instance EccentricSet | Collectible Int = SetCollection(EccentricOrd) just as you can do in SML. (3) Finally it would be nice to extend the module syntax to allow named instances to be selectively exported and imported, just like variables. If I could ignore all pre-existing Haskell code I would specify that whenever a module has a specific import list, no instances are imported unless specified. However this is politically impossible, so instead I suggest that all anonymous instances continue to be implicitly imported, as now, but that named instances are only imported when named in the import list. EG "import File(instance SetCollection)". Also, I think it would be nice to have something similar to the "qualified" operator, by which class membership is NOT automatically inherited, and would have to be explicitly specified by referring to "SetCollection.insert" or indeed "SetCollection.singleton"; in particular this would provide a clean way of handling overlapping classes. OK, so I realise this is probably not the final answer, but wouldn't it be nice if something along these lines could be got to work? From ger@tzi.de Fri Dec 22 15:56:41 2000 From: ger@tzi.de (George Russell) Date: Fri, 22 Dec 2000 16:56:41 +0100 Subject: List.partition a bit too eager Message-ID: <3A4379B9.CBA6D281@tzi.de> I think the following program import List main = putStr . show . fst . (partition id) . cycle $ [True,False] should display [True,True,True,...]. But instead, for both GHC and Hugs, you get a stack overflow. Is this a bug, or could someone explain it to me? From qrczak@knm.org.pl Sun Dec 24 20:25:12 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 24 Dec 2000 20:25:12 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: Thu, 21 Dec 2000 21:20:46 +0100, George Russell pisze: > So if you agree with me up to here, perhaps you are agreed that it is worth > while trying to find a middle way, in which we try to combine both approaches. I am thinking about a yet different approach. Leave classes and SML structures as they are, and make *records* more flexible, to be used instead of classes if instances are to be manipulated explicitly, and instead of structures if we are using Haskell rather than SML or OCaml, and instead of objects if we are using Haskell rather than some OO language, and as a general way of expressing things behaving like fixed dictionaries of values. I have yet to play more with it. I already have some thoughts and a working preprocessor which translates my extensions to Haskell (with multi-parameter classes and fundeps). -------- GOALS -------- * Replace the current record mechanism with a better one. * Don't require sets of fields of different record types disjoint. It's not only to avoid inventing unique field names, but also to have functions polymorphic over all records containing specific fields of specific types. * Provide a way to specialize existing record types to new types that behave similarly except of small changes. I.e. kind of inheritance. * Since Haskell does not have subtyping, have coercions up the inheritance tree. Overloading functions on record types is not always enough, e.g. to put records in a heterogeneous collection they must be coerced to a common type. * Don't constrain the implementation of field access for different record types. As long as it behaves like a record, it is a record. * Don't constrain the implementation of methods even for the same record type. Since Haskell does not have subtyping, records which would have different types in other languages can have the same type in Haskell, as long as the same interface suffices. * Express keyword parameters of functions. A function might use many parameters refining its behavior which usually have some default values. Old code using that function must not break when more parameters are added. * A piece of code should be understandable locally, independently of definitions and instances present elsewhere. * Have a nice syntax. * Keep it simple and easily translatable to the core language. Fields and methods are really the same thing. Moreover, inheritance is really delegation and coercions are the same things as field accesses as well. Record types are not anonymous, unlike TREX. Field names are born implicitly and live in a separate namespace. Each field name is associated with a class of record types having that field. Instances of these classes are defined implicitly for types defined as records, but can also be given explicitly for any type. -------- FIELD SELECTION -------- A field selection expression of the form expr.label is equivalent to (.label) expr where (.label) :: (r.label :: a) => r -> a is an overloaded selector function. (rec.label:: a) is a syntax for Has_label rec a, where Has_label is the implicitly defined class for this label. Such class would look like this if it were defined as normal classes: class Has_label r a | r -> a where (.label) :: r -> a set_label :: r -> a -> r except that there are no real names Has_label nor set_label. -------- DEFINITION OF RECORD TYPES -------- The definition of a record type: data Monoid e = record zero :: e plus :: e -> e -> e defines the appropriate single-constructor algebraic type and obvious instances: instance (Monoid e).zero :: e where ... instance (Monoid e).plus :: e -> e -> e where ... We can construct values of this type thus: numAddMonoid :: Num e => Monoid e numAddMonoid = record zero = 0 plus = (+) The meaning of such overloaded record creation expressions will be specified later. -------- INHERITANCE -------- Here is another example of a record type definition: data Group e = record monoid :: Monoid e minus :: e -> e -> e neg :: e -> e monoid (zero, plus) x `minus` y = x `plus` neg y neg y = zero `minus` y This record type has three direct members: monoid, minus, and neg. monoid holds its zero and plus. We want to be able to extract zero and plus of a group directly, instead of going through the underlying monoid. We could define appropriate instances: instance (Group e).zero :: e where ... instance (Group e).plus :: e -> e -> e where ... and this is what the inheritance declaration monoid (zero, plus) does automatically for us. So groups too have zero and plus, which are deleagated to the monoid. Seen from outside, these fields are indistinguishable from proper Group's fields. -------- DEFAULT DEFINITIONS -------- minus and neg in Group have default definitions expressed in terms of each other. When making a Group we can provide the definition of either one or both, otherwise both will diverge. We could provide default definitions of inherited methods too. If they had default definition in the supertype, they would be overridden. This is how the system expresses OO methods belonging to a type: by default definitions. They can be overridden in subtypes or at object creation time. How is it done that the default definition of minus refers to the definition of neg which will be supplied later? It is not known yet which fields will be specified at creation time. OTOH at the creation time it is not known which fields have default definitions, because the creation expression is polymorphic over record types containing specific fields and will be instantiated based on the context. There is a standard class defined as follows: class Record r where bless :: r -> r A record creation expression, say: record zero = 0 plus = (+) is a syntactic sugar for a recursively defined object: let this = bless this `set_zero` 0 `set_plus` (+) in this The bless function, named after Perl's mechanism used in a similar context, returns a record with all fields initialized using their default definitions, or bottoms for fields with no defaults. Default definitions refer to other fields through the parameter of bless. As seen above, bless is applied to the record to be constructed, and then fields with values specified at creation time are overridden. That way all field definitions can find right versions of other fields, no matter which were defined together with the type and which were supplied at the creation time. The type of the above record creation expression is (Record r, Num a, Num b, r.zero :: a, r.plus :: b -> b -> b) => r -------- DEFINITION OF BLESS -------- Definition of a record type automatically makes it an instance of the class Record. A field from which some other fields are inherited is initialized to blessed value of the same field taken from the parameter of bless, modified by setting those fields which have default defintions. It sounds complicated but this is what yields right bindings of all definitions. If a type behaves like a record, it is a record. You can make Record instances of arbitrary types, making them constructible using the record syntax. bless should be lazy. Field setters can be strict. -------- UPDATING FIELDS -------- If fields represent state changing over time, they can be mutable references. Fields can also be updated in a functional style, but this is really construction of new objects basing on old ones. Field update syntax is as follows: expr.record label1 = value1 label2 = value2 It is equivalent to simple nested set_label applications. Fields initialized with default definitions will not switch to refer to updated values of other fields! All magic already happened at record creation time. This can be changed in at least two ways. First, you can define instances of appropriate Has_label classes yourself and associate arbitrary magic with field updates. Second, you can make such instance for the field that you want to be a function of other fields instead of putting the field in the record directly. Definitions of two methods of Has_label classes have special syntax: instance (a,b).fst :: a where (a,_).fst = a (_,b).record {fst = a} = (a,b) instance (a,b).snd :: b where (_,b).snd = b (a,_).record {snd = b} = (a,b) I.e. pattern.label is equivalent to (.label) pattern and defines the getter function, and pattern1.record {label = pattern2} defines the setter when applied to the record matching pattern1 and field value matching pattern2. Braces can be omitted, but they make the syntax more clear. -------- SYNTAX DETAILS -------- The record keyword triggers the layout rules. Value definitions after the record keyword look like let bindings. They can be defined by cases with argument patterns on the left of the equal sign. In record type definitions, record creations and record updates definitions of fields can refer to all fields mentioned in those constructs in an unqualified form. They can also refer to a special variable called this, which holds the whole record after construction or update. -------- EXAMPLE -------- This example introduces a feature of renaming fields while inheriting. > data Monoid e = record > zero :: e > plus :: e -> e -> e > > numAddMonoid :: Num e => Monoid e > numAddMonoid = record > zero = 0 > plus = (+) > > numMulMonoid :: Num e => Monoid e > numMulMonoid = record > zero = 1 > plus = (*) > > data Group e = record > monoid :: Monoid e > minus :: e -> e -> e > neg :: e -> e > monoid (zero, plus) > x `minus` y = x `plus` neg y > neg y = zero `minus` y > > numAddGroup :: Num e => Group e > numAddGroup = record > monoid = numAddMonoid > minus = (-) > neg = negate > > numMulGroup :: Fractional e => Group e > numMulGroup = record > monoid = numMulMonoid > minus = (/) > neg = recip > > data Ring e = record > addGroup :: Group e > mulMonoid :: Monoid e > addGroup (monoid as addMonoid, zero, plus, minus, neg) > mulMonoid (zero as one, plus as times) > > numRing :: Num e => Ring e > numRing = record > addGroup = numAddGroup > mulMonoid = numMulMonoid > > data Field e = record > addGroup :: Group e > mulGroup :: Group e > addGroup (monoid as addMonoid, zero, plus, minus, neg) > mulGroup (monoid as mulMonoid, zero as one, plus as times, > minus as div, neg as recip) > > instance (Field e).ring :: Ring e where > f.ring = record > addGroup = f.addGroup > mulMonoid = f.mulMonoid > f.record {ring = r} = f.record > addGroup = r.addGroup > mulMonoid = r.mulMonoid > > -- Alternatively a Field could consist of a Ring and div + recip. > -- The difference is an implementation detail not visible outside. > -- The following definition will work with either variant: > > numField :: Fractional e => Field e > numField = record > addGroup = numAddGroup > mulGroup = numMulGroup -------- PROBLEMS -------- If those records are to simulate classes, they should be able to have polymorphic fields. Unfortunately it does not work to have overloaded setters in this case. I don't know a good solution. Similarly we would want to have records with existentially quantified types. Again it does not work to have overloaded getters and setters. Listing all inherited fields can be annoying. It would not really work otherwise, as arbitrary instances for sypertypes can be added at any time. It is not necessary to list all fields: other fields are available through the field we inherit from anyway. It would be desirable to selectively export instances. -------- PROTOTYPE IMPLEMENTATION -------- I have an implementation of this in the form of a preprocessor, based on hssource from ghc-4.11's hslibs. I will polish it and put for downloading to let people play with my records. I hope to have more interesting examples. The difference between this implementation and the above proposal is that types of inherited fields must be given explicitly. This is because delegation instances would otherwise have to have types which are not accepted by ghc, and they would require -fallow-undecidable-instances if they were legal (which is not a surprise because cyclic inheritance makes it impossible to determine the type of the field). I reported the problem under the subject "Problem with functional dependencies" on December 17th. I believe that both problems can be fixed, especially if handling those constructs were inside the compiler. -------- THE REST OF MY REPLY TO GEORGE RUSSELL -------- > (1) We extend type classes to allow them to introduce types. If your classes were expressed as my records, it would roughly correspond to existential quantification. But there are big problems with typechecking in this approach. I hope somebody will invent a solution. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From fjh@cs.mu.oz.au Tue Dec 26 01:10:55 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Tue, 26 Dec 2000 12:10:55 +1100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: <3A42661E.7FCCAFFA@tzi.de> References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: <20001226121054.A20508@hg.cs.mu.oz.au> On 21-Dec-2000, George Russell wrote: > (3) Finally it would be nice to extend the module syntax to allow named > instances to be selectively exported and imported, just like variables. Mercury's module system allows instance declarations (which, as in Haskell 98, are unnamed) to be selectively exported. :- module foo. :- interface. :- import_module enum. :- type t. :- instance enum(t). :- implementation. :- instance enum(t) where [ ... ]. Mercury doesn't directly support selective import -- you can only import a whole module, not part of it. But if you really want that you can achieve it by putting each instance declaration in its own nested module. :- module foo. :- interface. :- import_module enum. :- type t. :- module enum_t. :- interface. :- instance enum(t). :- end_module enum_t. :- implementation. :- module enum_t. :- implementation. :- instance enum(t) where [ ... ]. :- end_module enum_t. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From qrczak@knm.org.pl Tue Dec 26 08:46:44 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 26 Dec 2000 08:46:44 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> <20001226121054.A20508@hg.cs.mu.oz.au> Message-ID: Tue, 26 Dec 2000 12:10:55 +1100, Fergus Henderson pisze: > Mercury's module system allows instance declarations (which, as in > Haskell 98, are unnamed) to be selectively exported. If they could be selectively exported in Haskell, how to make it compatible with the current assumption that they are exported by default? Selective hiding would be weird. Perhaps there should be a separate section for exporting instances. If not present, then everything is exported (as with plain module contents). I hope selective export would help with resolving conflicting instances. There might be a confusion if a function does indeed get a sorted list of objects of type T but it expected a different ordering, but the danger of inability of linking two independent libraries due to an innocent overlapping instance might be worse. As we are at it, it would be nice to be able to specify signatures and other interface details where they belong - in the export list. With a different syntax of the export list; there would be an ambiguity if ..., var1, var2 :: Type, ... gives Type to both variables or only one, and items should be separated by layoutable semicolons. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From Doug_Ransom@pml.com Wed Dec 27 18:33:42 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Wed, 27 Dec 2000 10:33:42 -0800 Subject: ANNOUNCE: HaXml 1.00 Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61DD@hermes.pml.com> I think it is important that a good haskell XML library be included as part of the haskell runtime library given XML's relevance. > -----Original Message----- > From: Malcolm Wallace [mailto:Malcolm.Wallace@cs.york.ac.uk] > Sent: Thursday, November 16, 2000 8:42 AM > To: haskell@haskell.org > Subject: ANNOUNCE: HaXml 1.00 > > > We are pleased to announce > > HaXml release 1.00 > -------------------- > > HaXml is a library enabling the use of Haskell and XML together, > together with several auxiliary tools for useful XML jobs. Fuller > details are on the web page. > > > What's new since 0.9? > --------------------- > The main addition is a full treatment of the external subset for DTDs. > The DtdToHaskell tool can now slurp in a single DTD from multiple > files, and also now treats conditional sections (INCLUDE and IGNORE) > correctly. > > There is improved error-reporting: lexing and parsing errors > now report > the relevant filename, and the line/column positions are more > accurate. > > > Where do I get it? > ------------------ > Web pages: http://www.cs.york.ac.uk/fp/HaXml/ > FTP site: ftp://ftp.cs.york.ac.uk/pub/haskell/HaXml/ > > An older version of HaXml is also included in GHC's hslibs, in package > "text". This will probably be updated to 1.00 at some time. > > Regards, > Malcolm > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > From Doug_Ransom@pml.com Thu Dec 28 01:30:19 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Wed, 27 Dec 2000 17:30:19 -0800 Subject: Learning Haskell and FP Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> I have read "The Craft of Functional Programming" by Simon Thompson and a few paper on the web. "The Craft" is a good book, but it is an introduction to FP. It seems to me it there are a lot of books on OO design I can pick up at the bookstore, but in the FP world, one must worm their way through all sorts of papers. I have seen papers on Catamorphisms, Monads, Programming with Barbed Wire, folds, etc. I think these papers are hard to understand if you don't have the acadademic/mathematical background -- being papers and not textbooks these papers assume a fair bit of base knowledge. I know I can design a fold function to use in place of primitive recursion for most data structures -- I just don't know if I should. It is pretty easy to get through "The Craft of Functional Programming" without understanding what Category Theory , a Catamorphism , or a Kleisli Composition is. I can see lots of real Software Engineering oppurtunities for these various techniques if I could just put them together. Is there a good textbook on Functional Programming which starts from a base point similar to "The craft of Functional Programming" but more advanced in terms of introducing necessary topics like Category theory, catamorphisms, monads, etc? I would find such a book very useful, especially if it concentrated on lazy functional programming. Doug Ransom Systems Engineer Power Measurement Ltd. http://www.pml.com 250-652-7100 office 250-652-0411 fax mailto:doug_ransom@pml.com From israelt@optushome.com.au Thu Dec 28 02:50:50 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 12:50:50 +1000 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> References: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: <200012281250500955.006178FD@mail> >I have read "The Craft of Functional Programming" by Simon Thompson and a >few paper on the web. "The Craft" is a good book, but it is an= introduction >to FP. >It seems to me it there are a lot of books on OO design I can pick up at= the >bookstore, but in the FP world, one must worm their way through all sorts= of >papers. I have seen papers on Catamorphisms, Monads, Programming with >Barbed Wire, folds, etc. I think these papers are hard to understand if= you >don't have the acadademic/mathematical background -- being papers and not >textbooks these papers assume a fair bit of base knowledge. I agree with this completely. The CFP book is a good introduction. Unforunately, the " Gentle Introduction To Haskell" that haskell.org links= to is not a very useful introduction. I am getting more out of Rex Paige's Two Dozen Short Lessons in Haskell.= ( I am studying Haskell and C# on my own in my spare time as break from my= medical practice ). From russell@brainlink.com Thu Dec 28 06:14:54 2000 From: russell@brainlink.com (Benjamin L. Russell) Date: Thu, 28 Dec 2000 01:14:54 -0500 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: While it may not be advanced or mathematical enough for your needs, you may wish to read _The Haskell School of Expression: Learning Functional Programming through Multimedia,_ by Paul Hudak. This is also an introductory book on functional programming, with a special focus on Haskell, although the examples used are mainly from multimedia. I compared the first few chapters of both _The Craft of Functional Programming_ and _The Haskell School of Expression,_ and personally found Hudak's book (the latter) much more interesting. The exercises are designed to teach the reader to think in terms of functional, as opposed to imperative or object-oriented, programming--hence the phrase in the title "School of Expression." --Ben -- Benjamin L. Russell russell@brainlink.com benjamin.russell.es.94@aya.yale.edu "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho On Wed, 27 Dec 2000 17:30:19 -0800 Doug Ransom wrote: > I have read "The Craft of Functional Programming" by > Simon Thompson and a > few paper on the web. "The Craft" is a good book, but it > is an introduction > to FP. > > > It seems to me it there are a lot of books on OO design I > can pick up at the > bookstore, but in the FP world, one must worm their way > through all sorts of > papers. I have seen papers on Catamorphisms, Monads, > Programming with > Barbed Wire, folds, etc. I think these papers are hard > to understand if you > don't have the acadademic/mathematical background -- > being papers and not > textbooks these papers assume a fair bit of base > knowledge. I know I can > design a fold function to use in place of primitive > recursion for most data > structures -- I just don't know if I should. It is pretty > easy to get > through "The Craft of Functional Programming" without > understanding what > Category Theory , a Catamorphism , or a Kleisli > Composition is. I can see > lots of real Software Engineering oppurtunities for these > various techniques > if I could just put them together. > > Is there a good textbook on Functional Programming which > starts from a base > point similar to "The craft of Functional Programming" > but more advanced in > terms of introducing necessary topics like Category > theory, catamorphisms, > monads, etc? I would find such a book very useful, > especially if it > concentrated on lazy functional programming. > > > Doug Ransom > Systems Engineer > Power Measurement Ltd. > http://www.pml.com > 250-652-7100 office > 250-652-0411 fax > mailto:doug_ransom@pml.com > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell From israelt@optushome.com.au Thu Dec 28 08:52:03 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 18:52:03 +1000 Subject: Learning Haskell and FP In-Reply-To: References: Message-ID: <200012281852030258.01AC2A6C@mail> >While it may not be advanced or mathematical enough for your needs, you= may wish to read _The Haskell School of Expression:=A0Learning Functional= Programming through Multimedia,_ by Paul Hudak. This is also an= introductory book on functional programming, with a special focus on= Haskell, although the examples used are mainly from multimedia. Is there an online version of Hudak's book ? ( For example Bruce Eckel has online versions of all his books available= online as well as in print ) >"Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho Translation please ! Basho is my favorite Japanese poet. Unfortunately my Japanese is at the Ohio level.. ( ohiogozaimazu) From israelt@optushome.com.au Thu Dec 28 08:53:08 2000 From: israelt@optushome.com.au (i r thomas) Date: Thu, 28 Dec 2000 18:53:08 +1000 Subject: Haskell newsgroup Message-ID: <200012281853080001.01AD2753@mail> How about starting a Haskell newsgroup ? The closest seems to be comp.lang.functional. From johanj@cs.uu.nl Thu Dec 28 14:06:26 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Thu, 28 Dec 2000 15:06:26 +0100 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> Message-ID: <20001228140611.B3E3B4536@mail.cs.uu.nl> >Is there a good textbook on Functional Programming which starts from a base >point similar to "The craft of Functional Programming" but more advanced in >terms of introducing necessary topics like Category theory, catamorphisms, >monads, etc? I would find such a book very useful, especially if it >concentrated on lazy functional programming. You might want to have a look at the series of three books on Advanced Functional Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would probably start with 925, which introduces monads, parser & pretty-printing combinators, monadic catamorphisms, constructor classes, etc. -- Johan Jeuring From franka@cs.uu.nl Thu Dec 28 15:48:57 2000 From: franka@cs.uu.nl (Frank Atanassow) Date: Thu, 28 Dec 2000 16:48:57 +0100 Subject: Learning Haskell and FP In-Reply-To: <200012281250500955.006178FD@mail>; from israelt@optushome.com.au on Thu, Dec 28, 2000 at 12:50:50PM +1000 References: <3233BEE02CB3D4118DBA00A0C99869401D61EA@hermes.pml.com> <200012281250500955.006178FD@mail> Message-ID: <20001228164857.A13674@cs.uu.nl> i r thomas wrote (on 28-12-00 12:50 +1000): > Unforunately, the " Gentle Introduction To Haskell" that haskell.org links to is not a very useful introduction. > I am getting more out of Rex Paige's Two Dozen Short Lessons in Haskell. ( I am studying Haskell and C# on my own in my spare time as break from my medical practice ). What did you find unuseful about GITH? How could it be improved? What were your expectations for it? What was more useful about Rex Paige's notes? >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > Translation please ! Is it OK if I show off and steal some thunder? :) "(It's) An old pond! The sound of water steadily dripping in..." -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Doug_Ransom@pml.com Thu Dec 28 17:34:18 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Thu, 28 Dec 2000 09:34:18 -0800 Subject: Haskell newsgroup Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61ED@hermes.pml.com> That would only work if the haskell mailing list was either delete or mirrored onto a newsgroup. I would prefer a newsgroup myself for bandwidth reasons. > -----Original Message----- > From: i r thomas [mailto:israelt@optushome.com.au] > Sent: Thursday, December 28, 2000 12:53 AM > To: haskell@haskell.org > Subject: Haskell newsgroup > > > How about starting a Haskell newsgroup ? > The closest seems to be comp.lang.functional. > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell > From Doug_Ransom@pml.com Thu Dec 28 17:36:37 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Thu, 28 Dec 2000 09:36:37 -0800 Subject: Learning Haskell and FP Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61EE@hermes.pml.com> Who are the audience for the books on Advanced Functional Programming? Academics with a theoretical CS background or someone with just a bit of understanding of FP? Ideally, I would like a course suited for someone who has completed a basic FP course. > -----Original Message----- > From: Johan Jeuring [mailto:johanj@cs.uu.nl] > Sent: Thursday, December 28, 2000 6:06 AM > To: Doug Ransom > Cc: haskell@haskell.org > Subject: Re: Learning Haskell and FP > > > >Is there a good textbook on Functional Programming which > starts from a base > >point similar to "The craft of Functional Programming" but > more advanced in > >terms of introducing necessary topics like Category theory, > catamorphisms, > >monads, etc? I would find such a book very useful, especially if it > >concentrated on lazy functional programming. > > You might want to have a look at the series of three books on Advanced > Functional > Programming, published in LNCS, as LNCS 925, 1129, and 1608. I would > probably start with 925, which introduces monads, parser & > pretty-printing > combinators, monadic catamorphisms, constructor classes, etc. > > -- Johan Jeuring > From shlomif@vipe.technion.ac.il Thu Dec 28 19:23:07 2000 From: shlomif@vipe.technion.ac.il (Shlomi Fish) Date: Thu, 28 Dec 2000 21:23:07 +0200 (IST) Subject: Haskell newsgroup In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61ED@hermes.pml.com> Message-ID: On Thu, 28 Dec 2000, Doug Ransom wrote: > That would only work if the haskell mailing list was either delete or > mirrored onto a newsgroup. I would prefer a newsgroup myself for bandwidth > reasons. > And I prefer a mailing-list. It's hard to access newsgroups from the Technion, and Deja-news seems to be little help when it comes to posting messages. Regards, Shlomi Fish ---------------------------------------------------------------------- Shlomi Fish shlomif@vipe.technion.ac.il Home Page: http://t2.technion.ac.il/~shlomif/ Home E-mail: shlomif@techie.com The prefix "God Said" has the extraordinary logical property of converting any statement that follows it into a true one. From wli@holomorphy.com Thu Dec 28 19:40:38 2000 From: wli@holomorphy.com (William Lee Irwin III) Date: Thu, 28 Dec 2000 11:40:38 -0800 Subject: Haskell newsgroup In-Reply-To: <200012281853080001.01AD2753@mail>; from israelt@optushome.com.au on Thu, Dec 28, 2000 at 06:53:08PM +1000 References: <200012281853080001.01AD2753@mail> Message-ID: <20001228114038.N685@holomorphy.com> On Thu, Dec 28, 2000 at 06:53:08PM +1000, i r thomas wrote: > How about starting a Haskell newsgroup ? > The closest seems to be comp.lang.functional. There is a Haskell IRC channel on EfNet. I've been fielding Haskell questions there with Albert Lai and Ada Lim for several months. There has also been Haskell-related activity on OpenProjects Network #lisp. comp.lang.functional seems to be inclusive enough to obviate the need for a dedicated newsgroup. Cheers, Bill -- "And who knows, if you try it, maybe you find out that you like SM(L)? ;)" -- Markus Mottl on comp.lang.functional From proff@iq.org Thu Dec 28 22:20:13 2000 From: proff@iq.org (Julian Assange) Date: 29 Dec 2000 09:20:13 +1100 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: George Russell's message of "Thu, 21 Dec 2000 21:20:46 +0100" References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: George Russell writes: > I'm writing, but that shouldn't be too hard to tweak. In particular I have > followed SML in using "." to express qualification by something, even though > Haskell already used "." for something else, because I can't be bothered right > now to dig up a better symbol. This is why all non S-exp like lanaguage are doomed to progressive syntactic cancer as the useful parts of operator name space and syntax space become progressively polluted and mutated by one fad after another. -- Julian Assange |If you want to build a ship, don't drum up people |together to collect wood or assign them tasks proff@iq.org |and work, but rather teach them to long for the endless proff@gnu.ai.mit.edu |immensity of the sea. -- Antoine de Saint Exupery From russell@brainlink.com Thu Dec 28 22:35:04 2000 From: russell@brainlink.com (Benjamin L. Russell) Date: Thu, 28 Dec 2000 17:35:04 -0500 Subject: Learning Haskell and FP In-Reply-To: <20001228164857.A13674@cs.uu.nl> Message-ID: On Thu, 28 Dec 2000 16:48:57 +0100 Frank Atanassow wrote: > i r thomas wrote (on 28-12-00 12:50 +1000): > > Unforunately, the " Gentle Introduction To Haskell" > that haskell.org links to is not a very useful > introduction. > > I am getting more out of Rex Paige's Two Dozen Short > Lessons in Haskell. ( I am studying Haskell and C# on my > own in my spare time as break from my medical practice ). > > What did you find unuseful about GITH? How could it be > improved? What were > your expectations for it? What was more useful about Rex > Paige's notes? I read part of _GITH,_ too; while it included information necessary for an introduction, the style seemed rather terse and dry, and rather difficult to follow at times, and read more like a manual with many technical details than a tutorial brimming with motivational material, especially when compared to _The Haskell School of Expression_ ("_HSE_" in the sequel). In particular, it could have had some more interesting examples or some more commentary, both of which made _HSE_ so fascinating. > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo > Basho > > > > Translation please ! > > Is it OK if I show off and steal some thunder? :) > > "(It's) An old pond! The sound of water steadily > dripping in..." Actually, if I may add, the translation I remember was the following: "[It's] An old pond! The sound of water as the frog jumps in...." "Kawazu" means "frog," and "tobikomu" means "(to) jump in." --Ben -- Benjamin L. Russell russell@brainlink.com benjamin.russell.es.94@aya.yale.edu "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho From jans@numeric-quest.com Thu Dec 28 18:29:46 2000 From: jans@numeric-quest.com (Jan Skibinski) Date: Thu, 28 Dec 2000 13:29:46 -0500 (EST) Subject: Learning Haskell and FP In-Reply-To: Message-ID: On Thu, 28 Dec 2000, Benjamin L. Russell wrote: > On Thu, 28 Dec 2000 16:48:57 +0100 > Frank Atanassow wrote: > > i r thomas wrote (on 28-12-00 12:50 +1000): > > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > > > > "(It's) An old pond! The sound of water steadily > > dripping in..." > > "[It's] An old pond! The sound of water as the frog jumps in...." Keeping with the minimalistic spirit of Haskell: pond frog plop! -- by James Kirkup, an English poet -- Supposedly from Hiroaki Sato collection of 80 English translations -- of this haiku. -- 3 down 77 to go.. Jan From fruehr@willamette.edu Fri Dec 29 00:42:32 2000 From: fruehr@willamette.edu (Fritz K Ruehr) Date: Thu, 28 Dec 2000 16:42:32 -0800 (PST) Subject: Learning Haskell and FP Message-ID: <200012290042.QAA29740@gemini.willamette.edu> [ Doug Ransom wrote about wanting a more advanced and design-oriented book on FP than "The Craft of Functional Programming" by Simon Thompson. In reply, Johan Jeuring recommended the Advanced Schools books (I concur). ] Let me add a few other recommendations, plus a vision of a book (not yet written, as far as I know) which might fit Doug's needs; I'll call it "The Design Patterns Haskell Companion" (see below). The "actual book" recommendations (all documented on haskell.org): * Introduction to Functional Programming using Haskell (second edition) by Richard Bird (Prentice Hall, ISBN: 0-13-484346-0) This book is an introductory text, like CFP, but it ramps up a bit faster and addresses design issues from a more advanced perspective (IMHO). It's certainly an excellent text, and it builds to a nice medium-sized design example (the program calculator of Chapter 12). It also leans toward a different style of design and programming, influenced by BMF/Squiggol. * Algebra of Programming by Richard Bird and Oege de Moor (Prentice Hall, ISBN: 0-13-507245-X) You might think of this as an advanced sequel to IFPH above, although it focuses more on the theory behind program calculation: categories and allegories figure prominently, and it leans even further in the direction indicated above. But there is nevertheless a lot of good material here which can serve as a foundation for design work, esp. the final chapters (7-10) on algorithms topics. * Algorithms: A Functional Programming Approach by Fethi Rabhi and Guy Lapalme (Addison-Wesley, ISBN: 0-201-59604-0) This is a concise tour through the usual gamut of data structures and algorithms topics typical of a "CS 2" course, but from a functional perspective. It is addressed more to people who are already familiar with programming and with the "standard" approach to DSA issues. It works very well as a reference but includes enough discussion to reward a straight reading. * Purely Functional Data Structures by Chris Okasaki (Cambridge University Press, ISBN: 0-521-66350-4) This one is similar to AFPA above (in being a tour of DSA topics from a functional perspective), but is a bit more advanced: e.g., Ch. 3 covers leftist heaps, binomial heaps and red-black trees. It also addresses issues of analysis in the context of lazy evaluation more thoroughly (Banker's method, etc.). The examples are written using SML, but an appendix (and a website) give Haskell versions. Of course, none of these books really answers the needs of the mature programmer/blossoming functional programmer who seeks advice on broader design issues in the context of lazy FP, esp. Haskell. This gap leads me to propose the fanciful book mentioned above: * The Design Patterns Haskell Companion by [someone(s) reading this list?] The title may be pandering a bit, but if the Smalltalk people can do it, why can't we? :) . In fact, the title is based on "The Design Patterns Smalltalk Companion" by Alpert, Brown and Woolf, a book I came across while reading up on design patterns. (It was recommended by a customer review on Amazon as being better than the original "gang of four" book.) The "Smalltalk Companion" serves an audience of mature programmers and attempts to document a number of "standard" design patterns in the specific context of Smalltalk. I'm not sure that the Haskell community would be comfortable referring to its collective design folklore in these terms, but I'm sure we would all welcome a good book written at this level which systematically addressed the motivation, rationale, trade-offs, etc. of the more advanced techniques of FP (i.e., monads, type and constructor classes, Xa-morphisms (for various X), higher-order and nested datatypes, etc.). As Johan mentioned, the "Advanced School" books serve this purpose to an extent, but they differ from my vision in two respects: first, they are collections of chapters on particular topics, written by different authors, and thus don't form a consistent, systematic review. Second, they are not (all) written from the specific perspective of design, so that for example they don't provide as much comparison and contrast *between* techniques. Of course, another motivation for such a book is that it might lend an air of credibility and maturity to the language, thus helping to promote it in the larger world. Casting it in terms of "design patterns" would certainly make sense for these purposes (and probably guarantees a certain audience, too), although I am still ambivalent about the need for Haskell to become a huge hit with mainstream audiences. In any case, if anyone is interested to write such a book, I will buy a copy :) . And if anyone wishes to collabrate on it, I am willing to help out. (I am not qualified to write it alone, and I think it would turn out best as a group effort in any case.) -- Fritz Ruehr fruehr@willamette.edu From john@foo.net Fri Dec 29 08:37:45 2000 From: john@foo.net (John Meacham) Date: Fri, 29 Dec 2000 00:37:45 -0800 Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) In-Reply-To: ; from qrczak@knm.org.pl on Sun, Dec 24, 2000 at 08:25:12PM +0000 References: <3A42661E.7FCCAFFA@tzi.de> Message-ID: <20001229003745.A11084@mark.ugcs.caltech.edu> I also like the approach of generalizing the record system, although I have not evaluated your particular proposal. Speaking of record improvements why is http://www.cse.ogi.edu/~mpj/pubs/lightrec.html not listed on the future of haskell page? has it already been determined to not be in the future of haskell or has no one gotten around to it? Does anyone else read this proposal and drool? Speaking of this proposal does anyone else see parallels between the lightweight modules proposal and the implicit parameters proposal http://www.cse.ogi.edu/~jlewis/implicit.ps.gz as implemented in ghc. in particular implicit parameters seem like they would be able to be implemented as syntatic sugar on the lightweight module system, one could rewrite implicit parameters as every function taking a record which we can call 'imp' now '?foo' can be rewritten as 'imp.foo' and the 'with ?foo = 1' construct can be rewritten as nimp = {imp | foo := 1} and then passing nimp to all called functions. I have not thought this too far thorough so I could be missing something obvious but I think it shows potential at least for the unification of two popular extensions. and I am pretty sure this was too obvious to mention in the lightweight records paper but the section of (.foo) being equivalent to (\{_|foo=v} -> v) seems appropriate. John -- -------------------------------------------------------------- John Meacham http://www.ugcs.caltech.edu/~john/ California Institute of Technology, Alum. john@foo.net -------------------------------------------------------------- From johanj@cs.uu.nl Fri Dec 29 10:48:58 2000 From: johanj@cs.uu.nl (Johan Jeuring) Date: Fri, 29 Dec 2000 11:48:58 +0100 Subject: Learning Haskell and FP In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61EE@hermes.pml.com> Message-ID: <20001229104844.5C7F94539@mail.cs.uu.nl> >Who are the audience for the books on Advanced Functional Programming? >Academics with a theoretical CS background or someone with just a bit of >understanding of FP? Ideally, I would like a course suited for someone who >has completed a basic FP course. It varies a bit per school (book) and per article. But certainly LNCS 925 contains a number of chapters that should be interesting for someone with a general CS background and a basic FP course. I know it has been used in a couple of undergraduate courses on advanced functional programming. Topics, Authors, LNCS nr: - Monads, Wadler, 925 - Parser Combinators, Fokker, 925 - Constructor Classes, Jones, 925 - (Monadic) folds (or catamorphisms), Meijer & Jeuring, 925 - Space leaks and heap profiling, Runciman & Rojemo, 1129 - Algorithms and data structures, Okasaki, 1129 - Graph algorithms, Launchbury, 925 - User Interfaces, Carlsson & Hallgren, 925, Peyton Jones & Finne 1129 etc. Johan Jeuring http://www.cs.uu.nl/~johanj/ From franka@cs.uu.nl Fri Dec 29 13:31:01 2000 From: franka@cs.uu.nl (Frank Atanassow) Date: Fri, 29 Dec 2000 14:31:01 +0100 Subject: Learning Haskell and FP In-Reply-To: ; from russell@brainlink.com on Thu, Dec 28, 2000 at 05:35:04PM -0500 References: <20001228164857.A13674@cs.uu.nl> Message-ID: <20001229143101.A14014@cs.uu.nl> Benjamin L. Russell wrote (on 28-12-00 17:35 -0500): > > >> "Furuike ya! Kawazu tobikomu mizu no oto." --Matsuo Basho > > [..] Is it OK if I show off and steal some thunder? :) So much for that idea...! > > "(It's) An old pond! The sound of water steadily dripping in..." > > Actually, if I may add, the translation I remember was the following: > > "[It's] An old pond! The sound of water as the frog jumps in...." > > "Kawazu" means "frog," and "tobikomu" means "(to) jump in." That makes sense. I was guessing that "kawazu" was the old form of modern "kawarazu" (`without changing'). Modern `frog' is "kaeru", though, and the transitive form of "kawaru" (`change') is also "kaeru", so I suppose there is some linguistic relationship. "tobikomu" makes much more sense this way too. I thought it was a figurative usage, but it still didn't sound right... -- Frank Atanassow, Information & Computing Sciences, Utrecht University Padualaan 14, PO Box 80.089, 3508 TB Utrecht, Netherlands Tel +31 (030) 253-3261 Fax +31 (030) 251-379 From Doug_Ransom@pml.com Fri Dec 29 15:52:24 2000 From: Doug_Ransom@pml.com (Doug Ransom) Date: Fri, 29 Dec 2000 07:52:24 -0800 Subject: Haskell Language Design Questions Message-ID: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> 1. Is the lack of dynamic binding of functions by design or because it was too much effort to be justified at the time the language was designed? In object oriented programming there can be several implementations of the same interface, and they can be stored in the same collection. 2. It seems to me that the Maybe monad is a poor substitute for exception handling because the functions that raise errors may not necessarily support it. For example, if I use someone elses custom type and a custom map function theirmap myApplicator SomeList and theirmap is not designed to support the Maybe monad, then it becomes hard to use if SomeFunction might raise an error. Am I missing something? Doug Ransom Systems Engineer Power Measurement Ltd. http://www.pml.com 250-652-7100 office 250-652-0411 fax mailto:doug_ransom@pml.com From israelt@optushome.com.au Fri Dec 29 06:50:36 2000 From: israelt@optushome.com.au (i r thomas) Date: Fri, 29 Dec 2000 16:50:36 +1000 Subject: Learning Haskell and FP In-Reply-To: <200012290042.QAA29740@gemini.willamette.edu> References: <200012290042.QAA29740@gemini.willamette.edu> Message-ID: <200012291650360884.018BF6C5@mail> On 12/28/2000 at 7:00 PM Bill Halchin wrote: >Hello IR, > I agree with the OU Haskell Tutorial. It is excellent!! Yes, with a bit of editing and more diagrams , it would probably be worth= publishing. >BTW, what is your C# source? The .NET Framework SDK is freely downloadable from MS ( around 100 megs ) and comes with a C# tutorial, C# reference and a command line C#. There are also a few chapters online of some C# books that cover issues= like namespaces and attributes. I am using the Antechinus C# editor as an IDE . This comes with a few basic= C# examples as well. ( for vi freaks, I have written a C# vim syntax file that will appear on= vim.org once it is polished up.) From fjh@cs.mu.oz.au Sat Dec 30 03:50:04 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Sat, 30 Dec 2000 14:50:04 +1100 Subject: Haskell Language Design Questions In-Reply-To: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> References: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> Message-ID: <20001230145004.A12063@hg.cs.mu.oz.au> On 29-Dec-2000, Doug Ransom wrote: > 1. Is the lack of dynamic binding of functions by design or because it was > too much effort to be justified at the time the language was designed? In > object oriented programming there can be several implementations of the same > interface, and they can be stored in the same collection. It's just something that didn't make it into Haskell 98. Hugs and ghc offer a language extension for that. It will almost certainly be in the next revision of Haskell. See . > 2. It seems to me that the Maybe monad is a poor substitute for > exception handling because the functions that raise errors may not > necessarily support it. Hugs and ghc also have exception handling extensions. See . There's also a paper or two on that. I hope you'll forgive the self-citation, but the only one for which I happen to have a reference on-hand is this one: A semantics for imprecise exceptions. Simon Peyton-Jones, Alastair Reid, Tony Hoare, Simon Marlow, and Fergus Henderson. Proceedings of the 1999 ACM SIGPLAN Conference on Programming Language Design and Implementation, May 1999. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From qrczak@knm.org.pl Sat Dec 30 09:34:22 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 30 Dec 2000 09:34:22 GMT Subject: Haskell Language Design Questions References: <3233BEE02CB3D4118DBA00A0C99869401D61F7@hermes.pml.com> <20001230145004.A12063@hg.cs.mu.oz.au> Message-ID: Sat, 30 Dec 2000 14:50:04 +1100, Fergus Henderson pisze: > It's just something that didn't make it into Haskell 98. > Hugs and ghc offer a language extension for that. > It will almost certainly be in the next revision of Haskell. See > . Existential quantification is not always necessary to obtain an equivalent of dynamic binding. Dynamic binding is often used instead of function closures or IO action closures, especially in languages which lack real closures. An object of the abstract type "output IO stream" is equivalent to a record (tuple, whatever) of values of types like Char -> IO () -- write a character String -> IO () -- write a string IO () -- flush IO () -- close "Dynamic binding" is a fancy way of saying that the function to be called will be chosen at runtime. So we have exactly this, expressed in a simpler way. OO languages provide subtyping and inheritance. This is harder. Subtyping done by explicit coercions up can be done, but it's tedious to write (my new record scheme proposal tries to help here), and it's impossible to coerce down. Inheritance can be done by delegation. It does not work to express everything like OO languages usually do, because they are not typesafe. That's why (IMHO) that OO languages are usually dynamically typed. OO-like subtyping is usually not able to accurately express binary methods or the requirement that an argument must provide several interfaces at once. Haskell's classes should be left for constraints on types (as opposed to values). I want to sort a list, I compare elements with each other. It does not make sense to say that an element is comparable. Comparable with what? A _type_ can be comparable (i.e. ordered), or the ordering itself may be expressed as an object, but it does not belong to objects being compared. It follows that it does not make sense to have "a heterogeneous collection of comparable objects" or casting an object up to the type "comparable". But I might not care if the fact that something is a stream open for writing is a property of its type which is not statically known (as when stream is modelled as a class) or a property of all objects of the given type which is concrete (as when stream is modelled as a record of functions) - because I usually work with one such object at a time. When it's expressed as a class, I gain the possibility of extracting from the same object at different places properties belonging to different interfaces, without explicit coercions. But it is necessary to use existential quantification for heterogeneous collections. When it's expressed as a record of functions, all streams are flattened to a single interface, it is more convenient to use but the information about the exact kind of stream is not available. These approaches can be mixed. With my new record scheme proposal it is more convenient to introduce a class of types of objects from which the interface of a stream open for writing (expressed as a record of functions) can be extracted. This class needs not to be explicitly defined (only the record of functions). Stream operations can also be seen as provided by the object itself instead of always going through the extracted interface. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From R.Daniel@Europe.com Sat Dec 30 15:16:30 2000 From: R.Daniel@Europe.com (R.Daniel) Date: Sat, 30 Dec 2000 15:16:30 +0000 Subject: The Hanoi Towers Message-ID: <5.0.0.25.2.20001230151115.009ef3a0@mail.ip.pt> --=====================_12490613==_.ALT Content-Type: text/plain; charset="us-ascii"; format=flowed hi, i was looking for the source code for the Hanoi Towers, if anyone has that, could you please send it to me? I apreciate the help , thankx ----->R.Daniel Aka AZONIC ICQ 28959546 --=====================_12490613==_.ALT Content-Type: text/html; charset="us-ascii" hi, i was looking for the source code for the Hanoi Towers, if anyone has that, could you please send it to me?

I apreciate the help , thankx

----->R.Daniel Aka AZONIC
        ICQ           28959546 --=====================_12490613==_.ALT-- From qrczak@knm.org.pl Sat Dec 30 17:53:05 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 30 Dec 2000 17:53:05 GMT Subject: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?) References: <3A42661E.7FCCAFFA@tzi.de> <20001229003745.A11084@mark.ugcs.caltech.edu> Message-ID: Fri, 29 Dec 2000 00:37:45 -0800, John Meacham pisze: > http://www.cse.ogi.edu/~mpj/pubs/lightrec.html I've read it and posted some comments in February 2000. There was no answer AFAIR. Here are they again, slightly edited and extended: I don't understand why to separate kinds of rows and record types, instead of having "a type which is known to be a record type", at least on the level visible for the programmer. So instead of type Point r = (r | x::Int, y::Int) type Colored r = (r | c::Color) type ColoredPoint r = Point (Colored r) p :: {ColoredPoint()} -- Point, Colored, ColoredPoint :: row -> row it would be type Point r = {r | x::Int, y::Int} type Colored r = {r | c::Color} type ColoredPoint r = Point (Colored r) p :: ColoredPoint() -- Point, Colored, ColoredPoint :: recordType -> recordType -- where recordType is something like a subkind of *. -------- It is bad to require the programmers to think in advance that a type is going to be subtyped, and write elaborated type Point r = (r | x::Int, y::Int) ... {Point()} ... instead of simpler type Point = {x::Int, y::Int} ... Point ... which is not extensible. -------- I got used to () as a unit type. It would be a pity to lose it. -------- A minor problem. If tuples are records, field names should be such that alphabetic order gives the sequential order of fields, or have a special rule of field ordering for names of tuple fields... -------- In general I don't quite like the fact that records are getting more anonymous. Magical instances of basic classes? How inelegant. If I want the record type to have an identity, it will have to be wrapped in a newtype, so I must think at the beginning if I will ever want to write specialized insances for it and then all the code will depend on the decision. Currently a datatype with named fields has both an identity and convenient syntax of field access. (And why newtype is not mentioned in section 5.1?) I like name equivalence where it increases type safety. Extensible records promote structural equivalence. Unfortunately the proposal seems to increase the number of irregularities and inelegant rules... If expr.Constructor for a multiparameter constructor yields a tuple, then for an unary constructor it should give a 1-tuple, no? I know it would be extremely inconvenient, especially as newtypes are more used, so I don't propose it, but it is getting less regular. What about nullary constructors - empty tuple? :-) I don't say that I don't like the proposal at all, or that I never wanted to have several types with the same field names. But it is not clean for me, it's a compromise between usability and elegance, and from the elegance point of view I like current records more. Maybe it would be helpful to show how to translate a program with extensible records to a program without them (I guess it's possible in a quite natural way, but requires global transformation of the whole program). -------- Extensible records makes a syntactic difference between field access and function call. So if one wants to export a type abstractly or simply to provide functions operating on it without fixing the fact that they are physically fields, he ends in writing functions like size:: MyRecord -> Int size x = x.MyRecord.size which are unnecessary now, even if size is simply a field. It reminds me of C++ which wants us to provide methods for accessing data fields (for allowing them to be later redefined as methods, and for allowing everything to be uniformly used with "()" after the feature name). Ugh. -------- My new record scheme proposal does not provide such lightweight extensibility, but fields can be added and deleted in a controlled way if the right types and instances are made. The distinction between having a field and having a supertype is blurred. Similarly between having itself a field called foo and having a supertype which has a field called foo. Similarly between creating a record by adding fields to another record and creating a record by putting another record as one of fields. Similarly between casting to a supertype by removing some fields and extracting the supertype represented by a field. An advantage is that the interface of records does not constrain the representation in any way. It's up to how instances are defined, with the provision of natural definitions for records implemented physically as product types. For example supplying a color for a colorless point and the reverse operation can be written thus: addColor :: (Record cp, cp.point :: p, cp.color :: Color) => p -> Color -> cp addColor p c = record point = p; color = c removeColor :: (cp.point :: p) => cp -> p removeColor = (.point) When the following definitions are present: data Point = record x, y :: Int data ColoredPoint = record point :: Point point (x, y) color :: Color these functions can be used as of types addColor :: Point -> Color -> ColoredPoint removeColor :: ColoredPoint -> Point A colored point can be constructed either as in addColor, from a point and a color, or thus: record x = ... y = ... color = ... If ColoredPoint were defined directly as data ColoredPoint = record x, y :: Int color :: Color the previous interface could be *retroactively* reconstructed thus: instance (ColoredPoint).point :: Point where cp.point = record x = cp.x; y = cp.y cp.record {point = p} = cp.record x = p.x; y = p.y Multiple inheritance can be modelled as well. And field renaming during inheritance. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTĘPCZA QRCZAK From kahl@heraklit.informatik.unibw-muenchen.de Fri Dec 22 16:04:45 2000 From: kahl@heraklit.informatik.unibw-muenchen.de (Wolfram Kahl) Date: 22 Dec 2000 16:04:45 -0000 Subject: 2nd CFP: RelMiS 2001 Message-ID: <20001222160445.29431.qmail@heraklit.informatik.unibw-muenchen.de> [please post. apologies for multiple copies] SECOND CALL FOR PAPERS RelMiS 2001 - Relational Methods in Software ============================================ 7-8 April 2001, Genova, Italy http://ist.unibw-muenchen.de/RelMiS/ A Satellite Event to ETAPS 2001 Important Dates =============== Deadline for submission: 10 January 2001 Notification of acceptance: 9 February 2001 Final version due: 28 February 2001 Workshop dates: 7-8 April 2001 Workshop Topics =============== * Relational Specifications and Modelling: methods and tools, tabular methods, abstract data types * Relational Software Design and Development Techniques: relational refinement, heuristic approaches for derivation, correctness considerations, dynamic programming, greedy algorithms, catamorphisms, paramorphisms, hylomorphisms and related topics * Programming with Relations: prototyping, testing, fault tolerance, information systems, information coding * Implementing relational algebra with mixed representation of relations * Handling of Large Relations: problems of scale, innovative representations, distributed implementation Submissions =========== Submissions will be evaluated by the Program Committee for inclusion in the proceedings, which will be published in the ENTCS series. Papers must contain original contributions, be clearly written, and include appropriate reference to and comparison with related work. Papers should be submitted electronically as uuencoded PostScript files at the address relmis@ist.unibw-muenchen.de. Preference will be given to papers that are no shorter than 10 and no longer than 15 pages. A separate message should also be sent, with a text-only one-page abstract and with mailing addresses (both postal and electronic), telephone number and fax number of the corresponding author. Final versions will have to be submitted as LaTeX source and have to adhere to the ENTCS style! Programme Committee =================== Rudolf Berghammer (Kiel), Jules Desharnais (Quebec), Wolfram Kahl (Munich), David L. Parnas (Hamilton), Gunther Schmidt (Munich) ------------- E-Mail: relmis@ist.unibw-muenchen.de Workshop home page: URL: http://ist.unibw-muenchen.de/RelMiS/