module Full where -- The example of using System.Console.Options. import Options -- Used modules from the console-program package. import System.Console.Command (Commands,Command(..),execute,showUsage) import qualified System.Console.Action as Action import qualified System.Console.Argument as Argument -- Standard tree type, used to build the tree of commands. import Data.Tree (Tree(Node)) main :: IO () main = execute defaults myCommands myCommands :: Commands MyConfig myCommands = Node (Command "count" [] [] "A program for counting" . Action.simple $ putStrLn "No command given; try \"count help\".") [ Node countUp [] , Node countDown [] , Node help [] ] countUp,countDown,help :: Command MyConfig countUp = Command { name = "up" , applicableNonOptions = [] , applicableOptions = [verboseOpt] , description = "Count up" , action = Action.usingConfiguration $ \ myConfig -> Action.simple $ if verbosity_ myConfig == Quiet then putStrLn "Counting quietly!" else mapM_ print [1 ..] } countDown = Command { name = "down" , description = "Count down from INT." , applicableNonOptions = ["INT"] , applicableOptions = [] , action = Action.withArgument Argument.natural $ \ upperBound -> Action.simple $ mapM_ print [upperBound, pred upperBound .. 1] } help = Command "help" [] [] "Show usage info" $ Action.simple (showUsage myCommands) verboseOpt = Argument.option Verbosity ['v'] ["verbose" ] verbosity "Specify the verbosity of the program; " verbosity :: Argument.Type Verbosity verbosity = Argument.Type { Argument.parser = \ x -> case x of "verbose" -> Right Verbose "normal" -> Right Normal "quiet" -> Right Quiet s -> Left $ "The argument " ++ show s ++ " could not be recognised as a verbosity." , Argument.name = "verbosity" , Argument.defaultValue = Just Verbose }