midi-0.2.2.3: Handling of MIDI messages and files
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sound.MIDI.Message.Channel

Description

Channel messages

Synopsis

Documentation

data T Source #

Constructors

Cons 

Instances

Instances details
Eq T Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

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

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

Ord T Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

compare :: T -> T -> Ordering #

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

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

(>) :: T -> T -> Bool #

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

max :: T -> T -> T #

min :: T -> T -> T #

Show T Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

showsPrec :: Int -> T -> ShowS #

show :: T -> String #

showList :: [T] -> ShowS #

Arbitrary T Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

arbitrary :: Gen T #

shrink :: T -> [T] #

C T Source # 
Instance details

Defined in Sound.MIDI.Message.Class.Query

C T Source # 
Instance details

Defined in Sound.MIDI.Message.Class.Construct

C T Source # 
Instance details

Defined in Sound.MIDI.Message.Class.Check

data Body Source #

Constructors

Voice T 
Mode T 

Instances

Instances details
Eq Body Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

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

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

Ord Body Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

compare :: Body -> Body -> Ordering #

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

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

(>) :: Body -> Body -> Bool #

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

max :: Body -> Body -> Body #

min :: Body -> Body -> Body #

Show Body Source # 
Instance details

Defined in Sound.MIDI.Message.Channel

Methods

showsPrec :: Int -> Body -> ShowS #

show :: Body -> String #

showList :: [Body] -> ShowS #

get :: C parser => Int -> Channel -> Int -> Fragile parser T Source #

Parse a MIDI Channel message. Note that since getting the first byte is a little complex (there are issues with running status), the code, channel and first data byte must be determined by the caller.

getWithStatus :: C parser => Int -> Fragile (T parser) T Source #

Parse an event. Note that in the case of a regular MIDI Event, the tag is the status, and we read the first byte of data before we call get. In the case of a MIDIEvent with running status, we find out the status from the parser (it's been nice enough to keep track of it for us), and the tag that we've already gotten is the first byte of data.

put :: C writer => T -> writer Source #

putWithStatus :: (Compression compress, C writer) => T -> T compress writer Source #

data Channel Source #

This definition should be in Message.Channel, but this results in a cyclic import.

Instances

Instances details
Bounded Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

Enum Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

Eq Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

Methods

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

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

Ord Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

Show Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

Ix Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

Arbitrary Channel Source # 
Instance details

Defined in Sound.MIDI.Parser.Status

data Pitch Source #

Instances

Instances details
Bounded Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Enum Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Eq Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

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

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

Ord Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

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 #

Show Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

showsPrec :: Int -> Pitch -> ShowS #

show :: Pitch -> String #

showList :: [Pitch] -> ShowS #

Ix Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Arbitrary Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

arbitrary :: Gen Pitch #

shrink :: Pitch -> [Pitch] #

Random Pitch Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

randomR :: RandomGen g => (Pitch, Pitch) -> g -> (Pitch, g) #

random :: RandomGen g => g -> (Pitch, g) #

randomRs :: RandomGen g => (Pitch, Pitch) -> g -> [Pitch] #

randoms :: RandomGen g => g -> [Pitch] #

data Velocity Source #

Instances

Instances details
Bounded Velocity Source #

ToDo: We have defined minBound = Velocity 0, but strictly spoken the minimum Velocity is 1, since Velocity zero means NoteOff. One can at least think of NoteOff with (Velocity 0), but I have never seen that.

Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Eq Velocity Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Ord Velocity Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Show Velocity Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Arbitrary Velocity Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Random Velocity Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

randomR :: RandomGen g => (Velocity, Velocity) -> g -> (Velocity, g) #

random :: RandomGen g => g -> (Velocity, g) #

randomRs :: RandomGen g => (Velocity, Velocity) -> g -> [Velocity] #

randoms :: RandomGen g => g -> [Velocity] #

data Program Source #

Instances

Instances details
Bounded Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Enum Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Eq Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

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

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

Ord Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Show Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Ix Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Arbitrary Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Random Program Source # 
Instance details

Defined in Sound.MIDI.Message.Channel.Voice

Methods

randomR :: RandomGen g => (Program, Program) -> g -> (Program, g) #

random :: RandomGen g => g -> (Program, g) #

randomRs :: RandomGen g => (Program, Program) -> g -> [Program] #

randoms :: RandomGen g => g -> [Program] #

data Controller Source #

We do not define Controller as enumeration with many constructors, because some controllers have multiple names and some are undefined. It is also more efficient this way. Thus you cannot use case for processing controller types, but you can use lookup instead.

maybe (putStrLn "unsupported controller") putStrLn $
lookup ctrl $
   (portamento, "portamento") :
   (modulation, "modulation") :
   []

Instances

Instances details
Bounded Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Enum Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Eq Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Ord Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Show Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Ix Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Arbitrary Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Random Controller Source # 
Instance details

Defined in Sound.MIDI.ControllerPrivate

Methods

randomR :: RandomGen g => (Controller, Controller) -> g -> (Controller, g) #

random :: RandomGen g => g -> (Controller, g) #

randomRs :: RandomGen g => (Controller, Controller) -> g -> [Controller] #

randoms :: RandomGen g => g -> [Controller] #

decodeStatus :: Int -> (Int, Channel) Source #

for internal use