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

Conferer.FromConfig.Internal

Description

Internal 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

fromConfig :: 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.

default fromConfig :: (Typeable a, Generic a, IntoDefaultsG (Rep a), FromConfigG (Rep a)) => Key -> Config -> IO a Source #

Instances

Instances details
FromConfig Bool Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfig :: Key -> Config -> IO Bool Source #

FromConfig Float Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfig :: Key -> Config -> IO Float Source #

FromConfig Int Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfig :: Key -> Config -> IO Int Source #

FromConfig Integer Source # 
Instance details

Defined in Conferer.FromConfig.Internal

FromConfig () Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

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

Typeable a => FromConfig a Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfig :: 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

Methods

fromConfig :: Key -> Config -> IO Text Source #

FromConfig File Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfig :: Key -> Config -> IO File Source #

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

Defined in Conferer.FromConfig.Internal

Methods

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

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

Defined in Conferer.FromConfig.Internal

Methods

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

fetchFromConfig :: forall a. (FromConfig a, Typeable a) => Key -> Config -> IO 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 #

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

Methods

fromConfig :: Key -> Config -> IO File Source #

parseBool :: Text -> Maybe Bool Source #

Helper function to parse a Bool from Text

data OverrideFromConfig a Source #

Constructors

OverrideFromConfig (Key -> Config -> IO a) 

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

Allow the programmer to override this FromConfig instance by providing a special OverrideFromConfig value.

To avoid infinite recursion we remove the Override before calling the value

Helper function to implement fetchFromConfig using the Read instance

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

Helper function to implement fetchFromConfig using the IsString instance

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

Helper function to implement fetchFromConfig using some parsing function

fromDynamics :: forall a. Typeable a => [Dynamic] -> Maybe a Source #

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.

overrideFetch :: forall a. Typeable a => (Key -> Config -> IO a) -> Dynamic Source #

Helper function to override the fetching function for a certain key.

This function creates a Dynamic that when added to the defaults allows overriding the default FromConfig instance.

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

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

throwMissingRequiredKeys :: forall t a. Typeable t => [Key] -> IO a Source #

Helper function to throw a MissingRequiredKey

missingRequiredKeys :: forall a. Typeable a => [Key] -> MissingRequiredKey Source #

Helper function to create a MissingRequiredKey

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

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

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

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

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

Same as fetchFromConfig using the root key

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

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

Same as fetchFromConfigWithDefault using the root key

class FromConfigG f where Source #

Purely Generics machinery, ignore...

Methods

fromConfigG :: Key -> Config -> IO (f a) Source #

Instances

Instances details
(FromConfig inner, Typeable inner) => FromConfigG (Rec0 inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfigG :: Key -> Config -> IO (Rec0 inner a) Source #

FromConfigG inner => FromConfigG (D1 metadata inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfigG :: Key -> Config -> IO (D1 metadata inner a) Source #

(FromConfigWithConNameG inner, Constructor constructor) => FromConfigG (C1 constructor inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfigG :: Key -> Config -> IO (C1 constructor inner a) Source #

class FromConfigWithConNameG f where Source #

Purely Generics machinery, ignore...

Methods

fromConfigWithConNameG :: String -> Key -> Config -> IO (f a) Source #

Instances

Instances details
(FromConfigWithConNameG left, FromConfigWithConNameG right) => FromConfigWithConNameG (left :*: right) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfigWithConNameG :: String -> Key -> Config -> IO ((left :*: right) a) Source #

(FromConfigG inner, Selector selector) => FromConfigWithConNameG (S1 selector inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

fromConfigWithConNameG :: String -> Key -> Config -> IO (S1 selector inner a) Source #

class IntoDefaultsG f where Source #

Purely Generics machinery, ignore...

Methods

intoDefaultsG :: Key -> f a -> [(Key, Dynamic)] Source #

Instances

Instances details
Typeable inner => IntoDefaultsG (Rec0 inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

intoDefaultsG :: Key -> Rec0 inner a -> [(Key, Dynamic)] Source #

IntoDefaultsG inner => IntoDefaultsG (D1 metadata inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

intoDefaultsG :: Key -> D1 metadata inner a -> [(Key, Dynamic)] Source #

(IntoDefaultsWithConNameG inner, Constructor constructor) => IntoDefaultsG (C1 constructor inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

intoDefaultsG :: Key -> C1 constructor inner a -> [(Key, Dynamic)] Source #

class IntoDefaultsWithConNameG f where Source #

Purely Generics machinery, ignore...

Methods

intoDefaultsWithConNameG :: String -> Key -> f a -> [(Key, Dynamic)] Source #

Instances

Instances details
(IntoDefaultsWithConNameG left, IntoDefaultsWithConNameG right) => IntoDefaultsWithConNameG (left :*: right) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

intoDefaultsWithConNameG :: String -> Key -> (left :*: right) a -> [(Key, Dynamic)] Source #

(IntoDefaultsG inner, Selector selector) => IntoDefaultsWithConNameG (S1 selector inner) Source # 
Instance details

Defined in Conferer.FromConfig.Internal

Methods

intoDefaultsWithConNameG :: String -> Key -> S1 selector inner a -> [(Key, Dynamic)] Source #