Copyright | (c) 2019 Lucas David Traverso |
---|---|
License | MPL-2.0 |
Maintainer | Lucas David Traverso <lucas6246@gmail.com> |
Stability | unstable |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Internal module providing FromConfig functionality
Synopsis
- class FromConfig a where
- fromConfig :: Key -> Config -> IO a
- fetchFromConfig :: forall a. (FromConfig a, Typeable a) => Key -> Config -> IO a
- class DefaultConfig a where
- configDef :: a
- newtype File = File FilePath
- unFile :: File -> FilePath
- parseBool :: Text -> Maybe Bool
- data OverrideFromConfig a = OverrideFromConfig (Key -> Config -> IO a)
- fetchFromConfigByRead :: (Typeable a, Read a) => Key -> Config -> IO a
- fetchFromConfigByIsString :: (Typeable a, IsString a) => Key -> Config -> IO a
- fetchFromConfigWith :: forall a. Typeable a => (Text -> Maybe a) -> Key -> Config -> IO a
- fromDynamics :: forall a. Typeable a => [Dynamic] -> Maybe a
- addDefaultsAfterDeconstructingToDefaults :: forall a. Typeable a => (a -> [(Key, Dynamic)]) -> Key -> Config -> IO Config
- overrideFetch :: forall a. Typeable a => (Key -> Config -> IO a) -> Dynamic
- data ConfigParsingError = ConfigParsingError Key Text TypeRep
- throwConfigParsingError :: forall a b. Typeable a => Key -> Text -> IO b
- configParsingError :: forall a. Typeable a => Key -> Text -> ConfigParsingError
- data MissingRequiredKey = MissingRequiredKey [Key] TypeRep
- throwMissingRequiredKey :: forall t a. Typeable t => Key -> IO a
- missingRequiredKey :: forall t. Typeable t => Key -> MissingRequiredKey
- throwMissingRequiredKeys :: forall t a. Typeable t => [Key] -> IO a
- missingRequiredKeys :: forall a. Typeable a => [Key] -> MissingRequiredKey
- fetchRequiredFromDefaults :: forall a. Typeable a => Key -> Config -> IO a
- fetchFromDefaults :: forall a. Typeable a => Key -> Config -> Maybe a
- fetchFromRootConfig :: forall a. (FromConfig a, Typeable a) => Config -> IO a
- fetchFromConfigWithDefault :: forall a. (Typeable a, FromConfig a) => Config -> Key -> a -> IO a
- fetchFromRootConfigWithDefault :: forall a. (Typeable a, FromConfig a) => Config -> a -> IO a
- class FromConfigG f where
- fromConfigG :: Key -> Config -> IO (f a)
- class FromConfigWithConNameG f where
- fromConfigWithConNameG :: String -> Key -> Config -> IO (f a)
- class IntoDefaultsG f where
- intoDefaultsG :: Key -> f a -> [(Key, Dynamic)]
- class IntoDefaultsWithConNameG f where
- intoDefaultsWithConNameG :: String -> Key -> f a -> [(Key, Dynamic)]
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 Source
s 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 Generic
s so most of the time user need
not to implement this typeclass.
Nothing
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 throwMissingRequiredKey
- 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
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
A newtype wrapper for a FilePath
to allow implementing FromConfig
with something better than just a String
data OverrideFromConfig a Source #
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
addDefaultsAfterDeconstructingToDefaults Source #
:: 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.
data ConfigParsingError Source #
Exception to show that a value couldn't be parsed properly
Instances
Eq ConfigParsingError Source # | |
Defined in Conferer.FromConfig.Internal (==) :: ConfigParsingError -> ConfigParsingError -> Bool # (/=) :: ConfigParsingError -> ConfigParsingError -> Bool # | |
Show ConfigParsingError Source # | |
Defined in Conferer.FromConfig.Internal showsPrec :: Int -> ConfigParsingError -> ShowS # show :: ConfigParsingError -> String # showList :: [ConfigParsingError] -> ShowS # | |
Exception ConfigParsingError Source # | |
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 MissingRequiredKey Source #
Exception to show that some non optional Key
was missing while trying
to fetchFromConfig
Instances
Eq MissingRequiredKey Source # | |
Defined in Conferer.FromConfig.Internal (==) :: MissingRequiredKey -> MissingRequiredKey -> Bool # (/=) :: MissingRequiredKey -> MissingRequiredKey -> Bool # | |
Show MissingRequiredKey Source # | |
Defined in Conferer.FromConfig.Internal showsPrec :: Int -> MissingRequiredKey -> ShowS # show :: MissingRequiredKey -> String # showList :: [MissingRequiredKey] -> ShowS # | |
Exception MissingRequiredKey Source # | |
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
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 fetchFromConfig
ing
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 Generic
s machinery, ignore...
Instances
(FromConfig inner, Typeable inner) => FromConfigG (Rec0 inner) Source # | |
Defined in Conferer.FromConfig.Internal | |
FromConfigG inner => FromConfigG (D1 metadata inner) Source # | |
Defined in Conferer.FromConfig.Internal | |
(FromConfigWithConNameG inner, Constructor constructor) => FromConfigG (C1 constructor inner) Source # | |
Defined in Conferer.FromConfig.Internal |
class FromConfigWithConNameG f where Source #
Purely Generic
s machinery, ignore...
Instances
(FromConfigWithConNameG left, FromConfigWithConNameG right) => FromConfigWithConNameG (left :*: right) Source # | |
Defined in Conferer.FromConfig.Internal | |
(FromConfigG inner, Selector selector) => FromConfigWithConNameG (S1 selector inner) Source # | |
Defined in Conferer.FromConfig.Internal |
class IntoDefaultsG f where Source #
Purely Generic
s machinery, ignore...
Instances
Typeable inner => IntoDefaultsG (Rec0 inner) Source # | |
Defined in Conferer.FromConfig.Internal | |
IntoDefaultsG inner => IntoDefaultsG (D1 metadata inner) Source # | |
Defined in Conferer.FromConfig.Internal | |
(IntoDefaultsWithConNameG inner, Constructor constructor) => IntoDefaultsG (C1 constructor inner) Source # | |
Defined in Conferer.FromConfig.Internal |
class IntoDefaultsWithConNameG f where Source #
Purely Generic
s machinery, ignore...
Instances
(IntoDefaultsWithConNameG left, IntoDefaultsWithConNameG right) => IntoDefaultsWithConNameG (left :*: right) Source # | |
Defined in Conferer.FromConfig.Internal | |
(IntoDefaultsG inner, Selector selector) => IntoDefaultsWithConNameG (S1 selector inner) Source # | |
Defined in Conferer.FromConfig.Internal |