
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? * 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? * 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 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). module Main where import SOEGraphics fillSquare w x y s = drawInWindow w (withColor Blue (polygon [(x,y), (x+s,y), (x+s,y+s), (x,y+s), (x,y)])) carpet w x y s = if s < 8 then fillSquare w x y s else let s' = s `div` 3 in do carpet w x y s' carpet w (x+s') y s' carpet w (x+s'*2) y s' 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? Thanks for any comments, Benjamin ----------------------------------------------------------------------------- BENJAMIN C. PIERCE, Professor Dept. of Computer & Information Science University of Pennsylvania +1 215 898-2012 3330 Walnut St. Fax: +1 215 898-0587 Philadelphia, PA 19104, USA http://www.cis.upenn.edu/~bcpierce -----------------------------------------------------------------------------

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/

On Thu, 6 Jan 2005, David Roundy wrote:
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.
... or -Wall to get lots of warnings

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.

Benjamin Pierce
* 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.

On Thu, 6 Jan 2005, 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?
Where not sure, a wildcard pattern at the end of the pattern list catches things. Myself I was always more irritated that I couldn't type things in such a way that the typechecker would catch it.
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?
Having given the code but the briefest glance, I suspect laziness is biting you? If so, others will be able to give you good pointers - I've not really had to deal with it myself (seq and strict constructors are probably good places to start from what I hear though). -- flippa@flippac.org Ivanova is always right. I will listen to Ivanova. I will not ignore Ivanova's recomendations. Ivanova is God. And, if this ever happens again, Ivanova will personally rip your lungs out!

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 x y s' carpet (x+s') y s' carpet (x+s'*2) y s' 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"

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

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 x y s' carpet w (x+s') y s' carpet w (x+s'*2) y s' 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 slllooooowwwwwwwwsss 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 x>s then return () else do {fillSquare w x y 5; loopx w (x+5) y s} blob w x y s = if y>s 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 x>s 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 y>s 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

On Thu, Jan 06, 2005 at 09:11:13AM -0800, Benjamin Pierce wrote:
* 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).
This is an artifact of the graphics library you're using, which aims at simplicity rather than efficiency. The program appears to be quite sequential, so one might assume that the space usage was proportional to the depth of the recursion. But in this library, each Window contains a Graphics value that describes the picture it contains, and drawInWindow just adds to that value, as well as triggering a redraw. As a result the space usage is proportional to the number of elements in the picture. Since there's no benefit from using the IO monad everywhere, you might as well construct the whole Graphics value and only call drawInWindow once (which also means less drawing). This way you only need to call withColor once as well, and that's a fairly expensive operation in this library. This version is faster and uses less space, though still proportional to the number of elements: fillSquare :: Int -> Int -> Int -> Graphics fillSquare x y s = polygon [(x,y), (x+s,y), (x+s,y+s), (x,y+s), (x,y)] carpet :: Int -> Int -> Int -> Graphics carpet x y s = if s < 8 then fillSquare x y s else let s' = s `div` 3 in overGraphics [ carpet x y s', carpet (x+s') y s', carpet (x+s'*2) y s', 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'] main = runGraphics ( do w <- openWindow "Carpet" (700,700) drawInWindow w (withColor Blue (carpet 50 50 600)) k <- getKey w closeWindow w ) Another alternative is to use Regions.

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?

* 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?
I just completely redesigned our first year undergraduate Haskell module and considered moving from Hugs to GHC. Because most students have Windows at home I don't consider installation a problem for GHC. GHC is the compiler for serious Haskell development. While this is not needed for beginners, I believe it demonstrates better to students that Haskell is not just an academic toy language. The error messages of GHC are generally better than those of Hugs; unfortunately GHC produces very bad parse errors and beginners tend to make lots of those (however, Hugs has the infamous unexpected semicolon error message). Hugs stops after the first error message, while GHC usually reports many errors. I think that for beginners the long list produced by GHC is more frustrating and they only repair one error at a time anyway. Hugs is also quicker in reporting an error. I also do not like that GHC exposes non-Haskell 98 features: if you type :t length you get length :: forall a. [a] -> Int. "forall" is not Haskell 98. So because of such a list of slightly beginner-unfriendly features I decided to stay with Hugs for this year. I might revise this next year, especially if GHC improves (I should ask Simon&Simon about these issues...) I also like the built-in HOOD of Hugs that makes "observe" polymorphic. However, I'll probably give up my original plan of using it in lectures to observe functions and thus get a better intuitive feeling for functions as mappings from inputs to results.
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?
I'm glad to see Ross' explanation that the space problem is caused by the library, because your code looked fine to me. I'm constantly surprised hearing from so many people about their space problems. I cannot remember having space problems with my programs. I don't know what everybody else is doing wrong :-) I do disagree with people recommending strictness annotations (seq etc). In contrast, I make my programs as lazy as possible. Actually I just remember once adding 'seq' to my pretty printing library to ensure it had the space complexity I wanted (not that there was a problem in practice). However, shortly afterwards I realised that I could rewrite that part in a way that made 'seq' superfluous, was shorter, nicer, and probably even slightly more efficient. Ciao, Olaf

O.Chitil@kent.ac.uk writes:
I'm constantly surprised hearing from so many people about their space problems. I cannot remember having space problems with my programs. I don't know what everybody else is doing wrong :-)
At least two common cases. Extracting compact data structures from large files. The contents of the large file is read as a linked list (ugh) of pointers (double ugh) to 32-bit Chars (triple ugh) -- twelve times the size of the file, if my calculations are correct. The contents can't be GC'ed before the extracted data is fully evaluated. (Now if the file was an mmap'ed array, it wouldn't be so bad, perhaps in the next generation IO that people are discussing this will be easier?) Naive use of foldl. I tend to think the default foldl should be strict (ie. replaced by foldl') -- are there important cases where it needs to be lazy?
I do disagree with people recommending strictness annotations (seq etc). In contrast, I make my programs as lazy as possible.
...but no lazier :-) -kzm -- If I haven't seen further, it is by standing in the footprints of giants

I'm constantly surprised hearing from so many people about their space problems. I cannot remember having space problems with my programs. I don't know what everybody else is doing wrong :-)
At least two common cases.
Extracting compact data structures from large files. The contents of the large file is read as a linked list (ugh) of pointers (double ugh) to 32-bit Chars (triple ugh) -- twelve times the size of the file, if my calculations are correct. The contents can't be GC'ed before the extracted data is fully evaluated. (Now if the file was an mmap'ed array, it wouldn't be so bad, perhaps in the next generation IO that people are discussing this will be easier?)
Naive use of foldl. I tend to think the default foldl should be strict (ie. replaced by foldl') -- are there important cases where it needs to be lazy?
Indeed, extracting a compact data structure from a large data structure can easily cost much space because of lazy evaluation. "foldl" is probably used mostly for that purpose. Me not having space problems is probably related to the kind of programs I write. Most of my programs are program transformations that take an abstract syntax tree as input and produce a different abstract syntax tree (again a large structure). Trying to be lazy then means trying to produce as much output as possible with processing as little output as possible. More formally that means if there is some partial input for a function such that for all completions of this partial input to fully defined inputs all outputs of the function have a common prefix, then the function should already yield this prefix as output for the partial input. In the example that I mentioned in my previous posting I did actually originally compute size information for a large data structure, so did extract something compact from something large. However, I then realised that I only did some very basic arithmetic with the size information before generating another large data structure of this computed size. So then I decided to not to compute integers at all but do the arithmetic directly on the algebraic data type. Gone was the space problem, without using seq. You might also want to look at Colin Runciman's paper "What about the Natural Numbers?" in the Journal of Functional Programming in which he argues for a type of lazy natural numbers, with the same semantics as data Nat = Zero | Succ Nat. It fits much better for computing the size of a lazy data structure. I don't claim that all space problems can easily be dealt with. Olaf

Jorge Adriano Aires
Naive use of foldl. I tend to think the default foldl should be strict (ie. replaced by foldl') -- are there important cases where it needs to be lazy?
Hi, One simple example would be,
reverse = foldl (flip (:)) []
No, it would work with strict foldl too. In fact in the absence of optimization it would work better (uses less time and space). The optimization required is inlining and strictness analysis. A function which requires lazy foldl for correctness would have to be sometimes lazy in its first argument, and at the same time some partial results would have to be undefined. By "function" I mean the first argument of foldl, treated as a binary function. Here this doesn't apply because flip (:) x y is always defined. And another common case for foldl, sum, doesn't apply because (+) is usually strict on both arguments (although in principle it does not have to be true because of overloading, which implies that a compiler can only optimize particular specializations of sum, not generic sum). I don't know of any real-life example. Perhaps there are cases where evaluating partial results is correct but inefficient. I don't know such case either. -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

No, it would work with strict foldl too. In fact in the absence of optimization it would work better (uses less time and space). The optimization required is inlining and strictness analysis.
Is this also true if your just going to use the first few elements after reversing it?
A function which requires lazy foldl for correctness would have to be sometimes lazy in its first argument, and at the same time some partial results would have to be undefined. By "function" I mean the first argument of foldl, treated as a binary function.
Here this doesn't apply because flip (:) x y is always defined. And another common case for foldl, sum, doesn't apply because (+) is usually strict on both arguments (although in principle it does not have to be true because of overloading, which implies that a compiler can only optimize particular specializations of sum, not generic sum).
I don't know of any real-life example.
Yes you are right, my bad. I was thinking as if lists were not lazy on their elements, therefore my second example... But yes, now it is not a common example anymore.
Perhaps there are cases where evaluating partial results is correct but inefficient. I don't know such case either.
Just replace the errors on my second example by some big computations... J.A.

Jorge Adriano Aires
No, it would work with strict foldl too. In fact in the absence of optimization it would work better (uses less time and space). The optimization required is inlining and strictness analysis.
Is this also true if your just going to use the first few elements after reversing it?
Yes. A strict fold would evaluate cons cells of the result while they are constructed, not list elements. They are all defined (flip (:) x y is always defined), so a strict foldl is correct. Making a cons cell should be not more expensive than making a thunk which will make a cons cell when evaluated. Well, unless the implementation doesn't inline flip and thus making these thunks is actually faster than running them. In this case a lazy foldl is more efficient than a strict foldl, as long as a sufficiently small part of the result is used; it's always less efficient if the whole result is examined. -- __("< Marcin Kowalczyk \__/ qrczak@knm.org.pl ^^ http://qrnik.knm.org.pl/~qrczak/

On Sunday 09 January 2005 21:30, Marcin 'Qrczak' Kowalczyk wrote:
Jorge Adriano Aires
writes: No, it would work with strict foldl too. In fact in the absence of optimization it would work better (uses less time and space). The optimization required is inlining and strictness analysis.
Is this also true if your just going to use the first few elements after reversing it?
Yes. A strict fold would evaluate cons cells of the result while they are constructed, not list elements. They are all defined (flip (:) x y is always defined), so a strict foldl is correct.
Yes, now I was refering to the efficiency issue only.
Making a cons cell should be not more expensive than making a thunk which will make a cons cell when evaluated.
Ok, I wasn't sure about this...
Well, unless the implementation doesn't inline flip and thus making these thunks is actually faster than running them. In this case a lazy foldl is more efficient than a strict foldl, as long as a sufficiently small part of the result is used; it's always less efficient if the whole result is examined.
Right. J.A.

(+) is usually strict on both arguments (although in principle it does not have to be true because of overloading, which implies that a compiler can only optimize particular specializations of sum, not generic sum).
Since you mention it, there was some talk about this in the #haskell channel, and I wondered why aren't sum and product members of Num with default instances, just like mconcat is also a member of Data.Monoid.Monoid. From the docs: "mconcat :: [a] -> a Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types" J.A.

On Friday 07 January 2005 12:03, Ketil Malde wrote:
Naive use of foldl. I tend to think the default foldl should be strict (ie. replaced by foldl') -- are there important cases where it needs to be lazy?
Hi, One simple example would be,
reverse = foldl (flip (:)) []
A better example would be building some other "lazy structure" that is strict on it's elements... J.A. ----------------------------------------------- module Test where import Data.List data L = E | !Int :+: L deriving Show -- my head h (x:+:xs) = x h E = error "ops" -- rev1 = foldl (flip (:+:)) E rev2 = foldl' (flip (:+:)) E l = [error "", error "", 1::Int] ---------------------------------------------- *Test> h (rev1 l) 1 (0.00 secs, 264560 bytes) *Test> h (rev2 l) *** Exception: (0.01 secs, 264524 bytes)

Benjamin Pierce wrote:
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?
I taught our FP class this fall using Hugs, but in the end wish that I had used GHC. There are lots of little reasons for this, but a big one was a problem with unpredictable space utilization. I don't have the examples at my fingertips, but there were simple variations of the same program that, by all common-sense reasoning, should have behaved in the opposite way with respect to space than what they exhibited. Indeed, the problem that you report in your "Sierpinkski Carpet" may likely be a problem with Hugs, and not the graphics lib, and Jacob Nelson's message seems to bear this out. SOEGraphics, by the way, is built on top of HGL, a general graphics lib written by Alastair Reid. At the time, it was the best option that we had, but Alastair no longer has time to maintain it, although I believe that Ross Paterson may be maintaining it now. In any case, SOEGraphics has grown a big buggy with respect to portability across platforms and compilers. I am about to update the SOE webpage with our current best shot at a portable and bug-free version of this, but ultimately I'd like to port everything over to something like wxHaskell. -Paul

On Fri, Jan 07, 2005 at 08:49:32AM -0500, Paul Hudak wrote:
I taught our FP class this fall using Hugs, but in the end wish that I had used GHC. There are lots of little reasons for this, but a big one was a problem with unpredictable space utilization. I don't have the examples at my fingertips, but there were simple variations of the same program that, by all common-sense reasoning, should have behaved in the opposite way with respect to space than what they exhibited.
Concrete examples would be interesting, especially if they didn't involve the graphic library.
Indeed, the problem that you report in your "Sierpinkski Carpet" may likely be a problem with Hugs, and not the graphics lib, and Jacob Nelson's message seems to bear this out.
No: it runs under GHCi, but it uses 16MB. Hugs has a 2MB heap by default (the size is measured in 8-byte cells).

Many thanks to everyone for the very helpful answers to my queries! - Benjamin
participants (16)
-
Benjamin Pierce
-
David Roundy
-
Dimitry Golubovsky
-
Greg Buchholz
-
Henning Thielemann
-
Jacob Nelson
-
Jorge Adriano Aires
-
karczma@info.unicaen.fr
-
Ketil Malde
-
Marcin 'Qrczak' Kowalczyk
-
O.Chitil@kent.ac.uk
-
Paul Hudak
-
Philippa Cowderoy
-
Ross Paterson
-
ross@soi.city.ac.uk
-
Shae Matijs Erisson