hsc3-lang-0.15: Haskell SuperCollider Language

Safe HaskellNone
LanguageHaskell98

Sound.SC3.Lang.Control.Midi

Contents

Description

Trivial midi functions.

Synopsis

Bits

b_join :: Bits a => a -> a -> a Source

Join two 7-bit values into a 14-bit value.

map (uncurry b_join) [(0,0),(0,64),(127,127)] == [0,8192,16383]

b_sep :: (Num t, Bits t) => t -> (t, t) Source

Inverse of b_join.

map b_sep [0,8192,16383] == [(0,0),(0,64),(127,127)]

Types

control_message :: (Eq a, Num a) => (a, a, a) -> Control_Message a Source

Control_Change midi messages may, in some cases, have commonly defined meanings.

control_message (0,123,0) == All_Notes_Off 0

OSC

parse_b :: Integral n => Message -> [n] Source

Parse midi-osc midi message.

parse_c :: Integral n => Message -> [n] Source

Variant of parse_b that give status byte as low and high.

parse_m :: (Bits n, Integral n) => Message -> Midi_Message n Source

Variant of parse_c that constructs a Midi_Message.

SC3

type Node_Id = Int Source

SC3 node identifiers are integers.

data KY a Source

Map of allocated Node_Ids. For a single input controller, key events always arrive in sequence (ie. on->off), ie. for any key on message we can allocate an ID and associate it with the key, an off message can retrieve the ID given the key.

Constructors

KY (Map a Node_Id) Node_Id 

ky_init :: Node_Id -> KY a Source

Initialise KY with starting Node_Id.

ky_alloc :: Ord a => KY a -> a -> (KY a, Node_Id) Source

KY Node_Id allocator.

ky_free :: Ord a => KY a -> a -> (KY a, Node_Id) Source

KY Node_Id removal.

ky_get :: Ord a => KY a -> a -> Node_Id Source

Lookup Node_Id.

IO (midi-osc)

type Midi_Init_f st = UDP -> IO st Source

type Midi_Recv_f st = UDP -> st -> Midi_Message Int -> IO st Source

Midi_Recv_f is passed the SC3 connection, the user state, a Midi_Message and, for Note_On and Note_Off messages, a Node_Id.

midi_act :: Midi_Recv_f st -> UDP -> st -> Message -> IO st Source

Parse incoming midi messages and run Midi_Receiver.

run_midi :: Midi_Init_f st -> Midi_Recv_f st -> IO () Source

Connect to midi-osc and sc3, run initialiser, and then receiver for each incoming message.

Monad

iterateM_ :: Monad m => st -> (st -> m st) -> m () Source