midi-0.1.3.1: Handling of MIDI messages and filesSource codeContentsIndex
Sound.MIDI.Message.Channel.Voice
Description
Channel voice messages
Synopsis
data T
= NoteOff Pitch Velocity
| NoteOn Pitch Velocity
| PolyAftertouch Pitch Pressure
| ProgramChange Program
| Control Controller ControllerValue
| PitchBend PitchBendRange
| MonoAftertouch Pressure
get :: C parser => Int -> Int -> Fallible parser T
putWithStatus :: C writer => (Int -> T writer ()) -> T -> T writer ()
type ControllerValue = Int
type PitchBendRange = Int
type Pressure = Int
isNote :: T -> Bool
isNoteOn :: T -> Bool
isNoteOff :: T -> Bool
zeroKey :: Pitch
explicitNoteOff :: T -> T
implicitNoteOff :: T -> T
toFloatController :: (Integral a, Fractional b) => a -> b
bankSelect :: Controller
modulation :: Controller
breathControl :: Controller
footControl :: Controller
portamentoTime :: Controller
dataEntry :: Controller
mainVolume :: Controller
balance :: Controller
panorama :: Controller
expression :: Controller
generalPurpose1 :: Controller
generalPurpose2 :: Controller
generalPurpose3 :: Controller
generalPurpose4 :: Controller
vectorX :: Controller
vectorY :: Controller
bankSelectMSB :: Controller
modulationMSB :: Controller
breathControlMSB :: Controller
footControlMSB :: Controller
portamentoTimeMSB :: Controller
dataEntryMSB :: Controller
mainVolumeMSB :: Controller
balanceMSB :: Controller
panoramaMSB :: Controller
expressionMSB :: Controller
generalPurpose1MSB :: Controller
generalPurpose2MSB :: Controller
generalPurpose3MSB :: Controller
generalPurpose4MSB :: Controller
bankSelectLSB :: Controller
modulationLSB :: Controller
breathControlLSB :: Controller
footControlLSB :: Controller
portamentoTimeLSB :: Controller
dataEntryLSB :: Controller
mainVolumeLSB :: Controller
balanceLSB :: Controller
panoramaLSB :: Controller
expressionLSB :: Controller
generalPurpose1LSB :: Controller
generalPurpose2LSB :: Controller
generalPurpose3LSB :: Controller
generalPurpose4LSB :: Controller
sustain :: Controller
porta :: Controller
sustenuto :: Controller
softPedal :: Controller
hold2 :: Controller
generalPurpose5 :: Controller
generalPurpose6 :: Controller
generalPurpose7 :: Controller
generalPurpose8 :: Controller
extDepth :: Controller
tremoloDepth :: Controller
chorusDepth :: Controller
celesteDepth :: Controller
phaserDepth :: Controller
dataIncrement :: Controller
dataDecrement :: Controller
nonRegisteredParameterLSB :: Controller
nonRegisteredParameterMSB :: Controller
registeredParameterLSB :: Controller
registeredParameterMSB :: Controller
data Pitch
fromPitch :: Pitch -> Int
toPitch :: Int -> Pitch
data Velocity
fromVelocity :: Velocity -> Int
toVelocity :: Int -> Velocity
data Program
fromProgram :: Program -> Int
toProgram :: Int -> Program
data Controller
fromController :: Controller -> Int
toController :: Int -> Controller
increasePitch :: Int -> Pitch -> Pitch
subtractPitch :: Pitch -> Pitch -> Int
maximumVelocity :: Num quant => quant
normalVelocity :: Num quant => quant
toFloatVelocity :: (Integral a, Fractional b) => a -> b
Documentation
data T Source
Constructors
NoteOff Pitch Velocity
NoteOn Pitch Velocity
PolyAftertouch Pitch Pressure
ProgramChange Program
Control Controller ControllerValue
PitchBend PitchBendRange
MonoAftertouch Pressure
show/hide Instances
get :: C parser => Int -> Int -> Fallible parser TSource
putWithStatus :: C writer => (Int -> T writer ()) -> T -> T writer ()Source
type ControllerValue = IntSource
type PitchBendRange = IntSource
type Pressure = IntSource
isNote :: T -> BoolSource
isNoteOn :: T -> BoolSource
NoteOn with zero velocity is considered NoteOff according to MIDI specification.
isNoteOff :: T -> BoolSource
NoteOn with zero velocity is considered NoteOff according to MIDI specification.
zeroKey :: PitchSource
A MIDI problem is that one cannot uniquely map a MIDI key to a frequency. The frequency depends on the instrument. I don't know if the deviations are defined for General MIDI. If this applies one could add transposition information to the use patch map. For now I have chosen a value that leads to the right frequency for some piano sound in my setup.
explicitNoteOff :: T -> TSource
Convert all NoteOn p 0 to NoteOff p 64. The latter one is easier to process.
implicitNoteOff :: T -> TSource
Convert all NoteOff p 64 to NoteOn p 0. The latter one can be encoded more efficiently using the running status.
toFloatController :: (Integral a, Fractional b) => a -> bSource
Map integral MIDI controller value to floating point value. Maximum integral MIDI controller value 127 is mapped to 1. Minimum integral MIDI controller value 0 is mapped to 0.
bankSelect :: ControllerSource
modulation :: ControllerSource
breathControl :: ControllerSource
footControl :: ControllerSource
portamentoTime :: ControllerSource
dataEntry :: ControllerSource
mainVolume :: ControllerSource
balance :: ControllerSource
panorama :: ControllerSource
expression :: ControllerSource
generalPurpose1 :: ControllerSource
generalPurpose2 :: ControllerSource
generalPurpose3 :: ControllerSource
generalPurpose4 :: ControllerSource
vectorX :: ControllerSource
vectorY :: ControllerSource
bankSelectMSB :: ControllerSource
modulationMSB :: ControllerSource
breathControlMSB :: ControllerSource
footControlMSB :: ControllerSource
portamentoTimeMSB :: ControllerSource
dataEntryMSB :: ControllerSource
mainVolumeMSB :: ControllerSource
balanceMSB :: ControllerSource
panoramaMSB :: ControllerSource
expressionMSB :: ControllerSource
generalPurpose1MSB :: ControllerSource
generalPurpose2MSB :: ControllerSource
generalPurpose3MSB :: ControllerSource
generalPurpose4MSB :: ControllerSource
bankSelectLSB :: ControllerSource
modulationLSB :: ControllerSource
breathControlLSB :: ControllerSource
footControlLSB :: ControllerSource
portamentoTimeLSB :: ControllerSource
dataEntryLSB :: ControllerSource
mainVolumeLSB :: ControllerSource
balanceLSB :: ControllerSource
panoramaLSB :: ControllerSource
expressionLSB :: ControllerSource
generalPurpose1LSB :: ControllerSource
generalPurpose2LSB :: ControllerSource
generalPurpose3LSB :: ControllerSource
generalPurpose4LSB :: ControllerSource
sustain :: ControllerSource
porta :: ControllerSource
sustenuto :: ControllerSource
softPedal :: ControllerSource
hold2 :: ControllerSource
generalPurpose5 :: ControllerSource
generalPurpose6 :: ControllerSource
generalPurpose7 :: ControllerSource
generalPurpose8 :: ControllerSource
extDepth :: ControllerSource
tremoloDepth :: ControllerSource
chorusDepth :: ControllerSource
celesteDepth :: ControllerSource
phaserDepth :: ControllerSource
dataIncrement :: ControllerSource
dataDecrement :: ControllerSource
nonRegisteredParameterLSB :: ControllerSource
nonRegisteredParameterMSB :: ControllerSource
registeredParameterLSB :: ControllerSource
registeredParameterMSB :: ControllerSource
data Pitch Source
show/hide Instances
fromPitch :: Pitch -> IntSource
toPitch :: Int -> PitchSource
data Velocity Source
show/hide Instances
fromVelocity :: Velocity -> IntSource
toVelocity :: Int -> VelocitySource
data Program Source
show/hide Instances
fromProgram :: Program -> IntSource
toProgram :: Int -> ProgramSource
data Controller Source

We do not define Controller as enumeration with many constructors, because some controller 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 Data.List.lookup instead.

 maybe (putStrLn "unsupported controller") putStrLn $
 lookup ctrl $
    (portamento, "portamento") :
    (modulation, "modulation") :
    []
show/hide Instances
fromController :: Controller -> IntSource
toController :: Int -> ControllerSource
increasePitch :: Int -> Pitch -> PitchSource
subtractPitch :: Pitch -> Pitch -> IntSource
maximumVelocity :: Num quant => quantSource
The velocity of an ordinary key stroke and the maximum possible velocity.
normalVelocity :: Num quant => quantSource
toFloatVelocity :: (Integral a, Fractional b) => a -> bSource
64 is given as default value by the MIDI specification and thus we map it to 1. 0 is mapped to 0. All other values are interpolated linearly.
Produced by Haddock version 2.6.0