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 qualified Sound.MIDI.Parser.Class as Parser
import qualified Sound.MIDI.Parser.Restricted as RestrictedParser
import qualified Sound.MIDI.Parser.ByteString as ByteStringParser
import qualified Sound.MIDI.Parser.Stream as StreamParser
import qualified Sound.MIDI.Parser.File as FileParser
import qualified Sound.MIDI.Parser.Status as StatusParser
import qualified Sound.MIDI.Parser.Report as Report
import Control.Monad.Trans.Class (lift, )
import Control.Monad (liftM, liftM2, )
import qualified Data.ByteString.Lazy as B
import qualified Control.Monad.Exception.Asynchronous as Async
import Data.List (genericReplicate, genericLength, )
import Data.Maybe (catMaybes, )
fromFile :: FilePath -> IO MIDIFile.T
fromFile =
FileParser.runIncompleteFile parse
fromByteList :: ByteList -> MIDIFile.T
fromByteList contents =
either
error id
(Report.result (maybeFromByteList contents))
maybeFromByteList ::
ByteList -> Report.T MIDIFile.T
maybeFromByteList =
StreamParser.runIncomplete parse . StreamParser.ByteList
maybeFromByteString ::
B.ByteString -> Report.T MIDIFile.T
maybeFromByteString =
ByteStringParser.runIncomplete parse
parse :: Parser.C parser => Parser.Partial (Parser.Fallible parser) MIDIFile.T
parse =
getChunk >>= \ (typ, hdLen) ->
case typ of
"MThd" ->
do (format, nTracks, division) <-
RestrictedParser.runFallible hdLen getHeader
excTracks <-
lift $ Parser.zeroOrMoreInc
(getTrackChunk >>= Async.mapM (lift . liftMaybe removeEndOfTrack))
flip Async.mapM excTracks $ \tracks ->
do let n = genericLength tracks
lift $ Parser.warnIf (n /= nTracks)
("header says " ++ show nTracks ++
" tracks, but " ++ show n ++ " tracks were found")
return (MIDIFile.Cons format division $ catMaybes tracks)
_ -> lift (Parser.warn ("found Alien chunk <" ++ typ ++ ">")) >>
Parser.skip hdLen >>
parse
liftMaybe :: Monad m => (a -> m b) -> Maybe a -> m (Maybe b)
liftMaybe f = maybe (return Nothing) (liftM Just . f)
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.warnIf
(not $ EventList.null eots)
"EndOfTrack inside a track"
Parser.warnIf
(not $ isEndOfTrack $ snd lastEvent)
"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.Fallible parser (String, NonNeg.Integer)
getChunk =
liftM2 (,)
(getString 4)
(getNByteCardinal 4)
getTrackChunk :: Parser.C parser => Parser.Partial (Parser.Fallible parser) (Maybe Track)
getTrackChunk =
do (typ, len) <- getChunk
if typ=="MTrk"
then liftM (fmap Just) $ lift $
RestrictedParser.run len $
StatusParser.run getTrack
else lift (Parser.warn ("found Alien chunk <" ++ typ ++ "> in track section")) >>
Parser.skip len >>
return (Async.pure Nothing)
getHeader :: Parser.C parser => Parser.Fallible 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.Fallible 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 => Parser.Partial (StatusParser.T parser) MIDIFile.Track
getTrack =
liftM
(fmap EventList.fromPairList)
(Parser.zeroOrMore Event.getTrackEvent)
showFile :: FilePath -> IO ()
showFile fileName = putStr . showChunks =<< readBinaryFile fileName
showChunks :: ByteList -> String
showChunks mf =
showMR (lift getChunks) (\(Async.Exceptional 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 (lift $ StatusParser.run getTrack)
(\(Async.Exceptional 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 :: Parser.Fallible (StreamParser.T StreamParser.ByteList) a -> (a->ShowS) -> ByteList -> ShowS
showMR m pp contents =
let report = StreamParser.run m (StreamParser.ByteList contents)
in unlinesS (map showString $ Report.warnings report) .
either showString pp (Report.result report)
getChunks ::
Parser.C parser => Parser.Partial parser [(String, ByteList)]
getChunks =
Parser.zeroOrMore $
do (typ, len) <- getChunk
body <- sequence (genericReplicate len getByte)
return (typ, body)