cfg-0.0.2.2: Type directed application configuration parsing and accessors
Copyright© Jonathan Lorimer 2023
LicenseMIT
Maintainerjonathanlorimer@pm.me
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

Cfg.Deriving.Config

Description

This module provides types and instances for deriving ConfigSource and ConfigParser instances via generic machinery. These types are also how you modify the key representation for your configuration.

Since: 0.0.2.0

Synopsis

Deriving Types

newtype Config a Source #

This newtype is the simplest deriving option. It doesn't allow you to alter key names with a KeyModifier, it only specifies record fields as keys within the configuration tree hierarchy. Therefore it is not possible to derive this for configuration values (such as product types without named record fields, or sum types), only top level records.

Example
Expand
>>> import GHC.Generics (Generic (..))
>>> import Cfg.Source (ConfigSource(..))
>>> import Cfg.Parser (ConfigParser(..))
>>> import Cfg.Deriving.Config (Config(..))
>>> import Cfg.Source.Default (DefaultSource(..))
>>> :{
data AppConfig = AppConfig
  { appConfigSetting1 :: Int
  , appConfigSetting2 :: Bool
  , appConfigSetting3 :: String
  }
  deriving (Generic, Show, DefaultSource)
  deriving (ConfigSource, ConfigParser) via (Config AppConfig)
:}
>>> pPrint $ configSource @AppConfig
Free
    ( fromList
        [
            ( "appConfigSetting1"
            , Free
                ( fromList [] )
            )
        ,
            ( "appConfigSetting2"
            , Free
                ( fromList [] )
            )
        ,
            ( "appConfigSetting3"
            , Free
                ( fromList [] )
            )
        ]
    )

Since: 0.0.2.0

Constructors

Config 

Fields

Instances

Instances details
(AssertTopLevelRecord (ConfigSource :: Type -> Constraint) a, DefaultSource a, Generic a, GConfigSource (Rep a)) => ConfigSource (Config a :: Type) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

Generic a => Generic (Config a) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

Associated Types

type Rep (Config a) 
Instance details

Defined in Cfg.Deriving.Config

type Rep (Config a) = Rep a

Methods

from :: Config a -> Rep (Config a) x #

to :: Rep (Config a) x -> Config a #

(AssertTopLevelRecord ConfigParser a, Generic a, GConfigParser (Rep a)) => ConfigParser (Config a) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

type Rep (Config a) Source # 
Instance details

Defined in Cfg.Deriving.Config

type Rep (Config a) = Rep a

newtype ConfigOpts (fieldModifier :: k) a Source #

This newtype is identical to Config except that it accepts a type argument which can be used to apply a KeyModifier to each record field name when generating keys.

Example
Expand
>>> import GHC.Generics (Generic (..))
>>> import Cfg.Source (ConfigSource(..))
>>> import Cfg.Parser (ConfigParser(..))
>>> import Cfg.Deriving.Config (Config(..))
>>> import Cfg.Source.Default (DefaultSource(..))
>>> :{
data AppConfig = AppConfig
  { appConfigSetting1 :: Int
  , appConfigSetting2 :: Bool
  , appConfigSetting3 :: String
  }
  deriving (Generic, Show, DefaultSource)
  deriving (ConfigSource, ConfigParser)
     via (ConfigOpts '[StripPrefix "app", CamelToSnake, ToUpper] AppConfig)
:}
>>> pPrint $ configSource @AppConfig
Free
    ( fromList
        [
            ( "CONFIG_SETTING1"
            , Free
                ( fromList [] )
            )
        ,
            ( "CONFIG_SETTING2"
            , Free
                ( fromList [] )
            )
        ,
            ( "CONFIG_SETTING3"
            , Free
                ( fromList [] )
            )
        ]
    )

Since: 0.0.2.0

Constructors

ConfigOpts 

Fields

Instances

Instances details
(GetConfigOptions t, AssertTopLevelRecord (ConfigSource :: Type -> Constraint) a, Generic a, DefaultSource a, GConfigSource (Rep a)) => ConfigSource (ConfigOpts t a :: Type) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

Generic a => Generic (ConfigOpts t a) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

Associated Types

type Rep (ConfigOpts t a) 
Instance details

Defined in Cfg.Deriving.Config

type Rep (ConfigOpts t a) = Rep a

Methods

from :: ConfigOpts t a -> Rep (ConfigOpts t a) x #

to :: Rep (ConfigOpts t a) x -> ConfigOpts t a #

(GetConfigOptions t, AssertTopLevelRecord (ConfigSource :: Type -> Constraint) a, Generic a, GConfigParser (Rep a)) => ConfigParser (ConfigOpts t a) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

type Rep (ConfigOpts t a) Source # 
Instance details

Defined in Cfg.Deriving.Config

type Rep (ConfigOpts t a) = Rep a

newtype ConfigRoot (rootType :: k) (fieldModifier :: k1) a Source #

This newtype is used to derive instances for your root configuration type (i.e. the top level record for all your configuration). The only additional functionality that it provides is that it lets you specify a root key, which is derived from either the type name or the data constructor name. You choose which name you select by providing either ConstructorName or TypeName as the first type argument to ConfigRoot. These RootKey types also take a type level argument where you can provide key modifiers, if you don't want to apply any key modifiers you can pass in Identity or an empty tuple or an empty type level list.

TypeName Example
Expand
>>> import GHC.Generics (Generic (..))
>>> import Cfg.Source (ConfigSource(..))
>>> import Cfg.Parser (ConfigParser(..))
>>> import Cfg.Deriving.Config (Config(..))
>>> import Cfg.Source.Default (DefaultSource(..))
>>> import Cfg.Deriving.KeyModifier
>>> :{
data TypeNameConfig = ConfigConstructor
  { appConfigSetting1 :: Int
  , appConfigSetting2 :: Bool
  , appConfigSetting3 :: String
  }
  deriving (Generic, Show, DefaultSource)
  deriving (ConfigSource, ConfigParser)
     via ConfigRoot
       ('TypeName '[StripSuffix "Config", CamelToSnake, ToUpper])
       '[StripPrefix "app", CamelToSnake, ToUpper]
       TypeNameConfig
:}
>>> pPrint $ configSource @TypeNameConfig
Free
    ( fromList
        [
            ( "TYPE_NAME"
            , Free
                ( fromList
                    [
                        ( "CONFIG_SETTING1"
                        , Free
                            ( fromList [] )
                        )
                    ,
                        ( "CONFIG_SETTING2"
                        , Free
                            ( fromList [] )
                        )
                    ,
                        ( "CONFIG_SETTING3"
                        , Free
                            ( fromList [] )
                        )
                    ]
                )
            )
        ]
    )
ConstructorName Example
Expand
>>> :{
data TypeNameConfig = ConfigConstructor
  { appConfigSetting1 :: Int
  , appConfigSetting2 :: Bool
  , appConfigSetting3 :: String
  }
  deriving (Generic, Show, DefaultSource)
  deriving (ConfigSource, ConfigParser)
     via ConfigRoot
       ('ConstructorName Identity)
       '[StripPrefix "app", CamelToSnake, ToUpper]
       TypeNameConfig
:}
>>> pPrint $ configSource @TypeNameConfig
Free
    ( fromList
        [
            ( "ConfigConstructor"
            , Free
                ( fromList
                    [
                        ( "CONFIG_SETTING1"
                        , Free
                            ( fromList [] )
                        )
                    ,
                        ( "CONFIG_SETTING2"
                        , Free
                            ( fromList [] )
                        )
                    ,
                        ( "CONFIG_SETTING3"
                        , Free
                            ( fromList [] )
                        )
                    ]
                )
            )
        ]
    )

Since: 0.0.2.0

Constructors

ConfigRoot 

Fields

Instances

Instances details
(ConfigRootOptions r f, AssertTopLevelRecord (ConfigSource :: Type -> Constraint) a, Generic a, DefaultSource a, GConfigSource (Rep a)) => ConfigSource (ConfigRoot r f a :: Type) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

Generic a => Generic (ConfigRoot r f a) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

Associated Types

type Rep (ConfigRoot r f a) 
Instance details

Defined in Cfg.Deriving.Config

type Rep (ConfigRoot r f a) = Rep a

Methods

from :: ConfigRoot r f a -> Rep (ConfigRoot r f a) x #

to :: Rep (ConfigRoot r f a) x -> ConfigRoot r f a #

(ConfigRootOptions r f, AssertTopLevelRecord ConfigParser a, Generic a, GConfigParser (Rep a)) => ConfigParser (ConfigRoot r f a) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

type Rep (ConfigRoot r f a) Source # 
Instance details

Defined in Cfg.Deriving.Config

type Rep (ConfigRoot r f a) = Rep a

Internal Typeclasses

class KeyModifier t => GetConfigOptions (t :: k) where Source #

Typeclass for reifying type level field label modifiers into KeyOptions

Since: 0.0.2.0

Instances

Instances details
KeyModifier t => GetConfigOptions (t :: k) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

class (KeyModifier r, KeyModifier f) => ConfigRootOptions (r :: k) (f :: k1) where Source #

Typeclass for reifying type level arguments into RootOptions

Since: 0.0.2.0

Instances

Instances details
(KeyModifier ('ConstructorName k2), KeyModifier f) => ConfigRootOptions ('ConstructorName k2 :: RootKey a) (f :: k1) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config

(KeyModifier ('TypeName k2), KeyModifier f) => ConfigRootOptions ('TypeName k2 :: RootKey a) (f :: k1) Source #

Since: 0.0.2.0

Instance details

Defined in Cfg.Deriving.Config