[Haskell-cafe] Problem with JHC

Daniel Fischer daniel.is.fischer at web.de
Wed Nov 11 22:58:54 EST 2009


Am Mittwoch 11 November 2009 23:50:21 schrieb Thomas DuBuisson:
> Like paolino, I did a couple tests and found:

>
>
> So the read for that does not work... but surprisingly...
>
> > data TreeX = Leaf Int | NotLeaf deriving (Show, Read)
>
> Dropping the Int from the second constructor works (ignore the
> constructor names, they are just place-holders).
>

>
> --- OTHER TESTS ---
> 1) data TreeX = Leaf | NotLeaf 5 deriving (Show, Read)
> Another unfortunate bug is that reversing the constructors (having
> Leaf as a nullary constructor and NotLeaf taking an Int) causes
> compilation to fail (using jhc-0.7.2-0).
>
> 2) data TreeX = Leaf Int | NotLeaf Int | OoopsLeaf deriving (Show, Read)
>
> Works fine - notice it ends with a nullary constructor...
> Hypothesis 1: All working Read derivations have data declarations with
> a nullary constructor at the end.

Must be something like that, it also dies badly reading Either (but reading integers 
works):

module Main where

a, n :: Either Int Char
a = Right 'a'
n = Left 4

sa = "Right 'a'"
sn = "Left 4"

main :: IO ()
main = do
    putStrLn "Showing:"
    print (sa == show a)
    print (sn == show n)
    putStrLn "Reading:"
    print (read "123" :: Integer)
    print (a == read sa)
    print (n == read sn)


results in
$ ./veither
Showing:
True
True
Reading:
123

veither_code.c:3642: case fell off

$ jhc --version
jhc 0.7.2 (0.7.2-0)
compiled by ghc-6.10 on a i386 running linux

>
> Cheers,
> Thomas




More information about the Haskell-Cafe mailing list