[Haskell-cafe] Some random newbie questions

Benjamin Pierce bcpierce at cis.upenn.edu
Thu Jan 6 12:11:13 EST 2005


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
-----------------------------------------------------------------------------




More information about the Haskell-Cafe mailing list