module Sound.Pulse.Sinkinfo
( SinkFlags(..)
, SinkState(..)
, Sinkinfo(..)
, getContextSinks
, getContextSinkByName
, getContextSinkByIndex
, getContextSinksM
, getContextSinkByNameM
, getContextSinkByIndexM
)
where
import Control.Applicative ((<$>), (<*>))
import Sound.Pulse
import Sound.Pulse.Volume
import Sound.Pulse.Operation
import Sound.Pulse.Userdata
import Data.Word (Word32, Word8, Word)
import Control.Monad (void)
import Foreign.Ptr (Ptr, FunPtr, freeHaskellFunPtr, castFunPtrToPtr, castPtrToFunPtr)
import Foreign.C.Types (CInt(..), CUInt(..))
import Foreign.C.String (peekCString, withCString, CString)
import Foreign.Storable (Storable(..))
import Sound.Pulse.Context (Context)
import Sound.Pulse.ChannelPosition
import Sound.Pulse.SampleSpec
import Sound.Pulse.Def (SinkFlags(..), sinkFlagssFromInt, SinkState(..), sinkStateFromInt)
data PropList
data FormatInfo
data SinkPortInfo
data Sinkinfo = Sinkinfo
{ siName :: String
, siIndex :: Word32
, siDescription :: String
, siSampleSpec :: SampleSpec
, siChannelMap :: ChannelMap
, siOwnerModule :: Word32
, siVolume :: CVolume
, siMute :: Bool
, siMonitorSource :: Word32
, siMonitorSourceName :: String
, siLatency :: Word
, siDriver :: String
, siFlags :: [SinkFlags]
, siProplist :: Ptr PropList
, siConfiguredLatency :: Word
, siBaseVolume :: Volume
, siState :: SinkState
, siVolumeSteps :: Word32
, siCard :: Word32
, siPorts :: [Ptr SinkPortInfo]
, siActivePort :: Ptr SinkPortInfo
, siFormats :: [Ptr FormatInfo]
} deriving (Eq, Show)
instance Storable Sinkinfo where
sizeOf _ = (416)
alignment _ = (8)
peek p = Sinkinfo
<$> (peekCString =<< (\hsc_ptr -> peekByteOff hsc_ptr 0) p)
<*> (\hsc_ptr -> peekByteOff hsc_ptr 8) p
<*> (peekCString =<< (\hsc_ptr -> peekByteOff hsc_ptr 16) p)
<*> (\hsc_ptr -> peekByteOff hsc_ptr 24) p
<*> (\hsc_ptr -> peekByteOff hsc_ptr 36) p
<*> (\hsc_ptr -> peekByteOff hsc_ptr 168) p
<*> (\hsc_ptr -> peekByteOff hsc_ptr 172) p
<*> ((/= (0 :: CInt)) <$> ((\hsc_ptr -> peekByteOff hsc_ptr 304) p))
<*> (\hsc_ptr -> peekByteOff hsc_ptr 308) p
<*> (peekCString =<< (\hsc_ptr -> peekByteOff hsc_ptr 312) p)
<*> (\hsc_ptr -> peekByteOff hsc_ptr 320) p
<*> (peekCString =<< (\hsc_ptr -> peekByteOff hsc_ptr 328) p)
<*> (sinkFlagssFromInt <$> ((\hsc_ptr -> peekByteOff hsc_ptr 304) p))
<*> (\hsc_ptr -> peekByteOff hsc_ptr 344) p
<*> (\hsc_ptr -> peekByteOff hsc_ptr 352) p
<*> (\hsc_ptr -> peekByteOff hsc_ptr 360) p
<*> (sinkStateFromInt <$> ((\hsc_ptr -> peekByteOff hsc_ptr 304) p))
<*> (\hsc_ptr -> peekByteOff hsc_ptr 368) p
<*> (\hsc_ptr -> peekByteOff hsc_ptr 372) p
<*> do
size :: Word8 <- (\hsc_ptr -> peekByteOff hsc_ptr 376) p
ptr <- (\hsc_ptr -> peekByteOff hsc_ptr 384) p
mapM (peekElemOff ptr . fromIntegral) [0.. size 1]
<*> (\hsc_ptr -> peekByteOff hsc_ptr 392) p
<*> do
size :: Word8 <- (\hsc_ptr -> peekByteOff hsc_ptr 400) p
ptr :: Ptr (Ptr FormatInfo) <- (\hsc_ptr -> peekByteOff hsc_ptr 408) p
mapM (peekElemOff ptr . fromIntegral) [0.. size 1]
poke _ (Sinkinfo {..}) = error "PA: Currently no sinkinfo poke"
type SinkinfoCB = Context -> Ptr Sinkinfo -> CInt -> Ptr Userdata -> IO ()
foreign import ccall "wrapper" mkSinkinfoCB :: SinkinfoCB -> IO (FunPtr SinkinfoCB)
foreign import ccall "pa_context_get_sink_info_list" pa_context_get_sink_info_list :: Context -> FunPtr SinkinfoCB -> Ptr Userdata -> IO (Ptr UOperation)
foreign import ccall "pa_context_get_sink_info_by_name" pa_context_get_sink_info_by_name :: Context -> CString -> FunPtr SinkinfoCB -> Ptr Userdata -> IO (Ptr UOperation)
foreign import ccall "pa_context_get_sink_info_by_index" pa_context_get_sink_info_by_index :: Context -> CUInt -> FunPtr SinkinfoCB -> Ptr Userdata -> IO (Ptr UOperation)
mkCallback :: (Sinkinfo -> IO ()) -> IO () -> IO (FunPtr SinkinfoCB)
mkCallback fun endf = mkSinkinfoCB $
\_ ptr end fP -> if end == 0
then fun =<< peek ptr
else do
endf
freeHaskellFunPtr (castPtrToFunPtr fP)
getContextSinks
:: Context
-> (Sinkinfo -> IO ())
-> IO ()
-> IO Operation
getContextSinks cxt fun endf = do
funP <- mkCallback fun endf
ptrToOperation =<< pa_context_get_sink_info_list cxt funP (castFunPtrToPtr funP)
getContextSinksM :: Pulse [Sinkinfo]
getContextSinksM = pulseListM (\c cb e -> void $ getContextSinks c cb e)
getContextSinkByName
:: Context
-> String
-> (Sinkinfo -> IO ())
-> IO Operation
getContextSinkByName cxt name fun = do
funP <- mkCallback fun (return ())
ptrToOperation =<< withCString name (\ptr -> pa_context_get_sink_info_by_name cxt ptr funP (castFunPtrToPtr funP))
getContextSinkByNameM :: String -> Pulse Sinkinfo
getContextSinkByNameM name =
Pulse (\cxt cb -> void $ getContextSinkByName cxt name cb)
getContextSinkByIndex
:: Context
-> Word32
-> (Sinkinfo -> IO ())
-> IO Operation
getContextSinkByIndex cxt idx fun = do
funP <- mkCallback fun (return ())
ptrToOperation =<< pa_context_get_sink_info_by_index cxt (fromIntegral idx) funP (castFunPtrToPtr funP)
getContextSinkByIndexM :: Word32 -> Pulse Sinkinfo
getContextSinkByIndexM index =
Pulse (\cxt cb -> void $ getContextSinkByIndex cxt index cb)