etc-0.4.1.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

data Config Source #

Instances
Eq Config Source # 
Instance details

Defined in System.Etc.Internal.Types

Methods

(==) :: Config -> Config -> Bool #

(/=) :: Config -> Config -> Bool #

Show Config Source # 
Instance details

Defined in System.Etc.Internal.Types

Semigroup Config Source # 
Instance details

Defined in System.Etc.Internal.Types

Monoid Config Source # 
Instance details

Defined in System.Etc.Internal.Types

IConfig Config Source # 
Instance details

Defined in System.Etc.Internal.Config

data Value a Source #

Constructors

Plain 

Fields

Sensitive 

Fields

Instances
Functor Value Source # 
Instance details

Defined in System.Etc.Internal.Types

Methods

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

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

Applicative Value Source # 
Instance details

Defined in System.Etc.Internal.Types

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 # 
Instance details

Defined in System.Etc.Internal.Types

Methods

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

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

Ord a => Ord (Value a) Source # 
Instance details

Defined in System.Etc.Internal.Types

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 # 
Instance details

Defined in System.Etc.Internal.Types

Methods

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

show :: Value a -> String #

showList :: [Value a] -> ShowS #

IsString a => IsString (Value a) Source # 
Instance details

Defined in System.Etc.Internal.Types

Methods

fromString :: String -> Value a #

Generic (Value a) Source # 
Instance details

Defined in System.Etc.Internal.Types

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 # 
Instance details

Defined in System.Etc.Internal.Types

type Rep (Value a) = D1 (MetaData "Value" "System.Etc.Internal.Types" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "Plain" PrefixI True) (S1 (MetaSel (Just "fromValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 a)) :+: C1 (MetaCons "Sensitive" PrefixI True) (S1 (MetaSel (Just "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 # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

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

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

Show cmd => Show (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

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

show :: ConfigSpec cmd -> String #

showList :: [ConfigSpec cmd] -> ShowS #

Generic (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Associated Types

type Rep (ConfigSpec cmd) :: * -> * #

Methods

from :: ConfigSpec cmd -> Rep (ConfigSpec cmd) x #

to :: Rep (ConfigSpec cmd) x -> ConfigSpec cmd #

Lift cmd => Lift (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

lift :: ConfigSpec cmd -> Q Exp #

FromJSON cmd => FromJSON (ConfigSpec cmd) # 
Instance details

Defined in System.Etc.Internal.Spec.Parser

type Rep (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

type Rep (ConfigSpec cmd) = D1 (MetaData "ConfigSpec" "System.Etc.Internal.Spec.Types" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "ConfigSpec" PrefixI True) (S1 (MetaSel (Just "specConfigFilepaths") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilesSpec)) :*: (S1 (MetaSel (Just "specCliProgramSpec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CliProgramSpec)) :*: S1 (MetaSel (Just "specConfigValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Text (ConfigValue cmd))))))

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).

readConfigSpecTH :: (Lift k, FromJSON k) => Proxy k -> Text -> ExpQ Source #

Reads a specified FilePath and parses a ConfigSpec at compilation time.

Exceptions

newtype InvalidConfigKeyPath Source #

Thrown when calling the getConfig or getConfigWith functions on a key that does not exist in the configuration spec

Constructors

InvalidConfigKeyPath 

Fields

Instances
Eq InvalidConfigKeyPath Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read InvalidConfigKeyPath Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show InvalidConfigKeyPath Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic InvalidConfigKeyPath Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep InvalidConfigKeyPath :: * -> * #

Exception InvalidConfigKeyPath Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep InvalidConfigKeyPath Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep InvalidConfigKeyPath = D1 (MetaData "InvalidConfigKeyPath" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" True) (C1 (MetaCons "InvalidConfigKeyPath" PrefixI True) (S1 (MetaSel (Just "inputKeys") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])))

data ConfigValueParserFailed Source #

Thrown when there is a type mismatch in a JSON parser given via getConfigWith

Constructors

ConfigValueParserFailed 

Fields

Instances
Eq ConfigValueParserFailed Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read ConfigValueParserFailed Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show ConfigValueParserFailed Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic ConfigValueParserFailed Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep ConfigValueParserFailed :: * -> * #

Exception ConfigValueParserFailed Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigValueParserFailed Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigValueParserFailed = D1 (MetaData "ConfigValueParserFailed" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "ConfigValueParserFailed" PrefixI True) (S1 (MetaSel (Just "inputKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: S1 (MetaSel (Just "parserErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data UnknownConfigKeyFound Source #

Thrown when the resolveFile function finds a key on a configuration file that is not specified in the given configuration spec

Constructors

UnknownConfigKeyFound 

Fields

Instances
Eq UnknownConfigKeyFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read UnknownConfigKeyFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show UnknownConfigKeyFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic UnknownConfigKeyFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep UnknownConfigKeyFound :: * -> * #

Exception UnknownConfigKeyFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep UnknownConfigKeyFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep UnknownConfigKeyFound = D1 (MetaData "UnknownConfigKeyFound" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "UnknownConfigKeyFound" PrefixI True) (S1 (MetaSel (Just "parentKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]) :*: (S1 (MetaSel (Just "keyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "siblingKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 [Text]))))

data SubConfigEntryExpected Source #

Thrown when there is a type mismatch on a configuration entry, specifically, when there is a raw value instead of a sub-config in a configuration file

Constructors

SubConfigEntryExpected 

Fields

Instances
Eq SubConfigEntryExpected Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read SubConfigEntryExpected Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show SubConfigEntryExpected Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic SubConfigEntryExpected Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep SubConfigEntryExpected :: * -> * #

Exception SubConfigEntryExpected Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep SubConfigEntryExpected Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep SubConfigEntryExpected = D1 (MetaData "SubConfigEntryExpected" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "SubConfigEntryExpected" PrefixI True) (S1 (MetaSel (Just "keyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "configValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Value)))

data ConfigValueTypeMismatchFound Source #

This error is thrown when a type mismatch is found in a raw value when calling resolveFile

Constructors

ConfigValueTypeMismatchFound 

Fields

Instances
Eq ConfigValueTypeMismatchFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read ConfigValueTypeMismatchFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show ConfigValueTypeMismatchFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic ConfigValueTypeMismatchFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep ConfigValueTypeMismatchFound :: * -> * #

Exception ConfigValueTypeMismatchFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigValueTypeMismatchFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigValueTypeMismatchFound = D1 (MetaData "ConfigValueTypeMismatchFound" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "ConfigValueTypeMismatchFound" PrefixI True) (S1 (MetaSel (Just "keyName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: (S1 (MetaSel (Just "configValueEntry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Value) :*: S1 (MetaSel (Just "configValueEntryType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ConfigValueType))))

newtype ConfigurationFileNotFound Source #

Thrown when a specified configuration file is not found in the system

Constructors

ConfigurationFileNotFound 

Fields

Instances
Eq ConfigurationFileNotFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read ConfigurationFileNotFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show ConfigurationFileNotFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic ConfigurationFileNotFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep ConfigurationFileNotFound :: * -> * #

Exception ConfigurationFileNotFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigurationFileNotFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigurationFileNotFound = D1 (MetaData "ConfigurationFileNotFound" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" True) (C1 (MetaCons "ConfigurationFileNotFound" PrefixI True) (S1 (MetaSel (Just "configFilepath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

newtype UnsupportedFileExtensionGiven Source #

Thrown when an input configuration file contains an unsupported file extension

Constructors

UnsupportedFileExtensionGiven 

Fields

Instances
Eq UnsupportedFileExtensionGiven Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read UnsupportedFileExtensionGiven Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show UnsupportedFileExtensionGiven Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic UnsupportedFileExtensionGiven Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep UnsupportedFileExtensionGiven :: * -> * #

Exception UnsupportedFileExtensionGiven Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep UnsupportedFileExtensionGiven Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep UnsupportedFileExtensionGiven = D1 (MetaData "UnsupportedFileExtensionGiven" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" True) (C1 (MetaCons "UnsupportedFileExtensionGiven" PrefixI True) (S1 (MetaSel (Just "configFilepath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data ConfigInvalidSyntaxFound Source #

Thrown when an input configuration file contains invalid syntax

Constructors

ConfigInvalidSyntaxFound 

Fields

Instances
Eq ConfigInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read ConfigInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show ConfigInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic ConfigInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep ConfigInvalidSyntaxFound :: * -> * #

Exception ConfigInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep ConfigInvalidSyntaxFound = D1 (MetaData "ConfigInvalidSyntaxFound" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "ConfigInvalidSyntaxFound" PrefixI True) (S1 (MetaSel (Just "configFilepath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "parserErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

data SpecInvalidSyntaxFound Source #

Thrown when an configuration spec file contains invalid syntax

Constructors

SpecInvalidSyntaxFound 

Fields

Instances
Eq SpecInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Read SpecInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Show SpecInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Generic SpecInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

Associated Types

type Rep SpecInvalidSyntaxFound :: * -> * #

Exception SpecInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep SpecInvalidSyntaxFound Source # 
Instance details

Defined in System.Etc.Internal.Errors

type Rep SpecInvalidSyntaxFound = D1 (MetaData "SpecInvalidSyntaxFound" "System.Etc.Internal.Errors" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "SpecInvalidSyntaxFound" PrefixI True) (S1 (MetaSel (Just "specFilepath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "parseErrorMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

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