| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Etc
Synopsis
- data Config
- class IConfig config
- data Value a
- getConfigValue :: (IConfig config, MonadThrow m, FromJSON result) => [Text] -> config -> m result
- getConfigValueWith :: (IConfig config, MonadThrow m) => (Value -> Parser result) -> [Text] -> config -> m result
- getSelectedConfigSource :: (IConfig config, MonadThrow m) => [Text] -> config -> m ConfigSource
- getAllConfigSources :: (IConfig config, MonadThrow m) => [Text] -> config -> m (Set ConfigSource)
- data ConfigSource
- data ConfigValue
- data ConfigSpec cmd
- parseConfigSpec :: MonadThrow m => Text -> m (ConfigSpec ())
- readConfigSpec :: Text -> IO (ConfigSpec ())
- readConfigSpecTH :: (Lift k, FromJSON k) => Proxy k -> Text -> ExpQ
- newtype InvalidConfigKeyPath = InvalidConfigKeyPath {}
- data ConfigValueParserFailed = ConfigValueParserFailed {
- inputKeys :: ![Text]
- parserErrorMessage :: !Text
- data UnknownConfigKeyFound = UnknownConfigKeyFound {
- parentKeys :: ![Text]
- keyName :: !Text
- siblingKeys :: ![Text]
- data SubConfigEntryExpected = SubConfigEntryExpected {
- keyName :: !Text
- configValue :: !Value
- data ConfigValueTypeMismatchFound = ConfigValueTypeMismatchFound {}
- newtype ConfigurationFileNotFound = ConfigurationFileNotFound {}
- newtype UnsupportedFileExtensionGiven = UnsupportedFileExtensionGiven {}
- data ConfigInvalidSyntaxFound = ConfigInvalidSyntaxFound {
- configFilepath :: !Text
- parserErrorMessage :: !Text
- data SpecInvalidSyntaxFound = SpecInvalidSyntaxFound {
- specFilepath :: !(Maybe Text)
- parseErrorMessage :: !Text
- resolveDefault :: ConfigSpec cmd -> Config
- resolveFiles :: ConfigSpec cmd -> IO (Config, Vector SomeException)
- resolveEnvPure :: ConfigSpec cmd -> [(Text, Text)] -> Config
- resolveEnv :: ConfigSpec cmd -> IO Config
Config
Use this functions to fetch values from the Etc.Config and cast them to types that make sense in your program
Instances
| Eq Config Source # | |
| Show Config Source # | |
| Semigroup Config Source # | |
| Monoid Config Source # | |
| IConfig Config Source # | |
Defined in System.Etc.Internal.Config Methods getConfigValue :: (MonadThrow m, FromJSON result) => [Text] -> Config -> m result Source # getConfigValueWith :: MonadThrow m => (Value -> Parser result) -> [Text] -> Config -> m result Source # getAllConfigSources :: MonadThrow m => [Text] -> Config -> m (Set ConfigSource) Source # getSelectedConfigSource :: MonadThrow m => [Text] -> Config -> m ConfigSource Source # | |
Minimal complete definition
getConfigValue, getConfigValueWith, getAllConfigSources, getSelectedConfigSource
Instances
| IConfig Config Source # | |
Defined in System.Etc.Internal.Config Methods getConfigValue :: (MonadThrow m, FromJSON result) => [Text] -> Config -> m result Source # getConfigValueWith :: MonadThrow m => (Value -> Parser result) -> [Text] -> Config -> m result Source # getAllConfigSources :: MonadThrow m => [Text] -> Config -> m (Set ConfigSource) Source # getSelectedConfigSource :: MonadThrow m => [Text] -> Config -> m ConfigSource Source # | |
Instances
| Functor Value Source # | |
| Applicative Value Source # | |
| Eq a => Eq (Value a) Source # | |
| Ord a => Ord (Value a) Source # | |
Defined in System.Etc.Internal.Types | |
| Show a => Show (Value a) Source # | |
| IsString a => IsString (Value a) Source # | |
Defined in System.Etc.Internal.Types Methods fromString :: String -> Value a # | |
| Generic (Value a) Source # | |
| type Rep (Value a) Source # | |
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))) | |
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 TextJust "root">>>getConfigValue ["db", "password"] config :: Maybe TextNothing
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"] configJust (DbConnectInfo {...})
getSelectedConfigSource :: (IConfig config, MonadThrow m) => [Text] -> config -> m ConfigSource Source #
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 ConfigSource Source #
Constructors
| File | |
Fields
| |
| Env | |
| Cli | |
| Default | |
| None | |
Instances
| Eq ConfigSource Source # | |
Defined in System.Etc.Internal.Types | |
| Ord ConfigSource Source # | |
Defined in System.Etc.Internal.Types Methods compare :: ConfigSource -> ConfigSource -> Ordering # (<) :: ConfigSource -> ConfigSource -> Bool # (<=) :: ConfigSource -> ConfigSource -> Bool # (>) :: ConfigSource -> ConfigSource -> Bool # (>=) :: ConfigSource -> ConfigSource -> Bool # max :: ConfigSource -> ConfigSource -> ConfigSource # min :: ConfigSource -> ConfigSource -> ConfigSource # | |
| Show ConfigSource Source # | |
Defined in System.Etc.Internal.Types Methods showsPrec :: Int -> ConfigSource -> ShowS # show :: ConfigSource -> String # showList :: [ConfigSource] -> ShowS # | |
data ConfigValue Source #
Instances
| Eq ConfigValue Source # | |
Defined in System.Etc.Internal.Types | |
| Show ConfigValue Source # | |
Defined in System.Etc.Internal.Types Methods showsPrec :: Int -> ConfigValue -> ShowS # show :: ConfigValue -> String # showList :: [ConfigValue] -> ShowS # | |
| Semigroup ConfigValue Source # | |
Defined in System.Etc.Internal.Types Methods (<>) :: ConfigValue -> ConfigValue -> ConfigValue # sconcat :: NonEmpty ConfigValue -> ConfigValue # stimes :: Integral b => b -> ConfigValue -> ConfigValue # | |
| Monoid ConfigValue Source # | |
Defined in System.Etc.Internal.Types Methods mempty :: ConfigValue # mappend :: ConfigValue -> ConfigValue -> ConfigValue # mconcat :: [ConfigValue] -> ConfigValue # | |
data ConfigSpec cmd Source #
Instances
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).
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 | |
Instances
data ConfigValueParserFailed Source #
Thrown when there is a type mismatch in a JSON parser given via
getConfigWith
Constructors
| ConfigValueParserFailed | |
Fields
| |
Instances
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
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
data ConfigValueTypeMismatchFound Source #
This error is thrown when a type mismatch is found in a raw value when
calling resolveFile
Constructors
| ConfigValueTypeMismatchFound | |
Fields
| |
Instances
newtype ConfigurationFileNotFound Source #
Thrown when a specified configuration file is not found in the system
Constructors
| ConfigurationFileNotFound | |
Fields
| |
Instances
newtype UnsupportedFileExtensionGiven Source #
Thrown when an input configuration file contains an unsupported file extension
Constructors
| UnsupportedFileExtensionGiven | |
Fields
| |
Instances
| Eq UnsupportedFileExtensionGiven Source # | |
Defined in System.Etc.Internal.Errors | |
| Read UnsupportedFileExtensionGiven Source # | |
| Show UnsupportedFileExtensionGiven Source # | |
Defined in System.Etc.Internal.Errors Methods showsPrec :: Int -> UnsupportedFileExtensionGiven -> ShowS # show :: UnsupportedFileExtensionGiven -> String # showList :: [UnsupportedFileExtensionGiven] -> ShowS # | |
| Generic UnsupportedFileExtensionGiven Source # | |
Defined in System.Etc.Internal.Errors Associated Types type Rep UnsupportedFileExtensionGiven :: * -> * # | |
| Exception UnsupportedFileExtensionGiven Source # | |
| type Rep UnsupportedFileExtensionGiven Source # | |
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
data SpecInvalidSyntaxFound Source #
Thrown when an configuration spec file contains invalid syntax
Constructors
| SpecInvalidSyntaxFound | |
Fields
| |
Instances
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
Arguments
| :: ConfigSpec cmd | ConfigSpec |
| -> Config | returns Configuration Map with default values included |
Gathers all default values from the etc/spec entries inside a ConfigSpec
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.
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.
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