| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
System.Etc.Internal.Types
Documentation
class IConfig config where Source #
Minimal complete definition
getConfigValue, getConfigValueWith, getAllConfigSources, getSelectedConfigSource
Methods
Arguments
| :: (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
| :: 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 {...})
getAllConfigSources :: MonadThrow m => [Text] -> config -> m (Set ConfigSource) Source #
getSelectedConfigSource :: MonadThrow m => [Text] -> config -> m ConfigSource Source #
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 # | |
Constructors
| Config | |
Fields | |
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 # | |
data ConfigValue Source #
Constructors
| ConfigValue | |
Fields
| |
| SubConfig | |
Fields
| |
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 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 FileSource Source #
Constructors
| FilePathSource | |
Fields
| |
| EnvVarFileSource | |
Fields
| |
Instances
| Eq FileSource Source # | |
Defined in System.Etc.Internal.Types | |
| Show FileSource Source # | |
Defined in System.Etc.Internal.Types Methods showsPrec :: Int -> FileSource -> ShowS # show :: FileSource -> String # showList :: [FileSource] -> ShowS # | |
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))) | |
markAsSensitive :: Bool -> a -> Value a Source #
deepMerge :: ConfigValue -> ConfigValue -> ConfigValue Source #
isEmptySubConfig :: ConfigValue -> Bool Source #
writeInSubConfig :: Text -> ConfigValue -> ConfigValue -> ConfigValue Source #
data ConfigValueType Source #