tidal-midi-0.9.4: MIDI support for tidal

Safe HaskellNone
LanguageHaskell98

Sound.Tidal.MIDI.Output

Contents

Description

A bridge between evaluated Tidal patterns and MIDI events.

This module contains functions necessary to mediate between Events generated from a Tidal Pattern and plain MIDI events sent through PMStream.

Synopsis

Types

data Output Source #

An abstract definition of a physical MIDI Output.

Manages virtual streams to multiple channels of a single connection to a MIDI device.

Constructors

Output 

Fields

type OutputState = (TickedConnectionCount, ConnectionCount, [ParamMap], OutputOnline) Source #

Keep track of virtual streams

  • Reflects the number of virtual streams that have already stored their events for this tick. Every time TickedConnectionCount cycles, MIDI events will be sent out.
  • ConnectionCount is increased on every new stream created via midiSetters
  • For each channel, currently used params and their values are kept.
  • Output will only be scheduling, once online, i.e. when the first stream is initialized

type TimedNote = (CLong, MIDIVelocity, MIDIDuration) Source #

A Triplet of the deviation from the note a5, velocity and duration

Initialization

makeConnection Source #

Arguments

:: MVar MidiDeviceMap

The current list of already connected devices

-> String

The MIDI device name

-> Int

The MIDI channel

-> ControllerShape

The definition of useable Controls

-> IO (ToMessageFunc, Output)

A function to schedule MIDI events and the output that keeps track of connections

Initialize a connection to the given MIDI device by Name

flushBackend :: Output -> Shape -> Tempo -> Int -> IO () Source #

Sends out MIDI events once all virtual streams have buffered their events.

This will be called after every tick

Scheduling

sendevents Source #

Arguments

:: Output

The connection to be used

-> Shape

The shape to be queried for latency

-> Tempo

The current speed

-> Tick

The number of ticks elapsed since start, may be reset when using cps (-1)

-> [MIDIEvent]

A list of events potentially needed to be sent

-> [MIDIEvent]

A list of reset events potentially needed to be sent

-> IO ([SentEvent], [MIDIEvent])

A list of events sent late and a list of events to send later

Sends out MIDI events due for this tick.

store :: Output -> Int -> Tempo -> Tick -> Onset -> Offset -> MidiMap -> ParamMap -> IO () Source #

Buffer a single tick's MIDI events for a single channel of a single connection

mkStore :: Int -> Output -> IO ToMessageFunc Source #

Returns a function to be called on every tick, splits the given ParamMap into MIDI note information and CCs.

storeParams :: Output -> Int -> ParamMap -> IO () -> IO () Source #

Union the currently stored paramstate for certain channel with the given one

scheduleTime :: (CULong, UTCTime) -> Double -> CULong Source #

Turn logicalOnset into MIDITime

Converters

toMidiValue :: ControllerShape -> Param -> Value -> Maybe Int Source #

Convert a Param's Value into a MIDI consumable datum.

Applies range mapping and scaling functions according to ControllerShape

cutShape :: Shape -> ParamMap -> Maybe ParamMap Source #

Keep only params that are in a given shape, replace missing with defaults

stripDefaults :: Maybe ParamMap -> Maybe ParamMap Source #

Keep only params that are explicitly set (i.e. not default)

State handling

Low-level functions

useOutput :: MVar MidiDeviceMap -> String -> ControllerShape -> IO (Maybe Output) Source #

open named MIDI output or use cached (PortMIDI doesn't like opening two connections to the same device!)

displayOutputDevices :: IO String Source #

Example usage:

>>> putStrLn =<< displayOutputDevices
ID:	Name
0:	Midi Through Port-0
2:	DSI Tetra MIDI 1

outputDevice :: DeviceID -> Int -> ControllerShape -> IO (Either Output PMError) Source #

Creates an Output wrapping a PortMidi device

makeRawEvent :: MIDIMessage -> CULong -> PMEvent Source #

noteOn :: MIDIChannel -> MIDINote -> MIDIVelocity -> MIDITime -> [MIDIEvent] Source #

noteOff :: MIDIChannel -> MIDINote -> MIDITime -> [MIDIEvent] Source #

makeCtrl :: MIDIChannel -> ControlChange -> MIDIDatum -> MIDITime -> [MIDIEvent] Source #