module Sound.ALSA.Sequencer.Marshal.ClientInfo where
import qualified Sound.ALSA.Sequencer.Marshal.Client as Client
import qualified Sound.ALSA.Sequencer.Marshal.Sequencer as Seq
import qualified Sound.ALSA.Sequencer.Area as Area
import qualified Sound.ALSA.Sequencer.Query as Query
import qualified Sound.ALSA.Sequencer.Utility as U
import qualified Sound.ALSA.Exception as Exc
import qualified Foreign.C.Types as C
import Foreign.Ptr (Ptr, )
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.client_info" =<< malloc_ p
fmap Cons (Area.newForeignPtr free =<< Area.peek p)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_malloc"
malloc_ :: Area.Ptr (Area.Ptr T_) -> IO C.CInt
foreign import ccall unsafe "alsa/asoundlib.h &snd_seq_client_info_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_client_info_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
getName :: T -> IO String
getName i = Area.peekCString =<< with i getName_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_name"
getName_ :: Area.Ptr T_ -> IO Area.CString
setName :: T -> String -> IO ()
setName i c =
Area.withCAString c $ \p -> with i (flip setName_ p)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_set_name"
setName_ :: Area.Ptr T_ -> Area.CString -> IO ()
getBroadcastFilter :: T -> IO Bool
getBroadcastFilter i =
fmap (0 /=) $ with i getBroadcastFilter_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_broadcast_filter"
getBroadcastFilter_ :: Area.Ptr T_ -> IO C.CInt
setBroadcastFilter :: T -> Bool -> IO ()
setBroadcastFilter i c =
let x = if c then 1 else 0
in with i (flip setBroadcastFilter_ x)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_set_broadcast_filter"
setBroadcastFilter_ :: Area.Ptr T_ -> C.CInt -> IO ()
getErrorBounce :: T -> IO Bool
getErrorBounce i =
fmap (0 /=) $ with i getErrorBounce_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_error_bounce"
getErrorBounce_ :: Area.Ptr T_ -> IO C.CInt
setErrorBounce :: T -> Bool -> IO ()
setErrorBounce i c =
let x = if c then 1 else 0
in with i (flip setErrorBounce_ x)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_set_error_bounce"
setErrorBounce_ :: Area.Ptr T_ -> C.CInt -> IO ()
getClient :: T -> IO Client.T
getClient i =
fmap Client.imp $ with i getClient_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_client"
getClient_ :: Area.Ptr T_ -> IO C.CInt
setClient :: T -> Client.T -> IO ()
setClient i c =
with i (flip setClient_ (Client.exp c))
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_set_client"
setClient_ :: Area.Ptr T_ -> C.CInt -> IO ()
getType :: T -> IO Client.Type
getType i =
fmap Client.impType $ with i getType_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_type"
getType_ :: Area.Ptr T_ -> IO C.CInt
getNumPorts :: T -> IO Word
getNumPorts i =
fmap fromIntegral $ with i getNumPorts_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_num_ports"
getNumPorts_ :: Area.Ptr T_ -> IO C.CInt
getEventLost :: T -> IO Word
getEventLost i =
fmap fromIntegral $ with i getEventLost_
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_client_info_get_event_lost"
getEventLost_ :: Area.Ptr T_ -> IO C.CInt
get :: Seq.T mode -> IO T
get (Seq.Cons h) =
do info <- malloc
Exc.checkResult_ "ClientInfo.get" =<< with info (get_ h)
return info
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_get_client_info"
get_ :: Ptr Seq.Core -> Ptr T_ -> IO C.CInt
getAny :: Seq.T mode -> Client.T -> IO T
getAny (Seq.Cons h) c =
do info <- malloc
Exc.checkResult_ "ClientInfo.getAny" =<<
with info (getAny_ h (Client.exp c))
return info
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_get_any_client_info"
getAny_
:: Ptr Seq.Core -> C.CInt -> Ptr T_ -> IO C.CInt
set :: Seq.T mode -> T -> IO ()
set (Seq.Cons h) info =
Exc.checkResult_ "set_client_info" =<< with info (set_ h)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_set_client_info"
set_ :: Ptr Seq.Core -> Ptr T_ -> IO C.CInt
queryInit :: T -> IO ()
queryInit x =
with x (flip setClient_ (1))
queryNext :: Seq.T mode -> T -> IO Bool
queryNext (Seq.Cons h) info =
U.checkResultQuery "ClientInfo.queryNext" =<< with info (queryNext_ h)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_query_next_client"
queryNext_ :: Ptr Seq.Core -> Ptr T_ -> IO C.CInt
instance Query.C T where
init = queryInit
next = queryNext