You are trying to assign two distinct types to dynFoo; that's a no-no. You need to move the usage of the polymorphic function out of the let so that the use at each distinct type doesn't get unified.


{-# OPTIONS -fglasgow-exts #-}
import Data.Dynamic

data Foo a = FVal a
             deriving (Show, Typeable)

type FooStr = Foo String
type FooInt = Foo Integer

main = do
  fooType <- getLine
  fooVal  <- getLine
  let foo   = toDyn (FVal fooVal)
      fs    = [foo]
      (f:_) = fs
  if fooType == "str"
     then dostuff (fromDyn f undefined :: Foo String)
     else dostuff (fromDyn f undefined :: Foo Int)


dostuff :: (Show a) => Foo a -> IO ()
dostuff (FVal x) = print x



BTW, this little example always stuffs a string into the FVal, so trying to get anything else out will fail.


Thanks for the example it makes a bit of sense now, I really appreciate you taking the time to help me on this.

Cheers,
Scott
_______________________________________________
Haskell-Cafe mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to