etc-0.4.0.0: Declarative configuration spec for Haskell projects

Safe HaskellNone
LanguageHaskell2010

System.Etc

Contents

Synopsis

Config

Use this functions to fetch values from the Etc.Config and cast them to types that make sense in your program

class IConfig config where Source #

Methods

getConfigValue Source #

Arguments

:: (MonadThrow m, FromJSON result) 
=> [Text]

Key to fetch from config map

-> config

Config record

-> m result 

Fetches a configuration value from a given key, if key is not found, you may pick the failure mode via the MonadThrow interface.

example:

>>> getConfigValue ["db", "user"] config :: Maybe Text
Just "root"
>>> getConfigValue ["db", "password"] config :: Maybe Text
Nothing

getConfigValueWith Source #

Arguments

:: MonadThrow m 
=> (Value -> Parser result)

JSON Parser function

-> [Text]

Key to fetch from config map

-> config

Config record

-> m result 

Fetches a configuration value from a given key, normally this key will point to a sub-config JSON object, which is then passed to the given JSON parser function. If key is not found, you may pick the failure mode via the MonadThrow interface.

example:

>>> import qualified Data.Aeson as JSON
>>> import qualified Data.Aeson.Types as JSON (Parser)
>>> connectInfoParser :: JSON.Value -> JSON.Parser DbConnectInfo
>>> getConfigValueWith connectInfoParser ["db"] config
Just (DbConnectInfo {...})

getAllConfigSources :: MonadThrow m => [Text] -> config -> m (Set ConfigSource) Source #

getSelectedConfigSource :: MonadThrow m => [Text] -> config -> m ConfigSource Source #

data Value a Source #

Constructors

Plain 

Fields

Sensitive 

Fields

Instances

Functor Value Source # 

Methods

fmap :: (a -> b) -> Value a -> Value b #

(<$) :: a -> Value b -> Value a #

Applicative Value Source # 

Methods

pure :: a -> Value a #

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

liftA2 :: (a -> b -> c) -> Value a -> Value b -> Value c #

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

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

Eq a => Eq (Value a) Source # 

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

Ord a => Ord (Value a) Source # 

Methods

compare :: Value a -> Value a -> Ordering #

(<) :: Value a -> Value a -> Bool #

(<=) :: Value a -> Value a -> Bool #

(>) :: Value a -> Value a -> Bool #

(>=) :: Value a -> Value a -> Bool #

max :: Value a -> Value a -> Value a #

min :: Value a -> Value a -> Value a #

Show a => Show (Value a) Source # 

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

IsString a => IsString (Value a) Source # 

Methods

fromString :: String -> Value a #

Generic (Value a) Source # 

Associated Types

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

Methods

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

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

type Rep (Value a) Source # 
type Rep (Value a) = D1 * (MetaData "Value" "System.Etc.Internal.Types" "etc-0.4.0.0-81A0mhdZGGC90miJOhFWd1" False) ((:+:) * (C1 * (MetaCons "Plain" PrefixI True) (S1 * (MetaSel (Just Symbol "fromValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))) (C1 * (MetaCons "Sensitive" PrefixI True) (S1 * (MetaSel (Just Symbol "fromValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))))

getConfigValue Source #

Arguments

:: (IConfig config, MonadThrow m, FromJSON result) 
=> [Text]

Key to fetch from config map

-> config

Config record

-> m result 

Fetches a configuration value from a given key, if key is not found, you may pick the failure mode via the MonadThrow interface.

example:

>>> getConfigValue ["db", "user"] config :: Maybe Text
Just "root"
>>> getConfigValue ["db", "password"] config :: Maybe Text
Nothing

getConfigValueWith Source #

Arguments

:: (IConfig config, MonadThrow m) 
=> (Value -> Parser result)

JSON Parser function

-> [Text]

Key to fetch from config map

-> config

Config record

-> m result 

Fetches a configuration value from a given key, normally this key will point to a sub-config JSON object, which is then passed to the given JSON parser function. If key is not found, you may pick the failure mode via the MonadThrow interface.

example:

>>> import qualified Data.Aeson as JSON
>>> import qualified Data.Aeson.Types as JSON (Parser)
>>> connectInfoParser :: JSON.Value -> JSON.Parser DbConnectInfo
>>> getConfigValueWith connectInfoParser ["db"] config
Just (DbConnectInfo {...})

getAllConfigSources :: (IConfig config, MonadThrow m) => [Text] -> config -> m (Set ConfigSource) Source #

ConfigSpec

Use this functions to read the configuration spec. Remember you can use JSON or YAML(*) filepaths

  • The yaml cabal flag must be used to support yaml syntax

data ConfigSpec cmd Source #

Instances

Eq cmd => Eq (ConfigSpec cmd) Source # 

Methods

(==) :: ConfigSpec cmd -> ConfigSpec cmd -> Bool #

(/=) :: ConfigSpec cmd -> ConfigSpec cmd -> Bool #

Show cmd => Show (ConfigSpec cmd) Source # 

Methods

showsPrec :: Int -> ConfigSpec cmd -> ShowS #

show :: ConfigSpec cmd -> String #

showList :: [ConfigSpec cmd] -> ShowS #

FromJSON cmd => FromJSON (ConfigSpec cmd) Source # 

data ConfigurationError Source #

parseConfigSpec Source #

Arguments

:: MonadThrow m 
=> Text

Text to be parsed

-> m (ConfigSpec ())

returns ConfigSpec

Parses a text input into a ConfigSpec, input can be JSON or YAML (if cabal flag is set).

readConfigSpec Source #

Arguments

:: Text

Filepath where contents are going to be read from and parsed

-> IO (ConfigSpec ())

returns ConfigSpec

Reads contents of a file and parses into a ConfigSpec, file contents can be either JSON or YAML (if cabal flag is set).

Resolvers

Use this functions to gather configuration values from different sources (environment variables, command lines or files). Then compose results together using the mappend function

resolveDefault Source #

Arguments

:: ConfigSpec cmd

ConfigSpec

-> Config

returns Configuration Map with default values included

Gathers all default values from the etc/spec entries inside a ConfigSpec

resolveFiles Source #

Arguments

:: ConfigSpec cmd

Config Spec

-> IO (Config, Vector SomeException)

Configuration Map with all values from files filled in and a list of warnings

Gathers configuration values from a list of files specified on the etc/filepaths entry of a Config Spec. This will return a Configuration Map with values from all filepaths merged in, and a list of errors in case there was an error reading one of the filepaths.

resolveEnvPure Source #

Arguments

:: ConfigSpec cmd

ConfigSpec

-> [(Text, Text)]

Environment Variable tuples

-> Config

returns Configuration Map with Environment Variables values filled in

Gathers all OS Environment Variable values (env entries) from the etc/spec entries inside a ConfigSpec. This version of the function gathers the input from a list of tuples rather than the OS.

resolveEnv Source #

Arguments

:: ConfigSpec cmd

Config Spec

-> IO Config

returns Configuration Map with Environment Variables values filled in

Gathers all OS Environment Variable values (env entries) from the etc/spec entries inside a ConfigSpec