module Sound.ALSA.Sequencer.Event (
output,
outputBuffer,
outputDirect,
outputPending,
extractOutput,
removeOutput,
drainOutput,
dropOutput,
dropOutputBuffer,
syncOutputQueue,
input,
inputPending,
dropInput,
dropInputBuffer,
Event.T(..), simple, forSourcePort, forConnection,
Event.Data(..),
Event.Type,
NoteEv(..), Note(..), simpleNote,
CtrlEv(..), Ctrl(..),
CustomEv(..), Custom(..), customZero,
ExtEv(..),
QueueEv(..),
AddrEv(..),
ConnEv(..),
EmptyEv(..),
Tag(..),
Tempo(..),
Parameter(..),
Value(..),
Channel(..),
Pitch(..),
Velocity(..), normalVelocity, offVelocity,
Duration(..),
) where
import Sound.ALSA.Sequencer.Marshal.Event as Event
import qualified Sound.ALSA.Sequencer.Address as Addr
import qualified Sound.ALSA.Sequencer.Port as Port
import qualified Sound.ALSA.Sequencer.Client as Client
import qualified Sound.ALSA.Sequencer.Connect as Connect
import qualified Sound.ALSA.Sequencer.Queue as Queue
import qualified Sound.ALSA.Sequencer.Marshal.Sequencer as Seq
import qualified Sound.ALSA.Sequencer.Marshal.Time as Time
import qualified Sound.ALSA.Exception as Exc
import qualified Foreign.C.Types as C
import Foreign.Ptr (Ptr, nullPtr, )
import Foreign.Marshal.Alloc (alloca, )
import Foreign.Storable (peek, )
import Data.Word (Word, )
syncOutputQueue :: Seq.T mode -> IO ()
syncOutputQueue (Seq.Cons h) =
Exc.checkResult_ "syncOutputQueue" =<< snd_seq_sync_output_queue h
foreign import ccall safe "alsa/asoundlib.h snd_seq_sync_output_queue"
snd_seq_sync_output_queue :: Ptr Seq.Core -> IO C.CInt
input :: Seq.AllowInput mode => Seq.T mode -> IO Event.T
input (Seq.Cons h) = alloca $ \p ->
do Exc.checkResult_ "input" =<< snd_seq_event_input h p
peek =<< peek p
foreign import ccall safe "alsa/asoundlib.h snd_seq_event_input"
snd_seq_event_input :: Ptr Seq.Core -> Ptr (Ptr Event.T) -> IO C.CInt
checkResult :: String -> C.CInt -> IO Word
checkResult loc n =
fmap fromIntegral $ Exc.checkResult loc n
inputPending
:: Seq.AllowInput mode
=> Seq.T mode
-> Bool
-> IO Word
inputPending (Seq.Cons h) fill =
checkResult "inputPending" =<< snd_seq_event_input_pending h (if fill then 1 else 0)
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_event_input_pending"
snd_seq_event_input_pending :: Ptr Seq.Core -> C.CInt -> IO C.CInt
output :: Seq.AllowOutput mode
=> Seq.T mode
-> Event.T
-> IO Word
output (Seq.Cons h) e =
Event.with e $ \p -> checkResult "output" =<< snd_seq_event_output h p
foreign import ccall safe "alsa/asoundlib.h snd_seq_event_output"
snd_seq_event_output :: Ptr Seq.Core -> Ptr Event.T -> IO C.CInt
outputBuffer :: Seq.AllowOutput mode
=> Seq.T mode
-> Event.T
-> IO Word
outputBuffer (Seq.Cons h) e =
Event.with e $ \p -> checkResult "outputBuffer" =<< snd_seq_event_output_buffer h p
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_event_output_buffer"
snd_seq_event_output_buffer :: Ptr Seq.Core -> Ptr Event.T -> IO C.CInt
outputDirect
:: Seq.AllowOutput mode
=> Seq.T mode
-> Event.T
-> IO Word
outputDirect (Seq.Cons h) e =
Event.with e $ \p -> checkResult "outputDirect" =<< snd_seq_event_output_direct h p
foreign import ccall safe "alsa/asoundlib.h snd_seq_event_output_direct"
snd_seq_event_output_direct :: Ptr Seq.Core -> Ptr Event.T -> IO C.CInt
outputPending
:: Seq.AllowOutput mode
=> Seq.T mode
-> IO Word
outputPending (Seq.Cons h) =
fromIntegral `fmap` snd_seq_event_output_pending h
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_event_output_pending"
snd_seq_event_output_pending :: Ptr Seq.Core -> IO C.CInt
extractOutput
:: Seq.AllowOutput mode
=> Seq.T mode
-> IO Event.T
extractOutput (Seq.Cons h) =
alloca $ \p -> do Exc.checkResult_ "extractOutput" =<< snd_seq_extract_output h p
peek =<< peek p
removeOutput :: Seq.AllowOutput mode
=> Seq.T mode -> IO ()
removeOutput (Seq.Cons h) = Exc.checkResult_ "removeOutput" =<< snd_seq_extract_output h nullPtr
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_extract_output"
snd_seq_extract_output :: Ptr Seq.Core -> Ptr (Ptr Event.T) -> IO C.CInt
drainOutput
:: Seq.AllowOutput mode
=> Seq.T mode
-> IO Word
drainOutput (Seq.Cons h) = checkResult "drainOutput" =<< snd_seq_drain_output h
foreign import ccall safe "alsa/asoundlib.h snd_seq_drain_output"
snd_seq_drain_output :: Ptr Seq.Core -> IO C.CInt
dropOutput
:: Seq.AllowOutput mode
=> Seq.T mode -> IO ()
dropOutput (Seq.Cons h) = Exc.checkResult_ "dropOutput" =<< snd_seq_drop_output h
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_drop_output"
snd_seq_drop_output :: Ptr Seq.Core -> IO C.CInt
dropOutputBuffer
:: Seq.AllowOutput mode
=> Seq.T mode -> IO ()
dropOutputBuffer (Seq.Cons h) = Exc.checkResult_ "dropOutputBuffer" =<< snd_seq_drop_output_buffer h
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_drop_output_buffer"
snd_seq_drop_output_buffer :: Ptr Seq.Core -> IO C.CInt
dropInput
:: Seq.AllowInput mode
=> Seq.T mode -> IO ()
dropInput (Seq.Cons h) = Exc.checkResult_ "dropInput" =<< snd_seq_drop_input h
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_drop_input"
snd_seq_drop_input :: Ptr Seq.Core -> IO C.CInt
dropInputBuffer
:: Seq.AllowInput mode
=> Seq.T mode -> IO ()
dropInputBuffer (Seq.Cons h) = Exc.checkResult_ "dropInputBuffer" =<< snd_seq_drop_input_buffer h
foreign import ccall unsafe "alsa/asoundlib.h snd_seq_drop_input_buffer"
snd_seq_drop_input_buffer :: Ptr Seq.Core -> IO C.CInt
simpleNote :: Channel -> Pitch -> Velocity -> Event.Note
simpleNote c n v =
Event.Note {
Event.noteChannel = c,
Event.noteNote = n,
Event.noteVelocity = v,
Event.noteOffVelocity = offVelocity,
Event.noteDuration = Duration 0
}
normalVelocity, offVelocity :: Velocity
normalVelocity = Velocity 64
offVelocity = Velocity 0
simple :: Addr.T -> Event.Data -> Event.T
simple src bdy = Cons
{ Event.highPriority = False
, Event.tag = Tag 0
, Event.queue = Queue.direct
, Event.time = Time.consAbs $ Time.Tick 0
, Event.source = src
, Event.dest = Addr.subscribers
, Event.body = bdy
}
forSourcePort :: Port.T -> Event.Data -> Event.T
forSourcePort port =
simple (Addr.Cons Client.unknown port)
forConnection :: Connect.T -> Event.Data -> Event.T
forConnection (Connect.Cons src dst) bdy =
(simple src bdy) { Event.dest = dst }
customZero :: Event.Custom
customZero = Event.Custom 0 0 0