
Martin Sjögren wrote:
I have a problem with Data.Dynamic. The problem is probably that I don't understand it. From my understanding, the following program should work:
-8<------------------------ import Data.Dynamic
data Foo = Foo { x :: Int } deriving Show
instance Typeable Foo where typeOf _ = mkAppTy (mkTyCon "Foo.Foo") []
main = do let dynObj = toDyn $ Foo 42 print dynObj let Just obj = fromDynamic dynObj :: Maybe Foo print obj -8<------------------------
But when I compile it (ghc Foo.hs) and run it (./a.out) I get:
<
> Fail: Foo.hs:13: Irrefutable pattern failed for pattern (Data.Maybe.Just obj)
Which indicates that fromDynamic returned Nothing. What is the problem here? Do I have to employ special trickery to use Dynamic with records?
You have to ensure that the TyCon is unique. A comment in Dynamic.hs
says:
-- | Builds a 'TyCon' object representing a type constructor. An
-- implementation of "Data.Dynamic" should ensure that the following holds:
--
-- > mkTyCon "a" == mkTyCon "a"
--
-- NOTE: GHC\'s implementation is quite hacky, and the above equation
-- does not necessarily hold. For defining your own instances of
-- 'Typeable', try to ensure that only one call to 'mkTyCon' exists
-- for each type constructor (put it at the top level, and annotate the
-- corresponding definition with a @NOINLINE@ pragma).
If you use:
fooTc = mkTyCon "Foo.Foo"
instance Typeable Foo where
typeOf _ = mkAppTy fooTc []
or compile with "-O", your program works.
--
Glynn Clements