module ZMidi.Core.Pretty.Internal
(
midi_header_columns
, tellMidiHeader
, byteList
, safeString
, textType
) where
import ZMidi.Core.Datatypes
import ZMidi.Core.Internal.SimpleFormat
import Data.Char
#ifndef MIN_VERSION_GLASGOW_HASKELL
import Data.Monoid
#endif
import Data.Word
midi_header_columns :: ColumnSpecs
midi_header_columns = ColumnSpecs '|' [ PadR 21, PadR 38 ]
tellMidiHeader :: MidiHeader -> Table ()
tellMidiHeader (MidiHeader fmt tcount td) =
localColumns midi_header_columns $ do
tellRow $ \_ _ -> [ text "MIDI Format", ppFormat fmt ]
tellRow $ \_ _ -> [ text "Number of tracks", integral tcount ]
tellRow $ \_ _ -> [ text "Time Division", ppTimeDivision td ]
ppFormat :: MidiFormat -> WString
ppFormat MF0 = text "Type 0 MIDI File"
ppFormat MF1 = text "Type 1 MIDI File"
ppFormat MF2 = text "Type 2 MIDI File"
ppTimeDivision :: MidiTimeDivision -> WString
ppTimeDivision (FPS i) = text "FPS" <+> integral i
ppTimeDivision (TPB i) = text "Ticks" <+> integral i
byteList :: (Show a, Integral a) => a -> [Word8] -> WString
byteList n ws | n < 10 = integral n <+> mconcat (map hex2 ws)
| otherwise = integral n <+> repeatChar 10 '.'
textType :: MidiTextType -> String
textType GENERIC_TEXT = "generic-text"
textType COPYRIGHT_NOTICE = "copyright-notice"
textType SEQUENCE_NAME = "sequence-name"
textType INSTRUMENT_NAME = "instrument-name"
textType LYRICS = "lyrics"
textType MARKER = "marker"
textType CUE_POINT = "cue-point"
safeString :: String -> String
safeString = map (f . ord)
where
f i | i < 164 = chr i
| otherwise = '#'