module Sound.ALSA.Sequencer.Queue
  ( 
    Queue.T
  , Queue.direct
  , alloc
  , allocNamed
  , free
  , with
  , withNamed
  , control
  ) where
import qualified Sound.ALSA.Sequencer.Marshal.Sequencer as Seq
import qualified Sound.ALSA.Sequencer.Marshal.Event as Event
import qualified Sound.ALSA.Sequencer.Marshal.Queue as Queue
import qualified Sound.ALSA.Exception as Exc
import Foreign.Ptr (Ptr, )
import Foreign.C.Types (CInt, )
import Foreign.C.String (CString, withCAString, )
import Control.Exception (bracket, )
alloc :: Seq.T mode -> IO Queue.T 
alloc (Seq.Cons h) =
  Queue.imp `fmap` (Exc.checkResult "alloc_queue" =<< snd_seq_alloc_queue h)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_alloc_queue"
  snd_seq_alloc_queue :: Ptr Seq.Core -> IO CInt
with :: Seq.T mode -> (Queue.T -> IO a) -> IO a
with s = bracket (alloc s) (free s)
allocNamed :: Seq.T mode -> String -> IO Queue.T
allocNamed (Seq.Cons h) x = withCAString x $ \s ->
  Queue.imp `fmap` (Exc.checkResult "alloc_named_queue" =<< snd_seq_alloc_named_queue h s)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_alloc_named_queue"
  snd_seq_alloc_named_queue :: Ptr Seq.Core -> CString -> IO CInt
withNamed :: Seq.T mode -> String -> (Queue.T -> IO a) -> IO a
withNamed s nm = bracket (allocNamed s nm) (free s)
free
  :: Seq.T mode   
  -> Queue.T    
  -> IO ()
free (Seq.Cons h) q =
  Exc.checkResult_ "free_queue" =<< snd_seq_free_queue h (Queue.exp q)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_free_queue"
  snd_seq_free_queue :: Ptr Seq.Core -> CInt -> IO CInt
control
  :: Seq.T mode   
  -> Queue.T         
  -> Event.QueueEv
  -> Int
  -> Maybe Event.T
  -> IO ()
control (Seq.Cons h) q a b me =
  Event.allocaMaybeEv me $ \p -> Exc.checkResult_ "control_queue" =<< snd_seq_control_queue h (Queue.exp q) (fromIntegral $ Event.expEv a) (fromIntegral b) p
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_control_queue"
  snd_seq_control_queue :: Ptr Seq.Core -> CInt -> CInt -> CInt -> Ptr Event.T -> IO CInt