Safe Haskell | None |
---|---|
Language | Haskell2010 |
Extensions |
|
- Program Configuration
- Program Configurations with Validation of Configuration Values
- Running an Configured Application
- Applicative Option Parsing with Default Values
- Parsing of Configuration Files with Default Values
- Command Line Option Parsing
- Misc Utils
- Configuration of Optional Values
- Simple Maybe Values
This module provides a collection of utils on top of the packages optparse-applicative, aeson, and yaml, for configuring libraries and applications in a composable way.
The main feature is the integration of command line option parsing and configuration files.
The purpose is to make management of configurations easy by providing an idiomatic style of defining and deploying configurations.
For each data type that is used as a configuration type the following must be provided:
- a default value,
- a
FromJSON
instance that yields a function that takes a value and updates that value with the parsed values, - a
ToJSON
instance, and - an options parser that yields a function that takes a value and updates that value with the values provided as command line options.
In addition to the above optionally a validation function may be provided that (recursively) validates a configuration value and returns either an error or a --possibly empty-- list-like structure of warnings.
The module provides operators and functions that make the implmentation of these entities easy for the common case that the configurations are encoded mainly as nested records.
The operators assume that lenses for the configuration record types are provided.
An complete usage example can be found in the file example/Example.hs
of the cabal package.
- type ProgramInfo α = ProgramInfoValidate α []
- programInfo :: String -> MParser α -> α -> ProgramInfo α
- piDescription :: Lens' (ProgramInfoValidate α λ) String
- piHelpHeader :: Lens' (ProgramInfoValidate α λ) (Maybe String)
- piHelpFooter :: Lens' (ProgramInfoValidate α λ) (Maybe String)
- piOptionParser :: Lens' (ProgramInfoValidate α λ) (MParser α)
- piDefaultConfiguration :: Lens' (ProgramInfoValidate α λ) α
- type ConfigValidation α λ = (MonadIO μ, Functor μ, Applicative μ, MonadError Text μ, MonadWriter (λ Text) μ) => α -> μ ()
- programInfoValidate :: String -> MParser α -> α -> ConfigValidation α λ -> ProgramInfoValidate α λ
- data ProgramInfoValidate α λ
- piValidateConfiguration :: Lens' (ProgramInfoValidate α λ) (ConfigValidationFunction α λ)
- data ConfigValidationFunction α λ
- piOptionParserAndDefaultConfiguration :: Lens (ProgramInfoValidate α λ) (ProgramInfoValidate β γ) (MParser α, α, ConfigValidationFunction α λ) (MParser β, β, ConfigValidationFunction β γ)
- runWithConfiguration :: (FromJSON (α -> α), ToJSON α, Foldable λ, Monoid (λ Text)) => ProgramInfoValidate α λ -> (α -> IO ()) -> IO ()
- type PkgInfo = (String, String, String, String)
- runWithPkgInfoConfiguration :: (FromJSON (α -> α), ToJSON α, Foldable λ, Monoid (λ Text)) => ProgramInfoValidate α λ -> PkgInfo -> (α -> IO ()) -> IO ()
- parseConfiguration :: (Applicative m, MonadIO m, MonadError Text m, FromJSON (α -> α), ToJSON α, Foldable λ, Monoid (λ Text)) => Text -> ProgramInfoValidate α λ -> [String] -> m α
- 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
- fileOption :: Mod OptionFields String -> Parser FilePath
- eitherReadP :: Text -> ReadP a -> Text -> Either Text a
- module Options.Applicative
- setProperty :: Lens' α β -> Text -> (Value -> Parser β) -> Object -> Parser (α -> α)
- (..:) :: FromJSON β => Lens' α β -> Text -> Object -> Parser (α -> α)
- (!..:) :: FromJSON β => Lens' α β -> Text -> Object -> Parser (α -> α)
- (%.:) :: FromJSON (β -> β) => Lens' α β -> Text -> Object -> Parser (α -> α)
- module Data.Aeson
- (%) :: (α -> β) -> α -> β
- (×) :: (α -> β) -> α -> β
- (<*<) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ)
- (>*>) :: Applicative φ => φ (α -> β) -> φ (β -> γ) -> φ (α -> γ)
- (<$<) :: Functor φ => (β -> γ) -> φ (α -> β) -> φ (α -> γ)
- (>$>) :: Functor φ => φ (α -> β) -> (β -> γ) -> φ (α -> γ)
- (<.>) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ)
- (⊙) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ)
- dropAndUncaml :: Int -> String -> String
- type Lens' σ α = Lens σ σ α α
- type Lens σ τ α β = Functor φ => (α -> φ β) -> σ -> φ τ
- maybeOption :: a -> Bool -> (a -> a) -> Maybe a -> Maybe a
Program Configuration
type ProgramInfo α = ProgramInfoValidate α [] Source
:: String | program description |
-> MParser α | parser for updating the default configuration |
-> α | default configuration |
-> ProgramInfo α |
Smart constructor for ProgramInfo
.
piHelpHeader
and piHelpFooter
are set to Nothing
.
The function piValidateConfiguration
is set to const (return [])
piDescription :: Lens' (ProgramInfoValidate α λ) String Source
Program Description
piHelpHeader :: Lens' (ProgramInfoValidate α λ) (Maybe String) Source
Help header
piHelpFooter :: Lens' (ProgramInfoValidate α λ) (Maybe String) Source
Help footer
piOptionParser :: Lens' (ProgramInfoValidate α λ) (MParser α) Source
Options parser for configuration
piDefaultConfiguration :: Lens' (ProgramInfoValidate α λ) α Source
Default configuration
Program Configurations with Validation of Configuration Values
type ConfigValidation α λ = (MonadIO μ, Functor μ, Applicative μ, MonadError Text μ, MonadWriter (λ Text) μ) => α -> μ () Source
A validation function. The type in the MonadWriter
is excpected to
be a Foldable
structure for collecting warnings.
programInfoValidate :: String -> MParser α -> α -> ConfigValidation α λ -> ProgramInfoValidate α λ Source
Smart constructor for ProgramInfo
.
piHelpHeader
and piHelpFooter
are set to Nothing
.
Low-level Config Validation
data ProgramInfoValidate α λ Source
data ConfigValidationFunction α λ Source
A newtype wrapper around a validation function. The only purpose of
this type is to avoid ImpredicativeTypes
when storing the function
in the ProgramInfoValidate
record.
piOptionParserAndDefaultConfiguration :: Lens (ProgramInfoValidate α λ) (ProgramInfoValidate β γ) (MParser α, α, ConfigValidationFunction α λ) (MParser β, β, ConfigValidationFunction β γ) Source
Lens
for simultaneous query and update of piOptionParser
and
piDefaultConfiguration
. This supports to change the type of ProgramInfo
with over
and set
.
Running an Configured Application
:: (FromJSON (α -> α), ToJSON α, Foldable λ, Monoid (λ Text)) | |
=> ProgramInfoValidate α λ | program info value; use |
-> (α -> IO ()) | computation that is given the configuration that is parsed from the command line. |
-> IO () |
Run an IO action with a configuration that is obtained by updating the given default configuration the values defined via command line arguments.
In addition to the options defined by the given options parser the following options are recognized:
--config-file, -c
- Parse the given file path as a (partial) configuration in YAML format.
--print-config, -p
- Print the final parsed configuration to standard out and exit.
--help, -h
- Print a help message and exit.
type PkgInfo = (String, String, String, String) Source
Information about the cabal package. The format is:
(info message, detailed info message, version string, license text)
See the documentation of Configuration.Utils.Setup for a way how to generate this information automatically from the package description during the build process.
runWithPkgInfoConfiguration Source
:: (FromJSON (α -> α), ToJSON α, Foldable λ, Monoid (λ Text)) | |
=> ProgramInfoValidate α λ | program info value; use |
-> PkgInfo | |
-> (α -> IO ()) | computation that is given the configuration that is parsed from the command line. |
-> IO () |
Run an IO action with a configuration that is obtained by updating the given default configuration the values defined via command line arguments.
In addition to the options defined by the given options parser the following options are recognized:
--config-file, -c
- Parse the given file path as a (partial) configuration in YAML format.
--print-config, -p
- Print the final parsed configuration to standard out and exit.
--help, -h
- Print a help message and exit.
--version, -v
- Print the version of the application and exit.
--info, -i
- Print a short info message for the application and exit.
--long-info
- Print a detailed info message for the application and exit.
--license
- Print the text of the lincense of the application and exit.
:: (Applicative m, MonadIO m, MonadError Text m, FromJSON (α -> α), ToJSON α, Foldable λ, Monoid (λ Text)) | |
=> Text | program name (used in error messages) |
-> ProgramInfoValidate α λ | program info value; use |
-> [String] | command line arguments |
-> m α |
Parse the command line arguments.
Any warnings from the configuration function are discarded.
The options --print-config
and --help
are just ignored.
NOTE this that this function may call unsafePerformIO
for
reading configuration files.
Applicative Option Parsing with Default Values
(.::) :: (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"
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.
module Options.Applicative
Parsing of Configuration Files with Default Values
:: Lens' α β | a lens into the target that is updated by the parser |
-> Text | the JSON property name |
-> (Value -> Parser β) | the JSON |
-> Object | |
-> Parser (α -> α) |
A JSON Value
parser for a property of a given
Object
that updates a setter with the parsed value.
data Auth = Auth { _userId ∷ !Int , _pwd ∷ !String } userId ∷ Functor φ ⇒ (Int → φ Int) → Auth → φ Auth userId f s = (\u → s { _userId = u }) <$> f (_userId 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) instance FromJSON (Auth → Auth) where parseJSON = withObject "Auth" $ \o → id <$< setProperty user "user" p o <*< setProperty pwd "pwd" parseJSON o where p = withText "user" $ \case "alice" → pure (0 ∷ Int) "bob" → pure 1 e → fail $ "unrecognized user " ⊕ e
(..:) :: FromJSON β => Lens' α β -> Text -> Object -> Parser (α -> α) infix 6 Source
A variant of the setProperty
that uses the default parseJSON
method from the
FromJSON
instance to parse the value of the property. Its usage pattern mimics the
usage pattern of the .:
operator from the aeson library.
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) instance FromJSON (Auth → Auth) where parseJSON = withObject "Auth" $ \o → id <$< user ..: "user" × o <*< pwd ..: "pwd" × o
(!..:) :: FromJSON β => Lens' α β -> Text -> Object -> Parser (α -> α) Source
This operator requires that a value is explicitly provided in a configuration file, thus preventing the default value from being used. Otherwise this operator does the same as '(..:)'.
(%.:) :: FromJSON (β -> β) => Lens' α β -> Text -> Object -> Parser (α -> α) infix 6 Source
A variant of the aeson operator .:
that creates a parser
that modifies a setter with a parsed function.
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) instance FromJSON (HttpURL → HttpURL) where parseJSON = withObject "HttpURL" $ \o → id <$< auth %.: "auth" × o <*< domain ..: "domain" × o
module Data.Aeson
Command Line Option Parsing
Misc Utils
(%) :: (α -> β) -> α -> β infixr 5 Source
This operator is an alternative for $
with a higher precedence. It is
suitable for usage within applicative style code without the need to add
parenthesis.
(×) :: (α -> β) -> α -> β infixr 5 Source
This operator is a UTF-8 version of %
which is an alternative for $
with a higher precedence. It is suitable for usage within applicative style
code without the need to add parenthesis.
The hex value of the UTF-8 character × is 0x00d7.
In VIM type: Ctrl-V u 00d7
You may also define a key binding by adding something like the following line to your vim configuration file:
iabbrev <buffer> >< ×
(<*<) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ) infixr 4 Source
Functional composition for applicative functors.
(>*>) :: Applicative φ => φ (α -> β) -> φ (β -> γ) -> φ (α -> γ) infixr 4 Source
Functional composition for applicative functors with its arguments flipped.
(<$<) :: Functor φ => (β -> γ) -> φ (α -> β) -> φ (α -> γ) infixr 4 Source
Applicative functional composition between a pure function and an applicative function.
(>$>) :: Functor φ => φ (α -> β) -> (β -> γ) -> φ (α -> γ) infixr 4 Source
Applicative functional composition between a pure function and an applicative function with its arguments flipped.
(<.>) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ) infixr 4 Source
Deprecated: use <*<
instead
Functional composition for applicative functors.
This is a rather popular operator. Due to conflicts (for instance with the lens package) it may have to be imported qualified.
(⊙) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ) infixr 4 Source
dropAndUncaml :: Int -> String -> String Source
type Lens' σ α = Lens σ σ α α Source
This is the same type as the type from the lens library with the same name.
In case it is already import from the lens package this should be hidden from the import.
type Lens σ τ α β = Functor φ => (α -> φ β) -> σ -> φ τ Source
This is the same type as the type from the lens library with the same name.
In case it is already import from the lens package this should be hidden from the import.
Configuration of Optional Values
Simple Maybe Values
Optional configuration values are supposed to be encoded by wrapping
the respective type with Maybe
.
For simple values the standard FromJSON
instance from the aeson
package can be used along with the ..:
operator.
data LogConfig = LogConfig { _logLevel ∷ !Int , _logFile ∷ !(Maybe String) } $(makeLenses ''LogConfig) defaultLogConfig ∷ LogConfig defaultLogConfig = LogConfig { _logLevel = 1 , _logFile = Nothing } instance FromJSON (LogConfig → LogConfig) where parseJSON = withObject "LogConfig" $ \o → id <$< logLevel ..: "LogLevel" % o <*< logFile ..: "LogConfig" % o instance ToJSON LogConfig where toJSON config = object [ "LogLevel" .= _logLevel config , "LogConfig" .= _logFile config ]
When defining command line option parsers with .::
and %::
all
options are optional. When an option is not present on the command
line the default value is used. For Maybe
values it is therefore
enough to wrap the parsed value into Just
.
pLogConfig ∷ MParser LogConfig pLogConfig = id #if MIN_VERSION_optparse-applicative(0,10,0) <$< logLevel .:: option auto #else <$< logLevel .:: option #endif % long "log-level" % metavar "INTEGER" % help "log level" <*< logFile .:: fmap Just % strOption % long "log-file" % metavar "FILENAME" % help "log file name"
Record Maybe Values
For product-type (record) Maybe
values the following orphan FromJSON
instance is provided:
instance (FromJSON (a → a), FromJSON a) ⇒ FromJSON (Maybe a → Maybe a) parseJSON Null = pure (const Nothing) parseJSON v = f <$> parseJSON v <*> parseJSON v where f g _ Nothing = Just g f _ g (Just x) = Just (g x)
(Using an orphan instance is generally problematic but convenient in this case. It's unlikely that an instance for this type is needed elsewhere. If this is an issue for you, please let me know. In that case we can define a new type for optional configuration values.)
The semantics are as follows:
- If the parsed configuration value is
Null
the result isNothing
. - If the parsed configuration value is not
Null
then the result is an update function that- updates the given default value if this value is
Just x
or - is a constant function that returns the value that is parsed
from the configuration using the
FromJSON
instance for the configuration type.
- updates the given default value if this value is
Note, that this instance requires an FromJSON
instance for the
configuration type itself as well as a FromJSON
instance for the update
function of the configuration type. The former can be defined by means of the
latter as follows:
instance FromJSON MyType where parseJSON v = parseJSON v <*> pure defaultMyType
This instance will cause the usage of defaultMyType
as default value if the
default value that is given to the configuration parser is Nothing
and the
parsed configuration is not Null
.
:: a | default value that is used if base configuration is |
-> Bool | whether to enable this parser or not (usually is a boolean option parser) |
-> (a -> a) | update function (usually given as applicative 'MParser a') |
-> Maybe a | the base value that is updated (usually the result of parsing the configuraton file) |
-> Maybe a |
Commandline parser for record Maybe
values
Example:
data Setting = Setting { _setA ∷ !Int , _setB ∷ !String } deriving (Show, Read, Eq, Ord, Typeable) $(makeLenses ''Setting) defaultSetting ∷ Setting defaultSetting = Setting { _setA = 0 , _setB = 1 } instance ToJSON Setting where toJSON setting = object [ "a" .= _setA setting , "b" .= _setB setting ] instance FromJSON (Setting → Setting) where parseJSON = withObject "Setting" $ \o → id <$< setA ..: "a" % o <*< setB ..: "b" % o instance FromJSON Setting where parseJSON v = parseJSON v <*> pure defaultSetting pSetting ∷ MParser Setting pSetting = id <$< setA .:: option auto % short 'a' <> metavar "INT" <> help "set a" <*< setB .:: option auto % short 'b' <> metavar "INT" <> help "set b" -- | Use 'Setting' as 'Maybe' in a configuration: -- data Config = Config { _maybeSetting ∷ !(Maybe Setting) } deriving (Show, Read, Eq, Ord, Typeable) $(makeLenses ''Config) defaultConfig ∷ Config defaultConfig = Config { _maybeSetting = defaultSetting } instance ToJSON Config where toJSON config = object [ "setting" .= maybeSetting ] instance FromJSON (Config → Config) where parseJSON = withObject "Config" $ \o → id <$< maybeSetting %.: "setting" % o pConfig ∷ MParser Config pConfig = id <$< maybeSetting %:: (maybeOption defaultSetting <$> pEnableSetting <*> pSetting) where pEnableSetting = boolOption % long "setting-enable" <> value False <> help "Enable configuration flags for setting"