Dynamic types: GHCI works, GHC doesn't?
Andre Pang
ozone@algorithm.com.au
Sat, 1 Jun 2002 23:01:57 +1000
--SLDf9lqlvOQaIe6s
Content-Type: text/plain; charset=us-ascii
Content-Disposition: inline
Hi all,
I'm trying to get a grip on the Dynamic types stuff supplied with
GHC, and I'm not sure if I'm doing something wrong, or whether
I've found a bug.
It seems that the fromDynamic and fromDyn functions seem to work
if you load your module into GHCI, but they don't work when you
compile it into a stand-alone executable with GHC. Here's an
example of what the output is meant to be like:
22:51(0) .../project/dynamic_types-bug% ghci -package lang DynamicTypesBug.hs
[ GHCI header deleted ]
Loading package std ... linking ... done.
Loading package lang ... linking ... done.
Compiling Main ( DynamicTypesBug.hs, interpreted )
Ok, modules loaded: Main.
Main> main
Static type: FootnoteData [Char] Int
Coerced (dynamic) type: FootnoteData [Char] Int
Does dynamic type == static type? True
Attempting to run fromDynamic on the dynamic type ...
5. This be the footnote
Main>
So, that all works fine. Compile it through GHC, however, and
this happens:
22:57(0) .../project/dynamic_types-bug% ghc --make -package lang DynamicTypesBug.hs
ghc-5.02.2: chasing modules from: DynamicTypesBug.hs
Compiling Main ( DynamicTypesBug.hs, ./DynamicTypesBug.o )
ghc: linking ...
22:57(0) .../project/dynamic_types-bug% ./a.out
Static type: FootnoteData [Char] Int
Coerced (dynamic) type: FootnoteData [Char] Int
Does dynamic type == static type? False
Attempting to run fromDynamic on the dynamic type ...
Fail: Maybe.fromJust: Nothing
Furthermore, if you compile it with GHC, then run GHCI afterward,
GHCI will use the Main.o object file rather than try to compile
it again, and will fail:
22:58(1) .../project/dynamic_types-bug% ghci -package lang DynamicTypesBug.hs
[ GHCI header deleted ]
Loading package std ... linking ... done.
Loading package lang ... linking ... done.
Skipping Main ( DynamicTypesBug.hs, ./DynamicTypesBug.o )
Ok, modules loaded: Main.
Main> main
Static type: FootnoteData [Char] Int
Coerced (dynamic) type: FootnoteData [Char] Int
Does dynamic type == static type? False
Attempting to run fromDynamic on the dynamic type ...
*** Exception: Maybe.fromJust: Nothing
Main>
I've seen this behaviour with:
* ghc-5.02.2 from the Debian ghc5 package
* ghc-5.02.1 on another Linux machine (compiled from source)
* ghc-5.03.20020204 snapshot on Windows (Sigbjorne's MSI package)
It's possible that I'm not using the Dynamic module functions
properly, since I don't think I understand them that well. In
particular, I'm a bit confused as to how to construct a TypeRep
with the mkAppTy function. See my code to see how I'm (mis)using
it :).
The code which exhibits this behaviour is attached to this
message (DynamicTypesBug.hs). Hopefully I'm just doing something
silly ...
--
#ozone/algorithm <ozone@algorithm.com.au> - trust.in.love.to.save
--SLDf9lqlvOQaIe6s
Content-Type: text/plain; charset=us-ascii
Content-Disposition: attachment; filename="DynamicTypesBug.hs"
module Main where
import Dynamic
import Maybe
data Phrase = Phrase PhraseStyle Dynamic
type PhraseStyle = String
instance Typeable FootnoteData where
typeOf _ = mkAppTy (mkTyCon "FootnoteData") [typeOf ("Foo" :: String), typeOf (7 :: Int)]
data FootnoteData = FootnoteData String Int
writeFootnote :: Phrase -> String
writeFootnote (Phrase _ dynData) = (show footnoteNumber) ++ ". " ++ footnoteString
where
(footnoteString, footnoteNumber) =
case footnoteData of
(FootnoteData s f) -> (s, f)
footnoteData = fromJust (fromDynamic dynData)
myFootnoteData = FootnoteData "This be the footnote" 5
dynaFootnoteData = toDyn myFootnoteData
myPhrase = Phrase "Footnote" dynaFootnoteData
main = do
putStrLn $ "Static type: " ++
show (typeOf myFootnoteData)
let coercedFootnoteData = fromJust (fromDynamic dynaFootnoteData) :: FootnoteData
putStrLn $ "Coerced (dynamic) type: " ++
show (typeOf coercedFootnoteData)
putStrLn $ "Does dynamic type == static type? " ++
show (typeOf coercedFootnoteData == typeOf myFootnoteData)
putStrLn "Attempting to run fromDynamic on the dynamic type ..."
putStrLn $ writeFootnote myPhrase
--SLDf9lqlvOQaIe6s--