Something's seriously broken in current (built today from CVS) ghci:


module Tst where

data List a = Nil | Cons a (List a) deriving Show

len Nil = 0
len (Cons _ l) = 1 + len l

data SList = SNil | SCons String SList deriving Show

slen SNil = 0
slen (SCons _ l) = 1 + slen l


Prelude> :l Tst.hs
Compiling Tst              ( Tst.hs, interpreted )
Ok, modules loaded: Tst.
Tst> Cons "foo" Nil
*** Exception: <<loop>>
Tst> len (Cons "foo" Nil)
*** Exception: <<loop>>
Tst> SCons "foo" SNil
SCons "foo" SNil
Tst> slen (SCons "foo" SNil)
1

Yet the compiler works okay, and compiled files work in ghci...

Prelude> :l Tst
Skipping  Tst              ( Tst.hs, ./Tst.o )
Ok, modules loaded: Tst.
Tst> Cons "Foo" Nil
Cons "Foo" Nil
Tst> len (Cons "foo" Nil)
1

So it's clearly something with the interpreter.


Lauri Alanko
[EMAIL PROTECTED]

_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to