etc-0.4.0.1: Declarative configuration spec for Haskell projects

Safe HaskellNone
LanguageHaskell2010

System.Etc.Internal.Spec.Types

Documentation

data ConfigurationError Source #

data CliOptValueType Source #

Constructors

StringOpt 
NumberOpt 
SwitchOpt 

Instances

Eq CliOptValueType Source # 
Show CliOptValueType Source # 
Generic CliOptValueType Source # 
type Rep CliOptValueType Source # 
type Rep CliOptValueType = D1 * (MetaData "CliOptValueType" "System.Etc.Internal.Spec.Types" "etc-0.4.0.1-4dAjba5FFiAF6sIx6yxiVq" False) ((:+:) * (C1 * (MetaCons "StringOpt" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "NumberOpt" PrefixI False) (U1 *)) (C1 * (MetaCons "SwitchOpt" PrefixI False) (U1 *))))

data CliArgValueType Source #

Constructors

StringArg 
NumberArg 

Instances

Eq CliArgValueType Source # 
Show CliArgValueType Source # 
Generic CliArgValueType Source # 
type Rep CliArgValueType Source # 
type Rep CliArgValueType = D1 * (MetaData "CliArgValueType" "System.Etc.Internal.Spec.Types" "etc-0.4.0.1-4dAjba5FFiAF6sIx6yxiVq" False) ((:+:) * (C1 * (MetaCons "StringArg" PrefixI False) (U1 *)) (C1 * (MetaCons "NumberArg" PrefixI False) (U1 *)))

data CliEntryMetadata Source #

Constructors

Opt 
Arg 

Fields

Instances

Eq CliEntryMetadata Source # 
Show CliEntryMetadata Source # 
Generic CliEntryMetadata Source # 
type Rep CliEntryMetadata Source # 

data CliEntrySpec cmd Source #

Instances

Eq cmd => Eq (CliEntrySpec cmd) Source # 

Methods

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

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

Show cmd => Show (CliEntrySpec cmd) Source # 
Generic (CliEntrySpec cmd) Source # 

Associated Types

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

Methods

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

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

FromJSON cmd => FromJSON (CliEntrySpec cmd) Source # 
type Rep (CliEntrySpec cmd) Source # 
type Rep (CliEntrySpec cmd) = D1 * (MetaData "CliEntrySpec" "System.Etc.Internal.Spec.Types" "etc-0.4.0.1-4dAjba5FFiAF6sIx6yxiVq" False) ((:+:) * (C1 * (MetaCons "CmdEntry" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "cliEntryCmdValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Vector cmd))) (S1 * (MetaSel (Just Symbol "cliEntryMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CliEntryMetadata)))) (C1 * (MetaCons "PlainEntry" PrefixI True) (S1 * (MetaSel (Just Symbol "cliEntryMetadata") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CliEntryMetadata))))

data CliCmdSpec Source #

Constructors

CliCmdSpec 

Fields

Instances

Eq CliCmdSpec Source # 
Show CliCmdSpec Source # 
Generic CliCmdSpec Source # 

Associated Types

type Rep CliCmdSpec :: * -> * #

FromJSON CliCmdSpec Source # 
type Rep CliCmdSpec Source # 
type Rep CliCmdSpec = D1 * (MetaData "CliCmdSpec" "System.Etc.Internal.Spec.Types" "etc-0.4.0.1-4dAjba5FFiAF6sIx6yxiVq" False) (C1 * (MetaCons "CliCmdSpec" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "cliCmdDesc") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text)) (S1 * (MetaSel (Just Symbol "cliCmdHeader") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))))

data ConfigSources cmd Source #

Constructors

ConfigSources 

Fields

Instances

Eq cmd => Eq (ConfigSources cmd) Source # 

Methods

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

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

Show cmd => Show (ConfigSources cmd) Source # 
Generic (ConfigSources cmd) Source # 

Associated Types

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

Methods

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

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

type Rep (ConfigSources cmd) Source # 
type Rep (ConfigSources cmd) = D1 * (MetaData "ConfigSources" "System.Etc.Internal.Spec.Types" "etc-0.4.0.1-4dAjba5FFiAF6sIx6yxiVq" False) (C1 * (MetaCons "ConfigSources" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "envVar") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Text))) (S1 * (MetaSel (Just Symbol "cliEntry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe (CliEntrySpec cmd))))))

data ConfigValue cmd Source #

Instances

Eq cmd => Eq (ConfigValue cmd) Source # 

Methods

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

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

Show cmd => Show (ConfigValue cmd) Source # 

Methods

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

show :: ConfigValue cmd -> String #

showList :: [ConfigValue cmd] -> ShowS #

Generic (ConfigValue cmd) Source # 

Associated Types

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

Methods

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

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

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

data ConfigSpec cmd Source #

Instances

Eq cmd => Eq (ConfigSpec cmd) Source # 

Methods

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

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

Show cmd => Show (ConfigSpec cmd) Source # 

Methods

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

show :: ConfigSpec cmd -> String #

showList :: [ConfigSpec cmd] -> ShowS #

FromJSON cmd => FromJSON (ConfigSpec cmd) Source #