module Sound.ALSA.Sequencer.Queue.Tempo
( T
, get
, set
, copy
, clone
, getQueue
, getTempo
, getPPQ
, getSkew
, getSkewBase
, setTempo
, setPPQ
, setSkew
, setSkewBase
) 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_tempo" =<< malloc_ p
fmap Cons (Area.newForeignPtr free =<< Area.peek p)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_malloc"
malloc_ :: Area.Ptr (Area.Ptr T_) -> IO C.CInt
foreign import ccall unsafe "alsa/asoundlib.h &snd_seq_queue_tempo_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_tempo_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_tempo"
=<< with status (get_ h q)
return status
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_get_queue_tempo"
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_tempo" =<< with info (set_ h q)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_set_queue_tempo"
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_tempo_get_queue"
getQueue_ :: Area.Ptr T_ -> IO C.CInt
getTempo :: T -> IO Word
getTempo i =
fmap fromIntegral $ with i getTempo_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_get_tempo"
getTempo_ :: Area.Ptr T_ -> IO C.CInt
setTempo :: T -> Word -> IO ()
setTempo i c =
with i (flip setTempo_ (fromIntegral c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_set_tempo"
setTempo_ :: Area.Ptr T_ -> C.CInt -> IO ()
getPPQ :: T -> IO Int
getPPQ i =
fmap fromIntegral $ with i getPPQ_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_get_ppq"
getPPQ_ :: Area.Ptr T_ -> IO C.CInt
setPPQ :: T -> Int -> IO ()
setPPQ i c =
with i (flip setPPQ_ (fromIntegral c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_set_ppq"
setPPQ_ :: Area.Ptr T_ -> C.CInt -> IO ()
getSkew :: T -> IO Word
getSkew i =
fmap fromIntegral $ with i getSkew_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_get_skew"
getSkew_ :: Area.Ptr T_ -> IO C.CInt
setSkew :: T -> Word -> IO ()
setSkew i c =
with i (flip setSkew_ (fromIntegral c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_set_skew"
setSkew_ :: Area.Ptr T_ -> C.CInt -> IO ()
getSkewBase :: T -> IO Word
getSkewBase i =
fmap fromIntegral $ with i getSkewBase_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_get_skew_base"
getSkewBase_ :: Area.Ptr T_ -> IO C.CInt
setSkewBase :: T -> Word -> IO ()
setSkewBase i c =
with i (flip setSkewBase_ (fromIntegral c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_queue_tempo_set_skew_base"
setSkewBase_ :: Area.Ptr T_ -> C.CInt -> IO ()