conferer-1.0.0.1: Configuration management library
Copyright(c) 2019 Lucas David Traverso
LicenseMPL-2.0
MaintainerLucas David Traverso <lucas6246@gmail.com>
Stabilitystable
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Conferer.FromConfig

Description

Public API module providing FromConfig functionality

Synopsis

Documentation

class FromConfig a where Source #

The typeclass for defining the way to get values from a Config, hiding the Text based nature of the Sources and parse whatever value as the types sees fit

Some of these instances are provided in different packages to avoid the heavy dependencies.

It provides a reasonable default using Generics so most of the time user need not to implement this typeclass.

Minimal complete definition

Nothing

Methods

fetchFromConfig :: Key -> Config -> IO a Source #

This function uses a Config and a scoping Key to get a value.

Some conventions:

  • When some Key is missing this function should throw MissingRequiredKey
  • For any t it should hold that fetchFromConfig k (config & addDefault k t) == t meaning that a default on the same key with the right type should be used as a default and with no configuration that value should be returned
  • Try desconstructing the value in as many keys as possible since is allows easier partial overriding.

Instances

Instances details
FromConfig Bool Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig Float Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig Int Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig Integer Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig () Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fetchFromConfig :: Key -> Config -> IO () Source #

Typeable a => FromConfig a Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fetchFromConfig :: Key -> Config -> IO a Source #

FromConfig String Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig ByteString Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig ByteString Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig Text Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

(Typeable a, FromConfig a) => FromConfig [a] Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fetchFromConfig :: Key -> Config -> IO [a] Source #

(Typeable a, FromConfig a) => FromConfig (Maybe a) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fetchFromConfig :: Key -> Config -> IO (Maybe a) Source #

class DefaultConfig a where Source #

Utility only typeclass to smooth the naming differences between default values for external library settings

This typeclass is not used internally it's only here for convinience for users

Methods

configDef :: a Source #

fetchFromConfigWithDefault :: forall a. (Typeable a, FromConfig a) => Config -> Key -> a -> IO a Source #

Same as fetchFromConfig but adding a user defined default before fetchFromConfiging so it doesn't throw a MissingKeyError

fetchFromRootConfig :: forall a. FromConfig a => Config -> IO a Source #

Same as fetchFromConfig using the root key

fetchFromRootConfigWithDefault :: forall a. (Typeable a, FromConfig a) => Config -> a -> IO a Source #

Same as fetchFromConfigWithDefault using the root key

fetchFromConfigByIsString :: (Typeable a, IsString a) => Key -> Config -> IO a Source #

Helper function to implement fetchFromConfig using the IsString instance

fetchFromConfigByRead :: (Typeable a, Read a) => Key -> Config -> IO a Source #

Helper function to implement fetchFromConfig using the Read instance

fetchFromConfigWith :: forall a. Typeable a => (Text -> Maybe a) -> Key -> Config -> IO a Source #

Helper function to implement fetchFromConfig using some parsing function

addDefaultsAfterDeconstructingToDefaults Source #

Arguments

:: forall a. Typeable a 
=> (a -> [(Key, Dynamic)])

Function to deconstruct the value

-> Key

Key where to look for the value

-> Config

The config

-> IO Config 

Helper function does the plumbing of desconstructing a default into smaller defaults, which is usefull for nested fetchFromConfig.

throwMissingRequiredKey :: forall t a. Typeable t => Key -> IO a Source #

Simplified helper function to throw a MissingRequiredKey

missingRequiredKey :: forall t. Typeable t => Key -> MissingRequiredKey Source #

Simplified helper function to create a MissingRequiredKey

throwConfigParsingError :: forall a b. Typeable a => Key -> Text -> IO b Source #

Helper function to throw ConfigParsingError

configParsingError :: forall a. Typeable a => Key -> Text -> ConfigParsingError Source #

Helper function to create a ConfigParsingError

data TypeMismatchWithDefault Source #

Exception to show that the provided default had the wrong type, this is usually a programmer error and a user that configures the library can not do much to fix it.

throwTypeMismatchWithDefault :: forall a b. Typeable a => Key -> Dynamic -> IO b Source #

Helper function to throw a TypeMismatchWithDefault

data Key Source #

This type is used extensivelly as a way to point into a Source and in turn into a Config. The intended way to create them is is using mkKey.

It's a list of alphanumeric words and each Source can interpret it as it sees fit.

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Conferer.Key.Internal

Methods

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

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

Ord Key Source # 
Instance details

Defined in Conferer.Key.Internal

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Show Key Source # 
Instance details

Defined in Conferer.Key.Internal

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

IsString Key Source # 
Instance details

Defined in Conferer.Key.Internal

Methods

fromString :: String -> Key #

(/.) :: Key -> Key -> Key Source #

Concatenate two keys

newtype File Source #

A newtype wrapper for a FilePath to allow implementing FromConfig with something better than just a String

Constructors

File FilePath 

Instances

Instances details
Eq File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

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

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

Ord File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

compare :: File -> File -> Ordering #

(<) :: File -> File -> Bool #

(<=) :: File -> File -> Bool #

(>) :: File -> File -> Bool #

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

max :: File -> File -> File #

min :: File -> File -> File #

Read File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Show File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

IsString File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromString :: String -> File #

FromConfig File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

data KeyLookupResult Source #

Result of a key lookup in a Config

Instances

Instances details
Show KeyLookupResult Source # 
Instance details

Defined in Conferer.Config.Internal.Types

fetchFromDefaults :: forall a. Typeable a => Key -> Config -> IO (Maybe a) Source #

Fetch from value from the defaults map of a Config or else return a Nothing

fetchRequiredFromDefaults :: forall a. Typeable a => Key -> Config -> IO a Source #

Fetch from value from the defaults map of a Config or else throw