Re: [Haskell-cafe] Begginer question

2005-01-06 Thread Jules Bean
On 6 Jan 2005, at 01:37, Maurício wrote:
import Complex;
complex_root :: (Float, Float, Float) - (Complex Float, Complex Float)
complex_root (a,b,c) = (x1,x2) where {	
	delta = b * b - 4 * a * c :: Float;
	sqr_delta = if delta = 0 then (sqrt delta) :+ 0 else 0 :+ (sqrt 
delta) :: (Complex Float);
	x1 = (b + sqr_delta)/(2 * a);
	x2 = (b - sqr_delta)/(2 * a);
}

Couldn't match `Float' against `Complex Float'
Expected type: Float
Inferred type: Complex Float
In the second argument of `(+)', namely `sqr_delta'
In the definition of `x1': x1 = (b + sqr_delta)

  Can you help me finding what is wrong? Shouldn't b be converted to 
Complex Float and be summed to sqr_delta?

Haskell will not automatically convert b from Float to Complex Float. 
The arguments of (+) should have the same type.

One alternative is to use b :+ 0 instead of b. (and similarly for a).
Another approach is to define a 'cast' function like:
toComplex x = (fromRational.toRational) x :: Complex Float
and then you can use toComplex b instead of b :+ 0.  that's more 
characters to type, though...

Note that sqr_delta isn't going to be defined as you expect, either. 
Since delta has type Float, sqrt delta has type Float. (And sqrt -1 :: 
Float is Not A Number). If you want to do it by hand this way, then you 
want:

sqr_delta = if delta = 0 then (sqrt delta) :+ 0 else 0 :+ (sqrt 
(-delta)) :: (Complex Float);
If delta was itself already Complex, then sqrt would do the right thing 
automatically.

Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Begginer question

2005-01-06 Thread Ketil Malde
Maurício [EMAIL PROTECTED] writes:

 complex_root :: (Float, Float, Float) - (Complex Float, Complex Float)
 complex_root (a,b,c) = (x1,x2) where {
   delta = b * b - 4 * a * c :: Float;
   sqr_delta = if delta = 0 then (sqrt delta) :+ 0 else 0 :+
   (sqrt delta) :: (Complex Float);
 
   x1 = (b + sqr_delta)/(2 * a);
   x2 = (b - sqr_delta)/(2 * a);
 }

 Couldn't match `Float' against `Complex Float'
  Expected type: Float
  Inferred type: Complex Float
  In the second argument of `(+)', namely `sqr_delta'
  In the definition of `x1': x1 = (b + sqr_delta)

The error message says it all, really.

If you examine the definition of x1, you see that (+) is applied to
two variables.  If you check these, you will discover that they have
different types, which is the cause of the error.  

Note that Haskell doesn't automatically convert arguments for you --
this is a feature.  

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Utility functions

2005-01-06 Thread Simon Marlow
On 30 December 2004 05:25, Philippa Cowderoy wrote:

 On Wed, 29 Dec 2004, John Goerzen wrote:
 
 But like I've said, I am willing to negotiate with people that
 require code under a license that lets them use it without releasing
 the code. I have also stated that I will put any part of the code
 I've written under the fptools license if that code will be added to
 fptools.  (I perceive that as a greater good than license pragmatism
 in this instance.)
 
 This is the bit I was worried about, the idea of GPLed library code in
 fptools disturbs me somewhat.

There are already a couple of bits of (L)GPL under fptools: GMP and
readline.  GMP we'd like to replace because it is necessarily a part of
every compiled Haskell program; readline isn't so important but it would
be nice to have a BSD-licensed replacement.

The policy for Haskell libraries in fptools is that licenses are
assigned no finer than package granularity, so that a user of a package
can have a reasonable chance of telling whether they are complying with
the relevant licenses.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Utility functions

2005-01-06 Thread Ketil Malde
Simon Marlow [EMAIL PROTECTED] writes:

 There are already a couple of bits of (L)GPL under fptools: GMP and
 readline.  GMP we'd like to replace because it is necessarily a part of
 every compiled Haskell program; readline isn't so important but it would
 be nice to have a BSD-licensed replacement.

Readline is GPL and GMP LGPL, aren't they?  So GMP only restricts
what you can do with modifications to that library (and thus only
affects developers who want to release a modified GHC without source),
while linking with readline will potentially affect regular users of
GHC. 

Or?

-kzm
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Re: Utility functions

2005-01-06 Thread Simon Marlow
On 06 January 2005 12:20, Ketil Malde wrote:

 Simon Marlow [EMAIL PROTECTED] writes:
 
 There are already a couple of bits of (L)GPL under fptools: GMP and
 readline.  GMP we'd like to replace because it is necessarily a part
 of every compiled Haskell program; readline isn't so important but
 it would be nice to have a BSD-licensed replacement.
 
 Readline is GPL and GMP LGPL, aren't they?

Yes.

 So GMP only restricts
 what you can do with modifications to that library (and thus only
 affects developers who want to release a modified GHC without source),
 while linking with readline will potentially affect regular users of
 GHC.

Strictly speaking you have to dynamically link GMP to avoid your program
being affected by the LGPL.  Most GHC installations use a dynamically
linked GMP, but some do not.

Readline's license affects GHC (because GHC itself links with it), but
it doesn't affect programs you compile with GHC unless you explicitly
request the readline package (unlike GMP, which is always linked in).

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Seeking comments on this IO proposal

2005-01-06 Thread Simon Marlow
On 17 December 2004 16:49, John Goerzen wrote:

 First, if someone were to make a working, useful package out of this,
 is it likely that it would become the standard (whatever that
 means) IO system in Haskell anytime in the near future?  I ask
 because I don't want to put a lot of time into developing an IO
 library, and code that works with it, only to have nobody use my code
 because it's incompatible with everything they're doing.

I'm keen to transition over to a more general IO framework, and I
believe Bens/my proposal is heading in the right direction.  When we
have a more complete implementation, I'd be happy to include it with GHC
for experimentation, and over time transition code to use the new
framework while leaving the old System.IO in place for the time being.

The design isn't by any means set in stone at this stage though.

 Second is my own level of expertise.  I frankly don't understand how
 much of that code could even compile (example: I couldn't find
 setNonBlockingFD anywhere in my docs; maybe it's from one of those
 GHC.* areas), and I don't really understand the whole array/buffer
 situation either.  I spent some time reading docs, and I'm still not
 sure exactly how one builds a mutable, resiable array.  I've also
 never done anything but the most trivial FFI work.

Much of the reason for the complexity is because I was paying careful
attention to performance (perhaps too much attention).  I don't want the
addition of a text encoding/decoding layer to the IO subsystem to affect
performance more than is necessary, and that means doing the translation
on raw character buffers rather than strings.

Unfortunately this does mean that porting to other compilers is going to
be more work.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Begginer question

2005-01-06 Thread Maurício
Ketil Malde wrote:
Maurício [EMAIL PROTECTED] writes:
  (...)
Couldn't match `Float' against `Complex Float'
Expected type: Float
Inferred type: Complex Float
In the second argument of `(+)', namely `sqr_delta'
In the definition of `x1': x1 = (b + sqr_delta)

The error message says it all, really.
 (...)
Note that Haskell doesn't automatically convert arguments for you --
this is a feature.  

-kzm
  When I type this:
*
import Complex;
a = 3 :+ 4;
*
and load it into ghci, a + 4 gives me 7.0 :+ 4.0, although a + 
(4::Float) gives me that error again. Why Haskell converts 4 to 
Complex but not a Float?

  Maurício
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Begginer question

2005-01-06 Thread karczma
Maurcio comments the remark of Ketil Malde 

Note that Haskell doesn't automatically convert arguments for you --
this is a feature.  

  When I type this: 

*
import Complex;
a = 3 :+ 4;
* 

and load it into ghci, a + 4 gives me 7.0 :+ 4.0, although a + 
(4::Float) gives me that error again. Why Haskell converts 4 to Complex 
but not a Float?
You should read thoroughly the Haskell documentation. You will learn
that Haskell casts EXPLICIT NUMERICAL CONSTANTS, but not variables. 

Actually this is not a conversion, but an overloading of numerical
constants. The lexical entity 4 behaves as fromInteger 4, and the
type checker uses the fromInteger appropriate to the context. Floating,
Complex, etc. With 4.0 it will work also (overloaded fromRational). 

Jerzy Karczmarczuk 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Begginer question

2005-01-06 Thread Jules Bean
On 6 Jan 2005, at 14:06, Maurício wrote:
*
import Complex;
a = 3 :+ 4;
*
and load it into ghci, a + 4 gives me 7.0 :+ 4.0, although a + 
(4::Float) gives me that error again. Why Haskell converts 4 to 
Complex but not a Float?

The answer lies available to you in ghci:
Prelude :t 4
4 :: forall t. (Num t) = t
The type of for is 'any type in the Num class'.  So '4' stands for the 
Integer four as well as the Float four and the Double four and indeed 
the Complex 4.

No conversion is actually happening.
Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Begginer question

2005-01-06 Thread Henning Thielemann

On Thu, 6 Jan 2005 [EMAIL PROTECTED] wrote:

 Actually this is not a conversion, but an overloading of numerical
 constants. The lexical entity 4 behaves as fromInteger 4, and the
 type checker uses the fromInteger appropriate to the context. Floating,
 Complex, etc. With 4.0 it will work also (overloaded fromRational). 

Though I think the syntax should distinguish between the polymorphic value
'4' and the bare integer from which it is convert, say '#4', that is '4 =
fromInteger #4'. 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-06 Thread David Roundy
On Thu, Jan 06, 2005 at 09:11:13AM -0800, Benjamin Pierce wrote:
 * As far as I can determine, there is no way to check pattern matches for
   exhaustiveness.  Coming from OCaml, this feels like losing a significant
   safety net!  How do people program so as not to be getting dynamic match
   failures all the time?

ghc does give warnings when pattern matches aren't exhaustive, at least
when called with the compile flags used with darcs.  It seems that you may
be interested in the -fwarn-incomplete-patterns compile flag with ghc.
-- 
David Roundy
http://civet.berkeley.edu/droundy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-06 Thread Henning Thielemann

On Thu, 6 Jan 2005, Benjamin Pierce wrote:

 * What are the relative advantages of Hugs and GHC, beyond the obvious (Hugs
   is smaller and easier for people not named Simon to modify, while GHC is a
   real compiler and has the most up-to-date hacks to the type checker)?  Do
   people generally use one or the other for everything, or are they similar
   enough to use Hugs at some moments and GHC at others?

Hugs is compiles faster, that is, it detects type errors faster than GHC
and thus it starts program execution earlier. So I use Hugs for fast type
checking and simple scripts, that should start quickly rather than run
short. I'm using GHC for maximum execution speed and to track down type
errors, because its error messages are more detailed.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-06 Thread Shae Matijs Erisson
Benjamin Pierce [EMAIL PROTECTED] writes:

 * What are the relative advantages of Hugs and GHC, beyond the obvious (Hugs
   is smaller and easier for people not named Simon to modify, while GHC is a
   real compiler and has the most up-to-date hacks to the type checker)?  Do
   people generally use one or the other for everything, or are they similar
   enough to use Hugs at some moments and GHC at others?

Hugs is written in C, it's easy to build and doesn't use much
ram/cpu/drivespace. 
GHC can be difficult to bootstrap for less popular setups (IBM Mainframes,
BeOS, Amiga, etc), and both building and using GHC can eat ram/cpu/drivespace.
On the feature side, Hugs is just that, a Haskell User's Gofer System.
GHC is more like a hotrod research compiler, there's always some neat new
feature in CVS that does really cool stuff. (ie Software Transactional Memory)
If you have a Sharp Zaurus, Hugs will work but GHC won't. 

 * HUnit and QuickCheck seem to offer very nice -- but different -- testing
   facilities.  Has anyone thought of combining them?  (In fact, is HUnit
   actually used?  The last revision seems to be a couple of years ago.)

I hacked up a test-first version of QuickCheck that saves failing test cases
and checks them again on the next run. That is effectively a combination of
HUnit and QuickCheck.
I sent in my code when the call for QuickCheck2 ideas happened. I know there
was a recent presentation on QC2 at Chalmers, but I don't know if the
test-first idea will be integrated, or when QC2 will be released.
My code is an inflexible hack I wrote as a proof of concept, it's definitely
not ready for real use.

PS. TaPL was great, on #haskell we call it The Brick Book 
Does it already have a standard nickname?
-- 
Shae Matijs Erisson - http://www.ScannedInAvian.com/ - Sockmonster once said:
You could switch out the unicycles for badgers, and the game would be the same.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: urls

2005-01-06 Thread Tristan Wibberley
Tristan Wibberley wrote:
http://research.microsoft.com/Users/simonpj/papers/assoc-types/index.htm
http://www.haskell.org/hawiki/GHC_206_2e4
oops, terribly sorry, was forwarding them to myself but mis-clicked :/
begin:vcard
fn:Tristan Wibberley
n:Wibberley;Tristan
email;internet:[EMAIL PROTECTED]
x-mozilla-html:FALSE
version:2.1
end:vcard

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The implementation of Functional

2005-01-06 Thread robert dockins
The following discussion occurred last September.  Is there any kind of 
update on any version of this book?

-
John Meacham writes:
  I am looking for the book The implementation of Functional
  Programming languages by S. L. Peyton Jones.
  This book is out of print and currently there is no electronic version
  of it. The Haskell bookstore folk are working on reconstructing it and
  making it available for print-on-demand,
  http://www.cafepress.com/haskell_books/, but it's not clear when
  exactly it will be available.
 
  Your other option is to try to find a used copy, but they are pretty
  expensive.

 I am working on getting that book available in the haskell bookstore. I
 searched quite a while before I found a used printed copy at a
 reasonable price and my search was part of my motivation for creating
 the bookstore.

 It is a bit trickier than the other books on the site because I only
 have a scanned in copy of the print version to work with, rather than
 LaTeX source. but I should have time this week to get it online.
 John
My wife (mainly) and I, with Simon's permission, have been working on
getting a web-enabled version of this available for quite some time.  It
hovers on the brink of completion, and should be there Real Soon Now as
well.  This will include a web enabled table of contents and next and back
buttons.
If I'd known how much time she would put in, I'd have never asked her for a
small favor...
Dave Barton
EDAptive Computing
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-06 Thread Greg Buchholz
Benjamin Pierce wrote:
 * What are the relative advantages of Hugs and GHC, beyond the obvious (Hugs
   is smaller and easier for people not named Simon to modify, while GHC is a
   real compiler and has the most up-to-date hacks to the type checker)?  Do
   people generally use one or the other for everything, or are they similar
   enough to use Hugs at some moments and GHC at others?
 snip
 * I wrote a little program for generating Sierpinkski Carpets, and was
   astonished to find that it runs out of heap under Hugs (with standard
   settings -- raising the heap size with -h leads to a happier result).

As one data point, I don't think SOEGraphics works with GHC or
recent versions of Hugs (http://www.haskell.org/soe/graphics.htm).  I
also tried a modified version of your Sierpinkski carpet program
(changed to spit out a PostScript file, since I don't have SOEGraphics).
Hugs chokes without increasing the stack, while my copy of GHC 6.2.1 runs
the program below quite fine, even without enabling optimizations.

Greg Buchholz


--Floating point PostScript version of Sierpinkski Carpet

fillSquare x y s = putStr $ x1 ++ y2 ++
x1 ++ y1 ++
x2 ++ y1 ++
x2 ++ y2 ++  box\n
  where
x1 = (show  x)++  
x2 = (show (x+s)) ++  
y1 = (show  y)++  
y2 = (show (y+s)) ++  

carpet x y s =
  if s  1
  then fillSquare x y s
  else let s' = s / 3
in do carpet xys'
  carpet (x+s')   ys'
  carpet (x+s'*2) ys'
  carpet x(y+s')   s'
  carpet (x+s'*2) (y+s')   s'
  carpet x(y+s'*2) s'
  carpet (x+s')   (y+s'*2) s'
  carpet (x+s'*2) (y+s'*2) s'

psPreamble = putStr $ %!PS-Adobe-2.0\n ++
  /box\n ++
  { newpath moveto lineto lineto lineto closepath fill} ++
  def\n 0.05 setlinewidth\n

main = do psPreamble
  carpet 50 250 500
  putStr showpage\n

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Some random newbie questions

2005-01-06 Thread karczma
A random newbie called (randomly probably) Benjamin Pierce writes: 

* I wrote a little program for generating Sierpinkski Carpets, and was
  astonished to find that it runs out of heap under Hugs (with standard
  settings -- raising the heap size with -h leads to a happier result).
...
import SOEGraphics 

fillSquare w x y s =
  drawInWindow w ... 

carpet w x y s =
  if s  8 
  then fillSquare w x y s
  else let s' = s `div` 3 
in do carpet w xys'
  carpet w (x+s')   ys'
  carpet w (x+s'*2) ys' 
  carpet w x(y+s')   s'
  carpet w (x+s'*2) (y+s')   s'
  carpet w x(y+s'*2) s'
  carpet w (x+s')   (y+s'*2) s'
  carpet w (x+s'*2) (y+s'*2) s' 

main = 
  runGraphics (
do w - openWindow Carpet (700,700)
   carpet w 50 50 600
   k - getKey w
   closeWindow w
  ) 

  I've clearly got a lot to learn about space usage in Haskell... can
  someone give me a hint about what is the problem here and how it might
  best be corrected?
Interesting (although hardly encouraging...) to see that other
people fell victim of *exactly* the same problem as myself, when
I tried to switch from Scheme to Haskell/Hugs while teaching graphics... 

In any case, Maestro, don't try to put your 'carpet' procedure under
the microscope, since in fact you have been stabbed in the back with an
empoisoned knife. This program, whose complexity can hardly be called
exorbitant also slllosss down, and fails in GC: 

= 

fillSquare w x y s =
drawInWindow w
 (withColor Blue
(polygon [(x,y), (x+s,y), (x+s,y+s), (x,y+s), (x,y)])) 

loopx w x y s =
if xs then return () else do {fillSquare w x y 5; loopx w (x+5) y s} 

blob w x y s =
if ys then return ()
  else do{loopx w x y s; blob w x (y+5) s} 

main = runGraphics (
   do w-openWindow Blob (900,900)
  blob w 50 50 800
  k-getKey w
  closeWindow w
 ) 

===
Greg Buchholz example with generating PS shows that even a non-optimized
program which avoids SOE works... 

It seems that there is something nasty with SOEGraphics, concretely
with window painting procedures (and with other operations iterated,
where the quotes around iteration is a sad irony...). 

It seems that Nothing Is Forgotten, or worse. Well, the following version: 

 

loopx :: Window - Int - Int - Int - IO ()
loopx w x y s =
if xs then return () else (fillSquare w x y 5) `seq` (loopx w (x+5) y s) 

blob :: Window - Int - Int - Int - IO ()
blob w x y s =
if ys then return ()
  else  (loopx w x y s) `seq` (blob w x (y+5) s) 

 

works pretty fast (under Windows 2000). But doesn't paint anything.
Perhaps I should use some deepSeq, or whatever? 

Sorry for not having anything more optimistic to say. In fact, waiting
for better weather I do such exercises using Clean... 

Jerzy Karczmarczuk 

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Some random newbie questions

2005-01-06 Thread Jacob Nelson


On Thu, 6 Jan 2005, Greg Buchholz wrote:

 As one data point, I don't think SOEGraphics works with GHC or
 recent versions of Hugs (http://www.haskell.org/soe/graphics.htm).

I had trouble with this recently, and a friend of a friend suggested I use
the latest GHC from CVS, and import Graphics.SOE, rather than SOEGraphics.
I ran the original code under GHCi 6.3, importing Graphics.SOE, without
problems.

Jacob Nelson
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The implementation of Functional

2005-01-06 Thread John Meacham
I have all the tiffs but just have not had time to convert them to a pdf
appropriate for cafepress to print up. Sorry for the delays.  
John


On Thu, Jan 06, 2005 at 02:21:57PM -0500, robert dockins wrote:
 
 The following discussion occurred last September.  Is there any kind of 
 update on any version of this book?
 
 -
 
 John Meacham writes:
   I am looking for the book The implementation of Functional
   Programming languages by S. L. Peyton Jones.
 
   This book is out of print and currently there is no electronic version
   of it. The Haskell bookstore folk are working on reconstructing it and
   making it available for print-on-demand,
   http://www.cafepress.com/haskell_books/, but it's not clear when
   exactly it will be available.
  
   Your other option is to try to find a used copy, but they are pretty
   expensive.
 
  I am working on getting that book available in the haskell bookstore. I
  searched quite a while before I found a used printed copy at a
  reasonable price and my search was part of my motivation for creating
  the bookstore.
 
  It is a bit trickier than the other books on the site because I only
  have a scanned in copy of the print version to work with, rather than
  LaTeX source. but I should have time this week to get it online.
  John
 
 My wife (mainly) and I, with Simon's permission, have been working on
 getting a web-enabled version of this available for quite some time.  It
 hovers on the brink of completion, and should be there Real Soon Now as
 well.  This will include a web enabled table of contents and next and back
 buttons.
 
 If I'd known how much time she would put in, I'd have never asked her for a
 small favor...
 
 Dave Barton
 EDAptive Computing
 
 -- 
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 

-- 
John Meacham - repetae.netjohn 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Some random newbie questions

2005-01-06 Thread Derek Elkins
 OK, I'm taking the plunge and using Haskell in a course I'm teaching
 this semester.  To get ready, I've been doing quite a bit of Haskell
 programming myself, and this has raised a few questions...
 
 * What are the relative advantages of Hugs and GHC, beyond the obvious
 (Hugs is smaller and easier for people not named Simon to modify,
 while GHC is a real compiler and has the most up-to-date hacks to
 the type checker)?  Do people generally use one or the other for
 everything, or are they similar enough to use Hugs at some moments and
 GHC at others?

All the below is my personal opinion:

My impression is that GHC is by far the most used Haskell
implementation.  In my opinion, the only reason Hugs should be used is
if it's the only implementation that will run on your system, otherwise
GHC or NHC will likely make a better choice.  Some of the differences
between GHC and the last version of Hugs I've looked at are:

1) GHCi views it's repl as being in a do-block, with the most important
consequence being the ability to define functions interactively, Hugs
views the input as an expression so functions can only be defined
locally.  Neither are rather impressive interactive environments (not
when compared to Squeak or CL listeners), but GHCi's is definitely more
convenient.

2) GHC is generally acknowledged to do a (significantly) better job with
error messages (both type and run-time errors).  To me, the difference
is so significant that, all other things being equal, GHC would still
win hands-down.

3) Most development of third-party libraries and tools target GHC
first, part of that has to do with

4) Beyond enhancements to type checking, GHC has many other extensions
such as: template haskell, preemptive concurrency (Hugs does have
cooperative concurrency), asynchronous exceptions, built-in arrow
notation, support for generics, and more.

5) And of course, (3) is also caused by second order effects of itself,
e.g. Yi uses GHC because it uses hs-plugins which is intimately related
to GHC.

6) GHC has support for profiling.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Hugs vs GHC (again) was: Re: Some random newbie questions

2005-01-06 Thread Dimitry Golubovsky
Hi,
Looks like Hugs and GHC are being compared again ;)
I am just interested to know, what is the current status of Unicode 
support in GHC? Hugs has had it for about a year (or more, in CVS) at 
least at the level of recognizing character categories and simple case 
conversions based on the Unicode database files. Also UTF-8 or 
locale-based I/O encoding conversion to internal Unicode is available. 
Does GHC has similar support?

Some time ago (about 1.5 years) I tried to play with Unicode I/O in GHC, 
and it looked like it did not have much Unicode support back then (at 
least on I/O level). Has anything progressed in this regard since then?

Most of this list subscribers seem to be GHC users, so can anybody answer?
BTW when answering the original post (brief quote below) different 
aspects were mentioned, but not internationalization ones. Is it really 
not that important?

Dimitry Golubovsky
Middletown, CT
Benjamin Pierce wrote:

* What are the relative advantages of Hugs and GHC, beyond the obvious (Hugs
  is smaller and easier for people not named Simon to modify, while GHC is a
  real compiler and has the most up-to-date hacks to the type checker)?  Do
  people generally use one or the other for everything, or are they similar
  enough to use Hugs at some moments and GHC at others?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe