{-# 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 -- CommandOptions', -- CommandLineAction, -- * Functions main ) where import Control.Applicative((<*>), (<$>)) import qualified Data.List import qualified Data.Ratio import qualified Distribution.Package import qualified Distribution.Text import qualified Distribution.Version import qualified Factory.Math.Probability as Math.Probability import qualified Squeeze.Data.CommandOptions as Data.CommandOptions import qualified Squeeze.Data.File as Data.File import qualified Squeeze.Squeeze as Squeeze import qualified Squeeze.Test.Performance as Test.Performance import qualified Squeeze.Test.QC as Test.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 import qualified ToolShed.TimeAction as TimeAction import qualified ToolShed.SelfValidate as SelfValidate -- | Coerce the polymorphic data-type to concrete instance, in order that it's fields may be read from the command-line. type CommandOptions' = Data.CommandOptions.CommandOptions Data.Ratio.Rational --'Double' would also be a suitable type-parameter. -- | Used to thread user-defined command-line options, though the list of functions which implement them. type CommandLineAction = (CommandOptions' -> IO CommandOptions') --Supplied as the type-argument to 'G.OptDescr'. {- | * Parses the command-line arguments, to determine 'Data.CommandOptions.CommandOptions', some of which may over-ride the 'Defaultable.defaultValue'. * Any arguments which follow known 'Data.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'. Because this may take an inordinately long time, it prints the results in real time, rather than batching until the optimum has been determined. * If /verbose/ has been specified, prints the CPU-time used, -} 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." defaultValue :: CommandOptions' defaultValue = Defaultable.defaultValue optDescrList :: [G.OptDescr CommandLineAction] optDescrList = [ -- String [String] (G.ArgDescr CommandLineAction) String G.Option "b" ["bisectionRatio"] (setBisectionRatio `G.ReqArg` "") ("The file-list is bisected at LHS/Total, & combinations from the LHS, concatenated with each of those from the RHS; default '" ++ show (Data.CommandOptions.bisectionRatio defaultValue) ++ "'."), G.Option "M" ["maximumBytes"] (setMaximumBytes `G.ReqArg` "") ("The maximum bytes of available space; default '" ++ show (Data.CommandOptions.maximumBytes defaultValue) ++ "'."), G.Option "m" ["minimumUsageRatio"] (setMinimumUsageRatio `G.ReqArg` "") ("The minimum acceptable space usage-ratio; default '" ++ show (Data.CommandOptions.minimumUsageRatio defaultValue) ++ "'."), G.Option "q" ["runQuickChecks"] (G.NoArg runQuickChecks) "Run Quick-checks using arbitrary data & then exit.", G.Option "" ["testPerformance"] ( testPerformance `G.ReqArg` "(, )" ) "Test the performance, using the specified number of randomly generated virtual files, the size of which conform to the specified probability-distribution; then exit.", G.Option "" ["graphPerformance"] ( graphPerformance `G.ReqArg` "" ) "Graph the performance, against a linearly increasing number of randomly generated virtual files, the size of which conform to the specified probability-distribution. Doesn't normally terminate.", G.Option "v" ["verbose"] (G.NoArg $ return . Data.CommandOptions.setVerbose) "Produce additional explanatory output where appropriate. CAVEAT: should precede other options.", 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, testPerformance, graphPerformance :: String -> CommandLineAction setBisectionRatio arg commandOptions = return {-to IO-monad-} commandOptions {Data.CommandOptions.bisectionRatio = read arg} setMaximumBytes arg commandOptions = return {-to IO-monad-} commandOptions {Data.CommandOptions.maximumBytes = read arg} setMinimumUsageRatio arg commandOptions = return {-to IO-monad-} commandOptions {Data.CommandOptions.minimumUsageRatio = read arg} testPerformance arg commandOptions = if not $ SelfValidate.isValid commandOptions then error $ "Invalid " ++ show commandOptions else do TimeAction.printCPUSeconds $ Test.Performance.run commandOptions fileCount probabilityDistribution >>= mapM_ print System.exitWith System.ExitSuccess where fileCount :: Int probabilityDistribution :: Math.Probability.DiscreteDistribution Double (fileCount, probabilityDistribution) = read arg graphPerformance arg commandOptions = if not $ SelfValidate.isValid commandOptions then error $ "Invalid " ++ show commandOptions else do mapM_ (\fileCount -> TimeAction.printCPUSeconds $ Test.Performance.run commandOptions fileCount probabilityDistribution >>= mapM_ print) [1 ..] System.exitWith $ System.ExitFailure 1 where probabilityDistribution :: Math.Probability.DiscreteDistribution Double probabilityDistribution = read arg runQuickChecks :: (Num f, Ord f) => Data.CommandOptions.CommandOptions f -> IO (Data.CommandOptions.CommandOptions f) runQuickChecks commandOptions = if not $ SelfValidate.isValid commandOptions then error $ "Invalid " ++ show commandOptions else do Test.QC.quickChecks $ if Data.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 (Data.CommandOptions.CommandOptions f) 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, 2, 0] [] } 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; ... if not $ SelfValidate.isValid commandOptions then error $ "Invalid " ++ show commandOptions else ( if Data.CommandOptions.verbose commandOptions then TimeAction.printCPUSeconds else id ) $ mapM_ print {-print immediately rather than batching-} =<< Squeeze.squeeze commandOptions =<< if null nonOptions then error "No files specified." else if "-" `elem` nonOptions then let getFilePaths :: IO Data.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