getopt-generics-0.13.0.2: Create command line interfaces with ease

Safe HaskellNone
LanguageHaskell2010

WithCli

Contents

Synopsis

Documentation

withCli :: WithCli main => main -> IO () Source #

withCli converts an IO operation into a program with a proper CLI. Retrieves command line arguments through withArgs. main (the given IO operation) can have arbitrarily many parameters provided all parameters have instances for HasArguments.

May throw the following exceptions:

  • ExitFailure 1 in case of invalid options. Error messages are written to stderr.
  • ExitSuccess in case --help is given. (ExitSuccess behaves like a normal exception, except that -- if uncaught -- the process will exit with exit-code 0.) Help output is written to stdout.

Example:

 import WithCli

 main :: IO ()
 main = withCli run

 run :: String -> Int -> Bool -> IO ()
 run s i b = print (s, i, b)

Using the above program in a shell:

 $ program foo 42 true
 ("foo",42,True)
 $ program --help
 program [OPTIONS] STRING INTEGER BOOL
   -h  --help  show help and exit
 $ program foo 42 bar
 cannot parse as BOOL: bar
 # exit-code 1
 $ program
 missing argument of type STRING
 missing argument of type INTEGER
 missing argument of type BOOL
 # exit-code 1
 $ program foo 42 yes bar
 unknown argument: bar
 # exit-code 1

class WithCli main Source #

Everything that can be used as a main function with withCli needs to have an instance of WithCli. You shouldn't need to implement your own instances.

Minimal complete definition

run

Instances

WithCli (IO ()) Source # 

Methods

run :: Modifiers -> Result (Parser Unnormalized a) -> (a -> IO ()) -> [String] -> IO ()

(HasArguments a, WithCli rest) => WithCli (a -> rest) Source # 

Methods

run :: Modifiers -> Result (Parser Unnormalized a) -> (a -> a -> rest) -> [String] -> IO ()

class HasArguments a where Source #

Everything that can be used as an argument to your main function (see withCli) needs to have a HasArguments instance.

HasArguments also allows to conjure up instances for record types to create more complex command line interfaces. Here's an example:

 {-# LANGUAGE DeriveAnyClass #-}
 {-# LANGUAGE DeriveGeneric #-}

 import WithCli

 data Options
   = Options {
     port :: Int,
     daemonize :: Bool,
     config :: Maybe FilePath
   }
   deriving (Show, Generic, HasArguments)

 main :: IO ()
 main = withCli run

 run :: Options -> IO ()
 run = print

In a shell this program behaves like this:

 $ program --port 8080 --config some/path
 Options {port = 8080, daemonize = False, config = Just "some/path"}
 $ program  --port 8080 --daemonize
 Options {port = 8080, daemonize = True, config = Nothing}
 $ program --port foo
 cannot parse as INTEGER: foo
 # exit-code 1
 $ program
 missing option: --port=INTEGER
 # exit-code 1
 $ program --help
 program [OPTIONS]
       --port=INTEGER
       --daemonize
       --config=STRING (optional)
   -h  --help                      show help and exit

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized a) Source #

argumentsParser :: (Generic a, GTo a, GDatatypeInfo a, All2 HasArguments (GCode a)) => Modifiers -> Maybe String -> Result (Parser Unnormalized a) Source #

Instances

HasArguments Bool Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized Bool) Source #

HasArguments Double Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized Double) Source #

HasArguments Float Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized Float) Source #

HasArguments Int Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized Int) Source #

HasArguments String Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized String) Source #

Argument a => HasArguments [a] Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized [a]) Source #

Argument a => HasArguments (Maybe a) Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized (Maybe a)) Source #

(HasArguments a, HasArguments b) => HasArguments (a, b) Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized (a, b)) Source #

(HasArguments a, HasArguments b, HasArguments c) => HasArguments (a, b, c) Source # 

Methods

argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized (a, b, c)) Source #

atomicArgumentsParser :: forall a. Argument a => Modifiers -> Maybe String -> Result (Parser Unnormalized a) Source #

Useful for implementing your own instances of HasArguments on top of a custom Argument instance.

class Argument a where Source #

Argument is a typeclass for things that can be parsed as atomic values from single command line arguments, e.g. strings (and filenames) and numbers.

Occasionally you might want to declare your own instance for additional type safety and for providing a more informative command argument type. Here's an example:

 {-# LANGUAGE DeriveDataTypeable #-}

 import WithCli

 data File = File FilePath
   deriving (Show, Typeable)

 instance Argument File where
   argumentType Proxy = "custom-file-type"
   parseArgument f = Just (File f)

 instance HasArguments File where
   argumentsParser = atomicArgumentsParser

 main :: IO ()
 main = withCli run

 run :: File -> IO ()
 run = print

And this is how the above program behaves:

 $ program --help
 program [OPTIONS] custom-file-type
   -h  --help  show help and exit
 $ program some/file
 File "some/file"

Minimal complete definition

argumentType, parseArgument

Modifiers

withCliModified :: WithCli main => [Modifier] -> main -> IO () Source #

This is a variant of withCli that allows to tweak the generated command line interface by providing a list of Modifiers.

data Modifier Source #

Modifiers can be used to customize the command line parser.

Constructors

AddShortOption String Char

AddShortOption fieldName c adds the Char c as a short option for the field addressed by fieldName.

RenameOption String String

RenameOption fieldName customName renames the option generated through the fieldName by customName.

RenameOptions (String -> Maybe String)

RenameOptions f renames all options with the given functions. In case the function returns Nothing the original field name is used.

Can be used together with stripPrefix.

UseForPositionalArguments String String

UseForPositionalArguments fieldName argumentType fills the field addressed by fieldName with the positional arguments (i.e. arguments that don't correspond to a flag). The field has to have type [String].

argumentType is used as the type of the positional arguments in the help output.

AddOptionHelp String String

AddOptionHelp fieldName helpText adds a help text for the option fieldName.

AddVersionFlag String

AddVersionFlag version adds a --version flag.

Useful Re-exports

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

Minimal complete definition

from, to

Instances

Generic Bool 

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic () 

Associated Types

type Rep () :: * -> * #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Version 

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic Fixity 

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Generic SourceStrictness 
Generic DecidedStrictness 
Generic [a] 

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Par1 p) 

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (I a) 

Associated Types

type Rep (I a) :: * -> * #

Methods

from :: I a -> Rep (I a) x #

to :: Rep (I a) x -> I a #

Generic (Either a b) 

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 k p) 

Associated Types

type Rep (V1 k p) :: * -> * #

Methods

from :: V1 k p -> Rep (V1 k p) x #

to :: Rep (V1 k p) x -> V1 k p #

Generic (U1 k p) 

Associated Types

type Rep (U1 k p) :: * -> * #

Methods

from :: U1 k p -> Rep (U1 k p) x #

to :: Rep (U1 k p) x -> U1 k p #

Generic (a, b) 

Associated Types

type Rep (a, b) :: * -> * #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Generic (Rec1 k f p) 

Associated Types

type Rep (Rec1 k f p) :: * -> * #

Methods

from :: Rec1 k f p -> Rep (Rec1 k f p) x #

to :: Rep (Rec1 k f p) x -> Rec1 k f p #

Generic (URec k (Ptr ()) p) 

Associated Types

type Rep (URec k (Ptr ()) p) :: * -> * #

Methods

from :: URec k (Ptr ()) p -> Rep (URec k (Ptr ()) p) x #

to :: Rep (URec k (Ptr ()) p) x -> URec k (Ptr ()) p #

Generic (URec k Char p) 

Associated Types

type Rep (URec k Char p) :: * -> * #

Methods

from :: URec k Char p -> Rep (URec k Char p) x #

to :: Rep (URec k Char p) x -> URec k Char p #

Generic (URec k Double p) 

Associated Types

type Rep (URec k Double p) :: * -> * #

Methods

from :: URec k Double p -> Rep (URec k Double p) x #

to :: Rep (URec k Double p) x -> URec k Double p #

Generic (URec k Float p) 

Associated Types

type Rep (URec k Float p) :: * -> * #

Methods

from :: URec k Float p -> Rep (URec k Float p) x #

to :: Rep (URec k Float p) x -> URec k Float p #

Generic (URec k Int p) 

Associated Types

type Rep (URec k Int p) :: * -> * #

Methods

from :: URec k Int p -> Rep (URec k Int p) x #

to :: Rep (URec k Int p) x -> URec k Int p #

Generic (URec k Word p) 

Associated Types

type Rep (URec k Word p) :: * -> * #

Methods

from :: URec k Word p -> Rep (URec k Word p) x #

to :: Rep (URec k Word p) x -> URec k Word p #

Generic (a, b, c) 

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (K k a b) 

Associated Types

type Rep (K k a b) :: * -> * #

Methods

from :: K k a b -> Rep (K k a b) x #

to :: Rep (K k a b) x -> K k a b #

Generic (K1 k i c p) 

Associated Types

type Rep (K1 k i c p) :: * -> * #

Methods

from :: K1 k i c p -> Rep (K1 k i c p) x #

to :: Rep (K1 k i c p) x -> K1 k i c p #

Generic ((:+:) k f g p) 

Associated Types

type Rep ((k :+: f) g p) :: * -> * #

Methods

from :: (k :+: f) g p -> Rep ((k :+: f) g p) x #

to :: Rep ((k :+: f) g p) x -> (k :+: f) g p #

Generic ((:*:) k f g p) 

Associated Types

type Rep ((k :*: f) g p) :: * -> * #

Methods

from :: (k :*: f) g p -> Rep ((k :*: f) g p) x #

to :: Rep ((k :*: f) g p) x -> (k :*: f) g p #

Generic (a, b, c, d) 

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (M1 k i c f p) 

Associated Types

type Rep (M1 k i c f p) :: * -> * #

Methods

from :: M1 k i c f p -> Rep (M1 k i c f p) x #

to :: Rep (M1 k i c f p) x -> M1 k i c f p #

Generic ((:.:) k2 k1 f g p) 

Associated Types

type Rep ((k2 :.: k1) f g p) :: * -> * #

Methods

from :: (k2 :.: k1) f g p -> Rep ((k2 :.: k1) f g p) x #

to :: Rep ((k2 :.: k1) f g p) x -> (k2 :.: k1) f g p #

Generic (a, b, c, d, e) 

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic ((:.:) l k f g p) 

Associated Types

type Rep ((l :.: k) f g p) :: * -> * #

Methods

from :: (l :.: k) f g p -> Rep ((l :.: k) f g p) x #

to :: Rep ((l :.: k) f g p) x -> (l :.: k) f g p #

Generic (a, b, c, d, e, f) 

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

class Typeable k (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

data Proxy k (t :: k) :: forall k. k -> * #

A concrete, poly-kinded proxy type

Constructors

Proxy 

Instances

Generic1 k (Proxy k) 

Associated Types

type Rep1 (Proxy k) (f :: Proxy k -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (Proxy k) f a #

to1 :: Rep1 (Proxy k) f a -> f a #

Monad (Proxy *)

Since: 4.7.0.0

Methods

(>>=) :: Proxy * a -> (a -> Proxy * b) -> Proxy * b #

(>>) :: Proxy * a -> Proxy * b -> Proxy * b #

return :: a -> Proxy * a #

fail :: String -> Proxy * a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

(<$) :: a -> Proxy * b -> Proxy * a #

Applicative (Proxy *)

Since: 4.7.0.0

Methods

pure :: a -> Proxy * a #

(<*>) :: Proxy * (a -> b) -> Proxy * a -> Proxy * b #

liftA2 :: (a -> b -> c) -> Proxy * a -> Proxy * b -> Proxy * c #

(*>) :: Proxy * a -> Proxy * b -> Proxy * b #

(<*) :: Proxy * a -> Proxy * b -> Proxy * a #

Foldable (Proxy *)

Since: 4.7.0.0

Methods

fold :: Monoid m => Proxy * m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy * a -> m #

foldr :: (a -> b -> b) -> b -> Proxy * a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy * a -> b #

foldl :: (b -> a -> b) -> b -> Proxy * a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy * a -> b #

foldr1 :: (a -> a -> a) -> Proxy * a -> a #

foldl1 :: (a -> a -> a) -> Proxy * a -> a #

toList :: Proxy * a -> [a] #

null :: Proxy * a -> Bool #

length :: Proxy * a -> Int #

elem :: Eq a => a -> Proxy * a -> Bool #

maximum :: Ord a => Proxy * a -> a #

minimum :: Ord a => Proxy * a -> a #

sum :: Num a => Proxy * a -> a #

product :: Num a => Proxy * a -> a #

Traversable (Proxy *)

Since: 4.7.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Proxy * a -> f (Proxy * b) #

sequenceA :: Applicative f => Proxy * (f a) -> f (Proxy * a) #

mapM :: Monad m => (a -> m b) -> Proxy * a -> m (Proxy * b) #

sequence :: Monad m => Proxy * (m a) -> m (Proxy * a) #

Alternative (Proxy *)

Since: 4.9.0.0

Methods

empty :: Proxy * a #

(<|>) :: Proxy * a -> Proxy * a -> Proxy * a #

some :: Proxy * a -> Proxy * [a] #

many :: Proxy * a -> Proxy * [a] #

MonadPlus (Proxy *)

Since: 4.9.0.0

Methods

mzero :: Proxy * a #

mplus :: Proxy * a -> Proxy * a -> Proxy * a #

Bounded (Proxy k t) 

Methods

minBound :: Proxy k t #

maxBound :: Proxy k t #

Enum (Proxy k s)

Since: 4.7.0.0

Methods

succ :: Proxy k s -> Proxy k s #

pred :: Proxy k s -> Proxy k s #

toEnum :: Int -> Proxy k s #

fromEnum :: Proxy k s -> Int #

enumFrom :: Proxy k s -> [Proxy k s] #

enumFromThen :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromTo :: Proxy k s -> Proxy k s -> [Proxy k s] #

enumFromThenTo :: Proxy k s -> Proxy k s -> Proxy k s -> [Proxy k s] #

Eq (Proxy k s)

Since: 4.7.0.0

Methods

(==) :: Proxy k s -> Proxy k s -> Bool #

(/=) :: Proxy k s -> Proxy k s -> Bool #

Ord (Proxy k s)

Since: 4.7.0.0

Methods

compare :: Proxy k s -> Proxy k s -> Ordering #

(<) :: Proxy k s -> Proxy k s -> Bool #

(<=) :: Proxy k s -> Proxy k s -> Bool #

(>) :: Proxy k s -> Proxy k s -> Bool #

(>=) :: Proxy k s -> Proxy k s -> Bool #

max :: Proxy k s -> Proxy k s -> Proxy k s #

min :: Proxy k s -> Proxy k s -> Proxy k s #

Read (Proxy k s)

Since: 4.7.0.0

Show (Proxy k s)

Since: 4.7.0.0

Methods

showsPrec :: Int -> Proxy k s -> ShowS #

show :: Proxy k s -> String #

showList :: [Proxy k s] -> ShowS #

Ix (Proxy k s)

Since: 4.7.0.0

Methods

range :: (Proxy k s, Proxy k s) -> [Proxy k s] #

index :: (Proxy k s, Proxy k s) -> Proxy k s -> Int #

unsafeIndex :: (Proxy k s, Proxy k s) -> Proxy k s -> Int

inRange :: (Proxy k s, Proxy k s) -> Proxy k s -> Bool #

rangeSize :: (Proxy k s, Proxy k s) -> Int #

unsafeRangeSize :: (Proxy k s, Proxy k s) -> Int

Generic (Proxy k t) 

Associated Types

type Rep (Proxy k t) :: * -> * #

Methods

from :: Proxy k t -> Rep (Proxy k t) x #

to :: Rep (Proxy k t) x -> Proxy k t #

Monoid (Proxy k s)

Since: 4.7.0.0

Methods

mempty :: Proxy k s #

mappend :: Proxy k s -> Proxy k s -> Proxy k s #

mconcat :: [Proxy k s] -> Proxy k s #

type Rep1 k (Proxy k) 
type Rep1 k (Proxy k) = D1 k (MetaData "Proxy" "Data.Proxy" "base" False) (C1 k (MetaCons "Proxy" PrefixI False) (U1 k))
type Rep (Proxy k t) 
type Rep (Proxy k t) = D1 * (MetaData "Proxy" "Data.Proxy" "base" False) (C1 * (MetaCons "Proxy" PrefixI False) (U1 *))
type Code (Proxy * t) 
type Code (Proxy * t) = (:) [*] ([] *) ([] [*])
type DatatypeInfoOf (Proxy * t) 
type DatatypeInfoOf (Proxy * t) = ADT "Data.Proxy" "Proxy" ((:) ConstructorInfo (Constructor "Proxy") ([] ConstructorInfo))