Re: GHC anormaly

1998-07-22 Thread Sigbjorn Finne


Tommy Thorn writes:
  Thanks for the report - as a result of constant folding, the compiler
  ends up with an Int that is outside the representable range.  There's
  two ways of looking at this, I guess - one being that the constant
  folder should check boundaries before folding (good idea, but not
  currently done.) The other is that the above panic caught an integer
  overflow at compile-time for you - be happy :-)
 
 AAARRGGHH! I'm not.  GHC is _slightly_ excused by the fact that the
 whole Int story seems to be badly defined in Haskell, but I suppose
 modulo 2^32 arithmetic, thus overflow doesn't exist.  More seriously,
 the program works correctly in Hugs and with ghc without -O.  Adding
 -O should definitely not change the semantics.
 

Well, no such guarantee is made that overflows are handled that way
for Ints, so the compiler should warn you regardless of whether you
assume that property of Ints (or, as the case might be, not.)

Anyway, why do you bother doing (v - 65536*65536) in your code when
that is equal to v in modulo 2^32 arithmetic?

--Sigbjorn



Re: No select in LibPosix?

1998-07-22 Thread Sigbjorn Finne



Tommy Thorn writes:
 I'm trying to rewrite a small C program and stumbled into an apparent
 lack of select.  Is this an intentional omission?  Notice, that I need 

Yes, select()/poll() is not part of POSIX.1 (or POSIX.4). What's
really needed is a library that provides the bits that POSIX don't,
but is commonly supported on Unix platforms. So, what about providing
the following:

   hWaitForInputs :: [Handle] - Maybe Int - IO ()
-- Nothing; wait indefinitely.
-- Just n ; wait n msecs.

generalising the std IO operation?

 to wait on stdin and a socket.  In Unix both of these are file
 discriptors, but the Socket library seems to talk about PortID.
 

PortIDs are a higher level type that classifies the different kinds of
connections made over sockets. Use one of the IO.Handles you get back
from the socket operations (or SocketPrim.socketToHandle) together
with Posix.handleToFd to get at the file descriptors.

It really shouldn't be necessary to go via Handles for this though, so
I'll add an operation in SocketPrim to get the file descriptor
straight from a Socket.

--Sigbjorn



Re: mkdependHS-?.??

1998-07-22 Thread Simon Marlow

Alex Ferguson [EMAIL PROTECTED] writes:

 Hi guys.  It recently struck me (with concommitant pain) that it'd be
 useful if the ghc install script put "versioned" copies (or links)
 to _all_ the executables, as it currently does with ghc/ghc-3.02.
 This is certainly true of mkdependHS, where the ghc-3ish version is
 of no use to someone working with a ghc-2.10 (say) program...

What's wrong with using 'ghc-3.02 -M' for dependencies, and 'ghc-2.01'
for compiling, if you really want to keep 2.10 around?

You could argue that mkdependHS should go in the lib directory, since
there's no need to call it directly anymore.  I'd buy that.

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: GHC licence

1998-07-22 Thread Fergus Henderson

On 21-Jul-1998, Hans Aberg [EMAIL PROTECTED] wrote:
 At 10:38 +0100 98/07/21, Simon L Peyton Jones wrote:
  Do you mean "public domain" literally, i.e. are you renouncing all
  copyright?  (The source code contains copyright notices, but no
  licence, as far as I can see.)
 
 No I am not renouncing all copyright.  By "public domain" I mean freely
 available for anyone to use for any purpose other than making money
 by selling the compiler itself.  That isn't a formal definition,
 but I'm sure you see the intent.
 
   The wording "public domain" is not a legal or otherwise well-defined
 concept,

IANAL, but I believe the phrase "public domain" is a well-defined concept.
It does not mean why Simon L Peyton Jones means by it, though.
If something is public domain, then anyone can use it for anything.

 so the advice to anybody writing publicly distributed software is
 claim the copyright, and then specify what rules there should be for its
 use.

Yes, indeed.  Copyright law forbids anyone from copying software without the
copyright owner's permission (except for certain specific circumstances,
e.g. "fair use").

   But the conditions should be spelled out in the copyright notice, I think.

Definitely.

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





Re: GHC licence

1998-07-22 Thread Fergus Henderson

On 21-Jul-1998, Hans Aberg [EMAIL PROTECTED] wrote:
 At 23:28 +1000 98/07/21, Fergus Henderson wrote:
 I ANAL, but I believe the phrase "public domain" is a well-defined concept.
 It does not mean why Simon L Peyton Jones means by it, though.
 If something is public domain, then anyone can use it for anything.
 
   I recall from the eighties about what wordings like "public domain",
 "free-ware" etc really meant, and it turned out that people meant different
 things.
 
   So to be one the sure side, I think ine should the wording "This software
 is public domain, that is, ...", spelling it out.
 
   (By the way, what does the "I ANAL" you use mean?)

IANAL stands for "I am not a lawyer".

(The space between the "I" and "A" was a typo.)

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





Re: Lisence [was: Fw: Could Haskell be taken over by Microsoft?]

1998-07-22 Thread Manuel M. T. Chakravarty

From: Dinesh Vadhia [EMAIL PROTECTED]
Subject: Fw: Could Haskell be taken over by Microsoft?
Date: Tue, 21 Jul 1998 14:49:07 -0700

[...]
 The situation would change dramatically if say, a Microsoft, picked it up
 and ran with it.  But they wouldn't do it unless they had full control over
 the language which the Haskell community wouldn't allow.
 
 On the other hand, Haskell could follow the Linux route with a GNU license.
 No problem with this except how many customers are seriously going to take
 the leap of faith.  It is a sad fact of life that the majority of the "real"
 market consists of conservative customers who look for a number of
 (non-product) things from a technology component including supplier status,
 pricing, support, and so on.  Having a a number of small companies providing
 Haskell support won't cut the mustard in the real 'big' world.
 
[...]

 If the Haskell community wants Haskell to be a significant product in the
 computer language and software development markets then the only route open
 is to setup a company whose sole purpose is that ... Everything else (for
 the Haskell community) is just wishful thinking.

I don't believe this.  Look at Perl.  It is distribute by
the "Artistic License" and I think everybody on this list
would be happy if Haskell had only a tenth of the popularity
of Perl.  (Even GHC's compiler driver is written in Perl ;-)

Cheers,

Manuel





Re: avoiding repeated use of show

1998-07-22 Thread Simon L Peyton Jones

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

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

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


 So I tried creating my own Stringable class:
  class Stringable a where
   toString::a - String
 
  (./) :: (Stringable a,Stringable b)= a-b-String
  x./y = (toString x)++(toString y)
 
 The trouble is that when I try doing things like:
 
  res = (2+2) ./ " hello"
 
 I get an "Unresolved top-level overloading" error.

 Is there any way to convince Haskell to just resolve these numbers to
 SOMETHING by default?  Then I can just declare that type an instance of
 Stringable.

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

(Stringable a, Num a)

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

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

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

instance Stringable Int where
   toString n = "Urk!"

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

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

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

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

Simon 






Re: GHC licence

1998-07-22 Thread michael

CC: Simon L Peyton Jones [EMAIL PROTECTED]


I do think that the GNU license would be a mistake -- as I understand, it   
would prevent the use of GHC in commercial projects, and I'm pretty sure   
that's something Simon wants to *encourage*.

 --
From:  jfk
Sent:  21 July 1998 20:20
To:  Simon L Peyton Jones [EMAIL PROTECTED]; [EMAIL PROTECTED];   
[EMAIL PROTECTED]
Subject:   Re: GHC licence (was Could Haskell be t


Simon L Peyton Jones wrote:

  Simon L Peyton Jones wrote:

  Do you mean "public domain" literally, i.e. are you renouncing all
  copyright?  (The source code contains copyright notices, but no
  licence, as far as I can see.)

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

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

It might be a good idea to publish GHC under the GNU Public License or
something similar. It grants everybody the right to use the software for
any purpose, including making extensions or modifications of it - as long
as the "derived work" is published under GPL as well. This ensures that   
no
company can take the product, make some small modifications to it and   
call
it their own. Whatever you choose to do, I think you need to be more
explicit about which rights you grant the users of GHC to avoid unwanted
use/misuse by anyone.

regards,

Joergen






instances of types. Reply.

1998-07-22 Thread S.D.Mechveliani

S. Alexander Jacobson [EMAIL PROTECTED]  wrote

 Haskell doesn't seem to allow

 instance Num (Int-Int) where ...
 or
 instance Stringable String where ...

How come?

PS I am sure this has been discussed before, but I missed it...


First, Num, needs Eq to be defined. Consider

   module T where
   instance Eq  (Int-Int) where  f==g = (f 0)==(g 0)
   instance Num (Int-Int) where  f+g  = \x-(f x)+(g x)

Second, some compilers say at this:
"
(the instance type must be of form (T a b c)
where T is not a synonym, and a,b,c are distinct type variables)
"
Maybe, they treat  Int Int  as a repeated variable?
At least, we may try to use some extension of Haskell-1.4.
For example in ghc, it helps  -fglasgow-exts.

--
Sergey Mechveliani
[EMAIL PROTECTED]










Re: Scoped typed variables.

1998-07-22 Thread Simon L Peyton Jones

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

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

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

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


Simon





RE: Scoped typed variables.

1998-07-22 Thread Mark P Jones

| Michael suggested
| 
|  f :: [a] - c
|  f xs = if len  fromInteger 3 then len else 0
|   where
| len :: c
| len = length xs
| 
| This relies on the 'c' from the type signature scoping over
| the definition, which is on alternative notation for scoped
| type variables.

Hmm, interesting.  Perhaps we need to allow type annotations on
left hand sides as well as embedded in patterns:

  f xs :: c = ...

I know it looks a bit ugly ... add a few more parens and it
starts to remind me of Pascal! :-)

All the best,
Mark






Re: avoiding repeated use of show

1998-07-22 Thread Ralf Hinze

 I would like to avoid using show all the time for printing strings e.g.
 
  val = "the sum of 2 and 2 is "++(show $ 2 + 2)++" whenever."
 
 I would prefer to type something like:
 
  val = "the sum of 2 and 2 is "./(2+2)./" whenever." 
  -- i can' find a better haskell compatible operator
 
 I can't simply "show" the arguments of (./) because showing strings adds
 quotation marks which I don't want in this context.
 
 So I tried creating my own Stringable class:
  class Stringable a where
   toString::a - String
 
  (./) :: (Stringable a,Stringable b)= a-b-String
  x./y = (toString x)++(toString y)

Nice idea. I polished the code somewhat ...

===

 infixr 0 

What about `' for catenation?

 toString  :: (Stringable a) = a - String
 toString a=  toStrings a ""

 class (Show a) = Stringable a where
 toStrings :: a - ShowS
 toStringList  :: [a] - ShowS

 toStrings =  shows
 toStringList []   =  showString "[]"
 toStringList (a : as) =  showChar '[' . toStrings a . showl as
 where showl []=  showChar ']'
   showl (a : as)  =  showString ", " . toStrings a . showl as

The class `Stringable' uses the `ShowS' mechanism to avoid quadratic
time behavior and employs the standard trick to allow overlapping
instances (Eric Meijer has written a short note about that topic):
[Char] and [a] should be treated differently.

 instance Stringable Char where
 toStringList s=  showString s

This instance declaration print strings as they are ...

 instance Stringable Int

 instance Stringable Integer

 instance Stringable a = Stringable [a]  where
 toStrings =  toStringList

 instance Stringable ShowS where
 toStrings =  id

This instance declaration is necessary to make `' useable. Note that
this is not (Standard) Haskell but works only with Hugs 1.3c (and
probably with GHC's next release).

 ()   :: (Stringable a, Stringable b) = a - b - ShowS
 a  b =  toStrings a . toStrings b

Note that `' yields `ShowS' and not `String'.

 val = "the sum of 2 and 2 is "  (2 + 2 :: Int)  " whenever."

Furthermore note that `val' has type `ShowS'. If quadratic time
behaviour is not a problem (does not occur?) you can safely omit the
`Stringable ShowS' instance and change `' to `toString a ++ toString b'.

 render:: (Stringable a) = a - IO ()
 render a  =  putStr (toString a)

`render' is quite flexible:

? render val
the sum of 2 and 2 is 4 whenever.
? render (toString "aaa")
aaa
? render "aaa"
aaa
? render (toStrings "aaa")
aaa

===

 Is there any way to convince Haskell to just resolve these numbers to
 SOMETHING by default?  Then I can just declare that type an instance of
 Stringable.

Unfortunately not. I did not succeed in persuading SPJ ;-). See

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

HTH, Ralf





RE: Scoped typed variables.

1998-07-22 Thread Alex Ferguson


Hi Mark (and all).

 I think the way that Hugs 1.3c handles it would meet your goals.  All that
 it requires is a strict extension to the syntax for patterns to allow type
 annotations.  These can be useful in their own right, but also can be
 applied to problems like the one that you gave:
 
   f :: [a] - a - [a]
   f ((x::a):xs) y = g y
  where
g :: a - [a]
g q = [x,q]

AKA "Proposal A" in SPJ's recent message on this topic:

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

I think "A" is fine, it's "B" (and hence, SPJ's Composite Motion, A+B)
that worries me, for the reasons I alluded to.  If "beefed up A"
does the job, I'm equally happy as with a more conservation syntax for
"B".


 In recent discussions with Simon, we discovered that
 this approach also works better if existential types are included in the
 language.

That makes at least intuitive sense to me (a "monomorphic type varible"
_is_ some sort of existential quantification, isn't it, in at least some
vague, hand-wavey way?) -- could you expand a little on the details of
this, though?

Slainte,
Alex.





Re: GHC licence

1998-07-22 Thread Bob Hutchison

On Wed, 22 Jul 1998 08:51:47 GMT, you wrote:

CC: Simon L Peyton Jones [EMAIL PROTECTED]


I do think that the GNU license would be a mistake -- as I understand, it   
would prevent the use of GHC in commercial projects, and I'm pretty sure   
that's something Simon wants to *encourage*.


There are *two* GNU licenses. The GPL is meant for tools, like GHC, and
would prevent certain uses of GHC. There is a second GNU license for
libraries, called LGPL, and this is important. The runtime components of
GHC should be licensed using the library license (just like the GNU
runtimes are). Using both licenses appropriately would allow for the use
of GHC in commercial software (as long as GHC itself was not included).
Any improvements GHC or its runtime would still have to be made public
by the commercial entity.

For example, Tower Eiffel has use GNU compilers for some time. The
runtime libraries of GNU compilers are protected by the library license.
Yet Tower Eiffel is certainly used for commercial products.

Cheers,
Bob
---
Bob Hutchison, [EMAIL PROTECTED], (416) 760-0565
([EMAIL PROTECTED] until INTERNIC fixes problems)
RedRock, Toronto, Canada





Re: avoiding repeated use of show

1998-07-22 Thread S. Alexander Jacobson

On Wed, 22 Jul 1998, Ralf Hinze wrote:
 What about `' for catenation?

I would be more inclined to use .  The reason is typing efficiency.
'' is awkward to be typing frequently immediately after '"'.

You are acutally using (.) below.  Is there a way to do that (via
Fran like lifting?)?
 
  instance Stringable ShowS where
  toStrings   =  id
 
 This instance declaration is necessary to make `' useable. Note that
 this is not (Standard) Haskell but works only with Hugs 1.3c (and
 probably with GHC's next release).

Why does this instance declaration require 1.3c?  Also, are there
substantive differences between Hugs 1.3c and GHC 3.3?  Are people
prototyping w/ 1.3c and then planning to build with the next GHC?

  () :: (Stringable a, Stringable b) = a - b - ShowS
  a  b   =  toStrings a . toStrings b
 
 Note that `' yields `ShowS' and not `String'.
 
  val = "the sum of 2 and 2 is "  (2 + 2 :: Int)  " whenever."

 Furthermore note that `val' has type `ShowS'. If quadratic time
 behaviour is not a problem (does not occur?) you can safely omit the
 `Stringable ShowS' instance and change `' to `toString a ++ toString b'.

I am not understanding this last bit.  Can you explain further?
 
 `render' is quite flexible:
 
 ? render val
 the sum of 2 and 2 is 4 whenever.
 ? render (toString "aaa")
 aaa
 ? render "aaa"
 aaa
 ? render (toStrings "aaa")
 aaa

Very cool.  Thank you.
 
 ===
 
  Is there any way to convince Haskell to just resolve these numbers to
  SOMETHING by default?  Then I can just declare that type an instance of
  Stringable.
 
 Unfortunately not. I did not succeed in persuading SPJ ;-). See
 
 http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Display.cgi?id=445

It sounds like he just wants more votes for this change.  I just added
mine (for whatever thats worth :-))

-Alex-

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





Re: GHC licence

1998-07-22 Thread Tony Finch

[EMAIL PROTECTED] wrote:

I do think that the GNU license would be a mistake -- as I understand, it   
would prevent the use of GHC in commercial projects, and I'm pretty sure   
that's something Simon wants to *encourage*.

The GPL explicitly allows commercial use. The commercially problematic
aspect of the GPL is that derived versions of GPLed software must be
distributed with source (and all the intellectual property exposed).
This does not propagate to works created using GPLed software.

Tony.
-- 
F.A.N.Finch  [EMAIL PROTECTED]
[EMAIL PROTECTED]   +44-7970-401-426
"Plenty more letters in the alphabet"





RE: Scoped typed variables.

1998-07-22 Thread Mark P Jones

Hi Alex,

|  I think the way that Hugs 1.3c handles it ...
| ...
| AKA "Proposal A" in SPJ's recent message on this topic:
|
| http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Display.cgi?id=274

Exactly, although I hadn't been referring to that at the
time.  The only negative point for proposal A listed there
is that:  "Can't capture variables appearing within type contexts".
I don't actually see why this is needed.

| it's "B" (and hence, SPJ's Composite Motion, A+B)
| that worries me, for the reasons I alluded to.

I share your concerns!

|  In recent discussions with Simon, we discovered that
|  this approach also works better if existential types are included in the
|  language.
|
| That makes at least intuitive sense to me (a "monomorphic type
| varible" _is_ some sort of existential quantification, isn't it,
| in at least some vague, hand-wavey way?) -- could you expand a
| little on the details of this, though?

Sure.  I think I can see where you're headed with your comments,
but I actually meant something else.  Specifically, if you allow
datatypes like:

data Twee = forall a. MkTwee (a - Int) a

where the a parameter is locally quantified, and you write functions
like:

f (MkTwee g u) = ...

then you can use a type annotation such as:

f (MkTwee g (u::a)) = ...

if you want to refer to the type of the existentially quantified
variable in the body of f.  There's no way to name that type with
the B proposal alone.

Hope that clears things up!

Mark





RE: Re: Scoped typed variables.

1998-07-22 Thread Mark P Jones

Ok, back to the main list we go!

| But the problem is that I need the type name c inside the body of
| the function!  I'm assuming always that I can solve a typeing
| problem by adding an explicit type signature wherever it's needed;
| however, that implies that I need to be able to get at the type
| names.

I was replying to your suggestion that you needed the extra line
to specify the context (Num c).  Yes, I agree that you might need
a way to name the result type c.  That can be handled in the way
we discussed earlier:  f xs :: c = ...  But why do you think that
you need some way to write down the context too?  I don't think
you do!

All the best,
Mark





Re: avoiding repeated use of show

1998-07-22 Thread Ralf Hinze

| I would be more inclined to use .  The reason is typing efficiency.
| '' is awkward to be typing frequently immediately after '"'.

I do not type that fast ;-).

| You are acutally using (.) below.  Is there a way to do that (via
| Fran like lifting?)?

I'm afraid no.

|   instance Stringable ShowS where
|   toStrings =  id
|  
|  This instance declaration is necessary to make `' useable. Note that
|  this is not (Standard) Haskell but works only with Hugs 1.3c (and
|  probably with GHC's next release).
| 
| Why does this instance declaration require 1.3c?  Also, are there
| substantive differences between Hugs 1.3c and GHC 3.3?  Are people
| prototyping w/ 1.3c and then planning to build with the next GHC?

Haskell requires that the instance head is of the form C a1 ... ak
where ai are type variables. However, the code _does_ work with GHC 3.2
if the flag `-fglasgow-exts' is on (sorry for the incomplete
information).

|   ()   :: (Stringable a, Stringable b) = a - b - 
|ShowS
|   a  b =  toStrings a . toStrings b
|  
|  Note that `' yields `ShowS' and not `String'.
|  
|   val = "the sum of 2 and 2 is "  (2 + 2 :: Int)  " whenever."
| 
|  Furthermore note that `val' has type `ShowS'. If quadratic time
|  behaviour is not a problem (does not occur?) you can safely omit the
|  `Stringable ShowS' instance and change `' to `toString a ++ toString b'.
| 
| I am not understanding this last bit.  Can you explain further?

Well. If you change () to

 ()  :: (Stringable a, Stringable b) = a - b - String
 a  b=  toString a ++ toString b

and make nested calls to () you may experience quadratic time
behaviour. The standard example involves printing a tree:

 data Bush a   =  Leaf a | Fork (Bush a) (Bush a)
  deriving (Show)

 lay   :: (Stringable a) = Bush a - String
 lay (Leaf a)  =  "(Leaf "  a  ")"
 lay (Fork l r)=  "(Fork "  lay l  lay r  ")"

Simply try

lay $ leftist [1 .. 1 :: Int]

where leftist is defined as follows.

 leftist   =  foldl1 Fork . map Leaf

BTW With the original definition of () it is quite easy to make
`Bush' an instance of `Stringable'.

 instance (Stringable a) = Stringable (Bush a) where
 toStrings (Leaf a)=  "(Leaf "  a  ")"
 toStrings (Fork l r)  =  "(Fork "  l  r  ")"

Maybe cunning, but I like it ;-).

Ralf





Re: Could Haskell be taken over by Microsoft?

1998-07-22 Thread Erik Meijer


-Original Message-
From: Wolfgang Beck [EMAIL PROTECTED]
To: [EMAIL PROTECTED]
Date: Tuesday, July 21, 1998 10:14 AM
Subject: Re: Could Haskell be taken over by Microsoft?



Step 1: MS introduces Haskell with all their marketing power

Step 2: VisualBasic programmers switch to Haskell after having
 read about Haskell in all those colorful magazines.

Step 3: As they don't understand the concept of functional
 languages, they complain about it. MS 'improves'
 Haskell by adding C-like constructs and variable
 assignments to the language.  It is now neither C nor
 functional, but they love it (not the member of this
 list I suppose).

Stop dreaming and let's get back to work. Microsoft is NOT 
interested in Haskell; they already have a functional language
that satisfies step 3: JScript, used in more web pages than Java
and soon taking over VB in Outlook98 and Visual Studio.

http://www.microsoft.com/Scripting/JScript/Jslang/jsobjFunction.htm.
http://premium.microsoft.com/msdn/library/periodic/period98/html/mind0498rs.htm

 Look what they have done to HTML, and you know what I mean.

What's wrong with DHTML? Netscape has done the same, but slightly
different.







Re: Scoped typed variables.

1998-07-22 Thread Alex Ferguson


Hi Jeff.

  http://www.cs.chalmers.se/~rjmh/Haskell/Messages/Display.cgi?id=274
 
  I think "A" is fine, it's "B" (and hence, SPJ's Composite Motion, A+B)
  that worries me, for the reasons I alluded to.  If "beefed up A"
  does the job, I'm equally happy as with a more conservation syntax for
  "B".

 Just as a sanity check, following an augmented proposal "A" where we can also
 annotate the return type as well, consider these:
 
 f :: a - (a - a) - a
 f x = \g - (g :: a - a) x
 
 f (x :: a) :: (a - a) - a = \g - (g :: a - a) x
 
 Which of these two is correct, and why?  Why not both?

Under "A+B", these would be equivalent.  Under "A++" (Mark's original
"A", only, plus the return types), the second of these is "correct"
(assuming a restricted interpretation of "a" is what was intended), but
in the first, the a's in sig and body are bound quite separately, so the
local type annotation would be too general.

Slainte,
Alex.





Re: instances of types.

1998-07-22 Thread Alex Ferguson


Sergey Mechveliani writes:
 Second, some compilers say at this:
 "
 (the instance type must be of form (T a b c)
 where T is not a synonym, and a,b,c are distinct type variables)
 "
 Maybe, they treat  Int Int  as a repeated variable?

Not quite, Int isn't a type variable at all, but an actual type.
Basically it's disallowing instance heads more than one type
constructor deep.  So for example, "instance C (T Int Char)" would
also be disallowed.

It isn't necessary for this to be anything like this restrictive, of
course, but basically it's (a sledgehammer) to enforce (the nut of)
non-overlap of instances.

SPJ et al proposed relaxing this for [Standard] Haskell [2.0],
and ghc will allow the more general cases with -fgla-exts, provided
the instances don't _actually_ overlap.  (Older versions of ghc
(3.00?) allow some overlap, too)

Slainte,
Alex.





Re: Scoped typed variables.

1998-07-22 Thread Alex Ferguson


Jeff Lewis:
 I'm not sure what the parenthetical comment about the interpretation of a 
means -
 take the definition at face value.

My point was: were they _intended_ to be same "a", or different?  What
is "face value" is surely simply begging the question.


 It's not at all clear to me that people should expect the a's to be
 different - I can't think of a good rationale for it (aside from the "don't 
break
 old code" argument, which, if that's the only argument, doesn't seem strong 
enough
 to me).

For Standard Haskell at least, it ought to be a pretty strong argument.

I don't accept that the "a"'s being different is bizarre and inexplicable
 -- up until the discussion of wanting to write these more restricted
types, I'd certainly never heard any criticism of it on those grounds.
Signatures and definitions were simply regarded as having quite separate
scopes.

Slainte,
Alex.





Re: Scoped typed variables.

1998-07-22 Thread Jeffrey R. Lewis

Alex Ferguson wrote:

  I think the way that Hugs 1.3c handles it would meet your goals.  All that
  it requires is a strict extension to the syntax for patterns to allow type
  annotations.  These can be useful in their own right, but also can be
  applied to problems like the one that you gave:
 
f :: [a] - a - [a]
f ((x::a):xs) y = g y
   where
 g :: a - [a]
 g q = [x,q]

 AKA "Proposal A" in SPJ's recent message on this topic:

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

 I think "A" is fine, it's "B" (and hence, SPJ's Composite Motion, A+B)
 that worries me, for the reasons I alluded to.  If "beefed up A"
 does the job, I'm equally happy as with a more conservation syntax for
 "B".

Just as a sanity check, following an augmented proposal "A" where we can also
annotate the return type as well, consider these:

f :: a - (a - a) - a
f x = \g - (g :: a - a) x

f (x :: a) :: (a - a) - a = \g - (g :: a - a) x

Which of these two is correct, and why?  Why not both?

Next check.  Consider these:

f g = ... (g :: a - a) ...
f (g :: a - a) = ... g ...

Which of these is correct, and why?  Why not both?

--Jeff





Re: Scoped typed variables.

1998-07-22 Thread Jeffrey R. Lewis

Ralf Hinze wrote:

 One could also argue that the culprit is Haskell's interpretation of
 type variables of which Report (p. 34) says: `[...] the type variables
 in a Haskell expression are all assumed to be universally quantified
 [..]'. Here is an even more irritating list of possibilities ...

 and so forth ... A solution could be to consider the type variables
 universally quantified at the _outermost_ possible level (currently
 it's the innermost). So `f e1 ... en = e' means `forall a1 .. am.f e1
 ... en = e' where the `ai's are the type variables occuring free in the
 definition. If we had explicit syntax for universal quantification
 (which I consider absolutely necessary) the former interpretation could
 be recovered using explicit quantifiers: ... (f :: forall a.a - a)
 ...


  This sounds great, but it could break old code, of course.  This would have a
different type under Ralf's proposal than Haskell 1.4:
(id :: a - a, id :: a - a)
However, I think something like it is the only sane way to go.  Whatever we do, type
variables should scope consistently.  With proposal "A" as is (such that it wouldn't
break old code, and just like in hugs 1.3c), a type variable would scope differently if
it was in a pattern verses being in an expression.  Ralf's proposal fixes that nicely,
and I don't think the cost in old code here would be very high.

--Jeff





Re: Fw: Could Haskell be taken over by Microsoft?

1998-07-22 Thread Jorgen Frojk Kjaersgaard

Dinesh Vadhia wrote:

 The recent thread of notes to "Could Haskell be taken over by Microsoft?"
 bears out what I've been thinking over the past year about Haskell which is
 ... "How on Earth is this Haskell stuff, not withstanding its merits, ever
 going to make it in the real world?".  From what I've read and seen I really
 see Haskell as nothing more than another 'interesting' computer language but
 ultimately confined to the academic/research community.

 The situation would change dramatically if say, a Microsoft, picked it up
 and ran with it.  But they wouldn't do it unless they had full control over
 the language which the Haskell community wouldn't allow.

Every popular language, except Java, is in some respect "public domain". The
language definitions of C, C++, Modula-2, Oberon, Pearl, you name it, are all
public domain and not under control of a single company but by a commission or
a group of researchers. These languages have good public domain implementations
as well. I do believe that a language must be public domain and have public
domain implementations to gain success in the long run. Being public domain
makes a language accessible to everybody from students and hobbyists to large
corporations. I know a company that works for military (NATO and the DoD) that
changed from Ada to C++ solely because they could get the Gnu C++ compiler for
free for all their supported platforms. Few languages can do without commercial
implementations, though,  since there are companies that will not use a PD
compiler for their work. We need the best of both worlds.

 On the other hand, Haskell could follow the Linux route with a GNU license.
 No problem with this except how many customers are seriously going to take
 the leap of faith.  It is a sad fact of life that the majority of the "real"
 market consists of conservative customers who look for a number of
 (non-product) things from a technology component including supplier status,
 pricing, support, and so on.  Having a a number of small companies providing
 Haskell support won't cut the mustard in the real 'big' world.

I think you seriously underestimate the GNU/Linux world. The GNU C and C++
compilers are probably the most popular compilers in the world. It's hard to
prove, but I don't think C++ had gained its very large popularity had it not
been for its PD definition and its good PD implementations.

I believe it is possible to make Haskell very popular if we focus more on its
practical use. We should focus more on developing libraries for "everyday
programming" and on improving code quality. Sure, it will benefit Haskell if a
commercial company develops libraries and more optimized compilers, but we, the
Haskell community, could also do it ourselves if more people got involved, also
outside the universities. The Linux community has shown that an OS can be built
by a large number of volunteers, so why not a compiler, development environment
and library?

 If the Haskell community wants Haskell to be a significant product in the
 computer language and software development markets then the only route open
 is to setup a company whose sole purpose is that ... Everything else (for
 the Haskell community) is just wishful thinking.

Can you mention any example of a company that has been established to maintain
a programming language, except JavaSoft, which can exist only because it is
sponsored by Sun?

regards, Joergen

--

Joergen Froejk Kjaersgaard
Systems Engineer, Informaticon Systemeering
...Linux - for freedom of choice... www.linux.org







Re: Scoped typed variables.

1998-07-22 Thread Ralf Hinze

|   Just as a sanity check, following an augmented proposal "A" where we can also
|   annotate the return type as well, consider these:
|  
|   f :: a - (a - a) - a
|   f x = \g - (g :: a - a) x
|  
|   f (x :: a) :: (a - a) - a = \g - (g :: a - a) x
|  
|   Which of these two is correct, and why?  Why not both?
| 
|  Under "A+B", these would be equivalent.  Under "A++" (Mark's original
|  "A", only, plus the return types), the second of these is "correct"
|  (assuming a restricted interpretation of "a" is what was intended), but
|  in the first, the a's in sig and body are bound quite separately, so the
|  local type annotation would be too general.
| 
| 
| I'm not sure what the parenthetical comment about the interpretation of a means -
| take the definition at face value.
| 
| I should have been more explicit - I'm interested not in why the first one would
| be incorrect, but how, for example, you would explain that to someone learning
| Haskell.  It's not at all clear to me that people should expect the a's to be
| different - I can't think of a good rationale for it (aside from the "don't break
| old code" argument, which, if that's the only argument, doesn't seem strong enough
| to me).

One could also argue that the culprit is Haskell's interpretation of
type variables of which Report (p. 34) says: `[...] the type variables
in a Haskell expression are all assumed to be universally quantified
[..]'. Here is an even more irritating list of possibilities ...

rapply  :: a - (a - a) - a
rapply a f  =  f a
rapply (a :: a) f   =  f a
rapply a (f :: a - a)  =  f a
rapply a f :: a =  f a
rapply a f  =  (f :: a - a) a
rapply a f  =  f (a :: a)
rapply a f  =  f a :: a

rapply a=  \f - f a
rapply (a :: a) =  \f - f a
rapply a:: (a - a) - a=  \f - f a
rapply a=  \(f :: a - a) - f a
rapply a=  \f - f a :: a

and so forth ... A solution could be to consider the type variables
universally quantified at the _outermost_ possible level (currently
it's the innermost). So `f e1 ... en = e' means `forall a1 .. am.f e1
... en = e' where the `ai's are the type variables occuring free in the
definition. If we had explicit syntax for universal quantification
(which I consider absolutely necessary) the former interpretation could
be recovered using explicit quantifiers: ... (f :: forall a.a - a)
...

Ralf

PS: I don't like the scope-mixture of type signatures and definitions.





Fw: Could Haskell be taken over by Microsoft?

1998-07-22 Thread Dinesh Vadhia

This note from Simon says it all precisely and what I alluded to in my
earlier note ...

Dinesh


-Original Message-
From: Simon Marlow [EMAIL PROTECTED]
To: [EMAIL PROTECTED] [EMAIL PROTECTED]
Cc: Jorgen Frojk Kjaersgaard [EMAIL PROTECTED]; [EMAIL PROTECTED]
[EMAIL PROTECTED]
Date: Wednesday, July 22, 1998 3:43 AM
Subject: Re: Could Haskell be taken over by Microsoft?


Marko Schuetz [EMAIL PROTECTED] writes:

 If they find (economic) interest in the language I am sure they will
 try to take over control of the language in their typical
 way, as they have done or tried to do with numerous technologies (Java
 being the most recent), by:

 - 'technical enhancement': that is introducing some features into
   Haskell and omitting/changing some others, while continuing to call
   it Haskell

 - 'bundling': connecting this MS-Haskell to some widespread software
   eg IE, making that software refuse to properly execute the majority
   of non-MS-Haskell programs.

Let's face it, this would be better than the situation we have now,
with only a handful of people worldwide who get paid to actively
develop Haskell compilers.  As a result, I can count the number of
good Haskell compilers on the fingers of half a hand.  And even those
don't have a decent GUI or development environment.  Ok, us hackers
are happy to use emacs, but that's not going to cut it in the real
world.

IMO, Haskell suffers too much from being a research vehicle.  I
believe the emphasis should be less on "let's protect our beautiful
language" and more on developing great tools and actually making the
thing *usable* for real-world tasks.  Languages don't get anywhere on
elegance alone.  Sad but true.

Cheers,
Simon

BTW, I'm moving to Microsoft too.

--
Simon Marlow [EMAIL PROTECTED]
University of Glasgow http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key