module Full where -- Used modules from the console-program package. import System.Console.Command (Commands,Tree(Node),Command(..),execute,showUsage,io) 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 myCommands = Node (Command "count" "A program for counting" . io $ putStrLn "No command given; try \"count help\".") [ Node countUp [] , Node countDown [] , Node help [] ] countUp,countDown,help :: Command countUp = Command { name = "up" , description = "Count up" , action = withOption verboseOpt $ \ v -> io $ if v == Quiet then putStrLn "Counting quietly!" else mapM_ print [1 ..] } countDown = Command { name = "down" , description = "Count down from INT." , action = withNonOption Argument.natural $ \ upperBound -> io $ mapM_ print [upperBound, pred upperBound .. 1] } help = Command "help" "Show usage info" $ io (showUsage myCommands) verboseOpt :: Option 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 }