module ZMidi.IO.Common (
mapDirInDir
, mapDir
, mapDir_
, foldrDirInDir
, foldrDir
, readMidiFile
, readMidiScoreSafe
, readQMidiScoreSafe
, readMidiScore
, readQMidiScore
, writeMidiScore
, logDuplicates
, removeTrackLabels
, putErrStrLn
, warning
)where
import ZMidi.Core ( MidiFile (..), readMidi, writeMidi )
import ZMidi.Score ( MidiScore (..), midiFileToMidiScore
, midiScoreToMidiFile, removeLabels, QMidiScore (..)
, quantiseQDevSafe, quantise )
import Control.Monad ( filterM, void )
import System.Directory ( getDirectoryContents, canonicalizePath
, doesDirectoryExist )
import System.IO ( stderr, hPutStrLn )
import System.FilePath ( (</>) )
import Data.Foldable ( foldrM )
import Data.List ( sort )
import Control.Concurrent.ParallelIO.Global ( parallel )
mapDirInDir :: (FilePath -> IO a) -> FilePath -> IO [a]
mapDirInDir f fp = do fs <- getDirectoryContents fp
>>= return . filter (\x -> x /= "." && x /= "..")
cfp <- canonicalizePath fp
filterM doesDirectoryExist (fmap (cfp </>) fs) >>= mapM f
mapDir_ :: (FilePath -> IO a) -> FilePath -> IO ()
mapDir_ f = void . mapDir f
mapDir :: (FilePath -> IO a) -> FilePath -> IO [a]
mapDir f fp = do fs <- getCurDirectoryContents fp
cin <- canonicalizePath fp
res <- parallel . map (f . (cin </>)) $ fs
return res
foldrDirInDir :: (FilePath -> b -> IO b) -> b -> FilePath -> IO b
foldrDirInDir f b fp =
do fs <- getDirectoryContents fp
>>= return . filter (\x -> x /= "." && x /= "..")
cfp <- canonicalizePath fp
filterM doesDirectoryExist (fmap (cfp </>) fs) >>= foldrM f b
foldrDir :: (FilePath -> b -> IO b) -> b -> FilePath -> IO b
foldrDir f b fp = do fs <- getCurDirectoryContents fp
cin <- canonicalizePath fp
putErrStrLn cin
foldrM (\x y -> f (cin </> x) $! y) b fs
readQMidiScoreSafe :: FilePath -> IO (Either String QMidiScore)
readQMidiScoreSafe f = readMidiScoreSafe f >>= return . (>>= quantiseQDevSafe)
readMidiScoreSafe :: FilePath -> IO (Either String MidiScore)
readMidiScoreSafe f = readMidi f >>= return . either (Left . show)
(Right . midiFileToMidiScore)
readQMidiScore :: FilePath -> IO (QMidiScore)
readQMidiScore f = readMidiScore f >>= return . quantise
readMidiScore :: FilePath -> IO (MidiScore)
readMidiScore f = readMidiFile f >>= return . midiFileToMidiScore
readMidiFile :: FilePath -> IO (MidiFile)
readMidiFile f = readMidi f >>= return . either (error . show) id
writeMidiScore :: MidiScore -> FilePath -> IO ()
writeMidiScore mf f = writeMidi f . midiScoreToMidiFile $ mf
logDuplicates :: FilePath -> IO ()
logDuplicates fp = do midis <- getCurDirectoryContents fp
>>= mapM (return . (fp </>))
>>= mapM (\x -> readMidiFile x >>= return . (x,))
mapM_ (checkFile midis) midis where
checkFile :: [(FilePath, MidiFile)] -> (FilePath, MidiFile) -> IO ()
checkFile midis (f, mf) = case filter (\(x,y) -> x /= f && y == mf) midis of
[] -> return ()
l -> mapM_ (\(m,_) -> putStrLn (f ++ " == " ++ m)) l
removeTrackLabels :: FilePath -> IO ()
removeTrackLabels f = readMidiFile f >>=
writeMidi (f ++ ".noLab.mid") . removeLabels
warning :: FilePath -> String -> IO ()
warning fp w = putErrStrLn ("Warning: skipping " ++ fp ++ ": " ++ w)
putErrStrLn :: String -> IO ()
putErrStrLn s = hPutStrLn stderr s
getCurDirectoryContents :: FilePath -> IO [FilePath]
getCurDirectoryContents fp =
getDirectoryContents fp >>= return . sort . filter (\x -> x /= "." && x /= "..")