Lazy IO and asynchronous callbacks?

Evan Laforge qdunkan at gmail.com
Thu Jul 8 19:01:28 EDT 2010


On Thu, Jul 8, 2010 at 3:25 PM, J. Garrett Morris <jgmorris at cs.pdx.edu> wrote:
> Hello everyone,
>
> I'm currently in the process of wrapping a C API, and I've run across
> an interesting possibility.  Basically, the C API exposes non-blocking
> versions of some potentially long-running operations, and will invoke
> a callback to indicate that the long running operation has finished.
> For instance, I have something like:
>
> int longRunningReadOperation(int length, byte * buf, void (*callback)())

I've done something much like this for a MIDI driver.  My approach was
to pass a haskell callback to the async reader (via "foreign import
ccall "wrapper").  The haskell function then shoves its data into a
chan.

There may very well be a better way to do this, but it definitely
feels better to me than relying on unsafeInterleaveIO magic.  Your
chan reader has to be in IO, but that's as it should be and you can
still pass the chunks off to pure functions.


initialize :: (ReadChan -> IO a) -> IO a
initialize app = do
    chan <- STM.newTChanIO
    Exception.bracket (make_read_callback (chan_callback chan))
        freeHaskellFunPtr $ \cb -> do
            check_ =<< c_initialize cb
            app chan `Exception.finally` terminate

foreign import ccall "core_midi_terminate" terminate :: IO ()
foreign import ccall "core_midi_initialize"
    c_initialize :: FunPtr ReadCallback -> IO CError
foreign import ccall "wrapper"
    make_read_callback :: ReadCallback -> IO (FunPtr ReadCallback)

chan_callback :: ReadChan -> ReadCallback
chan_callback chan sourcep ctimestamp len bytesp = do
    -- Oddly enough, even though ByteString is Word8, the ptr packing function
    -- wants CChar.
    bytes <- ByteString.packCStringLen (castPtr bytesp, fromIntegral len)
    rdev <- deRefStablePtr sourcep
    let rmsg = Midi.ReadMessage
                rdev (decode_timestamp ctimestamp) (Parse.decode bytes)
    STM.atomically $ STM.writeTChan chan rmsg


More information about the Glasgow-haskell-users mailing list