The following program prints "ZCze 1 2" (usual setup: Linux, ghc-4.02
from the repository):
data Foo = Int := Int deriving Show
main = print (1 := 2)
Even more strange things go on with names here (file Baz.hs):
module Baz where
data TheZigAndZagShow = Zig | Zag
Compilation yields a file Bazz.hi (??) with the content:
__interface Bazz 1 402 where
import PrelBase 1 :: addr2Integer 1 foldr 1 int2Integer 1 integer_0 1 integer_1 1
integer_2 1 integer_m1 1;
import PrelPack 1 :: packCStringzh 1 unpackAppendCStringzh 1 unpackCStringzh 1
unpackFoldrCStringzh 1 unpackNByteszh 1;
__instimport IO ; __instimport PrelAddr ; __instimport PrelArr ; __instimport
PrelBounded ; __instimport PrelCCall ; __instimport PrelConc ; __instimport
PrelForeign ; __instimport PrelIOBase ; __instimport PrelNum ; __instimport
PrelNumExtra ; __instimport PrelStable ; __instimport PrelTup ;
__export Bazz TheZZigAndZZagShow{ZZig ZZag};
1 data TheZZigAndZZagShow = ZZig | ZZag ;
Aversion to singleton z's? :-)
Cheers,
Sven
--
Sven Panne Tel.: +49/89/2178-2235
LMU, Institut fuer Informatik FAX : +49/89/2178-2211
LFE Programmier- und Modellierungssprachen Oettingenstr. 67
mailto:[EMAIL PROTECTED] D-80538 Muenchen
http://www.pms.informatik.uni-muenchen.de/mitarbeiter/panne