Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Conferer.Types
Synopsis
- data Source = Source {
- getKeyInSource :: Key -> IO (Maybe Text)
- newtype Key = Path {}
- keyName :: Key -> Text
- data Config = Config {}
- type SourceCreator = Config -> IO Source
- keyNotPresentError :: forall a. Typeable a => Key -> Proxy a -> FailedToFetchError
- class DefaultConfig a where
- configDef :: a
- class FromConfig a where
- updateFromConfig :: Key -> Config -> a -> IO a
- fetchFromConfig :: Key -> Config -> IO (Maybe a)
- class FromConfigG f where
- updateFromConfigG :: Key -> Config -> f a -> IO (f a)
- fetchFromConfigG :: Key -> Config -> IO (Maybe (f a))
- data ConfigParsingError = ConfigParsingError Key Text TypeRep
- data FailedToFetchError = FailedToFetchError Key TypeRep
Documentation
Core interface for library provided configuration, basically consists of
getting a Key
and informing returning a maybe signaling the value and
if it's present in that specific source
The way to index Source
s, basically list of names that will be adapted
to whatever the source needs
Core type that the user of this library interact with, in the future it may contain more this besides a list of sources
type SourceCreator = Config -> IO Source Source #
The type for creating a source given a Config
, some sources require a
certain configuration to be initialized (for example: the redis source
needs connection info to connect to the server)
keyNotPresentError :: forall a. Typeable a => Key -> Proxy a -> FailedToFetchError Source #
class DefaultConfig a where Source #
Default defining instance
Here a Nothing
means that the value didn't appear in the config, some
instances never return a value since they have defaults that can never
fail
Instances
DefaultConfig (Maybe a) Source # | |
Defined in Conferer.FromConfig.Basics |
class FromConfig a where Source #
Main typeclass for defining the way to get values from config, hiding the
Text
based nature of the Source
s.
updated using a config, so for example a Warp.Settings can get updated from a config,
but that doesn't make much sense for something like an Int
You'd normally would never implement this typeclass, if you want to implement
FromConfig
you should implement that directly, and if you want to use
DefaultConfig
and FromConfig
to implement FromConfig
you should let
the default Generics
based implementation do it's thing
Minimal complete definition
Nothing
Methods
updateFromConfig :: Key -> Config -> a -> IO a Source #
updateFromConfig :: (Generic a, Typeable a, FromConfigG (Rep a)) => Key -> Config -> a -> IO a Source #
fetchFromConfig :: Key -> Config -> IO (Maybe a) Source #
fetchFromConfig :: (Generic a, FromConfigG (Rep a)) => Key -> Config -> IO (Maybe a) Source #
Instances
FromConfig Bool Source # | |
FromConfig Float Source # | |
FromConfig Int Source # | |
FromConfig Integer Source # | |
FromConfig String Source # | |
FromConfig ByteString Source # | |
Defined in Conferer.FromConfig.Basics Methods updateFromConfig :: Key -> Config -> ByteString -> IO ByteString Source # fetchFromConfig :: Key -> Config -> IO (Maybe ByteString) Source # | |
FromConfig Text Source # | |
FromConfig a => FromConfig (Maybe a) Source # | |
class FromConfigG f where Source #
Purely Generics
machinery, ignore...
Methods
updateFromConfigG :: Key -> Config -> f a -> IO (f a) Source #
fetchFromConfigG :: Key -> Config -> IO (Maybe (f a)) Source #
Instances
FromConfig inner => FromConfigG (Rec0 inner) Source # | Purely |
FromConfigG inner => FromConfigG (D1 metadata inner) Source # | |
(FromConfigWithConNameG inner, Constructor constructor) => FromConfigG (C1 constructor inner) Source # | |
data ConfigParsingError Source #
Constructors
ConfigParsingError Key Text TypeRep |
Instances
Eq ConfigParsingError Source # | |
Defined in Conferer.Types Methods (==) :: ConfigParsingError -> ConfigParsingError -> Bool # (/=) :: ConfigParsingError -> ConfigParsingError -> Bool # | |
Show ConfigParsingError Source # | |
Defined in Conferer.Types Methods showsPrec :: Int -> ConfigParsingError -> ShowS # show :: ConfigParsingError -> String # showList :: [ConfigParsingError] -> ShowS # | |
Exception ConfigParsingError Source # | |
Defined in Conferer.Types Methods toException :: ConfigParsingError -> SomeException # fromException :: SomeException -> Maybe ConfigParsingError # |
data FailedToFetchError Source #
Constructors
FailedToFetchError Key TypeRep |
Instances
Eq FailedToFetchError Source # | |
Defined in Conferer.Types Methods (==) :: FailedToFetchError -> FailedToFetchError -> Bool # (/=) :: FailedToFetchError -> FailedToFetchError -> Bool # | |
Show FailedToFetchError Source # | |
Defined in Conferer.Types Methods showsPrec :: Int -> FailedToFetchError -> ShowS # show :: FailedToFetchError -> String # showList :: [FailedToFetchError] -> ShowS # | |
Exception FailedToFetchError Source # | |
Defined in Conferer.Types Methods toException :: FailedToFetchError -> SomeException # fromException :: SomeException -> Maybe FailedToFetchError # |