module Sound.MIDI.File.Load
(fromFile, fromByteList, maybeFromByteList, maybeFromByteString,
showFile, )
where
import Sound.MIDI.File
import qualified Sound.MIDI.File as MIDIFile
import qualified Sound.MIDI.File.Event.Meta as MetaEvent
import qualified Sound.MIDI.File.Event as Event
import qualified Data.EventList.Relative.TimeBody as EventList
import qualified Numeric.NonNegative.Wrapper as NonNeg
import Sound.MIDI.IO (ByteList, readBinaryFile, )
import Sound.MIDI.String (unlinesS)
import Sound.MIDI.Parser.Primitive
import Sound.MIDI.Parser.Class (PossiblyIncomplete, )
import qualified Sound.MIDI.Parser.Class as Parser
import qualified Sound.MIDI.Parser.Restricted as ParserRestricted
import qualified Sound.MIDI.Parser.ByteString as ParserByteString
import qualified Sound.MIDI.Parser.Stream as ParserStream
import qualified Sound.MIDI.Parser.File as ParserFile
import qualified Sound.MIDI.Parser.State as ParserState
import qualified Sound.MIDI.Parser.Status as StatusParser
import qualified Sound.MIDI.Parser.Report as Report
import qualified Control.Monad.State as State
import Control.Monad (liftM, liftM2, when, )
import qualified Data.ByteString.Lazy as B
import Sound.MIDI.Utility (mapSnd, )
import Data.List (genericReplicate, genericLength, )
import Data.Maybe (catMaybes, )
fromFile :: FilePath -> IO MIDIFile.T
fromFile =
ParserFile.runIncompleteFile parse
fromByteList :: ByteList -> MIDIFile.T
fromByteList contents =
either
error id
(Report.result (maybeFromByteList contents))
maybeFromByteList ::
ByteList -> Report.T MIDIFile.T
maybeFromByteList =
ParserStream.runIncomplete parse . ParserStream.ByteList
maybeFromByteString ::
B.ByteString -> Report.T MIDIFile.T
maybeFromByteString =
ParserByteString.runIncomplete parse
parse :: Parser.C parser => parser (PossiblyIncomplete MIDIFile.T)
parse =
getChunk >>= \ (typ, hdLen) ->
case typ of
"MThd" ->
do (format, nTracks, division) <-
ParserRestricted.run hdLen getHeader
~(me, tracks) <-
Parser.zeroOrMoreInc
(do (me0,track) <- getTrackChunk
trackNoEOT <-
maybe (return Nothing) (liftM Just . removeEndOfTrack) track
return (me0, trackNoEOT))
let n = genericLength tracks
Parser.force $ when (n /= nTracks) $
Parser.warn ("header says " ++ show nTracks ++
" tracks, but " ++ show n ++ " tracks were found")
return (me, MIDIFile.Cons format division $ catMaybes tracks)
_ -> Parser.warn ("found Alien chunk <" ++ typ ++ ">") >>
Parser.skip hdLen >>
parse
removeEndOfTrack :: Parser.C parser => Track -> parser Track
removeEndOfTrack xs =
maybe
(Parser.warn "Empty track, missing EndOfTrack" >>
return xs)
(\(initEvents, lastEvent) ->
let (eots, track) =
EventList.partition isEndOfTrack initEvents
in do Parser.force $ when
(not $ EventList.null eots)
(Parser.warn "EndOfTrack inside a track")
Parser.force $ when
(not $ isEndOfTrack $ snd lastEvent)
(Parser.warn "Track does not end with EndOfTrack")
return track)
(EventList.viewR xs)
isEndOfTrack :: Event.T -> Bool
isEndOfTrack ev =
case ev of
Event.MetaEvent MetaEvent.EndOfTrack -> True
_ -> False
getChunk :: Parser.C parser => parser (String, NonNeg.Integer)
getChunk =
liftM2 (,)
(getString 4)
(getNByteCardinal 4)
getTrackChunk :: Parser.C parser => parser (PossiblyIncomplete (Maybe Track))
getTrackChunk =
do (typ, len) <- getChunk
if typ=="MTrk"
then liftM (mapSnd Just) $
ParserRestricted.run len $
StatusParser.run getTrack
else Parser.warn ("found Alien chunk <" ++ typ ++ "> in track section") >>
Parser.skip len >>
return (Nothing, Nothing)
getHeader :: Parser.C parser => parser (MIDIFile.Type, NonNeg.Int, Division)
getHeader =
do
format <- makeEnum =<< get2
nTracks <- liftM (NonNeg.fromNumberMsg "MIDI.Load.getHeader") get2
division <- getDivision
return (format, nTracks, division)
getDivision :: Parser.C parser => parser Division
getDivision =
do
x <- get1
y <- get1
return $
if x < 128
then Ticks (NonNeg.fromNumberMsg "MIDI.Load.getDivision" (x*256+y))
else SMPTE (256x) y
getTrack :: Parser.C parser => StatusParser.T parser (PossiblyIncomplete MIDIFile.Track)
getTrack =
liftM
(mapSnd EventList.fromPairList)
(ParserState.zeroOrMore Event.getTrackEvent)
showFile :: FilePath -> IO ()
showFile fileName = putStr . showChunks =<< readBinaryFile fileName
showChunks :: ByteList -> String
showChunks mf =
showMR getChunks (\(me,cs) ->
unlinesS (map pp cs) .
maybe id (\e -> showString ("incomplete chunk list: " ++ e ++ "\n")) me) mf ""
where
pp :: (String, ByteList) -> ShowS
pp ("MThd",contents) =
showString "Header: " .
showMR getHeader shows contents
pp ("MTrk",contents) =
showString "Track:\n" .
showMR (StatusParser.run getTrack)
(\(me,track) str ->
EventList.foldr
MIDIFile.showTime
(\e -> MIDIFile.showEvent e . showString "\n")
(maybe "" (\e -> "incomplete track: " ++ e ++ "\n") me ++ str) track)
contents
pp (ty,contents) =
showString "Alien Chunk: " .
showString ty .
showString " " .
shows contents .
showString "\n"
showMR :: ParserStream.T ParserStream.ByteList a -> (a->ShowS) -> ByteList -> ShowS
showMR m pp contents =
let report = ParserStream.run m (ParserStream.ByteList contents)
in unlinesS (map showString $ Report.warnings report) .
either showString pp (Report.result report)
getChunks ::
Parser.C parser => parser (PossiblyIncomplete [(String, ByteList)])
getChunks =
Parser.zeroOrMore $
do (typ, len) <- getChunk
body <- sequence (genericReplicate len getByte)
return (typ, body)