module Sound.MIDI.File(
T(..), Division(..), Track, Type(..),
empty,
ElapsedTime, fromElapsedTime, toElapsedTime,
Tempo, fromTempo, toTempo,
explicitNoteOff, implicitNoteOff,
showLines, changeVelocity, getTracks, resampleTime,
showEvent, showTime,
sortEvents, progChangeBeforeSetTempo,
) where
import qualified Sound.MIDI.Message.Channel.Voice as VoiceMsg
import qualified Sound.MIDI.Message.Channel as ChannelMsg
import qualified Sound.MIDI.File.Event.Meta as MetaEvent
import qualified Sound.MIDI.File.Event as Event
import Sound.MIDI.File.Event.Meta (
ElapsedTime, fromElapsedTime, toElapsedTime,
Tempo, fromTempo, toTempo,
)
import qualified Data.EventList.Relative.TimeBody as EventList
import Test.QuickCheck (Arbitrary(arbitrary), )
import qualified Test.QuickCheck as QC
import Control.Monad (liftM, liftM2, )
import Sound.MIDI.String (rightS, )
import Data.Ix(Ix)
import Data.List(groupBy, sort)
import Data.Maybe(fromMaybe)
data T = Cons Type Division [Track] deriving (Show, Eq)
data Type = Mixed | Parallel | Serial
deriving (Show, Eq, Ord, Ix, Enum, Bounded)
data Division = Ticks Tempo | SMPTE Int Int
deriving (Show, Eq)
type Track = EventList.T ElapsedTime Event.T
empty :: T
empty = Cons Mixed (Ticks 0) [EventList.empty]
instance Arbitrary T where
arbitrary =
do (typ, content) <-
QC.oneof $
fmap (\track -> (Mixed, [track])) arbitrary :
fmap (\tracks -> (Parallel, tracks)) arbitrary :
fmap (\tracks -> (Serial, tracks)) arbitrary :
[]
division <- arbitrary
return (Cons typ division content)
instance Arbitrary Division where
arbitrary =
QC.oneof $
liftM (Ticks . (1+)) arbitrary :
liftM2 (\x y -> SMPTE (1+abs x) (1+abs y)) arbitrary arbitrary :
[]
mapTrack :: (Track -> Track) -> T -> T
mapTrack f (Cons mfType division tracks) =
Cons mfType division (map f tracks)
explicitNoteOff :: T -> T
explicitNoteOff =
mapTrack (EventList.mapBody (Event.mapVoice VoiceMsg.explicitNoteOff))
implicitNoteOff :: T -> T
implicitNoteOff =
mapTrack (EventList.mapBody (Event.mapVoice VoiceMsg.implicitNoteOff))
showLines :: T -> String
showLines (Cons mfType division tracks) =
let showTrack track =
unlines
(" (" :
map
(\event -> " " ++ show event ++ " :")
(EventList.toPairList track) ++
" []) :" :
[])
in "MIDIFile.Cons " ++ show mfType ++ " (" ++ show division ++ ") (\n" ++
concatMap showTrack tracks ++
" [])"
showTime :: ElapsedTime -> ShowS
showTime t =
rightS 10 (shows t) . showString " : "
showEvent :: Event.T -> ShowS
showEvent (Event.MIDIEvent e) =
showString "Event.MIDIEvent " . shows e
showEvent (Event.MetaEvent e) =
showString "Event.MetaEvent " . shows e
showEvent (Event.SystemExclusive s) =
showString "SystemExclusive " . shows s
changeVelocity :: Double -> T -> T
changeVelocity r =
let multVel vel =
VoiceMsg.toVelocity $
round (r * fromIntegral (VoiceMsg.fromVelocity vel))
procVoice (VoiceMsg.NoteOn pitch vel) = VoiceMsg.NoteOn pitch (multVel vel)
procVoice (VoiceMsg.NoteOff pitch vel) = VoiceMsg.NoteOff pitch (multVel vel)
procVoice me = me
in mapTrack (EventList.mapBody (Event.mapVoice procVoice))
resampleTime :: Double -> T -> T
resampleTime r =
let divTime time = round (fromIntegral time / r)
newTempo tmp = round (fromIntegral tmp * r)
procEvent ev =
case ev of
Event.MetaEvent (MetaEvent.SetTempo tmp) ->
Event.MetaEvent (MetaEvent.SetTempo (newTempo tmp))
_ -> ev
in mapTrack (EventList.mapBody procEvent . EventList.mapTime divTime)
getTracks :: T -> [Track]
getTracks (Cons _ _ trks) = trks
sortEvents :: T -> T
sortEvents =
let coincideNote ev0 ev1 =
fromMaybe False $
do (_,x0) <- Event.maybeVoice ev0
(_,x1) <- Event.maybeVoice ev1
return (VoiceMsg.isNote x0 && VoiceMsg.isNote x1)
sortTrack =
EventList.flatten . EventList.mapBody sort .
EventList.mapCoincident (groupBy coincideNote)
in mapTrack sortTrack
progChangeBeforeSetTempo :: T -> T
progChangeBeforeSetTempo =
let sortTrack evs =
do ((t0,st@(Event.MetaEvent (MetaEvent.SetTempo _))), rest0)
<- EventList.viewL evs
((t1,pc@(Event.MIDIEvent (ChannelMsg.Cons _
(ChannelMsg.Voice (VoiceMsg.ProgramChange _))))), rest1)
<- EventList.viewL rest0
return $
EventList.cons t0 pc $
EventList.cons 0 st $
EventList.delay t1 rest1
in mapTrack (\track -> fromMaybe track (sortTrack track))