configuration-tools-0.2.2: Tools for specifying and parsing configurations

Safe HaskellNone

Configuration.Utils

Contents

Description

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:

  1. a default value,
  2. a FromJSON instance that yields a function that takes a value and updates that value with the parsed values,
  3. a ToJSON instance, and
  4. an options parser that yields a function that takes a value and updates that value with the values provided as command line options.

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.

Synopsis

Program Configuration

programInfo :: String -> MParser α -> α -> ProgramInfo αSource

Smart constructor for ProgramInfo.

piHelpHeader and piHelpFooter are set to Nothing.

piDescription :: Lens' (ProgramInfo α) StringSource

Program Description

piOptionParser :: Lens' (ProgramInfo α) (MParser α)Source

options parser for configuration (TODO consider using a typeclass for this)

piDefaultConfiguration :: Lens' (ProgramInfo α) αSource

default configuration

piOptionParserAndDefaultConfiguration :: Lens (ProgramInfo α) (ProgramInfo β) (MParser α, α) (MParser β, β)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

runWithConfiguration :: (FromJSON (α -> α), ToJSON α) => ProgramInfo α -> (α -> IO ()) -> IO ()Source

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 :: (FromJSON (α -> α), ToJSON α) => ProgramInfo α -> PkgInfo -> (α -> IO ()) -> IO ()Source

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-inf
Print a detailed info message for the application and exit.
--license
Print the text of the lincense of the application and exit.

Applicative Option Parsing with Default Values

type MParser α = Parser (α -> α)Source

Type of option parsers that yield a modification function.

(.::) :: (Alternative φ, Applicative φ) => Lens' α β -> φ β -> φ (α -> α)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 → φ Au user f s = (\u → s { _user = u }) <$> f (_user s)
 pwd ∷ Functor φ ⇒ (String → φ String) → Auth → φ Au 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' α β -> φ (β -> β) -> φ (α -> α)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 → φ HttpU auth f s = (\u → s { _auth = u }) <$> f (_auth s)
 domain ∷ Functor φ ⇒ (String → φ String) → HttpURL → φ HttpU domain f s = (\u → s { _domain = u }) <$> f (_domain s)
 path ∷ Functor φ ⇒ (String → φ String) → HttpURL → φ HttpU 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"

Parsing of Configuration Files with Default Values

setPropertySource

Arguments

:: Lens' α β

Lens that into the target that is updated by the parser

-> Text

the JSON property name

-> (Value -> Parser β)

the JSON Value parser that is used to parse the value of the property

-> Object

the parsed JSON Value 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 → φ Au userId f s = (\u → s { _userId = u }) <$> f (_userId s)
 pwd ∷ Functor φ ⇒ (String → φ String) → Auth → φ Au 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 → faile $ "unrecognized user " ⊕ 

(..:) :: FromJSON β => Lens' α β -> Text -> Object -> Parser (α -> α)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 → φ Au user f s = (\u → s { _user = u }) <$> f (_user s)
 pwd ∷ Functor φ ⇒ (String → φ String) → Auth → φ Au 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

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 → φ HttpU auth f s = (\u → s { _auth = u }) <$> f (_auth s)
 domain ∷ Functor φ ⇒ (String → φ String) → HttpURL → φ HttpU domain f s = (\u → s { _domain = u }) <$> f (_domain s)
 path ∷ Functor φ ⇒ (String → φ String) → HttpURL → φ HttpU 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

Misc Utils

(%) :: (α -> β) -> α -> βSource

This operator is an alternative for $ with a higher precedence which makes it suitable for usage within Applicative style funtors without the need to add parenthesis.

(×) :: (α -> β) -> α -> βSource

This operator is a UTF-8 version of % which is an alternative for $ with a higher precedence which makes it suitable for usage within Applicative style funtors 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 φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ)Source

Functional composition for applicative functors.

(>*>) :: Applicative φ => φ (α -> β) -> φ (β -> γ) -> φ (α -> γ)Source

Functional composition for applicative functors with its arguments flipped.

(<$<) :: Functor φ => (β -> γ) -> φ (α -> β) -> φ (α -> γ)Source

Applicative functional composition between a pure function and an applicative function.

(>$>) :: Functor φ => φ (α -> β) -> (β -> γ) -> φ (α -> γ)Source

Applicative functional composition between a pure function and an applicative function with its arguments flipped.

(<.>) :: Applicative φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ)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 φ => φ (β -> γ) -> φ (α -> β) -> φ (α -> γ)Source

Deprecated: use <*< instead

For people who like nicely aligned code and do not mind messing with editor key-maps: here a version of <.> that uses a unicode symbol

The hex value of the UTF-8 character ⊙ is 0x2299.

A convenient VIM key-map is:

 iabbrev <buffer> ../ ⊙

type Lens' σ α = Lens σ σ α αSource

This is the same type as the type from the lens library with the same name.

type Lens σ τ α β = Functor φ => (α -> φ β) -> σ -> φ τSource

This is the same type as the type from the lens library with the same name.

Configuration of Optional Values

Optional configuration values are supposed to be encoded by wrapping the respective type with Maybe.

For this 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 is Nothing. * 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.

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.

Reexports

module Data.Aeson