[Haskell-cafe] Dynamic types through unsafeCoerce

Alfonso Acosta alfonso.acosta at gmail.com
Thu Dec 14 17:15:34 EST 2006


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 <u.stenzel at web.de> wrote:
> 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)


More information about the Haskell-Cafe mailing list