\begin{code} -- | -- Maintainer : silva.samuel@alumni.uminho.pt -- Stability : experimental -- Portability: portable -- This module implements module Main where import qualified Text.XML.MusicXML as MusicXML --import Music.Analysis.MusicXML2Haskore --import Music.Analysis.MusicXML.Functions import Control.Monad import Data.List import System.IO import System.Environment import System.Console.GetOpt \end{code} \begin{code} -- | warn :: String -> IO () warn msg = putStrLn msg >> hFlush stdout -- | version :: String version = "0.1.2" \end{code} \begin{code} -- | data Option = Unknown -- | MusicXML | Abstract | ABC | Lilypond | Haskore -- | Format -- | MusicXML2Abstract -- | Abstract2ABC -- | Abstract2Lilypond -- | MusicXML2Haskore | Help | Version deriving (Eq, Show) -- | options :: [OptDescr Option] options = [ Option ['v','V'] ["version"] (NoArg Version) "show version number" , Option ['h','H','?'] ["help"] (NoArg Help) "show help" ] -- | header :: String -> String header prog = "Usage: "++ prog ++" [OPTIONS...] FILES..." \end{code} \begin{code} --Nothing Nothing importMusicXML :: FilePath -> IO (Maybe MusicXML.MusicXMLDoc) importMusicXML input = do musicxml <- MusicXML.read_FILE MusicXML.read_MusicXMLDoc input case MusicXML.isOK musicxml of True -> return (Just (MusicXML.fromOK musicxml)) False -> putStrLn ("Can't read "++show input) >> return Nothing \end{code} \begin{code} main :: IO () main = do argv <- getArgs prog <- getProgName case getOpt Permute options argv of (o,n,[]) | Help`elem`o -> putStrLn (usageInfo (header prog) options) | Version`elem`o -> putStrLn (unwords [prog, version]) | otherwise -> mapM_ (\input -> do importMusicXML input) n (_,_,errs) -> putStrLn (unlines errs ++ usageInfo (header prog) options) \end{code} \begin{nocode} -- | main :: IO () main = do argv <- getArgs prog <- getProgName curdir <- getCurrentDirectory case getOpt Permute options' argv of (o,n,[]) | Help'`elem`o -> putStrLn (usageInfo (header prog) options') | Version'`elem`o -> putStrLn (unwords [prog, version]) | Check`elem`o -> mapM_ (maybe (return ()) (either (procScriptFile True) setCurrentDirectory) . parseOptions) (o ++ map Input' n) >> setCurrentDirectory curdir | otherwise -> mapM_ (maybe (return ()) (either (procScriptFile False) setCurrentDirectory) . parseOptions) (o ++ map Input' n) >> setCurrentDirectory curdir (_,_,errs) -> putStrLn (unlines errs ++ usageInfo (header prog) options') \end{nocode}