Copyright | Copyright © 2015 PivotCloud, Inc. |
---|---|
License | MIT |
Maintainer | Lars Kuhtz <lkuhtz@pivotmail.com> |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
This module provides tools for defining command line parsers for configuration types.
Unlike normal command line parsers the parsers for configuration types are expected to yield an update function that takes a value and updates the value with the settings from the command line.
Assuming that
- all configuration types are nested Haskell records or simple types and
- that there are lenses for all record fields
usually the operators .::
and %::
are all that is needed from this module.
The module Configuration.Utils.Monoid provides tools for the case that
a simple type is a container with a monoid instance, such as List
or
HashMap
.
The module Configuration.Utils.Maybe explains the usage of optional
Maybe
values in configuration types.
- type MParser α = Parser (α -> α)
- (.::) :: (Alternative φ, Applicative φ) => Lens' α β -> φ β -> φ (α -> α)
- (%::) :: (Alternative φ, Applicative φ) => Lens' α β -> φ (β -> β) -> φ (α -> α)
- boolReader :: (Eq a, Show a, FoldCase a, IsString a, IsString e, Monoid e) => a -> Either e Bool
- boolOption :: Mod OptionFields Bool -> Parser Bool
- boolOption_ :: Mod FlagFields Bool -> Parser Bool
- enableDisableFlag :: Mod FlagFields Bool -> Parser Bool
- fileOption :: Mod OptionFields String -> Parser FilePath
- eitherReadP :: Text -> ReadP a -> Text -> Either Text a
- module Options.Applicative
Documentation
(.::) :: (Alternative φ, Applicative φ) => Lens' α β -> φ β -> φ (α -> α) infixr 5 Source
An operator for applying a setter to an option parser that yields a value.
Example usage:
data Auth = Auth { _user ∷ !String , _pwd ∷ !String } user ∷ Functor φ ⇒ (String → φ String) → Auth → φ Auth user f s = (\u → s { _user = u }) <$> f (_user s) pwd ∷ Functor φ ⇒ (String → φ String) → Auth → φ Auth pwd f s = (\p → s { _pwd = p }) <$> f (_pwd s) -- or with lenses and TemplateHaskell just: -- $(makeLenses ''Auth) pAuth ∷ MParser Auth pAuth = id <$< user .:: strOption × long "user" ⊕ short 'u' ⊕ help "user name" <*< pwd .:: strOption × long "pwd" ⊕ help "password for user"
(%::) :: (Alternative φ, Applicative φ) => Lens' α β -> φ (β -> β) -> φ (α -> α) infixr 5 Source
An operator for applying a setter to an option parser that yields a modification function.
Example usage:
data HttpURL = HttpURL { _auth ∷ !Auth , _domain ∷ !String } auth ∷ Functor φ ⇒ (Auth → φ Auth) → HttpURL → φ HttpURL auth f s = (\u → s { _auth = u }) <$> f (_auth s) domain ∷ Functor φ ⇒ (String → φ String) → HttpURL → φ HttpURL domain f s = (\u → s { _domain = u }) <$> f (_domain s) path ∷ Functor φ ⇒ (String → φ String) → HttpURL → φ HttpURL path f s = (\u → s { _path = u }) <$> f (_path s) -- or with lenses and TemplateHaskell just: -- $(makeLenses ''HttpURL) pHttpURL ∷ MParser HttpURL pHttpURL = id <$< auth %:: pAuth <*< domain .:: strOption × long "domain" ⊕ short 'd' ⊕ help "HTTP domain"
Misc Utils
boolReader :: (Eq a, Show a, FoldCase a, IsString a, IsString e, Monoid e) => a -> Either e Bool Source
boolOption :: Mod OptionFields Bool -> Parser Bool Source
The boolOption
is an alternative to switch
.
Using switch
with command line parsers that overwrite settings
from a configuration file is problematic: the absence of the switch
is interpreted as setting the respective configuration value to False
.
So there is no way to specify on the command line that the value from
the configuration file shall be used. Some command line UIs use two
different options for those values, for instance --enable-feature
and
--disable-feature
. This option instead expects a Boolean value. Beside
that it behaves like any other option.
boolOption_ :: Mod FlagFields Bool -> Parser Bool Source
An alternative syntax for boolOption
for options with long names.
Instead of taking a boolean argument the presence of the option acts as a
switch to set the respective configuration setting to True
. If the option
is not present the setting is left unchanged.
In addition for long option names a respective unset flag is provided. For
instance for a flag --verbose
there will also be a flag --no-verbose
.
This can still be used with short option names only, but no unset flag would be provided.
enableDisableFlag :: Mod FlagFields Bool -> Parser Bool Source
An option parser for flags that are enabled via the flag name prefixed
with --enable-
and disabled via the flag name prefix --disable-
. The
prefixes are applied to all long option names. Short option names are parsed
unchanged and and cause the flag to be enabled.
This resembles the style of flags that is used for instances with Cabal.
module Options.Applicative