Copyright | (c) Erick Gonzalez 2017-2018 |
---|---|
License | BSD3 |
Maintainer | erick@codemonkeylabs.de |
Safe Haskell | None |
Language | Haskell2010 |
This module provides the tools to build a complete "structured" CLI application, similar to those found in systems like Cisco IOS or console configuration utilities etc. It aims to be easy for implementors to use.
Synopsis
- data Action
- data CLIException
- type Commands = CommandsT IO
- data CommandsT m a
- type Handler m = String -> m Action
- data Node m
- type Parser m = Node m -> String -> m ParseResult
- data ParseResult
- = Done { }
- | Partial {
- getPartialHints :: [(String, String)]
- getPartialRemaining :: String
- | Fail { }
- | NoMatch
- data Settings m = Settings {
- getHistory :: Maybe FilePath
- getBanner :: String
- getPrompt :: String
- isBatch :: Bool
- handleException :: ExceptionHandler m
- type Validator m = String -> m (Maybe String)
- (>+) :: Monad m => CommandsT m () -> CommandsT m () -> CommandsT m ()
- command :: Monad m => String -> String -> m Action -> CommandsT m ()
- command' :: Monad m => String -> String -> m Bool -> m Action -> CommandsT m ()
- custom :: Monad m => String -> String -> Parser m -> m Bool -> Handler m -> CommandsT m ()
- exit :: Monad m => m Action
- isCompleted :: Monad m => SearchResult m -> Bool
- isIncomplete :: Monad m => SearchResult m -> Bool
- isNoResult :: Monad m => SearchResult m -> Bool
- labelParser :: Monad m => Node m -> String -> m ParseResult
- newLevel :: Monad m => m Action
- noAction :: Monad m => m Action
- param :: Monad m => String -> String -> Validator m -> Handler m -> CommandsT m ()
- param' :: Monad m => String -> String -> Validator m -> m Bool -> Handler m -> CommandsT m ()
- runCLI :: MonadException m => String -> Settings m -> CommandsT m a -> m (Either CLIException a)
- top :: Monad m => m Action
How to use this module:
It is often the case that a simple example is the best user guide, at least for the experienced programmer. The following code illustrates a basic but functioning CLI application
module Main where import Control.Monad (void) import Control.Monad.IO.Class (liftIO) import Data.Default (def) import System.Console.StructuredCLI root :: Commands () root = do world >+ do hello bye command "exit" "return to previous level" exit world :: Commands () world = command "world" "enter into the world" $ return NewLevel hello :: Commands () hello = command "hello" "prints a greeting" $ do liftIO . putStrLn $ "Hello world!" return NoAction bye :: Commands () bye = command "bye" "say goodbye" $ do liftIO . putStrLn $ "Sayonara!" return NoAction main :: IO () main = void $ runCLI "Hello CLI" def root
resulting example CLI session:
>>>
Hello CLI > ?
- world: enter into the world
>>>
Hello CLI > world
>>>
Hello CLI world > ?
- exit: return to previous level - bye: say goodbye - hello: prints a greeting
>>>
Hello CLI world > hello
Hello world!>>>
Hello CLI world > bye
Sayonara!>>>
Hello CLI world > exit
>>>
Hello CLI >
A good way to get you started is to grab the example code available under example/Main.hs and modify it to suit your needs.
An Action
is returned as the result of a command handler provided by the user and
it instructs the CLI of any changes in the CLI state
data CLIException Source #
Exit | |
InternalError String | |
SyntaxError String | |
UndecisiveInput String [String] | |
HelpRequested [(String, String)] | |
InvalidOperation String |
Instances
Show CLIException Source # | |
Defined in System.Console.StructuredCLI showsPrec :: Int -> CLIException -> ShowS # show :: CLIException -> String # showList :: [CLIException] -> ShowS # |
type Commands = CommandsT IO Source #
An alias type for the case where CommandsT wraps IO only (i.e. no state, etc)
The CommandsT
transformer monad is the key to building a CLI tree. It is meant to
be used as a transformer wrapping an application specific "user" monad (for example, a State
monad encapsulating application state). This monad is executed _once_ upon calling runCLI
to build the command tree. Keep in mind however that any parsers or actions used in
any given command all run in the "user" monad and unlike the process of building the command
tree, they will be called multiple times as the user navigates the CLI at runtime.
Each CommandsT
monadic action corresponds to a single "node" (a.k.a. command) in the CLI.
Succesive actions simply add commands to the current "level". It is possible to "nest"
a new level to a command by using the '(>+)' operator. When properly indented (see example code
above) it provides a pretty self explanatory way to build the CLI tree.
Instances
MonadTrans CommandsT Source # | |
Defined in System.Console.StructuredCLI | |
Monad m => Monad (CommandsT m) Source # | |
Functor f => Functor (CommandsT f) Source # | |
Applicative a => Applicative (CommandsT a) Source # | |
Defined in System.Console.StructuredCLI | |
MonadIO m => MonadIO (CommandsT m) Source # | |
Defined in System.Console.StructuredCLI |
The Node
type contains the internal representation of a command. Normally there is no
need to be concerned with it other than perhaps passing it opaquely to any utility parsers
(like labelParser
for example), when writing a custom parser
data ParseResult Source #
There is no need to concern oneself with the ParseResult
type unless one is writing
a custom parser, which should actually be rarer than not.
Done | |
| |
Partial | |
| |
Fail | |
| |
NoMatch | Parsing provided input doesnt match this command. The difference between |
Instances
Show ParseResult Source # | |
Defined in System.Console.StructuredCLI showsPrec :: Int -> ParseResult -> ShowS # show :: ParseResult -> String # showList :: [ParseResult] -> ShowS # | |
Monad m => Default (Parser m) Source # | |
Defined in System.Console.StructuredCLI |
Settings | CLI Settings provided upon launching the CLI. It is recommended to modify
the settings provided by the |
|
type Validator m = String -> m (Maybe String) Source #
A Validator
is a function to which a parsed string is given in order to perform
any checks for validity that may be applicable, or even transforming the argument if
necessary. Note that the validator runs in the "user" monad
(>+) :: Monad m => CommandsT m () -> CommandsT m () -> CommandsT m () Source #
the CommandsT "nest" operation. It adds a new deeper CLI level to the command on the left
side with the commands on the right side, for example:
activate >+ do
foo
bar
baz
Would result in the following CLI command structure:
>>>
> activate
>>>
activate > ?
>>>
- foo ..
>>>
- bar ..
>>>
- baz ..
:: Monad m | |
=> String | Command keyword |
-> String | Help text for this command |
-> m Action | Action in the "user" monad (i.e. |
-> CommandsT m () |
Build a command node that is always active and takes no parameters
:: Monad m | |
=> String | Command keyword |
-> String | Help text for this command |
-> m Bool | Enable action in the "user" monad |
-> m Action | Action in the "user" monad (i.e. |
-> CommandsT m () |
A variation of command
that allows for "disabling" the command at runtime by
running the given "enable" monadic action (as always in the "user" monad) to check
if the command should be displayed as an option and/or accepted or not.
:: Monad m | |
=> String | Command keyword |
-> String | Help text for this command |
-> Parser m | Custom parser (runs in the "user" monad) |
-> m Bool | Enable action in the "user" monad |
-> Handler m | Handling action. Takes the validator output as argument |
-> CommandsT m () |
Create a command using a custom parser, providing thus complete flexibility
exit :: Monad m => m Action Source #
A utility action to "leave" the current CLI level. Equivalent to return $ LevelUp 1
isCompleted :: Monad m => SearchResult m -> Bool Source #
isIncomplete :: Monad m => SearchResult m -> Bool Source #
isNoResult :: Monad m => SearchResult m -> Bool Source #
labelParser :: Monad m => Node m -> String -> m ParseResult Source #
A utility parser that reads an input and parses a command label. It can be used as part of custom parsers to first read the command keyword before parsing any arguments etc.
newLevel :: Monad m => m Action Source #
A utility action to "nest" into a new CLI level. Equivalent to return NewLevel
noAction :: Monad m => m Action Source #
A utility action to leave the current CLI level untouched. Equivalent to return NoAction
:: Monad m | |
=> String | Command keyword |
-> String | Help text for this command (including argument description) |
-> Validator m | Monadic validator (in the "user" monad) |
-> Handler m | Handling action. Takes the validator output as argument |
-> CommandsT m () |
Build a command node that takes one parameter (delimited by space). The parsed parameter is fed to the validator monadic function (in the "user" monad) and the resulting string if any is fed in turn as an argument to the handler action (also in the "user" monad).
:: Monad m | |
=> String | Command keyword |
-> String | Help text for this command (including argument description) |
-> Validator m | Monadic validator (in the "user" monad) |
-> m Bool | Enable action in the "user" monad |
-> Handler m | Handling action. Takes the validator output as argument |
-> CommandsT m () |
A variation of param
that allows for "disabling" the command at runtime by
running the given "enable" monadic action (as always in the "user" monad) to check
if the command should be displayed as an option and/or accepted or not.
runCLI :: MonadException m => String -> Settings m -> CommandsT m a -> m (Either CLIException a) Source #
top :: Monad m => m Action Source #
A utility action to reset the CLI tree to the root node . Equivalent to return ToRoot