{-# LANGUAGE DeriveDataTypeable #-} -- | The CommandLine module handles parsing of the command-line -- options. It should more or less be a black box, providing Main -- with only the information it requires. -- -- Which is why we're allowed all of this unsafe voodoo. -- module CommandLine ( Args(..), get_args ) where import System.Console.CmdArgs ( Ann, Annotate( (:=) ), Data, Typeable, (+=), auto, cmdArgs_, def, details, explicit, groupname, help, helpArg, modes_, name, program, record, summary, versionArg ) -- Get the version from Cabal. import Paths_hath (version) import Data.Version (showVersion) -- | The name of our program. program_name :: String program_name = "hath" -- | A brief summary; displays the program name and version. my_summary :: String my_summary = program_name ++ "-" ++ (showVersion version) barriers_help :: String barriers_help = "(regexed mode) place barriers in front/back of the regex " ++ "to prevent e.g. '127.0.0.1' from matching '127.0.0.100'" -- | The Args type represents the possible command-line options. The -- duplication here seems necessary; CmdArgs' magic requires us to -- define some things explicitly. -- -- The application currently has six modes (if this number is wrong, -- it means I forgot to update the comment!), all of which take the -- same options and arguments. -- data Args = Regexed { barriers :: Bool } | Reduced { barriers :: Bool } | Duped { barriers :: Bool } | Diffed { barriers :: Bool } | Listed { barriers :: Bool } | Reversed { barriers :: Bool } deriving (Data, Show, Typeable) -- | Description of the 'Regexed' mode. regexed_description :: String regexed_description = "Compute a regular expression matching the input CIDRs." -- | Description of the 'Reduced' mode. reduced_description :: String reduced_description = "Combine any redundant/adjacent CIDR blocks into one." -- | Description of the 'Duped' mode. duped_description :: String duped_description = "Display what would be removed by 'reduced'." -- | Description of the 'Diffed' mode. diffed_description :: String diffed_description = "Display both additions and deletions in a diff-like format." -- | Description of the 'Listed' mode. listed_description :: String listed_description = "Enumerate the IP addresses contained within the input CIDRs." -- | Description of the 'Reversed' mode. reversed_description :: String reversed_description = "Perform a reverse DNS (PTR) lookup on each IP address " ++ "contained within the input CIDRs." -- | We use explicit annotation here because if we use the magic -- annotation, we have to duplicate the same argument definitions six -- times. -- arg_spec :: Annotate Ann arg_spec = modes_ [regexed += auto, reduced, duped, diffed, listed, reversed] += program program_name += summary my_summary += helpArg [explicit, name "help", name "h", groupname "Common flags"] += versionArg [explicit, name "version", name "v", groupname "Common flags"] where make_mode :: (Bool -> Args) -> String -> (Annotate Ann) make_mode ctor desc = record (ctor def) [ barriers := def += groupname "Common flags" += help barriers_help ] += details [" " ++ desc] regexed = make_mode Regexed regexed_description reduced = make_mode Reduced reduced_description duped = make_mode Duped duped_description diffed = make_mode Diffed diffed_description listed = make_mode Listed listed_description reversed = make_mode Reversed reversed_description -- | This is the public interface; i.e. what main() should use to get -- the command-line arguments. get_args :: IO Args get_args = cmdArgs_ arg_spec