Copyright | (c) Samuel Schlesinger 2020 |
---|---|
License | MIT |
Maintainer | sgschlesinger@gmail.com |
Stability | experimental |
Portability | POSIX, Windows |
Safe Haskell | None |
Language | Haskell2010 |
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 can be found as:
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 ())
The point of this library is mainly so that you can write command line interfaces quickly and easily, and not have to write any boilerplate.
Synopsis
- command :: HasProgram p => ProgramT p IO a -> IO (Maybe a)
- command_ :: HasProgram p => ProgramT p IO a -> IO ()
- arg :: KnownSymbol name => (x -> ProgramT p m a) -> ProgramT (Arg name x & p) m a
- opt :: (KnownSymbol option, KnownSymbol name) => (Maybe x -> ProgramT p m a) -> ProgramT (Opt option name x & p) m a
- raw :: m a -> ProgramT Raw m a
- sub :: KnownSymbol s => ProgramT p m a -> ProgramT (s & p) m a
- named :: KnownSymbol s => ProgramT p m a -> ProgramT (Named s & p) m a
- flag :: KnownSymbol f => (Bool -> ProgramT p m a) -> ProgramT (Flag f & p) m a
- toplevel :: forall s p m a. (HasProgram p, KnownSymbol s, MonadIO m) => ProgramT p m () -> ProgramT (Named s & (("help" & Raw) + p)) m ()
- (<+>) :: forall x y m a. ProgramT x m a -> ProgramT y m a -> ProgramT (x + y) m a
- usage :: forall p m a. (MonadIO m, HasProgram p) => ProgramT Raw m ()
- data (&) :: k -> * -> *
- data a + b
- data Arg :: Symbol -> * -> *
- data Opt :: Symbol -> Symbol -> * -> *
- data Named :: Symbol -> *
- data Raw :: *
- data Flag :: Symbol -> *
- class HasProgram p where
- run :: ProgramT p IO a -> CommanderT State IO a
- hoist :: (forall x. m x -> n x) -> ProgramT p m a -> ProgramT p n a
- invocations :: [Text]
- data CommanderT state m a
- = Action (state -> m (CommanderT state m a, state))
- | Defeat
- | Victory a
- runCommanderT :: Monad m => CommanderT state m a -> state -> m (Maybe a)
- initialState :: IO State
- data State = State {}
- class Unrender t where
Run CLI Programs
command :: 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_ :: 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.
CLI Combinators
arg :: KnownSymbol name => (x -> ProgramT p m a) -> ProgramT (Arg name x & p) m a Source #
Argument combinator
opt :: (KnownSymbol option, KnownSymbol name) => (Maybe x -> ProgramT p m a) -> ProgramT (Opt option name x & p) m a Source #
Option combinator
sub :: KnownSymbol s => ProgramT p m a -> ProgramT (s & p) m a Source #
Subcommand combinator
named :: KnownSymbol s => ProgramT p m a -> ProgramT (Named s & p) m a Source #
Named command combinator, should only really be used at the top level.
flag :: KnownSymbol f => (Bool -> ProgramT p m a) -> ProgramT (Flag f & p) m a Source #
Boolean flag combinator
toplevel :: forall s p m a. (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 a. (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.
Type Level CLI Description
data (&) :: k -> * -> * infixr 4 Source #
The type level program sequencing combinator, taking two program types and sequencing them one after another.
Instances
(KnownSymbol flag, HasProgram p) => HasProgram (Flag flag & p :: Type) Source # | |
(KnownSymbol name, HasProgram p) => HasProgram (Named name & p :: Type) Source # | |
(KnownSymbol name, KnownSymbol option, HasProgram p, Unrender t) => HasProgram (Opt option name t & p :: Type) Source # | |
Defined in Options.Commander | |
(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Arg name t & p :: Type) Source # | |
(KnownSymbol sub, HasProgram p) => HasProgram (sub & p :: Type) Source # | |
newtype ProgramT (Flag flag & p :: Type) m a Source # | |
Defined in Options.Commander newtype ProgramT (Flag flag & p :: Type) m a = FlagProgramT {
| |
newtype ProgramT (Named name & p :: Type) m a Source # | |
Defined in Options.Commander | |
newtype ProgramT (Opt option name t & p :: Type) m a Source # | |
Defined in Options.Commander newtype ProgramT (Opt option name t & p :: Type) m a = OptProgramT {
| |
newtype ProgramT (Arg name t & p :: Type) m a Source # | |
Defined in Options.Commander | |
newtype ProgramT (sub & p :: Type) m a Source # | |
Defined in Options.Commander |
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
(HasProgram x, HasProgram y) => HasProgram (x + y :: Type) Source # | |
data ProgramT (x + y :: Type) m a Source # | |
Defined in Options.Commander |
data Arg :: Symbol -> * -> * Source #
The type level argument combinator, with a Symbol
designating the
name of that argument.
Instances
(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Arg name t & p :: Type) Source # | |
newtype ProgramT (Arg name t & p :: Type) m a Source # | |
Defined in Options.Commander |
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
(KnownSymbol name, KnownSymbol option, HasProgram p, Unrender t) => HasProgram (Opt option name t & p :: Type) Source # | |
Defined in Options.Commander | |
newtype ProgramT (Opt option name t & p :: Type) m a Source # | |
Defined in Options.Commander newtype ProgramT (Opt option name t & p :: Type) m a = OptProgramT {
|
data Named :: Symbol -> * Source #
The type level naming combinator, giving your program a name for the sake of documentation.
Instances
(KnownSymbol name, HasProgram p) => HasProgram (Named name & p :: Type) Source # | |
newtype ProgramT (Named name & p :: Type) m a Source # | |
Defined in Options.Commander |
The type level raw monadic program combinator, allowing a command line program to just do some computation.
Instances
HasProgram Raw Source # | |
newtype ProgramT Raw m a Source # | |
Defined in Options.Commander |
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
(KnownSymbol flag, HasProgram p) => HasProgram (Flag flag & p :: Type) Source # | |
newtype ProgramT (Flag flag & p :: Type) m a Source # | |
Defined in Options.Commander newtype ProgramT (Flag flag & p :: Type) m a = FlagProgramT {
|
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. All of the different invocations
are also stored to give a primitive form of automatically generated
documentation.
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 #
invocations :: [Text] Source #
Instances
HasProgram Raw Source # | |
(KnownSymbol flag, HasProgram p) => HasProgram (Flag flag & p :: Type) Source # | |
(KnownSymbol name, HasProgram p) => HasProgram (Named name & p :: Type) Source # | |
(KnownSymbol name, KnownSymbol option, HasProgram p, Unrender t) => HasProgram (Opt option name t & p :: Type) Source # | |
Defined in Options.Commander | |
(Unrender t, KnownSymbol name, HasProgram p) => HasProgram (Arg name t & p :: Type) Source # | |
(KnownSymbol sub, HasProgram p) => HasProgram (sub & p :: Type) Source # | |
(HasProgram x, HasProgram y) => HasProgram (x + y :: Type) Source # | |
The CommanderT Monad
data CommanderT state m a Source #
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. We will deal with the subset of these actions where
every function must decrease the size of the state, as those are the
actions for which this is a monad.
Action (state -> m (CommanderT state m a, state)) | |
Defeat | |
Victory a |
Instances
MonadTrans (CommanderT state) Source # | |
Defined in Options.Commander lift :: Monad m => m a -> CommanderT state m a # | |
Monad m => Monad (CommanderT state m) Source # | |
Defined in Options.Commander (>>=) :: CommanderT state m a -> (a -> CommanderT state m b) -> CommanderT state m b # (>>) :: CommanderT state m a -> CommanderT state m b -> CommanderT state m b # return :: a -> CommanderT state m a # fail :: String -> CommanderT state m a # | |
Functor m => Functor (CommanderT state m) Source # | |
Defined in Options.Commander fmap :: (a -> b) -> CommanderT state m a -> CommanderT state m b # (<$) :: a -> CommanderT state m b -> CommanderT state m a # | |
Monad m => Applicative (CommanderT state m) Source # | |
Defined in Options.Commander pure :: a -> CommanderT state m a # (<*>) :: CommanderT state m (a -> b) -> CommanderT state m a -> CommanderT state m b # liftA2 :: (a -> b -> c) -> CommanderT state m a -> CommanderT state m b -> CommanderT state m c # (*>) :: CommanderT state m a -> CommanderT state m b -> CommanderT state m b # (<*) :: CommanderT state m a -> CommanderT state m b -> CommanderT state m a # | |
MonadIO m => MonadIO (CommanderT state m) Source # | |
Defined in Options.Commander liftIO :: IO a -> CommanderT state m a # | |
Monad m => Alternative (CommanderT state m) Source # | |
Defined in Options.Commander empty :: CommanderT state m a # (<|>) :: CommanderT state m a -> CommanderT state m a -> CommanderT state m a # some :: CommanderT state m a -> CommanderT state m [a] # many :: CommanderT state m a -> CommanderT state m [a] # |
runCommanderT :: Monad m => CommanderT state m a -> state -> m (Maybe a) Source #
We can run a CommanderT
action on a 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.
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
.
Parsing Arguments and Options
class Unrender t where Source #
A class for interpreting command line arguments into Haskell types.
Instances
Unrender Bool Source # | |
Unrender Char Source # | |
Unrender Int Source # | |
Unrender Int8 Source # | |
Unrender Int16 Source # | |
Unrender Int32 Source # | |
Unrender Int64 Source # | |
Unrender Integer Source # | |
Unrender Natural Source # | |
Unrender Word Source # | |
Unrender Word8 Source # | |
Unrender Word16 Source # | |
Unrender Word32 Source # | |
Unrender Word64 Source # | |
Unrender () Source # | |
Unrender String Source # | |
Unrender Text Source # | |
Unrender a => Unrender (Maybe a) Source # | |
(Unrender a, Unrender b) => Unrender (Either a b) Source # | |