module Sound.ALSA.Sequencer.Queue.Timer
( T
, get
, set
, copy
, clone
, getQueue
, getType
, getResolution
, setType
, setResolution
, Type(..)
) where
import qualified Sound.ALSA.Sequencer.Marshal.Queue as Queue
import qualified Sound.ALSA.Sequencer.Marshal.Sequencer as Seq
import qualified Sound.ALSA.Sequencer.Area as Area
import qualified Sound.ALSA.Exception as Exc
import qualified Foreign.C.Types as C
import Data.Word (Word, )
data T_
newtype T = Cons (Area.ForeignPtr T_)
with :: T -> (Area.Ptr T_ -> IO a) -> IO a
with (Cons p) f = Area.withForeignPtr p f
malloc :: IO T
malloc = Area.alloca $ \p ->
do Exc.checkResult_ "Sequencer.queue_timer" =<< malloc_ p
fmap Cons (Area.newForeignPtr free =<< Area.peek p)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_malloc"
malloc_ :: Area.Ptr (Area.Ptr T_) -> IO C.CInt
foreign import ccall unsafe "alsa/asoundlib.h &snd_seq_queue_timer_free"
free :: Area.FunPtr (Area.Ptr T_ -> IO ())
copy
:: T
-> T
-> IO ()
copy to from =
with to $ \p1 ->
with from $ \p2 ->
copy_ p1 p2
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_copy"
copy_ :: Area.Ptr T_ -> Area.Ptr T_ -> IO ()
clone :: T -> IO T
clone from =
do to <- malloc
copy to from
return to
instance Area.C T where
malloc = malloc
copy = copy
clone = clone
get :: Seq.T mode -> Queue.T -> IO T
get h q =
do status <- malloc
Exc.checkResult_ "get_queue_timer"
=<< with status (get_ h q)
return status
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_get_queue_timer"
get_ :: Seq.T mode -> Queue.T -> Area.Ptr T_ -> IO C.CInt
set :: Seq.T mode -> Queue.T -> T -> IO ()
set h q info =
Exc.checkResult_ "set_queue_timer" =<< with info (set_ h q)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_set_queue_timer"
set_ :: Seq.T mode -> Queue.T -> Area.Ptr T_ -> IO C.CInt
getQueue :: T -> IO Queue.T
getQueue i =
fmap Queue.imp $ with i getQueue_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_get_queue"
getQueue_ :: Area.Ptr T_ -> IO C.CInt
getType :: T -> IO Type
getType i =
fmap impType $ with i getType_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_get_type"
getType_ :: Area.Ptr T_ -> IO C.CInt
setType :: T -> Type -> IO ()
setType i c =
with i (flip setType_ (expType c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_set_type"
setType_ :: Area.Ptr T_ -> C.CInt -> IO ()
getResolution :: T -> IO Word
getResolution i =
fmap fromIntegral $ with i getResolution_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_get_resolution"
getResolution_ :: Area.Ptr T_ -> IO C.CInt
setResolution :: T -> Word -> IO ()
setResolution i c =
with i (flip setResolution_ (fromIntegral c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_timer_set_resolution"
setResolution_ :: Area.Ptr T_ -> C.CInt -> IO ()
data Type =
Alsa
| MidiClock
| MidiTick
deriving (Show, Eq, Ord, Enum)
expType :: Type -> C.CInt
expType t = case t of
Alsa -> 0
MidiClock -> 1
MidiTick -> 2
impType :: C.CInt -> Type
impType t = case t of
0 -> Alsa
1 -> MidiClock
2 -> MidiTick
_ -> error ("QueueTimer.impType: unknown timer type (" ++ show t ++ ")")