Purity of the stack execution model? (fwd)

Johan Nordlander nordland@cse.ogi.edu
Fri, 16 Feb 2001 20:30:02 -0800


Koen Claessen wrote:
> 
> Hi!
> 
> Somebody posted the following message on
> comp.lang.functional. It reports an error when having a main
> function which has type "IO [()]", together with using
> runhugs.
> 
> This is a bug; the Haskell report says that main "must be a
> computation of type IO t for some type t".
> 
> /Koen.
> 
> [..]
>
> However, if I try the following:
> 
>     module Main where
>     actions = [putStr "foo", putStr "bar"]
>     nl = putStr "\n"
>     main = sequence actions >> nl >> mapM (>> nl) (reverse actions)
> 
> I get this message from runhugs:
> 
>     Program error: fromDyn failed.  Expecting <<IO() >> found <<IO[
>     Program error: {instShow_v1536_v1601 [instTypeable_v1537 (head
>     (unsafePerformIO main))]}runhugs: Error occurred


This bug, as well as the secondary one that shows up in the aborted error
message above, are now corrected in the CVS repository (but won't be visible 
until tomorrow).  They are however both too minor to warrant any patch to the 
current release.  Notice also that it is always possible to circumvent the 
bug by defining

   main = old_main >> return ()

Anyone who wants to access the Hugs98 cvs repository should point their web 
browser to

   http://cvs.haskell.org/cgi-bin/cvsweb.cgi/hugs98/

-- Johan