| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
WithCli
Contents
Synopsis
- withCli :: WithCli main => main -> IO ()
- class WithCli main
- class HasArguments a where
- argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized a)
- atomicArgumentsParser :: forall a. Argument a => Modifiers -> Maybe String -> Result (Parser Unnormalized a)
- class Argument a where
- argumentType :: Proxy a -> String
- parseArgument :: String -> Maybe a
- withCliModified :: WithCli main => [Modifier] -> main -> IO ()
- data Modifier
- class Generic a
- class Typeable (a :: k)
- data Proxy (t :: k) = Proxy
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:
in case of invalid options. Error messages are written toExitFailure1stderr.in caseExitSuccess--helpis given. (behaves like a normal exception, except that -- if uncaught -- the process will exit with exit-codeExitSuccess0.) Help output is written tostdout.
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 1Everything 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
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 = printIn 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 exitMinimal complete definition
Nothing
Methods
argumentsParser :: Modifiers -> Maybe String -> Result (Parser Unnormalized a) Source #
default argumentsParser :: (Generic a, GTo a, GDatatypeInfo a, All2 HasArguments (GCode a)) => Modifiers -> Maybe String -> Result (Parser Unnormalized a) Source #
Instances
| HasArguments String Source # | |
Defined in WithCli.HasArguments | |
| HasArguments Bool Source # | |
Defined in WithCli.HasArguments | |
| HasArguments Double Source # | |
Defined in WithCli.HasArguments | |
| HasArguments Float Source # | |
Defined in WithCli.HasArguments | |
| HasArguments Int Source # | |
Defined in WithCli.HasArguments | |
| Argument a => HasArguments (Maybe a) Source # | |
Defined in WithCli.HasArguments | |
| Argument a => HasArguments [a] Source # | |
Defined in WithCli.HasArguments | |
| (HasArguments a, HasArguments b) => HasArguments (a, b) Source # | |
Defined in WithCli.HasArguments | |
| (HasArguments a, HasArguments b, HasArguments c) => HasArguments (a, b, c) Source # | |
Defined in WithCli.HasArguments | |
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 = printAnd 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"
Instances
| Argument String Source # | |
Defined in WithCli.Argument | |
| Argument Integer Source # | |
Defined in WithCli.Argument | |
| Argument Double Source # | |
Defined in WithCli.Argument | |
| Argument Float Source # | |
Defined in WithCli.Argument | |
| Argument Int Source # | |
Defined in WithCli.Argument | |
Modifiers
Modifiers can be used to customize the command line parser.
Constructors
| AddShortOption String Char |
|
| RenameOption String String |
|
| RenameOptions (String -> Maybe String) |
Can be used together with |
| UseForPositionalArguments String String |
|
| AddOptionHelp String String |
|
| AddVersionFlag String |
|
Useful Re-exports
Representable types of kind *.
This class is derivable in GHC with the DeriveGeneric flag on.
A Generic instance must satisfy the following laws:
from.to≡idto.from≡id
Instances
The class Typeable allows a concrete representation of a type to
be calculated.
Minimal complete definition
typeRep#
Proxy is a type that holds no data, but has a phantom parameter of
arbitrary type (or even kind). Its use is to provide type information, even
though there is no value available of that type (or it may be too costly to
create one).
Historically, is a safer alternative to the
Proxy :: Proxy a idiom.undefined :: a
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy |
Instances
| Generic1 (Proxy :: k -> Type) | |
| Foldable (Proxy :: TYPE LiftedRep -> Type) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> 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 # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
| Traversable (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Alternative (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| Applicative (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Functor (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
| MonadPlus (Proxy :: Type -> Type) | Since: base-4.9.0.0 |
| Monoid (Proxy s) | Since: base-4.7.0.0 |
| Semigroup (Proxy s) | Since: base-4.9.0.0 |
| Bounded (Proxy t) | Since: base-4.7.0.0 |
| Enum (Proxy s) | Since: base-4.7.0.0 |
| Generic (Proxy t) | |
| Ix (Proxy s) | Since: base-4.7.0.0 |
Defined in Data.Proxy | |
| Read (Proxy t) | Since: base-4.7.0.0 |
| Show (Proxy s) | Since: base-4.7.0.0 |
| Eq (Proxy s) | Since: base-4.7.0.0 |
| Ord (Proxy s) | Since: base-4.7.0.0 |
| type Rep1 (Proxy :: k -> Type) | Since: base-4.6.0.0 |
| type Rep (Proxy t) | Since: base-4.6.0.0 |
| type Code (Proxy t) | |
Defined in Generics.SOP.Instances | |
| type DatatypeInfoOf (Proxy t) | |
Defined in Generics.SOP.Instances type DatatypeInfoOf (Proxy t) = 'ADT "Data.Proxy" "Proxy" '['Constructor "Proxy"] '['[] :: [StrictnessInfo]] | |