commander-cli-0.10.2.0: A command line argument/option parser library
Copyright(c) Samuel Schlesinger 2020
LicenseMIT
Maintainersgschlesinger@gmail.com
Stabilityexperimental
PortabilityPOSIX, Windows
Safe HaskellNone
LanguageHaskell2010

Options.Commander

Description

Commander is an embedded domain specific language describing a command line interface, along with ways to run those as real programs. An complete example of such a command line interface is:

main :: IO ()
main = command_ . toplevel "file" $
 (sub "maybe-read" $
  arg "filename" filename ->
  flag "read" b -> raw $
    if b
      then putStrLn =<< readFile filename
      else pure ())
  <+>
 (sub "maybe-write" $
  opt "file" @"file-to-write" mfilename -> raw $
    case mfilename of
      Just filename -> putStrLn =<< readFile filename
      Nothing -> pure ())

If I run this program with the argument help, it will output:

usage:
name: file
|
+- subprogram: help
|
+- subprogram: maybe-read
|  |
|  `- argument: filename :: [Char]
|     |
|     `- flag: ~read
|
`- subprogram: maybe-write
   |
   `- option: -file :: [Char]

The point of this library is mainly so that you can write command line interfaces quickly and easily, with somewhat useful help messages, and not have to write any boilerplate.

Synopsis

Parsing Arguments and Options

If you want to use a Haskell type as an argument or option, you will need to implement the Unrender class. Your type needs to be Typeable for the sake of generating documentation.

class Typeable t => Unrender t where Source #

A class for interpreting command line arguments into Haskell types.

Methods

unrender :: Text -> Maybe t Source #

Instances

Instances details
Unrender Bool Source # 
Instance details

Defined in Options.Commander

Unrender Char Source # 
Instance details

Defined in Options.Commander

Unrender Int Source # 
Instance details

Defined in Options.Commander

Methods

unrender :: Text -> Maybe Int Source #

Unrender Int8 Source # 
Instance details

Defined in Options.Commander

Unrender Int16 Source # 
Instance details

Defined in Options.Commander

Unrender Int32 Source # 
Instance details

Defined in Options.Commander

Unrender Int64 Source # 
Instance details

Defined in Options.Commander

Unrender Integer Source # 
Instance details

Defined in Options.Commander

Unrender Natural Source # 
Instance details

Defined in Options.Commander

Unrender Word Source # 
Instance details

Defined in Options.Commander

Unrender Word8 Source # 
Instance details

Defined in Options.Commander

Unrender Word16 Source # 
Instance details

Defined in Options.Commander

Unrender Word32 Source # 
Instance details

Defined in Options.Commander

Unrender Word64 Source # 
Instance details

Defined in Options.Commander

Unrender () Source # 
Instance details

Defined in Options.Commander

Methods

unrender :: Text -> Maybe () Source #

Unrender String Source # 
Instance details

Defined in Options.Commander

Unrender ByteString Source # 
Instance details

Defined in Options.Commander

Unrender ByteString Source # 
Instance details

Defined in Options.Commander

Unrender Text Source # 
Instance details

Defined in Options.Commander

(Unrender a, Unrender b) => Unrender (Either a b) Source # 
Instance details

Defined in Options.Commander

Methods

unrender :: Text -> Maybe (Either a b) Source #

Defining CLI Programs

To construct a ProgramT (a specification of a CLI program), you can have arguments, options, raw actions in a monad (typically IO), subprograms, named programs, environment variables, you can combine programs together using <+>, and you can generate primitive usage information with usage. There are combinators for retrieving environment variables as well. We also have a convenience combinator, toplevel, which lets you add a name and a help command to your program using the usage combinator.

arg :: forall name x p m a. KnownSymbol name => (x -> ProgramT p m a) -> ProgramT (Arg name x & p) m a Source #

Environment

Argument combinator

opt :: forall option name x p m a. (KnownSymbol option, KnownSymbol name) => (Maybe x -> ProgramT p m a) -> ProgramT (Opt option name x & p) m a Source #

Option combinator

optDef :: forall option name x p m a. (KnownSymbol option, KnownSymbol name) => x -> (x -> ProgramT p m a) -> ProgramT (Opt option name x & p) m a Source #

Option combinator with default

raw :: forall m a. m a -> ProgramT Raw m a Source #

Raw monadic combinator

sub :: forall s p m a. KnownSymbol s => ProgramT p m a -> ProgramT (s & p) m a Source #

Subcommand combinator

named :: forall s p m a. KnownSymbol s => ProgramT p m a -> ProgramT (Named s & p) m a Source #

Named command combinator, useful at the top level for naming a program. Typically, the name will be the name or alias of the executable you expect to produce.

flag :: forall f p m a. KnownSymbol f => (Bool -> ProgramT p m a) -> ProgramT (Flag f & p) m a Source #

Boolean flag combinator

toplevel :: forall s p m. (HasProgram p, KnownSymbol s, MonadIO m) => ProgramT p m () -> ProgramT (Named s & (("help" & Raw) + p)) m () Source #

A convenience combinator that constructs the program I often want to run out of a program I want to write.

(<+>) :: forall x y m a. ProgramT x m a -> ProgramT y m a -> ProgramT (x + y) m a infixr 2 Source #

The command line program which consists of trying to enter one and then trying the other.

usage :: forall p m. (MonadIO m, HasProgram p) => ProgramT Raw m () Source #

A meta-combinator that takes a type-level description of a command line program and produces a simple usage program.

env :: forall name p x m a. KnownSymbol name => (x -> ProgramT p m a) -> ProgramT (Env 'Required name x & p) m a Source #

Required environment variable combinator

envOpt :: forall name x p m a. KnownSymbol name => (Maybe x -> ProgramT p m a) -> ProgramT (Env 'Optional name x & p) m a Source #

Optional environment variable combinator

envOptDef :: forall name x p m a. KnownSymbol name => x -> (x -> ProgramT p m a) -> ProgramT (Env 'Optional name x & p) m a Source #

Optional environment variable combinator with default

description :: forall description p m a. (HasProgram p, KnownSymbol description) => ProgramT p m a -> ProgramT (Description description & p) m a Source #

A combinator which takes a program, and a type-level Symbol description of that program, and produces a program here the documentation is annotated with the given description.

annotated :: forall annotation combinator p m a. ProgramT (combinator & p) m a -> ProgramT (Annotated annotation combinator & p) m a Source #

A combinator which augments the documentation of the next element, by adding a description after its name and type.

Run CLI Programs

To run a ProgramT (a specification of a CLI program), you will need to use command or command_.

command :: forall p a. HasProgram p => ProgramT p IO a -> IO (Maybe a) Source #

This is a combinator which runs a ProgramT with the options, arguments, and flags that I get using the initialState function, returning Just the output of the program upon successful option and argument parsing and returning Nothing otherwise.

command_ :: forall p a. HasProgram p => ProgramT p IO a -> IO () Source #

This is a combinator which runs a ProgramT with the options, arguments, and flags that I get using the initialState function, ignoring the output of the program.

Each ProgramT has a type level description, build from these type level combinators.

data (&) :: k -> * -> * infixr 4 Source #

The type level program sequencing combinator, taking two program types and sequencing them one after another.

Instances

Instances details
(KnownSymbol annotation, HasProgram (combinator & p)) => HasProgram (Annotated annotation combinator & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Annotated annotation combinator & p) m a Source #

Methods

run :: ProgramT (Annotated annotation combinator & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Annotated annotation combinator & p) m a -> ProgramT (Annotated annotation combinator & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol description, HasProgram p) => HasProgram (Description description & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Description description & p) m a Source #

Methods

run :: ProgramT (Description description & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Description description & p) m a -> ProgramT (Description description & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Env 'Required name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Env 'Required name t & p) m a Source #

Methods

run :: ProgramT (Env 'Required name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Env 'Required name t & p) m a -> ProgramT (Env 'Required name t & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Env 'Optional name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Env 'Optional name t & p) m a Source #

Methods

run :: ProgramT (Env 'Optional name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Env 'Optional name t & p) m a -> ProgramT (Env 'Optional name t & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol flag, HasProgram p) => HasProgram (Flag flag & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Flag flag & p) m a Source #

Methods

run :: ProgramT (Flag flag & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Flag flag & p) m a -> ProgramT (Flag flag & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol name, KnownSymbol option, HasProgram p, Unrender t) => HasProgram (Opt option name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Opt option name t & p) m a Source #

Methods

run :: ProgramT (Opt option name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Opt option name t & p) m a -> ProgramT (Opt option name t & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Arg name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Arg name t & p) m a Source #

Methods

run :: ProgramT (Arg name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Arg name t & p) m a -> ProgramT (Arg name t & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol name, HasProgram p) => HasProgram (Named name & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Named name & p) m a Source #

Methods

run :: ProgramT (Named name & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Named name & p) m a -> ProgramT (Named name & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol sub, HasProgram p) => HasProgram (sub & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (sub & p) m a Source #

Methods

run :: ProgramT (sub & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (sub & p) m a -> ProgramT (sub & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Annotated annotation combinator & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Annotated annotation combinator & p :: Type) m a = AnnotatedProgramT {}
newtype ProgramT (Description description & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Description description & p :: Type) m a = DescriptionProgramT {}
newtype ProgramT (Env 'Required name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Env 'Required name t & p :: Type) m a = EnvProgramT'Required {}
data ProgramT (Env 'Optional name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Flag flag & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Flag flag & p :: Type) m a = FlagProgramT {}
data ProgramT (Opt option name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

data ProgramT (Opt option name t & p :: Type) m a = OptProgramT {}
newtype ProgramT (Arg name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Arg name t & p :: Type) m a = ArgProgramT {}
newtype ProgramT (Named name & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Named name & p :: Type) m a = NamedProgramT {}
newtype ProgramT (sub & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (sub & p :: Type) m a = SubProgramT {}

data a + b infixr 2 Source #

The type level combining combinator, taking two program types as input, and being interpreted as a program which attempts to run the first command line program and, if parsing its flags, subprograms, options or arguments fails, runs the second, otherwise failing.

Instances

Instances details
(HasProgram x, HasProgram y) => HasProgram (x + y :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (x + y) m a Source #

Methods

run :: ProgramT (x + y) IO a -> CommanderT State IO a Source #

hoist :: (forall x0. m x0 -> n x0) -> ProgramT (x + y) m a -> ProgramT (x + y) n a Source #

documentation :: Forest String Source #

data ProgramT (x + y :: Type) m a Source # 
Instance details

Defined in Options.Commander

data ProgramT (x + y :: Type) m a = (ProgramT x m a) :+: (ProgramT y m a)

data Arg :: Symbol -> * -> * Source #

The type level argument combinator, with a Symbol designating the name of that argument.

Instances

Instances details
(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Arg name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Arg name t & p) m a Source #

Methods

run :: ProgramT (Arg name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Arg name t & p) m a -> ProgramT (Arg name t & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Arg name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Arg name t & p :: Type) m a = ArgProgramT {}

data Opt :: Symbol -> Symbol -> * -> * Source #

The type level option combinator, with a Symbol designating the option's name and another representing the metavariables name for documentation purposes.

Instances

Instances details
(KnownSymbol name, KnownSymbol option, HasProgram p, Unrender t) => HasProgram (Opt option name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Opt option name t & p) m a Source #

Methods

run :: ProgramT (Opt option name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Opt option name t & p) m a -> ProgramT (Opt option name t & p) n a Source #

documentation :: Forest String Source #

data ProgramT (Opt option name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

data ProgramT (Opt option name t & p :: Type) m a = OptProgramT {}

data Named :: Symbol -> * Source #

The type level combinator for constructing named programs, giving your program a name at the toplevel for the sake of documentation.

Instances

Instances details
(KnownSymbol name, HasProgram p) => HasProgram (Named name & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Named name & p) m a Source #

Methods

run :: ProgramT (Named name & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Named name & p) m a -> ProgramT (Named name & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Named name & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Named name & p :: Type) m a = NamedProgramT {}

data Raw :: * Source #

The type level raw monadic program combinator, allowing a command line program to just do some computation.

Instances

Instances details
HasProgram Raw Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT Raw m a Source #

Methods

run :: ProgramT Raw IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT Raw m a -> ProgramT Raw n a Source #

documentation :: Forest String Source #

newtype ProgramT Raw m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT Raw m a = RawProgramT {}

data Flag :: Symbol -> * Source #

The type level flag combinator, taking a name as input, allowing your program to take flags with the syntax ~flag.

Instances

Instances details
(KnownSymbol flag, HasProgram p) => HasProgram (Flag flag & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Flag flag & p) m a Source #

Methods

run :: ProgramT (Flag flag & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Flag flag & p) m a -> ProgramT (Flag flag & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Flag flag & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Flag flag & p :: Type) m a = FlagProgramT {}

data Env :: Optionality -> Symbol -> * -> * Source #

The type level environment variable combinator, taking a name as input, allowing your program to take environment variables as input automatically.

Instances

Instances details
(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Env 'Required name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Env 'Required name t & p) m a Source #

Methods

run :: ProgramT (Env 'Required name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Env 'Required name t & p) m a -> ProgramT (Env 'Required name t & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Env 'Optional name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Env 'Optional name t & p) m a Source #

Methods

run :: ProgramT (Env 'Optional name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Env 'Optional name t & p) m a -> ProgramT (Env 'Optional name t & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Env 'Required name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Env 'Required name t & p :: Type) m a = EnvProgramT'Required {}
data ProgramT (Env 'Optional name t & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

data Optionality Source #

The type level tag for whether or not a variable is required or not.

Constructors

Required 
Optional 

data Description :: Symbol -> * Source #

The type level description combinator, allowing a command line program to have better documentation.

Instances

Instances details
(KnownSymbol description, HasProgram p) => HasProgram (Description description & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Description description & p) m a Source #

Methods

run :: ProgramT (Description description & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Description description & p) m a -> ProgramT (Description description & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Description description & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Description description & p :: Type) m a = DescriptionProgramT {}

data Annotated :: Symbol -> * -> * Source #

The type level annotated combinator, allowing a command line

Instances

Instances details
(KnownSymbol annotation, HasProgram (combinator & p)) => HasProgram (Annotated annotation combinator & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Annotated annotation combinator & p) m a Source #

Methods

run :: ProgramT (Annotated annotation combinator & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Annotated annotation combinator & p) m a -> ProgramT (Annotated annotation combinator & p) n a Source #

documentation :: Forest String Source #

newtype ProgramT (Annotated annotation combinator & p :: Type) m a Source # 
Instance details

Defined in Options.Commander

newtype ProgramT (Annotated annotation combinator & p :: Type) m a = AnnotatedProgramT {}

Interpreting CLI Programs

The HasProgram class forms the backbone of this library, defining the syntax for CLI programs using the ProgramT data family, and defining the interpretation of all of the various pieces of a CLI.

class HasProgram p where Source #

This is the workhorse of the library. Basically, it allows you to run your ProgramT representation of your program as a CommanderT and pump the State through it until you've processed all of the arguments, options, and flags that you have specified must be used in your ProgramT. You can think of ProgramT as a useful syntax for command line programs, but CommanderT as the semantics of that program. We also give the ability to hoist ProgramT actions between monads if you can uniformly turn computations in one into another. We also store documentation in the form of a Forest String, in order to automatically generate usage programs.

Associated Types

data ProgramT p (m :: * -> *) a Source #

Methods

run :: ProgramT p IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT p m a -> ProgramT p n a Source #

documentation :: Forest String Source #

Instances

Instances details
HasProgram Raw Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT Raw m a Source #

Methods

run :: ProgramT Raw IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT Raw m a -> ProgramT Raw n a Source #

documentation :: Forest String Source #

(KnownSymbol annotation, HasProgram (combinator & p)) => HasProgram (Annotated annotation combinator & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Annotated annotation combinator & p) m a Source #

Methods

run :: ProgramT (Annotated annotation combinator & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Annotated annotation combinator & p) m a -> ProgramT (Annotated annotation combinator & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol description, HasProgram p) => HasProgram (Description description & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Description description & p) m a Source #

Methods

run :: ProgramT (Description description & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Description description & p) m a -> ProgramT (Description description & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Env 'Required name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Env 'Required name t & p) m a Source #

Methods

run :: ProgramT (Env 'Required name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Env 'Required name t & p) m a -> ProgramT (Env 'Required name t & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Env 'Optional name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Env 'Optional name t & p) m a Source #

Methods

run :: ProgramT (Env 'Optional name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Env 'Optional name t & p) m a -> ProgramT (Env 'Optional name t & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol flag, HasProgram p) => HasProgram (Flag flag & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Flag flag & p) m a Source #

Methods

run :: ProgramT (Flag flag & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Flag flag & p) m a -> ProgramT (Flag flag & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol name, KnownSymbol option, HasProgram p, Unrender t) => HasProgram (Opt option name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Opt option name t & p) m a Source #

Methods

run :: ProgramT (Opt option name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Opt option name t & p) m a -> ProgramT (Opt option name t & p) n a Source #

documentation :: Forest String Source #

(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Arg name t & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Arg name t & p) m a Source #

Methods

run :: ProgramT (Arg name t & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Arg name t & p) m a -> ProgramT (Arg name t & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol name, HasProgram p) => HasProgram (Named name & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (Named name & p) m a Source #

Methods

run :: ProgramT (Named name & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (Named name & p) m a -> ProgramT (Named name & p) n a Source #

documentation :: Forest String Source #

(KnownSymbol sub, HasProgram p) => HasProgram (sub & p :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (sub & p) m a Source #

Methods

run :: ProgramT (sub & p) IO a -> CommanderT State IO a Source #

hoist :: (forall x. m x -> n x) -> ProgramT (sub & p) m a -> ProgramT (sub & p) n a Source #

documentation :: Forest String Source #

(HasProgram x, HasProgram y) => HasProgram (x + y :: Type) Source # 
Instance details

Defined in Options.Commander

Associated Types

data ProgramT (x + y) m a Source #

Methods

run :: ProgramT (x + y) IO a -> CommanderT State IO a Source #

hoist :: (forall x0. m x0 -> n x0) -> ProgramT (x + y) m a -> ProgramT (x + y) n a Source #

documentation :: Forest String Source #

The CommanderT Monad

The CommanderT monad is how your CLI programs are interpreted by run. It has the ability to backtrack and it maintains some state.

data CommanderT state (f :: Type -> Type) a #

A CommanderT action is a metaphor for a military commander. At each step, we have a new Action to take, or we could have experienced Defeat, or we can see Victory. While a real life commander worries about moving his troops around in order to achieve a victory in battle, a CommanderT worries about iteratively transforming a state to find some value.

In more practical terms, a term of type CommanderT can be thought of as a backtracking, stateful computation which can either result in a result being produced, or nothing being produced. It is a Monad for any base Functor you want to use as the effect inside of the stateful computation, similarly to the free monad.

Constructors

Action (state -> f (CommanderT state f a, state)) 
Defeat 
Victory a 

Instances

Instances details
MonadTrans (CommanderT state) 
Instance details

Defined in Control.Monad.Commander

Methods

lift :: Monad m => m a -> CommanderT state m a #

Functor f => Monad (CommanderT state f) 
Instance details

Defined in Control.Monad.Commander

Methods

(>>=) :: CommanderT state f a -> (a -> CommanderT state f b) -> CommanderT state f b #

(>>) :: CommanderT state f a -> CommanderT state f b -> CommanderT state f b #

return :: a -> CommanderT state f a #

Functor f => Functor (CommanderT state f) 
Instance details

Defined in Control.Monad.Commander

Methods

fmap :: (a -> b) -> CommanderT state f a -> CommanderT state f b #

(<$) :: a -> CommanderT state f b -> CommanderT state f a #

Functor f => Applicative (CommanderT state f) 
Instance details

Defined in Control.Monad.Commander

Methods

pure :: a -> CommanderT state f a #

(<*>) :: CommanderT state f (a -> b) -> CommanderT state f a -> CommanderT state f b #

liftA2 :: (a -> b -> c) -> CommanderT state f a -> CommanderT state f b -> CommanderT state f c #

(*>) :: CommanderT state f a -> CommanderT state f b -> CommanderT state f b #

(<*) :: CommanderT state f a -> CommanderT state f b -> CommanderT state f a #

MonadIO m => MonadIO (CommanderT state m) 
Instance details

Defined in Control.Monad.Commander

Methods

liftIO :: IO a -> CommanderT state m a #

Functor f => Alternative (CommanderT state f) 
Instance details

Defined in Control.Monad.Commander

Methods

empty :: CommanderT state f a #

(<|>) :: CommanderT state f a -> CommanderT state f a -> CommanderT state f a #

some :: CommanderT state f a -> CommanderT state f [a] #

many :: CommanderT state f a -> CommanderT state f [a] #

runCommanderT :: Monad m => CommanderT state m a -> state -> m (Maybe a) #

We can run a CommanderT on some state and see if it has a successful campaign.

initialState :: IO State Source #

A simple default for getting out the arguments, options, and flags using getArgs. We use the syntax ~flag for flags and -opt for options, with arguments using the typical ordered representation.

data State Source #

This is the State that the CommanderT library uses for its role in this library. It is not inlined, because that does nothing but obfuscate the CommanderT monad. It consists of arguments, options, and flags.

Constructors

State 

Instances

Instances details
Eq State Source # 
Instance details

Defined in Options.Commander

Methods

(==) :: State -> State -> Bool #

(/=) :: State -> State -> Bool #

Ord State Source # 
Instance details

Defined in Options.Commander

Methods

compare :: State -> State -> Ordering #

(<) :: State -> State -> Bool #

(<=) :: State -> State -> Bool #

(>) :: State -> State -> Bool #

(>=) :: State -> State -> Bool #

max :: State -> State -> State #

min :: State -> State -> State #

Show State Source # 
Instance details

Defined in Options.Commander

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

Generic State Source # 
Instance details

Defined in Options.Commander

Associated Types

type Rep State :: Type -> Type #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

type Rep State Source # 
Instance details

Defined in Options.Commander

type Rep State = D1 ('MetaData "State" "Options.Commander" "commander-cli-0.10.2.0-9wycb3e2L6W7Xhu1DaCBCF" 'False) (C1 ('MetaCons "State" 'PrefixI 'True) (S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]) :*: (S1 ('MetaSel ('Just "options") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashMap Text Text)) :*: S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HashSet Text)))))

Middleware for CommanderT

If you want to modify your interpreted CLI program, in its CommanderT form, you can use the concept of Middleware. A number of these are provided for debugging complex CLI programs, in case they aren't doing what you'd expect.

type Middleware m n = forall a. CommanderT State m a -> CommanderT State n a Source #

The type of middleware, which can transform interpreted command line programs by meddling with arguments, options, or flags, or by adding effects for every step. You can also change the underlying monad.

logState :: MonadIO m => Middleware m m Source #

Middleware to log the state to standard out for every step of the CommanderT computation.

transform :: (Monad m, Monad n) => (forall a. m a -> n a) -> Middleware m n Source #

Middleware to transform the base monad with a natural transformation.

withActionEffects :: Monad m => m a -> Middleware m m Source #

Middleware to add monadic effects for every Action. Useful for debugging complex command line programs.

withDefeatEffects :: Monad m => m a -> Middleware m m Source #

Middleware to have effects whenever the program might backtrack.

withVictoryEffects :: Monad m => m a -> Middleware m m Source #

Middleware to have effects whenever the program successfully computes a result.