[Haskell-cafe] abstract extensible types?

Alberto G. Corona agocorona at gmail.com
Wed Nov 12 05:38:03 EST 2008


Is there any abstract container  that permits the addition of  new types of
data? I know how to simulate the extension of Algebraic datatypes, but this
does not permit the addition of data with new types in the same container
and recover them in a  type-safe way.

Did I reinvent the Weel? I found something, that permits this for any
Typeable datatype. For example


 x=5
 list= [put x,  put "hello"]

 [t1,t2 ]= list

 x' = get t1 :: Int
 s = get t2 :: String
 print (x' +1)     -- 2
 print s            -- "hello"

 x''= get t2 :: Int            --"get: casting from String  to type Int"



The code:

data Abstract= forall a. Typeable a => T !String  a


class FromToAbstract x where
 put :: x -> Abstract
 get ::  Abstract -> x
 unsafeGet :: Abstract -> x

 -- get(put x)== x

instance Typeable x => FromToAbstract x where
 put x= T (typeString x) x

 get (Abstract type1 a)= if type2 == type1 then v
                        else error ("get: casting "++ "from type "++type1++"
to type "++type2)
           where
           v=  unsafeCoerce a :: x
           type2= typeString v

 unsafeGet (Abstract type1 a)= unsafeCoerce a


typeString !x= tyConString $ typeRepTyCon $ typeOf x

instance Typeable T where
  typeOf _= mkTyConApp (mkTyCon "Abstract") []
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20081112/127293e0/attachment.htm


More information about the Haskell-Cafe mailing list