etc-0.4.1.0: Declarative configuration spec for Haskell projects

Safe HaskellNone
LanguageHaskell2010

System.Etc.Spec

Synopsis

Documentation

data ConfigSpec cmd Source #

Instances
Eq cmd => Eq (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

(==) :: ConfigSpec cmd -> ConfigSpec cmd -> Bool #

(/=) :: ConfigSpec cmd -> ConfigSpec cmd -> Bool #

Show cmd => Show (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

showsPrec :: Int -> ConfigSpec cmd -> ShowS #

show :: ConfigSpec cmd -> String #

showList :: [ConfigSpec cmd] -> ShowS #

Generic (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Associated Types

type Rep (ConfigSpec cmd) :: * -> * #

Methods

from :: ConfigSpec cmd -> Rep (ConfigSpec cmd) x #

to :: Rep (ConfigSpec cmd) x -> ConfigSpec cmd #

Lift cmd => Lift (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

lift :: ConfigSpec cmd -> Q Exp #

FromJSON cmd => FromJSON (ConfigSpec cmd) # 
Instance details

Defined in System.Etc.Internal.Spec.Parser

type Rep (ConfigSpec cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

type Rep (ConfigSpec cmd) = D1 (MetaData "ConfigSpec" "System.Etc.Internal.Spec.Types" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "ConfigSpec" PrefixI True) (S1 (MetaSel (Just "specConfigFilepaths") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilesSpec)) :*: (S1 (MetaSel (Just "specCliProgramSpec") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CliProgramSpec)) :*: S1 (MetaSel (Just "specConfigValues") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Text (ConfigValue cmd))))))

data ConfigValue cmd Source #

Instances
Eq cmd => Eq (ConfigValue cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

(==) :: ConfigValue cmd -> ConfigValue cmd -> Bool #

(/=) :: ConfigValue cmd -> ConfigValue cmd -> Bool #

Show cmd => Show (ConfigValue cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

showsPrec :: Int -> ConfigValue cmd -> ShowS #

show :: ConfigValue cmd -> String #

showList :: [ConfigValue cmd] -> ShowS #

Generic (ConfigValue cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Associated Types

type Rep (ConfigValue cmd) :: * -> * #

Methods

from :: ConfigValue cmd -> Rep (ConfigValue cmd) x #

to :: Rep (ConfigValue cmd) x -> ConfigValue cmd #

Lift cmd => Lift (ConfigValue cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

Methods

lift :: ConfigValue cmd -> Q Exp #

FromJSON cmd => FromJSON (ConfigValue cmd) # 
Instance details

Defined in System.Etc.Internal.Spec.Parser

type Rep (ConfigValue cmd) Source # 
Instance details

Defined in System.Etc.Internal.Spec.Types

type Rep (ConfigValue cmd) = D1 (MetaData "ConfigValue" "System.Etc.Internal.Spec.Types" "etc-0.4.1.0-7q0W6i0k47BIqxo3Mr9o9p" False) (C1 (MetaCons "ConfigValue" PrefixI True) ((S1 (MetaSel (Just "defaultValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Value)) :*: S1 (MetaSel (Just "configValueType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ConfigValueType)) :*: (S1 (MetaSel (Just "isSensitive") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool) :*: S1 (MetaSel (Just "configSources") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (ConfigSources cmd)))) :+: C1 (MetaCons "SubConfig" PrefixI True) (S1 (MetaSel (Just "subConfig") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap Text (ConfigValue cmd)))))

parseConfigSpec Source #

Arguments

:: MonadThrow m 
=> Text

Text to be parsed

-> m (ConfigSpec ())

returns ConfigSpec

Parses a text input into a ConfigSpec, input can be JSON or YAML (if cabal flag is set).

readConfigSpecTH :: (Lift k, FromJSON k) => Proxy k -> Text -> ExpQ Source #

Reads a specified FilePath and parses a ConfigSpec at compilation time.

readConfigSpec Source #

Arguments

:: Text

Filepath where contents are going to be read from and parsed

-> IO (ConfigSpec ())

returns ConfigSpec

Reads contents of a file and parses into a ConfigSpec, file contents can be either JSON or YAML (if cabal flag is set).