From venneri@dsi.unifi.it Mon Oct 9 19:19:30 2000 Date: Mon, 9 Oct 2000 14:19:30 -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.
Affiliated workshops will be scheduled from  September 2 through September 8.

Researchers and practitioners are invited to submit workshop proposals,
that may be sent to the PLI 2001 Workshop Chair
Betti Venneri, venneri@dsi.unifi.it,
by e-mail (Postscript, Pdf, ASCII) 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),
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.

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.


web page:   http://music.dsi.unifi.it/pli01/wkshops




From fldrsimonmar@microsoft.com Mon Oct 9 10:54:52 2000 Date: Mon, 9 Oct 2000 02:54:52 -0700 From: Simon Marlow fldrsimonmar@microsoft.com Subject: Mailing list software changing
Dear Haskell & Haskell-cafe,

At haskell.org we're migrating the mailing lists from majordomo (which is
somewhat old and clunky) to Mailman, which will amongst other things make my
life a lot easier, provide better archives, add digest support and allow
subscription/unsubscription via a web interface.

You should all receive a notification shortly about subscription to the new
lists.  Unfortunately it seems we have to do this, because the confirmation
contains the password for accessing & modifying your personal subscription
details on the web.  If you *don't* receive a confirmation in the next 24
hours, please let me know.

Heres hoping everything goes smoothly, and once again I apologise for the
extra spam in your mailbox.

Cheers,
	Simon


From mpj@cse.ogi.edu Tue Oct 10 03:26:00 2000 Date: Mon, 9 Oct 2000 19:26:00 -0700 From: Mark P Jones mpj@cse.ogi.edu Subject: type class
Hi Zhanyong,

| In Haskell, instances of a type class can only be well-formed type
| constructors ...
| Note there is no type constructor abstraction.
|=20
| In practice, I found this rule too restrictive.

There are good reasons for the restrictions that were alluded to in
my constructor classes paper, and again in Typing Haskell in Haskell.
Some text from emails written when this topic came up previously is
attached to the end of this message.

Actually, the first part of the attached email deals with a different
problem (making Set an instance of Monad), but since that also came
up for discussion again quite recently, I don't think it will hurt to
include it again here.

| How about extending TC with a branch for abstraction:
|=20
| TC ::=3D ...
|      | /\a. TC  -- abstraction
|=20
| This is too powerful and will get out of control -- we surely don't =
want
| to give TC the full power of lambda-calculus.  So let's impose a
| restriction: in /\a.TC, a must occur free in TC *exactly once*.  This
| way, abstraction can only be used to specify with respect to which
| argument a partial application is.  (or I think so -- I haven't tried =
to
| prove it.)

My instinct (which perhaps somebody will prove incorrect) is that this =
will
not help.  Suppose, for example, that you needed to unify ([a],[b]) with =
f c
as part of the type inference process.  How would you solve this =
problem?
Alas, there are several different, and incompatible ways:

   ([a], [b]) =3D  (/\a. ([a],[b])) a
              =3D  (/\b. ([a],[b])) b
              =3D  (/\c. (c, [b])) [a]
              =3D  (/\d. ([a], d)) [b]
              =3D  (/\e. e) ([a], [b])

Note that the /\-terms in each of these examples satisfies your =
restriction.
So I don't think you'll be able to obtain most general unifiers or =
principal
types with this restriction.

In my opinion, Dale Miller's work on Higher-order patterns (introduced, =
I think
in about 1991, but I don't have references) would probably be the best =
starting
point for serious experimentation in this area.

Hope this helps,
Mark


-- From the archives: =
-------------------------------------------------------
Hi Michael,

| "...type synonyms must be fully applied".  I think the above
| example is a valid objection to this.

I'll append some text that I wrote on a previous occasion when somebody
asked why type synonyms couldn't be partially applied.  I hope that it
will help to explain why the restriction is not easy to lift, however
desirable it might be.  The example there was a little different, but
I'm sure that you'll see the correspondence.

| The other example of something that I want to declare as a monad, but
| which I can not is this:  Consider a type of collection of some sort =
that
| requires the types of the elements to be instances of some specific =
class.

This too is a problem that has come up quite a few times in the past.
As yet, I'm not sure that anyone has a definitive answer for it either,
although the work that John Hughes presented at the Haskell workshop on
Restricted Datatypes is perhaps the closest that anyone has come so far.
A general problem here is that there are differences between =
conventional
mathematics---where you can have sets of any type---and the mathematics =
of
programming languages---where interesting set datatypes can only be
constructed on types whose elements have, at least, an equality.  In =
Haskell
terms, mathematics has an equality function of type: forall a. a -> a -> =
Bool;
the same operator is available to mathematicians who reason about =
Haskell
programs.  But Haskell programmers have to make do with a more =
restrictive
operator of type forall a. Eq a =3D> a -> a -> Bool.  (Which is not =
actually
an equality operator at all when you look at what's really going on; =
it's
just a kind of identity function or projection!)

All the best,
Mark
=20
Here's the text I promised:

| I'd like to use monadic code on the following type
|     type IOF b a =3D b -> IO a
| The following seemed reasonable enough:
|     instance Monad (IOF b) where ...
| But Hugs and GHC both object ...

The example is rejected because type synonyms can only be used if a
full complement of arguments has been given.  There are at least two
kinds of problem that can occur if you relax this restriction, but
both are related to unification/matching.

Suppose that we allow your definition.  And suppose that we also allow:
  instance Monad ((->) env) where ...
which is a perfectly reasonable thing to do (it's the reader monad).
Now what should we do when faced with the problem of unifying two
type expressions like:  m c  and  b -> IO a ... Haskell unifies these
with the substitution:  {m +-> ((->) b), c +-> IO a}, but with your
instance decl, you might have preferred { m +-> IOF b, c +-> a }.
In other words, it's ambiguous, and the choice between these two could
change the semantics because you'll end up picking different instances
depending on which choice you make.

Or consider what you really mean when you write (IOF b) ... my guess
is that you're thinking of it as adding a kind of lambda, so that

   IOF b =3D \a. a -> IO b

This is appealing, but also means that we'd need to move up to =
higher-order
unification which is undecidable and non-unitary.  For example, now
we could match m c  to  b -> IO a  in all kinds of interesting ways:

     b -> IO a  =3D  (\b . b -> IO a) b
                =3D  (\a . b -> IO a) a
                =3D  (\z . b -> z) (IO a)
                =3D  (\z . b -> IO a) Int
                =3D  ...

Now we really have ambiguity problems to worry about!

Requiring type synonyms to be fully applied --- in effect, telling us
that a synonym is nothing more than an abbreviation, and has no other
consequences for the semantics --- seems like a nice way to avoid these
problems.

-------------------------------------------------------------------------=
---



From zhanyong.wan@yale.edu Wed Oct 11 14:53:52 2000 Date: Wed, 11 Oct 2000 09:53:52 -0400 From: Zhanyong Wan zhanyong.wan@yale.edu Subject: type class
Hi Mark,

Thanks for the references you provided!

Mark P Jones wrote:

> My instinct (which perhaps somebody will prove incorrect) is that this will
> not help.  Suppose, for example, that you needed to unify ([a],[b]) with f c
> as part of the type inference process.  How would you solve this problem?
> Alas, there are several different, and incompatible ways:
> 
>    ([a], [b]) =  (/\a. ([a],[b])) a
>               =  (/\b. ([a],[b])) b
>               =  (/\c. (c, [b])) [a]
>               =  (/\d. ([a], d)) [b]
>               =  (/\e. e) ([a], [b])
> 
> Note that the /\-terms in each of these examples satisfies your restriction.
> So I don't think you'll be able to obtain most general unifiers or principal
> types with this restriction.

Let's put your example into the context of type classes:

	class T f c where
	  method :: f c

Now when we want to use method as a ([a],[b]), ambiguity arises, as you
suggested.

However, I think this just means we should allow *at most one* of the
following instances to be declared:

	instance T (/\a. ([a],[b])) a
        instance T (/\b. ([a],[b])) b
        instance T (/\c. (c, [b])) [a]
        instance T (/\d. ([a], d)) [b]
        instance T (/\e. e) ([a], [b])

In other words, the above instances are considered overlapping.
____________________________________________________
|  As long as we only have one of these instances  |
|  in the program, there is no ambiguity.          |
----------------------------------------------------

I'm sure there must be other ramifications (e.g. maybe now whether two
instances are overlapping becomes undecidable -- I haven't thought over
it yet), but it seems worth further investigation.

-- Zhanyong


From senganb@ia.nsc.com Thu Oct 12 21:11:16 2000 Date: Thu, 12 Oct 2000 16:11:16 -0400 From: Sengan senganb@ia.nsc.com Subject: How does one find lazyness bottlenecks?
Now that ghc 4.08 has a time profiler, I've been improving a program
I wrote over the last year. However now the GC time dominates the
execution time (>60%). I can see that my program is not being lazy,
but I have no idea why. How can I use profiling (or any other means)
to determine where my program is not being sufficiently lazy? Are there
papers on such things I could read?

Sengan


From fjh@cs.mu.oz.au Fri Oct 13 01:49:05 2000 Date: Fri, 13 Oct 2000 11:49:05 +1100 From: Fergus Henderson fjh@cs.mu.oz.au Subject: How does one find lazyness bottlenecks?
On 12-Oct-2000, Sengan <senganb@ia.nsc.com> wrote:
> Now that ghc 4.08 has a time profiler, I've been improving a program
> I wrote over the last year. However now the GC time dominates the
> execution time (>60%). I can see that my program is not being lazy,
> but I have no idea why.

What makes you think that the GC time is due to insufficient laziness?
My first thought is that high GC times may well be due to the opposite,
too much laziness.  Being lazy means that you create closures to represent
unevaluated expressions, and those closures will eventually need to be
garbage collected.

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


From chak@cse.unsw.edu.au Fri Oct 13 05:16:48 2000 Date: Fri, 13 Oct 2000 15:16:48 +1100 From: Manuel M. T. Chakravarty chak@cse.unsw.edu.au Subject: How does one find lazyness bottlenecks?
Sengan <senganb@ia.nsc.com> wrote,

> Now that ghc 4.08 has a time profiler, I've been improving a program
> I wrote over the last year. However now the GC time dominates the
> execution time (>60%). I can see that my program is not being lazy,
> but I have no idea why. How can I use profiling (or any other means)
> to determine where my program is not being sufficiently lazy? Are there
> papers on such things I could read?

If GC times dominates, you probably have a space leak.  So,
you should use space profiling to determine where the leak
is.  Depending on what kind of program you have, it is often
also informative to check the space profiles for different
kinds of inputs, as the leak might only occur for certain
inputs.  Depending on the code exercised by the inputs
triggering the leak, you might get a rough idea which parts
of your program leak.

Cheers,
Manuel



From sylvan@ravinet.com Fri Oct 13 11:18:26 2000 Date: Fri, 13 Oct 2000 13:18:26 +0300 (EEST) From: Sylvan Ravinet sylvan@ravinet.com Subject: Haskell to XSLT?
Hello,

I was wondering if there are ways to translate Haskell code to XSLT. Any
ideas?

Thank you for your help,

Best regards,

-Sylvan
-- 
No, try not. Do, or do not. There's no try. -Yoda
Sylvan Ravinet: http://www.ravinet.com/sylvan/contact/ -- This message is
Copyright 2000 by Sylvan Ravinet. All rights (and responsibility) reserved.



From luti@linkexpress.com.br Fri Oct 13 22:42:24 2000 Date: Fri, 13 Oct 2000 18:42:24 -0300 From: Luciano Caixeta Moreira luti@linkexpress.com.br Subject: (no subject)
This is a multi-part message in MIME format.

------=_NextPart_000_0035_01C03545.53E7F560
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable

unsubscribe haskell@haskell.org

------=_NextPart_000_0035_01C03545.53E7F560
Content-Type: text/html;
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable

<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.0 Transitional//EN">
<HTML><HEAD>
<META http-equiv=3DContent-Type content=3D"text/html; =
charset=3Diso-8859-1">
<META content=3D"MSHTML 5.50.4134.100" name=3DGENERATOR>
<STYLE></STYLE>
</HEAD>
<BODY bgColor=3D#ffffff>
<DIV><FONT face=3DArial><FONT size=3D2>unsubscribe </FONT><A=20
href=3D"mailto:haskell@haskell.org"><FONT=20
size=3D2>haskell@haskell.org</FONT></A></FONT></DIV></BODY></HTML>

------=_NextPart_000_0035_01C03545.53E7F560--



From romildo@urano.iceb.ufop.br Sat Oct 14 05:38:09 2000 Date: Sat, 14 Oct 2000 02:38:09 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: Haskore and nhc98
Hello.

I am just curious whether anybody has already
tried Haskore (http://www.haskell.org/haskore/)
with the NHC98 Haskell compiler. I am trying to
do it, while GHC 4.08.1 is non functional in my
RH Linux 7.0 box.

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


From romildo@urano.iceb.ufop.br Sat Oct 14 06:48:06 2000 Date: Sat, 14 Oct 2000 03:48:06 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: Binary files and NHC98
--wRRV7LY7NUeQGEoC
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit

Hello.

In order to experiment with the Binary module
distributed with nhc98, I wrote the attached
program which writes a binary file and then
reads it. When executed, I got an extra
byte (8) that I cannot explain:

	[65,66,67,68,8]

Any clues why it appears?

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

--wRRV7LY7NUeQGEoC
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="BinaryFile.hs"

module Main where

import IO (IOMode(ReadMode,WriteMode))
import Binary (openBin,closeBin,getBits,putBits,isEOFBin,
               BinIOMode(RO,WO),BinLocation(File),BinHandle)

-- convert from IOMode to BinIOMode
ioModeToBinIOMode           :: IOMode -> BinIOMode
ioModeToBinIOMode ReadMode   = RO
ioModeToBinIOMode WriteMode  = WO

-- open a binary file
openBinaryFile          :: FilePath -> IOMode -> IO BinHandle
openBinaryFile path mode = openBin (File path (ioModeToBinIOMode mode))

-- write a list of integers (8 bits) to binary file
writeBinaryFile   	:: FilePath -> [Int] -> IO ()
writeBinaryFile fileName xs =
    do f <- openBinaryFile fileName WriteMode
       let writeToBin [] = return ()
           writeToBin (x:xs) = do putBits f 8 x
                                  writeToBin xs
       writeToBin xs
       closeBin f

-- read a list of integers (8 bits) from binary file
readBinaryFile  :: FilePath -> IO [Int]
readBinaryFile fileName =
    do f <- openBinaryFile fileName ReadMode
       let readFromBin = do eof <- isEOFBin f
                            if eof
                               then return []
                               else do x <- getBits f 8
                                       xs <- readFromBin
                                       return (x:xs)
       xs <- readFromBin
       closeBin f
       return xs

-- test the above
main = do writeBinaryFile "test.bin" [65,66,67,68]
          xs <- readBinaryFile "test.bin"
          putStrLn (show xs)

--wRRV7LY7NUeQGEoC--


From romildo@urano.iceb.ufop.br Sat Oct 14 08:49:52 2000 Date: Sat, 14 Oct 2000 05:49:52 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: NHC98 and GHC 4.08.1 differ on monad related functions
--4Ckj6UjgE2iN1+kY
Content-Type: text/plain; charset=iso-8859-1
Content-Disposition: inline
Content-Transfer-Encoding: 8bit

Hello.

While porting Haskore to NHC98 I got an error
I am not understanding. I have attached a test
module that shows the error message:

$ nhc98 -c Test.hs

====================================
        Error after type deriving/checking:
No default for  Monad.MonadPlus at 7:1.(171,[(2,209)])
No default for  Monad.MonadPlus at 6:1.(174,[(2,208)])

GHC 4.08.1 and Hugs98 accepts the code without
complaining.

Any hints?

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

--4Ckj6UjgE2iN1+kY
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="Test.hs"

module Test where

import Monad

zeroOrMore, oneOrMore :: MonadPlus m => m a -> m [a]
zeroOrMore m      = return [] `mplus` oneOrMore m
oneOrMore  m      = do { a <- m; as <- zeroOrMore m; return (a:as) }


--4Ckj6UjgE2iN1+kY--


From nikhil@acm.org Mon Oct 16 09:21:39 2000 Date: Mon, 16 Oct 2000 01:21:39 -0700 From: Rishiyur S. Nikhil nikhil@acm.org Subject: Haskell puzzle
In Haskell, is the following transformation always legal?

    \x->\y->e     transforms to    \x y->e

After answering this question, please scroll down about 75 lines for a
follow-up question.











































































What if the two lambda-bound variables are the same?  I.e., the lhs is

    \x->\x->e

Please refer to Section 3.3 of the Haskell 98 Report, para 3 (one line
para).


From timd@macquarie.com.au Tue Oct 17 02:30:58 2000 Date: Tue, 17 Oct 2000 12:30:58 +1100 (EST) From: Timothy Docker timd@macquarie.com.au Subject: Mutually recursive structures
The following problem has been taxing me....

I have a list of pairs that I have parsed from a input file, which
represent a hiirarchy, where the first element is the name of the object,
and the second is the name of the parent if there is one:

     type ParseOutput = [(String,Maybe String)]


I wish to convert this to a list of "objects", where from each object I can
navigate to the parent object (if any), or the children (if any):

    data Obj = Obj { name::String,
                     parent::(Maybe Obj),
                     children::[Obj] }

    type Result = [Obj]

    convert:: ParseOutput -> Result

In a language with mutable references, this would be a relatively
straightforward. I would just create a dictionary mapping from name to
Obj, and then iterate over them, filling in the parents and children
where appropriate.

    odict = {}
    for (name,parent) in parseOutput:
        odict[name] = Obj()

    for (name,parent) in parseOutput:
        if parent:
            parent = odict[parent]
            child  = odict[name]
            child.parent = parent
            parent.children.append( child )

This gives away my background! How can I do this in Haskell? If I
don't have mutable references, I figure that I must need to use
laziness in some way, perhaps similar to how I would build an infinite
structure.

A hint or two would be great.

Tim


From Tom.Pledger@peace.com Tue Oct 17 04:32:13 2000 Date: Tue, 17 Oct 2000 16:32:13 +1300 (NZDT) From: Tom Pledger Tom.Pledger@peace.com Subject: Mutually recursive structures
Timothy Docker writes:
 > [...] How can I do this in Haskell? If I don't have mutable
 > references, I figure that I must need to use laziness in some way,
 > perhaps similar to how I would build an infinite structure.

http://www.mail-archive.com/haskell@haskell.org/msg06321.html

I have nothing to add to that explanation, so will conserve
bandwidth by


From christian@lescher.de Tue Oct 17 20:29:25 2000 Date: Tue, 17 Oct 2000 20:29:25 +0100 From: Christian Lescher christian@lescher.de Subject: Haskell function with String arguments in DLL
I'm trying to build a DLL with a Haskell function of type String ->
String, that should be called from outside (e.g. VBA), but it still
doesn't work.

I'm afraid I need an example or some kind of 'step by step instruction'.
Who can help me? (I use GHC 4.08.1.)

Christian




From timd@macquarie.com.au Tue Oct 17 22:25:58 2000 Date: Wed, 18 Oct 2000 08:25:58 +1100 (EST) From: Timothy Docker timd@macquarie.com.au Subject: Mutually recursive structures
Tom Pledger writes:

 > Timothy Docker writes:
 >  > [...] How can I do this in Haskell? If I don't have mutable
 >  > references, I figure that I must need to use laziness in some way,
 >  > perhaps similar to how I would build an infinite structure.
 > 
 > http://www.mail-archive.com/haskell@haskell.org/msg06321.html
 > 

To be honest, I found this code quite confusing, I think because
of the way in which a the "tail" needs to be joined back to the
"head" in creating a circular data structure.

I did eventually come up with a solution that seems straightforward
enough, although I have no idea of its efficiency...

  | type ParseOutput = [(String,Maybe String)]
  | 
  | data Obj = Obj { oname::String,
  | 		 oparent::(Maybe Obj),
  | 		 ochildren::[Obj] }
  | 
  | convert:: ParseOutput -> [Obj]
  | convert output = converted
  |     where converted = map mkObj output
  | 	  mkObj (name,parent) = (Obj name
  | 				     (fmap (findObj converted) parent)
  | 				     (filter (hasParentNamed name) converted) )
  | 
  | findObj:: [Obj] -> String  -> Obj
  | findObj [] name      = error ("No object with name "++name)
  | findObj (o:os) name  | name == (oname o) = o
  | 		     | otherwise         = findObj os name
  | 
  | hasParentNamed :: String -> Obj -> Bool
  | hasParentNamed name obj = maybe False ((==name).oname) (oparent obj)
  | 

Thanks for the pointer.

Tim


From koen@cs.chalmers.se Wed Oct 18 11:57:56 2000 Date: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST) From: Koen Claessen koen@cs.chalmers.se Subject: Num class
Hi all,

For years I have wondered why the Num class has the Eq class
and the Show class as super classes.

Because of this, I cannot make functions an instance of Num
(becuase they are not in Eq or Show). Or a datatype
respresenting an infinite amount of digits (because Eq would
not make any sense).

Now I have found out the reason!

However, it does not make me happy, it makes me even more
sad.

It is of the defaulting mechanism of course! The defaulting
mechanism works as follows: If there is an unresolved
overloading error on a type variable a, which has as an
*only* constraint (Num a), then we take a to be the suitable
default.

If Show were not a super class of Num, the following program
would generate an error:

  main = print 42

If Eq were not a super class, the following program would
not work:

  main = print (if 42 == 42 then "koe" else "apa")

These programs are all fixed by inserting Show and Eq as
super classes of Num. So that one does not even notice!

Until now.

I am interfacing to an external library that uses
double-precision floating points internally for all numbers.
This is to be as general as possible. However, I know that
when I put for example an Integer in, I get one out too.
Thus, I want to give a Haskell interface that can deal with
this by any numeric type. So I define a type class:

  class Num a => Number a where
    convertToDouble   :: a -> Double
    convertFromDouble :: Double -> a

(somehow the Haskell numerical hierarchy does not even let
me define general functions that do this! -- but that is
besides the point.)

  instance Number Int
  instance Number Integer
  instance Number Float
  instance Number Double
  ...

All my library functions now have the shape:

  libraryFunction :: Number a => ... a ...

Where as actually:

  primLibraryFunction :: ... Double ...

And now the bad thing... When I use "libraryFunction" on a
numeric constant, such as 42, I get the error:

  ERROR "library.hs" (line 8): Unresolved overloading
  *** Binding             : main
  *** Outstanding context : Number b

This is really annoying, and it is not clear why the default
mechanism works this way.

So here are my questions. Why does the default mechanism
have this restriction? I know that the default mechanism is
already broken (some desirable properties are destroyed) --
what properties will be broken by lifting this restriction?

/Koen.

--
Koen Claessen         http://www.cs.chalmers.se/~koen     
phone:+46-31-772 5424      mailto:koen@cs.chalmers.se
-----------------------------------------------------
Chalmers University of Technology, Gothenburg, Sweden



From p.turner@computer.org Wed Oct 18 12:37:38 2000 Date: Wed, 18 Oct 2000 07:37:38 -0400 From: Scott Turner p.turner@computer.org Subject: pronunciation of >>=
Is there a common way to pronounce ">>=" in discussions or when teaching?
I've learned all my Haskell from printed/visual documents.
--
Scott Turner
p.turner@computer.org       http://www.ma.ultranet.com/~pkturner


From d95lars@dtek.chalmers.se Wed Oct 18 12:43:34 2000 Date: Wed, 18 Oct 2000 13:43:34 +0200 (MEST) From: Lars Lundgren d95lars@dtek.chalmers.se Subject: pronunciation of >>=
On Wed, 18 Oct 2000, Scott Turner wrote:

> Is there a common way to pronounce ">>=" in discussions or when teaching?
> I've learned all my Haskell from printed/visual documents.

How about 'bind'? and ">>" => 'then'.

/Lars L




From qrczak@knm.org.pl Wed Oct 18 21:02:18 2000 Date: 18 Oct 2000 20:02:18 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: Num class
Wed, 18 Oct 2000 12:57:56 +0200 (MET DST), Koen Claessen <koen@cs.chalmers.se> pisze:

> The defaulting mechanism works as follows: If there is an unresolved
> overloading error on a type variable a, which has as an *only*
> constraint (Num a), then we take a to be the suitable default.

This is not what the Haskell 98 Report says. Section 4.3.4:

"In situations where an ambiguous type is discovered, an ambiguous
type variable is defaultable if at least one of its classes is a
numeric class (that is, Num or a subclass of Num) and if all of its
classes are defined in the Prelude or a standard library (Figures 6--7
show the numeric classes, and Figure 5 shows the classes defined in
the Prelude.)"

I see no good reason for Show superclass of Num.

Eq makes a little more sense, but could be dropped too. It would be
inferred separately when a numeric literal is used in a pattern.

I agree that the default mechanism is ugly, and that at least the
restriction about classes defined in standard libraries should
be removed.

Clean has per-class defaults. I don't know how conflicting defaults
coming from different class constraints should be solved, or what about
multiparameter classes, and whether extending the defaulting mechanism
is a good idea at all. But since we don't have anything better...

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



From mpj@cse.ogi.edu Wed Oct 18 22:46:24 2000 Date: Wed, 18 Oct 2000 14:46:24 -0700 From: Mark P Jones mpj@cse.ogi.edu Subject: Num class
This is a multi-part message in MIME format.

------=_NextPart_000_0001_01C03912.2FCECB10
Content-Type: text/plain;
	charset="iso-8859-1"
Content-Transfer-Encoding: quoted-printable

Hi Koen,

| If Show were not a super class of Num, the following program
| would generate an error:
|=20
|   main =3D print 42
|=20
| If Eq were not a super class, the following program would
| not work:
|=20
|   main =3D print (if 42 =3D=3D 42 then "koe" else "apa")
|=20
| These programs are all fixed by inserting Show and Eq as
| super classes of Num. So that one does not even notice!

Your claims are incorrect.  Both of these examples type check
without any errors, and regardless of whether Show and Eq are
included as superclasses of Num.  It is easy to verify this
using "Typing Haskell in Haskell" (http://www.cse.ogi.edu/~mpj/thih);
I'll attach the script that I used for this below.  Put this in
the same directory as all the other .hs files and load it into
Hugs.  Then edit StdPrel.hs to remove the superclasses of cNum,
(replace [cEq, cShow] with []), and it will still work.

| For years I have wondered why the Num class has the Eq class
| and the Show class as super classes.
|=20
| Because of this, I cannot make functions an instance of Num
| (because they are not in Eq or Show). Or a datatype
| representing an infinite amount of digits (because Eq would
| not make any sense).
|=20
| Now I have found out the reason!

I don't think you have.

I do not know the reason either, but I suspect that it is largely
historical; when Haskell was first designed, the only types that
people wanted to put in Num were also equality and showable types.
By making Eq and Show superclasses of Num, types could sometimes
be stated more concisely, writing things like (Num a) =3D> ... instead
of (Num a, Eq a, Show a) =3D> ...

In the past ten years since the Haskell class hierarchy was, more or
less, fixed, we've seen several examples of types that don't quite
fit (Like functions, computable reals, etc. which might make sense
in Num but not in Eq).  A natural conclusion is that several of the
superclass relations between classes should be removed.  But realize
that there is an unavoidable compromise here: generality versus the
convenience of shorter types.  I suggest that there is no point on
the spectrum that would keep everybody happy all the time.

| It is of the defaulting mechanism of course!
| ...

Defaulting is a red herring in trying to understand why Show
and Eq are superclasses of Num.  Marcin has already pointed
out that your description of the Haskell defaulting mechanism
is not correct by quoting from the Haskell report.  You can
find another description, again based on the report, in the
thih paper.

| So I define a type class:
|   class Num a =3D> Number a where
|     convertToDouble   :: a -> Double
|     convertFromDouble :: Double -> a
|...=20
| All my library functions now have the shape:
|   libraryFunction :: Number a =3D> ... a ...
| ...
| And now the bad thing... When I use "libraryFunction" on a
| numeric constant, such as 42, I get the error:
|=20
|   ERROR "library.hs" (line 8): Unresolved overloading
|   *** Binding             : main
|   *** Outstanding context : Number b
|=20
| So here are my questions. Why does the default mechanism
| have this restriction? I know that the default mechanism is
| already broken (some desirable properties are destroyed) --
| what properties will be broken by lifting this restriction?

Defaulting only kicks in if (a) at least one class is numeric,
and (b) all classes are standard.  Number is not a standard
class (you just defined it yourself), so defaulting will not
apply.  Defaulting was designed to work in this way so that
(i) it would catch and deal with the most common problems
occurring with numeric literals, and (ii) it would not be used
too often; defaulting is in general undesirable because it
can silently change the semantics.  Again, defaulting is an
example of a compromise in the design of Haskell.  Ideally,
you'd do without it all together, but if you went that way,
you'd end up having to write more type information in your
programs.  And again, I don't suppose there is a universally
satisfactory point on this spectrum.

All the best,
Mark

-------------------------------------------------------------------------=
---
mpj@cse.ogi.edu  Pacific Software Research Center, Oregon Graduate =
Institute
Want to do a PhD or PostDoc?   Interested in joining PacSoft?   Let us =
know!

------=_NextPart_000_0001_01C03912.2FCECB10
Content-Type: text/plain;
	name="SourceFortyTwo.hs"
Content-Transfer-Encoding: quoted-printable
Content-Disposition: attachment;
	filename="SourceFortyTwo.hs"

module SourceFortyTwo where

import Testbed
import HaskellPrims
import HaskellPrelude

-------------------------------------------------------------------------=
----
-- Test Framework:

main     :: IO ()
main      =3D test imports fortyTwo

saveList :: IO ()
saveList  =3D save "FortyTwo" imports fortyTwo

imports  :: [Assump]
imports   =3D defnsHaskellPrims ++ defnsHaskellPrelude

-------------------------------------------------------------------------=
----
-- Test Program:

fortyTwo :: [BindGroup]
fortyTwo
 =3D map toBg
   [[("main", Nothing, [([], ap [evar "print", elit (LitInt 42)])])],
    [("main'", Nothing,
     [([], ap [evar "print",=20
               eif (ap [econst eqMfun, elit (LitInt 42), elit (LitInt =
42)])
                   (elit (LitStr "koe"))
                   (elit (LitStr "apa"))])])]]

-------------------------------------------------------------------------=
----

------=_NextPart_000_0001_01C03912.2FCECB10--



From senganb@ia.nsc.com Thu Oct 19 01:31:02 2000 Date: Wed, 18 Oct 2000 18:31:02 -0600 (MDT) From: Sengan Baring-Gould senganb@ia.nsc.com Subject: mapM/concatMapM
mapM seems to be a memory hog (and thus also concatMapM). In the following eg:

> main = mapM print ([1..102400] :: [Integer])

memory usage climbs to 1.6M with ghc and needs -K20M, whereas with

> main = print ([1..102400] :: [Integer])

memory usage is only 1300 bytes. 

I instrumented mapM:

> main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer])

> mapM2             :: Monad m => (a -> m b) -> [a] -> m [b]
> mapM2 f []         = return []
> mapM2 f (c:cs)     = _scc_ "a" (>>=) (_scc_ "d" f c) (\x ->
>                      _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs ->
>                      _scc_ "f" return (x:xs)))

and found that a and b were the worst heap users (according to hp2ps),
ie the two >>='s

Why is this so? What can I do about it? My code uses mapM pretty extensively,
and I think its suffering from this problem. I notice that ghc does not seem
to use mapM except in 2 modules.

Another odd thing is that hp2ps says that a & b are the culprits, but the
-p and -px options say p is. Why?

Sengan


From jenglish@flightlab.com Thu Oct 19 03:03:05 2000 Date: Wed, 18 Oct 2000 19:03:05 -0700 From: Joe English jenglish@flightlab.com Subject: mapM/concatMapM
senganb@ia.nsc.com (Sengan Baring-Gould) wrote:

> mapM seems to be a memory hog (and thus also concatMapM).
> In the following eg:
> 
> > main = mapM print ([1..102400] :: [Integer])
> 
> memory usage climbs to 1.6M with ghc and needs -K20M

As a guess: since 'mapM print ([1..102400] :: [Integer])'
has type 'IO [()]', perhaps the result of the IO operation --
a list of 100K empty tuples -- is the culprit, even though
the result is never used.

Does 'mapM_ print ... ' (:: IO ()) perform any better?


--Joe English

  jenglish@flightlab.com


From senganb@ia.nsc.com Thu Oct 19 05:09:21 2000 Date: Wed, 18 Oct 2000 22:09:21 -0600 (MDT) From: Sengan Baring-Gould senganb@ia.nsc.com Subject: mapM/concatMapMy
> 
> 
> senganb@ia.nsc.com (Sengan Baring-Gould) wrote:
> 
> > mapM seems to be a memory hog (and thus also concatMapM).
> > In the following eg:
> > 
> > > main = mapM print ([1..102400] :: [Integer])
> > 
> > memory usage climbs to 1.6M with ghc and needs -K20M
> 
> As a guess: since 'mapM print ([1..102400] :: [Integer])'
> has type 'IO [()]', perhaps the result of the IO operation --
> a list of 100K empty tuples -- is the culprit, even though
> the result is never used.
> 
> Does 'mapM_ print ... ' (:: IO ()) perform any better?

Yes, but in the following eg

> main = print $ sum x
> x = _scc_ "x" [1..102400] :: [Integer]

x takes 1M allocations, and I would think that () would be smaller than
an Integer. Therefore I'm not sure that is the reason. The sum is there to
force the evaluation.

Sengan


From senganb@ia.nsc.com Thu Oct 19 05:34:01 2000 Date: Wed, 18 Oct 2000 22:34:01 -0600 (MDT) From: Sengan Baring-Gould senganb@ia.nsc.com Subject: mapM/concatMapMy
> > senganb@ia.nsc.com (Sengan Baring-Gould) wrote:
> > 
> > > mapM seems to be a memory hog (and thus also concatMapM).
> > > In the following eg:
> > > 
> > > > main = mapM print ([1..102400] :: [Integer])
> > > 
> > > memory usage climbs to 1.6M with ghc and needs -K20M
> > 
> > As a guess: since 'mapM print ([1..102400] :: [Integer])'
> > has type 'IO [()]', perhaps the result of the IO operation --
> > a list of 100K empty tuples -- is the culprit, even though
> > the result is never used.
> > 
> > Does 'mapM_ print ... ' (:: IO ()) perform any better?
> 
> Yes, but in the following eg
> 
> > main = print $ sum x
> > x = _scc_ "x" [1..102400] :: [Integer]
> 
> x takes 1M allocations, and I would think that () would be smaller than
> an Integer. Therefore I'm not sure that is the reason. The sum is there to
> force the evaluation.

Assuming you are right, why do I see the same 1.6M profile with:

> main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) >> return ()

> mapM2             :: Monad m => (a -> m b) -> [a] -> m [b]
> mapM2 f []         = return []
> mapM2 f (c:cs)     = _scc_ "a" (>>=) (_scc_ "d" f c) (\x ->
>                      _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs ->
>                      _scc_ "f" return (x:xs)))

Is >>= not lazy?

Sengan


From senganb@ia.nsc.com Thu Oct 19 07:11:29 2000 Date: Thu, 19 Oct 2000 00:11:29 -0600 (MDT) From: Sengan Baring-Gould senganb@ia.nsc.com Subject: mapM/concatMapMy
Actually I think I figured it out:

   (>>=) (f c) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (>>=) _(f c)_ (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (>>=) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (\(MN c1) \fc2 -> MN $ \s0 -> let (r1,io1,s1) = c1  s0
                                     (  MN c2  ) = fc2 r1
                                     (r2,io2,s2) = c2  s1 in (r2,io1 >> io2,s2))
   (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs)))
-> (MN $ \s0 -> let (r1,io1,s1) = c1  s0
                    (  MN c2  ) = (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) r1
                    (r2,io2,s2) = c2  s1 in (r2,io1 >> io2,s2))
-> (MN $ \s0 -> let (r1,io1,s1) = c1  s0
                    (  MN c2  ) = (>>=) (mapM f cs) (\xs -> return (r1:xs))
                    (r2,io2,s2) = c2  s1 in (r2,io1 >> io2,s2))
-> (MN $ \s0 -> let (r1,io1,s1) = c1  s0
                    (  MN c2  ) = (>>=) (mapM f cs) (\xs -> return (r1:xs))
                    (r2,io2,s2) = c2  s1 in (r2,io1 >> io2,s2))
-> (MN $ \s0 -> let (r1,io1,s1) = c1  s0
                    (  MN c2  ) = (>>=) (mapM f cs) (\xs -> return (r1:xs))
                    (r2,io2,s2) = c2  s1 in (r2,io1 >> io2,s2))

So the "return (r1:xs)" will only happen once the whole mapM has completed,
leaving, if I only use r1 at first, a whole load of partially evaluated
iterations of mapM in the heap.

This also means that sequences such as "mapM x >>= mapM y >>= mapM z" are very
inefficient and should be replaced by mapM (z.y.x) whereever possible.

Agreed?

Sengan


From xvw@trinity.warande.net Thu Oct 19 22:24:13 2000 Date: Thu, 19 Oct 2000 23:24:13 +0200 (CEST) From: xander xvw@trinity.warande.net Subject: hugs/ghc + shared mem access
Hi,

I'm exploring my options to connect 2 programs (1 Haskell, 1 non-Haskell).
I could connect both programs by 1 or 2 sockets. I was wondering whether
it's feasible to access shared memory from within hugs as an alternative?

Any answers?

Thanks,
xander van wiggen




From frido@q-software-solutions.com.NO-spam Fri Oct 20 07:46:37 2000 Date: 20 Oct 2000 08:46:37 +0200 From: Friedrich Dominicus frido@q-software-solutions.com.NO-spam Subject: A question regarding haskell mode for Emacs
I wonder if there are some known troubles. This mode yesterday nearly
drive me nuts. Indentation seem to be ok from the layout, but I got
complains about block closed to early, missing ; ...

Regards
Friedrich

-- 
for e-mail reply remove all after .com 


From romildo@urano.iceb.ufop.br Fri Oct 20 10:21:51 2000 Date: Fri, 20 Oct 2000 07:21:51 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: Extensible data types?
Hello.

I am back with the issue of extensible union types. Basically
I want to extend a data type with new value constructors.
Some members of the list pointed me to the paper

   "Monad Transformers and Modular Interpreters"
   Sheng Liang, Paul Hudak and Mark Jones

The authors suggest using a type constructor to express
the disjoint union of two other types:

   data Either a b = Left a | Right b

which indeed is part of the Haskell 98 Prelude. Then they introduce
a subtype relationship using multiparameter type classes:

   class SubType sub sup where
      inj :: sub -> sup			-- injection
      prj :: sup -> Maybe sub		-- projection

The Either data type consructor is then used to express
the desired subtype relationshipe:

   instance SubType a (Either a b) where
      inj           = Left
      prj (Left x)  = Just x
      prj _         = Nothing

   instance SubType a b => SubType a (Either c b) where
      inj           = Right . inj
      prj (Right x) = prj x
      prj _         = Nothing

The authors implemented their system in Gofer, due to
restrictions in the type class system of Haskell.
But now that there are Haskell extensions to support
multiparametric type classes, that could be implemented
in Haskell.

The above code fails to type check due to instances
overlapping. Hugs gives the following error message:

   ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType"
   *** This instance   : SubType a (Either b c)
   *** Overlaps with   : SubType a (Either a b)
   *** Common instance : SubType a (Either a b)

(I did not check Gofer, but is there a way to solve these
overlapping of instances in it?)

So this is scheme is not going to work with Haskell (extended
with multiparameter type classes).

I would like hear any comments from the Haskell comunity on
this subject. Is there a workaround for the overlapping instances?

Regards.

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


From labra@pinon.ccu.uniovi.es Fri Oct 20 11:36:39 2000 Date: Fri, 20 Oct 2000 12:36:39 +0200 (METDST) From: Jose Emilio Labra Gayo labra@pinon.ccu.uniovi.es Subject: Extensible data types?
> 
> The above code fails to type check due to instances
> overlapping. Hugs gives the following error message:
> 
In Hugs, there is a flag that you can set to allow overlapping instances

	:s +o

In GHC, you can also set

	-fallow-overlapping-instances

BTW, I use extensible union types in a "Language prototyping System" that
I am implementing and which compiles with GHC and Hugs (it is based
on Liang, Hudak and Jones paper). 
You can download the source code from 
  "http://lsi.uniovi.es/~labra/LPS/LPS.html"

Best regards, Jose Labra
http://lsi.uniovi.es/~labra





From doaitse@cs.uu.nl Fri Oct 20 14:16:34 2000 Date: Fri, 20 Oct 2000 15:16:34 +0200 From: S. Doaitse Swierstra doaitse@cs.uu.nl Subject: Extensible data types?
It is exactly for reasons like these that we developped our small 
attribute grammar system:

http://www.cs.uu.nl/groups/ST/Software/UU_AG/index.html

Doaitse Swiesrtra

At 7:21 AM -0200 10/20/00, Jos=E9 Romildo Malaquias wrote:
>Hello.
>
>I am back with the issue of extensible union types. Basically
>I want to extend a data type with new value constructors.
>Some members of the list pointed me to the paper
>
>    "Monad Transformers and Modular Interpreters"
>    Sheng Liang, Paul Hudak and Mark Jones
>
>The authors suggest using a type constructor to express
>the disjoint union of two other types:
>
>    data Either a b =3D Left a | Right b
>
>which indeed is part of the Haskell 98 Prelude. Then they introduce
>a subtype relationship using multiparameter type classes:
>
>    class SubType sub sup where
>       inj :: sub -> sup			-- injection
>       prj :: sup -> Maybe sub		-- projection
>
>The Either data type consructor is then used to express
>the desired subtype relationshipe:
>
>    instance SubType a (Either a b) where
>       inj           =3D Left
>       prj (Left x)  =3D Just x
>       prj _         =3D Nothing
>
>    instance SubType a b =3D> SubType a (Either c b) where
>       inj           =3D Right . inj
>       prj (Right x) =3D prj x
>       prj _         =3D Nothing
>
>The authors implemented their system in Gofer, due to
>restrictions in the type class system of Haskell.
>But now that there are Haskell extensions to support
>multiparametric type classes, that could be implemented
>in Haskell.
>
>The above code fails to type check due to instances
>overlapping. Hugs gives the following error message:
>
>    ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType"
>    *** This instance   : SubType a (Either b c)
>    *** Overlaps with   : SubType a (Either a b)
>    *** Common instance : SubType a (Either a b)
>
>(I did not check Gofer, but is there a way to solve these
>overlapping of instances in it?)
>
>So this is scheme is not going to work with Haskell (extended
>with multiparameter type classes).
>
>I would like hear any comments from the Haskell comunity on
>this subject. Is there a workaround for the overlapping instances?
>
>Regards.
>
>Romildo
>--
>Prof. Jos=E9 Romildo Malaquias <romildo@iceb.ufop.br>
>Departamento de Computa=E7=E3o
>Universidade Federal de Ouro Preto
>Brasil
>
>_______________________________________________
>Haskell mailing list
>Haskell@haskell.org
>http://www.haskell.org/mailman/listinfo/haskell

-- 
__________________________________________________________________________
S. Doaitse Swierstra, Department of Computer Science, Utrecht University
                       P.O.Box 80.089, 3508 TB UTRECHT,   the Netherlands
                       Mail:  mailto: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 legere@its.caltech.edu Fri Oct 20 16:21:12 2000 Date: Fri, 20 Oct 2000 08:21:12 -0700 (PDT) From: Ronald J. Legere legere@its.caltech.edu Subject: .net and haskell
 I was reading some .net stuff (ducks) on microsoft, and they
mentioned haskell as one of the languages someone was targetting for it.
Anyone know anything about this project?
Cheers!


+++++++++++++++++++++++++++++++++++++++++++++++++
Ron Legere  -- http://www.its.caltech.edu/~legere
Caltech Quantum Optics
MC 12-33
Pasadena CA 91125
626-395-8343
FAX: 626-793-9506
+++++++++++++++++++++++++++++++++++++++++++++++++






From romildo@urano.iceb.ufop.br Sat Oct 21 09:48:40 2000 Date: Sat, 21 Oct 2000 06:48:40 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: Passing an environment around
The following discussion is been conducted in the Clean mailing list.
As the issue is pertinent also to Haskell, I have cross-posted this
letter to the Haskell mailing list too.

Romildo.

On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote:
> Indeed Fran behaviors are like your alternative #1 (function passing), and
> hence sharing loss is a concern.  Simon PJ is right that I have a paper
> discussing this issue and some others.  See "Functional Implementations of
> Continuous Modeled Animation" on my pubs page
> (http://research.microsoft.com/~conal/papers). 
> 
> About alternative #2 (implicit arguments), would it help?  Does it eliminate
> the non-memoized redundant function applications, or just hide them?  For
> Fran, Erik Meijer suggested implicit functions to me a couple of years ago.
> I hadn't thought of it, and it did indeed seem to be attractive at first as
> a way to eliminate the need for overloading in Fran.  However, the (Time ->
> a) representation of Fran behaviors is not really viable, so I wouldn't
> merely want to hide that representation behind implicit arguments.

It seems that implicit parameters does not eliminate redundant function
applications, as Conal Elliott has commented. Reading the paper

   Implicit Parameters: Dynamic Scoping with Static Types
   Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury
   http://www.cse.ogi.edu/~jlewis/

(especially section 5.1) I got this impression. I would like to hear
from others as well, as I had some difficulties with the paper.

> I don't see how alternative #3 would work.
> 
> Of the three approaches, I think #1 is probably the best way to go.
> Functional programming encourages us to program with higher-order functions,
> and doing so naturally leads to this loss-of-sharing problem.  Memoization
> is thus a useful tool.  Adding it to Clean would probably help others as
> well as you.
> 
> 
> I recommend that you find out how real computer algebra systems address this
> issue.  I've used these systems some and have the impression that there is a
> default set of simplification rules, plus some strategies for non-standard
> "simplifications" like factoring.  You could apply the default set in a
> bottom-up way, with no need for memoization.  This is precisely the approach
> used for algebraic simplification in Pan (an Haskell-based image synthesis
> library).  See the recent paper "Compiling Embedded Languages" on my pubs
> page.  You can also get the Pan source release to check out the real
> details.
> 
> Good luck, and please let me know how it turns out.
> 
> 	- Conal
> 
>  -----Original Message-----
> From: 	Simon Peyton-Jones  
> Sent:	Thursday, October 19, 2000 1:51 AM
> To:	José Romildo Malaquias; clean-list@cs.kun.nl
> Cc:	Conal Elliott (E-mail); Meurig Sage (E-mail)
> Subject:	RE: [clean-list] Passing an environment around
> 
> It's interesting that *exactly* this issue came up when Conal
> Eliott was implementing Fran in Haskell.  His 'behaviours'
> are very like your expressions. 
> 	type Behaviour a = Time -> a
> and he found exactly the loss of sharing that you did.
> 
> For some reason, though, I'd never thought of applying the
> implicit-parameter
> approach to Fran.  (Perhaps because Implicit parameters came along after
> Fran.)  
> But I think it's rather a good idea. 
> 
> I think Conal may have a paper describing the implementation choices
> he explored; I'm copying him.
> 
> Simon
> 
> | -----Original Message-----
> | From: José Romildo Malaquias [mailto:romildo@urano.iceb.ufop.br]
> | Sent: 18 October 2000 08:12
> | To: clean-list@cs.kun.nl
> | Subject: [clean-list] Passing an environment around
> | 
> | 
> | Hello.
> | 
> | I am implementing a Computer Algebra system (CALG) in Clean, 
> | and I have a
> | problem I would like the opinion of Clean programmers.
> | 
> | The CALG system should be able to simplify (or better, to transform)
> | algebraic expressions (from Mathematics) involving integers, 
> | named constants
> | (like "pi" and "e"), variables, arithmetic operations (addition,
> | multiplication, exponentiation), and other forms of expressions
> | (trigonometric, logarithmic, derivatives, integrals, 
> | equations, etc.). The
> | tansformaations should follow the rules from Algebra and 
> | other areas of
> | Mathematica. But we know that in general an algebraic 
> | expression can be
> | transformed in different ways, depending on the goal of the
> | transformation. Thus, the algebraic expression
> | 
> |    a^2 + b^2 + 3*a*b - a*b
> | 
> | could result in
> | 
> |    a^2 + 2*a*b + b^2
> | 
> | or in
> | 
> |   (a + b)^2
> | 
> | To control the transformations made with an algebraic 
> | expression there is a
> | set of flags collected in a record. I will call this record 
> | the environment
> | in which the expression should be simplified. The algorithms I am
> | implementing may change this environment temporarily for some local
> | transformations. So the enviroment should be passed around in 
> | the function
> | calls I am writing. This way the functions that implements the
> | transformations will have an extra argument representing the 
> | environment in
> | which the transformation is to be performed.
> | 
> | Let's take an example: the algorithm for addition will have 
> | two arguments to
> | be added and a third argument corresponding to the enviroment:
> | 
> |    add :: Expr Expr Env -> Expr
> | 
> | and its result will depend of the flags in the environment. 
> | But it is highly
> | desirable to define functions like add as BINARY INFIX 
> | OPERATORS. Having 3
> | arguments, add cannot be made a binary operator!
> | 
> |   --------------------------------------------------------------------
> |   So I am looking for alternative ways to pass the environment around.
> |   --------------------------------------------------------------------
> | 
> | 1. Handle the arguments as functions themselves, which, given 
> | an enviroment,
> |    returns the simplified algebraic expression in that environment:
> | 
> |    add :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr)
> | 
> |    Now add can be made a binary infix operator. This solution has the
> |    disadvantage that we loose sharing when doing local 
> | simplifications. For
> |    example:
> | 
> |    f :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr)
> |    f fx fy = (add (add fx fy) fy)
> | 
> |    fe1, fe2 :: Env -> Exp
> |    fe1 e = ...
> |    fe2 e = ...
> | 
> |    initialEnv :: Env
> |    initialEnv = ...
> | 
> |    Start = f fe1 fe2 initialEnv
> | 
> |    In this program fragment, fe2 may be applied twice to the same
> |    environment value, computing its body twice. The resulting 
> | program would
> |    be too inneficient. If Clean had a mean of implementing MEMOIZATION
> |    FUNCTIONS, the computation of a memoized function 
> | application to the same
> |    argument would evalute the body of the function only the 
> | first time the
> |    function is applied. Subsequent applications of that 
> | function to the same
> |    argument would remember the result of the previous 
> | application and would
> |    reutilize it. Then this way of handling environment 
> | passing would be a
> |    good solution.
> | 
> |    For more on memo functions see
> |    <http://www.cse.ogi.edu/~byron/memo/dispose.ps>.
> | 
> | 2. Extend Clean to support IMPLICIT PARAMETER PASSING (that 
> | is, a form of
> |    dynamic scoping), as has been done in some Haskell 
> | implementations (Hugs,
> |    GHC). Than the environment could be passed implicitly and 
> | add could be
> |    considered to have only 2 arguments
> | 
> |    add :: (Env ?env) => Exp Exp -> Exp
> | 
> |    Here ?env represents an implicit parameter. It is not 
> | passed explicitly
> |    like the two argument parameters. It can be used normally 
> | in the function
> |    definition, like any normal parameter. To pass an argument 
> | implicitly,
> |    there is 2 additional forms of expression: dlet and with:
> | 
> |    dlet ?env = ... in add e1 e2
> | 
> |    add e1 e2 with ?env = ...
> | 
> |    I think this could be the best solution to my problem, if Clean had
> |    such extension implemented.
> | 
> |    For more information, see
> |    <http://www.cse.ogi.edu/~jlewis/implicit.pdf.gz>
> | 
> | 3. Join the algebraic expression and the environment in a single value
> | 
> |    add :: (Env,Exp) (Env,Exp) -> (Env,Exp)
> | 
> |    The enviroment is then carried around with each expression.
> |    But now add has two enviroments to consult. Which one should be
> |    used?
> | 
> | Would be other good alternatives to solve this problem?
> | 
> | Would future versions of Clean support
> | 
> |   - memoization functions, or
> |   - implciit parameter passing?
> | 
> | I am open to discussion on this topics.
> | 
> | Regards,
> | 
> | Romildo
> | -- 
> | Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
> | Departamento de Computação
> | Universidade Federal de Ouro Preto
> | Brasil
> | 
> | _______________________________________________
> | clean-list mailing list
> | clean-list@cs.kun.nl
> | http://www.cs.kun.nl/mailman/listinfo/clean-list
> | 
> 
> _______________________________________________
> clean-list mailing list
> clean-list@cs.kun.nl
> http://www.cs.kun.nl/mailman/listinfo/clean-list

-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


From romildo@urano.iceb.ufop.br Mon Oct 23 13:22:35 2000 Date: Mon, 23 Oct 2000 10:22:35 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: Overloaded function and implicit parameter passing
Hi.

While experimenting with the implicit parameter
extension to Haskell 98, implemented in GHC 4.08.1
and latest Hugs, I came accross a difference among
those implementations regarding overloading functions
with implicit parameters.

As a test consider the program

------------------------- cut here
module Main where

class C a where
    f :: (?env :: Integer) => a -> Integer

instance C Integer where
    f x = ?env + x

main = putStrLn (show (f (45::Integer) with ?env = 100))
------------------------- cut here

Hugs accepts this program and outputs 145, as expected.
But GHC 4.08.1 refuses to compile it, emitting the
message

$ ghc -fglasgow-exts Test1.hs -o test1

Test1.hs:7:
    Unbound implicit parameter `env_rJX :: Integer'
    arising from use of `env_rJX' at Test1.hs:7
    In the first argument of `+', namely `env_rJX'
    In the right-hand side of an equation for `f': env_rJX + x

Compilation had errors

Would anybody comment on what is going on with GHC?

I am willing to use implicit parameters in the
software I am developing, but I have the need
to overload functions with implicit parameters.
While Hugs is good for development, its performance
may rule it out when the final product is ready.
So I will need a good Haskell compiler to compile
my system.

Any comments?

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


From fjh@cs.mu.oz.au Mon Oct 23 15:02:14 2000 Date: Tue, 24 Oct 2000 01:02:14 +1100 From: Fergus Henderson fjh@cs.mu.oz.au Subject: Overloaded function and implicit parameter passing
On 23-Oct-2000, José Romildo Malaquias <romildo@urano.iceb.ufop.br> wrote:
> ------------------------- cut here
> module Main where
> 
> class C a where
>     f :: (?env :: Integer) => a -> Integer
> 
> instance C Integer where
>     f x = ?env + x
> 
> main = putStrLn (show (f (45::Integer) with ?env = 100))
> ------------------------- cut here
...
> $ ghc -fglasgow-exts Test1.hs -o test1
> 
> Test1.hs:7:
>     Unbound implicit parameter `env_rJX :: Integer'
>     arising from use of `env_rJX' at Test1.hs:7
...
> Would anybody comment on what is going on with GHC?

That sure looks to me like a bug in GHC's support for implicit
parameter passing.

-- 
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 ru@ohio.river.org Mon Oct 23 21:28:09 2000 Date: Mon, 23 Oct 2000 13:28:09 -0700 (PDT) From: Richard ru@ohio.river.org Subject: mapM/concatMapMy
Sengan Baring-Gould writes:

>Is >>= not lazy?

since no experts have answered yet, this newbie will answer.
I think it's strict.

somewhere in the compiler doco, IIRC, it says (>>=) was lazy at
first, but experience showed it was more confusing for users
(Haskell programmers).

moreover, from the hslibs documentation, LazyST chapter:
"The lazy ST monad tends to be more prone to space leaks than the
strict version, so most programmers will use the former unless
laziness is explicitly required."
http://haskell.org/ghc/docs/latest/set/sec-lazyst.html


From quintela@fi.udc.es Tue Oct 24 05:48:25 2000 Date: 24 Oct 2000 06:48:25 +0200 From: Juan J. Quintela quintela@fi.udc.es Subject: CFP: Eight International Conference on Computer Aided Systems Theory
The following message is a courtesy copy of an article
that has been posted to comp.lang.ml,comp.lang.functional as well.


Dear Colleagues,

I would be most grateful if you would distribute the appended
Call For Papers to your colleagues (and/or any mailing lists
you see appropriate).  Any help in distributing the Call For
Papers would be most appreciated.

Kindest regards,

        Juan Quintela


CALL FOR PAPERS
---------------

Eight International Conference on Computer Aided Systems Theory

Formal Methods and Tools for Computer Science

See the webpage at:

http://azuaje.ulpgc.es/congresos/eurocast2001/

The topics for the workshop are:

Workshop "FP"

Contributions addressing to the following and similar issues:
1.Concurrency. Distributed and web applications.
2.Verification:tools and methods.
3.Persistence.
4.Typing and theoretical foundations.

You only have to send one extended abstract before the:

31 October.

-- 
In theory, practice and theory are the same, but in practice they 
are different -- Larry McVoy


From rjmh@cs.chalmers.se Tue Oct 24 09:16:54 2000 Date: Tue, 24 Oct 2000 10:16:54 +0200 (MET DST) From: John Hughes rjmh@cs.chalmers.se Subject: mapM/concatMapMy
	Sengan Baring-Gould writes:

	>Is >>= not lazy?

	since no experts have answered yet, this newbie will answer.
	I think it's strict.

Well, it depends. (>>=) is an overloaded operator, with a different
implementation for every monad -- when you define a monad, you give the
implementation of (>>=). If your implementation is strict (presumably in the
first operand), then (>>=) is strict *at that type*. If your implementation is
lazy, then it isn't. The same goes for (+): at most types (+) is strict, but
if you define your own kind of number with a lazy addition, then on that type
(+) will be lazy.

For many monads, (>>=) *is* strict, which fits with the intuition that it is a
`sequencing' operator. But by no means for all. The simplest counter-example
is the identity monad:

	newtype Id a = Id a

	instance Monad Id where
	  return = Id
	  Id x >>= f = f x

where m>>=f is strict in m only if f is a strict function. A more interesting
example is the state transformer monad:

	newtype ST s a = ST (s -> (a,s))

	instance Monad (ST s) where
	  return x = ST (\s -> (x,s))
	  ST h >>= f = ST (\s -> let (a,s') = h s
				     ST h' = f a
				 in h' s')

where once again, the implementation of (>>=) is strict only if f is a 
strict function. Hence `lazy state' makes sense!

John Hughes


From delapla@lami.univ-evry.fr Tue Oct 24 13:57:16 2000 Date: Tue, 24 Oct 2000 14:57:16 +0200 From: Franck Delaplace delapla@lami.univ-evry.fr Subject: LOOKING FOR B-TREES MODULE
I am looking for an haskell module which implements balanced trees ?
Can somebdody help me =


Thank you  =



-- =

Franck Delaplace @w3:http://taillefer.lami.univ-evry.fr:8090/~delapla/
La.M.I-U.M.R   C.N.R.S
Universit=E9 d'Evry Val d'Essonne    =

Cours Monseigneur Rom=E9ro          =

91025 Evry CEDEX (France)


From wohlstad@cs.ucdavis.edu Tue Oct 24 19:25:29 2000 Date: Tue, 24 Oct 2000 11:25:29 -0700 (PDT) From: Eric Allen Wohlstadter wohlstad@cs.ucdavis.edu Subject: Group theory
Are there any Haskell libraries or programs related to group theory? I am
taking a class and it seems like Haskell would be a good programming
language for exploring/reasoning about group theory. What I had in mind
was perhaps you could have a function which takes a list(set) and a
function with two arguments(binary operator) and checks to see whether or
not it is a group. I think it might be a fun exercies to write myself but
I'd like to see if it's already been done or what you guys think about it.

	Eric Wohlstadter
	UCDavis Software Engineering






From dongen@cs.ucc.ie Tue Oct 24 19:29:58 2000 Date: Tue, 24 Oct 2000 19:29:58 +0100 From: Marc van Dongen dongen@cs.ucc.ie Subject: Group theory
Eric Allen Wohlstadter (wohlstad@cs.ucdavis.edu) wrote:

: Are there any Haskell libraries or programs related to group theory? I am
: taking a class and it seems like Haskell would be a good programming
: language for exploring/reasoning about group theory. What I had in mind
: was perhaps you could have a function which takes a list(set) and a
: function with two arguments(binary operator) and checks to see whether or
: not it is a group. I think it might be a fun exercies to write myself but
: I'd like to see if it's already been done or what you guys think about it.

I think Sergey Mechveliani's docon (algebraic DOmain CONstructor)
has facilities for that. Have a look at:

http://www.cs.bell-labs.com/who/wadler/realworld/docon.html


Regards,


Marc van Dongen


From mechvel@math.botik.ru Wed Oct 25 08:20:32 2000 Date: Wed, 25 Oct 2000 11:20:32 +0400 From: S.D.Mechveliani mechvel@math.botik.ru Subject: group theory. Reply
Hi, all,


To   Eric Allen Wohlstadter's (wohlstad@cs.ucdavis.edu)

: Are there any Haskell libraries or programs related to group theory? I am
: taking a class and it seems like Haskell would be a good programming
: language for exploring/reasoning about group theory. What I had in mind
: was perhaps you could have a function which takes a list(set) and a
: function with two arguments(binary operator) and checks to see whether or
: not it is a group. I think it might be a fun exercies to write myself but
: I'd like to see if it's already been done or what you guys think about it.


Marc van Dongen <dongen@cs.ucc.ie>  writes

> I think Sergey Mechveliani's docon (algebraic DOmain CONstructor)
> has facilities for that. Have a look at:
>
> http://www.cs.bell-labs.com/who/wadler/realworld/docon.html


Sorry, 
DoCon  (<http://www.botik.ru/pub/local/Mechveliani/docon/2.01/>)

really supports the Commutative Rings, 
but provides almost nothing for the Group theory.

For example, for the domain    (Integer,Integer) 

it would set automatically  (IsGroup,Yes)  for the
Additive semigroup  and     (IsGroup,No)   for the Multiplicative
semigroup.
For the additive case, it would also set the group generator list
[(1,0),(0,1)].
In both cases, it would also set  cardinality = Infinity.
Similar attributes are formed for the constructors of  Permutation, 
Vector, Matrix, Polyninomial, Fraction, ResidueRing.
And that is all.
It does not provide so far any real algorithmic support for the Group 
theory, except some operations on permutations. 

But one may develop the program by adding the needed algorithms and 
introducing new attributes.


:  What I had in mind
: was perhaps you could have a function which takes a list(set) and a
: function with two arguments(binary operator) and checks to see whether or
: not it is a group. I think it might be a fun exercies to write myself but
: I'd like to see if it's already been done or what you guys think about it.

I never programmed this. It looks like some exercise in algorithms. 
There are also books on the combinatorial group theory, maybe, they
say something about efficient procedures for this.


Regards,

------------------
Sergey Mechveliani
mechvel@botik.ru









From karczma@info.unicaen.fr Wed Oct 25 10:58:04 2000 Date: Wed, 25 Oct 2000 10:58:04 +0100 From: Jerzy Karczmarczuk karczma@info.unicaen.fr Subject: group theory. Reply
S.D.Mechveliani wrote:
> 
> Hi, all,
> 
> To   Eric Allen Wohlstadter's 
> 
> : Are there any Haskell libraries or programs related to group theory? 

...

> Marc van Dongen <dongen@cs.ucc.ie>  writes
> 
> > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor)
> > has facilities for that. 
...

> Sorry,
> DoCon  (<http://www.botik.ru/pub/local/Mechveliani/docon/2.01/>)
> 
> really supports the Commutative Rings,
> but provides almost nothing for the Group theory.
> 

EAW again:
> : ... I think it might be a fun exercies to write myself but
> : I'd like to see if it's already been done or what you guys 
> : think about it.

SM:
> I never programmed this. It looks like some exercise in algorithms.
> There are also books on the combinatorial group theory, maybe, they
> say something about efficient procedures for this.

==
"Some exercise in algorithms". Hm. There is more to that than this...

This issue has been recently stirred a bit in the comp.functional
newsgroup, in a larger context, general Math, not necessarily the
group theor. There are at least two people *interested* in it, 
although they didn't do much yet (for various reasons...)

Suggestion: Take GAP!
( http://www-history.mcs.st-and.ac.uk/~gap/ )

Plenty of simply coded algorithms, specifically in this domain.
I coded just for fun a few simple things in Haskell some time ago,
and it was a real pleasure. The code is cleaner and simpler. Its
presentation is also much cleaner than the original algorithms
written in GAP language. But I discarded all this stuff, thinking
that I would have never time enough to get back to it...

This is a nice project, and I would participate with pleasure in it,
although the time factor is still there...
Dima Pasechnik (<d.pasechnik@twi.tudelft.nl>; does he read it?) 
- apparently - as well.  


Jerzy Karczmarczuk
Caen, France


From senganb@ia.nsc.com Wed Oct 25 17:21:42 2000 Date: Wed, 25 Oct 2000 10:21:42 -0600 (MDT) From: Sengan Baring-Gould senganb@ia.nsc.com Subject: Haskell Programming Environment
> Hello,
> 
> I'm writing my master thesis. Its subject is 'Haskell Programming
> Environment'. It is (or rather will be) an extended text editor working i=
> n
> graphical (XFree86) environment designed for Haskell programmers. It will=
>  be
> implemented using Fudgets library.
> I'm wondering what features would you like to find in such environment. W=
> hat
> should be neccessary, what would help, what would make writing programs
> easier, etc.
> I have some concepts, but I would like to hear some suggestions from you.
> 
> Thanks for all answers.

a) the ablility to highlight an area of code and get its type (be it a function,
   or some well-formed chunk of code
 
b) the ability to highlight a function and get its definition in another area
   (think multiple text editing in vim)

c) interaction with hugs/stg-hugs so that just written code can be pasted into
   a "hugs window" for evaluation.

d) Debug mode which automatically adds "deriving show" to all datatypes which
   are not showable/adds exporting of all Datatypes as non-abstract for use in
   hugs to just allow things to be tried out.

e) Debug mode which invisibly replaces functions such as "fromJust" with error
   making versions (... fromJust' "the file and line at which I'm invoked" ...)
   to make it easier to find the cause of the error (fromJust Nothing just comes
   up with an error telling you that it's fromJust that failed. Last time that
   happened, I hacked hugs to dump the evaluation stack, from which I guessed
   which possible fromJusts it could have been).

f) Use ghc's .hi file to allow strictness of arguments to appear if you leave
   the mouse over an argument.

g) For bonus points (harder, but really useful when stuck):
   given an expression, show me (possibly using daVinci) how it gets evaluated:
   Lazyness behaviour is not always obvious, I'd like to see it.

I've been wanting to code one of these myself, but have had no time. Try and see
if stg-hugs is useable yet since that would be a much better environment to do
it in.

Sengan


From Keith.Wansbrough@cl.cam.ac.uk Wed Oct 25 17:26:51 2000 Date: Wed, 25 Oct 2000 17:26:51 +0100 From: Keith Wansbrough Keith.Wansbrough@cl.cam.ac.uk Subject: Haskell Programming Environment
> I've been wanting to code one of these myself, but have had no time. Try and see
> if stg-hugs is useable yet since that would be a much better environment to do
> it in.

It's now called GHCi, and is being written right now by the GHC team.
Not sure when the estimated completion time is, but it can't be that
far off.

--KW 8-)



From ger@Informatik.Uni-Bremen.DE Wed Oct 25 21:08:55 2000 Date: Wed, 25 Oct 2000 22:08:55 +0200 From: George Russell ger@Informatik.Uni-Bremen.DE Subject: cpp superior to ghc . . .
Why does the Haskell language not allow "type" declarations to appear in 
the declaration parts of where and let clauses?  I've just been writing a huge
functions which requires lots and lots of repetitive internal type annotations 
(to disambiguate some complicated overloading) but I can't abbreviate them with 
"type" because they depend on things only in scope inside the function.  In the
end I abbreviated them with a few #define's but I don't really think it should
be that way . . .


From qrczak@knm.org.pl Thu Oct 26 06:09:48 2000 Date: 26 Oct 2000 05:09:48 GMT From: Marcin 'Qrczak' Kowalczyk qrczak@knm.org.pl Subject: cpp superior to ghc . . .
Wed, 25 Oct 2000 22:08:55 +0200, George Russell <ger@Informatik.Uni-Bremen.DE> pisze:

> Why does the Haskell language not allow "type" declarations to
> appear in the declaration parts of where and let clauses?

Because you can always lift them to the top level.

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



From koen@cs.chalmers.se Thu Oct 26 08:01:21 2000 Date: Thu, 26 Oct 2000 09:01:21 +0200 (MET DST) From: Koen Claessen koen@cs.chalmers.se Subject: cpp superior to ghc . . .
George Russell complained:

 | Why does the Haskell language not allow "type"
 | declarations to appear in the declaration parts of
 | where and let clauses?

Marcin 'Qrczak' Kowalczyk replied:

 | Because you can always lift them to the top level.

This is the ultimate non-answer.

First of all, it is wrong. George meant to be able to use
type variables present in the top-level type in the local
type declarations. Something like:

  doWithStack :: a -> a
  doWithStack x = stacking []
   where
    type Stack = [a]

    stacking :: Stack -> a
    stacking = ...

The problem is really two-fold: bound type variables (like
"a") are not in scope in the body of the function, and local
type declarations are not allowed.

Secondly, "because another way of doing it is possible" is
not an answer. We allow local declarations of functions, but
we have known for ages we can all lambda-lift them to
top-level...

Regards,
Koen.

--
Koen Claessen         http://www.cs.chalmers.se/~koen     
phone:+46-31-772 5424      mailto:koen@cs.chalmers.se
-----------------------------------------------------
Chalmers University of Technology, Gothenburg, Sweden



From mk167280@students.mimuw.edu.pl Thu Oct 26 08:29:49 2000 Date: Thu, 26 Oct 2000 09:29:49 +0200 (CEST) From: Marcin 'Qrczak' Kowalczyk mk167280@students.mimuw.edu.pl Subject: cpp superior to ghc . . .
On Thu, 26 Oct 2000, Koen Claessen wrote:

> The problem is really two-fold: bound type variables (like
> "a") are not in scope in the body of the function, and local
> type declarations are not allowed.

GHC and Hugs do solve the first problem by providing a language extension:
names of type variables in pattern type signatures and result type
signatures are available in their scope. I wish this extension becomes
a future standard.

Some people say that type variables from ordinary type signatures should
be in scope too.

-- 
Marcin 'Qrczak' Kowalczyk



From simonpj@microsoft.com Thu Oct 26 18:27:51 2000 Date: Thu, 26 Oct 2000 10:27:51 -0700 From: Simon Peyton-Jones simonpj@microsoft.com Subject: .net and haskell
|  I was reading some .net stuff (ducks) on microsoft, and they
| mentioned haskell as one of the languages someone was 
| targetting for it.
| Anyone know anything about this project?

I know of several stabs in this direction, none completed.

- There is most of a Java back end for GHC

- There are various pieces of a C# back end for GHC,
	compiling via in intermediate generic OO language
	called GOO.  Nigel Perry is working on this (actively
	I think)

- Don Syme and Reuben Thomas are working on a back end for
	GHC that compiles to a polymorphically-typed IL for .NET
	that is Don's baby.  A lot of this works, but it's not complete.

Maybe others are doing stuff too?   It's a pity that there's nothing
that's usable yet, but I hope that'll change.

Simon


From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 11:16:19 2000 Date: Fri, 27 Oct 2000 12:16:19 +0200 From: =?iso-8859-1?Q?Matthias_H=F6chsmann?= mhoechsm@techfak.uni-bielefeld.de Subject: class instance with nested types
This is a multi-part message in MIME format.

--Boundary_(ID_5jIOsd3oqicabXDXApeVOg)
Content-type: text/plain; charset=iso-8859-1
Content-transfer-encoding: 7BIT

Hello,

I have the following problem:

basic datatypes

> type Sequence a = [a]
> data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> type Forest a = Sequence (Tree a)

i want to construct a class Xy

> class Xy s a where
>      test :: s a -> a

and make an instance for list of characters

> instance Xy [] Char where
>      test [a] = a

this works, and an instance for a forest and tried something like this

> instance  ([] Tree) Char where
> test x@(N a xs):txs = a

I get illegal type errors. Is it possible to use nested types in a class ?

Hope you can help me 
Matthias


--Boundary_(ID_5jIOsd3oqicabXDXApeVOg)
Content-type: text/html; charset=iso-8859-1
Content-transfer-encoding: 7BIT

<!DOCTYPE HTML PUBLIC "-//W3C//DTD HTML 4.0 Transitional//EN">
<HTML><HEAD>
<META content="text/html; charset=iso-8859-1" http-equiv=Content-Type>
<META content="MSHTML 5.00.2614.3500" name=GENERATOR>
<STYLE></STYLE>
</HEAD>
<BODY bgColor=#ffffff>
<DIV><FONT face=Arial size=2>Hello,</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>I have the following problem:</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>basic datatypes</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>&gt; type Sequence a = [a]</FONT></DIV>
<DIV><FONT face=Arial size=2>&gt; data Tree a = N a (Forest a) deriving 
(Ord,Eq,Show)</FONT></DIV>
<DIV><FONT face=Arial size=2>&gt; type Forest a = Sequence (Tree a)</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>i want to construct a class Xy</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>&gt; class Xy s a where</FONT></DIV>
<DIV><FONT face=Arial size=2>&gt;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; test :: s a 
-&gt; a</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>and make an instance for list of 
characters</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>&gt; instance Xy [] Char where</FONT></DIV>
<DIV><FONT face=Arial size=2>&gt;&nbsp;&nbsp;&nbsp;&nbsp;&nbsp; test [a] = 
a</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>this works, and an instance for a forest and tried 
something like this</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>&gt; instance </FONT>&nbsp;<FONT face=Arial 
size=2>([] Tree) Char where</FONT></DIV>
<DIV><FONT face=Arial size=2>&gt; test x@(N a xs):txs = a</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>I get illegal type errors. Is it possible 
to&nbsp;use nested types in a class ?</FONT></DIV>
<DIV>&nbsp;</DIV>
<DIV><FONT face=Arial size=2>Hope you can help me </FONT></DIV>
<DIV><FONT face=Arial size=2>Matthias</FONT></DIV>
<DIV>&nbsp;</DIV></BODY></HTML>

--Boundary_(ID_5jIOsd3oqicabXDXApeVOg)--


From d95lars@dtek.chalmers.se Fri Oct 27 11:14:58 2000 Date: Fri, 27 Oct 2000 12:14:58 +0200 (MEST) From: Lars Lundgren d95lars@dtek.chalmers.se Subject: class instance with nested types
On Fri, 27 Oct 2000, Matthias Höchsmann wrote:

> Hello,
> 
> I have the following problem:
> 
> basic datatypes
> 
> > type Sequence a = [a]
> > data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> > type Forest a = Sequence (Tree a)
> 
> i want to construct a class Xy
> 
> > class Xy s a where
> >      test :: s a -> a
> 
> and make an instance for list of characters
> 
> > instance Xy [] Char where
> >      test [a] = a
> 
> this works, and an instance for a forest and tried something like this
> 
> > instance  ([] Tree) Char where
> > test x@(N a xs):txs = a
> 

Don't you mean

test (N a xs:txs) = a

?

/Lars L




From N.Perry@massey.ac.nz Fri Oct 27 11:59:13 2000 Date: Fri, 27 Oct 2000 12:59:13 +0200 From: Nigel Perry N.Perry@massey.ac.nz Subject: .net and haskell
At 10:27 am -0700 26/10/00, Simon Peyton-Jones wrote:
>|  I was reading some .net stuff (ducks) on microsoft, and they
>| mentioned haskell as one of the languages someone was
>| targetting for it.
>| Anyone know anything about this project?
>
>I know of several stabs in this direction, none completed.
>
>- There is most of a Java back end for GHC
>
>- There are various pieces of a C# back end for GHC,
>	compiling via in intermediate generic OO language
>	called GOO.  Nigel Perry is working on this (actively
>	I think)

This is indeed being worked on. Currently user code compiles (as far as it
has been tested) but there is no prelude yet so it doesn't run too well ;-)
The code generator was designed for research and supporting scripting,
which is a kind way of saying it doesn't produce blazingly fast code.

>
>- Don Syme and Reuben Thomas are working on a back end for
>	GHC that compiles to a polymorphically-typed IL for .NET
>	that is Don's baby.  A lot of this works, but it's not complete.
>
>Maybe others are doing stuff too?   It's a pity that there's nothing
>that's usable yet, but I hope that'll change.

Cheers,
	Nigel


From rossberg@ps.uni-sb.de Fri Oct 27 13:07:37 2000 Date: Fri, 27 Oct 2000 14:07:37 +0200 From: Andreas Rossberg rossberg@ps.uni-sb.de Subject: class instance with nested types
Matthias Höchsmann wrote:
> 
> > type Sequence a = [a]
> > data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> > type Forest a = Sequence (Tree a)
> 
> i want to construct a class Xy
> 
> > class Xy s a where
> >      test :: s a -> a
> 
> [...]
> 
> > instance  ([] Tree) Char where
> > test x@(N a xs):txs = a

To make it syntactically correct this should at least be something like

> instance Xy ([] Tree) Char where
> test (N a xs:txs) = a

But the real problem is in the expression ([] Tree), which is the same
as writing [Tree]. This is not a legal type expression, since Tree is a
type constructor, not a ground type, so you cannot apply it to the list
constructor.

What you are trying to say is probably something like this:

> instance Xy (\a . [Tree a]) Char	-- not Haskell

But unfortunately there are no lambdas on the type level - they would
render the type system undecidable. For the same reason it is not
allowed to use a type synonym in an instance declaration:

> instance Xy Forest Char		-- illegal

The only thing you can do is turning Forest into a data type:

> data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> data Forest a = Forest [Tree a]
 
> instance Xy Forest Char where
> test (Forest (N a xs:txs)) = a

HTH,

	- Andreas

-- 
Andreas Rossberg, rossberg@ps.uni-sb.de

:: be declarative. be functional. just be. ::


From rossberg@ps.uni-sb.de Fri Oct 27 13:12:45 2000 Date: Fri, 27 Oct 2000 14:12:45 +0200 From: Andreas Rossberg rossberg@ps.uni-sb.de Subject: class instance with nested types
I mumbled:
> 
> This is not a legal type expression, since Tree is a
> type constructor, not a ground type, so you cannot apply it to the list
> constructor.

The other way round, of course: you cannot apply the list constructor to
it.

	- Andreas

-- 
Andreas Rossberg, rossberg@ps.uni-sb.de

:: be declarative. be functional. just be. ::


From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 14:25:00 2000 Date: Fri, 27 Oct 2000 15:25:00 +0200 From: =?iso-8859-1?Q?Matthias_H=F6chsmann?= mhoechsm@techfak.uni-bielefeld.de Subject: class instance with nested types
Yes, I wanted to type it like you do. 
But anyway, i fixed the problem following Andreas Rossbergs suggestion.

Matthias


> 
> Don't you mean
> 
> test (N a xs:txs) = a
> 
> ?
> 
> /Lars L
> 
> 
> 
> _______________________________________________
> Haskell mailing list
> Haskell@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell



From jeff@galconn.com Fri Oct 27 16:10:29 2000 Date: Fri, 27 Oct 2000 08:10:29 -0700 From: Jeffrey R. Lewis jeff@galconn.com Subject: Overloaded function and implicit parameter passing
José Romildo Malaquias wrote:

> Hi.
>
> While experimenting with the implicit parameter
> extension to Haskell 98, implemented in GHC 4.08.1
> and latest Hugs, I came accross a difference among
> those implementations regarding overloading functions
> with implicit parameters.
>
> As a test consider the program
>
> ------------------------- cut here
> module Main where
>
> class C a where
>     f :: (?env :: Integer) => a -> Integer
>
> instance C Integer where
>     f x = ?env + x
>
> main = putStrLn (show (f (45::Integer) with ?env = 100))
> ------------------------- cut here
>
> Hugs accepts this program and outputs 145, as expected.
> But GHC 4.08.1 refuses to compile it, emitting the
> message
>
> $ ghc -fglasgow-exts Test1.hs -o test1
>
> Test1.hs:7:
>     Unbound implicit parameter `env_rJX :: Integer'
>     arising from use of `env_rJX' at Test1.hs:7
>     In the first argument of `+', namely `env_rJX'
>     In the right-hand side of an equation for `f': env_rJX + x
>
> Compilation had errors
>
> Would anybody comment on what is going on with GHC?
>
> I am willing to use implicit parameters in the
> software I am developing, but I have the need
> to overload functions with implicit parameters.
> While Hugs is good for development, its performance
> may rule it out when the final product is ready.
> So I will need a good Haskell compiler to compile
> my system.
>
> Any comments?

Certainly a bug.  I'll look at it when I get a chance.

--Jeff



From romildo@urano.iceb.ufop.br Fri Oct 27 17:41:19 2000 Date: Fri, 27 Oct 2000 14:41:19 -0200 From: =?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?= romildo@urano.iceb.ufop.br Subject: Passing an environment around
On Fri, Oct 27, 2000 at 09:07:24AM -0700, Jeffrey R. Lewis wrote:
> José Romildo Malaquias wrote:
> 
> > On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote:
> > > Indeed Fran behaviors are like your alternative #1 (function passing), and
> > > hence sharing loss is a concern.  Simon PJ is right that I have a paper
> > > discussing this issue and some others.  See "Functional Implementations of
> > > Continuous Modeled Animation" on my pubs page
> > > (http://research.microsoft.com/~conal/papers).
> > >
> > > About alternative #2 (implicit arguments), would it help?  Does it eliminate
> > > the non-memoized redundant function applications, or just hide them?  For
> > > Fran, Erik Meijer suggested implicit functions to me a couple of years ago.
> > > I hadn't thought of it, and it did indeed seem to be attractive at first as
> > > a way to eliminate the need for overloading in Fran.  However, the (Time ->
> > > a) representation of Fran behaviors is not really viable, so I wouldn't
> > > merely want to hide that representation behind implicit arguments.
> >
> > It seems that implicit parameters does not eliminate redundant function
> > applications, as Conal Elliott has commented. Reading the paper
> >
> >    Implicit Parameters: Dynamic Scoping with Static Types
> >    Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury
> >    http://www.cse.ogi.edu/~jlewis/
> >
> > (especially section 5.1) I got this impression. I would like to hear
> > from others as well, as I had some difficulties with the paper.
> 
> I am sorry you had difficulties!

The difficulties I had is basicaly due to my lack of solid knowledge on
type theory and semantic formalisms. Not that the paper was badly
written.

> Yes, as implemented using the dictionary
> translation, implicit parameterization can lead to loss of sharing, exactly in
> the same way that overloading (and HOF in general) can lead to loss of sharing.
> 
> However, I can imagine that a compiler might chose to implement implicit
> parameters more like dynamic variables in lisp.   Each implicit param essentially
> becomes a global variable, implemented as a stack of values - the top of the
> stack is the value currently in scope.  This would avoid the sharing problem
> nicely.
> 
> --Jeff

I suppose your implementation of implicit parameterization in GHC and Hugs
uses the dictionary translation, right? Would an alternative implementation
based on a stack of values be viable and even done? Does it have serious
drawbacks when compared with the dictionary translation technique?

Thanks.

Romildo
-- 
Prof. José Romildo Malaquias <romildo@iceb.ufop.br>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


From dublins@home.com Sun Oct 29 18:55:51 2000 Date: Sun, 29 Oct 2000 10:55:51 -0800 From: S Dublin dublins@home.com Subject:


From lmagnani@cc.gatech.edu  Sun Oct 29 16:08:27 2000
Date: Sun, 29 Oct 2000 10:08:27 -0600
From: Lorenzo Magnani lmagnani@cc.gatech.edu
Subject: MBR'01 Conference

Please accept our apologies if you receive multiple copies of this call 

If you want to receive updated information please send your complete
address

Last updated October 29, 2000   

********************************************************************** 
                            
        
                      MODEL-BASED REASONING:

 SCIENTIFIC DISCOVERY, TECHNOLOGICAL INNOVATION, VALUES  (MBR'01), 
               
                  Pavia, Italy, May 17-19, 2001. 

********************************************************************** 
          
       Up-to date information on the conference will be found at 
  
                http://philos.unipv.it/courses/progra1.html
             or
        http://www.unipv.it/webphilos_lab/courses/progra1.html
   
********************************************************************** 
 
GENERAL INFORMATION 
 
>From Thursday 17 to Saturday 19 May 2001 (three days) the 
International Conference "MODEL-BASED REASONING. SCIENTIFIC DISCOVERY,
TECNOLOGICAL INNOVATION, VALUES" will be held at the University of 
Pavia (near Milan, Italy). 
 

PROGRAM  

The conference will deal with the logical, epistemological, and 
cognitive aspects of modeling practices employed in scientific 
discovery and technological innovation, including computational
models of such practices. Abduction is widely recognized as a 
significant reasoning process in discovery whose features are 
in need of explication. We will solicit papers that examine various
forms of model-based reasoning, such as analogical and visual 
modeling, from philosophical, historical, sociological, psychological,
or computational perspectives. We also plan to address the problem 
of model-based reasoning in ethics reasoning, especially pertaining
to science and technology. 
 

RELEVANT RESEARCH AREAS  
 
We shall call for papers that cover topics from the following list:   
   
- abduction   
- analogical reasoning    
- causal and counterfactual reasoning in model construction
- computational models of model-based reasoning and scientific reasoning 
- conceptual combination and theory formation   
- hypothetical and explanatory reasoning   
- logical analyses that may contribute to our understanding 
  of the issues in model-based reasoning   
- model-based reasoning in ethics
- models and manipulative reasoning  
- models and technological innovation
- thought experimenting   
- visual, spatial, imagistic modeling, reasoning, and simulation  

 
 
SUBMISSIONS OF PAPERS 
 
All submitted papers will be carefully refereed. The precise format 
of the conference will be fixed after we have an idea of the number of 
accepted papers. We are thinking in terms of presentations of 40 and 
20 minutes. The funding is Italian and US, but we are also looking
elsewhere 
for further financing (and would appreciate any suggestions).  
A selected subset will be invited for inclusion (subject to refereeing)
in a book which will constitute an advanced handbook for scientists
and researchers. The book will be published by an international
publishing house. Moreover another selected subset will be invited 
for inclusion (subject to refereeing) in special issues of suitable 
international Journals. 
 

FORMAT 
 
Authors must submit three printed copies and an electronic version
- formatted in Microsoft Word, RTF, PDF, or Postcript format -
of an extended abstract (about 1000 words) not later than 

November  30, 2000.

Please send electronically the extended abstract 
to the program chair at the address

lmagnani@cc.gatech.edu

in case of problem with the above address please use
lorenzo@philos.unipv.it or
lmagnaniusa@netscape.net
 
 
REGISTRATION AND FURTHER INFORMATION 
 
Registration Fees:

Before 15 March 2001:
Normal:   ITL. 300.000 = appr. US$ 155  (EUR 154.93)
                                        (to participate in all
                                        the activities of the
Conference)
Students:  Free

After  15 March 2001:
Normal:   ITL. 350.000 = appr. US$ 175   (EUR 180.75) 
                                         (to participate in all
                                         the activities of the
Conference)
Students: Free

METHOD OF PAYMENT AND REGISTRATION DEADLINE:

Bank (Swift) Transfer to BANCA REGIONALE EUROPEA S.p.A
BRANCH PAVIA - Sede
SWIFT BREUITM2 301
Bank Code 06906.11301
Acc. n. 520 Dipartimento di Filosofia
indicating  CONVEGNO INTERNAZIONALE MBR'01

PLEASE REGISTER by email, fax or air mail (before March 15, 2001) by
sending PROGRAM CHAIR first and last name, function, institution, full
address, phone, fax and email.

For information about paper submission and the program that is not  
available on the web site, please contact the program chair.
 

IMPORTANT DATES 

Registration deadline............................15 March 2001 
Submission deadline..............................30 Nov   2000 
Notification of acceptance.....................28 Feb   2001
Final papers 
(from those selected for publication) due........30 June  2001
Conference....................................17-19 May   2001
 
PROGRAM CHAIR

Lorenzo MAGNANI
School of Public Policy and College of Computing
Program in Philosophy, Science, & Technology
Georgia Institute of Technology, 685 Cherry Street
Atlanta, GA, 30332 - 0345, USA
Office: 404-894-0950 & 404-385-0884, Home: 404-875-3566
Fax: 404-385-0504 & 404-894-2970 
Email: lorenzo.magnani@cc.gatech.edu

Address in Italy:
Department of Philosophy and Computational Philosophy Laboratory
University of Pavia,
Piazza Botta 6, 27100 Pavia, Italy
Office: +39-0382-506283, Home: +39-0383-371067
Fax: +39-0382-23215
Email: lorenzo@philos.unipv.it

PROGRAM CO-CHAIR

Nancy J. NERSESSIAN (Program Co-Chair) 
Program in Cognitive Science
School of Public Policy and College of Computing, 
Georgia Institute of Technology, Atlanta, USA  
Email: nancyn@cc.gatech.edu

PROGRAM CO-CHAIR

Kenneth J. KNOESPEL (Program Co-Chair)
School of History, Technology, and Society, and
Program in Cognitive Science
Georgia Institute of Technology, Atlanta, USA  
Email: kenneth.knoespel@hts.gatech.edu


PROGRAM COMMITTEE 

- Ann Bostrom, School of Public Policy, Georgia Institute
 of Technology,
  Atlanta, GA, USA
- Elena Gagliasso, Department of Philosophical and Epistemological
Studies, 
  University of Rome La Sapienza, Rome, ITALY
- Dedre Gentner, Psychology Department, Northwestern University,
Evanston,
  IL 60208, USA
- Ronald N. Giere, Department of Philosophy, University of Minnesota,
MN, USA
- Mark L. Johnson, Department of Philosophy, 1295 University of Oregon,
  Eugene, OR, USA
- Kenneth Knoespel, School of History, Technology, and Society, Georgia 
  Institute of Technology, Atlanta, GA, USA
- Lorenzo Magnani, Department of Philosophy, University of Pavia, Pavia,
ITALY
  and School of Public Policy and College of Computing, Georgia 
  Institute of Technology, Atlanta, GA, USA 
- Pat Langley, Adaptive Systems Group, DaimlerChrysler Research &
Technology
  Center, Palo Alto, CA, USA
- Nancy J. Nersessian, School of Public Policy and College of Computing,
Georgia 
  Institute of Technology, Atlanta, GA, USA
- Brian Norton, School of Public Policy, Georgia Institute of
Technology,
  Atlanta, GA, USA
- Claudio Pizzi, Department of Philosophy and Social Sciences,
University of 
  Siena, Siena, ITALY
- Mario Stefanelli, Department of Computer Science, University of Pavia, 
  Pavia, ITALY
- Paul Thagard, Department of Philosophy, University of Waterloo,
Waterloo, 
  CANADA
- Ryan D. Tweney, Bowling Green State University, Bowling Green, OH, USA
- Stella Vosniadou, Department of Philosophy and History of Science, 
  Brain and Cognitive Science Division, National and Capodistrian
University
  of Athens, Athens, GREECE.


LOCAL ORGANIZING COMMITTEE
 
Riccardo Dossena (riki.dox@libero), Elena Gandini (elegand@yahoo.com), 
Rosella Gennari (gennari@hum.uva.nl), Lorenzo Magnani
(lmagnani@cc.gatech.edu), 
Massimo Manganaro (triskel@worldonline.it), Stefania Pernice
(stepernice@libero.it),
Matteo Piazza (pimat@yahoo.com), Giulio Poletti (philosophia@libero.it)
Stefano Rini (s.rini@philos.unipv.it), Andrea Venturi
 (aventuri@philos.unipv.,it) (Department of Philosophy, University of
Pavia, Pavia, Italy), Mario Stefanelli (mstefa@ipvstefa.unipv.it)
(Department of Computer Science, University of Pavia, Pavia, Italy).


IMPORTANT ADDRESSES 

LORENZO MAGNANI (Conference Chair)
School of Public Policy and College of Computing
Program in Philosophy, Science, & Technology
Georgia Institute of Technology, 685 Cherry Street
Atlanta, GA, 30332 - 0345, USA
Office: 404-894-9050 & 404-385-0884, Home: 404-875-3566
Fax: 404-385-0504 & 404-894-2970 
Email: lorenzo.magnani@cc.gatech.edu

Address in Italy:
Department of Philosophy and Computational Philosophy Laboratory
University of Pavia,
Piazza Botta 6, 27100 Pavia, Italy
Office: +39-0382-506283, Home: +39-0383-371067
Fax: +39-0382-23215
Email: lorenzo@philos.unipv.it



CONFERENCE SITE:

Collegio Ghislieri, Piazza Ghislieri, 27100 PAVIA, Italy,
phone +39 0382 22044. 



The Conference is sponsored by  
UNIVERSITY OF PAVIA, ITALY
GEORGIA INSTITUTE OF TECHNOLOGY, ATLANTA, GA, USA
UNIVERSITY OF SIENA, ITALY
UNIVERSITY OF ROME "LA SAPIENZA", ITALY,
MURST (Ministero dell'Università e della Ricerca Scientifica e
Tecnologica), 
ITALY,
CARIPLO (CASSA DI RISPARMIO DELLE PROVINCIE LOMBARDE, MILAN, ITALY)

HOW TO REACH PAVIA 

LINATE Airport:
People arriving by plane at LINATE should take the bus to the
CENTRAL STATION of Milan (cf below fron this Station to Pavia).
In LINATE it could be convenient to take a Taxi because the 
airport is close to the center of Milan. Moreover, The bus 
company SGEA offers six runs from LINATE to Pavia at 
9.00, 10.00, 12.00 AM and 2.00, 5.00, 8.30 PM. The last stop
is Pavia, near the station (see again our updated web page for
possible alterations of this time-table) (from Pavia to LINATE
six runs at 5,00, 7.45, 10.00 AM, 1.00, 4.00, 6.00 PM)
(one hour trip). In Pavia there is only one station. 
The easiest way to reach the center of the town is to 
get off at the station and than take the bus n. 3.


MALPENSA 2000 and OLD MALPENSA Airports (usually people
arrive to Malpensa 2000 and not to OLD MALPENSA):
People arriving by plane at MALPENSA 2000 (also called MALPENSA
2000 Terminal 1) or at "old" MALPENSA (now called MALPENSA NORTH
but also called Malpensa 2000 Terminal 2) should  take the bus
to the CENTRAL STATION of  Milan. There is also a bus AND A 
TRAIN from Malpensa 2000 to the NORTH STATION (Piazzale Cadorna)
of Milan, in this case from NORTH Station you will have to take
the underground MM1 to the Central Station: trains to Pavia leave
from Central station). Moreover, the bus company SGEA offers 
four runs from MALPENSA 2000 to Pavia at 9.00 AM, 1:30 PM, 
5.00 PM, and 9:30 PM - from Malpensa North (OLD Malpensa or 
Malpensa 2000 Terminal 2 5 munutes later) (from Pavia to MALPENSA
2000 and to OLD MALPENSA four runs at 7.00 AM, 11:00 AM, 3.15 PM,
and 7:00 PM) (one hour and half trip). The last stop is Pavia,
near the station (see again our updated web page for possible
alterations of this time-table) In Pavia there is  only one 
station. The easiest way to reach the center of the town is to 
get off at the station and than take the bus n. 3.


There are trains from MILAN (Central Station) to PAVIA and vice
Versa about every an hour (routes: MILAN-GENOVA; MILAN-VENTIMIGLIA;
MILAN-LA SPEZIA; MILAN-SAVONA; MILAN-SESTRI LEVANTE; MILAN-IMPERIA;
MILAN-ALBENGA; Pavia is the first stop only if the train is not slow,
that is, if it is not, in ITALIAN, "L", locale).

In Pavia there is only one rail station. The easiest way to reach the
center of the town is to get off at the station and than take the bus
n. 3.  


ACCOMMODATION

The WEB site of the Tourist Office is
http://www.systemy.it/pavia/home.html
(new! sorry, only in Italian). The email address is info@apt.pv.it. When 
available you will find the whole list of hotels
and other information concerning Pavia and its history. See also 
http://www.itwg.com/ct_00036.asp.

In case of accommodation problems remember we will have at our 
disposal some rooms at special "conference rates" in the Colleges 
of the University. For further information  please contact the 
Program Chair. As the the conferences dates are very close to 
summer holidays we recommend making your reservations as early
as possible and before March 31, 2000 at the latest.


ALL ACCOMMODATIONS (EXCEPT FOR INVITED SPEAKERS)
 WILL BE PROCESSED BY:

Agenzia Viaggi ALOHATOUR
Corso Cairoli 11
I - 27100 PAVIA
Italy
Phone: +39-0382-539565
Fax:   +39-0382-539572 
         +39-0382-539504 
email (only to request information): aloha@buonviaggio.it

(cut here)

**********************************************************************

ACCOMMODATION FORM - MBR'01

----------------------------------------------------------------------
TO BE FAXED:   +39-0382-539572 
                             +39-0382-539504 
OR MAILED:     Agenzia Viaggi ALOHATOUR
               Corso Cairoli 11
               I - 27100 PAVIA
               Italy
email (only to request information): aloha@buonviaggio.it
----------------------------------------------------------------------
FILL IN CAPITAL LETTERS, PLEASE

LAST NAME:___________________FIRST NAME:_____________Prof./Dr./Mr./Ms.

AFFILIATION/UNIVERSITY/DEPT.__________________________________________

STREET:_______________________________________________________________

TOWN:___________________________CODE:_____________COUNTRY:____________

PHONE:__________________FAX:__________________E-MAIL:_________________

TYPE OF TRAVELLING:__________________DATE OF ARRIVAL:_________________

DATE OF DEPARTURE:___________________NUMBER OF NIGHTS:________________

CREDIT CARD
NUMBER AND TYPE__________________________ EXPIRATION_____________

(you can also pay by bank transfer and postal order, please see below)


ACCOMMODATION INCL. BREAKFAST

                  SINGLE ROOM+BATH.  /   DOUBLE ROOM+BATH.  

***HOTEL EXCELSIOR,
Piazza Stazione,
PAVIA                 LIT. 100.000   /   LIT. 150.000   ______________
                     (EUR. 51.64    /    EUR.  77.46) 
****HOTEL ARISTON,
Via Scopoli,
PAVIA                 LIT. 130.000   /   LIT. 190.000   +_____________
                     (EUR. 67.13     /    EUR.  98.12)                   
****HOTEL MODERNO,
Viale V. Emanuele,
PAVIA                 LIT. 170.000   /   LIT. 230.000   +_____________
                      (EUR. 87.79  /    EUR.  118.78) 

RESERVATION CHARGE             LIT.  25.000   +_______
                              (EUR.  12.91) 


TOTAL AMOUNT:                                           =_____________


ACCOMMODATION DEPOSIT:     ONE NIGHT     LIT.........  - _____________
                                        (EUR)            

ACCOMMODATION BALANCE:                   LIT.........   =_____________
                                        (EUR)........    

Hotel Excelsior (from the station walk east)
Hotel Moderno (from the station walk north)
To reach Hotel Ariston take the bus n. 3 or taxi.
____________________________________________________________________
PLEASE FAX OR MAIL THIS FORM AND 
PAY BY *CREDIT CARD* BEFORE *15 MARCH 2001* 
TO:
 FAX:   +39-0382-539572 
                             +39-0382-539504 
MAIL ADDRESS:     Agenzia Viaggi ALOHATOUR
               Corso Cairoli 11
               I - 27100 PAVIA
               Italy
email (only to request information): aloha@buonviaggio.it
DATE OF PAYMENT____________YOUR SIGNATURE____________________
________________________________________________________________________

PLEASE FAX OR MAIL THIS FORM AND PAY BY *BANK TRANSFER*
BEFORE *15 MARCH 2001* (fax or mail also a copy of the bank transfer)
TO:
BANCA REGIONALE EUROPEA
S.p.A.BRANCH PAVIA - SedeSWIFT BREUITM2
301Bank Code 6906.11301
Agenzia Viaggi ALOHATOUR S.r.l. Acc.n 19952/4  

DATE OF PAYMENT____________YOUR SIGNATURE___________________
________________________________________________________________________

PLEASE FAX OR MAIL THIS FORM AND PAY BY *POSTAL ORDER*
BEFORE* 15 MARCH 2001* 
(fax or mail also a copy of the postal receipt) TO:
Agenzia Viaggi ALOHATOUR
Corso Cairoli 11
I - 27100 
PAVIA
Italy                                                                     
DATE OF PAYMENT______________________YOUR
SIGNATURE______________________

_________________________________________________________________________
ALHOATOUR WILL MAIL OR FAX YOU THE RESERVATION VOUCHER  

ALOHATOUR WILL SATISFY THE REQUESTS AS FAR AS POSSIBLE. 
IF NOT POSSIBLE, ANOTHER SIMILAR ACCOMMODATION WILL BE 
ARRANGED.


From venneri@dsi.unifi.it Mon Oct 9 19:19:30 2000 From: venneri@dsi.unifi.it (b.venneri) Date: Mon, 9 Oct 2000 14:19:30 -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. Affiliated workshops will be scheduled from September 2 through September 8. Researchers and practitioners are invited to submit workshop proposals, that may be sent to the PLI 2001 Workshop Chair Betti Venneri, venneri@dsi.unifi.it, by e-mail (Postscript, Pdf, ASCII) 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), 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. 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. web page: http://music.dsi.unifi.it/pli01/wkshops From fldrsimonmar@microsoft.com Mon Oct 9 10:54:52 2000 From: fldrsimonmar@microsoft.com (Simon Marlow) Date: Mon, 9 Oct 2000 02:54:52 -0700 Subject: Mailing list software changing Message-ID: <9584A4A864BD8548932F2F88EB30D1C6115734@TVP-MSG-01.europe.corp.microsoft.com> Dear Haskell & Haskell-cafe, At haskell.org we're migrating the mailing lists from majordomo (which is somewhat old and clunky) to Mailman, which will amongst other things make my life a lot easier, provide better archives, add digest support and allow subscription/unsubscription via a web interface. You should all receive a notification shortly about subscription to the new lists. Unfortunately it seems we have to do this, because the confirmation contains the password for accessing & modifying your personal subscription details on the web. If you *don't* receive a confirmation in the next 24 hours, please let me know. Heres hoping everything goes smoothly, and once again I apologise for the extra spam in your mailbox. Cheers, Simon From mpj@cse.ogi.edu Tue Oct 10 03:26:00 2000 From: mpj@cse.ogi.edu (Mark P Jones) Date: Mon, 9 Oct 2000 19:26:00 -0700 Subject: type class In-Reply-To: <39D38A5F.F01D7437@yale.edu> Message-ID: Hi Zhanyong, | In Haskell, instances of a type class can only be well-formed type | constructors ... | Note there is no type constructor abstraction. |=20 | In practice, I found this rule too restrictive. There are good reasons for the restrictions that were alluded to in my constructor classes paper, and again in Typing Haskell in Haskell. Some text from emails written when this topic came up previously is attached to the end of this message. Actually, the first part of the attached email deals with a different problem (making Set an instance of Monad), but since that also came up for discussion again quite recently, I don't think it will hurt to include it again here. | How about extending TC with a branch for abstraction: |=20 | TC ::=3D ... | | /\a. TC -- abstraction |=20 | This is too powerful and will get out of control -- we surely don't = want | to give TC the full power of lambda-calculus. So let's impose a | restriction: in /\a.TC, a must occur free in TC *exactly once*. This | way, abstraction can only be used to specify with respect to which | argument a partial application is. (or I think so -- I haven't tried = to | prove it.) My instinct (which perhaps somebody will prove incorrect) is that this = will not help. Suppose, for example, that you needed to unify ([a],[b]) with = f c as part of the type inference process. How would you solve this = problem? Alas, there are several different, and incompatible ways: ([a], [b]) =3D (/\a. ([a],[b])) a =3D (/\b. ([a],[b])) b =3D (/\c. (c, [b])) [a] =3D (/\d. ([a], d)) [b] =3D (/\e. e) ([a], [b]) Note that the /\-terms in each of these examples satisfies your = restriction. So I don't think you'll be able to obtain most general unifiers or = principal types with this restriction. In my opinion, Dale Miller's work on Higher-order patterns (introduced, = I think in about 1991, but I don't have references) would probably be the best = starting point for serious experimentation in this area. Hope this helps, Mark -- From the archives: = ------------------------------------------------------- Hi Michael, | "...type synonyms must be fully applied". I think the above | example is a valid objection to this. I'll append some text that I wrote on a previous occasion when somebody asked why type synonyms couldn't be partially applied. I hope that it will help to explain why the restriction is not easy to lift, however desirable it might be. The example there was a little different, but I'm sure that you'll see the correspondence. | The other example of something that I want to declare as a monad, but | which I can not is this: Consider a type of collection of some sort = that | requires the types of the elements to be instances of some specific = class. This too is a problem that has come up quite a few times in the past. As yet, I'm not sure that anyone has a definitive answer for it either, although the work that John Hughes presented at the Haskell workshop on Restricted Datatypes is perhaps the closest that anyone has come so far. A general problem here is that there are differences between = conventional mathematics---where you can have sets of any type---and the mathematics = of programming languages---where interesting set datatypes can only be constructed on types whose elements have, at least, an equality. In = Haskell terms, mathematics has an equality function of type: forall a. a -> a -> = Bool; the same operator is available to mathematicians who reason about = Haskell programs. But Haskell programmers have to make do with a more = restrictive operator of type forall a. Eq a =3D> a -> a -> Bool. (Which is not = actually an equality operator at all when you look at what's really going on; = it's just a kind of identity function or projection!) All the best, Mark =20 Here's the text I promised: | I'd like to use monadic code on the following type | type IOF b a =3D b -> IO a | The following seemed reasonable enough: | instance Monad (IOF b) where ... | But Hugs and GHC both object ... The example is rejected because type synonyms can only be used if a full complement of arguments has been given. There are at least two kinds of problem that can occur if you relax this restriction, but both are related to unification/matching. Suppose that we allow your definition. And suppose that we also allow: instance Monad ((->) env) where ... which is a perfectly reasonable thing to do (it's the reader monad). Now what should we do when faced with the problem of unifying two type expressions like: m c and b -> IO a ... Haskell unifies these with the substitution: {m +-> ((->) b), c +-> IO a}, but with your instance decl, you might have preferred { m +-> IOF b, c +-> a }. In other words, it's ambiguous, and the choice between these two could change the semantics because you'll end up picking different instances depending on which choice you make. Or consider what you really mean when you write (IOF b) ... my guess is that you're thinking of it as adding a kind of lambda, so that IOF b =3D \a. a -> IO b This is appealing, but also means that we'd need to move up to = higher-order unification which is undecidable and non-unitary. For example, now we could match m c to b -> IO a in all kinds of interesting ways: b -> IO a =3D (\b . b -> IO a) b =3D (\a . b -> IO a) a =3D (\z . b -> z) (IO a) =3D (\z . b -> IO a) Int =3D ... Now we really have ambiguity problems to worry about! Requiring type synonyms to be fully applied --- in effect, telling us that a synonym is nothing more than an abbreviation, and has no other consequences for the semantics --- seems like a nice way to avoid these problems. -------------------------------------------------------------------------= --- From zhanyong.wan@yale.edu Wed Oct 11 14:53:52 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Wed, 11 Oct 2000 09:53:52 -0400 Subject: type class References: Message-ID: <39E470F0.4F351EEC@yale.edu> Hi Mark, Thanks for the references you provided! Mark P Jones wrote: > My instinct (which perhaps somebody will prove incorrect) is that this will > not help. Suppose, for example, that you needed to unify ([a],[b]) with f c > as part of the type inference process. How would you solve this problem? > Alas, there are several different, and incompatible ways: > > ([a], [b]) = (/\a. ([a],[b])) a > = (/\b. ([a],[b])) b > = (/\c. (c, [b])) [a] > = (/\d. ([a], d)) [b] > = (/\e. e) ([a], [b]) > > Note that the /\-terms in each of these examples satisfies your restriction. > So I don't think you'll be able to obtain most general unifiers or principal > types with this restriction. Let's put your example into the context of type classes: class T f c where method :: f c Now when we want to use method as a ([a],[b]), ambiguity arises, as you suggested. However, I think this just means we should allow *at most one* of the following instances to be declared: instance T (/\a. ([a],[b])) a instance T (/\b. ([a],[b])) b instance T (/\c. (c, [b])) [a] instance T (/\d. ([a], d)) [b] instance T (/\e. e) ([a], [b]) In other words, the above instances are considered overlapping. ____________________________________________________ | As long as we only have one of these instances | | in the program, there is no ambiguity. | ---------------------------------------------------- I'm sure there must be other ramifications (e.g. maybe now whether two instances are overlapping becomes undecidable -- I haven't thought over it yet), but it seems worth further investigation. -- Zhanyong From senganb@ia.nsc.com Thu Oct 12 21:11:16 2000 From: senganb@ia.nsc.com (Sengan) Date: Thu, 12 Oct 2000 16:11:16 -0400 Subject: How does one find lazyness bottlenecks? Message-ID: <39E61AE4.1D8DACE9@ia.nsc.com> Now that ghc 4.08 has a time profiler, I've been improving a program I wrote over the last year. However now the GC time dominates the execution time (>60%). I can see that my program is not being lazy, but I have no idea why. How can I use profiling (or any other means) to determine where my program is not being sufficiently lazy? Are there papers on such things I could read? Sengan From fjh@cs.mu.oz.au Fri Oct 13 01:49:05 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Fri, 13 Oct 2000 11:49:05 +1100 Subject: How does one find lazyness bottlenecks? In-Reply-To: <39E61AE4.1D8DACE9@ia.nsc.com> References: <39E61AE4.1D8DACE9@ia.nsc.com> Message-ID: <20001013114905.A3316@hg.cs.mu.oz.au> On 12-Oct-2000, Sengan wrote: > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. What makes you think that the GC time is due to insufficient laziness? My first thought is that high GC times may well be due to the opposite, too much laziness. Being lazy means that you create closures to represent unevaluated expressions, and those closures will eventually need to be garbage collected. -- Fergus Henderson | "I have always known that the pursuit WWW: | of excellence is a lethal habit" PGP: finger fjh@128.250.37.3 | -- the last words of T. S. Garp. From chak@cse.unsw.edu.au Fri Oct 13 05:16:48 2000 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Fri, 13 Oct 2000 15:16:48 +1100 Subject: How does one find lazyness bottlenecks? In-Reply-To: <39E61AE4.1D8DACE9@ia.nsc.com> References: <39E61AE4.1D8DACE9@ia.nsc.com> Message-ID: <20001013151648K.chak@cse.unsw.edu.au> Sengan wrote, > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. How can I use profiling (or any other means) > to determine where my program is not being sufficiently lazy? Are there > papers on such things I could read? If GC times dominates, you probably have a space leak. So, you should use space profiling to determine where the leak is. Depending on what kind of program you have, it is often also informative to check the space profiles for different kinds of inputs, as the leak might only occur for certain inputs. Depending on the code exercised by the inputs triggering the leak, you might get a rough idea which parts of your program leak. Cheers, Manuel From sylvan@ravinet.com Fri Oct 13 11:18:26 2000 From: sylvan@ravinet.com (Sylvan Ravinet) Date: Fri, 13 Oct 2000 13:18:26 +0300 (EEST) Subject: Haskell to XSLT? Message-ID: Hello, I was wondering if there are ways to translate Haskell code to XSLT. Any ideas? Thank you for your help, Best regards, -Sylvan -- No, try not. Do, or do not. There's no try. -Yoda Sylvan Ravinet: http://www.ravinet.com/sylvan/contact/ -- This message is Copyright 2000 by Sylvan Ravinet. All rights (and responsibility) reserved. From luti@linkexpress.com.br Fri Oct 13 22:42:24 2000 From: luti@linkexpress.com.br (Luciano Caixeta Moreira) Date: Fri, 13 Oct 2000 18:42:24 -0300 Subject: (no subject) Message-ID: <003e01c0355e$7cb4de40$a8adfcc8@servidor> This is a multi-part message in MIME format. ------=_NextPart_000_0035_01C03545.53E7F560 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable unsubscribe haskell@haskell.org ------=_NextPart_000_0035_01C03545.53E7F560 Content-Type: text/html; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable
unsubscribe haskell@haskell.org
------=_NextPart_000_0035_01C03545.53E7F560-- From romildo@urano.iceb.ufop.br Sat Oct 14 05:38:09 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 02:38:09 -0200 Subject: Haskore and nhc98 Message-ID: <20001014023809.A18261@urano.iceb.ufop.br> Hello. I am just curious whether anybody has already tried Haskore (http://www.haskell.org/haskore/) with the NHC98 Haskell compiler. I am trying to do it, while GHC 4.08.1 is non functional in my RH Linux 7.0 box. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From romildo@urano.iceb.ufop.br Sat Oct 14 06:48:06 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 03:48:06 -0200 Subject: Binary files and NHC98 Message-ID: <20001014034806.A23040@urano.iceb.ufop.br> --wRRV7LY7NUeQGEoC Content-Type: text/plain; charset=iso-8859-1 Content-Disposition: inline Content-Transfer-Encoding: 8bit Hello. In order to experiment with the Binary module distributed with nhc98, I wrote the attached program which writes a binary file and then reads it. When executed, I got an extra byte (8) that I cannot explain: [65,66,67,68,8] Any clues why it appears? Regards, Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil --wRRV7LY7NUeQGEoC Content-Type: text/plain; charset=us-ascii Content-Disposition: attachment; filename="BinaryFile.hs" module Main where import IO (IOMode(ReadMode,WriteMode)) import Binary (openBin,closeBin,getBits,putBits,isEOFBin, BinIOMode(RO,WO),BinLocation(File),BinHandle) -- convert from IOMode to BinIOMode ioModeToBinIOMode :: IOMode -> BinIOMode ioModeToBinIOMode ReadMode = RO ioModeToBinIOMode WriteMode = WO -- open a binary file openBinaryFile :: FilePath -> IOMode -> IO BinHandle openBinaryFile path mode = openBin (File path (ioModeToBinIOMode mode)) -- write a list of integers (8 bits) to binary file writeBinaryFile :: FilePath -> [Int] -> IO () writeBinaryFile fileName xs = do f <- openBinaryFile fileName WriteMode let writeToBin [] = return () writeToBin (x:xs) = do putBits f 8 x writeToBin xs writeToBin xs closeBin f -- read a list of integers (8 bits) from binary file readBinaryFile :: FilePath -> IO [Int] readBinaryFile fileName = do f <- openBinaryFile fileName ReadMode let readFromBin = do eof <- isEOFBin f if eof then return [] else do x <- getBits f 8 xs <- readFromBin return (x:xs) xs <- readFromBin closeBin f return xs -- test the above main = do writeBinaryFile "test.bin" [65,66,67,68] xs <- readBinaryFile "test.bin" putStrLn (show xs) --wRRV7LY7NUeQGEoC-- From romildo@urano.iceb.ufop.br Sat Oct 14 08:49:52 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 05:49:52 -0200 Subject: NHC98 and GHC 4.08.1 differ on monad related functions Message-ID: <20001014054952.A27804@urano.iceb.ufop.br> --4Ckj6UjgE2iN1+kY Content-Type: text/plain; charset=iso-8859-1 Content-Disposition: inline Content-Transfer-Encoding: 8bit Hello. While porting Haskore to NHC98 I got an error I am not understanding. I have attached a test module that shows the error message: $ nhc98 -c Test.hs ==================================== Error after type deriving/checking: No default for Monad.MonadPlus at 7:1.(171,[(2,209)]) No default for Monad.MonadPlus at 6:1.(174,[(2,208)]) GHC 4.08.1 and Hugs98 accepts the code without complaining. Any hints? Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil --4Ckj6UjgE2iN1+kY Content-Type: text/plain; charset=us-ascii Content-Disposition: attachment; filename="Test.hs" module Test where import Monad zeroOrMore, oneOrMore :: MonadPlus m => m a -> m [a] zeroOrMore m = return [] `mplus` oneOrMore m oneOrMore m = do { a <- m; as <- zeroOrMore m; return (a:as) } --4Ckj6UjgE2iN1+kY-- From nikhil@acm.org Mon Oct 16 09:21:39 2000 From: nikhil@acm.org (Rishiyur S. Nikhil) Date: Mon, 16 Oct 2000 01:21:39 -0700 Subject: Haskell puzzle Message-ID: <39EABA93.DAD34B10@mediaone.net> In Haskell, is the following transformation always legal? \x->\y->e transforms to \x y->e After answering this question, please scroll down about 75 lines for a follow-up question. What if the two lambda-bound variables are the same? I.e., the lhs is \x->\x->e Please refer to Section 3.3 of the Haskell 98 Report, para 3 (one line para). From timd@macquarie.com.au Tue Oct 17 02:30:58 2000 From: timd@macquarie.com.au (Timothy Docker) Date: Tue, 17 Oct 2000 12:30:58 +1100 (EST) Subject: Mutually recursive structures Message-ID: <14827.43685.102410.194472@tcc2> The following problem has been taxing me.... I have a list of pairs that I have parsed from a input file, which represent a hiirarchy, where the first element is the name of the object, and the second is the name of the parent if there is one: type ParseOutput = [(String,Maybe String)] I wish to convert this to a list of "objects", where from each object I can navigate to the parent object (if any), or the children (if any): data Obj = Obj { name::String, parent::(Maybe Obj), children::[Obj] } type Result = [Obj] convert:: ParseOutput -> Result In a language with mutable references, this would be a relatively straightforward. I would just create a dictionary mapping from name to Obj, and then iterate over them, filling in the parents and children where appropriate. odict = {} for (name,parent) in parseOutput: odict[name] = Obj() for (name,parent) in parseOutput: if parent: parent = odict[parent] child = odict[name] child.parent = parent parent.children.append( child ) This gives away my background! How can I do this in Haskell? If I don't have mutable references, I figure that I must need to use laziness in some way, perhaps similar to how I would build an infinite structure. A hint or two would be great. Tim From Tom.Pledger@peace.com Tue Oct 17 04:32:13 2000 From: Tom.Pledger@peace.com (Tom Pledger) Date: Tue, 17 Oct 2000 16:32:13 +1300 (NZDT) Subject: Mutually recursive structures In-Reply-To: <14827.43685.102410.194472@tcc2> References: <14827.43685.102410.194472@tcc2> Message-ID: <14827.51261.117517.96548@waytogo.peace.co.nz> Timothy Docker writes: > [...] How can I do this in Haskell? If I don't have mutable > references, I figure that I must need to use laziness in some way, > perhaps similar to how I would build an infinite structure. http://www.mail-archive.com/haskell@haskell.org/msg06321.html I have nothing to add to that explanation, so will conserve bandwidth by From christian@lescher.de Tue Oct 17 20:29:25 2000 From: christian@lescher.de (Christian Lescher) Date: Tue, 17 Oct 2000 20:29:25 +0100 Subject: Haskell function with String arguments in DLL Message-ID: <39ECA895.4681986B@lescher.de> I'm trying to build a DLL with a Haskell function of type String -> String, that should be called from outside (e.g. VBA), but it still doesn't work. I'm afraid I need an example or some kind of 'step by step instruction'. Who can help me? (I use GHC 4.08.1.) Christian From timd@macquarie.com.au Tue Oct 17 22:25:58 2000 From: timd@macquarie.com.au (Timothy Docker) Date: Wed, 18 Oct 2000 08:25:58 +1100 (EST) Subject: Mutually recursive structures In-Reply-To: <14827.51261.117517.96548@waytogo.peace.co.nz> References: <14827.43685.102410.194472@tcc2> <14827.51261.117517.96548@waytogo.peace.co.nz> Message-ID: <14828.49022.234836.837956@tcc2> Tom Pledger writes: > Timothy Docker writes: > > [...] How can I do this in Haskell? If I don't have mutable > > references, I figure that I must need to use laziness in some way, > > perhaps similar to how I would build an infinite structure. > > http://www.mail-archive.com/haskell@haskell.org/msg06321.html > To be honest, I found this code quite confusing, I think because of the way in which a the "tail" needs to be joined back to the "head" in creating a circular data structure. I did eventually come up with a solution that seems straightforward enough, although I have no idea of its efficiency... | type ParseOutput = [(String,Maybe String)] | | data Obj = Obj { oname::String, | oparent::(Maybe Obj), | ochildren::[Obj] } | | convert:: ParseOutput -> [Obj] | convert output = converted | where converted = map mkObj output | mkObj (name,parent) = (Obj name | (fmap (findObj converted) parent) | (filter (hasParentNamed name) converted) ) | | findObj:: [Obj] -> String -> Obj | findObj [] name = error ("No object with name "++name) | findObj (o:os) name | name == (oname o) = o | | otherwise = findObj os name | | hasParentNamed :: String -> Obj -> Bool | hasParentNamed name obj = maybe False ((==name).oname) (oparent obj) | Thanks for the pointer. Tim From koen@cs.chalmers.se Wed Oct 18 11:57:56 2000 From: koen@cs.chalmers.se (Koen Claessen) Date: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST) Subject: Num class Message-ID: Hi all, For years I have wondered why the Num class has the Eq class and the Show class as super classes. Because of this, I cannot make functions an instance of Num (becuase they are not in Eq or Show). Or a datatype respresenting an infinite amount of digits (because Eq would not make any sense). Now I have found out the reason! However, it does not make me happy, it makes me even more sad. It is of the defaulting mechanism of course! The defaulting mechanism works as follows: If there is an unresolved overloading error on a type variable a, which has as an *only* constraint (Num a), then we take a to be the suitable default. If Show were not a super class of Num, the following program would generate an error: main = print 42 If Eq were not a super class, the following program would not work: main = print (if 42 == 42 then "koe" else "apa") These programs are all fixed by inserting Show and Eq as super classes of Num. So that one does not even notice! Until now. I am interfacing to an external library that uses double-precision floating points internally for all numbers. This is to be as general as possible. However, I know that when I put for example an Integer in, I get one out too. Thus, I want to give a Haskell interface that can deal with this by any numeric type. So I define a type class: class Num a => Number a where convertToDouble :: a -> Double convertFromDouble :: Double -> a (somehow the Haskell numerical hierarchy does not even let me define general functions that do this! -- but that is besides the point.) instance Number Int instance Number Integer instance Number Float instance Number Double ... All my library functions now have the shape: libraryFunction :: Number a => ... a ... Where as actually: primLibraryFunction :: ... Double ... And now the bad thing... When I use "libraryFunction" on a numeric constant, such as 42, I get the error: ERROR "library.hs" (line 8): Unresolved overloading *** Binding : main *** Outstanding context : Number b This is really annoying, and it is not clear why the default mechanism works this way. So here are my questions. Why does the default mechanism have this restriction? I know that the default mechanism is already broken (some desirable properties are destroyed) -- what properties will be broken by lifting this restriction? /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden From p.turner@computer.org Wed Oct 18 12:37:38 2000 From: p.turner@computer.org (Scott Turner) Date: Wed, 18 Oct 2000 07:37:38 -0400 Subject: pronunciation of >>= Message-ID: <3.0.5.32.20001018073738.009a6750@mail.billygoat.org> Is there a common way to pronounce ">>=" in discussions or when teaching? I've learned all my Haskell from printed/visual documents. -- Scott Turner p.turner@computer.org http://www.ma.ultranet.com/~pkturner From d95lars@dtek.chalmers.se Wed Oct 18 12:43:34 2000 From: d95lars@dtek.chalmers.se (Lars Lundgren) Date: Wed, 18 Oct 2000 13:43:34 +0200 (MEST) Subject: pronunciation of >>= In-Reply-To: <3.0.5.32.20001018073738.009a6750@mail.billygoat.org> Message-ID: On Wed, 18 Oct 2000, Scott Turner wrote: > Is there a common way to pronounce ">>=" in discussions or when teaching? > I've learned all my Haskell from printed/visual documents. How about 'bind'? and ">>" => 'then'. /Lars L From qrczak@knm.org.pl Wed Oct 18 21:02:18 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 18 Oct 2000 20:02:18 GMT Subject: Num class References: Message-ID: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST), Koen Claessen pisze: > The defaulting mechanism works as follows: If there is an unresolved > overloading error on a type variable a, which has as an *only* > constraint (Num a), then we take a to be the suitable default. This is not what the Haskell 98 Report says. Section 4.3.4: "In situations where an ambiguous type is discovered, an ambiguous type variable is defaultable if at least one of its classes is a numeric class (that is, Num or a subclass of Num) and if all of its classes are defined in the Prelude or a standard library (Figures 6--7 show the numeric classes, and Figure 5 shows the classes defined in the Prelude.)" I see no good reason for Show superclass of Num. Eq makes a little more sense, but could be dropped too. It would be inferred separately when a numeric literal is used in a pattern. I agree that the default mechanism is ugly, and that at least the restriction about classes defined in standard libraries should be removed. Clean has per-class defaults. I don't know how conflicting defaults coming from different class constraints should be solved, or what about multiparameter classes, and whether extending the defaulting mechanism is a good idea at all. But since we don't have anything better... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK From mpj@cse.ogi.edu Wed Oct 18 22:46:24 2000 From: mpj@cse.ogi.edu (Mark P Jones) Date: Wed, 18 Oct 2000 14:46:24 -0700 Subject: Num class In-Reply-To: Message-ID: This is a multi-part message in MIME format. ------=_NextPart_000_0001_01C03912.2FCECB10 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable Hi Koen, | If Show were not a super class of Num, the following program | would generate an error: |=20 | main =3D print 42 |=20 | If Eq were not a super class, the following program would | not work: |=20 | main =3D print (if 42 =3D=3D 42 then "koe" else "apa") |=20 | These programs are all fixed by inserting Show and Eq as | super classes of Num. So that one does not even notice! Your claims are incorrect. Both of these examples type check without any errors, and regardless of whether Show and Eq are included as superclasses of Num. It is easy to verify this using "Typing Haskell in Haskell" (http://www.cse.ogi.edu/~mpj/thih); I'll attach the script that I used for this below. Put this in the same directory as all the other .hs files and load it into Hugs. Then edit StdPrel.hs to remove the superclasses of cNum, (replace [cEq, cShow] with []), and it will still work. | For years I have wondered why the Num class has the Eq class | and the Show class as super classes. |=20 | Because of this, I cannot make functions an instance of Num | (because they are not in Eq or Show). Or a datatype | representing an infinite amount of digits (because Eq would | not make any sense). |=20 | Now I have found out the reason! I don't think you have. I do not know the reason either, but I suspect that it is largely historical; when Haskell was first designed, the only types that people wanted to put in Num were also equality and showable types. By making Eq and Show superclasses of Num, types could sometimes be stated more concisely, writing things like (Num a) =3D> ... instead of (Num a, Eq a, Show a) =3D> ... In the past ten years since the Haskell class hierarchy was, more or less, fixed, we've seen several examples of types that don't quite fit (Like functions, computable reals, etc. which might make sense in Num but not in Eq). A natural conclusion is that several of the superclass relations between classes should be removed. But realize that there is an unavoidable compromise here: generality versus the convenience of shorter types. I suggest that there is no point on the spectrum that would keep everybody happy all the time. | It is of the defaulting mechanism of course! | ... Defaulting is a red herring in trying to understand why Show and Eq are superclasses of Num. Marcin has already pointed out that your description of the Haskell defaulting mechanism is not correct by quoting from the Haskell report. You can find another description, again based on the report, in the thih paper. | So I define a type class: | class Num a =3D> Number a where | convertToDouble :: a -> Double | convertFromDouble :: Double -> a |...=20 | All my library functions now have the shape: | libraryFunction :: Number a =3D> ... a ... | ... | And now the bad thing... When I use "libraryFunction" on a | numeric constant, such as 42, I get the error: |=20 | ERROR "library.hs" (line 8): Unresolved overloading | *** Binding : main | *** Outstanding context : Number b |=20 | So here are my questions. Why does the default mechanism | have this restriction? I know that the default mechanism is | already broken (some desirable properties are destroyed) -- | what properties will be broken by lifting this restriction? Defaulting only kicks in if (a) at least one class is numeric, and (b) all classes are standard. Number is not a standard class (you just defined it yourself), so defaulting will not apply. Defaulting was designed to work in this way so that (i) it would catch and deal with the most common problems occurring with numeric literals, and (ii) it would not be used too often; defaulting is in general undesirable because it can silently change the semantics. Again, defaulting is an example of a compromise in the design of Haskell. Ideally, you'd do without it all together, but if you went that way, you'd end up having to write more type information in your programs. And again, I don't suppose there is a universally satisfactory point on this spectrum. All the best, Mark -------------------------------------------------------------------------= --- mpj@cse.ogi.edu Pacific Software Research Center, Oregon Graduate = Institute Want to do a PhD or PostDoc? Interested in joining PacSoft? Let us = know! ------=_NextPart_000_0001_01C03912.2FCECB10 Content-Type: text/plain; name="SourceFortyTwo.hs" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="SourceFortyTwo.hs" module SourceFortyTwo where import Testbed import HaskellPrims import HaskellPrelude -------------------------------------------------------------------------= ---- -- Test Framework: main :: IO () main =3D test imports fortyTwo saveList :: IO () saveList =3D save "FortyTwo" imports fortyTwo imports :: [Assump] imports =3D defnsHaskellPrims ++ defnsHaskellPrelude -------------------------------------------------------------------------= ---- -- Test Program: fortyTwo :: [BindGroup] fortyTwo =3D map toBg [[("main", Nothing, [([], ap [evar "print", elit (LitInt 42)])])], [("main'", Nothing, [([], ap [evar "print",=20 eif (ap [econst eqMfun, elit (LitInt 42), elit (LitInt = 42)]) (elit (LitStr "koe")) (elit (LitStr "apa"))])])]] -------------------------------------------------------------------------= ---- ------=_NextPart_000_0001_01C03912.2FCECB10-- From senganb@ia.nsc.com Thu Oct 19 01:31:02 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 18:31:02 -0600 (MDT) Subject: mapM/concatMapM Message-ID: <200010190031.SAA16141@ia.nsc.com> mapM seems to be a memory hog (and thus also concatMapM). In the following eg: > main = mapM print ([1..102400] :: [Integer]) memory usage climbs to 1.6M with ghc and needs -K20M, whereas with > main = print ([1..102400] :: [Integer]) memory usage is only 1300 bytes. I instrumented mapM: > main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) > mapM2 :: Monad m => (a -> m b) -> [a] -> m [b] > mapM2 f [] = return [] > mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x -> > _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs -> > _scc_ "f" return (x:xs))) and found that a and b were the worst heap users (according to hp2ps), ie the two >>='s Why is this so? What can I do about it? My code uses mapM pretty extensively, and I think its suffering from this problem. I notice that ghc does not seem to use mapM except in 2 modules. Another odd thing is that hp2ps says that a & b are the culprits, but the -p and -px options say p is. Why? Sengan From jenglish@flightlab.com Thu Oct 19 03:03:05 2000 From: jenglish@flightlab.com (Joe English) Date: Wed, 18 Oct 2000 19:03:05 -0700 Subject: mapM/concatMapM In-Reply-To: <200010190031.SAA16141@ia.nsc.com> References: <200010190031.SAA16141@ia.nsc.com> Message-ID: <200010190203.TAA16483@dragon.flightlab.com> senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > mapM seems to be a memory hog (and thus also concatMapM). > In the following eg: > > > main = mapM print ([1..102400] :: [Integer]) > > memory usage climbs to 1.6M with ghc and needs -K20M As a guess: since 'mapM print ([1..102400] :: [Integer])' has type 'IO [()]', perhaps the result of the IO operation -- a list of 100K empty tuples -- is the culprit, even though the result is never used. Does 'mapM_ print ... ' (:: IO ()) perform any better? --Joe English jenglish@flightlab.com From senganb@ia.nsc.com Thu Oct 19 05:09:21 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 22:09:21 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190203.TAA16483@dragon.flightlab.com> from "Joe English" at Oct 18, 2000 07:03:05 PM Message-ID: <200010190409.WAA16637@ia.nsc.com> > > > senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > > > mapM seems to be a memory hog (and thus also concatMapM). > > In the following eg: > > > > > main = mapM print ([1..102400] :: [Integer]) > > > > memory usage climbs to 1.6M with ghc and needs -K20M > > As a guess: since 'mapM print ([1..102400] :: [Integer])' > has type 'IO [()]', perhaps the result of the IO operation -- > a list of 100K empty tuples -- is the culprit, even though > the result is never used. > > Does 'mapM_ print ... ' (:: IO ()) perform any better? Yes, but in the following eg > main = print $ sum x > x = _scc_ "x" [1..102400] :: [Integer] x takes 1M allocations, and I would think that () would be smaller than an Integer. Therefore I'm not sure that is the reason. The sum is there to force the evaluation. Sengan From senganb@ia.nsc.com Thu Oct 19 05:34:01 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 22:34:01 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190409.WAA16637@ia.nsc.com> from "senganb@ia.nsc.com" at Oct 18, 2000 10:09:21 PM Message-ID: <200010190434.WAA20212@ia.nsc.com> > > senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > > > > > mapM seems to be a memory hog (and thus also concatMapM). > > > In the following eg: > > > > > > > main = mapM print ([1..102400] :: [Integer]) > > > > > > memory usage climbs to 1.6M with ghc and needs -K20M > > > > As a guess: since 'mapM print ([1..102400] :: [Integer])' > > has type 'IO [()]', perhaps the result of the IO operation -- > > a list of 100K empty tuples -- is the culprit, even though > > the result is never used. > > > > Does 'mapM_ print ... ' (:: IO ()) perform any better? > > Yes, but in the following eg > > > main = print $ sum x > > x = _scc_ "x" [1..102400] :: [Integer] > > x takes 1M allocations, and I would think that () would be smaller than > an Integer. Therefore I'm not sure that is the reason. The sum is there to > force the evaluation. Assuming you are right, why do I see the same 1.6M profile with: > main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) >> return () > mapM2 :: Monad m => (a -> m b) -> [a] -> m [b] > mapM2 f [] = return [] > mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x -> > _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs -> > _scc_ "f" return (x:xs))) Is >>= not lazy? Sengan From senganb@ia.nsc.com Thu Oct 19 07:11:29 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Thu, 19 Oct 2000 00:11:29 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190434.WAA20212@ia.nsc.com> from "senganb@ia.nsc.com" at Oct 18, 2000 10:34:01 PM Message-ID: <200010190611.AAA03566@ia.nsc.com> Actually I think I figured it out: (>>=) (f c) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (>>=) _(f c)_ (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (>>=) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (\(MN c1) \fc2 -> MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = fc2 r1 (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) r1 (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) So the "return (r1:xs)" will only happen once the whole mapM has completed, leaving, if I only use r1 at first, a whole load of partially evaluated iterations of mapM in the heap. This also means that sequences such as "mapM x >>= mapM y >>= mapM z" are very inefficient and should be replaced by mapM (z.y.x) whereever possible. Agreed? Sengan From xvw@trinity.warande.net Thu Oct 19 22:24:13 2000 From: xvw@trinity.warande.net (xander) Date: Thu, 19 Oct 2000 23:24:13 +0200 (CEST) Subject: hugs/ghc + shared mem access Message-ID: Hi, I'm exploring my options to connect 2 programs (1 Haskell, 1 non-Haskell). I could connect both programs by 1 or 2 sockets. I was wondering whether it's feasible to access shared memory from within hugs as an alternative? Any answers? Thanks, xander van wiggen From frido@q-software-solutions.com.NO-spam Fri Oct 20 07:46:37 2000 From: frido@q-software-solutions.com.NO-spam (Friedrich Dominicus) Date: 20 Oct 2000 08:46:37 +0200 Subject: A question regarding haskell mode for Emacs In-Reply-To: John Atwood's message of "Tue, 22 Aug 2000 13:20:14 -0700 (PDT)" References: <200008222020.NAA25101@jasper.CS.ORST.EDU> Message-ID: <8766morovm.fsf@q-software-solutions.com> I wonder if there are some known troubles. This mode yesterday nearly drive me nuts. Indentation seem to be ok from the layout, but I got complains about block closed to early, missing ; ... Regards Friedrich -- for e-mail reply remove all after .com From romildo@urano.iceb.ufop.br Fri Oct 20 10:21:51 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Fri, 20 Oct 2000 07:21:51 -0200 Subject: Extensible data types? In-Reply-To: ; from rob@benchees.demon.co.uk on Mon, Sep 25, 2000 at 12:32:47PM +0100 References: ; <20000925082731.A3440@urano.iceb.ufop.br> Message-ID: <20001020072151.A1810@urano.iceb.ufop.br> Hello. I am back with the issue of extensible union types. Basically I want to extend a data type with new value constructors. Some members of the list pointed me to the paper "Monad Transformers and Modular Interpreters" Sheng Liang, Paul Hudak and Mark Jones The authors suggest using a type constructor to express the disjoint union of two other types: data Either a b = Left a | Right b which indeed is part of the Haskell 98 Prelude. Then they introduce a subtype relationship using multiparameter type classes: class SubType sub sup where inj :: sub -> sup -- injection prj :: sup -> Maybe sub -- projection The Either data type consructor is then used to express the desired subtype relationshipe: instance SubType a (Either a b) where inj = Left prj (Left x) = Just x prj _ = Nothing instance SubType a b => SubType a (Either c b) where inj = Right . inj prj (Right x) = prj x prj _ = Nothing The authors implemented their system in Gofer, due to restrictions in the type class system of Haskell. But now that there are Haskell extensions to support multiparametric type classes, that could be implemented in Haskell. The above code fails to type check due to instances overlapping. Hugs gives the following error message: ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType" *** This instance : SubType a (Either b c) *** Overlaps with : SubType a (Either a b) *** Common instance : SubType a (Either a b) (I did not check Gofer, but is there a way to solve these overlapping of instances in it?) So this is scheme is not going to work with Haskell (extended with multiparameter type classes). I would like hear any comments from the Haskell comunity on this subject. Is there a workaround for the overlapping instances? Regards. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From labra@pinon.ccu.uniovi.es Fri Oct 20 11:36:39 2000 From: labra@pinon.ccu.uniovi.es (Jose Emilio Labra Gayo) Date: Fri, 20 Oct 2000 12:36:39 +0200 (METDST) Subject: Extensible data types? In-Reply-To: <20001020072151.A1810@urano.iceb.ufop.br> Message-ID: > > The above code fails to type check due to instances > overlapping. Hugs gives the following error message: > In Hugs, there is a flag that you can set to allow overlapping instances :s +o In GHC, you can also set -fallow-overlapping-instances BTW, I use extensible union types in a "Language prototyping System" that I am implementing and which compiles with GHC and Hugs (it is based on Liang, Hudak and Jones paper). You can download the source code from "http://lsi.uniovi.es/~labra/LPS/LPS.html" Best regards, Jose Labra http://lsi.uniovi.es/~labra From doaitse@cs.uu.nl Fri Oct 20 14:16:34 2000 From: doaitse@cs.uu.nl (S. Doaitse Swierstra) Date: Fri, 20 Oct 2000 15:16:34 +0200 Subject: Extensible data types? In-Reply-To: <20001020072151.A1810@urano.iceb.ufop.br> References: ; <20000925082731.A3440@urano.iceb.ufop.br> <20001020072151.A1810@urano.iceb.ufop.br> Message-ID: It is exactly for reasons like these that we developped our small attribute grammar system: http://www.cs.uu.nl/groups/ST/Software/UU_AG/index.html Doaitse Swiesrtra At 7:21 AM -0200 10/20/00, Jos=E9 Romildo Malaquias wrote: >Hello. > >I am back with the issue of extensible union types. Basically >I want to extend a data type with new value constructors. >Some members of the list pointed me to the paper > > "Monad Transformers and Modular Interpreters" > Sheng Liang, Paul Hudak and Mark Jones > >The authors suggest using a type constructor to express >the disjoint union of two other types: > > data Either a b =3D Left a | Right b > >which indeed is part of the Haskell 98 Prelude. Then they introduce >a subtype relationship using multiparameter type classes: > > class SubType sub sup where > inj :: sub -> sup -- injection > prj :: sup -> Maybe sub -- projection > >The Either data type consructor is then used to express >the desired subtype relationshipe: > > instance SubType a (Either a b) where > inj =3D Left > prj (Left x) =3D Just x > prj _ =3D Nothing > > instance SubType a b =3D> SubType a (Either c b) where > inj =3D Right . inj > prj (Right x) =3D prj x > prj _ =3D Nothing > >The authors implemented their system in Gofer, due to >restrictions in the type class system of Haskell. >But now that there are Haskell extensions to support >multiparametric type classes, that could be implemented >in Haskell. > >The above code fails to type check due to instances >overlapping. Hugs gives the following error message: > > ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType" > *** This instance : SubType a (Either b c) > *** Overlaps with : SubType a (Either a b) > *** Common instance : SubType a (Either a b) > >(I did not check Gofer, but is there a way to solve these >overlapping of instances in it?) > >So this is scheme is not going to work with Haskell (extended >with multiparameter type classes). > >I would like hear any comments from the Haskell comunity on >this subject. Is there a workaround for the overlapping instances? > >Regards. > >Romildo >-- >Prof. Jos=E9 Romildo Malaquias >Departamento de Computa=E7=E3o >Universidade Federal de Ouro Preto >Brasil > >_______________________________________________ >Haskell mailing list >Haskell@haskell.org >http://www.haskell.org/mailman/listinfo/haskell -- __________________________________________________________________________ S. Doaitse Swierstra, Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands Mail: mailto: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 legere@its.caltech.edu Fri Oct 20 16:21:12 2000 From: legere@its.caltech.edu (Ronald J. Legere) Date: Fri, 20 Oct 2000 08:21:12 -0700 (PDT) Subject: .net and haskell In-Reply-To: Message-ID: I was reading some .net stuff (ducks) on microsoft, and they mentioned haskell as one of the languages someone was targetting for it. Anyone know anything about this project? Cheers! +++++++++++++++++++++++++++++++++++++++++++++++++ Ron Legere -- http://www.its.caltech.edu/~legere Caltech Quantum Optics MC 12-33 Pasadena CA 91125 626-395-8343 FAX: 626-793-9506 +++++++++++++++++++++++++++++++++++++++++++++++++ From romildo@urano.iceb.ufop.br Sat Oct 21 09:48:40 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 21 Oct 2000 06:48:40 -0200 Subject: Passing an environment around In-Reply-To: ; from conal@MICROSOFT.com on Thu, Oct 19, 2000 at 09:08:16AM -0700 References: Message-ID: <20001021064840.A19051@urano.iceb.ufop.br> The following discussion is been conducted in the Clean mailing list. As the issue is pertinent also to Haskell, I have cross-posted this letter to the Haskell mailing list too. Romildo. On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote: > Indeed Fran behaviors are like your alternative #1 (function passing), and > hence sharing loss is a concern. Simon PJ is right that I have a paper > discussing this issue and some others. See "Functional Implementations of > Continuous Modeled Animation" on my pubs page > (http://research.microsoft.com/~conal/papers). > > About alternative #2 (implicit arguments), would it help? Does it eliminate > the non-memoized redundant function applications, or just hide them? For > Fran, Erik Meijer suggested implicit functions to me a couple of years ago. > I hadn't thought of it, and it did indeed seem to be attractive at first as > a way to eliminate the need for overloading in Fran. However, the (Time -> > a) representation of Fran behaviors is not really viable, so I wouldn't > merely want to hide that representation behind implicit arguments. It seems that implicit parameters does not eliminate redundant function applications, as Conal Elliott has commented. Reading the paper Implicit Parameters: Dynamic Scoping with Static Types Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury http://www.cse.ogi.edu/~jlewis/ (especially section 5.1) I got this impression. I would like to hear from others as well, as I had some difficulties with the paper. > I don't see how alternative #3 would work. > > Of the three approaches, I think #1 is probably the best way to go. > Functional programming encourages us to program with higher-order functions, > and doing so naturally leads to this loss-of-sharing problem. Memoization > is thus a useful tool. Adding it to Clean would probably help others as > well as you. > > > I recommend that you find out how real computer algebra systems address this > issue. I've used these systems some and have the impression that there is a > default set of simplification rules, plus some strategies for non-standard > "simplifications" like factoring. You could apply the default set in a > bottom-up way, with no need for memoization. This is precisely the approach > used for algebraic simplification in Pan (an Haskell-based image synthesis > library). See the recent paper "Compiling Embedded Languages" on my pubs > page. You can also get the Pan source release to check out the real > details. > > Good luck, and please let me know how it turns out. > > - Conal > > -----Original Message----- > From: Simon Peyton-Jones > Sent: Thursday, October 19, 2000 1:51 AM > To: José Romildo Malaquias; clean-list@cs.kun.nl > Cc: Conal Elliott (E-mail); Meurig Sage (E-mail) > Subject: RE: [clean-list] Passing an environment around > > It's interesting that *exactly* this issue came up when Conal > Eliott was implementing Fran in Haskell. His 'behaviours' > are very like your expressions. > type Behaviour a = Time -> a > and he found exactly the loss of sharing that you did. > > For some reason, though, I'd never thought of applying the > implicit-parameter > approach to Fran. (Perhaps because Implicit parameters came along after > Fran.) > But I think it's rather a good idea. > > I think Conal may have a paper describing the implementation choices > he explored; I'm copying him. > > Simon > > | -----Original Message----- > | From: José Romildo Malaquias [mailto:romildo@urano.iceb.ufop.br] > | Sent: 18 October 2000 08:12 > | To: clean-list@cs.kun.nl > | Subject: [clean-list] Passing an environment around > | > | > | Hello. > | > | I am implementing a Computer Algebra system (CALG) in Clean, > | and I have a > | problem I would like the opinion of Clean programmers. > | > | The CALG system should be able to simplify (or better, to transform) > | algebraic expressions (from Mathematics) involving integers, > | named constants > | (like "pi" and "e"), variables, arithmetic operations (addition, > | multiplication, exponentiation), and other forms of expressions > | (trigonometric, logarithmic, derivatives, integrals, > | equations, etc.). The > | tansformaations should follow the rules from Algebra and > | other areas of > | Mathematica. But we know that in general an algebraic > | expression can be > | transformed in different ways, depending on the goal of the > | transformation. Thus, the algebraic expression > | > | a^2 + b^2 + 3*a*b - a*b > | > | could result in > | > | a^2 + 2*a*b + b^2 > | > | or in > | > | (a + b)^2 > | > | To control the transformations made with an algebraic > | expression there is a > | set of flags collected in a record. I will call this record > | the environment > | in which the expression should be simplified. The algorithms I am > | implementing may change this environment temporarily for some local > | transformations. So the enviroment should be passed around in > | the function > | calls I am writing. This way the functions that implements the > | transformations will have an extra argument representing the > | environment in > | which the transformation is to be performed. > | > | Let's take an example: the algorithm for addition will have > | two arguments to > | be added and a third argument corresponding to the enviroment: > | > | add :: Expr Expr Env -> Expr > | > | and its result will depend of the flags in the environment. > | But it is highly > | desirable to define functions like add as BINARY INFIX > | OPERATORS. Having 3 > | arguments, add cannot be made a binary operator! > | > | -------------------------------------------------------------------- > | So I am looking for alternative ways to pass the environment around. > | -------------------------------------------------------------------- > | > | 1. Handle the arguments as functions themselves, which, given > | an enviroment, > | returns the simplified algebraic expression in that environment: > | > | add :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr) > | > | Now add can be made a binary infix operator. This solution has the > | disadvantage that we loose sharing when doing local > | simplifications. For > | example: > | > | f :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr) > | f fx fy = (add (add fx fy) fy) > | > | fe1, fe2 :: Env -> Exp > | fe1 e = ... > | fe2 e = ... > | > | initialEnv :: Env > | initialEnv = ... > | > | Start = f fe1 fe2 initialEnv > | > | In this program fragment, fe2 may be applied twice to the same > | environment value, computing its body twice. The resulting > | program would > | be too inneficient. If Clean had a mean of implementing MEMOIZATION > | FUNCTIONS, the computation of a memoized function > | application to the same > | argument would evalute the body of the function only the > | first time the > | function is applied. Subsequent applications of that > | function to the same > | argument would remember the result of the previous > | application and would > | reutilize it. Then this way of handling environment > | passing would be a > | good solution. > | > | For more on memo functions see > | . > | > | 2. Extend Clean to support IMPLICIT PARAMETER PASSING (that > | is, a form of > | dynamic scoping), as has been done in some Haskell > | implementations (Hugs, > | GHC). Than the environment could be passed implicitly and > | add could be > | considered to have only 2 arguments > | > | add :: (Env ?env) => Exp Exp -> Exp > | > | Here ?env represents an implicit parameter. It is not > | passed explicitly > | like the two argument parameters. It can be used normally > | in the function > | definition, like any normal parameter. To pass an argument > | implicitly, > | there is 2 additional forms of expression: dlet and with: > | > | dlet ?env = ... in add e1 e2 > | > | add e1 e2 with ?env = ... > | > | I think this could be the best solution to my problem, if Clean had > | such extension implemented. > | > | For more information, see > | > | > | 3. Join the algebraic expression and the environment in a single value > | > | add :: (Env,Exp) (Env,Exp) -> (Env,Exp) > | > | The enviroment is then carried around with each expression. > | But now add has two enviroments to consult. Which one should be > | used? > | > | Would be other good alternatives to solve this problem? > | > | Would future versions of Clean support > | > | - memoization functions, or > | - implciit parameter passing? > | > | I am open to discussion on this topics. > | > | Regards, > | > | Romildo > | -- > | Prof. José Romildo Malaquias > | Departamento de Computação > | Universidade Federal de Ouro Preto > | Brasil > | > | _______________________________________________ > | clean-list mailing list > | clean-list@cs.kun.nl > | http://www.cs.kun.nl/mailman/listinfo/clean-list > | > > _______________________________________________ > clean-list mailing list > clean-list@cs.kun.nl > http://www.cs.kun.nl/mailman/listinfo/clean-list -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From romildo@urano.iceb.ufop.br Mon Oct 23 13:22:35 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Mon, 23 Oct 2000 10:22:35 -0200 Subject: Overloaded function and implicit parameter passing Message-ID: <20001023102235.A11238@urano.iceb.ufop.br> Hi. While experimenting with the implicit parameter extension to Haskell 98, implemented in GHC 4.08.1 and latest Hugs, I came accross a difference among those implementations regarding overloading functions with implicit parameters. As a test consider the program ------------------------- cut here module Main where class C a where f :: (?env :: Integer) => a -> Integer instance C Integer where f x = ?env + x main = putStrLn (show (f (45::Integer) with ?env = 100)) ------------------------- cut here Hugs accepts this program and outputs 145, as expected. But GHC 4.08.1 refuses to compile it, emitting the message $ ghc -fglasgow-exts Test1.hs -o test1 Test1.hs:7: Unbound implicit parameter `env_rJX :: Integer' arising from use of `env_rJX' at Test1.hs:7 In the first argument of `+', namely `env_rJX' In the right-hand side of an equation for `f': env_rJX + x Compilation had errors Would anybody comment on what is going on with GHC? I am willing to use implicit parameters in the software I am developing, but I have the need to overload functions with implicit parameters. While Hugs is good for development, its performance may rule it out when the final product is ready. So I will need a good Haskell compiler to compile my system. Any comments? Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From fjh@cs.mu.oz.au Mon Oct 23 15:02:14 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Tue, 24 Oct 2000 01:02:14 +1100 Subject: Overloaded function and implicit parameter passing In-Reply-To: <20001023102235.A11238@urano.iceb.ufop.br> References: <20001023102235.A11238@urano.iceb.ufop.br> Message-ID: <20001024010214.A11699@hg.cs.mu.oz.au> On 23-Oct-2000, José Romildo Malaquias wrote: > ------------------------- cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > ------------------------- cut here ... > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 ... > Would anybody comment on what is going on with GHC? That sure looks to me like a bug in GHC's support for implicit parameter passing. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From ru@ohio.river.org Mon Oct 23 21:28:09 2000 From: ru@ohio.river.org (Richard) Date: Mon, 23 Oct 2000 13:28:09 -0700 (PDT) Subject: mapM/concatMapMy In-Reply-To: <200010190434.WAA20212@ia.nsc.com> References: <200010190409.WAA16637@ia.nsc.com> <200010190434.WAA20212@ia.nsc.com> Message-ID: <200010232028.NAA14294@ohio.river.org> Sengan Baring-Gould writes: >Is >>= not lazy? since no experts have answered yet, this newbie will answer. I think it's strict. somewhere in the compiler doco, IIRC, it says (>>=) was lazy at first, but experience showed it was more confusing for users (Haskell programmers). moreover, from the hslibs documentation, LazyST chapter: "The lazy ST monad tends to be more prone to space leaks than the strict version, so most programmers will use the former unless laziness is explicitly required." http://haskell.org/ghc/docs/latest/set/sec-lazyst.html From quintela@fi.udc.es Tue Oct 24 05:48:25 2000 From: quintela@fi.udc.es (Juan J. Quintela) Date: 24 Oct 2000 06:48:25 +0200 Subject: CFP: Eight International Conference on Computer Aided Systems Theory Message-ID: The following message is a courtesy copy of an article that has been posted to comp.lang.ml,comp.lang.functional as well. Dear Colleagues, I would be most grateful if you would distribute the appended Call For Papers to your colleagues (and/or any mailing lists you see appropriate). Any help in distributing the Call For Papers would be most appreciated. Kindest regards, Juan Quintela CALL FOR PAPERS --------------- Eight International Conference on Computer Aided Systems Theory Formal Methods and Tools for Computer Science See the webpage at: http://azuaje.ulpgc.es/congresos/eurocast2001/ The topics for the workshop are: Workshop "FP" Contributions addressing to the following and similar issues: 1.Concurrency. Distributed and web applications. 2.Verification:tools and methods. 3.Persistence. 4.Typing and theoretical foundations. You only have to send one extended abstract before the: 31 October. -- In theory, practice and theory are the same, but in practice they are different -- Larry McVoy From rjmh@cs.chalmers.se Tue Oct 24 09:16:54 2000 From: rjmh@cs.chalmers.se (John Hughes) Date: Tue, 24 Oct 2000 10:16:54 +0200 (MET DST) Subject: mapM/concatMapMy Message-ID: <200010240816.KAA17042@muppet30.cs.chalmers.se> Sengan Baring-Gould writes: >Is >>= not lazy? since no experts have answered yet, this newbie will answer. I think it's strict. Well, it depends. (>>=) is an overloaded operator, with a different implementation for every monad -- when you define a monad, you give the implementation of (>>=). If your implementation is strict (presumably in the first operand), then (>>=) is strict *at that type*. If your implementation is lazy, then it isn't. The same goes for (+): at most types (+) is strict, but if you define your own kind of number with a lazy addition, then on that type (+) will be lazy. For many monads, (>>=) *is* strict, which fits with the intuition that it is a `sequencing' operator. But by no means for all. The simplest counter-example is the identity monad: newtype Id a = Id a instance Monad Id where return = Id Id x >>= f = f x where m>>=f is strict in m only if f is a strict function. A more interesting example is the state transformer monad: newtype ST s a = ST (s -> (a,s)) instance Monad (ST s) where return x = ST (\s -> (x,s)) ST h >>= f = ST (\s -> let (a,s') = h s ST h' = f a in h' s') where once again, the implementation of (>>=) is strict only if f is a strict function. Hence `lazy state' makes sense! John Hughes From delapla@lami.univ-evry.fr Tue Oct 24 13:57:16 2000 From: delapla@lami.univ-evry.fr (Franck Delaplace) Date: Tue, 24 Oct 2000 14:57:16 +0200 Subject: LOOKING FOR B-TREES MODULE Message-ID: <39F5872C.8B54DC16@lami.univ-evry.fr> I am looking for an haskell module which implements balanced trees ? Can somebdody help me = Thank you = -- = Franck Delaplace @w3:http://taillefer.lami.univ-evry.fr:8090/~delapla/ La.M.I-U.M.R C.N.R.S Universit=E9 d'Evry Val d'Essonne = Cours Monseigneur Rom=E9ro = 91025 Evry CEDEX (France) From wohlstad@cs.ucdavis.edu Tue Oct 24 19:25:29 2000 From: wohlstad@cs.ucdavis.edu (Eric Allen Wohlstadter) Date: Tue, 24 Oct 2000 11:25:29 -0700 (PDT) Subject: Group theory In-Reply-To: <200010240816.KAA17042@muppet30.cs.chalmers.se> Message-ID: Are there any Haskell libraries or programs related to group theory? I am taking a class and it seems like Haskell would be a good programming language for exploring/reasoning about group theory. What I had in mind was perhaps you could have a function which takes a list(set) and a function with two arguments(binary operator) and checks to see whether or not it is a group. I think it might be a fun exercies to write myself but I'd like to see if it's already been done or what you guys think about it. Eric Wohlstadter UCDavis Software Engineering From dongen@cs.ucc.ie Tue Oct 24 19:29:58 2000 From: dongen@cs.ucc.ie (Marc van Dongen) Date: Tue, 24 Oct 2000 19:29:58 +0100 Subject: Group theory In-Reply-To: ; from wohlstad@cs.ucdavis.edu on Tue, Oct 24, 2000 at 11:25:29AM -0700 References: <200010240816.KAA17042@muppet30.cs.chalmers.se> Message-ID: <20001024192958.D25711@cs.ucc.ie> Eric Allen Wohlstadter (wohlstad@cs.ucdavis.edu) wrote: : Are there any Haskell libraries or programs related to group theory? I am : taking a class and it seems like Haskell would be a good programming : language for exploring/reasoning about group theory. What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) has facilities for that. Have a look at: http://www.cs.bell-labs.com/who/wadler/realworld/docon.html Regards, Marc van Dongen From mechvel@math.botik.ru Wed Oct 25 08:20:32 2000 From: mechvel@math.botik.ru (S.D.Mechveliani) Date: Wed, 25 Oct 2000 11:20:32 +0400 Subject: group theory. Reply Message-ID: Hi, all, To Eric Allen Wohlstadter's (wohlstad@cs.ucdavis.edu) : Are there any Haskell libraries or programs related to group theory? I am : taking a class and it seems like Haskell would be a good programming : language for exploring/reasoning about group theory. What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. Marc van Dongen writes > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) > has facilities for that. Have a look at: > > http://www.cs.bell-labs.com/who/wadler/realworld/docon.html Sorry, DoCon () really supports the Commutative Rings, but provides almost nothing for the Group theory. For example, for the domain (Integer,Integer) it would set automatically (IsGroup,Yes) for the Additive semigroup and (IsGroup,No) for the Multiplicative semigroup. For the additive case, it would also set the group generator list [(1,0),(0,1)]. In both cases, it would also set cardinality = Infinity. Similar attributes are formed for the constructors of Permutation, Vector, Matrix, Polyninomial, Fraction, ResidueRing. And that is all. It does not provide so far any real algorithmic support for the Group theory, except some operations on permutations. But one may develop the program by adding the needed algorithms and introducing new attributes. : What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. I never programmed this. It looks like some exercise in algorithms. There are also books on the combinatorial group theory, maybe, they say something about efficient procedures for this. Regards, ------------------ Sergey Mechveliani mechvel@botik.ru From karczma@info.unicaen.fr Wed Oct 25 10:58:04 2000 From: karczma@info.unicaen.fr (Jerzy Karczmarczuk) Date: Wed, 25 Oct 2000 10:58:04 +0100 Subject: group theory. Reply References: Message-ID: <39F6AEAC.F5C9C988@info.unicaen.fr> S.D.Mechveliani wrote: > > Hi, all, > > To Eric Allen Wohlstadter's > > : Are there any Haskell libraries or programs related to group theory? ... > Marc van Dongen writes > > > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) > > has facilities for that. ... > Sorry, > DoCon () > > really supports the Commutative Rings, > but provides almost nothing for the Group theory. > EAW again: > : ... I think it might be a fun exercies to write myself but > : I'd like to see if it's already been done or what you guys > : think about it. SM: > I never programmed this. It looks like some exercise in algorithms. > There are also books on the combinatorial group theory, maybe, they > say something about efficient procedures for this. == "Some exercise in algorithms". Hm. There is more to that than this... This issue has been recently stirred a bit in the comp.functional newsgroup, in a larger context, general Math, not necessarily the group theor. There are at least two people *interested* in it, although they didn't do much yet (for various reasons...) Suggestion: Take GAP! ( http://www-history.mcs.st-and.ac.uk/~gap/ ) Plenty of simply coded algorithms, specifically in this domain. I coded just for fun a few simple things in Haskell some time ago, and it was a real pleasure. The code is cleaner and simpler. Its presentation is also much cleaner than the original algorithms written in GAP language. But I discarded all this stuff, thinking that I would have never time enough to get back to it... This is a nice project, and I would participate with pleasure in it, although the time factor is still there... Dima Pasechnik (; does he read it?) - apparently - as well. Jerzy Karczmarczuk Caen, France From senganb@ia.nsc.com Wed Oct 25 17:21:42 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 25 Oct 2000 10:21:42 -0600 (MDT) Subject: Haskell Programming Environment In-Reply-To: <20001025084900Z474423-538+2802@webmail1.ahoj.pl> from "=?ISO-8859-2?Q? Pawe=B3?= Kot" at Oct 25, 2000 10:48:57 AM Message-ID: <200010251621.KAA02114@ia.nsc.com> > Hello, > > I'm writing my master thesis. Its subject is 'Haskell Programming > Environment'. It is (or rather will be) an extended text editor working i= > n > graphical (XFree86) environment designed for Haskell programmers. It will= > be > implemented using Fudgets library. > I'm wondering what features would you like to find in such environment. W= > hat > should be neccessary, what would help, what would make writing programs > easier, etc. > I have some concepts, but I would like to hear some suggestions from you. > > Thanks for all answers. a) the ablility to highlight an area of code and get its type (be it a function, or some well-formed chunk of code b) the ability to highlight a function and get its definition in another area (think multiple text editing in vim) c) interaction with hugs/stg-hugs so that just written code can be pasted into a "hugs window" for evaluation. d) Debug mode which automatically adds "deriving show" to all datatypes which are not showable/adds exporting of all Datatypes as non-abstract for use in hugs to just allow things to be tried out. e) Debug mode which invisibly replaces functions such as "fromJust" with error making versions (... fromJust' "the file and line at which I'm invoked" ...) to make it easier to find the cause of the error (fromJust Nothing just comes up with an error telling you that it's fromJust that failed. Last time that happened, I hacked hugs to dump the evaluation stack, from which I guessed which possible fromJusts it could have been). f) Use ghc's .hi file to allow strictness of arguments to appear if you leave the mouse over an argument. g) For bonus points (harder, but really useful when stuck): given an expression, show me (possibly using daVinci) how it gets evaluated: Lazyness behaviour is not always obvious, I'd like to see it. I've been wanting to code one of these myself, but have had no time. Try and see if stg-hugs is useable yet since that would be a much better environment to do it in. Sengan From Keith.Wansbrough@cl.cam.ac.uk Wed Oct 25 17:26:51 2000 From: Keith.Wansbrough@cl.cam.ac.uk (Keith Wansbrough) Date: Wed, 25 Oct 2000 17:26:51 +0100 Subject: Haskell Programming Environment In-Reply-To: Your message of "Wed, 25 Oct 2000 10:21:42 MDT." <200010251621.KAA02114@ia.nsc.com> Message-ID: > I've been wanting to code one of these myself, but have had no time. Try and see > if stg-hugs is useable yet since that would be a much better environment to do > it in. It's now called GHCi, and is being written right now by the GHC team. Not sure when the estimated completion time is, but it can't be that far off. --KW 8-) From ger@Informatik.Uni-Bremen.DE Wed Oct 25 21:08:55 2000 From: ger@Informatik.Uni-Bremen.DE (George Russell) Date: Wed, 25 Oct 2000 22:08:55 +0200 Subject: cpp superior to ghc . . . Message-ID: <39F73DD7.E744A061@informatik.uni-bremen.de> Why does the Haskell language not allow "type" declarations to appear in the declaration parts of where and let clauses? I've just been writing a huge functions which requires lots and lots of repetitive internal type annotations (to disambiguate some complicated overloading) but I can't abbreviate them with "type" because they depend on things only in scope inside the function. In the end I abbreviated them with a few #define's but I don't really think it should be that way . . . From qrczak@knm.org.pl Thu Oct 26 06:09:48 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 26 Oct 2000 05:09:48 GMT Subject: cpp superior to ghc . . . References: <39F73DD7.E744A061@informatik.uni-bremen.de> Message-ID: Wed, 25 Oct 2000 22:08:55 +0200, George Russell pisze: > Why does the Haskell language not allow "type" declarations to > appear in the declaration parts of where and let clauses? Because you can always lift them to the top level. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK From koen@cs.chalmers.se Thu Oct 26 08:01:21 2000 From: koen@cs.chalmers.se (Koen Claessen) Date: Thu, 26 Oct 2000 09:01:21 +0200 (MET DST) Subject: cpp superior to ghc . . . In-Reply-To: Message-ID: George Russell complained: | Why does the Haskell language not allow "type" | declarations to appear in the declaration parts of | where and let clauses? Marcin 'Qrczak' Kowalczyk replied: | Because you can always lift them to the top level. This is the ultimate non-answer. First of all, it is wrong. George meant to be able to use type variables present in the top-level type in the local type declarations. Something like: doWithStack :: a -> a doWithStack x = stacking [] where type Stack = [a] stacking :: Stack -> a stacking = ... The problem is really two-fold: bound type variables (like "a") are not in scope in the body of the function, and local type declarations are not allowed. Secondly, "because another way of doing it is possible" is not an answer. We allow local declarations of functions, but we have known for ages we can all lambda-lift them to top-level... Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden From mk167280@students.mimuw.edu.pl Thu Oct 26 08:29:49 2000 From: mk167280@students.mimuw.edu.pl (Marcin 'Qrczak' Kowalczyk) Date: Thu, 26 Oct 2000 09:29:49 +0200 (CEST) Subject: cpp superior to ghc . . . In-Reply-To: Message-ID: On Thu, 26 Oct 2000, Koen Claessen wrote: > The problem is really two-fold: bound type variables (like > "a") are not in scope in the body of the function, and local > type declarations are not allowed. GHC and Hugs do solve the first problem by providing a language extension: names of type variables in pattern type signatures and result type signatures are available in their scope. I wish this extension becomes a future standard. Some people say that type variables from ordinary type signatures should be in scope too. -- Marcin 'Qrczak' Kowalczyk From simonpj@microsoft.com Thu Oct 26 18:27:51 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Thu, 26 Oct 2000 10:27:51 -0700 Subject: .net and haskell Message-ID: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmond.corp.microsoft.com> | I was reading some .net stuff (ducks) on microsoft, and they | mentioned haskell as one of the languages someone was | targetting for it. | Anyone know anything about this project? I know of several stabs in this direction, none completed. - There is most of a Java back end for GHC - There are various pieces of a C# back end for GHC, compiling via in intermediate generic OO language called GOO. Nigel Perry is working on this (actively I think) - Don Syme and Reuben Thomas are working on a back end for GHC that compiles to a polymorphically-typed IL for .NET that is Don's baby. A lot of this works, but it's not complete. Maybe others are doing stuff too? It's a pity that there's nothing that's usable yet, but I hope that'll change. Simon From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 11:16:19 2000 From: mhoechsm@techfak.uni-bielefeld.de (=?iso-8859-1?Q?Matthias_H=F6chsmann?=) Date: Fri, 27 Oct 2000 12:16:19 +0200 Subject: class instance with nested types Message-ID: <001801c03ffe$f321de20$0701a8c0@mulder> This is a multi-part message in MIME format. --Boundary_(ID_5jIOsd3oqicabXDXApeVOg) Content-type: text/plain; charset=iso-8859-1 Content-transfer-encoding: 7BIT Hello, I have the following problem: basic datatypes > type Sequence a = [a] > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > type Forest a = Sequence (Tree a) i want to construct a class Xy > class Xy s a where > test :: s a -> a and make an instance for list of characters > instance Xy [] Char where > test [a] = a this works, and an instance for a forest and tried something like this > instance ([] Tree) Char where > test x@(N a xs):txs = a I get illegal type errors. Is it possible to use nested types in a class ? Hope you can help me Matthias --Boundary_(ID_5jIOsd3oqicabXDXApeVOg) Content-type: text/html; charset=iso-8859-1 Content-transfer-encoding: 7BIT
Hello,
 
I have the following problem:
 
basic datatypes
 
> type Sequence a = [a]
> data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> type Forest a = Sequence (Tree a)
 
i want to construct a class Xy
 
> class Xy s a where
>      test :: s a -> a
 
and make an instance for list of characters
 
> instance Xy [] Char where
>      test [a] = a
 
this works, and an instance for a forest and tried something like this
 
> instance  ([] Tree) Char where
> test x@(N a xs):txs = a
 
I get illegal type errors. Is it possible to use nested types in a class ?
 
Hope you can help me
Matthias
 
--Boundary_(ID_5jIOsd3oqicabXDXApeVOg)-- From d95lars@dtek.chalmers.se Fri Oct 27 11:14:58 2000 From: d95lars@dtek.chalmers.se (Lars Lundgren) Date: Fri, 27 Oct 2000 12:14:58 +0200 (MEST) Subject: class instance with nested types In-Reply-To: <001801c03ffe$f321de20$0701a8c0@mulder> Message-ID: On Fri, 27 Oct 2000, Matthias Höchsmann wrote: > Hello, > > I have the following problem: > > basic datatypes > > > type Sequence a = [a] > > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > > type Forest a = Sequence (Tree a) > > i want to construct a class Xy > > > class Xy s a where > > test :: s a -> a > > and make an instance for list of characters > > > instance Xy [] Char where > > test [a] = a > > this works, and an instance for a forest and tried something like this > > > instance ([] Tree) Char where > > test x@(N a xs):txs = a > Don't you mean test (N a xs:txs) = a ? /Lars L From N.Perry@massey.ac.nz Fri Oct 27 11:59:13 2000 From: N.Perry@massey.ac.nz (Nigel Perry) Date: Fri, 27 Oct 2000 12:59:13 +0200 Subject: .net and haskell In-Reply-To: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmon d.corp.microsoft.com> References: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmon d.corp.microsoft.com> Message-ID: At 10:27 am -0700 26/10/00, Simon Peyton-Jones wrote: >| I was reading some .net stuff (ducks) on microsoft, and they >| mentioned haskell as one of the languages someone was >| targetting for it. >| Anyone know anything about this project? > >I know of several stabs in this direction, none completed. > >- There is most of a Java back end for GHC > >- There are various pieces of a C# back end for GHC, > compiling via in intermediate generic OO language > called GOO. Nigel Perry is working on this (actively > I think) This is indeed being worked on. Currently user code compiles (as far as it has been tested) but there is no prelude yet so it doesn't run too well ;-) The code generator was designed for research and supporting scripting, which is a kind way of saying it doesn't produce blazingly fast code. > >- Don Syme and Reuben Thomas are working on a back end for > GHC that compiles to a polymorphically-typed IL for .NET > that is Don's baby. A lot of this works, but it's not complete. > >Maybe others are doing stuff too? It's a pity that there's nothing >that's usable yet, but I hope that'll change. Cheers, Nigel From rossberg@ps.uni-sb.de Fri Oct 27 13:07:37 2000 From: rossberg@ps.uni-sb.de (Andreas Rossberg) Date: Fri, 27 Oct 2000 14:07:37 +0200 Subject: class instance with nested types References: <001801c03ffe$f321de20$0701a8c0@mulder> Message-ID: <39F97009.9C9BB220@ps.uni-sb.de> Matthias Höchsmann wrote: > > > type Sequence a = [a] > > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > > type Forest a = Sequence (Tree a) > > i want to construct a class Xy > > > class Xy s a where > > test :: s a -> a > > [...] > > > instance ([] Tree) Char where > > test x@(N a xs):txs = a To make it syntactically correct this should at least be something like > instance Xy ([] Tree) Char where > test (N a xs:txs) = a But the real problem is in the expression ([] Tree), which is the same as writing [Tree]. This is not a legal type expression, since Tree is a type constructor, not a ground type, so you cannot apply it to the list constructor. What you are trying to say is probably something like this: > instance Xy (\a . [Tree a]) Char -- not Haskell But unfortunately there are no lambdas on the type level - they would render the type system undecidable. For the same reason it is not allowed to use a type synonym in an instance declaration: > instance Xy Forest Char -- illegal The only thing you can do is turning Forest into a data type: > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > data Forest a = Forest [Tree a] > instance Xy Forest Char where > test (Forest (N a xs:txs)) = a HTH, - Andreas -- Andreas Rossberg, rossberg@ps.uni-sb.de :: be declarative. be functional. just be. :: From rossberg@ps.uni-sb.de Fri Oct 27 13:12:45 2000 From: rossberg@ps.uni-sb.de (Andreas Rossberg) Date: Fri, 27 Oct 2000 14:12:45 +0200 Subject: class instance with nested types References: <001801c03ffe$f321de20$0701a8c0@mulder> <39F97009.9C9BB220@ps.uni-sb.de> Message-ID: <39F9713D.C0581888@ps.uni-sb.de> I mumbled: > > This is not a legal type expression, since Tree is a > type constructor, not a ground type, so you cannot apply it to the list > constructor. The other way round, of course: you cannot apply the list constructor to it. - Andreas -- Andreas Rossberg, rossberg@ps.uni-sb.de :: be declarative. be functional. just be. :: From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 14:25:00 2000 From: mhoechsm@techfak.uni-bielefeld.de (=?iso-8859-1?Q?Matthias_H=F6chsmann?=) Date: Fri, 27 Oct 2000 15:25:00 +0200 Subject: class instance with nested types References: Message-ID: <006201c04019$69f81540$0701a8c0@mulder> Yes, I wanted to type it like you do. But anyway, i fixed the problem following Andreas Rossbergs suggestion. Matthias > > Don't you mean > > test (N a xs:txs) = a > > ? > > /Lars L > > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell From jeff@galconn.com Fri Oct 27 16:10:29 2000 From: jeff@galconn.com (Jeffrey R. Lewis) Date: Fri, 27 Oct 2000 08:10:29 -0700 Subject: Overloaded function and implicit parameter passing References: <20001023102235.A11238@urano.iceb.ufop.br> Message-ID: <39F99AE5.8A60CAF5@galconn.com> José Romildo Malaquias wrote: > Hi. > > While experimenting with the implicit parameter > extension to Haskell 98, implemented in GHC 4.08.1 > and latest Hugs, I came accross a difference among > those implementations regarding overloading functions > with implicit parameters. > > As a test consider the program > > ------------------------- cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > ------------------------- cut here > > Hugs accepts this program and outputs 145, as expected. > But GHC 4.08.1 refuses to compile it, emitting the > message > > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 > In the first argument of `+', namely `env_rJX' > In the right-hand side of an equation for `f': env_rJX + x > > Compilation had errors > > Would anybody comment on what is going on with GHC? > > I am willing to use implicit parameters in the > software I am developing, but I have the need > to overload functions with implicit parameters. > While Hugs is good for development, its performance > may rule it out when the final product is ready. > So I will need a good Haskell compiler to compile > my system. > > Any comments? Certainly a bug. I'll look at it when I get a chance. --Jeff From romildo@urano.iceb.ufop.br Fri Oct 27 17:41:19 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Fri, 27 Oct 2000 14:41:19 -0200 Subject: Passing an environment around In-Reply-To: <39F9A83C.311C016A@galconn.com>; from jeff@galconn.com on Fri, Oct 27, 2000 at 09:07:24AM -0700 References: <20001021064840.A19051@urano.iceb.ufop.br> <39F9A83C.311C016A@galconn.com> Message-ID: <20001027144119.A20783@urano.iceb.ufop.br> On Fri, Oct 27, 2000 at 09:07:24AM -0700, Jeffrey R. Lewis wrote: > José Romildo Malaquias wrote: > > > On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote: > > > Indeed Fran behaviors are like your alternative #1 (function passing), and > > > hence sharing loss is a concern. Simon PJ is right that I have a paper > > > discussing this issue and some others. See "Functional Implementations of > > > Continuous Modeled Animation" on my pubs page > > > (http://research.microsoft.com/~conal/papers). > > > > > > About alternative #2 (implicit arguments), would it help? Does it eliminate > > > the non-memoized redundant function applications, or just hide them? For > > > Fran, Erik Meijer suggested implicit functions to me a couple of years ago. > > > I hadn't thought of it, and it did indeed seem to be attractive at first as > > > a way to eliminate the need for overloading in Fran. However, the (Time -> > > > a) representation of Fran behaviors is not really viable, so I wouldn't > > > merely want to hide that representation behind implicit arguments. > > > > It seems that implicit parameters does not eliminate redundant function > > applications, as Conal Elliott has commented. Reading the paper > > > > Implicit Parameters: Dynamic Scoping with Static Types > > Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury > > http://www.cse.ogi.edu/~jlewis/ > > > > (especially section 5.1) I got this impression. I would like to hear > > from others as well, as I had some difficulties with the paper. > > I am sorry you had difficulties! The difficulties I had is basicaly due to my lack of solid knowledge on type theory and semantic formalisms. Not that the paper was badly written. > Yes, as implemented using the dictionary > translation, implicit parameterization can lead to loss of sharing, exactly in > the same way that overloading (and HOF in general) can lead to loss of sharing. > > However, I can imagine that a compiler might chose to implement implicit > parameters more like dynamic variables in lisp. Each implicit param essentially > becomes a global variable, implemented as a stack of values - the top of the > stack is the value currently in scope. This would avoid the sharing problem > nicely. > > --Jeff I suppose your implementation of implicit parameterization in GHC and Hugs uses the dictionary translation, right? Would an alternative implementation based on a stack of values be viable and even done? Does it have serious drawbacks when compared with the dictionary translation technique? Thanks. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From dublins@home.com Sun Oct 29 18:55:51 2000 From: dublins@home.com (S Dublin) Date: Sun, 29 Oct 2000 10:55:51 -0800 Subject: Message-ID: <20001029185558.PTNY2380.femail1.sdc1.sfba.home.com@[65.3.159.89]> From lmagnani@cc.gatech.edu Sun Oct 29 16:08:27 2000 From: lmagnani@cc.gatech.edu (Lorenzo Magnani) Date: Sun, 29 Oct 2000 10:08:27 -0600 Subject: MBR'01 Conference Message-ID: <39FC4B7B.6BF0445A@cc.gatech.edu> Please accept our apologies if you receive multiple copies of this call If you want to receive updated information please send your complete address Last updated October 29, 2000 ********************************************************************** MODEL-BASED REASONING: SCIENTIFIC DISCOVERY, TECHNOLOGICAL INNOVATION, VALUES (MBR'01), Pavia, Italy, May 17-19, 2001. ********************************************************************** Up-to date information on the conference will be found at http://philos.unipv.it/courses/progra1.html or http://www.unipv.it/webphilos_lab/courses/progra1.html ********************************************************************** GENERAL INFORMATION From Thursday 17 to Saturday 19 May 2001 (three days) the International Conference "MODEL-BASED REASONING. SCIENTIFIC DISCOVERY, TECNOLOGICAL INNOVATION, VALUES" will be held at the University of Pavia (near Milan, Italy). PROGRAM The conference will deal with the logical, epistemological, and cognitive aspects of modeling practices employed in scientific discovery and technological innovation, including computational models of such practices. Abduction is widely recognized as a significant reasoning process in discovery whose features are in need of explication. We will solicit papers that examine various forms of model-based reasoning, such as analogical and visual modeling, from philosophical, historical, sociological, psychological, or computational perspectives. We also plan to address the problem of model-based reasoning in ethics reasoning, especially pertaining to science and technology. RELEVANT RESEARCH AREAS We shall call for papers that cover topics from the following list: - abduction - analogical reasoning - causal and counterfactual reasoning in model construction - computational models of model-based reasoning and scientific reasoning - conceptual combination and theory formation - hypothetical and explanatory reasoning - logical analyses that may contribute to our understanding of the issues in model-based reasoning - model-based reasoning in ethics - models and manipulative reasoning - models and technological innovation - thought experimenting - visual, spatial, imagistic modeling, reasoning, and simulation SUBMISSIONS OF PAPERS All submitted papers will be carefully refereed. The precise format of the conference will be fixed after we have an idea of the number of accepted papers. We are thinking in terms of presentations of 40 and 20 minutes. The funding is Italian and US, but we are also looking elsewhere for further financing (and would appreciate any suggestions). A selected subset will be invited for inclusion (subject to refereeing) in a book which will constitute an advanced handbook for scientists and researchers. The book will be published by an international publishing house. Moreover another selected subset will be invited for inclusion (subject to refereeing) in special issues of suitable international Journals. FORMAT Authors must submit three printed copies and an electronic version - formatted in Microsoft Word, RTF, PDF, or Postcript format - of an extended abstract (about 1000 words) not later than November 30, 2000. Please send electronically the extended abstract to the program chair at the address lmagnani@cc.gatech.edu in case of problem with the above address please use lorenzo@philos.unipv.it or lmagnaniusa@netscape.net REGISTRATION AND FURTHER INFORMATION Registration Fees: Before 15 March 2001: Normal: ITL. 300.000 = appr. US$ 155 (EUR 154.93) (to participate in all the activities of the Conference) Students: Free After 15 March 2001: Normal: ITL. 350.000 = appr. US$ 175 (EUR 180.75) (to participate in all the activities of the Conference) Students: Free METHOD OF PAYMENT AND REGISTRATION DEADLINE: Bank (Swift) Transfer to BANCA REGIONALE EUROPEA S.p.A BRANCH PAVIA - Sede SWIFT BREUITM2 301 Bank Code 06906.11301 Acc. n. 520 Dipartimento di Filosofia indicating CONVEGNO INTERNAZIONALE MBR'01 PLEASE REGISTER by email, fax or air mail (before March 15, 2001) by sending PROGRAM CHAIR first and last name, function, institution, full address, phone, fax and email. For information about paper submission and the program that is not available on the web site, please contact the program chair. IMPORTANT DATES Registration deadline............................15 March 2001 Submission deadline..............................30 Nov 2000 Notification of acceptance.....................28 Feb 2001 Final papers (from those selected for publication) due........30 June 2001 Conference....................................17-19 May 2001 PROGRAM CHAIR Lorenzo MAGNANI School of Public Policy and College of Computing Program in Philosophy, Science, & Technology Georgia Institute of Technology, 685 Cherry Street Atlanta, GA, 30332 - 0345, USA Office: 404-894-0950 & 404-385-0884, Home: 404-875-3566 Fax: 404-385-0504 & 404-894-2970 Email: lorenzo.magnani@cc.gatech.edu Address in Italy: Department of Philosophy and Computational Philosophy Laboratory University of Pavia, Piazza Botta 6, 27100 Pavia, Italy Office: +39-0382-506283, Home: +39-0383-371067 Fax: +39-0382-23215 Email: lorenzo@philos.unipv.it PROGRAM CO-CHAIR Nancy J. NERSESSIAN (Program Co-Chair) Program in Cognitive Science School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, USA Email: nancyn@cc.gatech.edu PROGRAM CO-CHAIR Kenneth J. KNOESPEL (Program Co-Chair) School of History, Technology, and Society, and Program in Cognitive Science Georgia Institute of Technology, Atlanta, USA Email: kenneth.knoespel@hts.gatech.edu PROGRAM COMMITTEE - Ann Bostrom, School of Public Policy, Georgia Institute of Technology, Atlanta, GA, USA - Elena Gagliasso, Department of Philosophical and Epistemological Studies, University of Rome La Sapienza, Rome, ITALY - Dedre Gentner, Psychology Department, Northwestern University, Evanston, IL 60208, USA - Ronald N. Giere, Department of Philosophy, University of Minnesota, MN, USA - Mark L. Johnson, Department of Philosophy, 1295 University of Oregon, Eugene, OR, USA - Kenneth Knoespel, School of History, Technology, and Society, Georgia Institute of Technology, Atlanta, GA, USA - Lorenzo Magnani, Department of Philosophy, University of Pavia, Pavia, ITALY and School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, GA, USA - Pat Langley, Adaptive Systems Group, DaimlerChrysler Research & Technology Center, Palo Alto, CA, USA - Nancy J. Nersessian, School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, GA, USA - Brian Norton, School of Public Policy, Georgia Institute of Technology, Atlanta, GA, USA - Claudio Pizzi, Department of Philosophy and Social Sciences, University of Siena, Siena, ITALY - Mario Stefanelli, Department of Computer Science, University of Pavia, Pavia, ITALY - Paul Thagard, Department of Philosophy, University of Waterloo, Waterloo, CANADA - Ryan D. Tweney, Bowling Green State University, Bowling Green, OH, USA - Stella Vosniadou, Department of Philosophy and History of Science, Brain and Cognitive Science Division, National and Capodistrian University of Athens, Athens, GREECE. LOCAL ORGANIZING COMMITTEE Riccardo Dossena (riki.dox@libero), Elena Gandini (elegand@yahoo.com), Rosella Gennari (gennari@hum.uva.nl), Lorenzo Magnani (lmagnani@cc.gatech.edu), Massimo Manganaro (triskel@worldonline.it), Stefania Pernice (stepernice@libero.it), Matteo Piazza (pimat@yahoo.com), Giulio Poletti (philosophia@libero.it) Stefano Rini (s.rini@philos.unipv.it), Andrea Venturi (aventuri@philos.unipv.,it) (Department of Philosophy, University of Pavia, Pavia, Italy), Mario Stefanelli (mstefa@ipvstefa.unipv.it) (Department of Computer Science, University of Pavia, Pavia, Italy). IMPORTANT ADDRESSES LORENZO MAGNANI (Conference Chair) School of Public Policy and College of Computing Program in Philosophy, Science, & Technology Georgia Institute of Technology, 685 Cherry Street Atlanta, GA, 30332 - 0345, USA Office: 404-894-9050 & 404-385-0884, Home: 404-875-3566 Fax: 404-385-0504 & 404-894-2970 Email: lorenzo.magnani@cc.gatech.edu Address in Italy: Department of Philosophy and Computational Philosophy Laboratory University of Pavia, Piazza Botta 6, 27100 Pavia, Italy Office: +39-0382-506283, Home: +39-0383-371067 Fax: +39-0382-23215 Email: lorenzo@philos.unipv.it CONFERENCE SITE: Collegio Ghislieri, Piazza Ghislieri, 27100 PAVIA, Italy, phone +39 0382 22044. The Conference is sponsored by UNIVERSITY OF PAVIA, ITALY GEORGIA INSTITUTE OF TECHNOLOGY, ATLANTA, GA, USA UNIVERSITY OF SIENA, ITALY UNIVERSITY OF ROME "LA SAPIENZA", ITALY, MURST (Ministero dell'Università e della Ricerca Scientifica e Tecnologica), ITALY, CARIPLO (CASSA DI RISPARMIO DELLE PROVINCIE LOMBARDE, MILAN, ITALY) HOW TO REACH PAVIA LINATE Airport: People arriving by plane at LINATE should take the bus to the CENTRAL STATION of Milan (cf below fron this Station to Pavia). In LINATE it could be convenient to take a Taxi because the airport is close to the center of Milan. Moreover, The bus company SGEA offers six runs from LINATE to Pavia at 9.00, 10.00, 12.00 AM and 2.00, 5.00, 8.30 PM. The last stop is Pavia, near the station (see again our updated web page for possible alterations of this time-table) (from Pavia to LINATE six runs at 5,00, 7.45, 10.00 AM, 1.00, 4.00, 6.00 PM) (one hour trip). In Pavia there is only one station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. MALPENSA 2000 and OLD MALPENSA Airports (usually people arrive to Malpensa 2000 and not to OLD MALPENSA): People arriving by plane at MALPENSA 2000 (also called MALPENSA 2000 Terminal 1) or at "old" MALPENSA (now called MALPENSA NORTH but also called Malpensa 2000 Terminal 2) should take the bus to the CENTRAL STATION of Milan. There is also a bus AND A TRAIN from Malpensa 2000 to the NORTH STATION (Piazzale Cadorna) of Milan, in this case from NORTH Station you will have to take the underground MM1 to the Central Station: trains to Pavia leave from Central station). Moreover, the bus company SGEA offers four runs from MALPENSA 2000 to Pavia at 9.00 AM, 1:30 PM, 5.00 PM, and 9:30 PM - from Malpensa North (OLD Malpensa or Malpensa 2000 Terminal 2 5 munutes later) (from Pavia to MALPENSA 2000 and to OLD MALPENSA four runs at 7.00 AM, 11:00 AM, 3.15 PM, and 7:00 PM) (one hour and half trip). The last stop is Pavia, near the station (see again our updated web page for possible alterations of this time-table) In Pavia there is only one station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. There are trains from MILAN (Central Station) to PAVIA and vice Versa about every an hour (routes: MILAN-GENOVA; MILAN-VENTIMIGLIA; MILAN-LA SPEZIA; MILAN-SAVONA; MILAN-SESTRI LEVANTE; MILAN-IMPERIA; MILAN-ALBENGA; Pavia is the first stop only if the train is not slow, that is, if it is not, in ITALIAN, "L", locale). In Pavia there is only one rail station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. ACCOMMODATION The WEB site of the Tourist Office is http://www.systemy.it/pavia/home.html (new! sorry, only in Italian). The email address is info@apt.pv.it. When available you will find the whole list of hotels and other information concerning Pavia and its history. See also http://www.itwg.com/ct_00036.asp. In case of accommodation problems remember we will have at our disposal some rooms at special "conference rates" in the Colleges of the University. For further information please contact the Program Chair. As the the conferences dates are very close to summer holidays we recommend making your reservations as early as possible and before March 31, 2000 at the latest. ALL ACCOMMODATIONS (EXCEPT FOR INVITED SPEAKERS) WILL BE PROCESSED BY: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy Phone: +39-0382-539565 Fax: +39-0382-539572 +39-0382-539504 email (only to request information): aloha@buonviaggio.it (cut here) ********************************************************************** ACCOMMODATION FORM - MBR'01 ---------------------------------------------------------------------- TO BE FAXED: +39-0382-539572 +39-0382-539504 OR MAILED: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy email (only to request information): aloha@buonviaggio.it ---------------------------------------------------------------------- FILL IN CAPITAL LETTERS, PLEASE LAST NAME:___________________FIRST NAME:_____________Prof./Dr./Mr./Ms. AFFILIATION/UNIVERSITY/DEPT.__________________________________________ STREET:_______________________________________________________________ TOWN:___________________________CODE:_____________COUNTRY:____________ PHONE:__________________FAX:__________________E-MAIL:_________________ TYPE OF TRAVELLING:__________________DATE OF ARRIVAL:_________________ DATE OF DEPARTURE:___________________NUMBER OF NIGHTS:________________ CREDIT CARD NUMBER AND TYPE__________________________ EXPIRATION_____________ (you can also pay by bank transfer and postal order, please see below) ACCOMMODATION INCL. BREAKFAST SINGLE ROOM+BATH. / DOUBLE ROOM+BATH. ***HOTEL EXCELSIOR, Piazza Stazione, PAVIA LIT. 100.000 / LIT. 150.000 ______________ (EUR. 51.64 / EUR. 77.46) ****HOTEL ARISTON, Via Scopoli, PAVIA LIT. 130.000 / LIT. 190.000 +_____________ (EUR. 67.13 / EUR. 98.12) ****HOTEL MODERNO, Viale V. Emanuele, PAVIA LIT. 170.000 / LIT. 230.000 +_____________ (EUR. 87.79 / EUR. 118.78) RESERVATION CHARGE LIT. 25.000 +_______ (EUR. 12.91) TOTAL AMOUNT: =_____________ ACCOMMODATION DEPOSIT: ONE NIGHT LIT......... - _____________ (EUR) ACCOMMODATION BALANCE: LIT......... =_____________ (EUR)........ Hotel Excelsior (from the station walk east) Hotel Moderno (from the station walk north) To reach Hotel Ariston take the bus n. 3 or taxi. ____________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *CREDIT CARD* BEFORE *15 MARCH 2001* TO: FAX: +39-0382-539572 +39-0382-539504 MAIL ADDRESS: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy email (only to request information): aloha@buonviaggio.it DATE OF PAYMENT____________YOUR SIGNATURE____________________ ________________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *BANK TRANSFER* BEFORE *15 MARCH 2001* (fax or mail also a copy of the bank transfer) TO: BANCA REGIONALE EUROPEA S.p.A.BRANCH PAVIA - SedeSWIFT BREUITM2 301Bank Code 6906.11301 Agenzia Viaggi ALOHATOUR S.r.l. Acc.n 19952/4 DATE OF PAYMENT____________YOUR SIGNATURE___________________ ________________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *POSTAL ORDER* BEFORE* 15 MARCH 2001* (fax or mail also a copy of the postal receipt) TO: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy DATE OF PAYMENT______________________YOUR SIGNATURE______________________ _________________________________________________________________________ ALHOATOUR WILL MAIL OR FAX YOU THE RESERVATION VOUCHER ALOHATOUR WILL SATISFY THE REQUESTS AS FAR AS POSSIBLE. IF NOT POSSIBLE, ANOTHER SIMILAR ACCOMMODATION WILL BE ARRANGED. From venneri@dsi.unifi.it Mon Oct 9 19:19:30 2000 From: venneri@dsi.unifi.it (b.venneri) Date: Mon, 9 Oct 2000 14:19:30 -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. Affiliated workshops will be scheduled from September 2 through September 8. Researchers and practitioners are invited to submit workshop proposals, that may be sent to the PLI 2001 Workshop Chair Betti Venneri, venneri@dsi.unifi.it, by e-mail (Postscript, Pdf, ASCII) 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), 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. 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. web page: http://music.dsi.unifi.it/pli01/wkshops From fldrsimonmar@microsoft.com Mon Oct 9 10:54:52 2000 From: fldrsimonmar@microsoft.com (Simon Marlow) Date: Mon, 9 Oct 2000 02:54:52 -0700 Subject: Mailing list software changing Message-ID: <9584A4A864BD8548932F2F88EB30D1C6115734@TVP-MSG-01.europe.corp.microsoft.com> Dear Haskell & Haskell-cafe, At haskell.org we're migrating the mailing lists from majordomo (which is somewhat old and clunky) to Mailman, which will amongst other things make my life a lot easier, provide better archives, add digest support and allow subscription/unsubscription via a web interface. You should all receive a notification shortly about subscription to the new lists. Unfortunately it seems we have to do this, because the confirmation contains the password for accessing & modifying your personal subscription details on the web. If you *don't* receive a confirmation in the next 24 hours, please let me know. Heres hoping everything goes smoothly, and once again I apologise for the extra spam in your mailbox. Cheers, Simon From mpj@cse.ogi.edu Tue Oct 10 03:26:00 2000 From: mpj@cse.ogi.edu (Mark P Jones) Date: Mon, 9 Oct 2000 19:26:00 -0700 Subject: type class In-Reply-To: <39D38A5F.F01D7437@yale.edu> Message-ID: Hi Zhanyong, | In Haskell, instances of a type class can only be well-formed type | constructors ... | Note there is no type constructor abstraction. |=20 | In practice, I found this rule too restrictive. There are good reasons for the restrictions that were alluded to in my constructor classes paper, and again in Typing Haskell in Haskell. Some text from emails written when this topic came up previously is attached to the end of this message. Actually, the first part of the attached email deals with a different problem (making Set an instance of Monad), but since that also came up for discussion again quite recently, I don't think it will hurt to include it again here. | How about extending TC with a branch for abstraction: |=20 | TC ::=3D ... | | /\a. TC -- abstraction |=20 | This is too powerful and will get out of control -- we surely don't = want | to give TC the full power of lambda-calculus. So let's impose a | restriction: in /\a.TC, a must occur free in TC *exactly once*. This | way, abstraction can only be used to specify with respect to which | argument a partial application is. (or I think so -- I haven't tried = to | prove it.) My instinct (which perhaps somebody will prove incorrect) is that this = will not help. Suppose, for example, that you needed to unify ([a],[b]) with = f c as part of the type inference process. How would you solve this = problem? Alas, there are several different, and incompatible ways: ([a], [b]) =3D (/\a. ([a],[b])) a =3D (/\b. ([a],[b])) b =3D (/\c. (c, [b])) [a] =3D (/\d. ([a], d)) [b] =3D (/\e. e) ([a], [b]) Note that the /\-terms in each of these examples satisfies your = restriction. So I don't think you'll be able to obtain most general unifiers or = principal types with this restriction. In my opinion, Dale Miller's work on Higher-order patterns (introduced, = I think in about 1991, but I don't have references) would probably be the best = starting point for serious experimentation in this area. Hope this helps, Mark -- From the archives: = ------------------------------------------------------- Hi Michael, | "...type synonyms must be fully applied". I think the above | example is a valid objection to this. I'll append some text that I wrote on a previous occasion when somebody asked why type synonyms couldn't be partially applied. I hope that it will help to explain why the restriction is not easy to lift, however desirable it might be. The example there was a little different, but I'm sure that you'll see the correspondence. | The other example of something that I want to declare as a monad, but | which I can not is this: Consider a type of collection of some sort = that | requires the types of the elements to be instances of some specific = class. This too is a problem that has come up quite a few times in the past. As yet, I'm not sure that anyone has a definitive answer for it either, although the work that John Hughes presented at the Haskell workshop on Restricted Datatypes is perhaps the closest that anyone has come so far. A general problem here is that there are differences between = conventional mathematics---where you can have sets of any type---and the mathematics = of programming languages---where interesting set datatypes can only be constructed on types whose elements have, at least, an equality. In = Haskell terms, mathematics has an equality function of type: forall a. a -> a -> = Bool; the same operator is available to mathematicians who reason about = Haskell programs. But Haskell programmers have to make do with a more = restrictive operator of type forall a. Eq a =3D> a -> a -> Bool. (Which is not = actually an equality operator at all when you look at what's really going on; = it's just a kind of identity function or projection!) All the best, Mark =20 Here's the text I promised: | I'd like to use monadic code on the following type | type IOF b a =3D b -> IO a | The following seemed reasonable enough: | instance Monad (IOF b) where ... | But Hugs and GHC both object ... The example is rejected because type synonyms can only be used if a full complement of arguments has been given. There are at least two kinds of problem that can occur if you relax this restriction, but both are related to unification/matching. Suppose that we allow your definition. And suppose that we also allow: instance Monad ((->) env) where ... which is a perfectly reasonable thing to do (it's the reader monad). Now what should we do when faced with the problem of unifying two type expressions like: m c and b -> IO a ... Haskell unifies these with the substitution: {m +-> ((->) b), c +-> IO a}, but with your instance decl, you might have preferred { m +-> IOF b, c +-> a }. In other words, it's ambiguous, and the choice between these two could change the semantics because you'll end up picking different instances depending on which choice you make. Or consider what you really mean when you write (IOF b) ... my guess is that you're thinking of it as adding a kind of lambda, so that IOF b =3D \a. a -> IO b This is appealing, but also means that we'd need to move up to = higher-order unification which is undecidable and non-unitary. For example, now we could match m c to b -> IO a in all kinds of interesting ways: b -> IO a =3D (\b . b -> IO a) b =3D (\a . b -> IO a) a =3D (\z . b -> z) (IO a) =3D (\z . b -> IO a) Int =3D ... Now we really have ambiguity problems to worry about! Requiring type synonyms to be fully applied --- in effect, telling us that a synonym is nothing more than an abbreviation, and has no other consequences for the semantics --- seems like a nice way to avoid these problems. -------------------------------------------------------------------------= --- From zhanyong.wan@yale.edu Wed Oct 11 14:53:52 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Wed, 11 Oct 2000 09:53:52 -0400 Subject: type class References: Message-ID: <39E470F0.4F351EEC@yale.edu> Hi Mark, Thanks for the references you provided! Mark P Jones wrote: > My instinct (which perhaps somebody will prove incorrect) is that this will > not help. Suppose, for example, that you needed to unify ([a],[b]) with f c > as part of the type inference process. How would you solve this problem? > Alas, there are several different, and incompatible ways: > > ([a], [b]) = (/\a. ([a],[b])) a > = (/\b. ([a],[b])) b > = (/\c. (c, [b])) [a] > = (/\d. ([a], d)) [b] > = (/\e. e) ([a], [b]) > > Note that the /\-terms in each of these examples satisfies your restriction. > So I don't think you'll be able to obtain most general unifiers or principal > types with this restriction. Let's put your example into the context of type classes: class T f c where method :: f c Now when we want to use method as a ([a],[b]), ambiguity arises, as you suggested. However, I think this just means we should allow *at most one* of the following instances to be declared: instance T (/\a. ([a],[b])) a instance T (/\b. ([a],[b])) b instance T (/\c. (c, [b])) [a] instance T (/\d. ([a], d)) [b] instance T (/\e. e) ([a], [b]) In other words, the above instances are considered overlapping. ____________________________________________________ | As long as we only have one of these instances | | in the program, there is no ambiguity. | ---------------------------------------------------- I'm sure there must be other ramifications (e.g. maybe now whether two instances are overlapping becomes undecidable -- I haven't thought over it yet), but it seems worth further investigation. -- Zhanyong From senganb@ia.nsc.com Thu Oct 12 21:11:16 2000 From: senganb@ia.nsc.com (Sengan) Date: Thu, 12 Oct 2000 16:11:16 -0400 Subject: How does one find lazyness bottlenecks? Message-ID: <39E61AE4.1D8DACE9@ia.nsc.com> Now that ghc 4.08 has a time profiler, I've been improving a program I wrote over the last year. However now the GC time dominates the execution time (>60%). I can see that my program is not being lazy, but I have no idea why. How can I use profiling (or any other means) to determine where my program is not being sufficiently lazy? Are there papers on such things I could read? Sengan From fjh@cs.mu.oz.au Fri Oct 13 01:49:05 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Fri, 13 Oct 2000 11:49:05 +1100 Subject: How does one find lazyness bottlenecks? In-Reply-To: <39E61AE4.1D8DACE9@ia.nsc.com> References: <39E61AE4.1D8DACE9@ia.nsc.com> Message-ID: <20001013114905.A3316@hg.cs.mu.oz.au> On 12-Oct-2000, Sengan wrote: > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. What makes you think that the GC time is due to insufficient laziness? My first thought is that high GC times may well be due to the opposite, too much laziness. Being lazy means that you create closures to represent unevaluated expressions, and those closures will eventually need to be garbage collected. -- Fergus Henderson | "I have always known that the pursuit WWW: | of excellence is a lethal habit" PGP: finger fjh@128.250.37.3 | -- the last words of T. S. Garp. From chak@cse.unsw.edu.au Fri Oct 13 05:16:48 2000 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Fri, 13 Oct 2000 15:16:48 +1100 Subject: How does one find lazyness bottlenecks? In-Reply-To: <39E61AE4.1D8DACE9@ia.nsc.com> References: <39E61AE4.1D8DACE9@ia.nsc.com> Message-ID: <20001013151648K.chak@cse.unsw.edu.au> Sengan wrote, > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. How can I use profiling (or any other means) > to determine where my program is not being sufficiently lazy? Are there > papers on such things I could read? If GC times dominates, you probably have a space leak. So, you should use space profiling to determine where the leak is. Depending on what kind of program you have, it is often also informative to check the space profiles for different kinds of inputs, as the leak might only occur for certain inputs. Depending on the code exercised by the inputs triggering the leak, you might get a rough idea which parts of your program leak. Cheers, Manuel From sylvan@ravinet.com Fri Oct 13 11:18:26 2000 From: sylvan@ravinet.com (Sylvan Ravinet) Date: Fri, 13 Oct 2000 13:18:26 +0300 (EEST) Subject: Haskell to XSLT? Message-ID: Hello, I was wondering if there are ways to translate Haskell code to XSLT. Any ideas? Thank you for your help, Best regards, -Sylvan -- No, try not. Do, or do not. There's no try. -Yoda Sylvan Ravinet: http://www.ravinet.com/sylvan/contact/ -- This message is Copyright 2000 by Sylvan Ravinet. All rights (and responsibility) reserved. From luti@linkexpress.com.br Fri Oct 13 22:42:24 2000 From: luti@linkexpress.com.br (Luciano Caixeta Moreira) Date: Fri, 13 Oct 2000 18:42:24 -0300 Subject: (no subject) Message-ID: <003e01c0355e$7cb4de40$a8adfcc8@servidor> This is a multi-part message in MIME format. ------=_NextPart_000_0035_01C03545.53E7F560 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable unsubscribe haskell@haskell.org ------=_NextPart_000_0035_01C03545.53E7F560 Content-Type: text/html; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable
unsubscribe haskell@haskell.org
------=_NextPart_000_0035_01C03545.53E7F560-- From romildo@urano.iceb.ufop.br Sat Oct 14 05:38:09 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 02:38:09 -0200 Subject: Haskore and nhc98 Message-ID: <20001014023809.A18261@urano.iceb.ufop.br> Hello. I am just curious whether anybody has already tried Haskore (http://www.haskell.org/haskore/) with the NHC98 Haskell compiler. I am trying to do it, while GHC 4.08.1 is non functional in my RH Linux 7.0 box. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From romildo@urano.iceb.ufop.br Sat Oct 14 06:48:06 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 03:48:06 -0200 Subject: Binary files and NHC98 Message-ID: <20001014034806.A23040@urano.iceb.ufop.br> --wRRV7LY7NUeQGEoC Content-Type: text/plain; charset=iso-8859-1 Content-Disposition: inline Content-Transfer-Encoding: 8bit Hello. In order to experiment with the Binary module distributed with nhc98, I wrote the attached program which writes a binary file and then reads it. When executed, I got an extra byte (8) that I cannot explain: [65,66,67,68,8] Any clues why it appears? Regards, Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil --wRRV7LY7NUeQGEoC Content-Type: text/plain; charset=us-ascii Content-Disposition: attachment; filename="BinaryFile.hs" module Main where import IO (IOMode(ReadMode,WriteMode)) import Binary (openBin,closeBin,getBits,putBits,isEOFBin, BinIOMode(RO,WO),BinLocation(File),BinHandle) -- convert from IOMode to BinIOMode ioModeToBinIOMode :: IOMode -> BinIOMode ioModeToBinIOMode ReadMode = RO ioModeToBinIOMode WriteMode = WO -- open a binary file openBinaryFile :: FilePath -> IOMode -> IO BinHandle openBinaryFile path mode = openBin (File path (ioModeToBinIOMode mode)) -- write a list of integers (8 bits) to binary file writeBinaryFile :: FilePath -> [Int] -> IO () writeBinaryFile fileName xs = do f <- openBinaryFile fileName WriteMode let writeToBin [] = return () writeToBin (x:xs) = do putBits f 8 x writeToBin xs writeToBin xs closeBin f -- read a list of integers (8 bits) from binary file readBinaryFile :: FilePath -> IO [Int] readBinaryFile fileName = do f <- openBinaryFile fileName ReadMode let readFromBin = do eof <- isEOFBin f if eof then return [] else do x <- getBits f 8 xs <- readFromBin return (x:xs) xs <- readFromBin closeBin f return xs -- test the above main = do writeBinaryFile "test.bin" [65,66,67,68] xs <- readBinaryFile "test.bin" putStrLn (show xs) --wRRV7LY7NUeQGEoC-- From romildo@urano.iceb.ufop.br Sat Oct 14 08:49:52 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 05:49:52 -0200 Subject: NHC98 and GHC 4.08.1 differ on monad related functions Message-ID: <20001014054952.A27804@urano.iceb.ufop.br> --4Ckj6UjgE2iN1+kY Content-Type: text/plain; charset=iso-8859-1 Content-Disposition: inline Content-Transfer-Encoding: 8bit Hello. While porting Haskore to NHC98 I got an error I am not understanding. I have attached a test module that shows the error message: $ nhc98 -c Test.hs ==================================== Error after type deriving/checking: No default for Monad.MonadPlus at 7:1.(171,[(2,209)]) No default for Monad.MonadPlus at 6:1.(174,[(2,208)]) GHC 4.08.1 and Hugs98 accepts the code without complaining. Any hints? Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil --4Ckj6UjgE2iN1+kY Content-Type: text/plain; charset=us-ascii Content-Disposition: attachment; filename="Test.hs" module Test where import Monad zeroOrMore, oneOrMore :: MonadPlus m => m a -> m [a] zeroOrMore m = return [] `mplus` oneOrMore m oneOrMore m = do { a <- m; as <- zeroOrMore m; return (a:as) } --4Ckj6UjgE2iN1+kY-- From nikhil@acm.org Mon Oct 16 09:21:39 2000 From: nikhil@acm.org (Rishiyur S. Nikhil) Date: Mon, 16 Oct 2000 01:21:39 -0700 Subject: Haskell puzzle Message-ID: <39EABA93.DAD34B10@mediaone.net> In Haskell, is the following transformation always legal? \x->\y->e transforms to \x y->e After answering this question, please scroll down about 75 lines for a follow-up question. What if the two lambda-bound variables are the same? I.e., the lhs is \x->\x->e Please refer to Section 3.3 of the Haskell 98 Report, para 3 (one line para). From timd@macquarie.com.au Tue Oct 17 02:30:58 2000 From: timd@macquarie.com.au (Timothy Docker) Date: Tue, 17 Oct 2000 12:30:58 +1100 (EST) Subject: Mutually recursive structures Message-ID: <14827.43685.102410.194472@tcc2> The following problem has been taxing me.... I have a list of pairs that I have parsed from a input file, which represent a hiirarchy, where the first element is the name of the object, and the second is the name of the parent if there is one: type ParseOutput = [(String,Maybe String)] I wish to convert this to a list of "objects", where from each object I can navigate to the parent object (if any), or the children (if any): data Obj = Obj { name::String, parent::(Maybe Obj), children::[Obj] } type Result = [Obj] convert:: ParseOutput -> Result In a language with mutable references, this would be a relatively straightforward. I would just create a dictionary mapping from name to Obj, and then iterate over them, filling in the parents and children where appropriate. odict = {} for (name,parent) in parseOutput: odict[name] = Obj() for (name,parent) in parseOutput: if parent: parent = odict[parent] child = odict[name] child.parent = parent parent.children.append( child ) This gives away my background! How can I do this in Haskell? If I don't have mutable references, I figure that I must need to use laziness in some way, perhaps similar to how I would build an infinite structure. A hint or two would be great. Tim From Tom.Pledger@peace.com Tue Oct 17 04:32:13 2000 From: Tom.Pledger@peace.com (Tom Pledger) Date: Tue, 17 Oct 2000 16:32:13 +1300 (NZDT) Subject: Mutually recursive structures In-Reply-To: <14827.43685.102410.194472@tcc2> References: <14827.43685.102410.194472@tcc2> Message-ID: <14827.51261.117517.96548@waytogo.peace.co.nz> Timothy Docker writes: > [...] How can I do this in Haskell? If I don't have mutable > references, I figure that I must need to use laziness in some way, > perhaps similar to how I would build an infinite structure. http://www.mail-archive.com/haskell@haskell.org/msg06321.html I have nothing to add to that explanation, so will conserve bandwidth by From christian@lescher.de Tue Oct 17 20:29:25 2000 From: christian@lescher.de (Christian Lescher) Date: Tue, 17 Oct 2000 20:29:25 +0100 Subject: Haskell function with String arguments in DLL Message-ID: <39ECA895.4681986B@lescher.de> I'm trying to build a DLL with a Haskell function of type String -> String, that should be called from outside (e.g. VBA), but it still doesn't work. I'm afraid I need an example or some kind of 'step by step instruction'. Who can help me? (I use GHC 4.08.1.) Christian From timd@macquarie.com.au Tue Oct 17 22:25:58 2000 From: timd@macquarie.com.au (Timothy Docker) Date: Wed, 18 Oct 2000 08:25:58 +1100 (EST) Subject: Mutually recursive structures In-Reply-To: <14827.51261.117517.96548@waytogo.peace.co.nz> References: <14827.43685.102410.194472@tcc2> <14827.51261.117517.96548@waytogo.peace.co.nz> Message-ID: <14828.49022.234836.837956@tcc2> Tom Pledger writes: > Timothy Docker writes: > > [...] How can I do this in Haskell? If I don't have mutable > > references, I figure that I must need to use laziness in some way, > > perhaps similar to how I would build an infinite structure. > > http://www.mail-archive.com/haskell@haskell.org/msg06321.html > To be honest, I found this code quite confusing, I think because of the way in which a the "tail" needs to be joined back to the "head" in creating a circular data structure. I did eventually come up with a solution that seems straightforward enough, although I have no idea of its efficiency... | type ParseOutput = [(String,Maybe String)] | | data Obj = Obj { oname::String, | oparent::(Maybe Obj), | ochildren::[Obj] } | | convert:: ParseOutput -> [Obj] | convert output = converted | where converted = map mkObj output | mkObj (name,parent) = (Obj name | (fmap (findObj converted) parent) | (filter (hasParentNamed name) converted) ) | | findObj:: [Obj] -> String -> Obj | findObj [] name = error ("No object with name "++name) | findObj (o:os) name | name == (oname o) = o | | otherwise = findObj os name | | hasParentNamed :: String -> Obj -> Bool | hasParentNamed name obj = maybe False ((==name).oname) (oparent obj) | Thanks for the pointer. Tim From koen@cs.chalmers.se Wed Oct 18 11:57:56 2000 From: koen@cs.chalmers.se (Koen Claessen) Date: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST) Subject: Num class Message-ID: Hi all, For years I have wondered why the Num class has the Eq class and the Show class as super classes. Because of this, I cannot make functions an instance of Num (becuase they are not in Eq or Show). Or a datatype respresenting an infinite amount of digits (because Eq would not make any sense). Now I have found out the reason! However, it does not make me happy, it makes me even more sad. It is of the defaulting mechanism of course! The defaulting mechanism works as follows: If there is an unresolved overloading error on a type variable a, which has as an *only* constraint (Num a), then we take a to be the suitable default. If Show were not a super class of Num, the following program would generate an error: main = print 42 If Eq were not a super class, the following program would not work: main = print (if 42 == 42 then "koe" else "apa") These programs are all fixed by inserting Show and Eq as super classes of Num. So that one does not even notice! Until now. I am interfacing to an external library that uses double-precision floating points internally for all numbers. This is to be as general as possible. However, I know that when I put for example an Integer in, I get one out too. Thus, I want to give a Haskell interface that can deal with this by any numeric type. So I define a type class: class Num a => Number a where convertToDouble :: a -> Double convertFromDouble :: Double -> a (somehow the Haskell numerical hierarchy does not even let me define general functions that do this! -- but that is besides the point.) instance Number Int instance Number Integer instance Number Float instance Number Double ... All my library functions now have the shape: libraryFunction :: Number a => ... a ... Where as actually: primLibraryFunction :: ... Double ... And now the bad thing... When I use "libraryFunction" on a numeric constant, such as 42, I get the error: ERROR "library.hs" (line 8): Unresolved overloading *** Binding : main *** Outstanding context : Number b This is really annoying, and it is not clear why the default mechanism works this way. So here are my questions. Why does the default mechanism have this restriction? I know that the default mechanism is already broken (some desirable properties are destroyed) -- what properties will be broken by lifting this restriction? /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden From p.turner@computer.org Wed Oct 18 12:37:38 2000 From: p.turner@computer.org (Scott Turner) Date: Wed, 18 Oct 2000 07:37:38 -0400 Subject: pronunciation of >>= Message-ID: <3.0.5.32.20001018073738.009a6750@mail.billygoat.org> Is there a common way to pronounce ">>=" in discussions or when teaching? I've learned all my Haskell from printed/visual documents. -- Scott Turner p.turner@computer.org http://www.ma.ultranet.com/~pkturner From d95lars@dtek.chalmers.se Wed Oct 18 12:43:34 2000 From: d95lars@dtek.chalmers.se (Lars Lundgren) Date: Wed, 18 Oct 2000 13:43:34 +0200 (MEST) Subject: pronunciation of >>= In-Reply-To: <3.0.5.32.20001018073738.009a6750@mail.billygoat.org> Message-ID: On Wed, 18 Oct 2000, Scott Turner wrote: > Is there a common way to pronounce ">>=" in discussions or when teaching? > I've learned all my Haskell from printed/visual documents. How about 'bind'? and ">>" => 'then'. /Lars L From qrczak@knm.org.pl Wed Oct 18 21:02:18 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 18 Oct 2000 20:02:18 GMT Subject: Num class References: Message-ID: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST), Koen Claessen pisze: > The defaulting mechanism works as follows: If there is an unresolved > overloading error on a type variable a, which has as an *only* > constraint (Num a), then we take a to be the suitable default. This is not what the Haskell 98 Report says. Section 4.3.4: "In situations where an ambiguous type is discovered, an ambiguous type variable is defaultable if at least one of its classes is a numeric class (that is, Num or a subclass of Num) and if all of its classes are defined in the Prelude or a standard library (Figures 6--7 show the numeric classes, and Figure 5 shows the classes defined in the Prelude.)" I see no good reason for Show superclass of Num. Eq makes a little more sense, but could be dropped too. It would be inferred separately when a numeric literal is used in a pattern. I agree that the default mechanism is ugly, and that at least the restriction about classes defined in standard libraries should be removed. Clean has per-class defaults. I don't know how conflicting defaults coming from different class constraints should be solved, or what about multiparameter classes, and whether extending the defaulting mechanism is a good idea at all. But since we don't have anything better... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK From mpj@cse.ogi.edu Wed Oct 18 22:46:24 2000 From: mpj@cse.ogi.edu (Mark P Jones) Date: Wed, 18 Oct 2000 14:46:24 -0700 Subject: Num class In-Reply-To: Message-ID: This is a multi-part message in MIME format. ------=_NextPart_000_0001_01C03912.2FCECB10 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable Hi Koen, | If Show were not a super class of Num, the following program | would generate an error: |=20 | main =3D print 42 |=20 | If Eq were not a super class, the following program would | not work: |=20 | main =3D print (if 42 =3D=3D 42 then "koe" else "apa") |=20 | These programs are all fixed by inserting Show and Eq as | super classes of Num. So that one does not even notice! Your claims are incorrect. Both of these examples type check without any errors, and regardless of whether Show and Eq are included as superclasses of Num. It is easy to verify this using "Typing Haskell in Haskell" (http://www.cse.ogi.edu/~mpj/thih); I'll attach the script that I used for this below. Put this in the same directory as all the other .hs files and load it into Hugs. Then edit StdPrel.hs to remove the superclasses of cNum, (replace [cEq, cShow] with []), and it will still work. | For years I have wondered why the Num class has the Eq class | and the Show class as super classes. |=20 | Because of this, I cannot make functions an instance of Num | (because they are not in Eq or Show). Or a datatype | representing an infinite amount of digits (because Eq would | not make any sense). |=20 | Now I have found out the reason! I don't think you have. I do not know the reason either, but I suspect that it is largely historical; when Haskell was first designed, the only types that people wanted to put in Num were also equality and showable types. By making Eq and Show superclasses of Num, types could sometimes be stated more concisely, writing things like (Num a) =3D> ... instead of (Num a, Eq a, Show a) =3D> ... In the past ten years since the Haskell class hierarchy was, more or less, fixed, we've seen several examples of types that don't quite fit (Like functions, computable reals, etc. which might make sense in Num but not in Eq). A natural conclusion is that several of the superclass relations between classes should be removed. But realize that there is an unavoidable compromise here: generality versus the convenience of shorter types. I suggest that there is no point on the spectrum that would keep everybody happy all the time. | It is of the defaulting mechanism of course! | ... Defaulting is a red herring in trying to understand why Show and Eq are superclasses of Num. Marcin has already pointed out that your description of the Haskell defaulting mechanism is not correct by quoting from the Haskell report. You can find another description, again based on the report, in the thih paper. | So I define a type class: | class Num a =3D> Number a where | convertToDouble :: a -> Double | convertFromDouble :: Double -> a |...=20 | All my library functions now have the shape: | libraryFunction :: Number a =3D> ... a ... | ... | And now the bad thing... When I use "libraryFunction" on a | numeric constant, such as 42, I get the error: |=20 | ERROR "library.hs" (line 8): Unresolved overloading | *** Binding : main | *** Outstanding context : Number b |=20 | So here are my questions. Why does the default mechanism | have this restriction? I know that the default mechanism is | already broken (some desirable properties are destroyed) -- | what properties will be broken by lifting this restriction? Defaulting only kicks in if (a) at least one class is numeric, and (b) all classes are standard. Number is not a standard class (you just defined it yourself), so defaulting will not apply. Defaulting was designed to work in this way so that (i) it would catch and deal with the most common problems occurring with numeric literals, and (ii) it would not be used too often; defaulting is in general undesirable because it can silently change the semantics. Again, defaulting is an example of a compromise in the design of Haskell. Ideally, you'd do without it all together, but if you went that way, you'd end up having to write more type information in your programs. And again, I don't suppose there is a universally satisfactory point on this spectrum. All the best, Mark -------------------------------------------------------------------------= --- mpj@cse.ogi.edu Pacific Software Research Center, Oregon Graduate = Institute Want to do a PhD or PostDoc? Interested in joining PacSoft? Let us = know! ------=_NextPart_000_0001_01C03912.2FCECB10 Content-Type: text/plain; name="SourceFortyTwo.hs" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="SourceFortyTwo.hs" module SourceFortyTwo where import Testbed import HaskellPrims import HaskellPrelude -------------------------------------------------------------------------= ---- -- Test Framework: main :: IO () main =3D test imports fortyTwo saveList :: IO () saveList =3D save "FortyTwo" imports fortyTwo imports :: [Assump] imports =3D defnsHaskellPrims ++ defnsHaskellPrelude -------------------------------------------------------------------------= ---- -- Test Program: fortyTwo :: [BindGroup] fortyTwo =3D map toBg [[("main", Nothing, [([], ap [evar "print", elit (LitInt 42)])])], [("main'", Nothing, [([], ap [evar "print",=20 eif (ap [econst eqMfun, elit (LitInt 42), elit (LitInt = 42)]) (elit (LitStr "koe")) (elit (LitStr "apa"))])])]] -------------------------------------------------------------------------= ---- ------=_NextPart_000_0001_01C03912.2FCECB10-- From senganb@ia.nsc.com Thu Oct 19 01:31:02 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 18:31:02 -0600 (MDT) Subject: mapM/concatMapM Message-ID: <200010190031.SAA16141@ia.nsc.com> mapM seems to be a memory hog (and thus also concatMapM). In the following eg: > main = mapM print ([1..102400] :: [Integer]) memory usage climbs to 1.6M with ghc and needs -K20M, whereas with > main = print ([1..102400] :: [Integer]) memory usage is only 1300 bytes. I instrumented mapM: > main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) > mapM2 :: Monad m => (a -> m b) -> [a] -> m [b] > mapM2 f [] = return [] > mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x -> > _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs -> > _scc_ "f" return (x:xs))) and found that a and b were the worst heap users (according to hp2ps), ie the two >>='s Why is this so? What can I do about it? My code uses mapM pretty extensively, and I think its suffering from this problem. I notice that ghc does not seem to use mapM except in 2 modules. Another odd thing is that hp2ps says that a & b are the culprits, but the -p and -px options say p is. Why? Sengan From jenglish@flightlab.com Thu Oct 19 03:03:05 2000 From: jenglish@flightlab.com (Joe English) Date: Wed, 18 Oct 2000 19:03:05 -0700 Subject: mapM/concatMapM In-Reply-To: <200010190031.SAA16141@ia.nsc.com> References: <200010190031.SAA16141@ia.nsc.com> Message-ID: <200010190203.TAA16483@dragon.flightlab.com> senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > mapM seems to be a memory hog (and thus also concatMapM). > In the following eg: > > > main = mapM print ([1..102400] :: [Integer]) > > memory usage climbs to 1.6M with ghc and needs -K20M As a guess: since 'mapM print ([1..102400] :: [Integer])' has type 'IO [()]', perhaps the result of the IO operation -- a list of 100K empty tuples -- is the culprit, even though the result is never used. Does 'mapM_ print ... ' (:: IO ()) perform any better? --Joe English jenglish@flightlab.com From senganb@ia.nsc.com Thu Oct 19 05:09:21 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 22:09:21 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190203.TAA16483@dragon.flightlab.com> from "Joe English" at Oct 18, 2000 07:03:05 PM Message-ID: <200010190409.WAA16637@ia.nsc.com> > > > senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > > > mapM seems to be a memory hog (and thus also concatMapM). > > In the following eg: > > > > > main = mapM print ([1..102400] :: [Integer]) > > > > memory usage climbs to 1.6M with ghc and needs -K20M > > As a guess: since 'mapM print ([1..102400] :: [Integer])' > has type 'IO [()]', perhaps the result of the IO operation -- > a list of 100K empty tuples -- is the culprit, even though > the result is never used. > > Does 'mapM_ print ... ' (:: IO ()) perform any better? Yes, but in the following eg > main = print $ sum x > x = _scc_ "x" [1..102400] :: [Integer] x takes 1M allocations, and I would think that () would be smaller than an Integer. Therefore I'm not sure that is the reason. The sum is there to force the evaluation. Sengan From senganb@ia.nsc.com Thu Oct 19 05:34:01 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 22:34:01 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190409.WAA16637@ia.nsc.com> from "senganb@ia.nsc.com" at Oct 18, 2000 10:09:21 PM Message-ID: <200010190434.WAA20212@ia.nsc.com> > > senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > > > > > mapM seems to be a memory hog (and thus also concatMapM). > > > In the following eg: > > > > > > > main = mapM print ([1..102400] :: [Integer]) > > > > > > memory usage climbs to 1.6M with ghc and needs -K20M > > > > As a guess: since 'mapM print ([1..102400] :: [Integer])' > > has type 'IO [()]', perhaps the result of the IO operation -- > > a list of 100K empty tuples -- is the culprit, even though > > the result is never used. > > > > Does 'mapM_ print ... ' (:: IO ()) perform any better? > > Yes, but in the following eg > > > main = print $ sum x > > x = _scc_ "x" [1..102400] :: [Integer] > > x takes 1M allocations, and I would think that () would be smaller than > an Integer. Therefore I'm not sure that is the reason. The sum is there to > force the evaluation. Assuming you are right, why do I see the same 1.6M profile with: > main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) >> return () > mapM2 :: Monad m => (a -> m b) -> [a] -> m [b] > mapM2 f [] = return [] > mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x -> > _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs -> > _scc_ "f" return (x:xs))) Is >>= not lazy? Sengan From senganb@ia.nsc.com Thu Oct 19 07:11:29 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Thu, 19 Oct 2000 00:11:29 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190434.WAA20212@ia.nsc.com> from "senganb@ia.nsc.com" at Oct 18, 2000 10:34:01 PM Message-ID: <200010190611.AAA03566@ia.nsc.com> Actually I think I figured it out: (>>=) (f c) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (>>=) _(f c)_ (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (>>=) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (\(MN c1) \fc2 -> MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = fc2 r1 (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) r1 (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) So the "return (r1:xs)" will only happen once the whole mapM has completed, leaving, if I only use r1 at first, a whole load of partially evaluated iterations of mapM in the heap. This also means that sequences such as "mapM x >>= mapM y >>= mapM z" are very inefficient and should be replaced by mapM (z.y.x) whereever possible. Agreed? Sengan From xvw@trinity.warande.net Thu Oct 19 22:24:13 2000 From: xvw@trinity.warande.net (xander) Date: Thu, 19 Oct 2000 23:24:13 +0200 (CEST) Subject: hugs/ghc + shared mem access Message-ID: Hi, I'm exploring my options to connect 2 programs (1 Haskell, 1 non-Haskell). I could connect both programs by 1 or 2 sockets. I was wondering whether it's feasible to access shared memory from within hugs as an alternative? Any answers? Thanks, xander van wiggen From frido@q-software-solutions.com.NO-spam Fri Oct 20 07:46:37 2000 From: frido@q-software-solutions.com.NO-spam (Friedrich Dominicus) Date: 20 Oct 2000 08:46:37 +0200 Subject: A question regarding haskell mode for Emacs In-Reply-To: John Atwood's message of "Tue, 22 Aug 2000 13:20:14 -0700 (PDT)" References: <200008222020.NAA25101@jasper.CS.ORST.EDU> Message-ID: <8766morovm.fsf@q-software-solutions.com> I wonder if there are some known troubles. This mode yesterday nearly drive me nuts. Indentation seem to be ok from the layout, but I got complains about block closed to early, missing ; ... Regards Friedrich -- for e-mail reply remove all after .com From romildo@urano.iceb.ufop.br Fri Oct 20 10:21:51 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Fri, 20 Oct 2000 07:21:51 -0200 Subject: Extensible data types? In-Reply-To: ; from rob@benchees.demon.co.uk on Mon, Sep 25, 2000 at 12:32:47PM +0100 References: ; <20000925082731.A3440@urano.iceb.ufop.br> Message-ID: <20001020072151.A1810@urano.iceb.ufop.br> Hello. I am back with the issue of extensible union types. Basically I want to extend a data type with new value constructors. Some members of the list pointed me to the paper "Monad Transformers and Modular Interpreters" Sheng Liang, Paul Hudak and Mark Jones The authors suggest using a type constructor to express the disjoint union of two other types: data Either a b = Left a | Right b which indeed is part of the Haskell 98 Prelude. Then they introduce a subtype relationship using multiparameter type classes: class SubType sub sup where inj :: sub -> sup -- injection prj :: sup -> Maybe sub -- projection The Either data type consructor is then used to express the desired subtype relationshipe: instance SubType a (Either a b) where inj = Left prj (Left x) = Just x prj _ = Nothing instance SubType a b => SubType a (Either c b) where inj = Right . inj prj (Right x) = prj x prj _ = Nothing The authors implemented their system in Gofer, due to restrictions in the type class system of Haskell. But now that there are Haskell extensions to support multiparametric type classes, that could be implemented in Haskell. The above code fails to type check due to instances overlapping. Hugs gives the following error message: ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType" *** This instance : SubType a (Either b c) *** Overlaps with : SubType a (Either a b) *** Common instance : SubType a (Either a b) (I did not check Gofer, but is there a way to solve these overlapping of instances in it?) So this is scheme is not going to work with Haskell (extended with multiparameter type classes). I would like hear any comments from the Haskell comunity on this subject. Is there a workaround for the overlapping instances? Regards. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From labra@pinon.ccu.uniovi.es Fri Oct 20 11:36:39 2000 From: labra@pinon.ccu.uniovi.es (Jose Emilio Labra Gayo) Date: Fri, 20 Oct 2000 12:36:39 +0200 (METDST) Subject: Extensible data types? In-Reply-To: <20001020072151.A1810@urano.iceb.ufop.br> Message-ID: > > The above code fails to type check due to instances > overlapping. Hugs gives the following error message: > In Hugs, there is a flag that you can set to allow overlapping instances :s +o In GHC, you can also set -fallow-overlapping-instances BTW, I use extensible union types in a "Language prototyping System" that I am implementing and which compiles with GHC and Hugs (it is based on Liang, Hudak and Jones paper). You can download the source code from "http://lsi.uniovi.es/~labra/LPS/LPS.html" Best regards, Jose Labra http://lsi.uniovi.es/~labra From doaitse@cs.uu.nl Fri Oct 20 14:16:34 2000 From: doaitse@cs.uu.nl (S. Doaitse Swierstra) Date: Fri, 20 Oct 2000 15:16:34 +0200 Subject: Extensible data types? In-Reply-To: <20001020072151.A1810@urano.iceb.ufop.br> References: ; <20000925082731.A3440@urano.iceb.ufop.br> <20001020072151.A1810@urano.iceb.ufop.br> Message-ID: It is exactly for reasons like these that we developped our small attribute grammar system: http://www.cs.uu.nl/groups/ST/Software/UU_AG/index.html Doaitse Swiesrtra At 7:21 AM -0200 10/20/00, Jos=E9 Romildo Malaquias wrote: >Hello. > >I am back with the issue of extensible union types. Basically >I want to extend a data type with new value constructors. >Some members of the list pointed me to the paper > > "Monad Transformers and Modular Interpreters" > Sheng Liang, Paul Hudak and Mark Jones > >The authors suggest using a type constructor to express >the disjoint union of two other types: > > data Either a b =3D Left a | Right b > >which indeed is part of the Haskell 98 Prelude. Then they introduce >a subtype relationship using multiparameter type classes: > > class SubType sub sup where > inj :: sub -> sup -- injection > prj :: sup -> Maybe sub -- projection > >The Either data type consructor is then used to express >the desired subtype relationshipe: > > instance SubType a (Either a b) where > inj =3D Left > prj (Left x) =3D Just x > prj _ =3D Nothing > > instance SubType a b =3D> SubType a (Either c b) where > inj =3D Right . inj > prj (Right x) =3D prj x > prj _ =3D Nothing > >The authors implemented their system in Gofer, due to >restrictions in the type class system of Haskell. >But now that there are Haskell extensions to support >multiparametric type classes, that could be implemented >in Haskell. > >The above code fails to type check due to instances >overlapping. Hugs gives the following error message: > > ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType" > *** This instance : SubType a (Either b c) > *** Overlaps with : SubType a (Either a b) > *** Common instance : SubType a (Either a b) > >(I did not check Gofer, but is there a way to solve these >overlapping of instances in it?) > >So this is scheme is not going to work with Haskell (extended >with multiparameter type classes). > >I would like hear any comments from the Haskell comunity on >this subject. Is there a workaround for the overlapping instances? > >Regards. > >Romildo >-- >Prof. Jos=E9 Romildo Malaquias >Departamento de Computa=E7=E3o >Universidade Federal de Ouro Preto >Brasil > >_______________________________________________ >Haskell mailing list >Haskell@haskell.org >http://www.haskell.org/mailman/listinfo/haskell -- __________________________________________________________________________ S. Doaitse Swierstra, Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands Mail: mailto: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 legere@its.caltech.edu Fri Oct 20 16:21:12 2000 From: legere@its.caltech.edu (Ronald J. Legere) Date: Fri, 20 Oct 2000 08:21:12 -0700 (PDT) Subject: .net and haskell In-Reply-To: Message-ID: I was reading some .net stuff (ducks) on microsoft, and they mentioned haskell as one of the languages someone was targetting for it. Anyone know anything about this project? Cheers! +++++++++++++++++++++++++++++++++++++++++++++++++ Ron Legere -- http://www.its.caltech.edu/~legere Caltech Quantum Optics MC 12-33 Pasadena CA 91125 626-395-8343 FAX: 626-793-9506 +++++++++++++++++++++++++++++++++++++++++++++++++ From romildo@urano.iceb.ufop.br Sat Oct 21 09:48:40 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 21 Oct 2000 06:48:40 -0200 Subject: Passing an environment around In-Reply-To: ; from conal@MICROSOFT.com on Thu, Oct 19, 2000 at 09:08:16AM -0700 References: Message-ID: <20001021064840.A19051@urano.iceb.ufop.br> The following discussion is been conducted in the Clean mailing list. As the issue is pertinent also to Haskell, I have cross-posted this letter to the Haskell mailing list too. Romildo. On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote: > Indeed Fran behaviors are like your alternative #1 (function passing), and > hence sharing loss is a concern. Simon PJ is right that I have a paper > discussing this issue and some others. See "Functional Implementations of > Continuous Modeled Animation" on my pubs page > (http://research.microsoft.com/~conal/papers). > > About alternative #2 (implicit arguments), would it help? Does it eliminate > the non-memoized redundant function applications, or just hide them? For > Fran, Erik Meijer suggested implicit functions to me a couple of years ago. > I hadn't thought of it, and it did indeed seem to be attractive at first as > a way to eliminate the need for overloading in Fran. However, the (Time -> > a) representation of Fran behaviors is not really viable, so I wouldn't > merely want to hide that representation behind implicit arguments. It seems that implicit parameters does not eliminate redundant function applications, as Conal Elliott has commented. Reading the paper Implicit Parameters: Dynamic Scoping with Static Types Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury http://www.cse.ogi.edu/~jlewis/ (especially section 5.1) I got this impression. I would like to hear from others as well, as I had some difficulties with the paper. > I don't see how alternative #3 would work. > > Of the three approaches, I think #1 is probably the best way to go. > Functional programming encourages us to program with higher-order functions, > and doing so naturally leads to this loss-of-sharing problem. Memoization > is thus a useful tool. Adding it to Clean would probably help others as > well as you. > > > I recommend that you find out how real computer algebra systems address this > issue. I've used these systems some and have the impression that there is a > default set of simplification rules, plus some strategies for non-standard > "simplifications" like factoring. You could apply the default set in a > bottom-up way, with no need for memoization. This is precisely the approach > used for algebraic simplification in Pan (an Haskell-based image synthesis > library). See the recent paper "Compiling Embedded Languages" on my pubs > page. You can also get the Pan source release to check out the real > details. > > Good luck, and please let me know how it turns out. > > - Conal > > -----Original Message----- > From: Simon Peyton-Jones > Sent: Thursday, October 19, 2000 1:51 AM > To: José Romildo Malaquias; clean-list@cs.kun.nl > Cc: Conal Elliott (E-mail); Meurig Sage (E-mail) > Subject: RE: [clean-list] Passing an environment around > > It's interesting that *exactly* this issue came up when Conal > Eliott was implementing Fran in Haskell. His 'behaviours' > are very like your expressions. > type Behaviour a = Time -> a > and he found exactly the loss of sharing that you did. > > For some reason, though, I'd never thought of applying the > implicit-parameter > approach to Fran. (Perhaps because Implicit parameters came along after > Fran.) > But I think it's rather a good idea. > > I think Conal may have a paper describing the implementation choices > he explored; I'm copying him. > > Simon > > | -----Original Message----- > | From: José Romildo Malaquias [mailto:romildo@urano.iceb.ufop.br] > | Sent: 18 October 2000 08:12 > | To: clean-list@cs.kun.nl > | Subject: [clean-list] Passing an environment around > | > | > | Hello. > | > | I am implementing a Computer Algebra system (CALG) in Clean, > | and I have a > | problem I would like the opinion of Clean programmers. > | > | The CALG system should be able to simplify (or better, to transform) > | algebraic expressions (from Mathematics) involving integers, > | named constants > | (like "pi" and "e"), variables, arithmetic operations (addition, > | multiplication, exponentiation), and other forms of expressions > | (trigonometric, logarithmic, derivatives, integrals, > | equations, etc.). The > | tansformaations should follow the rules from Algebra and > | other areas of > | Mathematica. But we know that in general an algebraic > | expression can be > | transformed in different ways, depending on the goal of the > | transformation. Thus, the algebraic expression > | > | a^2 + b^2 + 3*a*b - a*b > | > | could result in > | > | a^2 + 2*a*b + b^2 > | > | or in > | > | (a + b)^2 > | > | To control the transformations made with an algebraic > | expression there is a > | set of flags collected in a record. I will call this record > | the environment > | in which the expression should be simplified. The algorithms I am > | implementing may change this environment temporarily for some local > | transformations. So the enviroment should be passed around in > | the function > | calls I am writing. This way the functions that implements the > | transformations will have an extra argument representing the > | environment in > | which the transformation is to be performed. > | > | Let's take an example: the algorithm for addition will have > | two arguments to > | be added and a third argument corresponding to the enviroment: > | > | add :: Expr Expr Env -> Expr > | > | and its result will depend of the flags in the environment. > | But it is highly > | desirable to define functions like add as BINARY INFIX > | OPERATORS. Having 3 > | arguments, add cannot be made a binary operator! > | > | -------------------------------------------------------------------- > | So I am looking for alternative ways to pass the environment around. > | -------------------------------------------------------------------- > | > | 1. Handle the arguments as functions themselves, which, given > | an enviroment, > | returns the simplified algebraic expression in that environment: > | > | add :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr) > | > | Now add can be made a binary infix operator. This solution has the > | disadvantage that we loose sharing when doing local > | simplifications. For > | example: > | > | f :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr) > | f fx fy = (add (add fx fy) fy) > | > | fe1, fe2 :: Env -> Exp > | fe1 e = ... > | fe2 e = ... > | > | initialEnv :: Env > | initialEnv = ... > | > | Start = f fe1 fe2 initialEnv > | > | In this program fragment, fe2 may be applied twice to the same > | environment value, computing its body twice. The resulting > | program would > | be too inneficient. If Clean had a mean of implementing MEMOIZATION > | FUNCTIONS, the computation of a memoized function > | application to the same > | argument would evalute the body of the function only the > | first time the > | function is applied. Subsequent applications of that > | function to the same > | argument would remember the result of the previous > | application and would > | reutilize it. Then this way of handling environment > | passing would be a > | good solution. > | > | For more on memo functions see > | . > | > | 2. Extend Clean to support IMPLICIT PARAMETER PASSING (that > | is, a form of > | dynamic scoping), as has been done in some Haskell > | implementations (Hugs, > | GHC). Than the environment could be passed implicitly and > | add could be > | considered to have only 2 arguments > | > | add :: (Env ?env) => Exp Exp -> Exp > | > | Here ?env represents an implicit parameter. It is not > | passed explicitly > | like the two argument parameters. It can be used normally > | in the function > | definition, like any normal parameter. To pass an argument > | implicitly, > | there is 2 additional forms of expression: dlet and with: > | > | dlet ?env = ... in add e1 e2 > | > | add e1 e2 with ?env = ... > | > | I think this could be the best solution to my problem, if Clean had > | such extension implemented. > | > | For more information, see > | > | > | 3. Join the algebraic expression and the environment in a single value > | > | add :: (Env,Exp) (Env,Exp) -> (Env,Exp) > | > | The enviroment is then carried around with each expression. > | But now add has two enviroments to consult. Which one should be > | used? > | > | Would be other good alternatives to solve this problem? > | > | Would future versions of Clean support > | > | - memoization functions, or > | - implciit parameter passing? > | > | I am open to discussion on this topics. > | > | Regards, > | > | Romildo > | -- > | Prof. José Romildo Malaquias > | Departamento de Computação > | Universidade Federal de Ouro Preto > | Brasil > | > | _______________________________________________ > | clean-list mailing list > | clean-list@cs.kun.nl > | http://www.cs.kun.nl/mailman/listinfo/clean-list > | > > _______________________________________________ > clean-list mailing list > clean-list@cs.kun.nl > http://www.cs.kun.nl/mailman/listinfo/clean-list -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From romildo@urano.iceb.ufop.br Mon Oct 23 13:22:35 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Mon, 23 Oct 2000 10:22:35 -0200 Subject: Overloaded function and implicit parameter passing Message-ID: <20001023102235.A11238@urano.iceb.ufop.br> Hi. While experimenting with the implicit parameter extension to Haskell 98, implemented in GHC 4.08.1 and latest Hugs, I came accross a difference among those implementations regarding overloading functions with implicit parameters. As a test consider the program ------------------------- cut here module Main where class C a where f :: (?env :: Integer) => a -> Integer instance C Integer where f x = ?env + x main = putStrLn (show (f (45::Integer) with ?env = 100)) ------------------------- cut here Hugs accepts this program and outputs 145, as expected. But GHC 4.08.1 refuses to compile it, emitting the message $ ghc -fglasgow-exts Test1.hs -o test1 Test1.hs:7: Unbound implicit parameter `env_rJX :: Integer' arising from use of `env_rJX' at Test1.hs:7 In the first argument of `+', namely `env_rJX' In the right-hand side of an equation for `f': env_rJX + x Compilation had errors Would anybody comment on what is going on with GHC? I am willing to use implicit parameters in the software I am developing, but I have the need to overload functions with implicit parameters. While Hugs is good for development, its performance may rule it out when the final product is ready. So I will need a good Haskell compiler to compile my system. Any comments? Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From fjh@cs.mu.oz.au Mon Oct 23 15:02:14 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Tue, 24 Oct 2000 01:02:14 +1100 Subject: Overloaded function and implicit parameter passing In-Reply-To: <20001023102235.A11238@urano.iceb.ufop.br> References: <20001023102235.A11238@urano.iceb.ufop.br> Message-ID: <20001024010214.A11699@hg.cs.mu.oz.au> On 23-Oct-2000, José Romildo Malaquias wrote: > ------------------------- cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > ------------------------- cut here ... > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 ... > Would anybody comment on what is going on with GHC? That sure looks to me like a bug in GHC's support for implicit parameter passing. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From ru@ohio.river.org Mon Oct 23 21:28:09 2000 From: ru@ohio.river.org (Richard) Date: Mon, 23 Oct 2000 13:28:09 -0700 (PDT) Subject: mapM/concatMapMy In-Reply-To: <200010190434.WAA20212@ia.nsc.com> References: <200010190409.WAA16637@ia.nsc.com> <200010190434.WAA20212@ia.nsc.com> Message-ID: <200010232028.NAA14294@ohio.river.org> Sengan Baring-Gould writes: >Is >>= not lazy? since no experts have answered yet, this newbie will answer. I think it's strict. somewhere in the compiler doco, IIRC, it says (>>=) was lazy at first, but experience showed it was more confusing for users (Haskell programmers). moreover, from the hslibs documentation, LazyST chapter: "The lazy ST monad tends to be more prone to space leaks than the strict version, so most programmers will use the former unless laziness is explicitly required." http://haskell.org/ghc/docs/latest/set/sec-lazyst.html From quintela@fi.udc.es Tue Oct 24 05:48:25 2000 From: quintela@fi.udc.es (Juan J. Quintela) Date: 24 Oct 2000 06:48:25 +0200 Subject: CFP: Eight International Conference on Computer Aided Systems Theory Message-ID: The following message is a courtesy copy of an article that has been posted to comp.lang.ml,comp.lang.functional as well. Dear Colleagues, I would be most grateful if you would distribute the appended Call For Papers to your colleagues (and/or any mailing lists you see appropriate). Any help in distributing the Call For Papers would be most appreciated. Kindest regards, Juan Quintela CALL FOR PAPERS --------------- Eight International Conference on Computer Aided Systems Theory Formal Methods and Tools for Computer Science See the webpage at: http://azuaje.ulpgc.es/congresos/eurocast2001/ The topics for the workshop are: Workshop "FP" Contributions addressing to the following and similar issues: 1.Concurrency. Distributed and web applications. 2.Verification:tools and methods. 3.Persistence. 4.Typing and theoretical foundations. You only have to send one extended abstract before the: 31 October. -- In theory, practice and theory are the same, but in practice they are different -- Larry McVoy From rjmh@cs.chalmers.se Tue Oct 24 09:16:54 2000 From: rjmh@cs.chalmers.se (John Hughes) Date: Tue, 24 Oct 2000 10:16:54 +0200 (MET DST) Subject: mapM/concatMapMy Message-ID: <200010240816.KAA17042@muppet30.cs.chalmers.se> Sengan Baring-Gould writes: >Is >>= not lazy? since no experts have answered yet, this newbie will answer. I think it's strict. Well, it depends. (>>=) is an overloaded operator, with a different implementation for every monad -- when you define a monad, you give the implementation of (>>=). If your implementation is strict (presumably in the first operand), then (>>=) is strict *at that type*. If your implementation is lazy, then it isn't. The same goes for (+): at most types (+) is strict, but if you define your own kind of number with a lazy addition, then on that type (+) will be lazy. For many monads, (>>=) *is* strict, which fits with the intuition that it is a `sequencing' operator. But by no means for all. The simplest counter-example is the identity monad: newtype Id a = Id a instance Monad Id where return = Id Id x >>= f = f x where m>>=f is strict in m only if f is a strict function. A more interesting example is the state transformer monad: newtype ST s a = ST (s -> (a,s)) instance Monad (ST s) where return x = ST (\s -> (x,s)) ST h >>= f = ST (\s -> let (a,s') = h s ST h' = f a in h' s') where once again, the implementation of (>>=) is strict only if f is a strict function. Hence `lazy state' makes sense! John Hughes From delapla@lami.univ-evry.fr Tue Oct 24 13:57:16 2000 From: delapla@lami.univ-evry.fr (Franck Delaplace) Date: Tue, 24 Oct 2000 14:57:16 +0200 Subject: LOOKING FOR B-TREES MODULE Message-ID: <39F5872C.8B54DC16@lami.univ-evry.fr> I am looking for an haskell module which implements balanced trees ? Can somebdody help me = Thank you = -- = Franck Delaplace @w3:http://taillefer.lami.univ-evry.fr:8090/~delapla/ La.M.I-U.M.R C.N.R.S Universit=E9 d'Evry Val d'Essonne = Cours Monseigneur Rom=E9ro = 91025 Evry CEDEX (France) From wohlstad@cs.ucdavis.edu Tue Oct 24 19:25:29 2000 From: wohlstad@cs.ucdavis.edu (Eric Allen Wohlstadter) Date: Tue, 24 Oct 2000 11:25:29 -0700 (PDT) Subject: Group theory In-Reply-To: <200010240816.KAA17042@muppet30.cs.chalmers.se> Message-ID: Are there any Haskell libraries or programs related to group theory? I am taking a class and it seems like Haskell would be a good programming language for exploring/reasoning about group theory. What I had in mind was perhaps you could have a function which takes a list(set) and a function with two arguments(binary operator) and checks to see whether or not it is a group. I think it might be a fun exercies to write myself but I'd like to see if it's already been done or what you guys think about it. Eric Wohlstadter UCDavis Software Engineering From dongen@cs.ucc.ie Tue Oct 24 19:29:58 2000 From: dongen@cs.ucc.ie (Marc van Dongen) Date: Tue, 24 Oct 2000 19:29:58 +0100 Subject: Group theory In-Reply-To: ; from wohlstad@cs.ucdavis.edu on Tue, Oct 24, 2000 at 11:25:29AM -0700 References: <200010240816.KAA17042@muppet30.cs.chalmers.se> Message-ID: <20001024192958.D25711@cs.ucc.ie> Eric Allen Wohlstadter (wohlstad@cs.ucdavis.edu) wrote: : Are there any Haskell libraries or programs related to group theory? I am : taking a class and it seems like Haskell would be a good programming : language for exploring/reasoning about group theory. What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) has facilities for that. Have a look at: http://www.cs.bell-labs.com/who/wadler/realworld/docon.html Regards, Marc van Dongen From mechvel@math.botik.ru Wed Oct 25 08:20:32 2000 From: mechvel@math.botik.ru (S.D.Mechveliani) Date: Wed, 25 Oct 2000 11:20:32 +0400 Subject: group theory. Reply Message-ID: Hi, all, To Eric Allen Wohlstadter's (wohlstad@cs.ucdavis.edu) : Are there any Haskell libraries or programs related to group theory? I am : taking a class and it seems like Haskell would be a good programming : language for exploring/reasoning about group theory. What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. Marc van Dongen writes > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) > has facilities for that. Have a look at: > > http://www.cs.bell-labs.com/who/wadler/realworld/docon.html Sorry, DoCon () really supports the Commutative Rings, but provides almost nothing for the Group theory. For example, for the domain (Integer,Integer) it would set automatically (IsGroup,Yes) for the Additive semigroup and (IsGroup,No) for the Multiplicative semigroup. For the additive case, it would also set the group generator list [(1,0),(0,1)]. In both cases, it would also set cardinality = Infinity. Similar attributes are formed for the constructors of Permutation, Vector, Matrix, Polyninomial, Fraction, ResidueRing. And that is all. It does not provide so far any real algorithmic support for the Group theory, except some operations on permutations. But one may develop the program by adding the needed algorithms and introducing new attributes. : What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. I never programmed this. It looks like some exercise in algorithms. There are also books on the combinatorial group theory, maybe, they say something about efficient procedures for this. Regards, ------------------ Sergey Mechveliani mechvel@botik.ru From karczma@info.unicaen.fr Wed Oct 25 10:58:04 2000 From: karczma@info.unicaen.fr (Jerzy Karczmarczuk) Date: Wed, 25 Oct 2000 10:58:04 +0100 Subject: group theory. Reply References: Message-ID: <39F6AEAC.F5C9C988@info.unicaen.fr> S.D.Mechveliani wrote: > > Hi, all, > > To Eric Allen Wohlstadter's > > : Are there any Haskell libraries or programs related to group theory? ... > Marc van Dongen writes > > > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) > > has facilities for that. ... > Sorry, > DoCon () > > really supports the Commutative Rings, > but provides almost nothing for the Group theory. > EAW again: > : ... I think it might be a fun exercies to write myself but > : I'd like to see if it's already been done or what you guys > : think about it. SM: > I never programmed this. It looks like some exercise in algorithms. > There are also books on the combinatorial group theory, maybe, they > say something about efficient procedures for this. == "Some exercise in algorithms". Hm. There is more to that than this... This issue has been recently stirred a bit in the comp.functional newsgroup, in a larger context, general Math, not necessarily the group theor. There are at least two people *interested* in it, although they didn't do much yet (for various reasons...) Suggestion: Take GAP! ( http://www-history.mcs.st-and.ac.uk/~gap/ ) Plenty of simply coded algorithms, specifically in this domain. I coded just for fun a few simple things in Haskell some time ago, and it was a real pleasure. The code is cleaner and simpler. Its presentation is also much cleaner than the original algorithms written in GAP language. But I discarded all this stuff, thinking that I would have never time enough to get back to it... This is a nice project, and I would participate with pleasure in it, although the time factor is still there... Dima Pasechnik (; does he read it?) - apparently - as well. Jerzy Karczmarczuk Caen, France From senganb@ia.nsc.com Wed Oct 25 17:21:42 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 25 Oct 2000 10:21:42 -0600 (MDT) Subject: Haskell Programming Environment In-Reply-To: <20001025084900Z474423-538+2802@webmail1.ahoj.pl> from "=?ISO-8859-2?Q? Pawe=B3?= Kot" at Oct 25, 2000 10:48:57 AM Message-ID: <200010251621.KAA02114@ia.nsc.com> > Hello, > > I'm writing my master thesis. Its subject is 'Haskell Programming > Environment'. It is (or rather will be) an extended text editor working i= > n > graphical (XFree86) environment designed for Haskell programmers. It will= > be > implemented using Fudgets library. > I'm wondering what features would you like to find in such environment. W= > hat > should be neccessary, what would help, what would make writing programs > easier, etc. > I have some concepts, but I would like to hear some suggestions from you. > > Thanks for all answers. a) the ablility to highlight an area of code and get its type (be it a function, or some well-formed chunk of code b) the ability to highlight a function and get its definition in another area (think multiple text editing in vim) c) interaction with hugs/stg-hugs so that just written code can be pasted into a "hugs window" for evaluation. d) Debug mode which automatically adds "deriving show" to all datatypes which are not showable/adds exporting of all Datatypes as non-abstract for use in hugs to just allow things to be tried out. e) Debug mode which invisibly replaces functions such as "fromJust" with error making versions (... fromJust' "the file and line at which I'm invoked" ...) to make it easier to find the cause of the error (fromJust Nothing just comes up with an error telling you that it's fromJust that failed. Last time that happened, I hacked hugs to dump the evaluation stack, from which I guessed which possible fromJusts it could have been). f) Use ghc's .hi file to allow strictness of arguments to appear if you leave the mouse over an argument. g) For bonus points (harder, but really useful when stuck): given an expression, show me (possibly using daVinci) how it gets evaluated: Lazyness behaviour is not always obvious, I'd like to see it. I've been wanting to code one of these myself, but have had no time. Try and see if stg-hugs is useable yet since that would be a much better environment to do it in. Sengan From Keith.Wansbrough@cl.cam.ac.uk Wed Oct 25 17:26:51 2000 From: Keith.Wansbrough@cl.cam.ac.uk (Keith Wansbrough) Date: Wed, 25 Oct 2000 17:26:51 +0100 Subject: Haskell Programming Environment In-Reply-To: Your message of "Wed, 25 Oct 2000 10:21:42 MDT." <200010251621.KAA02114@ia.nsc.com> Message-ID: > I've been wanting to code one of these myself, but have had no time. Try and see > if stg-hugs is useable yet since that would be a much better environment to do > it in. It's now called GHCi, and is being written right now by the GHC team. Not sure when the estimated completion time is, but it can't be that far off. --KW 8-) From ger@Informatik.Uni-Bremen.DE Wed Oct 25 21:08:55 2000 From: ger@Informatik.Uni-Bremen.DE (George Russell) Date: Wed, 25 Oct 2000 22:08:55 +0200 Subject: cpp superior to ghc . . . Message-ID: <39F73DD7.E744A061@informatik.uni-bremen.de> Why does the Haskell language not allow "type" declarations to appear in the declaration parts of where and let clauses? I've just been writing a huge functions which requires lots and lots of repetitive internal type annotations (to disambiguate some complicated overloading) but I can't abbreviate them with "type" because they depend on things only in scope inside the function. In the end I abbreviated them with a few #define's but I don't really think it should be that way . . . From qrczak@knm.org.pl Thu Oct 26 06:09:48 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 26 Oct 2000 05:09:48 GMT Subject: cpp superior to ghc . . . References: <39F73DD7.E744A061@informatik.uni-bremen.de> Message-ID: Wed, 25 Oct 2000 22:08:55 +0200, George Russell pisze: > Why does the Haskell language not allow "type" declarations to > appear in the declaration parts of where and let clauses? Because you can always lift them to the top level. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK From koen@cs.chalmers.se Thu Oct 26 08:01:21 2000 From: koen@cs.chalmers.se (Koen Claessen) Date: Thu, 26 Oct 2000 09:01:21 +0200 (MET DST) Subject: cpp superior to ghc . . . In-Reply-To: Message-ID: George Russell complained: | Why does the Haskell language not allow "type" | declarations to appear in the declaration parts of | where and let clauses? Marcin 'Qrczak' Kowalczyk replied: | Because you can always lift them to the top level. This is the ultimate non-answer. First of all, it is wrong. George meant to be able to use type variables present in the top-level type in the local type declarations. Something like: doWithStack :: a -> a doWithStack x = stacking [] where type Stack = [a] stacking :: Stack -> a stacking = ... The problem is really two-fold: bound type variables (like "a") are not in scope in the body of the function, and local type declarations are not allowed. Secondly, "because another way of doing it is possible" is not an answer. We allow local declarations of functions, but we have known for ages we can all lambda-lift them to top-level... Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden From mk167280@students.mimuw.edu.pl Thu Oct 26 08:29:49 2000 From: mk167280@students.mimuw.edu.pl (Marcin 'Qrczak' Kowalczyk) Date: Thu, 26 Oct 2000 09:29:49 +0200 (CEST) Subject: cpp superior to ghc . . . In-Reply-To: Message-ID: On Thu, 26 Oct 2000, Koen Claessen wrote: > The problem is really two-fold: bound type variables (like > "a") are not in scope in the body of the function, and local > type declarations are not allowed. GHC and Hugs do solve the first problem by providing a language extension: names of type variables in pattern type signatures and result type signatures are available in their scope. I wish this extension becomes a future standard. Some people say that type variables from ordinary type signatures should be in scope too. -- Marcin 'Qrczak' Kowalczyk From simonpj@microsoft.com Thu Oct 26 18:27:51 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Thu, 26 Oct 2000 10:27:51 -0700 Subject: .net and haskell Message-ID: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmond.corp.microsoft.com> | I was reading some .net stuff (ducks) on microsoft, and they | mentioned haskell as one of the languages someone was | targetting for it. | Anyone know anything about this project? I know of several stabs in this direction, none completed. - There is most of a Java back end for GHC - There are various pieces of a C# back end for GHC, compiling via in intermediate generic OO language called GOO. Nigel Perry is working on this (actively I think) - Don Syme and Reuben Thomas are working on a back end for GHC that compiles to a polymorphically-typed IL for .NET that is Don's baby. A lot of this works, but it's not complete. Maybe others are doing stuff too? It's a pity that there's nothing that's usable yet, but I hope that'll change. Simon From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 11:16:19 2000 From: mhoechsm@techfak.uni-bielefeld.de (=?iso-8859-1?Q?Matthias_H=F6chsmann?=) Date: Fri, 27 Oct 2000 12:16:19 +0200 Subject: class instance with nested types Message-ID: <001801c03ffe$f321de20$0701a8c0@mulder> This is a multi-part message in MIME format. --Boundary_(ID_5jIOsd3oqicabXDXApeVOg) Content-type: text/plain; charset=iso-8859-1 Content-transfer-encoding: 7BIT Hello, I have the following problem: basic datatypes > type Sequence a = [a] > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > type Forest a = Sequence (Tree a) i want to construct a class Xy > class Xy s a where > test :: s a -> a and make an instance for list of characters > instance Xy [] Char where > test [a] = a this works, and an instance for a forest and tried something like this > instance ([] Tree) Char where > test x@(N a xs):txs = a I get illegal type errors. Is it possible to use nested types in a class ? Hope you can help me Matthias --Boundary_(ID_5jIOsd3oqicabXDXApeVOg) Content-type: text/html; charset=iso-8859-1 Content-transfer-encoding: 7BIT
Hello,
 
I have the following problem:
 
basic datatypes
 
> type Sequence a = [a]
> data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> type Forest a = Sequence (Tree a)
 
i want to construct a class Xy
 
> class Xy s a where
>      test :: s a -> a
 
and make an instance for list of characters
 
> instance Xy [] Char where
>      test [a] = a
 
this works, and an instance for a forest and tried something like this
 
> instance  ([] Tree) Char where
> test x@(N a xs):txs = a
 
I get illegal type errors. Is it possible to use nested types in a class ?
 
Hope you can help me
Matthias
 
--Boundary_(ID_5jIOsd3oqicabXDXApeVOg)-- From d95lars@dtek.chalmers.se Fri Oct 27 11:14:58 2000 From: d95lars@dtek.chalmers.se (Lars Lundgren) Date: Fri, 27 Oct 2000 12:14:58 +0200 (MEST) Subject: class instance with nested types In-Reply-To: <001801c03ffe$f321de20$0701a8c0@mulder> Message-ID: On Fri, 27 Oct 2000, Matthias Höchsmann wrote: > Hello, > > I have the following problem: > > basic datatypes > > > type Sequence a = [a] > > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > > type Forest a = Sequence (Tree a) > > i want to construct a class Xy > > > class Xy s a where > > test :: s a -> a > > and make an instance for list of characters > > > instance Xy [] Char where > > test [a] = a > > this works, and an instance for a forest and tried something like this > > > instance ([] Tree) Char where > > test x@(N a xs):txs = a > Don't you mean test (N a xs:txs) = a ? /Lars L From N.Perry@massey.ac.nz Fri Oct 27 11:59:13 2000 From: N.Perry@massey.ac.nz (Nigel Perry) Date: Fri, 27 Oct 2000 12:59:13 +0200 Subject: .net and haskell In-Reply-To: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmon d.corp.microsoft.com> References: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmon d.corp.microsoft.com> Message-ID: At 10:27 am -0700 26/10/00, Simon Peyton-Jones wrote: >| I was reading some .net stuff (ducks) on microsoft, and they >| mentioned haskell as one of the languages someone was >| targetting for it. >| Anyone know anything about this project? > >I know of several stabs in this direction, none completed. > >- There is most of a Java back end for GHC > >- There are various pieces of a C# back end for GHC, > compiling via in intermediate generic OO language > called GOO. Nigel Perry is working on this (actively > I think) This is indeed being worked on. Currently user code compiles (as far as it has been tested) but there is no prelude yet so it doesn't run too well ;-) The code generator was designed for research and supporting scripting, which is a kind way of saying it doesn't produce blazingly fast code. > >- Don Syme and Reuben Thomas are working on a back end for > GHC that compiles to a polymorphically-typed IL for .NET > that is Don's baby. A lot of this works, but it's not complete. > >Maybe others are doing stuff too? It's a pity that there's nothing >that's usable yet, but I hope that'll change. Cheers, Nigel From rossberg@ps.uni-sb.de Fri Oct 27 13:07:37 2000 From: rossberg@ps.uni-sb.de (Andreas Rossberg) Date: Fri, 27 Oct 2000 14:07:37 +0200 Subject: class instance with nested types References: <001801c03ffe$f321de20$0701a8c0@mulder> Message-ID: <39F97009.9C9BB220@ps.uni-sb.de> Matthias Höchsmann wrote: > > > type Sequence a = [a] > > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > > type Forest a = Sequence (Tree a) > > i want to construct a class Xy > > > class Xy s a where > > test :: s a -> a > > [...] > > > instance ([] Tree) Char where > > test x@(N a xs):txs = a To make it syntactically correct this should at least be something like > instance Xy ([] Tree) Char where > test (N a xs:txs) = a But the real problem is in the expression ([] Tree), which is the same as writing [Tree]. This is not a legal type expression, since Tree is a type constructor, not a ground type, so you cannot apply it to the list constructor. What you are trying to say is probably something like this: > instance Xy (\a . [Tree a]) Char -- not Haskell But unfortunately there are no lambdas on the type level - they would render the type system undecidable. For the same reason it is not allowed to use a type synonym in an instance declaration: > instance Xy Forest Char -- illegal The only thing you can do is turning Forest into a data type: > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > data Forest a = Forest [Tree a] > instance Xy Forest Char where > test (Forest (N a xs:txs)) = a HTH, - Andreas -- Andreas Rossberg, rossberg@ps.uni-sb.de :: be declarative. be functional. just be. :: From rossberg@ps.uni-sb.de Fri Oct 27 13:12:45 2000 From: rossberg@ps.uni-sb.de (Andreas Rossberg) Date: Fri, 27 Oct 2000 14:12:45 +0200 Subject: class instance with nested types References: <001801c03ffe$f321de20$0701a8c0@mulder> <39F97009.9C9BB220@ps.uni-sb.de> Message-ID: <39F9713D.C0581888@ps.uni-sb.de> I mumbled: > > This is not a legal type expression, since Tree is a > type constructor, not a ground type, so you cannot apply it to the list > constructor. The other way round, of course: you cannot apply the list constructor to it. - Andreas -- Andreas Rossberg, rossberg@ps.uni-sb.de :: be declarative. be functional. just be. :: From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 14:25:00 2000 From: mhoechsm@techfak.uni-bielefeld.de (=?iso-8859-1?Q?Matthias_H=F6chsmann?=) Date: Fri, 27 Oct 2000 15:25:00 +0200 Subject: class instance with nested types References: Message-ID: <006201c04019$69f81540$0701a8c0@mulder> Yes, I wanted to type it like you do. But anyway, i fixed the problem following Andreas Rossbergs suggestion. Matthias > > Don't you mean > > test (N a xs:txs) = a > > ? > > /Lars L > > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell From jeff@galconn.com Fri Oct 27 16:10:29 2000 From: jeff@galconn.com (Jeffrey R. Lewis) Date: Fri, 27 Oct 2000 08:10:29 -0700 Subject: Overloaded function and implicit parameter passing References: <20001023102235.A11238@urano.iceb.ufop.br> Message-ID: <39F99AE5.8A60CAF5@galconn.com> José Romildo Malaquias wrote: > Hi. > > While experimenting with the implicit parameter > extension to Haskell 98, implemented in GHC 4.08.1 > and latest Hugs, I came accross a difference among > those implementations regarding overloading functions > with implicit parameters. > > As a test consider the program > > ------------------------- cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > ------------------------- cut here > > Hugs accepts this program and outputs 145, as expected. > But GHC 4.08.1 refuses to compile it, emitting the > message > > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 > In the first argument of `+', namely `env_rJX' > In the right-hand side of an equation for `f': env_rJX + x > > Compilation had errors > > Would anybody comment on what is going on with GHC? > > I am willing to use implicit parameters in the > software I am developing, but I have the need > to overload functions with implicit parameters. > While Hugs is good for development, its performance > may rule it out when the final product is ready. > So I will need a good Haskell compiler to compile > my system. > > Any comments? Certainly a bug. I'll look at it when I get a chance. --Jeff From romildo@urano.iceb.ufop.br Fri Oct 27 17:41:19 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Fri, 27 Oct 2000 14:41:19 -0200 Subject: Passing an environment around In-Reply-To: <39F9A83C.311C016A@galconn.com>; from jeff@galconn.com on Fri, Oct 27, 2000 at 09:07:24AM -0700 References: <20001021064840.A19051@urano.iceb.ufop.br> <39F9A83C.311C016A@galconn.com> Message-ID: <20001027144119.A20783@urano.iceb.ufop.br> On Fri, Oct 27, 2000 at 09:07:24AM -0700, Jeffrey R. Lewis wrote: > José Romildo Malaquias wrote: > > > On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote: > > > Indeed Fran behaviors are like your alternative #1 (function passing), and > > > hence sharing loss is a concern. Simon PJ is right that I have a paper > > > discussing this issue and some others. See "Functional Implementations of > > > Continuous Modeled Animation" on my pubs page > > > (http://research.microsoft.com/~conal/papers). > > > > > > About alternative #2 (implicit arguments), would it help? Does it eliminate > > > the non-memoized redundant function applications, or just hide them? For > > > Fran, Erik Meijer suggested implicit functions to me a couple of years ago. > > > I hadn't thought of it, and it did indeed seem to be attractive at first as > > > a way to eliminate the need for overloading in Fran. However, the (Time -> > > > a) representation of Fran behaviors is not really viable, so I wouldn't > > > merely want to hide that representation behind implicit arguments. > > > > It seems that implicit parameters does not eliminate redundant function > > applications, as Conal Elliott has commented. Reading the paper > > > > Implicit Parameters: Dynamic Scoping with Static Types > > Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury > > http://www.cse.ogi.edu/~jlewis/ > > > > (especially section 5.1) I got this impression. I would like to hear > > from others as well, as I had some difficulties with the paper. > > I am sorry you had difficulties! The difficulties I had is basicaly due to my lack of solid knowledge on type theory and semantic formalisms. Not that the paper was badly written. > Yes, as implemented using the dictionary > translation, implicit parameterization can lead to loss of sharing, exactly in > the same way that overloading (and HOF in general) can lead to loss of sharing. > > However, I can imagine that a compiler might chose to implement implicit > parameters more like dynamic variables in lisp. Each implicit param essentially > becomes a global variable, implemented as a stack of values - the top of the > stack is the value currently in scope. This would avoid the sharing problem > nicely. > > --Jeff I suppose your implementation of implicit parameterization in GHC and Hugs uses the dictionary translation, right? Would an alternative implementation based on a stack of values be viable and even done? Does it have serious drawbacks when compared with the dictionary translation technique? Thanks. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From dublins@home.com Sun Oct 29 18:55:51 2000 From: dublins@home.com (S Dublin) Date: Sun, 29 Oct 2000 10:55:51 -0800 Subject: Message-ID: <20001029185558.PTNY2380.femail1.sdc1.sfba.home.com@[65.3.159.89]> From lmagnani@cc.gatech.edu Sun Oct 29 16:08:27 2000 From: lmagnani@cc.gatech.edu (Lorenzo Magnani) Date: Sun, 29 Oct 2000 10:08:27 -0600 Subject: MBR'01 Conference Message-ID: <39FC4B7B.6BF0445A@cc.gatech.edu> Please accept our apologies if you receive multiple copies of this call If you want to receive updated information please send your complete address Last updated October 29, 2000 ********************************************************************** MODEL-BASED REASONING: SCIENTIFIC DISCOVERY, TECHNOLOGICAL INNOVATION, VALUES (MBR'01), Pavia, Italy, May 17-19, 2001. ********************************************************************** Up-to date information on the conference will be found at http://philos.unipv.it/courses/progra1.html or http://www.unipv.it/webphilos_lab/courses/progra1.html ********************************************************************** GENERAL INFORMATION From Thursday 17 to Saturday 19 May 2001 (three days) the International Conference "MODEL-BASED REASONING. SCIENTIFIC DISCOVERY, TECNOLOGICAL INNOVATION, VALUES" will be held at the University of Pavia (near Milan, Italy). PROGRAM The conference will deal with the logical, epistemological, and cognitive aspects of modeling practices employed in scientific discovery and technological innovation, including computational models of such practices. Abduction is widely recognized as a significant reasoning process in discovery whose features are in need of explication. We will solicit papers that examine various forms of model-based reasoning, such as analogical and visual modeling, from philosophical, historical, sociological, psychological, or computational perspectives. We also plan to address the problem of model-based reasoning in ethics reasoning, especially pertaining to science and technology. RELEVANT RESEARCH AREAS We shall call for papers that cover topics from the following list: - abduction - analogical reasoning - causal and counterfactual reasoning in model construction - computational models of model-based reasoning and scientific reasoning - conceptual combination and theory formation - hypothetical and explanatory reasoning - logical analyses that may contribute to our understanding of the issues in model-based reasoning - model-based reasoning in ethics - models and manipulative reasoning - models and technological innovation - thought experimenting - visual, spatial, imagistic modeling, reasoning, and simulation SUBMISSIONS OF PAPERS All submitted papers will be carefully refereed. The precise format of the conference will be fixed after we have an idea of the number of accepted papers. We are thinking in terms of presentations of 40 and 20 minutes. The funding is Italian and US, but we are also looking elsewhere for further financing (and would appreciate any suggestions). A selected subset will be invited for inclusion (subject to refereeing) in a book which will constitute an advanced handbook for scientists and researchers. The book will be published by an international publishing house. Moreover another selected subset will be invited for inclusion (subject to refereeing) in special issues of suitable international Journals. FORMAT Authors must submit three printed copies and an electronic version - formatted in Microsoft Word, RTF, PDF, or Postcript format - of an extended abstract (about 1000 words) not later than November 30, 2000. Please send electronically the extended abstract to the program chair at the address lmagnani@cc.gatech.edu in case of problem with the above address please use lorenzo@philos.unipv.it or lmagnaniusa@netscape.net REGISTRATION AND FURTHER INFORMATION Registration Fees: Before 15 March 2001: Normal: ITL. 300.000 = appr. US$ 155 (EUR 154.93) (to participate in all the activities of the Conference) Students: Free After 15 March 2001: Normal: ITL. 350.000 = appr. US$ 175 (EUR 180.75) (to participate in all the activities of the Conference) Students: Free METHOD OF PAYMENT AND REGISTRATION DEADLINE: Bank (Swift) Transfer to BANCA REGIONALE EUROPEA S.p.A BRANCH PAVIA - Sede SWIFT BREUITM2 301 Bank Code 06906.11301 Acc. n. 520 Dipartimento di Filosofia indicating CONVEGNO INTERNAZIONALE MBR'01 PLEASE REGISTER by email, fax or air mail (before March 15, 2001) by sending PROGRAM CHAIR first and last name, function, institution, full address, phone, fax and email. For information about paper submission and the program that is not available on the web site, please contact the program chair. IMPORTANT DATES Registration deadline............................15 March 2001 Submission deadline..............................30 Nov 2000 Notification of acceptance.....................28 Feb 2001 Final papers (from those selected for publication) due........30 June 2001 Conference....................................17-19 May 2001 PROGRAM CHAIR Lorenzo MAGNANI School of Public Policy and College of Computing Program in Philosophy, Science, & Technology Georgia Institute of Technology, 685 Cherry Street Atlanta, GA, 30332 - 0345, USA Office: 404-894-0950 & 404-385-0884, Home: 404-875-3566 Fax: 404-385-0504 & 404-894-2970 Email: lorenzo.magnani@cc.gatech.edu Address in Italy: Department of Philosophy and Computational Philosophy Laboratory University of Pavia, Piazza Botta 6, 27100 Pavia, Italy Office: +39-0382-506283, Home: +39-0383-371067 Fax: +39-0382-23215 Email: lorenzo@philos.unipv.it PROGRAM CO-CHAIR Nancy J. NERSESSIAN (Program Co-Chair) Program in Cognitive Science School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, USA Email: nancyn@cc.gatech.edu PROGRAM CO-CHAIR Kenneth J. KNOESPEL (Program Co-Chair) School of History, Technology, and Society, and Program in Cognitive Science Georgia Institute of Technology, Atlanta, USA Email: kenneth.knoespel@hts.gatech.edu PROGRAM COMMITTEE - Ann Bostrom, School of Public Policy, Georgia Institute of Technology, Atlanta, GA, USA - Elena Gagliasso, Department of Philosophical and Epistemological Studies, University of Rome La Sapienza, Rome, ITALY - Dedre Gentner, Psychology Department, Northwestern University, Evanston, IL 60208, USA - Ronald N. Giere, Department of Philosophy, University of Minnesota, MN, USA - Mark L. Johnson, Department of Philosophy, 1295 University of Oregon, Eugene, OR, USA - Kenneth Knoespel, School of History, Technology, and Society, Georgia Institute of Technology, Atlanta, GA, USA - Lorenzo Magnani, Department of Philosophy, University of Pavia, Pavia, ITALY and School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, GA, USA - Pat Langley, Adaptive Systems Group, DaimlerChrysler Research & Technology Center, Palo Alto, CA, USA - Nancy J. Nersessian, School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, GA, USA - Brian Norton, School of Public Policy, Georgia Institute of Technology, Atlanta, GA, USA - Claudio Pizzi, Department of Philosophy and Social Sciences, University of Siena, Siena, ITALY - Mario Stefanelli, Department of Computer Science, University of Pavia, Pavia, ITALY - Paul Thagard, Department of Philosophy, University of Waterloo, Waterloo, CANADA - Ryan D. Tweney, Bowling Green State University, Bowling Green, OH, USA - Stella Vosniadou, Department of Philosophy and History of Science, Brain and Cognitive Science Division, National and Capodistrian University of Athens, Athens, GREECE. LOCAL ORGANIZING COMMITTEE Riccardo Dossena (riki.dox@libero), Elena Gandini (elegand@yahoo.com), Rosella Gennari (gennari@hum.uva.nl), Lorenzo Magnani (lmagnani@cc.gatech.edu), Massimo Manganaro (triskel@worldonline.it), Stefania Pernice (stepernice@libero.it), Matteo Piazza (pimat@yahoo.com), Giulio Poletti (philosophia@libero.it) Stefano Rini (s.rini@philos.unipv.it), Andrea Venturi (aventuri@philos.unipv.,it) (Department of Philosophy, University of Pavia, Pavia, Italy), Mario Stefanelli (mstefa@ipvstefa.unipv.it) (Department of Computer Science, University of Pavia, Pavia, Italy). IMPORTANT ADDRESSES LORENZO MAGNANI (Conference Chair) School of Public Policy and College of Computing Program in Philosophy, Science, & Technology Georgia Institute of Technology, 685 Cherry Street Atlanta, GA, 30332 - 0345, USA Office: 404-894-9050 & 404-385-0884, Home: 404-875-3566 Fax: 404-385-0504 & 404-894-2970 Email: lorenzo.magnani@cc.gatech.edu Address in Italy: Department of Philosophy and Computational Philosophy Laboratory University of Pavia, Piazza Botta 6, 27100 Pavia, Italy Office: +39-0382-506283, Home: +39-0383-371067 Fax: +39-0382-23215 Email: lorenzo@philos.unipv.it CONFERENCE SITE: Collegio Ghislieri, Piazza Ghislieri, 27100 PAVIA, Italy, phone +39 0382 22044. The Conference is sponsored by UNIVERSITY OF PAVIA, ITALY GEORGIA INSTITUTE OF TECHNOLOGY, ATLANTA, GA, USA UNIVERSITY OF SIENA, ITALY UNIVERSITY OF ROME "LA SAPIENZA", ITALY, MURST (Ministero dell'Università e della Ricerca Scientifica e Tecnologica), ITALY, CARIPLO (CASSA DI RISPARMIO DELLE PROVINCIE LOMBARDE, MILAN, ITALY) HOW TO REACH PAVIA LINATE Airport: People arriving by plane at LINATE should take the bus to the CENTRAL STATION of Milan (cf below fron this Station to Pavia). In LINATE it could be convenient to take a Taxi because the airport is close to the center of Milan. Moreover, The bus company SGEA offers six runs from LINATE to Pavia at 9.00, 10.00, 12.00 AM and 2.00, 5.00, 8.30 PM. The last stop is Pavia, near the station (see again our updated web page for possible alterations of this time-table) (from Pavia to LINATE six runs at 5,00, 7.45, 10.00 AM, 1.00, 4.00, 6.00 PM) (one hour trip). In Pavia there is only one station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. MALPENSA 2000 and OLD MALPENSA Airports (usually people arrive to Malpensa 2000 and not to OLD MALPENSA): People arriving by plane at MALPENSA 2000 (also called MALPENSA 2000 Terminal 1) or at "old" MALPENSA (now called MALPENSA NORTH but also called Malpensa 2000 Terminal 2) should take the bus to the CENTRAL STATION of Milan. There is also a bus AND A TRAIN from Malpensa 2000 to the NORTH STATION (Piazzale Cadorna) of Milan, in this case from NORTH Station you will have to take the underground MM1 to the Central Station: trains to Pavia leave from Central station). Moreover, the bus company SGEA offers four runs from MALPENSA 2000 to Pavia at 9.00 AM, 1:30 PM, 5.00 PM, and 9:30 PM - from Malpensa North (OLD Malpensa or Malpensa 2000 Terminal 2 5 munutes later) (from Pavia to MALPENSA 2000 and to OLD MALPENSA four runs at 7.00 AM, 11:00 AM, 3.15 PM, and 7:00 PM) (one hour and half trip). The last stop is Pavia, near the station (see again our updated web page for possible alterations of this time-table) In Pavia there is only one station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. There are trains from MILAN (Central Station) to PAVIA and vice Versa about every an hour (routes: MILAN-GENOVA; MILAN-VENTIMIGLIA; MILAN-LA SPEZIA; MILAN-SAVONA; MILAN-SESTRI LEVANTE; MILAN-IMPERIA; MILAN-ALBENGA; Pavia is the first stop only if the train is not slow, that is, if it is not, in ITALIAN, "L", locale). In Pavia there is only one rail station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. ACCOMMODATION The WEB site of the Tourist Office is http://www.systemy.it/pavia/home.html (new! sorry, only in Italian). The email address is info@apt.pv.it. When available you will find the whole list of hotels and other information concerning Pavia and its history. See also http://www.itwg.com/ct_00036.asp. In case of accommodation problems remember we will have at our disposal some rooms at special "conference rates" in the Colleges of the University. For further information please contact the Program Chair. As the the conferences dates are very close to summer holidays we recommend making your reservations as early as possible and before March 31, 2000 at the latest. ALL ACCOMMODATIONS (EXCEPT FOR INVITED SPEAKERS) WILL BE PROCESSED BY: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy Phone: +39-0382-539565 Fax: +39-0382-539572 +39-0382-539504 email (only to request information): aloha@buonviaggio.it (cut here) ********************************************************************** ACCOMMODATION FORM - MBR'01 ---------------------------------------------------------------------- TO BE FAXED: +39-0382-539572 +39-0382-539504 OR MAILED: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy email (only to request information): aloha@buonviaggio.it ---------------------------------------------------------------------- FILL IN CAPITAL LETTERS, PLEASE LAST NAME:___________________FIRST NAME:_____________Prof./Dr./Mr./Ms. AFFILIATION/UNIVERSITY/DEPT.__________________________________________ STREET:_______________________________________________________________ TOWN:___________________________CODE:_____________COUNTRY:____________ PHONE:__________________FAX:__________________E-MAIL:_________________ TYPE OF TRAVELLING:__________________DATE OF ARRIVAL:_________________ DATE OF DEPARTURE:___________________NUMBER OF NIGHTS:________________ CREDIT CARD NUMBER AND TYPE__________________________ EXPIRATION_____________ (you can also pay by bank transfer and postal order, please see below) ACCOMMODATION INCL. BREAKFAST SINGLE ROOM+BATH. / DOUBLE ROOM+BATH. ***HOTEL EXCELSIOR, Piazza Stazione, PAVIA LIT. 100.000 / LIT. 150.000 ______________ (EUR. 51.64 / EUR. 77.46) ****HOTEL ARISTON, Via Scopoli, PAVIA LIT. 130.000 / LIT. 190.000 +_____________ (EUR. 67.13 / EUR. 98.12) ****HOTEL MODERNO, Viale V. Emanuele, PAVIA LIT. 170.000 / LIT. 230.000 +_____________ (EUR. 87.79 / EUR. 118.78) RESERVATION CHARGE LIT. 25.000 +_______ (EUR. 12.91) TOTAL AMOUNT: =_____________ ACCOMMODATION DEPOSIT: ONE NIGHT LIT......... - _____________ (EUR) ACCOMMODATION BALANCE: LIT......... =_____________ (EUR)........ Hotel Excelsior (from the station walk east) Hotel Moderno (from the station walk north) To reach Hotel Ariston take the bus n. 3 or taxi. ____________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *CREDIT CARD* BEFORE *15 MARCH 2001* TO: FAX: +39-0382-539572 +39-0382-539504 MAIL ADDRESS: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy email (only to request information): aloha@buonviaggio.it DATE OF PAYMENT____________YOUR SIGNATURE____________________ ________________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *BANK TRANSFER* BEFORE *15 MARCH 2001* (fax or mail also a copy of the bank transfer) TO: BANCA REGIONALE EUROPEA S.p.A.BRANCH PAVIA - SedeSWIFT BREUITM2 301Bank Code 6906.11301 Agenzia Viaggi ALOHATOUR S.r.l. Acc.n 19952/4 DATE OF PAYMENT____________YOUR SIGNATURE___________________ ________________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *POSTAL ORDER* BEFORE* 15 MARCH 2001* (fax or mail also a copy of the postal receipt) TO: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy DATE OF PAYMENT______________________YOUR SIGNATURE______________________ _________________________________________________________________________ ALHOATOUR WILL MAIL OR FAX YOU THE RESERVATION VOUCHER ALOHATOUR WILL SATISFY THE REQUESTS AS FAR AS POSSIBLE. IF NOT POSSIBLE, ANOTHER SIMILAR ACCOMMODATION WILL BE ARRANGED. From venneri@dsi.unifi.it Mon Oct 9 19:19:30 2000 From: venneri@dsi.unifi.it (b.venneri) Date: Mon, 9 Oct 2000 14:19:30 -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. Affiliated workshops will be scheduled from September 2 through September 8. Researchers and practitioners are invited to submit workshop proposals, that may be sent to the PLI 2001 Workshop Chair Betti Venneri, venneri@dsi.unifi.it, by e-mail (Postscript, Pdf, ASCII) 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), 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. 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. web page: http://music.dsi.unifi.it/pli01/wkshops From fldrsimonmar@microsoft.com Mon Oct 9 10:54:52 2000 From: fldrsimonmar@microsoft.com (Simon Marlow) Date: Mon, 9 Oct 2000 02:54:52 -0700 Subject: Mailing list software changing Message-ID: <9584A4A864BD8548932F2F88EB30D1C6115734@TVP-MSG-01.europe.corp.microsoft.com> Dear Haskell & Haskell-cafe, At haskell.org we're migrating the mailing lists from majordomo (which is somewhat old and clunky) to Mailman, which will amongst other things make my life a lot easier, provide better archives, add digest support and allow subscription/unsubscription via a web interface. You should all receive a notification shortly about subscription to the new lists. Unfortunately it seems we have to do this, because the confirmation contains the password for accessing & modifying your personal subscription details on the web. If you *don't* receive a confirmation in the next 24 hours, please let me know. Heres hoping everything goes smoothly, and once again I apologise for the extra spam in your mailbox. Cheers, Simon From mpj@cse.ogi.edu Tue Oct 10 03:26:00 2000 From: mpj@cse.ogi.edu (Mark P Jones) Date: Mon, 9 Oct 2000 19:26:00 -0700 Subject: type class In-Reply-To: <39D38A5F.F01D7437@yale.edu> Message-ID: Hi Zhanyong, | In Haskell, instances of a type class can only be well-formed type | constructors ... | Note there is no type constructor abstraction. |=20 | In practice, I found this rule too restrictive. There are good reasons for the restrictions that were alluded to in my constructor classes paper, and again in Typing Haskell in Haskell. Some text from emails written when this topic came up previously is attached to the end of this message. Actually, the first part of the attached email deals with a different problem (making Set an instance of Monad), but since that also came up for discussion again quite recently, I don't think it will hurt to include it again here. | How about extending TC with a branch for abstraction: |=20 | TC ::=3D ... | | /\a. TC -- abstraction |=20 | This is too powerful and will get out of control -- we surely don't = want | to give TC the full power of lambda-calculus. So let's impose a | restriction: in /\a.TC, a must occur free in TC *exactly once*. This | way, abstraction can only be used to specify with respect to which | argument a partial application is. (or I think so -- I haven't tried = to | prove it.) My instinct (which perhaps somebody will prove incorrect) is that this = will not help. Suppose, for example, that you needed to unify ([a],[b]) with = f c as part of the type inference process. How would you solve this = problem? Alas, there are several different, and incompatible ways: ([a], [b]) =3D (/\a. ([a],[b])) a =3D (/\b. ([a],[b])) b =3D (/\c. (c, [b])) [a] =3D (/\d. ([a], d)) [b] =3D (/\e. e) ([a], [b]) Note that the /\-terms in each of these examples satisfies your = restriction. So I don't think you'll be able to obtain most general unifiers or = principal types with this restriction. In my opinion, Dale Miller's work on Higher-order patterns (introduced, = I think in about 1991, but I don't have references) would probably be the best = starting point for serious experimentation in this area. Hope this helps, Mark -- From the archives: = ------------------------------------------------------- Hi Michael, | "...type synonyms must be fully applied". I think the above | example is a valid objection to this. I'll append some text that I wrote on a previous occasion when somebody asked why type synonyms couldn't be partially applied. I hope that it will help to explain why the restriction is not easy to lift, however desirable it might be. The example there was a little different, but I'm sure that you'll see the correspondence. | The other example of something that I want to declare as a monad, but | which I can not is this: Consider a type of collection of some sort = that | requires the types of the elements to be instances of some specific = class. This too is a problem that has come up quite a few times in the past. As yet, I'm not sure that anyone has a definitive answer for it either, although the work that John Hughes presented at the Haskell workshop on Restricted Datatypes is perhaps the closest that anyone has come so far. A general problem here is that there are differences between = conventional mathematics---where you can have sets of any type---and the mathematics = of programming languages---where interesting set datatypes can only be constructed on types whose elements have, at least, an equality. In = Haskell terms, mathematics has an equality function of type: forall a. a -> a -> = Bool; the same operator is available to mathematicians who reason about = Haskell programs. But Haskell programmers have to make do with a more = restrictive operator of type forall a. Eq a =3D> a -> a -> Bool. (Which is not = actually an equality operator at all when you look at what's really going on; = it's just a kind of identity function or projection!) All the best, Mark =20 Here's the text I promised: | I'd like to use monadic code on the following type | type IOF b a =3D b -> IO a | The following seemed reasonable enough: | instance Monad (IOF b) where ... | But Hugs and GHC both object ... The example is rejected because type synonyms can only be used if a full complement of arguments has been given. There are at least two kinds of problem that can occur if you relax this restriction, but both are related to unification/matching. Suppose that we allow your definition. And suppose that we also allow: instance Monad ((->) env) where ... which is a perfectly reasonable thing to do (it's the reader monad). Now what should we do when faced with the problem of unifying two type expressions like: m c and b -> IO a ... Haskell unifies these with the substitution: {m +-> ((->) b), c +-> IO a}, but with your instance decl, you might have preferred { m +-> IOF b, c +-> a }. In other words, it's ambiguous, and the choice between these two could change the semantics because you'll end up picking different instances depending on which choice you make. Or consider what you really mean when you write (IOF b) ... my guess is that you're thinking of it as adding a kind of lambda, so that IOF b =3D \a. a -> IO b This is appealing, but also means that we'd need to move up to = higher-order unification which is undecidable and non-unitary. For example, now we could match m c to b -> IO a in all kinds of interesting ways: b -> IO a =3D (\b . b -> IO a) b =3D (\a . b -> IO a) a =3D (\z . b -> z) (IO a) =3D (\z . b -> IO a) Int =3D ... Now we really have ambiguity problems to worry about! Requiring type synonyms to be fully applied --- in effect, telling us that a synonym is nothing more than an abbreviation, and has no other consequences for the semantics --- seems like a nice way to avoid these problems. -------------------------------------------------------------------------= --- From zhanyong.wan@yale.edu Wed Oct 11 14:53:52 2000 From: zhanyong.wan@yale.edu (Zhanyong Wan) Date: Wed, 11 Oct 2000 09:53:52 -0400 Subject: type class References: Message-ID: <39E470F0.4F351EEC@yale.edu> Hi Mark, Thanks for the references you provided! Mark P Jones wrote: > My instinct (which perhaps somebody will prove incorrect) is that this will > not help. Suppose, for example, that you needed to unify ([a],[b]) with f c > as part of the type inference process. How would you solve this problem? > Alas, there are several different, and incompatible ways: > > ([a], [b]) = (/\a. ([a],[b])) a > = (/\b. ([a],[b])) b > = (/\c. (c, [b])) [a] > = (/\d. ([a], d)) [b] > = (/\e. e) ([a], [b]) > > Note that the /\-terms in each of these examples satisfies your restriction. > So I don't think you'll be able to obtain most general unifiers or principal > types with this restriction. Let's put your example into the context of type classes: class T f c where method :: f c Now when we want to use method as a ([a],[b]), ambiguity arises, as you suggested. However, I think this just means we should allow *at most one* of the following instances to be declared: instance T (/\a. ([a],[b])) a instance T (/\b. ([a],[b])) b instance T (/\c. (c, [b])) [a] instance T (/\d. ([a], d)) [b] instance T (/\e. e) ([a], [b]) In other words, the above instances are considered overlapping. ____________________________________________________ | As long as we only have one of these instances | | in the program, there is no ambiguity. | ---------------------------------------------------- I'm sure there must be other ramifications (e.g. maybe now whether two instances are overlapping becomes undecidable -- I haven't thought over it yet), but it seems worth further investigation. -- Zhanyong From senganb@ia.nsc.com Thu Oct 12 21:11:16 2000 From: senganb@ia.nsc.com (Sengan) Date: Thu, 12 Oct 2000 16:11:16 -0400 Subject: How does one find lazyness bottlenecks? Message-ID: <39E61AE4.1D8DACE9@ia.nsc.com> Now that ghc 4.08 has a time profiler, I've been improving a program I wrote over the last year. However now the GC time dominates the execution time (>60%). I can see that my program is not being lazy, but I have no idea why. How can I use profiling (or any other means) to determine where my program is not being sufficiently lazy? Are there papers on such things I could read? Sengan From fjh@cs.mu.oz.au Fri Oct 13 01:49:05 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Fri, 13 Oct 2000 11:49:05 +1100 Subject: How does one find lazyness bottlenecks? In-Reply-To: <39E61AE4.1D8DACE9@ia.nsc.com> References: <39E61AE4.1D8DACE9@ia.nsc.com> Message-ID: <20001013114905.A3316@hg.cs.mu.oz.au> On 12-Oct-2000, Sengan wrote: > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. What makes you think that the GC time is due to insufficient laziness? My first thought is that high GC times may well be due to the opposite, too much laziness. Being lazy means that you create closures to represent unevaluated expressions, and those closures will eventually need to be garbage collected. -- Fergus Henderson | "I have always known that the pursuit WWW: | of excellence is a lethal habit" PGP: finger fjh@128.250.37.3 | -- the last words of T. S. Garp. From chak@cse.unsw.edu.au Fri Oct 13 05:16:48 2000 From: chak@cse.unsw.edu.au (Manuel M. T. Chakravarty) Date: Fri, 13 Oct 2000 15:16:48 +1100 Subject: How does one find lazyness bottlenecks? In-Reply-To: <39E61AE4.1D8DACE9@ia.nsc.com> References: <39E61AE4.1D8DACE9@ia.nsc.com> Message-ID: <20001013151648K.chak@cse.unsw.edu.au> Sengan wrote, > Now that ghc 4.08 has a time profiler, I've been improving a program > I wrote over the last year. However now the GC time dominates the > execution time (>60%). I can see that my program is not being lazy, > but I have no idea why. How can I use profiling (or any other means) > to determine where my program is not being sufficiently lazy? Are there > papers on such things I could read? If GC times dominates, you probably have a space leak. So, you should use space profiling to determine where the leak is. Depending on what kind of program you have, it is often also informative to check the space profiles for different kinds of inputs, as the leak might only occur for certain inputs. Depending on the code exercised by the inputs triggering the leak, you might get a rough idea which parts of your program leak. Cheers, Manuel From sylvan@ravinet.com Fri Oct 13 11:18:26 2000 From: sylvan@ravinet.com (Sylvan Ravinet) Date: Fri, 13 Oct 2000 13:18:26 +0300 (EEST) Subject: Haskell to XSLT? Message-ID: Hello, I was wondering if there are ways to translate Haskell code to XSLT. Any ideas? Thank you for your help, Best regards, -Sylvan -- No, try not. Do, or do not. There's no try. -Yoda Sylvan Ravinet: http://www.ravinet.com/sylvan/contact/ -- This message is Copyright 2000 by Sylvan Ravinet. All rights (and responsibility) reserved. From luti@linkexpress.com.br Fri Oct 13 22:42:24 2000 From: luti@linkexpress.com.br (Luciano Caixeta Moreira) Date: Fri, 13 Oct 2000 18:42:24 -0300 Subject: (no subject) Message-ID: <003e01c0355e$7cb4de40$a8adfcc8@servidor> This is a multi-part message in MIME format. ------=_NextPart_000_0035_01C03545.53E7F560 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable unsubscribe haskell@haskell.org ------=_NextPart_000_0035_01C03545.53E7F560 Content-Type: text/html; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable
unsubscribe haskell@haskell.org
------=_NextPart_000_0035_01C03545.53E7F560-- From romildo@urano.iceb.ufop.br Sat Oct 14 05:38:09 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 02:38:09 -0200 Subject: Haskore and nhc98 Message-ID: <20001014023809.A18261@urano.iceb.ufop.br> Hello. I am just curious whether anybody has already tried Haskore (http://www.haskell.org/haskore/) with the NHC98 Haskell compiler. I am trying to do it, while GHC 4.08.1 is non functional in my RH Linux 7.0 box. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From romildo@urano.iceb.ufop.br Sat Oct 14 06:48:06 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 03:48:06 -0200 Subject: Binary files and NHC98 Message-ID: <20001014034806.A23040@urano.iceb.ufop.br> --wRRV7LY7NUeQGEoC Content-Type: text/plain; charset=iso-8859-1 Content-Disposition: inline Content-Transfer-Encoding: 8bit Hello. In order to experiment with the Binary module distributed with nhc98, I wrote the attached program which writes a binary file and then reads it. When executed, I got an extra byte (8) that I cannot explain: [65,66,67,68,8] Any clues why it appears? Regards, Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil --wRRV7LY7NUeQGEoC Content-Type: text/plain; charset=us-ascii Content-Disposition: attachment; filename="BinaryFile.hs" module Main where import IO (IOMode(ReadMode,WriteMode)) import Binary (openBin,closeBin,getBits,putBits,isEOFBin, BinIOMode(RO,WO),BinLocation(File),BinHandle) -- convert from IOMode to BinIOMode ioModeToBinIOMode :: IOMode -> BinIOMode ioModeToBinIOMode ReadMode = RO ioModeToBinIOMode WriteMode = WO -- open a binary file openBinaryFile :: FilePath -> IOMode -> IO BinHandle openBinaryFile path mode = openBin (File path (ioModeToBinIOMode mode)) -- write a list of integers (8 bits) to binary file writeBinaryFile :: FilePath -> [Int] -> IO () writeBinaryFile fileName xs = do f <- openBinaryFile fileName WriteMode let writeToBin [] = return () writeToBin (x:xs) = do putBits f 8 x writeToBin xs writeToBin xs closeBin f -- read a list of integers (8 bits) from binary file readBinaryFile :: FilePath -> IO [Int] readBinaryFile fileName = do f <- openBinaryFile fileName ReadMode let readFromBin = do eof <- isEOFBin f if eof then return [] else do x <- getBits f 8 xs <- readFromBin return (x:xs) xs <- readFromBin closeBin f return xs -- test the above main = do writeBinaryFile "test.bin" [65,66,67,68] xs <- readBinaryFile "test.bin" putStrLn (show xs) --wRRV7LY7NUeQGEoC-- From romildo@urano.iceb.ufop.br Sat Oct 14 08:49:52 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 14 Oct 2000 05:49:52 -0200 Subject: NHC98 and GHC 4.08.1 differ on monad related functions Message-ID: <20001014054952.A27804@urano.iceb.ufop.br> --4Ckj6UjgE2iN1+kY Content-Type: text/plain; charset=iso-8859-1 Content-Disposition: inline Content-Transfer-Encoding: 8bit Hello. While porting Haskore to NHC98 I got an error I am not understanding. I have attached a test module that shows the error message: $ nhc98 -c Test.hs ==================================== Error after type deriving/checking: No default for Monad.MonadPlus at 7:1.(171,[(2,209)]) No default for Monad.MonadPlus at 6:1.(174,[(2,208)]) GHC 4.08.1 and Hugs98 accepts the code without complaining. Any hints? Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil --4Ckj6UjgE2iN1+kY Content-Type: text/plain; charset=us-ascii Content-Disposition: attachment; filename="Test.hs" module Test where import Monad zeroOrMore, oneOrMore :: MonadPlus m => m a -> m [a] zeroOrMore m = return [] `mplus` oneOrMore m oneOrMore m = do { a <- m; as <- zeroOrMore m; return (a:as) } --4Ckj6UjgE2iN1+kY-- From nikhil@acm.org Mon Oct 16 09:21:39 2000 From: nikhil@acm.org (Rishiyur S. Nikhil) Date: Mon, 16 Oct 2000 01:21:39 -0700 Subject: Haskell puzzle Message-ID: <39EABA93.DAD34B10@mediaone.net> In Haskell, is the following transformation always legal? \x->\y->e transforms to \x y->e After answering this question, please scroll down about 75 lines for a follow-up question. What if the two lambda-bound variables are the same? I.e., the lhs is \x->\x->e Please refer to Section 3.3 of the Haskell 98 Report, para 3 (one line para). From timd@macquarie.com.au Tue Oct 17 02:30:58 2000 From: timd@macquarie.com.au (Timothy Docker) Date: Tue, 17 Oct 2000 12:30:58 +1100 (EST) Subject: Mutually recursive structures Message-ID: <14827.43685.102410.194472@tcc2> The following problem has been taxing me.... I have a list of pairs that I have parsed from a input file, which represent a hiirarchy, where the first element is the name of the object, and the second is the name of the parent if there is one: type ParseOutput = [(String,Maybe String)] I wish to convert this to a list of "objects", where from each object I can navigate to the parent object (if any), or the children (if any): data Obj = Obj { name::String, parent::(Maybe Obj), children::[Obj] } type Result = [Obj] convert:: ParseOutput -> Result In a language with mutable references, this would be a relatively straightforward. I would just create a dictionary mapping from name to Obj, and then iterate over them, filling in the parents and children where appropriate. odict = {} for (name,parent) in parseOutput: odict[name] = Obj() for (name,parent) in parseOutput: if parent: parent = odict[parent] child = odict[name] child.parent = parent parent.children.append( child ) This gives away my background! How can I do this in Haskell? If I don't have mutable references, I figure that I must need to use laziness in some way, perhaps similar to how I would build an infinite structure. A hint or two would be great. Tim From Tom.Pledger@peace.com Tue Oct 17 04:32:13 2000 From: Tom.Pledger@peace.com (Tom Pledger) Date: Tue, 17 Oct 2000 16:32:13 +1300 (NZDT) Subject: Mutually recursive structures In-Reply-To: <14827.43685.102410.194472@tcc2> References: <14827.43685.102410.194472@tcc2> Message-ID: <14827.51261.117517.96548@waytogo.peace.co.nz> Timothy Docker writes: > [...] How can I do this in Haskell? If I don't have mutable > references, I figure that I must need to use laziness in some way, > perhaps similar to how I would build an infinite structure. http://www.mail-archive.com/haskell@haskell.org/msg06321.html I have nothing to add to that explanation, so will conserve bandwidth by From christian@lescher.de Tue Oct 17 20:29:25 2000 From: christian@lescher.de (Christian Lescher) Date: Tue, 17 Oct 2000 20:29:25 +0100 Subject: Haskell function with String arguments in DLL Message-ID: <39ECA895.4681986B@lescher.de> I'm trying to build a DLL with a Haskell function of type String -> String, that should be called from outside (e.g. VBA), but it still doesn't work. I'm afraid I need an example or some kind of 'step by step instruction'. Who can help me? (I use GHC 4.08.1.) Christian From timd@macquarie.com.au Tue Oct 17 22:25:58 2000 From: timd@macquarie.com.au (Timothy Docker) Date: Wed, 18 Oct 2000 08:25:58 +1100 (EST) Subject: Mutually recursive structures In-Reply-To: <14827.51261.117517.96548@waytogo.peace.co.nz> References: <14827.43685.102410.194472@tcc2> <14827.51261.117517.96548@waytogo.peace.co.nz> Message-ID: <14828.49022.234836.837956@tcc2> Tom Pledger writes: > Timothy Docker writes: > > [...] How can I do this in Haskell? If I don't have mutable > > references, I figure that I must need to use laziness in some way, > > perhaps similar to how I would build an infinite structure. > > http://www.mail-archive.com/haskell@haskell.org/msg06321.html > To be honest, I found this code quite confusing, I think because of the way in which a the "tail" needs to be joined back to the "head" in creating a circular data structure. I did eventually come up with a solution that seems straightforward enough, although I have no idea of its efficiency... | type ParseOutput = [(String,Maybe String)] | | data Obj = Obj { oname::String, | oparent::(Maybe Obj), | ochildren::[Obj] } | | convert:: ParseOutput -> [Obj] | convert output = converted | where converted = map mkObj output | mkObj (name,parent) = (Obj name | (fmap (findObj converted) parent) | (filter (hasParentNamed name) converted) ) | | findObj:: [Obj] -> String -> Obj | findObj [] name = error ("No object with name "++name) | findObj (o:os) name | name == (oname o) = o | | otherwise = findObj os name | | hasParentNamed :: String -> Obj -> Bool | hasParentNamed name obj = maybe False ((==name).oname) (oparent obj) | Thanks for the pointer. Tim From koen@cs.chalmers.se Wed Oct 18 11:57:56 2000 From: koen@cs.chalmers.se (Koen Claessen) Date: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST) Subject: Num class Message-ID: Hi all, For years I have wondered why the Num class has the Eq class and the Show class as super classes. Because of this, I cannot make functions an instance of Num (becuase they are not in Eq or Show). Or a datatype respresenting an infinite amount of digits (because Eq would not make any sense). Now I have found out the reason! However, it does not make me happy, it makes me even more sad. It is of the defaulting mechanism of course! The defaulting mechanism works as follows: If there is an unresolved overloading error on a type variable a, which has as an *only* constraint (Num a), then we take a to be the suitable default. If Show were not a super class of Num, the following program would generate an error: main = print 42 If Eq were not a super class, the following program would not work: main = print (if 42 == 42 then "koe" else "apa") These programs are all fixed by inserting Show and Eq as super classes of Num. So that one does not even notice! Until now. I am interfacing to an external library that uses double-precision floating points internally for all numbers. This is to be as general as possible. However, I know that when I put for example an Integer in, I get one out too. Thus, I want to give a Haskell interface that can deal with this by any numeric type. So I define a type class: class Num a => Number a where convertToDouble :: a -> Double convertFromDouble :: Double -> a (somehow the Haskell numerical hierarchy does not even let me define general functions that do this! -- but that is besides the point.) instance Number Int instance Number Integer instance Number Float instance Number Double ... All my library functions now have the shape: libraryFunction :: Number a => ... a ... Where as actually: primLibraryFunction :: ... Double ... And now the bad thing... When I use "libraryFunction" on a numeric constant, such as 42, I get the error: ERROR "library.hs" (line 8): Unresolved overloading *** Binding : main *** Outstanding context : Number b This is really annoying, and it is not clear why the default mechanism works this way. So here are my questions. Why does the default mechanism have this restriction? I know that the default mechanism is already broken (some desirable properties are destroyed) -- what properties will be broken by lifting this restriction? /Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden From p.turner@computer.org Wed Oct 18 12:37:38 2000 From: p.turner@computer.org (Scott Turner) Date: Wed, 18 Oct 2000 07:37:38 -0400 Subject: pronunciation of >>= Message-ID: <3.0.5.32.20001018073738.009a6750@mail.billygoat.org> Is there a common way to pronounce ">>=" in discussions or when teaching? I've learned all my Haskell from printed/visual documents. -- Scott Turner p.turner@computer.org http://www.ma.ultranet.com/~pkturner From d95lars@dtek.chalmers.se Wed Oct 18 12:43:34 2000 From: d95lars@dtek.chalmers.se (Lars Lundgren) Date: Wed, 18 Oct 2000 13:43:34 +0200 (MEST) Subject: pronunciation of >>= In-Reply-To: <3.0.5.32.20001018073738.009a6750@mail.billygoat.org> Message-ID: On Wed, 18 Oct 2000, Scott Turner wrote: > Is there a common way to pronounce ">>=" in discussions or when teaching? > I've learned all my Haskell from printed/visual documents. How about 'bind'? and ">>" => 'then'. /Lars L From qrczak@knm.org.pl Wed Oct 18 21:02:18 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 18 Oct 2000 20:02:18 GMT Subject: Num class References: Message-ID: Wed, 18 Oct 2000 12:57:56 +0200 (MET DST), Koen Claessen pisze: > The defaulting mechanism works as follows: If there is an unresolved > overloading error on a type variable a, which has as an *only* > constraint (Num a), then we take a to be the suitable default. This is not what the Haskell 98 Report says. Section 4.3.4: "In situations where an ambiguous type is discovered, an ambiguous type variable is defaultable if at least one of its classes is a numeric class (that is, Num or a subclass of Num) and if all of its classes are defined in the Prelude or a standard library (Figures 6--7 show the numeric classes, and Figure 5 shows the classes defined in the Prelude.)" I see no good reason for Show superclass of Num. Eq makes a little more sense, but could be dropped too. It would be inferred separately when a numeric literal is used in a pattern. I agree that the default mechanism is ugly, and that at least the restriction about classes defined in standard libraries should be removed. Clean has per-class defaults. I don't know how conflicting defaults coming from different class constraints should be solved, or what about multiparameter classes, and whether extending the defaulting mechanism is a good idea at all. But since we don't have anything better... -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK From mpj@cse.ogi.edu Wed Oct 18 22:46:24 2000 From: mpj@cse.ogi.edu (Mark P Jones) Date: Wed, 18 Oct 2000 14:46:24 -0700 Subject: Num class In-Reply-To: Message-ID: This is a multi-part message in MIME format. ------=_NextPart_000_0001_01C03912.2FCECB10 Content-Type: text/plain; charset="iso-8859-1" Content-Transfer-Encoding: quoted-printable Hi Koen, | If Show were not a super class of Num, the following program | would generate an error: |=20 | main =3D print 42 |=20 | If Eq were not a super class, the following program would | not work: |=20 | main =3D print (if 42 =3D=3D 42 then "koe" else "apa") |=20 | These programs are all fixed by inserting Show and Eq as | super classes of Num. So that one does not even notice! Your claims are incorrect. Both of these examples type check without any errors, and regardless of whether Show and Eq are included as superclasses of Num. It is easy to verify this using "Typing Haskell in Haskell" (http://www.cse.ogi.edu/~mpj/thih); I'll attach the script that I used for this below. Put this in the same directory as all the other .hs files and load it into Hugs. Then edit StdPrel.hs to remove the superclasses of cNum, (replace [cEq, cShow] with []), and it will still work. | For years I have wondered why the Num class has the Eq class | and the Show class as super classes. |=20 | Because of this, I cannot make functions an instance of Num | (because they are not in Eq or Show). Or a datatype | representing an infinite amount of digits (because Eq would | not make any sense). |=20 | Now I have found out the reason! I don't think you have. I do not know the reason either, but I suspect that it is largely historical; when Haskell was first designed, the only types that people wanted to put in Num were also equality and showable types. By making Eq and Show superclasses of Num, types could sometimes be stated more concisely, writing things like (Num a) =3D> ... instead of (Num a, Eq a, Show a) =3D> ... In the past ten years since the Haskell class hierarchy was, more or less, fixed, we've seen several examples of types that don't quite fit (Like functions, computable reals, etc. which might make sense in Num but not in Eq). A natural conclusion is that several of the superclass relations between classes should be removed. But realize that there is an unavoidable compromise here: generality versus the convenience of shorter types. I suggest that there is no point on the spectrum that would keep everybody happy all the time. | It is of the defaulting mechanism of course! | ... Defaulting is a red herring in trying to understand why Show and Eq are superclasses of Num. Marcin has already pointed out that your description of the Haskell defaulting mechanism is not correct by quoting from the Haskell report. You can find another description, again based on the report, in the thih paper. | So I define a type class: | class Num a =3D> Number a where | convertToDouble :: a -> Double | convertFromDouble :: Double -> a |...=20 | All my library functions now have the shape: | libraryFunction :: Number a =3D> ... a ... | ... | And now the bad thing... When I use "libraryFunction" on a | numeric constant, such as 42, I get the error: |=20 | ERROR "library.hs" (line 8): Unresolved overloading | *** Binding : main | *** Outstanding context : Number b |=20 | So here are my questions. Why does the default mechanism | have this restriction? I know that the default mechanism is | already broken (some desirable properties are destroyed) -- | what properties will be broken by lifting this restriction? Defaulting only kicks in if (a) at least one class is numeric, and (b) all classes are standard. Number is not a standard class (you just defined it yourself), so defaulting will not apply. Defaulting was designed to work in this way so that (i) it would catch and deal with the most common problems occurring with numeric literals, and (ii) it would not be used too often; defaulting is in general undesirable because it can silently change the semantics. Again, defaulting is an example of a compromise in the design of Haskell. Ideally, you'd do without it all together, but if you went that way, you'd end up having to write more type information in your programs. And again, I don't suppose there is a universally satisfactory point on this spectrum. All the best, Mark -------------------------------------------------------------------------= --- mpj@cse.ogi.edu Pacific Software Research Center, Oregon Graduate = Institute Want to do a PhD or PostDoc? Interested in joining PacSoft? Let us = know! ------=_NextPart_000_0001_01C03912.2FCECB10 Content-Type: text/plain; name="SourceFortyTwo.hs" Content-Transfer-Encoding: quoted-printable Content-Disposition: attachment; filename="SourceFortyTwo.hs" module SourceFortyTwo where import Testbed import HaskellPrims import HaskellPrelude -------------------------------------------------------------------------= ---- -- Test Framework: main :: IO () main =3D test imports fortyTwo saveList :: IO () saveList =3D save "FortyTwo" imports fortyTwo imports :: [Assump] imports =3D defnsHaskellPrims ++ defnsHaskellPrelude -------------------------------------------------------------------------= ---- -- Test Program: fortyTwo :: [BindGroup] fortyTwo =3D map toBg [[("main", Nothing, [([], ap [evar "print", elit (LitInt 42)])])], [("main'", Nothing, [([], ap [evar "print",=20 eif (ap [econst eqMfun, elit (LitInt 42), elit (LitInt = 42)]) (elit (LitStr "koe")) (elit (LitStr "apa"))])])]] -------------------------------------------------------------------------= ---- ------=_NextPart_000_0001_01C03912.2FCECB10-- From senganb@ia.nsc.com Thu Oct 19 01:31:02 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 18:31:02 -0600 (MDT) Subject: mapM/concatMapM Message-ID: <200010190031.SAA16141@ia.nsc.com> mapM seems to be a memory hog (and thus also concatMapM). In the following eg: > main = mapM print ([1..102400] :: [Integer]) memory usage climbs to 1.6M with ghc and needs -K20M, whereas with > main = print ([1..102400] :: [Integer]) memory usage is only 1300 bytes. I instrumented mapM: > main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) > mapM2 :: Monad m => (a -> m b) -> [a] -> m [b] > mapM2 f [] = return [] > mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x -> > _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs -> > _scc_ "f" return (x:xs))) and found that a and b were the worst heap users (according to hp2ps), ie the two >>='s Why is this so? What can I do about it? My code uses mapM pretty extensively, and I think its suffering from this problem. I notice that ghc does not seem to use mapM except in 2 modules. Another odd thing is that hp2ps says that a & b are the culprits, but the -p and -px options say p is. Why? Sengan From jenglish@flightlab.com Thu Oct 19 03:03:05 2000 From: jenglish@flightlab.com (Joe English) Date: Wed, 18 Oct 2000 19:03:05 -0700 Subject: mapM/concatMapM In-Reply-To: <200010190031.SAA16141@ia.nsc.com> References: <200010190031.SAA16141@ia.nsc.com> Message-ID: <200010190203.TAA16483@dragon.flightlab.com> senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > mapM seems to be a memory hog (and thus also concatMapM). > In the following eg: > > > main = mapM print ([1..102400] :: [Integer]) > > memory usage climbs to 1.6M with ghc and needs -K20M As a guess: since 'mapM print ([1..102400] :: [Integer])' has type 'IO [()]', perhaps the result of the IO operation -- a list of 100K empty tuples -- is the culprit, even though the result is never used. Does 'mapM_ print ... ' (:: IO ()) perform any better? --Joe English jenglish@flightlab.com From senganb@ia.nsc.com Thu Oct 19 05:09:21 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 22:09:21 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190203.TAA16483@dragon.flightlab.com> from "Joe English" at Oct 18, 2000 07:03:05 PM Message-ID: <200010190409.WAA16637@ia.nsc.com> > > > senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > > > mapM seems to be a memory hog (and thus also concatMapM). > > In the following eg: > > > > > main = mapM print ([1..102400] :: [Integer]) > > > > memory usage climbs to 1.6M with ghc and needs -K20M > > As a guess: since 'mapM print ([1..102400] :: [Integer])' > has type 'IO [()]', perhaps the result of the IO operation -- > a list of 100K empty tuples -- is the culprit, even though > the result is never used. > > Does 'mapM_ print ... ' (:: IO ()) perform any better? Yes, but in the following eg > main = print $ sum x > x = _scc_ "x" [1..102400] :: [Integer] x takes 1M allocations, and I would think that () would be smaller than an Integer. Therefore I'm not sure that is the reason. The sum is there to force the evaluation. Sengan From senganb@ia.nsc.com Thu Oct 19 05:34:01 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 18 Oct 2000 22:34:01 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190409.WAA16637@ia.nsc.com> from "senganb@ia.nsc.com" at Oct 18, 2000 10:09:21 PM Message-ID: <200010190434.WAA20212@ia.nsc.com> > > senganb@ia.nsc.com (Sengan Baring-Gould) wrote: > > > > > mapM seems to be a memory hog (and thus also concatMapM). > > > In the following eg: > > > > > > > main = mapM print ([1..102400] :: [Integer]) > > > > > > memory usage climbs to 1.6M with ghc and needs -K20M > > > > As a guess: since 'mapM print ([1..102400] :: [Integer])' > > has type 'IO [()]', perhaps the result of the IO operation -- > > a list of 100K empty tuples -- is the culprit, even though > > the result is never used. > > > > Does 'mapM_ print ... ' (:: IO ()) perform any better? > > Yes, but in the following eg > > > main = print $ sum x > > x = _scc_ "x" [1..102400] :: [Integer] > > x takes 1M allocations, and I would think that () would be smaller than > an Integer. Therefore I'm not sure that is the reason. The sum is there to > force the evaluation. Assuming you are right, why do I see the same 1.6M profile with: > main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) >> return () > mapM2 :: Monad m => (a -> m b) -> [a] -> m [b] > mapM2 f [] = return [] > mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x -> > _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs -> > _scc_ "f" return (x:xs))) Is >>= not lazy? Sengan From senganb@ia.nsc.com Thu Oct 19 07:11:29 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Thu, 19 Oct 2000 00:11:29 -0600 (MDT) Subject: mapM/concatMapMy In-Reply-To: <200010190434.WAA20212@ia.nsc.com> from "senganb@ia.nsc.com" at Oct 18, 2000 10:34:01 PM Message-ID: <200010190611.AAA03566@ia.nsc.com> Actually I think I figured it out: (>>=) (f c) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (>>=) _(f c)_ (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (>>=) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (\(MN c1) \fc2 -> MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = fc2 r1 (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) (MN c1) (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (\x -> (>>=) (mapM f cs) (\xs -> return (x:xs))) r1 (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) -> (MN $ \s0 -> let (r1,io1,s1) = c1 s0 ( MN c2 ) = (>>=) (mapM f cs) (\xs -> return (r1:xs)) (r2,io2,s2) = c2 s1 in (r2,io1 >> io2,s2)) So the "return (r1:xs)" will only happen once the whole mapM has completed, leaving, if I only use r1 at first, a whole load of partially evaluated iterations of mapM in the heap. This also means that sequences such as "mapM x >>= mapM y >>= mapM z" are very inefficient and should be replaced by mapM (z.y.x) whereever possible. Agreed? Sengan From xvw@trinity.warande.net Thu Oct 19 22:24:13 2000 From: xvw@trinity.warande.net (xander) Date: Thu, 19 Oct 2000 23:24:13 +0200 (CEST) Subject: hugs/ghc + shared mem access Message-ID: Hi, I'm exploring my options to connect 2 programs (1 Haskell, 1 non-Haskell). I could connect both programs by 1 or 2 sockets. I was wondering whether it's feasible to access shared memory from within hugs as an alternative? Any answers? Thanks, xander van wiggen From frido@q-software-solutions.com.NO-spam Fri Oct 20 07:46:37 2000 From: frido@q-software-solutions.com.NO-spam (Friedrich Dominicus) Date: 20 Oct 2000 08:46:37 +0200 Subject: A question regarding haskell mode for Emacs In-Reply-To: John Atwood's message of "Tue, 22 Aug 2000 13:20:14 -0700 (PDT)" References: <200008222020.NAA25101@jasper.CS.ORST.EDU> Message-ID: <8766morovm.fsf@q-software-solutions.com> I wonder if there are some known troubles. This mode yesterday nearly drive me nuts. Indentation seem to be ok from the layout, but I got complains about block closed to early, missing ; ... Regards Friedrich -- for e-mail reply remove all after .com From romildo@urano.iceb.ufop.br Fri Oct 20 10:21:51 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Fri, 20 Oct 2000 07:21:51 -0200 Subject: Extensible data types? In-Reply-To: ; from rob@benchees.demon.co.uk on Mon, Sep 25, 2000 at 12:32:47PM +0100 References: ; <20000925082731.A3440@urano.iceb.ufop.br> Message-ID: <20001020072151.A1810@urano.iceb.ufop.br> Hello. I am back with the issue of extensible union types. Basically I want to extend a data type with new value constructors. Some members of the list pointed me to the paper "Monad Transformers and Modular Interpreters" Sheng Liang, Paul Hudak and Mark Jones The authors suggest using a type constructor to express the disjoint union of two other types: data Either a b = Left a | Right b which indeed is part of the Haskell 98 Prelude. Then they introduce a subtype relationship using multiparameter type classes: class SubType sub sup where inj :: sub -> sup -- injection prj :: sup -> Maybe sub -- projection The Either data type consructor is then used to express the desired subtype relationshipe: instance SubType a (Either a b) where inj = Left prj (Left x) = Just x prj _ = Nothing instance SubType a b => SubType a (Either c b) where inj = Right . inj prj (Right x) = prj x prj _ = Nothing The authors implemented their system in Gofer, due to restrictions in the type class system of Haskell. But now that there are Haskell extensions to support multiparametric type classes, that could be implemented in Haskell. The above code fails to type check due to instances overlapping. Hugs gives the following error message: ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType" *** This instance : SubType a (Either b c) *** Overlaps with : SubType a (Either a b) *** Common instance : SubType a (Either a b) (I did not check Gofer, but is there a way to solve these overlapping of instances in it?) So this is scheme is not going to work with Haskell (extended with multiparameter type classes). I would like hear any comments from the Haskell comunity on this subject. Is there a workaround for the overlapping instances? Regards. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From labra@pinon.ccu.uniovi.es Fri Oct 20 11:36:39 2000 From: labra@pinon.ccu.uniovi.es (Jose Emilio Labra Gayo) Date: Fri, 20 Oct 2000 12:36:39 +0200 (METDST) Subject: Extensible data types? In-Reply-To: <20001020072151.A1810@urano.iceb.ufop.br> Message-ID: > > The above code fails to type check due to instances > overlapping. Hugs gives the following error message: > In Hugs, there is a flag that you can set to allow overlapping instances :s +o In GHC, you can also set -fallow-overlapping-instances BTW, I use extensible union types in a "Language prototyping System" that I am implementing and which compiles with GHC and Hugs (it is based on Liang, Hudak and Jones paper). You can download the source code from "http://lsi.uniovi.es/~labra/LPS/LPS.html" Best regards, Jose Labra http://lsi.uniovi.es/~labra From doaitse@cs.uu.nl Fri Oct 20 14:16:34 2000 From: doaitse@cs.uu.nl (S. Doaitse Swierstra) Date: Fri, 20 Oct 2000 15:16:34 +0200 Subject: Extensible data types? In-Reply-To: <20001020072151.A1810@urano.iceb.ufop.br> References: ; <20000925082731.A3440@urano.iceb.ufop.br> <20001020072151.A1810@urano.iceb.ufop.br> Message-ID: It is exactly for reasons like these that we developped our small attribute grammar system: http://www.cs.uu.nl/groups/ST/Software/UU_AG/index.html Doaitse Swiesrtra At 7:21 AM -0200 10/20/00, Jos=E9 Romildo Malaquias wrote: >Hello. > >I am back with the issue of extensible union types. Basically >I want to extend a data type with new value constructors. >Some members of the list pointed me to the paper > > "Monad Transformers and Modular Interpreters" > Sheng Liang, Paul Hudak and Mark Jones > >The authors suggest using a type constructor to express >the disjoint union of two other types: > > data Either a b =3D Left a | Right b > >which indeed is part of the Haskell 98 Prelude. Then they introduce >a subtype relationship using multiparameter type classes: > > class SubType sub sup where > inj :: sub -> sup -- injection > prj :: sup -> Maybe sub -- projection > >The Either data type consructor is then used to express >the desired subtype relationshipe: > > instance SubType a (Either a b) where > inj =3D Left > prj (Left x) =3D Just x > prj _ =3D Nothing > > instance SubType a b =3D> SubType a (Either c b) where > inj =3D Right . inj > prj (Right x) =3D prj x > prj _ =3D Nothing > >The authors implemented their system in Gofer, due to >restrictions in the type class system of Haskell. >But now that there are Haskell extensions to support >multiparametric type classes, that could be implemented >in Haskell. > >The above code fails to type check due to instances >overlapping. Hugs gives the following error message: > > ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType" > *** This instance : SubType a (Either b c) > *** Overlaps with : SubType a (Either a b) > *** Common instance : SubType a (Either a b) > >(I did not check Gofer, but is there a way to solve these >overlapping of instances in it?) > >So this is scheme is not going to work with Haskell (extended >with multiparameter type classes). > >I would like hear any comments from the Haskell comunity on >this subject. Is there a workaround for the overlapping instances? > >Regards. > >Romildo >-- >Prof. Jos=E9 Romildo Malaquias >Departamento de Computa=E7=E3o >Universidade Federal de Ouro Preto >Brasil > >_______________________________________________ >Haskell mailing list >Haskell@haskell.org >http://www.haskell.org/mailman/listinfo/haskell -- __________________________________________________________________________ S. Doaitse Swierstra, Department of Computer Science, Utrecht University P.O.Box 80.089, 3508 TB UTRECHT, the Netherlands Mail: mailto: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 legere@its.caltech.edu Fri Oct 20 16:21:12 2000 From: legere@its.caltech.edu (Ronald J. Legere) Date: Fri, 20 Oct 2000 08:21:12 -0700 (PDT) Subject: .net and haskell In-Reply-To: Message-ID: I was reading some .net stuff (ducks) on microsoft, and they mentioned haskell as one of the languages someone was targetting for it. Anyone know anything about this project? Cheers! +++++++++++++++++++++++++++++++++++++++++++++++++ Ron Legere -- http://www.its.caltech.edu/~legere Caltech Quantum Optics MC 12-33 Pasadena CA 91125 626-395-8343 FAX: 626-793-9506 +++++++++++++++++++++++++++++++++++++++++++++++++ From romildo@urano.iceb.ufop.br Sat Oct 21 09:48:40 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Sat, 21 Oct 2000 06:48:40 -0200 Subject: Passing an environment around In-Reply-To: ; from conal@MICROSOFT.com on Thu, Oct 19, 2000 at 09:08:16AM -0700 References: Message-ID: <20001021064840.A19051@urano.iceb.ufop.br> The following discussion is been conducted in the Clean mailing list. As the issue is pertinent also to Haskell, I have cross-posted this letter to the Haskell mailing list too. Romildo. On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote: > Indeed Fran behaviors are like your alternative #1 (function passing), and > hence sharing loss is a concern. Simon PJ is right that I have a paper > discussing this issue and some others. See "Functional Implementations of > Continuous Modeled Animation" on my pubs page > (http://research.microsoft.com/~conal/papers). > > About alternative #2 (implicit arguments), would it help? Does it eliminate > the non-memoized redundant function applications, or just hide them? For > Fran, Erik Meijer suggested implicit functions to me a couple of years ago. > I hadn't thought of it, and it did indeed seem to be attractive at first as > a way to eliminate the need for overloading in Fran. However, the (Time -> > a) representation of Fran behaviors is not really viable, so I wouldn't > merely want to hide that representation behind implicit arguments. It seems that implicit parameters does not eliminate redundant function applications, as Conal Elliott has commented. Reading the paper Implicit Parameters: Dynamic Scoping with Static Types Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury http://www.cse.ogi.edu/~jlewis/ (especially section 5.1) I got this impression. I would like to hear from others as well, as I had some difficulties with the paper. > I don't see how alternative #3 would work. > > Of the three approaches, I think #1 is probably the best way to go. > Functional programming encourages us to program with higher-order functions, > and doing so naturally leads to this loss-of-sharing problem. Memoization > is thus a useful tool. Adding it to Clean would probably help others as > well as you. > > > I recommend that you find out how real computer algebra systems address this > issue. I've used these systems some and have the impression that there is a > default set of simplification rules, plus some strategies for non-standard > "simplifications" like factoring. You could apply the default set in a > bottom-up way, with no need for memoization. This is precisely the approach > used for algebraic simplification in Pan (an Haskell-based image synthesis > library). See the recent paper "Compiling Embedded Languages" on my pubs > page. You can also get the Pan source release to check out the real > details. > > Good luck, and please let me know how it turns out. > > - Conal > > -----Original Message----- > From: Simon Peyton-Jones > Sent: Thursday, October 19, 2000 1:51 AM > To: José Romildo Malaquias; clean-list@cs.kun.nl > Cc: Conal Elliott (E-mail); Meurig Sage (E-mail) > Subject: RE: [clean-list] Passing an environment around > > It's interesting that *exactly* this issue came up when Conal > Eliott was implementing Fran in Haskell. His 'behaviours' > are very like your expressions. > type Behaviour a = Time -> a > and he found exactly the loss of sharing that you did. > > For some reason, though, I'd never thought of applying the > implicit-parameter > approach to Fran. (Perhaps because Implicit parameters came along after > Fran.) > But I think it's rather a good idea. > > I think Conal may have a paper describing the implementation choices > he explored; I'm copying him. > > Simon > > | -----Original Message----- > | From: José Romildo Malaquias [mailto:romildo@urano.iceb.ufop.br] > | Sent: 18 October 2000 08:12 > | To: clean-list@cs.kun.nl > | Subject: [clean-list] Passing an environment around > | > | > | Hello. > | > | I am implementing a Computer Algebra system (CALG) in Clean, > | and I have a > | problem I would like the opinion of Clean programmers. > | > | The CALG system should be able to simplify (or better, to transform) > | algebraic expressions (from Mathematics) involving integers, > | named constants > | (like "pi" and "e"), variables, arithmetic operations (addition, > | multiplication, exponentiation), and other forms of expressions > | (trigonometric, logarithmic, derivatives, integrals, > | equations, etc.). The > | tansformaations should follow the rules from Algebra and > | other areas of > | Mathematica. But we know that in general an algebraic > | expression can be > | transformed in different ways, depending on the goal of the > | transformation. Thus, the algebraic expression > | > | a^2 + b^2 + 3*a*b - a*b > | > | could result in > | > | a^2 + 2*a*b + b^2 > | > | or in > | > | (a + b)^2 > | > | To control the transformations made with an algebraic > | expression there is a > | set of flags collected in a record. I will call this record > | the environment > | in which the expression should be simplified. The algorithms I am > | implementing may change this environment temporarily for some local > | transformations. So the enviroment should be passed around in > | the function > | calls I am writing. This way the functions that implements the > | transformations will have an extra argument representing the > | environment in > | which the transformation is to be performed. > | > | Let's take an example: the algorithm for addition will have > | two arguments to > | be added and a third argument corresponding to the enviroment: > | > | add :: Expr Expr Env -> Expr > | > | and its result will depend of the flags in the environment. > | But it is highly > | desirable to define functions like add as BINARY INFIX > | OPERATORS. Having 3 > | arguments, add cannot be made a binary operator! > | > | -------------------------------------------------------------------- > | So I am looking for alternative ways to pass the environment around. > | -------------------------------------------------------------------- > | > | 1. Handle the arguments as functions themselves, which, given > | an enviroment, > | returns the simplified algebraic expression in that environment: > | > | add :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr) > | > | Now add can be made a binary infix operator. This solution has the > | disadvantage that we loose sharing when doing local > | simplifications. For > | example: > | > | f :: (Env -> Expr) (Env -> Expr) -> (Env -> Expr) > | f fx fy = (add (add fx fy) fy) > | > | fe1, fe2 :: Env -> Exp > | fe1 e = ... > | fe2 e = ... > | > | initialEnv :: Env > | initialEnv = ... > | > | Start = f fe1 fe2 initialEnv > | > | In this program fragment, fe2 may be applied twice to the same > | environment value, computing its body twice. The resulting > | program would > | be too inneficient. If Clean had a mean of implementing MEMOIZATION > | FUNCTIONS, the computation of a memoized function > | application to the same > | argument would evalute the body of the function only the > | first time the > | function is applied. Subsequent applications of that > | function to the same > | argument would remember the result of the previous > | application and would > | reutilize it. Then this way of handling environment > | passing would be a > | good solution. > | > | For more on memo functions see > | . > | > | 2. Extend Clean to support IMPLICIT PARAMETER PASSING (that > | is, a form of > | dynamic scoping), as has been done in some Haskell > | implementations (Hugs, > | GHC). Than the environment could be passed implicitly and > | add could be > | considered to have only 2 arguments > | > | add :: (Env ?env) => Exp Exp -> Exp > | > | Here ?env represents an implicit parameter. It is not > | passed explicitly > | like the two argument parameters. It can be used normally > | in the function > | definition, like any normal parameter. To pass an argument > | implicitly, > | there is 2 additional forms of expression: dlet and with: > | > | dlet ?env = ... in add e1 e2 > | > | add e1 e2 with ?env = ... > | > | I think this could be the best solution to my problem, if Clean had > | such extension implemented. > | > | For more information, see > | > | > | 3. Join the algebraic expression and the environment in a single value > | > | add :: (Env,Exp) (Env,Exp) -> (Env,Exp) > | > | The enviroment is then carried around with each expression. > | But now add has two enviroments to consult. Which one should be > | used? > | > | Would be other good alternatives to solve this problem? > | > | Would future versions of Clean support > | > | - memoization functions, or > | - implciit parameter passing? > | > | I am open to discussion on this topics. > | > | Regards, > | > | Romildo > | -- > | Prof. José Romildo Malaquias > | Departamento de Computação > | Universidade Federal de Ouro Preto > | Brasil > | > | _______________________________________________ > | clean-list mailing list > | clean-list@cs.kun.nl > | http://www.cs.kun.nl/mailman/listinfo/clean-list > | > > _______________________________________________ > clean-list mailing list > clean-list@cs.kun.nl > http://www.cs.kun.nl/mailman/listinfo/clean-list -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From romildo@urano.iceb.ufop.br Mon Oct 23 13:22:35 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Mon, 23 Oct 2000 10:22:35 -0200 Subject: Overloaded function and implicit parameter passing Message-ID: <20001023102235.A11238@urano.iceb.ufop.br> Hi. While experimenting with the implicit parameter extension to Haskell 98, implemented in GHC 4.08.1 and latest Hugs, I came accross a difference among those implementations regarding overloading functions with implicit parameters. As a test consider the program ------------------------- cut here module Main where class C a where f :: (?env :: Integer) => a -> Integer instance C Integer where f x = ?env + x main = putStrLn (show (f (45::Integer) with ?env = 100)) ------------------------- cut here Hugs accepts this program and outputs 145, as expected. But GHC 4.08.1 refuses to compile it, emitting the message $ ghc -fglasgow-exts Test1.hs -o test1 Test1.hs:7: Unbound implicit parameter `env_rJX :: Integer' arising from use of `env_rJX' at Test1.hs:7 In the first argument of `+', namely `env_rJX' In the right-hand side of an equation for `f': env_rJX + x Compilation had errors Would anybody comment on what is going on with GHC? I am willing to use implicit parameters in the software I am developing, but I have the need to overload functions with implicit parameters. While Hugs is good for development, its performance may rule it out when the final product is ready. So I will need a good Haskell compiler to compile my system. Any comments? Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From fjh@cs.mu.oz.au Mon Oct 23 15:02:14 2000 From: fjh@cs.mu.oz.au (Fergus Henderson) Date: Tue, 24 Oct 2000 01:02:14 +1100 Subject: Overloaded function and implicit parameter passing In-Reply-To: <20001023102235.A11238@urano.iceb.ufop.br> References: <20001023102235.A11238@urano.iceb.ufop.br> Message-ID: <20001024010214.A11699@hg.cs.mu.oz.au> On 23-Oct-2000, José Romildo Malaquias wrote: > ------------------------- cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > ------------------------- cut here ... > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 ... > Would anybody comment on what is going on with GHC? That sure looks to me like a bug in GHC's support for implicit parameter passing. -- Fergus Henderson | "I have always known that the pursuit | of excellence is a lethal habit" WWW: | -- the last words of T. S. Garp. From ru@ohio.river.org Mon Oct 23 21:28:09 2000 From: ru@ohio.river.org (Richard) Date: Mon, 23 Oct 2000 13:28:09 -0700 (PDT) Subject: mapM/concatMapMy In-Reply-To: <200010190434.WAA20212@ia.nsc.com> References: <200010190409.WAA16637@ia.nsc.com> <200010190434.WAA20212@ia.nsc.com> Message-ID: <200010232028.NAA14294@ohio.river.org> Sengan Baring-Gould writes: >Is >>= not lazy? since no experts have answered yet, this newbie will answer. I think it's strict. somewhere in the compiler doco, IIRC, it says (>>=) was lazy at first, but experience showed it was more confusing for users (Haskell programmers). moreover, from the hslibs documentation, LazyST chapter: "The lazy ST monad tends to be more prone to space leaks than the strict version, so most programmers will use the former unless laziness is explicitly required." http://haskell.org/ghc/docs/latest/set/sec-lazyst.html From quintela@fi.udc.es Tue Oct 24 05:48:25 2000 From: quintela@fi.udc.es (Juan J. Quintela) Date: 24 Oct 2000 06:48:25 +0200 Subject: CFP: Eight International Conference on Computer Aided Systems Theory Message-ID: The following message is a courtesy copy of an article that has been posted to comp.lang.ml,comp.lang.functional as well. Dear Colleagues, I would be most grateful if you would distribute the appended Call For Papers to your colleagues (and/or any mailing lists you see appropriate). Any help in distributing the Call For Papers would be most appreciated. Kindest regards, Juan Quintela CALL FOR PAPERS --------------- Eight International Conference on Computer Aided Systems Theory Formal Methods and Tools for Computer Science See the webpage at: http://azuaje.ulpgc.es/congresos/eurocast2001/ The topics for the workshop are: Workshop "FP" Contributions addressing to the following and similar issues: 1.Concurrency. Distributed and web applications. 2.Verification:tools and methods. 3.Persistence. 4.Typing and theoretical foundations. You only have to send one extended abstract before the: 31 October. -- In theory, practice and theory are the same, but in practice they are different -- Larry McVoy From rjmh@cs.chalmers.se Tue Oct 24 09:16:54 2000 From: rjmh@cs.chalmers.se (John Hughes) Date: Tue, 24 Oct 2000 10:16:54 +0200 (MET DST) Subject: mapM/concatMapMy Message-ID: <200010240816.KAA17042@muppet30.cs.chalmers.se> Sengan Baring-Gould writes: >Is >>= not lazy? since no experts have answered yet, this newbie will answer. I think it's strict. Well, it depends. (>>=) is an overloaded operator, with a different implementation for every monad -- when you define a monad, you give the implementation of (>>=). If your implementation is strict (presumably in the first operand), then (>>=) is strict *at that type*. If your implementation is lazy, then it isn't. The same goes for (+): at most types (+) is strict, but if you define your own kind of number with a lazy addition, then on that type (+) will be lazy. For many monads, (>>=) *is* strict, which fits with the intuition that it is a `sequencing' operator. But by no means for all. The simplest counter-example is the identity monad: newtype Id a = Id a instance Monad Id where return = Id Id x >>= f = f x where m>>=f is strict in m only if f is a strict function. A more interesting example is the state transformer monad: newtype ST s a = ST (s -> (a,s)) instance Monad (ST s) where return x = ST (\s -> (x,s)) ST h >>= f = ST (\s -> let (a,s') = h s ST h' = f a in h' s') where once again, the implementation of (>>=) is strict only if f is a strict function. Hence `lazy state' makes sense! John Hughes From delapla@lami.univ-evry.fr Tue Oct 24 13:57:16 2000 From: delapla@lami.univ-evry.fr (Franck Delaplace) Date: Tue, 24 Oct 2000 14:57:16 +0200 Subject: LOOKING FOR B-TREES MODULE Message-ID: <39F5872C.8B54DC16@lami.univ-evry.fr> I am looking for an haskell module which implements balanced trees ? Can somebdody help me = Thank you = -- = Franck Delaplace @w3:http://taillefer.lami.univ-evry.fr:8090/~delapla/ La.M.I-U.M.R C.N.R.S Universit=E9 d'Evry Val d'Essonne = Cours Monseigneur Rom=E9ro = 91025 Evry CEDEX (France) From wohlstad@cs.ucdavis.edu Tue Oct 24 19:25:29 2000 From: wohlstad@cs.ucdavis.edu (Eric Allen Wohlstadter) Date: Tue, 24 Oct 2000 11:25:29 -0700 (PDT) Subject: Group theory In-Reply-To: <200010240816.KAA17042@muppet30.cs.chalmers.se> Message-ID: Are there any Haskell libraries or programs related to group theory? I am taking a class and it seems like Haskell would be a good programming language for exploring/reasoning about group theory. What I had in mind was perhaps you could have a function which takes a list(set) and a function with two arguments(binary operator) and checks to see whether or not it is a group. I think it might be a fun exercies to write myself but I'd like to see if it's already been done or what you guys think about it. Eric Wohlstadter UCDavis Software Engineering From dongen@cs.ucc.ie Tue Oct 24 19:29:58 2000 From: dongen@cs.ucc.ie (Marc van Dongen) Date: Tue, 24 Oct 2000 19:29:58 +0100 Subject: Group theory In-Reply-To: ; from wohlstad@cs.ucdavis.edu on Tue, Oct 24, 2000 at 11:25:29AM -0700 References: <200010240816.KAA17042@muppet30.cs.chalmers.se> Message-ID: <20001024192958.D25711@cs.ucc.ie> Eric Allen Wohlstadter (wohlstad@cs.ucdavis.edu) wrote: : Are there any Haskell libraries or programs related to group theory? I am : taking a class and it seems like Haskell would be a good programming : language for exploring/reasoning about group theory. What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) has facilities for that. Have a look at: http://www.cs.bell-labs.com/who/wadler/realworld/docon.html Regards, Marc van Dongen From mechvel@math.botik.ru Wed Oct 25 08:20:32 2000 From: mechvel@math.botik.ru (S.D.Mechveliani) Date: Wed, 25 Oct 2000 11:20:32 +0400 Subject: group theory. Reply Message-ID: Hi, all, To Eric Allen Wohlstadter's (wohlstad@cs.ucdavis.edu) : Are there any Haskell libraries or programs related to group theory? I am : taking a class and it seems like Haskell would be a good programming : language for exploring/reasoning about group theory. What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. Marc van Dongen writes > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) > has facilities for that. Have a look at: > > http://www.cs.bell-labs.com/who/wadler/realworld/docon.html Sorry, DoCon () really supports the Commutative Rings, but provides almost nothing for the Group theory. For example, for the domain (Integer,Integer) it would set automatically (IsGroup,Yes) for the Additive semigroup and (IsGroup,No) for the Multiplicative semigroup. For the additive case, it would also set the group generator list [(1,0),(0,1)]. In both cases, it would also set cardinality = Infinity. Similar attributes are formed for the constructors of Permutation, Vector, Matrix, Polyninomial, Fraction, ResidueRing. And that is all. It does not provide so far any real algorithmic support for the Group theory, except some operations on permutations. But one may develop the program by adding the needed algorithms and introducing new attributes. : What I had in mind : was perhaps you could have a function which takes a list(set) and a : function with two arguments(binary operator) and checks to see whether or : not it is a group. I think it might be a fun exercies to write myself but : I'd like to see if it's already been done or what you guys think about it. I never programmed this. It looks like some exercise in algorithms. There are also books on the combinatorial group theory, maybe, they say something about efficient procedures for this. Regards, ------------------ Sergey Mechveliani mechvel@botik.ru From karczma@info.unicaen.fr Wed Oct 25 10:58:04 2000 From: karczma@info.unicaen.fr (Jerzy Karczmarczuk) Date: Wed, 25 Oct 2000 10:58:04 +0100 Subject: group theory. Reply References: Message-ID: <39F6AEAC.F5C9C988@info.unicaen.fr> S.D.Mechveliani wrote: > > Hi, all, > > To Eric Allen Wohlstadter's > > : Are there any Haskell libraries or programs related to group theory? ... > Marc van Dongen writes > > > I think Sergey Mechveliani's docon (algebraic DOmain CONstructor) > > has facilities for that. ... > Sorry, > DoCon () > > really supports the Commutative Rings, > but provides almost nothing for the Group theory. > EAW again: > : ... I think it might be a fun exercies to write myself but > : I'd like to see if it's already been done or what you guys > : think about it. SM: > I never programmed this. It looks like some exercise in algorithms. > There are also books on the combinatorial group theory, maybe, they > say something about efficient procedures for this. == "Some exercise in algorithms". Hm. There is more to that than this... This issue has been recently stirred a bit in the comp.functional newsgroup, in a larger context, general Math, not necessarily the group theor. There are at least two people *interested* in it, although they didn't do much yet (for various reasons...) Suggestion: Take GAP! ( http://www-history.mcs.st-and.ac.uk/~gap/ ) Plenty of simply coded algorithms, specifically in this domain. I coded just for fun a few simple things in Haskell some time ago, and it was a real pleasure. The code is cleaner and simpler. Its presentation is also much cleaner than the original algorithms written in GAP language. But I discarded all this stuff, thinking that I would have never time enough to get back to it... This is a nice project, and I would participate with pleasure in it, although the time factor is still there... Dima Pasechnik (; does he read it?) - apparently - as well. Jerzy Karczmarczuk Caen, France From senganb@ia.nsc.com Wed Oct 25 17:21:42 2000 From: senganb@ia.nsc.com (Sengan Baring-Gould) Date: Wed, 25 Oct 2000 10:21:42 -0600 (MDT) Subject: Haskell Programming Environment In-Reply-To: <20001025084900Z474423-538+2802@webmail1.ahoj.pl> from "=?ISO-8859-2?Q? Pawe=B3?= Kot" at Oct 25, 2000 10:48:57 AM Message-ID: <200010251621.KAA02114@ia.nsc.com> > Hello, > > I'm writing my master thesis. Its subject is 'Haskell Programming > Environment'. It is (or rather will be) an extended text editor working i= > n > graphical (XFree86) environment designed for Haskell programmers. It will= > be > implemented using Fudgets library. > I'm wondering what features would you like to find in such environment. W= > hat > should be neccessary, what would help, what would make writing programs > easier, etc. > I have some concepts, but I would like to hear some suggestions from you. > > Thanks for all answers. a) the ablility to highlight an area of code and get its type (be it a function, or some well-formed chunk of code b) the ability to highlight a function and get its definition in another area (think multiple text editing in vim) c) interaction with hugs/stg-hugs so that just written code can be pasted into a "hugs window" for evaluation. d) Debug mode which automatically adds "deriving show" to all datatypes which are not showable/adds exporting of all Datatypes as non-abstract for use in hugs to just allow things to be tried out. e) Debug mode which invisibly replaces functions such as "fromJust" with error making versions (... fromJust' "the file and line at which I'm invoked" ...) to make it easier to find the cause of the error (fromJust Nothing just comes up with an error telling you that it's fromJust that failed. Last time that happened, I hacked hugs to dump the evaluation stack, from which I guessed which possible fromJusts it could have been). f) Use ghc's .hi file to allow strictness of arguments to appear if you leave the mouse over an argument. g) For bonus points (harder, but really useful when stuck): given an expression, show me (possibly using daVinci) how it gets evaluated: Lazyness behaviour is not always obvious, I'd like to see it. I've been wanting to code one of these myself, but have had no time. Try and see if stg-hugs is useable yet since that would be a much better environment to do it in. Sengan From Keith.Wansbrough@cl.cam.ac.uk Wed Oct 25 17:26:51 2000 From: Keith.Wansbrough@cl.cam.ac.uk (Keith Wansbrough) Date: Wed, 25 Oct 2000 17:26:51 +0100 Subject: Haskell Programming Environment In-Reply-To: Your message of "Wed, 25 Oct 2000 10:21:42 MDT." <200010251621.KAA02114@ia.nsc.com> Message-ID: > I've been wanting to code one of these myself, but have had no time. Try and see > if stg-hugs is useable yet since that would be a much better environment to do > it in. It's now called GHCi, and is being written right now by the GHC team. Not sure when the estimated completion time is, but it can't be that far off. --KW 8-) From ger@Informatik.Uni-Bremen.DE Wed Oct 25 21:08:55 2000 From: ger@Informatik.Uni-Bremen.DE (George Russell) Date: Wed, 25 Oct 2000 22:08:55 +0200 Subject: cpp superior to ghc . . . Message-ID: <39F73DD7.E744A061@informatik.uni-bremen.de> Why does the Haskell language not allow "type" declarations to appear in the declaration parts of where and let clauses? I've just been writing a huge functions which requires lots and lots of repetitive internal type annotations (to disambiguate some complicated overloading) but I can't abbreviate them with "type" because they depend on things only in scope inside the function. In the end I abbreviated them with a few #define's but I don't really think it should be that way . . . From qrczak@knm.org.pl Thu Oct 26 06:09:48 2000 From: qrczak@knm.org.pl (Marcin 'Qrczak' Kowalczyk) Date: 26 Oct 2000 05:09:48 GMT Subject: cpp superior to ghc . . . References: <39F73DD7.E744A061@informatik.uni-bremen.de> Message-ID: Wed, 25 Oct 2000 22:08:55 +0200, George Russell pisze: > Why does the Haskell language not allow "type" declarations to > appear in the declaration parts of where and let clauses? Because you can always lift them to the top level. -- __("< Marcin Kowalczyk * qrczak@knm.org.pl http://qrczak.ids.net.pl/ \__/ ^^ SYGNATURA ZASTÊPCZA QRCZAK From koen@cs.chalmers.se Thu Oct 26 08:01:21 2000 From: koen@cs.chalmers.se (Koen Claessen) Date: Thu, 26 Oct 2000 09:01:21 +0200 (MET DST) Subject: cpp superior to ghc . . . In-Reply-To: Message-ID: George Russell complained: | Why does the Haskell language not allow "type" | declarations to appear in the declaration parts of | where and let clauses? Marcin 'Qrczak' Kowalczyk replied: | Because you can always lift them to the top level. This is the ultimate non-answer. First of all, it is wrong. George meant to be able to use type variables present in the top-level type in the local type declarations. Something like: doWithStack :: a -> a doWithStack x = stacking [] where type Stack = [a] stacking :: Stack -> a stacking = ... The problem is really two-fold: bound type variables (like "a") are not in scope in the body of the function, and local type declarations are not allowed. Secondly, "because another way of doing it is possible" is not an answer. We allow local declarations of functions, but we have known for ages we can all lambda-lift them to top-level... Regards, Koen. -- Koen Claessen http://www.cs.chalmers.se/~koen phone:+46-31-772 5424 mailto:koen@cs.chalmers.se ----------------------------------------------------- Chalmers University of Technology, Gothenburg, Sweden From mk167280@students.mimuw.edu.pl Thu Oct 26 08:29:49 2000 From: mk167280@students.mimuw.edu.pl (Marcin 'Qrczak' Kowalczyk) Date: Thu, 26 Oct 2000 09:29:49 +0200 (CEST) Subject: cpp superior to ghc . . . In-Reply-To: Message-ID: On Thu, 26 Oct 2000, Koen Claessen wrote: > The problem is really two-fold: bound type variables (like > "a") are not in scope in the body of the function, and local > type declarations are not allowed. GHC and Hugs do solve the first problem by providing a language extension: names of type variables in pattern type signatures and result type signatures are available in their scope. I wish this extension becomes a future standard. Some people say that type variables from ordinary type signatures should be in scope too. -- Marcin 'Qrczak' Kowalczyk From simonpj@microsoft.com Thu Oct 26 18:27:51 2000 From: simonpj@microsoft.com (Simon Peyton-Jones) Date: Thu, 26 Oct 2000 10:27:51 -0700 Subject: .net and haskell Message-ID: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmond.corp.microsoft.com> | I was reading some .net stuff (ducks) on microsoft, and they | mentioned haskell as one of the languages someone was | targetting for it. | Anyone know anything about this project? I know of several stabs in this direction, none completed. - There is most of a Java back end for GHC - There are various pieces of a C# back end for GHC, compiling via in intermediate generic OO language called GOO. Nigel Perry is working on this (actively I think) - Don Syme and Reuben Thomas are working on a back end for GHC that compiles to a polymorphically-typed IL for .NET that is Don's baby. A lot of this works, but it's not complete. Maybe others are doing stuff too? It's a pity that there's nothing that's usable yet, but I hope that'll change. Simon From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 11:16:19 2000 From: mhoechsm@techfak.uni-bielefeld.de (=?iso-8859-1?Q?Matthias_H=F6chsmann?=) Date: Fri, 27 Oct 2000 12:16:19 +0200 Subject: class instance with nested types Message-ID: <001801c03ffe$f321de20$0701a8c0@mulder> This is a multi-part message in MIME format. --Boundary_(ID_5jIOsd3oqicabXDXApeVOg) Content-type: text/plain; charset=iso-8859-1 Content-transfer-encoding: 7BIT Hello, I have the following problem: basic datatypes > type Sequence a = [a] > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > type Forest a = Sequence (Tree a) i want to construct a class Xy > class Xy s a where > test :: s a -> a and make an instance for list of characters > instance Xy [] Char where > test [a] = a this works, and an instance for a forest and tried something like this > instance ([] Tree) Char where > test x@(N a xs):txs = a I get illegal type errors. Is it possible to use nested types in a class ? Hope you can help me Matthias --Boundary_(ID_5jIOsd3oqicabXDXApeVOg) Content-type: text/html; charset=iso-8859-1 Content-transfer-encoding: 7BIT
Hello,
 
I have the following problem:
 
basic datatypes
 
> type Sequence a = [a]
> data Tree a = N a (Forest a) deriving (Ord,Eq,Show)
> type Forest a = Sequence (Tree a)
 
i want to construct a class Xy
 
> class Xy s a where
>      test :: s a -> a
 
and make an instance for list of characters
 
> instance Xy [] Char where
>      test [a] = a
 
this works, and an instance for a forest and tried something like this
 
> instance  ([] Tree) Char where
> test x@(N a xs):txs = a
 
I get illegal type errors. Is it possible to use nested types in a class ?
 
Hope you can help me
Matthias
 
--Boundary_(ID_5jIOsd3oqicabXDXApeVOg)-- From d95lars@dtek.chalmers.se Fri Oct 27 11:14:58 2000 From: d95lars@dtek.chalmers.se (Lars Lundgren) Date: Fri, 27 Oct 2000 12:14:58 +0200 (MEST) Subject: class instance with nested types In-Reply-To: <001801c03ffe$f321de20$0701a8c0@mulder> Message-ID: On Fri, 27 Oct 2000, Matthias Höchsmann wrote: > Hello, > > I have the following problem: > > basic datatypes > > > type Sequence a = [a] > > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > > type Forest a = Sequence (Tree a) > > i want to construct a class Xy > > > class Xy s a where > > test :: s a -> a > > and make an instance for list of characters > > > instance Xy [] Char where > > test [a] = a > > this works, and an instance for a forest and tried something like this > > > instance ([] Tree) Char where > > test x@(N a xs):txs = a > Don't you mean test (N a xs:txs) = a ? /Lars L From N.Perry@massey.ac.nz Fri Oct 27 11:59:13 2000 From: N.Perry@massey.ac.nz (Nigel Perry) Date: Fri, 27 Oct 2000 12:59:13 +0200 Subject: .net and haskell In-Reply-To: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmon d.corp.microsoft.com> References: <74096918BE6FD94B9068105F877C002D0110D402@red-pt-02.redmon d.corp.microsoft.com> Message-ID: At 10:27 am -0700 26/10/00, Simon Peyton-Jones wrote: >| I was reading some .net stuff (ducks) on microsoft, and they >| mentioned haskell as one of the languages someone was >| targetting for it. >| Anyone know anything about this project? > >I know of several stabs in this direction, none completed. > >- There is most of a Java back end for GHC > >- There are various pieces of a C# back end for GHC, > compiling via in intermediate generic OO language > called GOO. Nigel Perry is working on this (actively > I think) This is indeed being worked on. Currently user code compiles (as far as it has been tested) but there is no prelude yet so it doesn't run too well ;-) The code generator was designed for research and supporting scripting, which is a kind way of saying it doesn't produce blazingly fast code. > >- Don Syme and Reuben Thomas are working on a back end for > GHC that compiles to a polymorphically-typed IL for .NET > that is Don's baby. A lot of this works, but it's not complete. > >Maybe others are doing stuff too? It's a pity that there's nothing >that's usable yet, but I hope that'll change. Cheers, Nigel From rossberg@ps.uni-sb.de Fri Oct 27 13:07:37 2000 From: rossberg@ps.uni-sb.de (Andreas Rossberg) Date: Fri, 27 Oct 2000 14:07:37 +0200 Subject: class instance with nested types References: <001801c03ffe$f321de20$0701a8c0@mulder> Message-ID: <39F97009.9C9BB220@ps.uni-sb.de> Matthias Höchsmann wrote: > > > type Sequence a = [a] > > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > > type Forest a = Sequence (Tree a) > > i want to construct a class Xy > > > class Xy s a where > > test :: s a -> a > > [...] > > > instance ([] Tree) Char where > > test x@(N a xs):txs = a To make it syntactically correct this should at least be something like > instance Xy ([] Tree) Char where > test (N a xs:txs) = a But the real problem is in the expression ([] Tree), which is the same as writing [Tree]. This is not a legal type expression, since Tree is a type constructor, not a ground type, so you cannot apply it to the list constructor. What you are trying to say is probably something like this: > instance Xy (\a . [Tree a]) Char -- not Haskell But unfortunately there are no lambdas on the type level - they would render the type system undecidable. For the same reason it is not allowed to use a type synonym in an instance declaration: > instance Xy Forest Char -- illegal The only thing you can do is turning Forest into a data type: > data Tree a = N a (Forest a) deriving (Ord,Eq,Show) > data Forest a = Forest [Tree a] > instance Xy Forest Char where > test (Forest (N a xs:txs)) = a HTH, - Andreas -- Andreas Rossberg, rossberg@ps.uni-sb.de :: be declarative. be functional. just be. :: From rossberg@ps.uni-sb.de Fri Oct 27 13:12:45 2000 From: rossberg@ps.uni-sb.de (Andreas Rossberg) Date: Fri, 27 Oct 2000 14:12:45 +0200 Subject: class instance with nested types References: <001801c03ffe$f321de20$0701a8c0@mulder> <39F97009.9C9BB220@ps.uni-sb.de> Message-ID: <39F9713D.C0581888@ps.uni-sb.de> I mumbled: > > This is not a legal type expression, since Tree is a > type constructor, not a ground type, so you cannot apply it to the list > constructor. The other way round, of course: you cannot apply the list constructor to it. - Andreas -- Andreas Rossberg, rossberg@ps.uni-sb.de :: be declarative. be functional. just be. :: From mhoechsm@techfak.uni-bielefeld.de Fri Oct 27 14:25:00 2000 From: mhoechsm@techfak.uni-bielefeld.de (=?iso-8859-1?Q?Matthias_H=F6chsmann?=) Date: Fri, 27 Oct 2000 15:25:00 +0200 Subject: class instance with nested types References: Message-ID: <006201c04019$69f81540$0701a8c0@mulder> Yes, I wanted to type it like you do. But anyway, i fixed the problem following Andreas Rossbergs suggestion. Matthias > > Don't you mean > > test (N a xs:txs) = a > > ? > > /Lars L > > > > _______________________________________________ > Haskell mailing list > Haskell@haskell.org > http://www.haskell.org/mailman/listinfo/haskell From jeff@galconn.com Fri Oct 27 16:10:29 2000 From: jeff@galconn.com (Jeffrey R. Lewis) Date: Fri, 27 Oct 2000 08:10:29 -0700 Subject: Overloaded function and implicit parameter passing References: <20001023102235.A11238@urano.iceb.ufop.br> Message-ID: <39F99AE5.8A60CAF5@galconn.com> José Romildo Malaquias wrote: > Hi. > > While experimenting with the implicit parameter > extension to Haskell 98, implemented in GHC 4.08.1 > and latest Hugs, I came accross a difference among > those implementations regarding overloading functions > with implicit parameters. > > As a test consider the program > > ------------------------- cut here > module Main where > > class C a where > f :: (?env :: Integer) => a -> Integer > > instance C Integer where > f x = ?env + x > > main = putStrLn (show (f (45::Integer) with ?env = 100)) > ------------------------- cut here > > Hugs accepts this program and outputs 145, as expected. > But GHC 4.08.1 refuses to compile it, emitting the > message > > $ ghc -fglasgow-exts Test1.hs -o test1 > > Test1.hs:7: > Unbound implicit parameter `env_rJX :: Integer' > arising from use of `env_rJX' at Test1.hs:7 > In the first argument of `+', namely `env_rJX' > In the right-hand side of an equation for `f': env_rJX + x > > Compilation had errors > > Would anybody comment on what is going on with GHC? > > I am willing to use implicit parameters in the > software I am developing, but I have the need > to overload functions with implicit parameters. > While Hugs is good for development, its performance > may rule it out when the final product is ready. > So I will need a good Haskell compiler to compile > my system. > > Any comments? Certainly a bug. I'll look at it when I get a chance. --Jeff From romildo@urano.iceb.ufop.br Fri Oct 27 17:41:19 2000 From: romildo@urano.iceb.ufop.br (=?iso-8859-1?Q?Jos=E9_Romildo_Malaquias?=) Date: Fri, 27 Oct 2000 14:41:19 -0200 Subject: Passing an environment around In-Reply-To: <39F9A83C.311C016A@galconn.com>; from jeff@galconn.com on Fri, Oct 27, 2000 at 09:07:24AM -0700 References: <20001021064840.A19051@urano.iceb.ufop.br> <39F9A83C.311C016A@galconn.com> Message-ID: <20001027144119.A20783@urano.iceb.ufop.br> On Fri, Oct 27, 2000 at 09:07:24AM -0700, Jeffrey R. Lewis wrote: > José Romildo Malaquias wrote: > > > On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote: > > > Indeed Fran behaviors are like your alternative #1 (function passing), and > > > hence sharing loss is a concern. Simon PJ is right that I have a paper > > > discussing this issue and some others. See "Functional Implementations of > > > Continuous Modeled Animation" on my pubs page > > > (http://research.microsoft.com/~conal/papers). > > > > > > About alternative #2 (implicit arguments), would it help? Does it eliminate > > > the non-memoized redundant function applications, or just hide them? For > > > Fran, Erik Meijer suggested implicit functions to me a couple of years ago. > > > I hadn't thought of it, and it did indeed seem to be attractive at first as > > > a way to eliminate the need for overloading in Fran. However, the (Time -> > > > a) representation of Fran behaviors is not really viable, so I wouldn't > > > merely want to hide that representation behind implicit arguments. > > > > It seems that implicit parameters does not eliminate redundant function > > applications, as Conal Elliott has commented. Reading the paper > > > > Implicit Parameters: Dynamic Scoping with Static Types > > Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury > > http://www.cse.ogi.edu/~jlewis/ > > > > (especially section 5.1) I got this impression. I would like to hear > > from others as well, as I had some difficulties with the paper. > > I am sorry you had difficulties! The difficulties I had is basicaly due to my lack of solid knowledge on type theory and semantic formalisms. Not that the paper was badly written. > Yes, as implemented using the dictionary > translation, implicit parameterization can lead to loss of sharing, exactly in > the same way that overloading (and HOF in general) can lead to loss of sharing. > > However, I can imagine that a compiler might chose to implement implicit > parameters more like dynamic variables in lisp. Each implicit param essentially > becomes a global variable, implemented as a stack of values - the top of the > stack is the value currently in scope. This would avoid the sharing problem > nicely. > > --Jeff I suppose your implementation of implicit parameterization in GHC and Hugs uses the dictionary translation, right? Would an alternative implementation based on a stack of values be viable and even done? Does it have serious drawbacks when compared with the dictionary translation technique? Thanks. Romildo -- Prof. José Romildo Malaquias Departamento de Computação Universidade Federal de Ouro Preto Brasil From dublins@home.com Sun Oct 29 18:55:51 2000 From: dublins@home.com (S Dublin) Date: Sun, 29 Oct 2000 10:55:51 -0800 Subject: Message-ID: <20001029185558.PTNY2380.femail1.sdc1.sfba.home.com@[65.3.159.89]> From lmagnani@cc.gatech.edu Sun Oct 29 16:08:27 2000 From: lmagnani@cc.gatech.edu (Lorenzo Magnani) Date: Sun, 29 Oct 2000 10:08:27 -0600 Subject: MBR'01 Conference Message-ID: <39FC4B7B.6BF0445A@cc.gatech.edu> Please accept our apologies if you receive multiple copies of this call If you want to receive updated information please send your complete address Last updated October 29, 2000 ********************************************************************** MODEL-BASED REASONING: SCIENTIFIC DISCOVERY, TECHNOLOGICAL INNOVATION, VALUES (MBR'01), Pavia, Italy, May 17-19, 2001. ********************************************************************** Up-to date information on the conference will be found at http://philos.unipv.it/courses/progra1.html or http://www.unipv.it/webphilos_lab/courses/progra1.html ********************************************************************** GENERAL INFORMATION From Thursday 17 to Saturday 19 May 2001 (three days) the International Conference "MODEL-BASED REASONING. SCIENTIFIC DISCOVERY, TECNOLOGICAL INNOVATION, VALUES" will be held at the University of Pavia (near Milan, Italy). PROGRAM The conference will deal with the logical, epistemological, and cognitive aspects of modeling practices employed in scientific discovery and technological innovation, including computational models of such practices. Abduction is widely recognized as a significant reasoning process in discovery whose features are in need of explication. We will solicit papers that examine various forms of model-based reasoning, such as analogical and visual modeling, from philosophical, historical, sociological, psychological, or computational perspectives. We also plan to address the problem of model-based reasoning in ethics reasoning, especially pertaining to science and technology. RELEVANT RESEARCH AREAS We shall call for papers that cover topics from the following list: - abduction - analogical reasoning - causal and counterfactual reasoning in model construction - computational models of model-based reasoning and scientific reasoning - conceptual combination and theory formation - hypothetical and explanatory reasoning - logical analyses that may contribute to our understanding of the issues in model-based reasoning - model-based reasoning in ethics - models and manipulative reasoning - models and technological innovation - thought experimenting - visual, spatial, imagistic modeling, reasoning, and simulation SUBMISSIONS OF PAPERS All submitted papers will be carefully refereed. The precise format of the conference will be fixed after we have an idea of the number of accepted papers. We are thinking in terms of presentations of 40 and 20 minutes. The funding is Italian and US, but we are also looking elsewhere for further financing (and would appreciate any suggestions). A selected subset will be invited for inclusion (subject to refereeing) in a book which will constitute an advanced handbook for scientists and researchers. The book will be published by an international publishing house. Moreover another selected subset will be invited for inclusion (subject to refereeing) in special issues of suitable international Journals. FORMAT Authors must submit three printed copies and an electronic version - formatted in Microsoft Word, RTF, PDF, or Postcript format - of an extended abstract (about 1000 words) not later than November 30, 2000. Please send electronically the extended abstract to the program chair at the address lmagnani@cc.gatech.edu in case of problem with the above address please use lorenzo@philos.unipv.it or lmagnaniusa@netscape.net REGISTRATION AND FURTHER INFORMATION Registration Fees: Before 15 March 2001: Normal: ITL. 300.000 = appr. US$ 155 (EUR 154.93) (to participate in all the activities of the Conference) Students: Free After 15 March 2001: Normal: ITL. 350.000 = appr. US$ 175 (EUR 180.75) (to participate in all the activities of the Conference) Students: Free METHOD OF PAYMENT AND REGISTRATION DEADLINE: Bank (Swift) Transfer to BANCA REGIONALE EUROPEA S.p.A BRANCH PAVIA - Sede SWIFT BREUITM2 301 Bank Code 06906.11301 Acc. n. 520 Dipartimento di Filosofia indicating CONVEGNO INTERNAZIONALE MBR'01 PLEASE REGISTER by email, fax or air mail (before March 15, 2001) by sending PROGRAM CHAIR first and last name, function, institution, full address, phone, fax and email. For information about paper submission and the program that is not available on the web site, please contact the program chair. IMPORTANT DATES Registration deadline............................15 March 2001 Submission deadline..............................30 Nov 2000 Notification of acceptance.....................28 Feb 2001 Final papers (from those selected for publication) due........30 June 2001 Conference....................................17-19 May 2001 PROGRAM CHAIR Lorenzo MAGNANI School of Public Policy and College of Computing Program in Philosophy, Science, & Technology Georgia Institute of Technology, 685 Cherry Street Atlanta, GA, 30332 - 0345, USA Office: 404-894-0950 & 404-385-0884, Home: 404-875-3566 Fax: 404-385-0504 & 404-894-2970 Email: lorenzo.magnani@cc.gatech.edu Address in Italy: Department of Philosophy and Computational Philosophy Laboratory University of Pavia, Piazza Botta 6, 27100 Pavia, Italy Office: +39-0382-506283, Home: +39-0383-371067 Fax: +39-0382-23215 Email: lorenzo@philos.unipv.it PROGRAM CO-CHAIR Nancy J. NERSESSIAN (Program Co-Chair) Program in Cognitive Science School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, USA Email: nancyn@cc.gatech.edu PROGRAM CO-CHAIR Kenneth J. KNOESPEL (Program Co-Chair) School of History, Technology, and Society, and Program in Cognitive Science Georgia Institute of Technology, Atlanta, USA Email: kenneth.knoespel@hts.gatech.edu PROGRAM COMMITTEE - Ann Bostrom, School of Public Policy, Georgia Institute of Technology, Atlanta, GA, USA - Elena Gagliasso, Department of Philosophical and Epistemological Studies, University of Rome La Sapienza, Rome, ITALY - Dedre Gentner, Psychology Department, Northwestern University, Evanston, IL 60208, USA - Ronald N. Giere, Department of Philosophy, University of Minnesota, MN, USA - Mark L. Johnson, Department of Philosophy, 1295 University of Oregon, Eugene, OR, USA - Kenneth Knoespel, School of History, Technology, and Society, Georgia Institute of Technology, Atlanta, GA, USA - Lorenzo Magnani, Department of Philosophy, University of Pavia, Pavia, ITALY and School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, GA, USA - Pat Langley, Adaptive Systems Group, DaimlerChrysler Research & Technology Center, Palo Alto, CA, USA - Nancy J. Nersessian, School of Public Policy and College of Computing, Georgia Institute of Technology, Atlanta, GA, USA - Brian Norton, School of Public Policy, Georgia Institute of Technology, Atlanta, GA, USA - Claudio Pizzi, Department of Philosophy and Social Sciences, University of Siena, Siena, ITALY - Mario Stefanelli, Department of Computer Science, University of Pavia, Pavia, ITALY - Paul Thagard, Department of Philosophy, University of Waterloo, Waterloo, CANADA - Ryan D. Tweney, Bowling Green State University, Bowling Green, OH, USA - Stella Vosniadou, Department of Philosophy and History of Science, Brain and Cognitive Science Division, National and Capodistrian University of Athens, Athens, GREECE. LOCAL ORGANIZING COMMITTEE Riccardo Dossena (riki.dox@libero), Elena Gandini (elegand@yahoo.com), Rosella Gennari (gennari@hum.uva.nl), Lorenzo Magnani (lmagnani@cc.gatech.edu), Massimo Manganaro (triskel@worldonline.it), Stefania Pernice (stepernice@libero.it), Matteo Piazza (pimat@yahoo.com), Giulio Poletti (philosophia@libero.it) Stefano Rini (s.rini@philos.unipv.it), Andrea Venturi (aventuri@philos.unipv.,it) (Department of Philosophy, University of Pavia, Pavia, Italy), Mario Stefanelli (mstefa@ipvstefa.unipv.it) (Department of Computer Science, University of Pavia, Pavia, Italy). IMPORTANT ADDRESSES LORENZO MAGNANI (Conference Chair) School of Public Policy and College of Computing Program in Philosophy, Science, & Technology Georgia Institute of Technology, 685 Cherry Street Atlanta, GA, 30332 - 0345, USA Office: 404-894-9050 & 404-385-0884, Home: 404-875-3566 Fax: 404-385-0504 & 404-894-2970 Email: lorenzo.magnani@cc.gatech.edu Address in Italy: Department of Philosophy and Computational Philosophy Laboratory University of Pavia, Piazza Botta 6, 27100 Pavia, Italy Office: +39-0382-506283, Home: +39-0383-371067 Fax: +39-0382-23215 Email: lorenzo@philos.unipv.it CONFERENCE SITE: Collegio Ghislieri, Piazza Ghislieri, 27100 PAVIA, Italy, phone +39 0382 22044. The Conference is sponsored by UNIVERSITY OF PAVIA, ITALY GEORGIA INSTITUTE OF TECHNOLOGY, ATLANTA, GA, USA UNIVERSITY OF SIENA, ITALY UNIVERSITY OF ROME "LA SAPIENZA", ITALY, MURST (Ministero dell'Università e della Ricerca Scientifica e Tecnologica), ITALY, CARIPLO (CASSA DI RISPARMIO DELLE PROVINCIE LOMBARDE, MILAN, ITALY) HOW TO REACH PAVIA LINATE Airport: People arriving by plane at LINATE should take the bus to the CENTRAL STATION of Milan (cf below fron this Station to Pavia). In LINATE it could be convenient to take a Taxi because the airport is close to the center of Milan. Moreover, The bus company SGEA offers six runs from LINATE to Pavia at 9.00, 10.00, 12.00 AM and 2.00, 5.00, 8.30 PM. The last stop is Pavia, near the station (see again our updated web page for possible alterations of this time-table) (from Pavia to LINATE six runs at 5,00, 7.45, 10.00 AM, 1.00, 4.00, 6.00 PM) (one hour trip). In Pavia there is only one station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. MALPENSA 2000 and OLD MALPENSA Airports (usually people arrive to Malpensa 2000 and not to OLD MALPENSA): People arriving by plane at MALPENSA 2000 (also called MALPENSA 2000 Terminal 1) or at "old" MALPENSA (now called MALPENSA NORTH but also called Malpensa 2000 Terminal 2) should take the bus to the CENTRAL STATION of Milan. There is also a bus AND A TRAIN from Malpensa 2000 to the NORTH STATION (Piazzale Cadorna) of Milan, in this case from NORTH Station you will have to take the underground MM1 to the Central Station: trains to Pavia leave from Central station). Moreover, the bus company SGEA offers four runs from MALPENSA 2000 to Pavia at 9.00 AM, 1:30 PM, 5.00 PM, and 9:30 PM - from Malpensa North (OLD Malpensa or Malpensa 2000 Terminal 2 5 munutes later) (from Pavia to MALPENSA 2000 and to OLD MALPENSA four runs at 7.00 AM, 11:00 AM, 3.15 PM, and 7:00 PM) (one hour and half trip). The last stop is Pavia, near the station (see again our updated web page for possible alterations of this time-table) In Pavia there is only one station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. There are trains from MILAN (Central Station) to PAVIA and vice Versa about every an hour (routes: MILAN-GENOVA; MILAN-VENTIMIGLIA; MILAN-LA SPEZIA; MILAN-SAVONA; MILAN-SESTRI LEVANTE; MILAN-IMPERIA; MILAN-ALBENGA; Pavia is the first stop only if the train is not slow, that is, if it is not, in ITALIAN, "L", locale). In Pavia there is only one rail station. The easiest way to reach the center of the town is to get off at the station and than take the bus n. 3. ACCOMMODATION The WEB site of the Tourist Office is http://www.systemy.it/pavia/home.html (new! sorry, only in Italian). The email address is info@apt.pv.it. When available you will find the whole list of hotels and other information concerning Pavia and its history. See also http://www.itwg.com/ct_00036.asp. In case of accommodation problems remember we will have at our disposal some rooms at special "conference rates" in the Colleges of the University. For further information please contact the Program Chair. As the the conferences dates are very close to summer holidays we recommend making your reservations as early as possible and before March 31, 2000 at the latest. ALL ACCOMMODATIONS (EXCEPT FOR INVITED SPEAKERS) WILL BE PROCESSED BY: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy Phone: +39-0382-539565 Fax: +39-0382-539572 +39-0382-539504 email (only to request information): aloha@buonviaggio.it (cut here) ********************************************************************** ACCOMMODATION FORM - MBR'01 ---------------------------------------------------------------------- TO BE FAXED: +39-0382-539572 +39-0382-539504 OR MAILED: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy email (only to request information): aloha@buonviaggio.it ---------------------------------------------------------------------- FILL IN CAPITAL LETTERS, PLEASE LAST NAME:___________________FIRST NAME:_____________Prof./Dr./Mr./Ms. AFFILIATION/UNIVERSITY/DEPT.__________________________________________ STREET:_______________________________________________________________ TOWN:___________________________CODE:_____________COUNTRY:____________ PHONE:__________________FAX:__________________E-MAIL:_________________ TYPE OF TRAVELLING:__________________DATE OF ARRIVAL:_________________ DATE OF DEPARTURE:___________________NUMBER OF NIGHTS:________________ CREDIT CARD NUMBER AND TYPE__________________________ EXPIRATION_____________ (you can also pay by bank transfer and postal order, please see below) ACCOMMODATION INCL. BREAKFAST SINGLE ROOM+BATH. / DOUBLE ROOM+BATH. ***HOTEL EXCELSIOR, Piazza Stazione, PAVIA LIT. 100.000 / LIT. 150.000 ______________ (EUR. 51.64 / EUR. 77.46) ****HOTEL ARISTON, Via Scopoli, PAVIA LIT. 130.000 / LIT. 190.000 +_____________ (EUR. 67.13 / EUR. 98.12) ****HOTEL MODERNO, Viale V. Emanuele, PAVIA LIT. 170.000 / LIT. 230.000 +_____________ (EUR. 87.79 / EUR. 118.78) RESERVATION CHARGE LIT. 25.000 +_______ (EUR. 12.91) TOTAL AMOUNT: =_____________ ACCOMMODATION DEPOSIT: ONE NIGHT LIT......... - _____________ (EUR) ACCOMMODATION BALANCE: LIT......... =_____________ (EUR)........ Hotel Excelsior (from the station walk east) Hotel Moderno (from the station walk north) To reach Hotel Ariston take the bus n. 3 or taxi. ____________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *CREDIT CARD* BEFORE *15 MARCH 2001* TO: FAX: +39-0382-539572 +39-0382-539504 MAIL ADDRESS: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy email (only to request information): aloha@buonviaggio.it DATE OF PAYMENT____________YOUR SIGNATURE____________________ ________________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *BANK TRANSFER* BEFORE *15 MARCH 2001* (fax or mail also a copy of the bank transfer) TO: BANCA REGIONALE EUROPEA S.p.A.BRANCH PAVIA - SedeSWIFT BREUITM2 301Bank Code 6906.11301 Agenzia Viaggi ALOHATOUR S.r.l. Acc.n 19952/4 DATE OF PAYMENT____________YOUR SIGNATURE___________________ ________________________________________________________________________ PLEASE FAX OR MAIL THIS FORM AND PAY BY *POSTAL ORDER* BEFORE* 15 MARCH 2001* (fax or mail also a copy of the postal receipt) TO: Agenzia Viaggi ALOHATOUR Corso Cairoli 11 I - 27100 PAVIA Italy DATE OF PAYMENT______________________YOUR SIGNATURE______________________ _________________________________________________________________________ ALHOATOUR WILL MAIL OR FAX YOU THE RESERVATION VOUCHER ALOHATOUR WILL SATISFY THE REQUESTS AS FAR AS POSSIBLE. IF NOT POSSIBLE, ANOTHER SIMILAR ACCOMMODATION WILL BE ARRANGED.