{-# LINE 1 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
--------------------------------------------------------------------------------
{-# LINE 2 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
-- |
-- Module    : Sound.ALSA.Sequencer.Client
-- Copyright : (c) Henning Thielemann, 2010-2012
--             (c) Iavor S. Diatchki, 2007
-- License   : BSD3
--
-- Maintainer: Henning Thielemann
-- Stability : provisional
--
-- This module contains functions for working with sequencer clients.
-- Reference:
-- <http://www.alsa-project.org/alsa-doc/alsa-lib/group___seq_client.html>
--------------------------------------------------------------------------------

module Sound.ALSA.Sequencer.Marshal.ClientInfo where


{-# LINE 19 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}

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

-- | Allocate an uninitialized object. (Not exported)
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 the content of one object into another.
copy
  :: T     -- ^ Destination
  -> T     -- ^ Source
  -> 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 ()

-- | Copy the content of an object to a newly created object.
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



{-# LINE 33 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}

-- read/write
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 ()


{-# LINE 36 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
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 ()


{-# LINE 37 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
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 ()


{-# LINE 38 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
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 ()


{-# LINE 40 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}

-- read only
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


{-# LINE 44 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
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


{-# LINE 46 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}
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


{-# LINE 48 "src/Sound/ALSA/Sequencer/Marshal/ClientInfo.hsc" #-}



-- | Create a new information area filled with data about the sequencer client.
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


-- | Create a new information area filled with data about an arbitrary client.
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 the information for the sequencer client based on the data
-- in the given information area.
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 =
  {-
  we cannot use setClient here,
  since Client uses an unsigned type and thus cannot represent -1
  -}
  with x (flip setClient_ (-1))

-- | Get information about the client with the next biggest identifier.
queryNext :: Seq.T mode -> T -> IO Bool  -- ^ Was there a next client?
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