[Haskell-cafe] Dynamic types through unsafeCoerce

Udo Stenzel u.stenzel at web.de
Wed Dec 13 09:16:39 EST 2006


Alfonso Acosta wrote:
> On 12/13/06, Udo Stenzel <u.stenzel at web.de> 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?
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20061213/394d43a8/attachment.bin


More information about the Haskell-Cafe mailing list