midi-simple-0.1.0.0: A simple and fast library for working with MIDI messages

Safe HaskellSafe
LanguageHaskell2010

Sound.MIDI.Types

Contents

Synopsis

MIDI messages

data MidiMessage Source #

A data type representing midi messages. Messages can be categorized into 5 subcategories

  1. Channel Voice Messages. Start, stop, or alter sounds being played.
  2. Channel Mode Messages. Control messages affecting the entire channel.
  3. System Real-Time Messages. Used by sequencers to regulate and synchronize timing.
  4. System Common Messages. Used for song selection, position pointers, etc.
  5. System Exclusive Messages. Used for device-specific extensions to the MIDI protocol.

Instances

Eq MidiMessage Source # 
Ord MidiMessage Source # 
Read MidiMessage Source # 
Show MidiMessage Source # 
Generic MidiMessage Source # 

Associated Types

type Rep MidiMessage :: * -> * #

type Rep MidiMessage Source # 

Basic MIDI types

data ChannelVoice Source #

Type holding channel voice messages. Channel Voice messages transmit real-time performance data over a single channel. Examples include "note-on" messages which contain a MIDI note number that specifies the note's pitch, a velocity value that indicates how forcefully the note was played, and the channel number; "note-off" messages that end a note; program change messages that change a device's patch; and control changes that allow adjustment of an instrument's parameters.

Instances

Eq ChannelVoice Source # 
Ord ChannelVoice Source # 
Read ChannelVoice Source # 
Show ChannelVoice Source # 
Generic ChannelVoice Source # 

Associated Types

type Rep ChannelVoice :: * -> * #

type Rep ChannelVoice Source # 
type Rep ChannelVoice = D1 (MetaData "ChannelVoice" "Sound.MIDI.Types" "midi-simple-0.1.0.0-5Zfda56lQOL3iUqD7uGYdJ" False) ((:+:) ((:+:) (C1 (MetaCons "NoteOff" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Pitch)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Velocity))))) ((:+:) (C1 (MetaCons "NoteOn" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Pitch)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Velocity))))) (C1 (MetaCons "Aftertouch" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Pitch)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Touch))))))) ((:+:) ((:+:) (C1 (MetaCons "ControlChange" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Controller)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word8))))) (C1 (MetaCons "PatchChange" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Patch))))) ((:+:) (C1 (MetaCons "ChannelPressure" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Touch)))) (C1 (MetaCons "PitchBend" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Channel)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word16)))))))

data ChannelMode Source #

A type for channel mode messages. Mode messages determine how an instrument will receive all subsequent voice messages. This includes whether the receiver will play notes monophonically or polyphonically and whether it will respond only to data sent on one specific voice channel or all of them.

Instances

Eq ChannelMode Source # 
Ord ChannelMode Source # 
Read ChannelMode Source # 
Show ChannelMode Source # 
Generic ChannelMode Source # 

Associated Types

type Rep ChannelMode :: * -> * #

type Rep ChannelMode Source # 

data SystemCommon Source #

A type for system common messages. System common messages are intended for all receivers in the system.

Instances

Eq SystemCommon Source # 
Ord SystemCommon Source # 
Read SystemCommon Source # 
Show SystemCommon Source # 
Generic SystemCommon Source # 

Associated Types

type Rep SystemCommon :: * -> * #

type Rep SystemCommon Source # 

data SystemRealTime Source #

System real time messages. The MIDI System Real Time messages are used to synchronize all of the MIDI clock-based equipment within a system, such as sequencers and drum machines. Most of the System Real Time messages are normally ignored by keyboard instruments and synthesizers. To help ensure accurate timing, System Real Time messages are given priority over other messages, and these single-byte messages may occur anywhere in the data stream (a Real Time message may appear between the status byte and data byte of some other MIDI message).

Instances

Eq SystemRealTime Source # 
Ord SystemRealTime Source # 
Read SystemRealTime Source # 
Show SystemRealTime Source # 
Generic SystemRealTime Source # 

Associated Types

type Rep SystemRealTime :: * -> * #

type Rep SystemRealTime Source # 
type Rep SystemRealTime = D1 (MetaData "SystemRealTime" "Sound.MIDI.Types" "midi-simple-0.1.0.0-5Zfda56lQOL3iUqD7uGYdJ" False) ((:+:) ((:+:) (C1 (MetaCons "TimingClock" PrefixI False) U1) ((:+:) (C1 (MetaCons "Start" PrefixI False) U1) (C1 (MetaCons "Continue" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Stop" PrefixI False) U1) ((:+:) (C1 (MetaCons "ActiveSensing" PrefixI False) U1) (C1 (MetaCons "SystemReset" PrefixI False) U1))))

data SystemExclusive Source #

System exclusive messages. System Exclusive messages may be used to send data such as patch parameters or sample data between MIDI devices. Manufacturers of MIDI equipment may define their own formats for System Exclusive data. Manufacturers are granted unique identification (ID) numbers by the MMA or the JMSC, and the manufacturer ID number is included as part of the System Exclusive message. See VendorId.

The representation used here is deliberately generic. Special sets of system exclusive messages can be implemented on top of this type.

Instances

Eq SystemExclusive Source # 
Ord SystemExclusive Source # 
Read SystemExclusive Source # 
Show SystemExclusive Source # 
Generic SystemExclusive Source # 
type Rep SystemExclusive Source # 
type Rep SystemExclusive = D1 (MetaData "SystemExclusive" "Sound.MIDI.Types" "midi-simple-0.1.0.0-5Zfda56lQOL3iUqD7uGYdJ" False) (C1 (MetaCons "Exclusive" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 VendorId)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))))

data VendorId Source #

Data type encapsulating vendor ID numbers as used in SystemExclusive. They have one of two possible formats:

  1. A one byte ID (represented by VendorIdShort)
  2. A three byte ID, which must begin with 0x00. (VendorIdLong)

Numeric MIDI data

Only use the direct constructors when you can assure that the values fit into 7 bits! In general you should prefer the smart constructors. For values outside of the 7 bit range, the numbers should generally wrap around, but no guarantees are made!

newtype Pitch Source #

Constructors

Pitch 

Fields

middleC :: Pitch Source #

The middle C on a piano as defined by the MIDI specification. This can serve as a reference value for working with pitches.

newtype Patch Source #

Constructors

Patch 

Fields

newtype Touch Source #

Constructors

Touch 

Fields

toClocks :: PositionPointer -> Int Source #

Convert a PositionPointer, used to indicate song position, to the MIDI clock. Song Position Pointer is always multiplied by 6 times the MIDI clocks (F8H). Thus the smallest Song Position change is 6 MIDI clocks, or 1/16 note.

Helper functions