{-# LANGUAGE CPP #-} module Main where import qualified Options.Applicative as O import qualified Data.ByteString as BS import qualified System.IO as IO import Sound.Libcdio import Sound.Libcdio.Read.CdText #if MIN_VERSION_base(4,11,0) #else import Data.Monoid ( (<>) ) #endif import Options.Applicative ( (<|>), (<**>) ) data Options = Options { source :: FilePath , sink :: Maybe FilePath , help :: Bool } deriving ( Eq, Ord, Show, Read ) options :: O.Parser Options options = Options <$> O.strArgument (O.metavar "FILE") <*> output <*> O.switch ( O.long "help" <> O.short 'h' <> O.help "Print this help message" ) output :: O.Parser (Maybe FilePath) output = O.flag' Nothing ( O.long "stdout" <> O.short 'O' <> O.help "Echo the resulting binary blob to stdout" ) <|> Just <$> O.strOption ( O.long "output" <> O.short 'o' <> O.metavar "FILE" <> O.value "cdtext.dat" <> O.help "Where to save the resulting CDTEXT blob" ) description :: O.InfoMod a description = O.fullDesc <> O.progDesc "Generate a binary CDTEXT file from readable data" main :: IO () main = do os <- O.execParser $ O.info (options <**> O.helper) description if help os then putStrLn "TODO: Print the help" else do let write p = case sink os of Just f -> IO.withBinaryFile f IO.WriteMode $ flip BS.hPut p Nothing -> BS.putStr p bs <- open (Just $ source os) False cdTextRaw case bs of Right (Just bs') -> write bs' Right Nothing -> IO.hPutStrLn IO.stderr "No CDTEXT on disc" _ -> IO.hPutStrLn IO.stderr "Unable to open device"