| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Dahdit.Midi.Midi
Synopsis
- newtype Channel = Channel {}
- newtype ChannelCount = ChannelCount {}
- newtype Note = Note {}
- newtype Velocity = Velocity {}
- newtype ControlNum = ControlNum {}
- newtype ControlVal = ControlVal {}
- newtype Pressure = Pressure {}
- newtype ProgramNum = ProgramNum {}
- newtype PitchBend = PitchBend {}
- newtype Song = Song {}
- newtype Position = Position {}
- newtype ShortManf = ShortManf {}
- newtype LongManf = LongManf {
- unLongManf :: Word16
- data Manf
- data QuarterTimeUnit
- data QuarterTime = QuarterTime {
- qtUnit :: !QuarterTimeUnit
- qtValue :: !Word4
- data ChanStatus = ChanStatus !Channel !ChanStatusType
- data RtStatus
- data CommonStatus
- data LiveStatus
- data RecStatus
- data ShortStatus
- data ChanStatusType
- data ChanVoiceData
- data ChanModeData
- data ChanData
- data UnivSysEx = UnivSysEx {
- useSubId :: !Word8
- usePayload :: !ShortByteString
- data ManfSysEx = ManfSysEx {
- mseManf :: !Manf
- msePayload :: !ShortByteString
- data SysExData
- data CommonData
- data LiveMsg
- newtype MetaString = MetaString {}
- data MetaData = MetaData {
- mdType :: !Word8
- mdBody :: !MetaString
- data RecMsg
- data ShortMsg
- msgNoteOn :: HasChanData s c => Channel -> Note -> Velocity -> c
- msgNoteOff :: Channel -> Note -> LiveMsg
- data Event = Event {}
- newtype Track = Track {}
- data MidFileType
- data MidFile = MidFile {}
- newtype SysExDump = SysExDump {}
Documentation
Instances
| Bounded Channel Source # | |
| Enum Channel Source # | |
| Num Channel Source # | |
| Integral Channel Source # | |
Defined in Dahdit.Midi.Midi | |
| Real Channel Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: Channel -> Rational # | |
| Show Channel Source # | |
| Binary Channel Source # | |
| StaticByteSized Channel Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize Channel :: Nat # Methods staticByteSize :: Proxy Channel -> ByteCount # | |
| Eq Channel Source # | |
| Ord Channel Source # | |
| Hashable Channel Source # | |
Defined in Dahdit.Midi.Midi | |
| Newtype Channel MidiWord7 Source # | |
| type StaticSize Channel Source # | |
Defined in Dahdit.Midi.Midi | |
newtype ChannelCount Source #
Constructors
| ChannelCount | |
Fields | |
Instances
Instances
| Enum Note Source # | |
| Num Note Source # | |
| Integral Note Source # | |
| Real Note Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: Note -> Rational # | |
| Show Note Source # | |
| Binary Note Source # | |
| StaticByteSized Note Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize Note :: Nat # Methods staticByteSize :: Proxy Note -> ByteCount # | |
| Eq Note Source # | |
| Ord Note Source # | |
| Hashable Note Source # | |
Defined in Dahdit.Midi.Midi | |
| type StaticSize Note Source # | |
Defined in Dahdit.Midi.Midi | |
Constructors
| Velocity | |
Fields | |
Instances
| Enum Velocity Source # | |
| Num Velocity Source # | |
| Integral Velocity Source # | |
Defined in Dahdit.Midi.Midi | |
| Real Velocity Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: Velocity -> Rational # | |
| Show Velocity Source # | |
| Binary Velocity Source # | |
| StaticByteSized Velocity Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize Velocity :: Nat # Methods staticByteSize :: Proxy Velocity -> ByteCount # | |
| Eq Velocity Source # | |
| Ord Velocity Source # | |
Defined in Dahdit.Midi.Midi | |
| Hashable Velocity Source # | |
Defined in Dahdit.Midi.Midi | |
| type StaticSize Velocity Source # | |
Defined in Dahdit.Midi.Midi | |
newtype ControlNum Source #
Constructors
| ControlNum | |
Fields | |
Instances
newtype ControlVal Source #
Constructors
| ControlVal | |
Fields | |
Instances
Constructors
| Pressure | |
Fields | |
Instances
| Enum Pressure Source # | |
| Num Pressure Source # | |
| Integral Pressure Source # | |
Defined in Dahdit.Midi.Midi | |
| Real Pressure Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: Pressure -> Rational # | |
| Show Pressure Source # | |
| Binary Pressure Source # | |
| StaticByteSized Pressure Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize Pressure :: Nat # Methods staticByteSize :: Proxy Pressure -> ByteCount # | |
| Eq Pressure Source # | |
| Ord Pressure Source # | |
Defined in Dahdit.Midi.Midi | |
| Hashable Pressure Source # | |
Defined in Dahdit.Midi.Midi | |
| type StaticSize Pressure Source # | |
Defined in Dahdit.Midi.Midi | |
newtype ProgramNum Source #
Constructors
| ProgramNum | |
Fields | |
Instances
Constructors
| PitchBend | |
Fields | |
Instances
Instances
| Enum Song Source # | |
| Num Song Source # | |
| Integral Song Source # | |
| Real Song Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: Song -> Rational # | |
| Show Song Source # | |
| Binary Song Source # | |
| StaticByteSized Song Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize Song :: Nat # Methods staticByteSize :: Proxy Song -> ByteCount # | |
| Eq Song Source # | |
| Ord Song Source # | |
| Hashable Song Source # | |
Defined in Dahdit.Midi.Midi | |
| type StaticSize Song Source # | |
Defined in Dahdit.Midi.Midi | |
Constructors
| Position | |
Fields | |
Instances
| Enum Position Source # | |
| Num Position Source # | |
| Integral Position Source # | |
Defined in Dahdit.Midi.Midi | |
| Real Position Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: Position -> Rational # | |
| Show Position Source # | |
| Binary Position Source # | |
| StaticByteSized Position Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize Position :: Nat # Methods staticByteSize :: Proxy Position -> ByteCount # | |
| Eq Position Source # | |
| Ord Position Source # | |
Defined in Dahdit.Midi.Midi | |
| Hashable Position Source # | |
Defined in Dahdit.Midi.Midi | |
| type StaticSize Position Source # | |
Defined in Dahdit.Midi.Midi | |
Constructors
| ShortManf | |
Fields | |
Instances
Constructors
| LongManf | |
Fields
| |
Instances
| Enum LongManf Source # | |
| Num LongManf Source # | |
| Integral LongManf Source # | |
Defined in Dahdit.Midi.Midi | |
| Real LongManf Source # | |
Defined in Dahdit.Midi.Midi Methods toRational :: LongManf -> Rational # | |
| Show LongManf Source # | |
| Binary LongManf Source # | |
| StaticByteSized LongManf Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize LongManf :: Nat # Methods staticByteSize :: Proxy LongManf -> ByteCount # | |
| Eq LongManf Source # | |
| Ord LongManf Source # | |
Defined in Dahdit.Midi.Midi | |
| Hashable LongManf Source # | |
Defined in Dahdit.Midi.Midi | |
| type StaticSize LongManf Source # | |
Defined in Dahdit.Midi.Midi | |
Instances
| Generic Manf Source # | |
| Show Manf Source # | |
| Binary Manf Source # | |
| Eq Manf Source # | |
| Ord Manf Source # | |
| type Rep Manf Source # | |
Defined in Dahdit.Midi.Midi type Rep Manf = D1 ('MetaData "Manf" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "ManfShort" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShortManf)) :+: C1 ('MetaCons "ManfLong" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 LongManf))) | |
data QuarterTimeUnit Source #
Constructors
| QTUFramesLow | |
| QTUFramesHigh | |
| QTUSecondsLow | |
| QTUSecondsHigh | |
| QTUMinutesLow | |
| QTUMinutesHigh | |
| QTUHoursLow | |
| QTUHoursHigh |
Instances
data QuarterTime Source #
Constructors
| QuarterTime | |
Fields
| |
Instances
data ChanStatus Source #
Constructors
| ChanStatus !Channel !ChanStatusType |
Instances
Constructors
| RtStatusTimingClock | |
| RtStatusStart | |
| RtStatusContinue | |
| RtStatusStop | |
| RtStatusActiveSensing | |
| RtStatusSystemReset |
Instances
| Bounded RtStatus Source # | |
| Enum RtStatus Source # | |
| Generic RtStatus Source # | |
| Show RtStatus Source # | |
| Eq RtStatus Source # | |
| Ord RtStatus Source # | |
Defined in Dahdit.Midi.Midi | |
| type Rep RtStatus Source # | |
Defined in Dahdit.Midi.Midi type Rep RtStatus = D1 ('MetaData "RtStatus" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) ((C1 ('MetaCons "RtStatusTimingClock" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RtStatusStart" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtStatusContinue" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "RtStatusStop" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RtStatusActiveSensing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RtStatusSystemReset" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
data CommonStatus Source #
Constructors
| CommonStatusTimeFrame | |
| CommonStatusSongPointer | |
| CommonStatusSongSelect | |
| CommonStatusTuneRequest |
Instances
data LiveStatus Source #
Constructors
| LiveStatusChan !ChanStatus | |
| LiveStatusSysEx | |
| LiveStatusSysCommon !CommonStatus | |
| LiveStatusSysRt !RtStatus |
Instances
Constructors
| RecStatusChan !ChanStatus | |
| RecStatusSysEx | |
| RecStatusMeta |
Instances
| Generic RecStatus Source # | |
| Show RecStatus Source # | |
| Binary RecStatus Source # | |
| StaticByteSized RecStatus Source # | |
Defined in Dahdit.Midi.Midi Associated Types type StaticSize RecStatus :: Nat # Methods staticByteSize :: Proxy RecStatus -> ByteCount # | |
| Eq RecStatus Source # | |
| Ord RecStatus Source # | |
| type Rep RecStatus Source # | |
Defined in Dahdit.Midi.Midi type Rep RecStatus = D1 ('MetaData "RecStatus" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "RecStatusChan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChanStatus)) :+: (C1 ('MetaCons "RecStatusSysEx" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RecStatusMeta" 'PrefixI 'False) (U1 :: Type -> Type))) | |
| type StaticSize RecStatus Source # | |
Defined in Dahdit.Midi.Midi | |
data ShortStatus Source #
Constructors
| ShortStatusChan !ChanStatus | |
| ShortStatusSysCommon !CommonStatus | |
| ShortStatusSysRt !RtStatus |
Instances
data ChanStatusType Source #
Constructors
| ChanStatusNoteOff | |
| ChanStatusNoteOn | |
| ChanStatusKeyAftertouch | |
| ChanStatusControlChange | |
| ChanStatusProgramChange | |
| ChanStatusChanAftertouch | |
| ChanStatusPitchBend |
Instances
data ChanVoiceData Source #
Constructors
Instances
| Show ChanVoiceData Source # | |
Defined in Dahdit.Midi.Midi Methods showsPrec :: Int -> ChanVoiceData -> ShowS # show :: ChanVoiceData -> String # showList :: [ChanVoiceData] -> ShowS # | |
| Eq ChanVoiceData Source # | |
Defined in Dahdit.Midi.Midi Methods (==) :: ChanVoiceData -> ChanVoiceData -> Bool # (/=) :: ChanVoiceData -> ChanVoiceData -> Bool # | |
| Ord ChanVoiceData Source # | |
Defined in Dahdit.Midi.Midi Methods compare :: ChanVoiceData -> ChanVoiceData -> Ordering # (<) :: ChanVoiceData -> ChanVoiceData -> Bool # (<=) :: ChanVoiceData -> ChanVoiceData -> Bool # (>) :: ChanVoiceData -> ChanVoiceData -> Bool # (>=) :: ChanVoiceData -> ChanVoiceData -> Bool # max :: ChanVoiceData -> ChanVoiceData -> ChanVoiceData # min :: ChanVoiceData -> ChanVoiceData -> ChanVoiceData # | |
data ChanModeData Source #
Constructors
| ChanModeAllSoundOff | |
| ChanModeResetAllControllers | |
| ChanModeLocalControlOff | |
| ChanModeLocalControlOn | |
| ChanModeAllNotesOff | |
| ChanModeOmniOff | |
| ChanModeOmniOn | |
| ChanModeMonoOn !ChannelCount | |
| ChanModeMonoOff |
Instances
Constructors
| ChanDataVoice !ChanVoiceData | |
| ChanDataMode !ChanModeData |
Instances
| Generic ChanData Source # | |
| Show ChanData Source # | |
| Eq ChanData Source # | |
| Ord ChanData Source # | |
Defined in Dahdit.Midi.Midi | |
| type Rep ChanData Source # | |
Defined in Dahdit.Midi.Midi type Rep ChanData = D1 ('MetaData "ChanData" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "ChanDataVoice" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChanVoiceData)) :+: C1 ('MetaCons "ChanDataMode" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChanModeData))) | |
Constructors
| UnivSysEx | |
Fields
| |
Instances
| Show UnivSysEx Source # | |
| Binary UnivSysEx Source # | |
| Eq UnivSysEx Source # | |
| Ord UnivSysEx Source # | |
Constructors
| ManfSysEx | |
Fields
| |
Instances
| Show ManfSysEx Source # | |
| Binary ManfSysEx Source # | |
| Eq ManfSysEx Source # | |
| Ord ManfSysEx Source # | |
Constructors
| SysExDataUniv !UnivSysEx | |
| SysExDataManf !ManfSysEx |
Instances
| Generic SysExData Source # | |
| Show SysExData Source # | |
| Binary SysExData Source # | |
| Eq SysExData Source # | |
| Ord SysExData Source # | |
| type Rep SysExData Source # | |
Defined in Dahdit.Midi.Midi type Rep SysExData = D1 ('MetaData "SysExData" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "SysExDataUniv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnivSysEx)) :+: C1 ('MetaCons "SysExDataManf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ManfSysEx))) | |
data CommonData Source #
Constructors
| CommonDataTimeFrame !QuarterTime | |
| CommonDataSongPointer !Position | |
| CommonDataSongSelect !Song | |
| CommonDataTuneRequest |
Instances
Constructors
| LiveMsgChan !Channel !ChanData | |
| LiveMsgSysEx !SysExData | |
| LiveMsgSysCommon !CommonData | |
| LiveMsgSysRt !RtStatus |
Instances
newtype MetaString Source #
A byte string prefixed by a single-byte length
Constructors
| MetaString | |
Fields | |
Instances
| IsString MetaString Source # | |
Defined in Dahdit.Midi.Midi Methods fromString :: String -> MetaString # | |
| Show MetaString Source # | |
Defined in Dahdit.Midi.Midi Methods showsPrec :: Int -> MetaString -> ShowS # show :: MetaString -> String # showList :: [MetaString] -> ShowS # | |
| Binary MetaString Source # | |
Defined in Dahdit.Midi.Midi | |
| Eq MetaString Source # | |
Defined in Dahdit.Midi.Midi | |
| Ord MetaString Source # | |
Defined in Dahdit.Midi.Midi Methods compare :: MetaString -> MetaString -> Ordering # (<) :: MetaString -> MetaString -> Bool # (<=) :: MetaString -> MetaString -> Bool # (>) :: MetaString -> MetaString -> Bool # (>=) :: MetaString -> MetaString -> Bool # max :: MetaString -> MetaString -> MetaString # min :: MetaString -> MetaString -> MetaString # | |
Constructors
| MetaData | |
Fields
| |
Instances
| Generic MetaData Source # | |
| Show MetaData Source # | |
| Binary MetaData Source # | |
| Eq MetaData Source # | |
| Ord MetaData Source # | |
Defined in Dahdit.Midi.Midi | |
| type Rep MetaData Source # | |
Defined in Dahdit.Midi.Midi type Rep MetaData = D1 ('MetaData "MetaData" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "MetaData" 'PrefixI 'True) (S1 ('MetaSel ('Just "mdType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "mdBody") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MetaString))) | |
Constructors
| RecMsgChan !Channel !ChanData | |
| RecMsgSysEx !SysExData | |
| RecMsgMeta !MetaData |
Instances
| Generic RecMsg Source # | |
| Show RecMsg Source # | |
| Binary RecMsg Source # | |
| Eq RecMsg Source # | |
| Ord RecMsg Source # | |
| type Rep RecMsg Source # | |
Defined in Dahdit.Midi.Midi type Rep RecMsg = D1 ('MetaData "RecMsg" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "RecMsgChan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Channel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChanData)) :+: (C1 ('MetaCons "RecMsgSysEx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SysExData)) :+: C1 ('MetaCons "RecMsgMeta" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MetaData)))) | |
Constructors
| ShortMsgChan !Channel !ChanData | |
| ShortMsgSysCommon !CommonData | |
| ShortMsgSysRt !RtStatus |
Instances
| Generic ShortMsg Source # | |
| Show ShortMsg Source # | |
| Binary ShortMsg Source # | |
| Eq ShortMsg Source # | |
| Ord ShortMsg Source # | |
Defined in Dahdit.Midi.Midi | |
| type Rep ShortMsg Source # | |
Defined in Dahdit.Midi.Midi type Rep ShortMsg = D1 ('MetaData "ShortMsg" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "ShortMsgChan" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Channel) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChanData)) :+: (C1 ('MetaCons "ShortMsgSysCommon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CommonData)) :+: C1 ('MetaCons "ShortMsgSysRt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RtStatus)))) | |
NOTE: Time delta is in number of ticks since previous message
Instances
| Generic Event Source # | |
| Show Event Source # | |
| Eq Event Source # | |
| Ord Event Source # | |
| type Rep Event Source # | |
Defined in Dahdit.Midi.Midi type Rep Event = D1 ('MetaData "Event" "Dahdit.Midi.Midi" "dahdit-midi-0.6.0-GVWPQ8LIqa2GtOee7SJOeh" 'False) (C1 ('MetaCons "Event" 'PrefixI 'True) (S1 ('MetaSel ('Just "evDelta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VarWord) :*: S1 ('MetaSel ('Just "evMsg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RecMsg))) | |
data MidFileType Source #
Instances
NOTE: Ticks could also be SMTPE-related, but we don't support that here
Constructors
| SysExDump | |
Fields | |
Instances
| Show SysExDump Source # | |
| Binary SysExDump Source # | |
| Eq SysExDump Source # | |
| Ord SysExDump Source # | |