Dynamic types through unsafeCoerce

Hi, I've been using Data.Dynamic but the Typeable requirement doesn't go well with FFI declarations (which don't accept type contexts). This is a little example of what I would like to do: data MyDyn = MyDyn myToDyn :: a -> MyDyn myToDyn = unsafeCoerce myFromDyn :: MyDyn -> a myFromDyn = unsafeCoerce -- this is a type I want to transform back and forth from dynamic -- and store into lists etc etc ... data MyType a b = MyType a b -- This it's "abstract" Generic type (it's contructor should be hidden) data MyGenType = MyGenType MyDyn mt2mgt :: MyType a b -> MyGenType mt2mgt = MyGenType.myToDyn mgt2mt :: MyGentype -> MyType a b mgt2mt (MyGenType dyn) = myfromDyn dyn The question is, ¿if only mt2mgt and mgt2mt are used by the user, would the use of unsafeCoerce be dangerous? Thanks in advance, Alfonso Acosta

On 12/9/06, Alfonso Acosta
I've been using Data.Dynamic but the Typeable requirement doesn't go well with FFI declarations (which don't accept type contexts).
Can you be a little more specific?
mt2mgt :: MyType a b -> MyGenType mt2mgt = MyGenType.myToDyn
mgt2mt :: MyGentype -> MyType a b mgt2mt (MyGenType dyn) = myfromDyn dyn
The question is, ¿if only mt2mgt and mgt2mt are used by the user, would the use of unsafeCoerce be dangerous?
mgt2mt . mt2mgt :: MyType a b -> MyType c d
Yes, it's dangerous. The reason Dynamic requires Typeable is to be
able to check that you're casting Dynamic back to the original type.
--
Taral

On 12/9/06, Taral
On 12/9/06, Alfonso Acosta
wrote: I've been using Data.Dynamic but the Typeable requirement doesn't go well with FFI declarations (which don't accept type contexts).
Can you be a little more specific?
Functions like this one are not directy exportable myfunc :: (Tyeable a, Typeable b) => MyType a b ...
mt2mgt :: MyType a b -> MyGenType mt2mgt = MyGenType.myToDyn
mgt2mt :: MyGentype -> MyType a b mgt2mt (MyGenType dyn) = myfromDyn dyn
mgt2mt . mt2mgt :: MyType a b -> MyType c d
Yes, it's dangerous. The reason Dynamic requires Typeable is to be able to check that you're casting Dynamic back to the original type.
Uhm thinking about it right now I realized that mgt2mt is hidden to the user, so I guess it wouldn't be dangerous if transformations like the following one are not. MyType Int Char ---> MyGenType ----> MyType a b So to summarize, Is transforming a monomorphic type to it's polymorphic equivalent through unsafeCoerce a dangerous operation?

On 12/9/06, Alfonso Acosta
Functions like this one are not directy exportable
myfunc :: (Tyeable a, Typeable b) => MyType a b ...
Well, that's true. Then again, you can't export that type anyway without use of a StablePtr. All StablePtrs are exportable.
Uhm thinking about it right now I realized that mgt2mt is hidden to the user, so I guess it wouldn't be dangerous if transformations like the following one are not.
MyType Int Char ---> MyGenType ----> MyType a b
So to summarize, Is transforming a monomorphic type to it's polymorphic equivalent through unsafeCoerce a dangerous operation?
Sure it is. The type you gave (MyType Int Char -> MyType a b) can
easily crash your program.
--
Taral

On 12/10/06, Taral
Sure it is. The type you gave (MyType Int Char -> MyType a b) can easily crash your program.
Ok I see. Why would that happen? I'm (maybe wrongly) taking as granted that the compiler/interpreter uses the same internal representation for both types. But that makes me think it shouldn't be that dangerous if nothing is later assumed about the type parameters "a" and "b".

On 12/10/06, Alfonso Acosta
On 12/10/06, Taral
wrote: Sure it is. The type you gave (MyType Int Char -> MyType a b) can easily crash your program.
Ok I see. Why would that happen? I'm (maybe wrongly) taking as granted that the compiler/interpreter uses the same internal representation for both types. But that makes me think it shouldn't be that dangerous if nothing is later assumed about the type parameters "a" and "b".
If the parameters aren't used, why not create a new data type without them? -- Cheers, Lemmih

Sure it is. The type you gave (MyType Int Char -> MyType a b) can easily crash your program.
Ok I see. Why would that happen? I'm (maybe wrongly) taking as granted that the compiler/interpreter uses the same internal representation for both types. But that makes me think it shouldn't be that dangerous if nothing is later assumed about the type parameters "a" and "b".
If the parameters aren't used, why not create a new data type without them?
They are used, but no monomorphic type is assumed.

On 12/10/06, Alfonso Acosta
On 12/10/06, Taral
wrote: Sure it is. The type you gave (MyType Int Char -> MyType a b) can easily crash your program.
Ok I see. Why would that happen? I'm (maybe wrongly) taking as granted that the compiler/interpreter uses the same internal representation for both types. But that makes me think it shouldn't be that dangerous if nothing is later assumed about the type parameters "a" and "b".
1. The Haskell Report does not guarantee that these things have the
same representation.
2. Assuming that a polymorphic type will never be made monomorphic is
like running without a safety net. The typecheck will not save you,
and it'll be a pain to debug if it goes wrong. If you're not using
those type parameters, then wrap it up so they can't be used.
Why not post some code snippets so we can see what you're doing?
--
Taral

On 12/10/06, Taral
On 12/10/06, Alfonso Acosta
wrote: On 12/10/06, Taral
wrote: Sure it is. The type you gave (MyType Int Char -> MyType a b) can easily crash your program.
Ok I see. Why would that happen? I'm (maybe wrongly) taking as granted that the compiler/interpreter uses the same internal representation for both types. But that makes me think it shouldn't be that dangerous if nothing is later assumed about the type parameters "a" and "b".
1. The Haskell Report does not guarantee that these things have the same representation.
Well, to be honest the idea of using unsafeCoerce came after browing the sources of the Lava (http://www.md.chalmers.se/~koen/Lava/ ) library. Now I have explicit permission to reuse them so I guess I'm allowed to paste a few snippets here as well. Here they approach the same problem I have by using unsafe Coerce -- This code implements Observable sharing references for circuits -- Some Comments made by Koen describing the problem: -- "The disadvantage is that, since the types of the -- Tables vary, the Ref has no idea what type of -- values it is supposed to store. So we use dynamic -- types." toDyn :: a -> Dyn toDyn = unsafeCoerce fromDyn :: Dyn -> a fromDyn = unsafeCoerce -- If GHC is used unsafeCoerce :: a -> b unsafeCoerce a = unsafePerformIO $ do writeIORef ref a readIORef ref where ref = unsafePerformIO $ do newIORef undefined -- If Hugs is used primitive unsafeCoerce "primUnsafeCoerce" :: a -> b -- Pieces of code where toDyn/fromDyn is used data Ref a = Ref (IORef [(TableTag, Dyn)]) a type TableTag = IORef () newtype TableIO a b = TableIO TableTag deriving Eq extendIO :: TableIO a b -> Ref a -> b -> IO () extendIO (TableIO t) (Ref r _) b = do list <- readIORef r writeIORef r ((t,toDyn b) : filter ((/= t) . fst) list) findIO :: TableIO a b -> Ref a -> IO (Maybe b) findIO (TableIO t) (Ref r _) = do list <- readIORef r return (fromDyn `fmap` lookup t list)
2. Assuming that a polymorphic type will never be made monomorphic is like running without a safety net. The typecheck will not save you, and it'll be a pain to debug if it goes wrong. If you're not using those type parameters, then wrap it up so they can't be used.
The problem is that, even if not mandatory, the binding would look more intuitive and similar to the original library with the (internal and user-hidden) use of those type parameters. I already tried to hide them through an existential and actually that's how the last version of the binding is implemented. As I already said. The user is only able to transform to dynamic but not back to a polymorphic type so I have control over those parameters.
Why not post some code snippets so we can see what you're doing?
If this mail doesn't clarify the problem I will try paste some snippets of my code (it's a real pain to try to simplify it) Thanks for your help Taral :)

Alfonso Acosta wrote:
I've been using Data.Dynamic but the Typeable requirement doesn't go well with FFI declarations (which don't accept type contexts).
You wouldn't need a Typeable context anyway; what's biting you is that Dynamic is not one of the primitive types that can pass across the FFI. There are good reasons for that and unsafeCoerce certainly cannot invalidate them. You want a StablePtr.
would the use of unsafeCoerce be dangerous?
If you have to ask, then yes. -Udo -- "Never confuse motion with action." -- Ernest Hemingway

On 12/9/06, Udo Stenzel
You wouldn't need a Typeable context anyway; what's biting you is that Dynamic is not one of the primitive types that can pass across the FFI. There are good reasons for that and unsafeCoerce certainly cannot invalidate them.
You want a StablePtr.
I'm using StablePtrs already, what made you assume I wasn't using them?
would the use of unsafeCoerce be dangerous?
If you have to ask, then yes.
The name of the function makes it clear, it is unsafe, but it is still used in many cases. I just wanted to know if it was dangerous is this concrete example. Taral gave a good reason
-Udo -- "Never confuse motion with action." -- Ernest Hemingway
-----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.1 (GNU/Linux)
iD8DBQFFexJhc1ZCC9bsOpURAsoCAJ9wSVhSY5+3sYAV0cRwKi7E3QHTvgCfVbVB GiVZSrY28i5FJUs+V1g1I34= =MSt3 -----END PGP SIGNATURE-----
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On 12/9/06, Alfonso Acosta
On 12/9/06, Udo Stenzel
wrote: You wouldn't need a Typeable context anyway; what's biting you is that Dynamic is not one of the primitive types that can pass across the FFI. There are good reasons for that and unsafeCoerce certainly cannot invalidate them.
You want a StablePtr.
I'm using StablePtrs already, what made you assume I wasn't using them?
How about using a StablePtr to a Dynamic? -- Cheers, Lemmih

On 12/10/06, Lemmih
How about using a StablePtr to a Dynamic?
I'm using them, but just forgot to put them in the example I wrote. myfunc :: (Tyeable a, Typeable b) => StablePtr (MyType a b) ... Either the way, it doesn't work due to the class context, which is not accepted byt the FFI.

On 12/10/06, Alfonso Acosta
On 12/10/06, Lemmih
wrote: How about using a StablePtr to a Dynamic?
I'm using them, but just forgot to put them in the example I wrote.
myfunc :: (Tyeable a, Typeable b) => StablePtr (MyType a b) ...
Either the way, it doesn't work due to the class context, which is not accepted byt the FFI.
You can go from 'MyType a b' to 'Dynamic' to 'StablePtr Dynamic' to 'Dynamic' to 'MyType a b'. -- Cheers, Lemmih

On 12/10/06, Lemmih
How about using a StablePtr to a Dynamic?
Uhm, that's a good idea cause no Typeable context will then be required and thus the function can be exported by the FFI. On the other hand, using Data.Dynamic requires any type to be an instance of Typeable. And thus requires the user to make such instantiation (which is a pain) GHC supports the "deriving" clause for the Typeable class, but it's not standard Haskell98 (and as far as I know, for example hugs doesn't support it) So it would be great to be able to use unsafeCoerce.

On 12/12/06, Alfonso Acosta
On 12/10/06, Lemmih
wrote: How about using a StablePtr to a Dynamic?
Uhm, that's a good idea cause no Typeable context will then be required and thus the function can be exported by the FFI.
On the other hand, using Data.Dynamic requires any type to be an instance of Typeable. And thus requires the user to make such instantiation (which is a pain)
GHC supports the "deriving" clause for the Typeable class, but it's not standard Haskell98 (and as far as I know, for example hugs doesn't support it)
So it would be great to be able to use unsafeCoerce.
Ah, you want type-safe casts without using Typeable? Good luck, you'll need it. -- Cheers, Lemmih

On 12/12/06, Alfonso Acosta
So it would be great to be able to use unsafeCoerce.
It would be great -- but Typeable is the only way to get *safe*
typecasts of this type. Otherwise, you may as well run without a
typechecker.
--
Taral

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 ---------

Ignore the previous message, wrong code, here I come again 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 GHC.Base 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 Descriptor hd = Descriptor { -- create a new instance and return its handler instantiate :: InstanceInitData -> hd, -- Run and return a new handler run :: hd -> IO hd} 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)) data Dyn = Dyn toDyn :: Descriptor hd -> Dyn toDyn = unsafeCoerce# fromDyn :: Dyn -> Descriptor hd fromDyn = unsafeCoerce# 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 -----------

Alfonso Acosta wrote:
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)
Well, all you need to do is to throw out your OO-Think (and with it Typeable and casts) and you'll realize what you're actually doing here: you're passing functions. Say so and everything comes naturally. (Warning: untested code.) -- ---------- type Descriptor = InstanceInitData -> Runner -- a function! Who would have thought it? newtype Runner = R { run :: IO Runner } -- could be a plain (IO Runner) instead of a newtype, if only it -- weren't a recursive type descInt, descChar :: Descriptor descInt = const (runInt 1) where runInt n = R (do print n ; return . runInt $ n*2) descChar = const (runChar 'a') where runChar c = R (do print c ; return . runChar $ succ hd) descList :: [Descriptor] -- homogenous! descList = [ descInt, descChar ] -- --------- Finished! Look Ma, no existentials, no Typeable, no wrappers, even the types have become simple! Descriptor doesn't even need a type argument anymore, and indeed, why should it? Its purpose is exactly to _hide_ an Int/Char/whatever, not to expose it. Okay, I cheated a bit: I _did_ split Descriptor in two. That feels more right anyway, since 'instantiate' is only going to be called once (I think) and before 'instantiate' is called, there is no meaningful 'run' function anyway (and of that I'm sure). If you don't like that, feel free to fuse Descriptor and Runner back into one record, but then you need to think about what to initialize 'run' to. In fact, even in OO-Think you should be passing a constructor, err... factory to C land, not a half-baked object. Rest is wrappers to be able to call the above from the netherworlds, "foreign export" statements snipped. Oh, and lots of 'freeStablePtr' are also missing. Adding them will be left as a training exercise :) -- --------- chooseDesc :: Int -> IO (StablePtr Descriptor) chooseDesc n = newStablePtr (descList !! n) cInstantiate :: StablePtr Descriptor -> InstanceInitData -> IO (StablePtr Runner) cInstantiate ptr iid = do desc <- deRefStablePtr ptr newStablePtr . desc $ iid cRun :: StablePtr Runner-> IO (StablePtr Runner) cRun hdptr = deRefStablePtr hdptr >>= run >>= newStablePtr -- --------- -Udo -- "I've seen it. It's rubbish." -- Marvin the Paranoid Android

I really like your approach Udo, and I would use it, but I added the
condition of not splitting the descriptor for a good reason, let me
explain it.
Let's summarize what we have first ...
Here is my _simplified_ Descriptor
-- Descriptor, equivalent to a C struct with function pointers
-- hd is the handler of the callbacks (void *) in C
data Descriptor hd =
Descriptor { -- create a new instance and return its handler
instantiate :: InstanceInitData -> hd,
-- Run and return a new handler
run :: hd -> IO hd}
And here is Udo's proposal
-- ----------
type Descriptor = InstanceInitData -> Runner
-- a function! Who would have thought it?
newtype Runner = R { run :: IO Runner }
-- could be a plain (IO Runner) instead of a newtype, if only it
-- weren't a recursive type
On 12/13/06, Udo Stenzel
Finished! Look Ma, no existentials, no Typeable, no wrappers, even the types have become simple!
I don't quite agree with this. I like the fact that type parameters are removed, which makes them homegeneus and solves the problem of storing them in a list but as a drawback the Runner type is less intuitive than the simple run function. There's nothing horrible about it, but considering it's a binding I think that the types should resemble the original C types as much as possible. That has many advantages: the original documentation of the library would still apply and anyone who understands C code which makes use of the original library could translate it easily to Haskell afterwards.
Okay, I cheated a bit: I _did_ split Descriptor in two. That feels more right anyway, since 'instantiate' is only going to be called once (I think) and before 'instantiate' is called, there is no meaningful 'run' function anyway (and of that I'm sure).
As I said the example I posted is quite simplified. Actually the real descriptor (a naive translation from a C struct) is: -- hd and id are (void *) in C and modelled as type parameters in Haskell data Descriptor id hd = Descriptor {uniqueID :: LadspaIndex, label :: String, properties :: LadspaProperties, name, maker, copyright :: String, portCount :: LadspaIndex, portDescriptors :: [PortDescriptor], portNames :: [String], portRangeHints :: [PortRangeHint], implementationData :: id, instantiate :: Descriptor id hd -> LadspaIndex -> Maybe hd, -- In this case we are using lists to represent the port I/O buffers, so the -- port connections (buffer pointers of ports) is handled by the marshaller -- connectPort :: (hd -> LadspaIndex -> Ptr LadspaData -> IO hd) activate :: Maybe(hd -> IO ()), -- (LadspaIndex,PortData) indicates the portnumber and its data run :: hd -> LadspaIndex -> [(LadspaIndex,PortData)] -> ([(LadspaIndex,PortData)], hd), -- Not yet implemented (is not mandatory for a plugin to provide them) -- runAdding :: -- setAddingGain :: deactivate :: Maybe(hd -> IO ()), cleanup :: hd -> IO ()} As you can see, apart from the run function , a Descriptor has some other data and other functions, which can be _optional_ ( see deactivate, and activate) Those optional funcions cause a problem when splitting the type Udo did: The C code must know which of those are optional when calling chooseDescriptor. One solution would be adding some Booleans to the Descriptor, indicating wether those functions are finally going to be used or not ... but that causes redundancy and permits inconsistencies (Boolean in Descriptor + Maybe value of the function itself which don't match). That's how I actually do it right now (see http://www.student.nada.kth.se/~alfonsoa/HLADSPA/HLADSPA-0.2.1/src/HLADSPA.h... ). But I'm not happy with it. The only elegant solution which I could come up to solve the problem is simply avoiding to split the Descriptor by using unsafeCoerce# (which is not that elegant) to store the descriptors in a list. Thats when I decided to start this thread ... and why I wrote that not splitting the Descriptor was a must. Any Suggestions?

Alfonso Acosta wrote:
On 12/13/06, Udo Stenzel
wrote: Finished! Look Ma, no existentials, no Typeable, no wrappers, even the types have become simple!
I like the fact that type parameters are removed, which makes them homegeneus and solves the problem of storing them in a list but as a drawback the Runner type is less intuitive than the simple run function.
Actually the Runner type _is_ a simple (impure) function. The complication is just that you wrote your example in such a way that 'run' has to return a new 'run' function, and that gives it the type (a where a = IO a), which is not possible in Haskell without the use of a newtype. [...]
As I said the example I posted is quite simplified. Actually the real descriptor (a naive translation from a C struct) is:
-- hd and id are (void *) in C and modelled as type parameters in Haskell data Descriptor id hd = Descriptor {uniqueID :: LadspaIndex, label :: String, properties :: LadspaProperties, name, maker, copyright :: String, portCount :: LadspaIndex, portDescriptors :: [PortDescriptor], portNames :: [String], portRangeHints :: [PortRangeHint], implementationData :: id, instantiate :: Descriptor id hd -> LadspaIndex -> Maybe hd, -- In this case we are using lists to represent the port I/O buffers, so the -- port connections (buffer pointers of ports) is handled by the marshaller -- connectPort :: (hd -> LadspaIndex -> Ptr LadspaData -> IO hd) activate :: Maybe(hd -> IO ()), -- (LadspaIndex,PortData) indicates the portnumber and its data run :: hd -> LadspaIndex -> [(LadspaIndex,PortData)] -> ([(LadspaIndex,PortData)], hd), -- Not yet implemented (is not mandatory for a plugin to provide them) -- runAdding :: -- setAddingGain :: deactivate :: Maybe(hd -> IO ()), cleanup :: hd -> IO ()}
As you can see, apart from the run function , a Descriptor has some other data and other functions, which can be _optional_ ( see deactivate, and activate)
Okay, beautiful solution first, again splitting Discriptor in two and ignoring some fields being optional. Again, you have a factory and an actual object, and we will implement it exactly this way, for the moment ignoring the exports to C. I'm also leaving out "implementationData", because it's impossible to see what that's used for. data HdMaker = HdMaker { uniqueID :: LadspaIndex, label :: String, ... instantiate :: LadspaIndex -> Maybe Hd } data Hd = Hd { connectPort :: LadspaIndex -> Ptr LadspaData -> IO Hd , activate :: IO () , run :: LadspaIndex -> [(LadspaIndex, PortData)] -> ([(LadspaIndex, PortData)], Hd) , deactivate :: IO () , cleanup :: IO () } newHdMaker ... = HdMaker { ... , instantiate = newHandle } where newHandle = Hd { connectPort = , activate = , run = , deactivate = , cleanup = } You should be able to see how this is to be fleshed out. The important point is that the fields of Hd (which are set in newHandle) don't need to be passed a handle of sorts later, since that handle is already available, though of course I can't infer where it is supposed to come from. As usual, add newStablePtr/derefStablePtr as needed. I guess the connectPort function has to construct yet another Hd. Now you don't want to split the Descriptor record, because the C world already decided to pass an additional opaque handle type. That's no problem: you handle is simple the set of functions that take handles as parameters. data Descriptor = Descriptor { uniqueID :: LadspaIndex, ... instantiate :: LadspaIndex -> Maybe Hd, connectPort :: Hd -> LadspaIndex -> Ptr LadspaData -> IO Hd, activate :: IO () ... } newDescriptor ... = Descriptor { ... instantiate = newHandle, connectPort Hd = hd_connectPort Hd, activate Hd = hd_activate Hd, ... } where the fields of Hd have to be suitably renamed.
Those optional funcions cause a problem when splitting the type Udo did: The C code must know which of those are optional when calling chooseDescriptor.
The easiest thing to do is to always put them in and stick (return ()) where you don't actually need an action. Putting a Maybe there is also possible, but then a wrapper function has to check whether there is actually a function to be called. It's not clear why you think that is less of a problem if you lump everything into a single record, the check has to be made anyway.
The only elegant solution which I could come up to solve the problem is simply avoiding to split the Descriptor by using unsafeCoerce# (which is not that elegant) to store the descriptors in a list.
That's neither elegant nor a solution. -Udo -- Did you know that if you took all the economists in the world and lined them up end to end, they'd still point in the wrong direction?

Sorry for the delay answering.
First of all I'd like to thank everyone taking part on this thread. I
wouldn't have expected it to get this long.
On 12/13/06, Udo Stenzel
Alfonso Acosta wrote:
-- hd and id are (void *) in C and modelled as type parameters in Haskell data Descriptor id hd = Descriptor {uniqueID :: LadspaIndex, label :: String, properties :: LadspaProperties, name, maker, copyright :: String, portCount :: LadspaIndex, portDescriptors :: [PortDescriptor], portNames :: [String], portRangeHints :: [PortRangeHint], implementationData :: id, instantiate :: Descriptor id hd -> LadspaIndex -> Maybe hd, -- In this case we are using lists to represent the port I/O buffers, so the -- port connections (buffer pointers of ports) is handled by the marshaller -- connectPort :: (hd -> LadspaIndex -> Ptr LadspaData -> IO hd) activate :: Maybe(hd -> IO ()), -- (LadspaIndex,PortData) indicates the portnumber and its data run :: hd -> LadspaIndex -> [(LadspaIndex,PortData)] -> ([(LadspaIndex,PortData)], hd), -- Not yet implemented (is not mandatory for a plugin to provide them) -- runAdding :: -- setAddingGain :: deactivate :: Maybe(hd -> IO ()), cleanup :: hd -> IO ()}
[snip]
.... I'm also leaving out "implementationData", because it's impossible to see what that's used for.
Read below.
... I guess the connectPort function has to construct yet another Hd.
Well, maybe it's difficult to understand how the initial struct works without looking at it. You can find it at: http://www.ladspa.org/ladspa_sdk/ladspa.h.txt , look for "typedef struct _LADSPA_Descriptor" If it absorbs too much time forget about it, I'm really thankful anyway for the effort you took already.
Now you don't want to split the Descriptor record, because the C world already decided to pass an additional opaque handle type. That's no problem: you handle is simple the set of functions that take handles as parameters.
data Descriptor = Descriptor { uniqueID :: LadspaIndex, ... instantiate :: LadspaIndex -> Maybe Hd, connectPort :: Hd -> LadspaIndex -> Ptr LadspaData -> IO Hd, activate :: IO () ... }
newDescriptor ... = Descriptor { ... instantiate = newHandle, connectPort Hd = hd_connectPort Hd, activate Hd = hd_activate Hd, ... }
where the fields of Hd have to be suitably renamed.
I don't understand how this is supposed to work, mainly due to the ommited code. Creating a full example considering just a few representative fileds (uniqueID, instantiate, run and activate) would deinitively help. I'm specially confused by the use of newHandle in the newDescriptor function because it's a function out of scope (you previously defined it inside a "where")
Those optional funcions cause a problem when splitting the type Udo did: The C code must know which of those are optional when calling chooseDescriptor.
The easiest thing to do is to always put them in and stick (return ()) where you don't actually need an action. Putting a Maybe there is also possible, but then a wrapper function has to check whether there is actually a function to be called. It's not clear why you think that is less of a problem if you lump everything into a single record, the check has to be made anyway.
If you don't split the descriptor the the check has to be done, but only _once_, then function won't be called anymore. Let me explain this ... The C code will ask for a descriptor. Then this descriptor will be chosen, marshaled and translated to C. The struct will then be filled with values and passed to a host (we are implemening the plugin side of ladspa), and we have no control over it (we cannot modify it) If by the time of marshaling a Descriptor we know which functions are ommited, we fill those fields with Null and forget about the probelm If we have to wait to instantiate a plugin in order to know wether they are optional or not (that's how it works if you split the Descriptor type) the only way to go is filling the C struct with phantom functions which might do something or not later, depending on what funtions are optional in the instance. What is sure is that .... 1) Externally (the C world of the plugin host) the plugin will be regarded as always using those functions 2) Thus, the phantom functions will be called all the time. If this happens ... you are right there's not such a difference between having a Maybe or a Null function cause the a call has to be made anyway to check it. Again, it will maybe just be easier to have a look at the C header than trying to understand me ;) It's really well documented. Sorry for being that tiresome. I didn't post it yet, but here is the solution I got to before statring this thread. data Handle hd => Descriptor id hd = Descriptor {uniqueID :: LadspaIndex, label :: String, properties :: LadspaProperties, name, maker, copyright :: String, portCount :: LadspaIndex, portDescriptors :: [PortDescriptor], portNames :: [String], portRangeHints :: [PortRangeHint], implementationData :: id, instantiate :: Descriptor id hd -> LadspaIndex -> Maybe hd, usesActivate :: Bool, usesDeactivate :: Bool} class Handle hd where -- In this case we are using lists to represent the port I/O buffers, so the -- port connections (buffer pointers of ports) is handled by the marshaller -- connectPort :: (hd -> LadspaIndex -> Ptr LadspaData -> IO hd) activate :: Maybe(hd -> IO ()) activate = Nothing -- (LadspaIndex,PortData) indicates the portnumber and its data run :: hd -> LadspaIndex -> [(LadspaIndex,PortData)] -> ([(LadspaIndex,PortData)], hd) -- Not yet implemented (is not mandatory for a plugin to provide them) -- runAdding :: -- setAddingGain :: deactivate :: Maybe(hd -> IO ()) -- default value deactivate = Nothing cleanup :: hd -> IO () cleanup _ = return () -- code for allowing to pack descriptors in lists. data GDescriptor = forall id hd.Handle hd => GDes (Descriptor id hd) des2GDes :: Handle hd => Descriptor id hd -> GDescriptor des2GDes = GDes Note the redundancy between usesActivate, usesDeactivate, and the Maybe values of the typeclass. It can lead to inconsistencies (usesActivate = False, activate = Just ... ). But it's the only way I could find to del with the problem I wrote about above (knowing if activate and deactivate will be used at the time of marshalling a descriptor)

On 12/13/06, Alfonso Acosta
-- hd and id are (void *) in C and modelled as type parameters in Haskell data Descriptor id hd = Descriptor {uniqueID :: LadspaIndex, label :: String, properties :: LadspaProperties, name, maker, copyright :: String, portCount :: LadspaIndex, portDescriptors :: [PortDescriptor], portNames :: [String], portRangeHints :: [PortRangeHint], implementationData :: id, instantiate :: Descriptor id hd -> LadspaIndex -> Maybe hd,
Oh, LADSPA. Suddenly everything make so much more sense.
First, the implementationData is useless to you. Put it in a closure
when building this object:
ladspa_descriptor = do
...
let implementationData = ...
return Descriptor { ... referencing implementationData ... }
No need to export that to the user only to have them pass it back in.
Second, you don't want the consumer to pick the hd type. If you're
willing to accept extensions (I think you are), make it existential:
data Descriptor = forall hd. Descriptor { ... }
This will ensure that you can't pass the handles from one plugin to
the methods of another.
--
Taral

On 12/13/06, Taral
Second, you don't want the consumer to pick the hd type. If you're willing to accept extensions (I think you are), make it existential:
data Descriptor = forall hd. Descriptor { ... }
This will ensure that you can't pass the handles from one plugin to the methods of another.
Third, we can split handles out as actual objects now:
data Descriptor =
Descriptor {uniqueID :: LadspaIndex,
label :: String,
properties :: LadspaProperties,
name, maker, copyright :: String,
portCount :: LadspaIndex,
portDescriptors :: [PortDescriptor],
portNames :: [String],
portRangeHints :: [PortRangeHint],
instantiate :: LadspaIndex -> IO (Maybe Handle),
}
data Handle =
Handle {descriptor :: Descriptor,
activate :: IO (),
-- (LadspaIndex,PortData) indicates the portnumber and its data
run :: LadspaIndex -> [(LadspaIndex,PortData)] -> IO
[(LadspaIndex, PortData)],
deactivate :: IO (),
cleanup :: IO (),
}
Then you'll want helpers that use Control.Exception.bracket to provide
exception-safe access to these objects. For example:
withHandle h = bracket (activate h) (deactivate h)
You can also optionally use cleanup as the finalizer for the
ForeignPtr underlying Handles, but the GC isn't guaranteed to be
timely about calling finalizers, so that may or may not be what you
want.
--
Taral

On 12/13/06, Taral
Third, we can split handles out as actual objects now:
This idea resembles how a descriptor is modelled in the last version of HLADSPA. The difference is that a handle is modelled as a type class and not a record (see http://www.student.nada.kth.se/~alfonsoa/HLADSPA/HLADSPA-0.2.1/src/HLADSPA.h... )
data Handle = Handle {descriptor :: Descriptor, activate :: IO (), -- (LadspaIndex,PortData) indicates the portnumber and its data run :: LadspaIndex -> [(LadspaIndex,PortData)] -> IO [(LadspaIndex, PortData)], deactivate :: IO (), cleanup :: IO (), }
I wouldn't quite call this a Handle ... actually it only contains the functions which operate over a handle (I would better call it Instance). It lacks the handle itself (the state passed to, and possibly altered by, the functions of an instance) and makes the instance stateless. e.g. you modified run :: hd -> LadspaIndex -> [(LadspaIndex,PortData)] -> ([(LadspaIndex,PortData)], hd), into run :: LadspaIndex -> [(LadspaIndex,PortData)] -> IO[(LadspaIndex, PortData)] Now the behaviour of run over the input audio doesn't depend on any state. That state is a must (and that's why handles are used). Otherwise things such as a delay effect wouldn't be able to remember how many samples it did process already between calls to run and thus wouldn't be feasible to implement.
Then you'll want helpers that use Control.Exception.bracket ...
Well, I couldn't find that function in hoogle and it's not present at http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception... But I think that you are suggesting is to leave activate or deactivate undefined in the record if they are not required. Then it should be checked wheter they are undefined or not controlling if a exception is raised when attempting to access them. I don't see how that is an advantage compared to using Maybe. Actually Nothing is more expressive than omitting the functions and furthermore I don't think that leaving record fiedls undefined is a good practice in general.
You can also optionally use cleanup as the finalizer for the ForeignPtr underlying Handles ...
I don't see what you mean here. I'm not using ForeignPtrs at all.

On 12/13/06, Taral
On 12/13/06, Alfonso Acosta
wrote: -- hd and id are (void *) in C and modelled as type parameters in Haskell data Descriptor id hd = Descriptor {uniqueID :: LadspaIndex, label :: String, properties :: LadspaProperties, name, maker, copyright :: String, portCount :: LadspaIndex, portDescriptors :: [PortDescriptor], portNames :: [String], portRangeHints :: [PortRangeHint], implementationData :: id, instantiate :: Descriptor id hd -> LadspaIndex -> Maybe hd,
Oh, LADSPA. Suddenly everything make so much more sense.
I'm glad it does, I probably should have just started a thread asking for advice for the translation of the struct. It's important to let people know the source of the problem when asking. I didn't mention it cause that question was already in HLADSPA's initial release announcement post (http://www.mail-archive.com/haskell-cafe@haskell.org/msg17620.html ) and didn't cause any excitement in the list :P.
First, the implementationData is useless to you. Put it in a closure when building this object:
That has been one of doubts from the begining (please check the message mentioned above) I decided to leave it, for compatibility with LADSPA (but you might be right saying that it's useles and should be removed). Again, I continue saying that the more a binding resembles the original library, the easier it would be for a developer who is familiar with the original library to begin using it.
ladspa_descriptor = do ... let implementationData = ... return Descriptor { ... referencing implementationData ... }
No need to export that to the user only to have them pass it back in.
Actually the library requires some C wrapping glue code (which does the memory management, inits GHC's RTS and does the marshalling) so I can just omit it and fill in in the wrapper with a NULL value.
Second, you don't want the consumer to pick the hd type. If you're willing to accept extensions (I think you are), make it existential:
data Descriptor = forall hd. Descriptor { ... }
This will ensure that you can't pass the handles from one plugin to the methods of another.
This is exactly how it was implemented in the initial release :) (please check the HLADSPA announcement for details). The Descriptor posted here is a naive translation from a C struct

On 12/13/06, Taral
On 12/13/06, Alfonso Acosta
wrote: deactivate :: Maybe(hd -> IO ()),
According to the spec, NULL here means no-op. So instead of using Maybe, just set deactivate = \_ -> return () if you see NULL.
I considered this solution as well, but is not really acceptable cause the function would be called anyway (which would harm performance). Furthermore is not sematically correct as externally the descriptor would be viewed as having a deactivate.

Hello Udo, Wednesday, December 13, 2006, 3:25:32 AM, you wrote:
Well, all you need to do is to throw out your OO-Think (and with it Typeable and casts) and you'll realize what you're actually doing here: you're passing functions. Say so and everything comes naturally.
Alfonso, you may be interested in reading the following pages where i put some examples of passing functions in the cases where OOP programmers use classes. after all, OOP class is just data+functions bundled together, while in Haskell these are separate concepts http://haskell.org/haskellwiki/OOP_vs_type_classes http://haskell.org/haskellwiki/IO_inside (look at "Example: a list of IO actions" and next chapters) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Alfonso Acosta wrote:
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 ...
It looks to me like the C code could make your program segfault from a type missmatch, if it gets a handle from instantiating one descriptor, and tries to run it from another. Building code which can fail that way hopefully requires unsafeCoerce! I think Udo's code is the best way to go, if it solves your problem. Udo's code is equivalent to code similar to yours but defined around the existential type data Descriptor = forall hd . Descriptor { -- create a new instance and return its handler instantiate :: InstanceInitData -> hd, -- Run and return a new handler run :: hd -> IO hd} Then observing that because hd is hidden you can only use an hd by passing it run, so you might as well wrap it up in that Runner type. If you want to be able to define several Descriptors over the same type hd, and trade handles back and forth between their run functions, then you will need some casting (but tools from Typeable and Dynamic should be enough, without bringing unsafeCoerce) Brandon

On 12/13/06, Brandon Moore
It looks to me like the C code could make your program segfault from a type missmatch, if it gets a handle from instantiating one descriptor, and tries to run it from another.
Well, the C code could even provide (by error or at will) any pointer value which could mismatch or not. C is potentially dangerous by definition and there is no way to cope with that whatever we export from Haskell. This is just a particular case of that major problem, in which we use a instance handle.
Building code which can fail that way hopefully requires unsafeCoerce!
Any haskell code which receives a C pointer is likely to suffer from the type-mismatch segfault problem you mentioned above. The purpose of using unsafeCoerce in my code is to allow me to pack some polymorphic values in a list as if they ware homogeneous. I don't see how unsafeCoerce would help me with a type mismatch.
I think Udo's code is the best way to go, if it solves your problem. Udo's code is equivalent to code similar to yours but defined around the existential type
data Descriptor = forall hd . Descriptor { -- create a new instance and return its handler instantiate :: InstanceInitData -> hd, -- Run and return a new handler run :: hd -> IO hd}
Hiding the hd parameter breaks the C-exported cRun function.
Then observing that because hd is hidden you can only use an hd by passing it run, so you might as well wrap it up in that Runner type.
Which yet again, requires splitting Descriptor in two.
If you want to be able to define several Descriptors over the same type hd, and ....
Different descriptors are allowed to have different handlers (void *) in C. That's a precondition, and furthermore, the source of my modelling problem and this thread :)
participants (6)
-
Alfonso Acosta
-
Brandon Moore
-
Bulat Ziganshin
-
Lemmih
-
Taral
-
Udo Stenzel