alsa-seq-0.6.0.9: Binding to the ALSA Library API (MIDI sequencer).
Copyright(c) Henning Thielemann 2011
(c) Iavor S. Diatchki 2007
LicenseBSD3
MaintainerHenning Thielemann
Stabilityprovisional
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.ALSA.Sequencer.Event

Description

This module contains functions for working with events. Reference: http://www.alsa-project.org/alsa-doc/alsa-lib/group___seq_event.html

Synopsis

Output

If you send an event but you do not hear something, then check the following conditions:

  • Check whether your event was actually delivered. E.g. use the event monitor aseqdump in order to see sent messages.
  • If the message was not delivered, maybe you quit the program too early and thus destroyed pending messages. Use syncOutputQueue at the end of the program in order to wait for all messages to be sent.
  • Make sure the sequencer supports output and the target port supports input.
  • Make sure to setup a connection to the receiver.
  • Make sure to have called drainOutput after output.
  • If you use a timestamp in an event, make sure you also declare a queue (and create one before).
  • Make sure you started the queue you used for sending.
  • Be aware of that QueueStart clears the queue before running the queue. That is, events sent before QueueStart are deleted. If you want to keep these events, then use QueueContinue instead.

output Source #

Arguments

:: AllowOutput mode 
=> T mode 
-> T 
-> IO Word

the number of remaining events (or bytes?)

Output an event and drain the buffer, if it became full. Throws exceptions. See also: outputDirect, outputBuffer, outputPending, drainOutput, dropOutput, extractOutput, removeOutput

outputBuffer Source #

Arguments

:: AllowOutput mode 
=> T mode 
-> T 
-> IO Word

the byte size of remaining events

Output an event without draining the buffer. Throws -EAGAIN if the buffer becomes full. See also output.

outputDirect Source #

Arguments

:: AllowOutput mode 
=> T mode 
-> T 
-> IO Word

number of bytes sent to the sequencer

Output an event directly to the sequencer, NOT through the output buffer. If an error occurs, then we throw an exception. See also output.

outputPending Source #

Arguments

:: AllowOutput mode 
=> T mode 
-> IO Word

size of pending events (in bytes)

Return the size (in bytes) of pending events on output buffer. See also output.

extractOutput Source #

Arguments

:: AllowOutput mode 
=> T mode 
-> IO T

the first event in the buffer (if one was present)

Extract the first event in output buffer. Throws (Errno 2) exception if output buffer is empty. See also output.

removeOutput :: AllowOutput mode => T mode -> IO () Source #

Remove the first event in output buffer. Throws an exception on error. See also output.

drainOutput Source #

Arguments

:: AllowOutput mode 
=> T mode 
-> IO Word

byte size of events remaining in the buffer.

Drain output buffer to sequencer. This function drains all pending events on the output buffer. The function returns immediately after the events are sent to the queues regardless whether the events are processed or not. To get synchronization with the all event processes, use syncOutputQueue after calling this function. Throws an exception on error. See also: output, syncOutputQueue.

dropOutput :: AllowOutput mode => T mode -> IO () Source #

Remove events from both the user-space output buffer, and the kernel-space sequencer queue. See also: drainOutput, dropOutputBuffer, removeOutput.

dropOutputBuffer :: AllowOutput mode => T mode -> IO () Source #

Remove events from the user-space output buffer. See also: dropOutput.

syncOutputQueue :: T mode -> IO () Source #

Wait until all events of the client are processed.

Input

input :: AllowInput mode => T mode -> IO T Source #

Get an event from the input buffer. If the input buffer is empty, then it is filled with data from the sequencer queue. If there is no data in the sequencer queue, then the process is either put to sleep (if the sequencer is operating in blocking mode), or we throw EAGAIN (if the sequence is operating in non-blocking mode).

We may also throw ENOSPC, which means that the sequencer queue over-run and some events were lost (this clears the input buffer).

inputPending Source #

Arguments

:: AllowInput mode 
=> T mode 
-> Bool

refill if empty?

-> IO Word

number of events in buffer

Returns the number of events in the input buffer. If the input buffer is empty and the boolean argument is true, then try to fill the input buffer with data from the sequencer queue. See also: input.

dropInput :: AllowInput mode => T mode -> IO () Source #

Remove events from both the user-space input buffer, and the kernel-space sequencer queue. See also: dropInputBuffer, removeOutput.

dropInputBuffer :: AllowInput mode => T mode -> IO () Source #

Remove events from the user-space input buffer. See also: dropInput.

Data types

data T Source #

Constructors

Cons 

Fields

Instances

Instances details
Storable T Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: T -> Int #

alignment :: T -> Int #

peekElemOff :: Ptr T -> Int -> IO T #

pokeElemOff :: Ptr T -> Int -> T -> IO () #

peekByteOff :: Ptr b -> Int -> IO T #

pokeByteOff :: Ptr b -> Int -> T -> IO () #

peek :: Ptr T -> IO T #

poke :: Ptr T -> T -> IO () #

Show T Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

simple :: T -> Data -> T Source #

Construct an ALSA sequencer event from very few information. Most fields are initialized with sensible defaults. You may use this as a start and alter its fields for your special needs.

(Event.simple myAddr (Event.simpleNote (Event.Channel 0) (Event.Pitch 60) Event.normalVelocity)) {Event.dest = destAddr}

class Type e Source #

Minimal complete definition

expEv

Instances

Instances details
Type AddrEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: AddrEv -> EType

Type ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: ConnEv -> EType

Type CtrlEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: CtrlEv -> EType

Type CustomEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: CustomEv -> EType

Type EmptyEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: EmptyEv -> EType

Type ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: ExtEv -> EType

Type NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: NoteEv -> EType

Type QueueEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: QueueEv -> EType

data NoteEv Source #

Constructors

ANote 
NoteOn 
NoteOff 
KeyPress 

Instances

Instances details
Type NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: NoteEv -> EType

Bounded NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Enum NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: NoteEv -> NoteEv -> Bool #

(/=) :: NoteEv -> NoteEv -> Bool #

Ord NoteEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

data Note Source #

Instances

Instances details
Storable Note Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: Note -> Int #

alignment :: Note -> Int #

peekElemOff :: Ptr Note -> Int -> IO Note #

pokeElemOff :: Ptr Note -> Int -> Note -> IO () #

peekByteOff :: Ptr b -> Int -> IO Note #

pokeByteOff :: Ptr b -> Int -> Note -> IO () #

peek :: Ptr Note -> IO Note #

poke :: Ptr Note -> Note -> IO () #

Show Note Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

simpleNote :: Channel -> Pitch -> Velocity -> Note Source #

Make a note whose unspecified fields contain 0.

data Ctrl Source #

Constructors

Ctrl 

Instances

Instances details
Storable Ctrl Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: Ctrl -> Int #

alignment :: Ctrl -> Int #

peekElemOff :: Ptr Ctrl -> Int -> IO Ctrl #

pokeElemOff :: Ptr Ctrl -> Int -> Ctrl -> IO () #

peekByteOff :: Ptr b -> Int -> IO Ctrl #

pokeByteOff :: Ptr b -> Int -> Ctrl -> IO () #

peek :: Ptr Ctrl -> IO Ctrl #

poke :: Ptr Ctrl -> Ctrl -> IO () #

Show Ctrl Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> Ctrl -> ShowS #

show :: Ctrl -> String #

showList :: [Ctrl] -> ShowS #

data CustomEv Source #

data Custom Source #

Constructors

Custom 

Instances

Instances details
Storable Custom Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Custom Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

data ExtEv Source #

Instances

Instances details
Type ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: ExtEv -> EType

Bounded ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Enum ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> ExtEv -> ShowS #

show :: ExtEv -> String #

showList :: [ExtEv] -> ShowS #

Eq ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: ExtEv -> ExtEv -> Bool #

(/=) :: ExtEv -> ExtEv -> Bool #

Ord ExtEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

compare :: ExtEv -> ExtEv -> Ordering #

(<) :: ExtEv -> ExtEv -> Bool #

(<=) :: ExtEv -> ExtEv -> Bool #

(>) :: ExtEv -> ExtEv -> Bool #

(>=) :: ExtEv -> ExtEv -> Bool #

max :: ExtEv -> ExtEv -> ExtEv #

min :: ExtEv -> ExtEv -> ExtEv #

data QueueEv Source #

Instances

Instances details
Type QueueEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: QueueEv -> EType

Show QueueEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq QueueEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: QueueEv -> QueueEv -> Bool #

(/=) :: QueueEv -> QueueEv -> Bool #

data ConnEv Source #

Instances

Instances details
Type ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

expEv :: ConnEv -> EType

Bounded ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Enum ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: ConnEv -> ConnEv -> Bool #

(/=) :: ConnEv -> ConnEv -> Bool #

Ord ConnEv Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

newtype Tag Source #

Constructors

Tag 

Fields

Instances

Instances details
Storable Tag Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: Tag -> Int #

alignment :: Tag -> Int #

peekElemOff :: Ptr Tag -> Int -> IO Tag #

pokeElemOff :: Ptr Tag -> Int -> Tag -> IO () #

peekByteOff :: Ptr b -> Int -> IO Tag #

pokeByteOff :: Ptr b -> Int -> Tag -> IO () #

peek :: Ptr Tag -> IO Tag #

poke :: Ptr Tag -> Tag -> IO () #

Ix Tag Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

range :: (Tag, Tag) -> [Tag] #

index :: (Tag, Tag) -> Tag -> Int #

unsafeIndex :: (Tag, Tag) -> Tag -> Int #

inRange :: (Tag, Tag) -> Tag -> Bool #

rangeSize :: (Tag, Tag) -> Int #

unsafeRangeSize :: (Tag, Tag) -> Int #

Show Tag Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Eq Tag Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: Tag -> Tag -> Bool #

(/=) :: Tag -> Tag -> Bool #

Ord Tag Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

compare :: Tag -> Tag -> Ordering #

(<) :: Tag -> Tag -> Bool #

(<=) :: Tag -> Tag -> Bool #

(>) :: Tag -> Tag -> Bool #

(>=) :: Tag -> Tag -> Bool #

max :: Tag -> Tag -> Tag #

min :: Tag -> Tag -> Tag #

newtype Tempo Source #

Constructors

Tempo 

Fields

Instances

Instances details
Storable Tempo Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: Tempo -> Int #

alignment :: Tempo -> Int #

peekElemOff :: Ptr Tempo -> Int -> IO Tempo #

pokeElemOff :: Ptr Tempo -> Int -> Tempo -> IO () #

peekByteOff :: Ptr b -> Int -> IO Tempo #

pokeByteOff :: Ptr b -> Int -> Tempo -> IO () #

peek :: Ptr Tempo -> IO Tempo #

poke :: Ptr Tempo -> Tempo -> IO () #

Ix Tempo Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Tempo Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> Tempo -> ShowS #

show :: Tempo -> String #

showList :: [Tempo] -> ShowS #

Eq Tempo Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: Tempo -> Tempo -> Bool #

(/=) :: Tempo -> Tempo -> Bool #

Ord Tempo Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

compare :: Tempo -> Tempo -> Ordering #

(<) :: Tempo -> Tempo -> Bool #

(<=) :: Tempo -> Tempo -> Bool #

(>) :: Tempo -> Tempo -> Bool #

(>=) :: Tempo -> Tempo -> Bool #

max :: Tempo -> Tempo -> Tempo #

min :: Tempo -> Tempo -> Tempo #

newtype Parameter Source #

Constructors

Parameter 

Fields

Instances

Instances details
Storable Parameter Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ix Parameter Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Parameter Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq Parameter Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ord Parameter Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

newtype Value Source #

Constructors

Value 

Fields

Instances

Instances details
Storable Value Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: Value -> Int #

alignment :: Value -> Int #

peekElemOff :: Ptr Value -> Int -> IO Value #

pokeElemOff :: Ptr Value -> Int -> Value -> IO () #

peekByteOff :: Ptr b -> Int -> IO Value #

pokeByteOff :: Ptr b -> Int -> Value -> IO () #

peek :: Ptr Value -> IO Value #

poke :: Ptr Value -> Value -> IO () #

Ix Value Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Value Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Ord Value Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

newtype Channel Source #

Constructors

Channel 

Fields

Instances

Instances details
Storable Channel Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ix Channel Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Channel Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq Channel Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: Channel -> Channel -> Bool #

(/=) :: Channel -> Channel -> Bool #

Ord Channel Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

newtype Pitch Source #

Constructors

Pitch 

Fields

Instances

Instances details
Storable Pitch Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

sizeOf :: Pitch -> Int #

alignment :: Pitch -> Int #

peekElemOff :: Ptr Pitch -> Int -> IO Pitch #

pokeElemOff :: Ptr Pitch -> Int -> Pitch -> IO () #

peekByteOff :: Ptr b -> Int -> IO Pitch #

pokeByteOff :: Ptr b -> Int -> Pitch -> IO () #

peek :: Ptr Pitch -> IO Pitch #

poke :: Ptr Pitch -> Pitch -> IO () #

Ix Pitch Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Pitch Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

Eq Pitch Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

(==) :: Pitch -> Pitch -> Bool #

(/=) :: Pitch -> Pitch -> Bool #

Ord Pitch Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Methods

compare :: Pitch -> Pitch -> Ordering #

(<) :: Pitch -> Pitch -> Bool #

(<=) :: Pitch -> Pitch -> Bool #

(>) :: Pitch -> Pitch -> Bool #

(>=) :: Pitch -> Pitch -> Bool #

max :: Pitch -> Pitch -> Pitch #

min :: Pitch -> Pitch -> Pitch #

newtype Velocity Source #

Constructors

Velocity 

Fields

Instances

Instances details
Storable Velocity Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ix Velocity Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Velocity Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq Velocity Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ord Velocity Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

newtype Duration Source #

Constructors

Duration 

Fields

Instances

Instances details
Storable Duration Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ix Duration Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Show Duration Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Eq Duration Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event

Ord Duration Source # 
Instance details

Defined in Sound.ALSA.Sequencer.Marshal.Event