[Haskell-cafe] Dynamic types through unsafeCoerce
Alfonso Acosta
alfonso.acosta at gmail.com
Tue Dec 12 17:58:35 EST 2006
Ok, instead of pushing about why I want to use unsafeCoerce (which I
know it's not a good thing) I decided (as suggested by Taral) to paste
a simplified example of my code.
If anyone finds a way of implementing something equivalent to this code without
unsafeCoerce# and ...
* Not changing chooseDesc or finding an equivalent
* Not splitting or changing Descriptor type (I already found an
equivalent way which uses existentials and in which the type is
splitted in two)
... I'll give up on my risky campaign on unsafeCoerce and you won't
won't have to stand my questions about it again ;)
-----------------
{-# OPTIONS_GHC -fglasgow-exts #-}
import Data.Dynamic
import Foreign
-- Fake instantiation Data
-- To make it simple, lets assume it doesn't need to be marshaled from C
type InstanceInitData = Int
-- Descriptor, equivalent to a C struct with function pointers
-- hd is the handler of the callbacks (void *) in C
data Typeable hd => Descriptor hd =
Descriptor { -- create a new instance and return its handler
instantiate :: InstanceInitData -> hd,
-- Run and return a new handler
run :: hd -> IO hd}
deriving Typeable
descInt:: Descriptor Int
descInt = Descriptor (\_ -> 1)
(\hd -> putStrLn (show hd) >> (return $ hd*2))
descChar :: Descriptor Char
descChar = Descriptor (\_ -> 'a')
(\hd -> putStrLn (show hd) >> (return $ succ hd))
descList :: [Dyn]
descList = [toDyn descInt, toDyn descChar]
-- Choose a descriptor, (called from C)
chooseDesc :: Int -> IO (StablePtr (Descriptor a))
chooseDesc n = newStablePtr (fromDyn (descList !! n))
foreign export ccall "chooseDesc"
chooseDesc :: Int -> IO (StablePtr (Descriptor hd))
-- Descriptor functions called from C
-- once the descriptor is obtanied through chooseDesc
cInstantiate ::
StablePtr (Descriptor hd) -> InstanceInitData -> IO (StablePtr hd)
cInstantiate ptr iid = do desc <- deRefStablePtr ptr
(newStablePtr.(instantiate desc)) iid
cRun ::
StablePtr (Descriptor hd) -> StablePtr hd -> IO (StablePtr hd)
cRun dptr hdptr = do desc <- deRefStablePtr dptr
hd <- deRefStablePtr hdptr
newhd <- (run desc) hd
newStablePtr newhd
---------
More information about the Haskell-Cafe
mailing list