{-# LANGUAGE CPP #-} {- Copyright (C) 2010 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] * Contains the entry-point of the application. * Processes the command-line arguments. -} module Main( -- * Type-classes -- CommandLineAction, -- * Functions main ) where import Control.Applicative((<*>), (<$>)) import qualified Control.Exception import qualified Data.List import qualified Distribution.Package import qualified Distribution.Text import qualified Distribution.Version import qualified Squeeze.CommandOptions as CommandOptions import qualified Squeeze.File as File import qualified Squeeze.FileCombination as FileCombination import qualified Squeeze.Squeeze as Squeeze import qualified Squeeze.QC as QC import qualified System import qualified System.Console.GetOpt as G import qualified System.IO import qualified System.IO.Error import qualified Test.QuickCheck import qualified ToolShed.Defaultable as Defaultable -- | Used to thread user-defined command-line options, though the list of functions which implement them. type CommandLineAction = (CommandOptions.CommandOptions -> IO CommandOptions.CommandOptions) --Supplied as the type-argument to 'G.OptDescr'. {- | * Parses the command-line arguments, to determine 'CommandOptions.CommandOptions', some of which may over-ride the 'Defaultable.defaultValue'. * Arguments following known 'CommandOptions.CommandOptions', are interpreted as file-names to consider when attempting to find a suitable fit for the specified space-constraints. * If the specified file-name is @-@, then 'System.IO.stdin' is read, to augment other non-options specified. * Delegates the donkey-work to 'Squeeze.squeeze', then formats & prints the resulting list of candidate solutions, each at least as good as the last. -} main :: IO () main = do progName <- System.getProgName args <- System.getArgs let usage :: String usage = "Usage:\t" ++ G.usageInfo progName optDescrList ++ " [, ...]\n\nExamples:\n\t" ++ progName ++ " -M 700000000 *.ogg\t\t#Find the best-fit for the globbed file-names, into the space available on a CD.\n\t" ++ progName ++ " Directory/ *.avi +RTS -N -H100M\t#Find the best-fit, for an atomic directory & the globbed files, into the default space, (ie that available on a DVD), using multiple cores, with extra heap pre-allocated." optDescrList :: [G.OptDescr CommandLineAction] optDescrList = [ -- String [String] (G.ArgDescr CommandLineAction) String G.Option "b" ["bisectionRatio"] (setBisectionRatio `G.ReqArg` "") ("To facilitate parallelization, the file-list is bisected at LHS/Total, and combinations from the LHS are concatenated in parallel with each of those from the RHS; default '" ++ show (CommandOptions.bisectionRatio Defaultable.defaultValue) ++ "'. Requires runtime-flags '+RTS -N -H100M -RTS'."), G.Option "M" ["maximumBytes"] (setMaximumBytes `G.ReqArg` "") ("The maximum bytes of available space; default '" ++ show (CommandOptions.maximumBytes Defaultable.defaultValue) ++ "'."), G.Option "m" ["minimumUsageRatio"] (setMinimumUsageRatio `G.ReqArg` "") ("The minimum acceptable space usage-ratio; default '" ++ show (CommandOptions.minimumUsageRatio Defaultable.defaultValue) ++ "'."), G.Option "q" ["runQuickChecks"] (G.NoArg runQuickChecks) "Run Quick-checks using arbitrary data & then exit. Specify '--verbose' before this option, for detailed output.", G.Option "v" ["verbose"] (G.NoArg $ return . CommandOptions.setVerbose) "Produce additional explanatory output where appropriate.", G.Option "" ["version"] (G.NoArg $ const printVersion) "Print version-information & then exit.", G.Option "?" ["help"] (G.NoArg $ const printUsage) "Display this help & then exit." ] where setBisectionRatio, setMaximumBytes, setMinimumUsageRatio :: String -> CommandLineAction setBisectionRatio arg commandLineArgs | ratio < 0.0 = Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.illegalOperationErrorType ("bisectionRatio='" ++ arg ++ "' must be >= 0.0") Nothing Nothing | ratio > 1.0 = Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.illegalOperationErrorType ("bisectionRatio='" ++ arg ++ "' must be <= 1.0") Nothing Nothing | otherwise = return {-to IO-monad-} commandLineArgs {CommandOptions.bisectionRatio = ratio} where ratio = read arg setMaximumBytes arg commandLineArgs | bytes <= 0 = Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.illegalOperationErrorType ("maximumBytes='" ++ arg ++ "' must be > 0") Nothing Nothing | otherwise = return {-to IO-monad-} commandLineArgs {CommandOptions.maximumBytes = bytes} where bytes = read arg setMinimumUsageRatio arg commandLineArgs | ratio < 0.0 = Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.illegalOperationErrorType ("minimumUsageRatio='" ++ arg ++ "' must be >= 0.0") Nothing Nothing | ratio > 1.0 = Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.illegalOperationErrorType ("minimumUsageRatio='" ++ arg ++ "' must be <= 1.0") Nothing Nothing | otherwise = return {-to IO-monad-} commandLineArgs {CommandOptions.minimumUsageRatio = ratio} where ratio = read arg runQuickChecks :: CommandOptions.CommandOptions -> IO CommandOptions.CommandOptions runQuickChecks commandOptions = QC.quickChecks ( if CommandOptions.verbose commandOptions then #if MIN_VERSION_QuickCheck(2,4,0) Test.QuickCheck.verboseCheck #else error "'Test.QuickCheck.verboseCheck' is only available as of 'QuickCheck-2.4'." #endif else Test.QuickCheck.quickCheck ) >> System.exitWith System.ExitSuccess printVersion, printUsage :: IO CommandOptions.CommandOptions printVersion = System.IO.hPutStrLn System.IO.stderr (Distribution.Text.display packageIdentifier ++ "\n\nCopyright (C) 2010 Dr. Alistair Ward.\nThis program comes with ABSOLUTELY NO WARRANTY.\nThis is free software, and you are welcome to redistribute it under certain conditions.\n\nWritten by Dr. Alistair Ward.") >> System.exitWith System.ExitSuccess where packageIdentifier :: Distribution.Package.PackageIdentifier packageIdentifier = Distribution.Package.PackageIdentifier { Distribution.Package.pkgName = Distribution.Package.PackageName "squeeze", Distribution.Package.pkgVersion = Distribution.Version.Version [1, 0, 1, 4] [] } printUsage = System.IO.hPutStrLn System.IO.stderr usage >> System.exitWith System.ExitSuccess -- G.getOpt :: G.ArgOrder CommandLineAction -> [G.OptDescr CommandLineAction] -> [String] -> ([CommandLineAction], [String], [String]) case G.getOpt G.RequireOrder optDescrList args of (commandLineActions, nonOptions, [{-errors-}]) -> do commandOptions <- Data.List.foldl' (>>=) ( return {-to IO-monad-} Defaultable.defaultValue ) {-transform using CommandLineAction-mutators-} commandLineActions --ie: do o1 <- CommandLineAction[0] commandOptions[0]; o2 <- CommandLineAction[1] o1; ... mapM_ (putStrLn . (`FileCombination.showFileCombination` "")) =<< Squeeze.squeeze commandOptions =<< if null nonOptions then Control.Exception.throw $ System.IO.Error.mkIOError System.IO.Error.doesNotExistErrorType "No files specified" Nothing Nothing else {-files specified-} if "-" `elem` nonOptions then let getFilePaths :: IO File.FilePathList getFilePaths = do eof <- System.IO.isEOF if eof then return {-to IO-monad-} [] else {-more to read-} (:) <$> getLine <*> getFilePaths {-recurse-} in (filter (/= "-") nonOptions ++) <$> getFilePaths else {-real fileNames-} return {-to IO-monad-} nonOptions (_, _, errors) -> System.IO.Error.ioError . System.IO.Error.userError $ concatMap init {-chop-} errors