On 12/13/06, Taral <[EMAIL PROTECTED]> wrote:
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 <[EMAIL PROTECTED]>
"You can't prove anything."
   -- Gödel's Incompetence Theorem
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to