Sound.JACK.MIDI
- data RawEvent
- rawEvent :: NFrames -> ByteString -> RawEvent
- rawEventTime :: RawEvent -> NFrames
- rawEventBuffer :: RawEvent -> ByteString
- toRawEventFunction :: (NFrames -> (NFrames, T) -> IO (NFrames, T)) -> NFrames -> RawEvent -> IO RawEvent
- type Port = Port EventBuffer
- withPort :: (Direction dir, ThrowsPortRegister e, ThrowsErrno e) => Client -> String -> (Port dir -> ExceptionalT e IO a) -> ExceptionalT e IO a
- setProcess :: ThrowsErrno e => Client -> Port Input -> (NFrames -> RawEvent -> IO RawEvent) -> Port Output -> ExceptionalT e IO ()
- readRawEvents :: ThrowsErrno e => Ptr EventBuffer -> ExceptionalT e IO [RawEvent]
- writeRawEvent :: ThrowsErrno e => Ptr EventBuffer -> RawEvent -> ExceptionalT e IO ()
- main :: (NFrames -> (NFrames, T) -> IO (NFrames, T)) -> IO ()
- mainRaw :: (NFrames -> RawEvent -> IO RawEvent) -> IO ()
Documentation
Represents a raw JACK MIDI event
Arguments
| :: NFrames | Sample index at which event is valid (relative to cycle start) |
| -> ByteString | Raw MIDI data |
| -> RawEvent |
Smart constructor for a raw MIDI event.
Arguments
| :: (NFrames -> (NFrames, T) -> IO (NFrames, T)) | transforms Sound.MIDI.File.Event |
| -> NFrames -> RawEvent -> IO RawEvent | transforms Sound.JACK.MIDI.RawEvent |
Converts high level MIDI Event transformation functions into raw MIDI Event transformation functions
Arguments
| :: (Direction dir, ThrowsPortRegister e, ThrowsErrno e) | |
| => Client | Jack client |
| -> String | name of the input port |
| -> (Port dir -> ExceptionalT e IO a) | |
| -> ExceptionalT e IO a |
Arguments
| :: ThrowsErrno e | |
| => Client | the JACK Client, whose process loop will be set |
| -> Port Input | where to get events from |
| -> (NFrames -> RawEvent -> IO RawEvent) | transforms input to output events |
| -> Port Output | where to put events |
| -> ExceptionalT e IO () | exception causing JACK to remove that client from the process() graph. |
sets the process loop of the JACK Client
Arguments
| :: ThrowsErrno e | |
| => Ptr EventBuffer | the PortBuffer to read from |
| -> ExceptionalT e IO [RawEvent] | pointers to newly allocated events, must be freed later! |
reads all available MIDI Events on the given PortBuffer
Arguments
| :: ThrowsErrno e | |
| => Ptr EventBuffer | the PortBuffer of the MIDI output to write to |
| -> RawEvent | the RawEvent to write |
| -> ExceptionalT e IO () |
writes a MIDI event to the PortBuffer of a MIDI output or throws eNOBUFS if buffer is full
Creates an input and an output, and transforms all input events into output events using the given function