On Apr 12, 2006, at 4:09 PM, Scott Weeks wrote:


Or carry an instance in along with a type parameter, using existentials or GADT.

Brandon Moore

Do you know of an example that would apply to my situation?

I think I neglected to state part of my problem. I am storing the root nodes of btree indexes in a heterogeneous list using Typeable. When they come out of the list they need to be unwrapped

I think this will clarify my situation because I've been doing a poor job of explaining:

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
      Just dynFoo = fromDynamic f
  dostuff dynFoo



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


This fails with:

 Ambiguous type variable `a' in the constraints:
      `Typeable a'
arising from use of `fromDynamic' at /Users/weeksie/workspace/ haskell/Main.hs:243:20-30
      `Show a'
arising from use of `dostuff' at /Users/weeksie/workspace/haskell/ Main.hs:247:2-8 Probable fix: add a type signature that fixes these type variable(s)


However, changing main:

main = do
  fooType <- getLine
  fooVal  <- getLine
  let foo   = toDyn (FVal fooVal)
      fs    = [foo]
      (f:_) = fs
      Just dynFoo = fromDynamic f
  if fooType == "str"
     then dostuff (dynFoo::FooStr)
     else dostuff (dynFoo::FooInt)


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.



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
          -- TMBG

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to