{- 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 to the program. * Provides command-line access to "ExtendedRegExChar". * Defines the permissible command-line arguments; aping /egrep/, but with the addition of /--verbose/, which enables one to see the details of the data-capture. [@TODO@] Coordinate the output of 'printVersion' with the definition in '.cabal'; this may not be feasible. -} module Main( -- * Type-classes -- CommandLineAction, -- * Functions -- $main main --Added for Haskell style scanner, 'scan-0.1.0.5'. ) where import Control.Applicative((<$>)) import qualified Data.List import qualified Distribution.Package import qualified Distribution.Text import qualified Distribution.Version import qualified Grecce.Assert.RegExOptsChar as Assert.RegExOptsChar import qualified Grecce.CommandOptions as CommandOptions import qualified Grecce.Grep as Grep import qualified Grecce.Performance.ExtendedRegEx as Performance.ExtendedRegEx import qualified Grecce.Performance.ExtendedRegExTestsNegative as Performance.ExtendedRegExTestsNegative import qualified Grecce.Performance.ExtendedRegExTestsPositive as Performance.ExtendedRegExTestsPositive import qualified Grecce.QC.QuickChecks as QC.QuickChecks import qualified RegExDot.CompilationOptions as CompilationOptions import qualified RegExDot.ExecutionOptions as ExecutionOptions import qualified System import qualified System.Console.GetOpt as G import qualified System.IO import qualified System.IO.Error 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'. * Arguments following 'CommandOptions.CommandOptions', are interpreted as a /regex/, followed by the names of the files to which it is applied. -} main :: IO () main = do progName <- System.getProgName args <- System.getArgs let usage :: String usage = "Usage:\t" ++ G.usageInfo progName optDescrList ++ " [, ...]" --Define the command-line options, & the 'CommandLineAction's used to handle them. optDescrList :: [G.OptDescr CommandLineAction] optDescrList = [ -- String [String] (G.ArgDescr CommandLineAction) String G.Option "e" ["regex"] (setExtendedRegExChar `G.ReqArg` "") "Input:\tdefine the regex.", G.Option "f" ["file"] (readExtendedRegExCharFromFile `G.ReqArg` "") "Input:\tread the regex from file.", G.Option "c" ["count"] (G.NoArg $ return {-to IO-monad-} . CommandOptions.setCountMatches) ("Output:\tprint only a count of matching lines per file; default '" ++ show (CommandOptions.countMatches Defaultable.defaultValue) ++ "'."), G.Option "l" ["files-with-matches"] (G.NoArg $ return {-to IO-monad-} . CommandOptions.setListFilesWithMatches) ("Output:\tlist names of files containing at least one match; default '" ++ show (CommandOptions.listFilesWithMatches Defaultable.defaultValue) ++ "'."), G.Option "L" ["files-without-match"] (G.NoArg $ return {-to IO-monad-} . CommandOptions.setListFilesWithoutMatch) ("Output:\tlist names of files not containing any matches; default '" ++ show (CommandOptions.listFilesWithoutMatch Defaultable.defaultValue) ++ "'."), G.Option "n" ["number"] (G.NoArg $ return {-to IO-monad-} . CommandOptions.setPrependLineNumbers) ("Output:\tprepend the line-number of the input, to the output; default '" ++ show (CommandOptions.prependLineNumbers Defaultable.defaultValue) ++ "'."), G.Option "v" ["invert-match"] (G.NoArg $ return {-to IO-monad-} . CommandOptions.setInvertMatch) ("Output:\tselect non-matching lines; default '" ++ show (CommandOptions.invertMatch Defaultable.defaultValue) ++ "'."), G.Option "" ["version"] (G.NoArg $ const printVersion) "Output:\tprint version-information & then exit.", G.Option "?" ["help"] (G.NoArg $ const printUsage) "Output:\tdisplay this help-text & then exit.", G.Option "" ["printCurrentSettings"] (G.NoArg printCurrentSettings) "Output:\tdisplay the currently defined options & then exit.", G.Option "" ["verbose"] (G.NoArg $ return {-to IO-monad-} . CommandOptions.setVerbose) ("Output:\tsee how the input data was captured by the RegEx; default '" ++ show (CommandOptions.verbose Defaultable.defaultValue) ++ "'."), G.Option "" ["performance"] ( extendedRegExCharPerformance `G.ReqArg` "(Int,Either [TestName])" ) ( "Test:\tcompare performance with other RegEx-engines, using the specified pair (, Left " ++ show [ minBound :: Performance.ExtendedRegExTestsNegative.TestName .. maxBound ] ++ " or Right " ++ show [ minBound :: Performance.ExtendedRegExTestsPositive.TestName .. maxBound ] ++ "). NB: specify this option last." ), G.Option "" ["runQuickChecks"] (G.NoArg runQuickChecks) "Test:\trun Quick-checks using arbitrary data & then exit. Specify 'verbose' before this option, for detailed output.", G.Option "" ["assert"] (assertFromFile `G.ReqArg` "") "Test:\trun the assertions, defined in the specified file, & then exit. NB: specify this option last.", G.Option "" ["assertPosix"] (assertPosixFromFile `G.ReqArg` "") "Test:\trun the assertions, defined in the specified file, against Text.Regex.Posix, & then exit. NB: specify this option last.", G.Option "" ["abortTrialRepetitionsOnInherentFailure"] (setExecutionOption abortTrialRepetitionsOnInherentFailure `G.ReqArg` "Bool") ("Performance:\tif an alternative can't match, irrespective of the subsequent concatenation, then terminate futile trial repetitions; default '" ++ show (ExecutionOptions.abortTrialRepetitionsOnInherentFailure Defaultable.defaultValue) ++ "'."), -- G.Option "" ["abortTrialRepetitionsOnZeroConsumption"] (setExecutionOption abortTrialRepetitionsOnZeroConsumption `G.ReqArg` "Bool") ("Performance:\tcheck for zero data-consumption by the n-th repetition of an alternative, before considering (n + 1); default '" ++ show (ExecutionOptions.abortTrialRepetitionsOnZeroConsumption Defaultable.defaultValue) ++ "'."), -- G.Option "" ["bypassInputDataForLiberalConsumer"] (setExecutionOption bypassInputDataForLiberalConsumer `G.ReqArg` "Bool") ("Performance:\tbypass reading of the unconsumed input data, if the remaining RegEx can consume a sufficient quantity of anything; default '" ++ show (ExecutionOptions.bypassInputDataForLiberalConsumer Defaultable.defaultValue) ++ "'."), G.Option "" ["catchIncompatibleAnchors"] (setExecutionOption catchIncompatibleAnchors `G.ReqArg` "Bool") ("Performance:\tavoid futile trial solutions, involving repetitions of anchored alternatives, which must consume data; default '" ++ show (ExecutionOptions.catchIncompatibleAnchors Defaultable.defaultValue) ++ "'."), G.Option "" ["checkExistenceOfInelasticTail"] (setExecutionOption checkExistenceOfInelasticTail `G.ReqArg` "Bool") ("Performance:\tif the regex ends in one or more Meta-data, whose repetition-range is precisely defined, check that this sequence exists at the end of the input data; default '" ++ show (ExecutionOptions.checkExistenceOfInelasticTail Defaultable.defaultValue) ++ "'."), G.Option "" ["checkForUnconsumableData"] (setExecutionOption checkForUnconsumableData `G.ReqArg` "Bool") ("Performance:\tcheck whether there's no possibility of consuming some of the input data; default '" ++ show (ExecutionOptions.checkForUnconsumableData Defaultable.defaultValue) ++ "'."), G.Option "" ["complyStrictlyWithPosix"] (setCompilationOption complyStrictlyWithPosix `G.ReqArg` "Bool") ("Output:\tdefine the offset of captured data, corresponding to a sub-expression which matched zero times, as the artificial value -1 specified by Posix; currently only affects results of 'assert'; default '" ++ show (CompilationOptions.complyStrictlyWithPosix Defaultable.defaultValue) ++ "'."), G.Option "" ["moderateGreed"] (setExecutionOption moderateGreed `G.ReqArg` "Bool") ("Performance:\tgreedily consume data, only up to the limit beyond which, future requirements would be compromised; default '" ++ show (ExecutionOptions.moderateGreed Defaultable.defaultValue) ++ "'."), G.Option "" ["permitReorderingOfAlternatives"] (setExecutionOption permitReorderingOfAlternatives `G.ReqArg` "Bool") ("Performance:\tpermit alternatives to be re-ordered, in an attempt to process the cheapest first; default '" ++ show (ExecutionOptions.permitReorderingOfAlternatives Defaultable.defaultValue) ++ "'."), G.Option "" ["preferAlternativesWhichFeedTheGreedy"] (setExecutionOption preferAlternativesWhichFeedTheGreedy `G.ReqArg` "Bool") ("Preference:\tprefer solutions in which the choice of alternatives directs data from non-greedy to greedy consumers; default '" ++ show (ExecutionOptions.preferAlternativesWhichFeedTheGreedy Defaultable.defaultValue) ++ "'."), G.Option "" ["preferAlternativesWhichMimickUnrolling"] (setExecutionOption preferAlternativesWhichMimickUnrolling `G.ReqArg` "Bool") ("Preference:\tprefer solutions in which the choice of alternatives consumes data like the unrolled repeatable group; default '" ++ show (ExecutionOptions.preferAlternativesWhichMimickUnrolling Defaultable.defaultValue) ++ "'."), G.Option "" ["preferFewerRepeatedAlternatives"] (setExecutionOption preferFewerRepeatedAlternatives `G.ReqArg` "Bool") ("Preference:\tprefer solutions employing fewer repetitions of alternatives, to discourage the capture of null lists; default '" ++ show (ExecutionOptions.preferFewerRepeatedAlternatives Defaultable.defaultValue) ++ "'."), G.Option "" ["unrollRepeatedSingletonAlternative"] (setExecutionOption unrollRepeatedSingletonAlternative `G.ReqArg` "Bool") ("Performance:\tunroll repetitions of singleton alternatives; this doesn't affect the result; default '" ++ show (ExecutionOptions.unrollRepeatedSingletonAlternative Defaultable.defaultValue) ++ "'."), G.Option "" ["useFirstMatchAmongAlternatives"] (setExecutionOption useFirstMatchAmongAlternatives `G.ReqArg` "Bool") ("Performance:\trather than performing an exhaustive search for the optimal choice amongst alternatives, merely select the first that matches; conform to Perl rather than Posix; default '" ++ show (ExecutionOptions.useFirstMatchAmongAlternatives Defaultable.defaultValue) ++ "'."), G.Option "" ["validateMinConsumptionOfAlternatives"] (setExecutionOption validateMinConsumptionOfAlternatives `G.ReqArg` "Bool") ("Performance:\twhen the number of repetitions of a group of alternatives is precisely specified, check the availability of the resulting minimum data-requirement; default '" ++ show (ExecutionOptions.validateMinConsumptionOfAlternatives Defaultable.defaultValue) ++ "'.") ] where 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 "grecce", Distribution.Package.pkgVersion = Distribution.Version.Version [0, 9, 0, 7] [] } printUsage = System.IO.hPutStrLn System.IO.stderr usage >> System.exitWith System.ExitSuccess printCurrentSettings, runQuickChecks :: CommandLineAction printCurrentSettings commandOptions = print commandOptions >> System.exitWith System.ExitSuccess runQuickChecks commandOptions = QC.QuickChecks.run (CommandOptions.verbose commandOptions) >> System.exitWith System.ExitSuccess extendedRegExCharPerformance, readExtendedRegExCharFromFile, assertFromFile, assertPosixFromFile, setExtendedRegExChar :: String -> CommandLineAction extendedRegExCharPerformance s commandOptions = ( uncurry $ Performance.ExtendedRegEx.run (CommandOptions.executionOptions commandOptions) ) (read s) >> System.exitWith System.ExitSuccess readExtendedRegExCharFromFile s commandOptions = (head . dropWhile null . lines <$> readFile s) >>= (`setExtendedRegExChar` commandOptions) assertFromFile fileName commandOptions = do failedTests <- Assert.RegExOptsChar.findFailures (CommandOptions.compilationOptions commandOptions) (CommandOptions.executionOptions commandOptions) <$> Assert.RegExOptsChar.readTests fileName if null failedTests then System.exitWith System.ExitSuccess else do mapM_ print failedTests System.exitWith $ System.ExitFailure 2 assertPosixFromFile fileName _ = do failedTests <- Assert.RegExOptsChar.findFailuresPosix <$> Assert.RegExOptsChar.readTests fileName if null failedTests then System.exitWith System.ExitSuccess else do mapM_ print failedTests System.exitWith $ System.ExitFailure 2 setExtendedRegExChar s commandOptions = case CommandOptions.extendedRegExChar commandOptions of Just e -> error $ "'" ++ show e ++ "' has already been defined" _ -> return {-to IO-monad-} commandOptions { CommandOptions.extendedRegExChar = Just $ read s } abortTrialRepetitionsOnInherentFailure, {-abortTrialRepetitionsOnZeroConsumption, bypassInputDataForLiberalConsumer,-} catchIncompatibleAnchors, checkExistenceOfInelasticTail, checkForUnconsumableData, moderateGreed, permitReorderingOfAlternatives, preferAlternativesWhichFeedTheGreedy, preferAlternativesWhichMimickUnrolling, preferFewerRepeatedAlternatives, unrollRepeatedSingletonAlternative, useFirstMatchAmongAlternatives, validateMinConsumptionOfAlternatives :: CommandOptions.ExecutionOptionsMutator abortTrialRepetitionsOnInherentFailure s e = e { ExecutionOptions.abortTrialRepetitionsOnInherentFailure = read s } -- abortTrialRepetitionsOnZeroConsumption s e = e { ExecutionOptions.abortTrialRepetitionsOnZeroConsumption = read s } -- bypassInputDataForLiberalConsumer s e = e { ExecutionOptions.bypassInputDataForLiberalConsumer = read s } catchIncompatibleAnchors s e = e { ExecutionOptions.catchIncompatibleAnchors = read s } checkExistenceOfInelasticTail s e = e { ExecutionOptions.checkExistenceOfInelasticTail = read s } checkForUnconsumableData s e = e { ExecutionOptions.checkForUnconsumableData = read s } moderateGreed s e = e { ExecutionOptions.moderateGreed = read s } permitReorderingOfAlternatives s e = e { ExecutionOptions.permitReorderingOfAlternatives = read s } preferAlternativesWhichFeedTheGreedy s e = e { ExecutionOptions.preferAlternativesWhichFeedTheGreedy = read s } preferAlternativesWhichMimickUnrolling s e = e { ExecutionOptions.preferAlternativesWhichMimickUnrolling = read s } preferFewerRepeatedAlternatives s e = e { ExecutionOptions.preferFewerRepeatedAlternatives = read s } unrollRepeatedSingletonAlternative s e = e { ExecutionOptions.unrollRepeatedSingletonAlternative = read s } useFirstMatchAmongAlternatives s e = e { ExecutionOptions.useFirstMatchAmongAlternatives = read s } validateMinConsumptionOfAlternatives s e = e { ExecutionOptions.validateMinConsumptionOfAlternatives = read s } complyStrictlyWithPosix :: CommandOptions.CompilationOptionsMutator complyStrictlyWithPosix s e = e { CompilationOptions.complyStrictlyWithPosix = read s } setCompilationOption :: CommandOptions.CompilationOptionsMutator -> String -> CommandLineAction setCompilationOption compilationOptionsMutator s = return {-to IO-monad-} . CommandOptions.setCompilationOption compilationOptionsMutator s setExecutionOption :: CommandOptions.ExecutionOptionsMutator -> String -> CommandLineAction setExecutionOption executionOptionsMutator s = return {-to IO-monad-} . CommandOptions.setExecutionOption executionOptionsMutator s -- G.getOpt :: G.ArgOrder CommandLineAction -> [G.OptDescr Action] -> [String] -> ([Action], [String], [String]) case G.getOpt G.RequireOrder optDescrList args of (commandLineActions, nonOptions, []) -> do commandOptions <- Data.List.foldl' (>>=) (return {-to IO-monad-} Defaultable.defaultValue) commandLineActions --Sequentially transform the 'CommandOptions', using 'CommandLineAction's corresponding to the specified command-line flags. Grep.grep commandOptions nonOptions --Perform the requested match, against the list of input-data files. (_, _, errors) -> System.IO.Error.ioError . System.IO.Error.userError $ concat errors ++ usage --Throw.