configifier-0.0.5: parser for config files, shell variables, command line args.

Safe HaskellNone
LanguageHaskell2010

Data.Configifier

Contents

Synopsis

config types

data a :*> b infixr 6 Source

Construction of config records (cons for record fields).

Constructors

a :*> b infixr 6 

Instances

(Eq a, Eq b) => Eq ((:*>) a b) 
(Ord a, Ord b) => Ord ((:*>) a b) 
(Show a, Show b) => Show ((:*>) a b) 
Typeable (* -> * -> *) (:*>) 

data s :> t infixr 9 Source

Construction of config record fields.

Instances

Typeable (Symbol -> * -> *) (:>) 

data a :>: s infixr 8 Source

Add descriptive text to record field for documentation.

Instances

Typeable (k -> Symbol -> *) ((:>:) k) 

type family ToConfigCode a :: ConfigCode * Source

Map user-provided config type to ConfigCode types.

type family NoDesc a :: ConfigCode * Source

Deprecated: use of NoDesc is redundant and can be dropped without replacement.

Equations

NoDesc a = a 

type family ToConfig a f :: * Source

Map ConfgCode types to the types of config values.

Equations

ToConfig (Record a b) f = ToConfig a f :*> ToConfig b f 
ToConfig (Label s a) f = f (ToConfig a f) 
ToConfig (Descr a s) f = ToConfig a f 
ToConfig (List a) f = [ToConfig a f] 
ToConfig (Option a) f = MaybeO (ToConfig a f) 
ToConfig (Type a) f = a 

data MaybeO a Source

MaybeO is isomorphic to Maybe, but is only used for Option values.

Constructors

JustO a 
NothingO 

Instances

Eq a => Eq (MaybeO a) 
Ord a => Ord (MaybeO a) 
Show a => Show (MaybeO a) 
Typeable (* -> *) MaybeO 

data Id a Source

Transformers' Identity is not in Typeable, so we roll our own. It's also less work to write.

Constructors

Id a 

Instances

Eq a => Eq (Id a) 
Ord a => Ord (Id a) 
Show a => Show (Id a) 
Typeable (* -> *) Id 

sources

tagged values

data Tagged cfg Source

Constructors

Tagged 

Fields

fromTagged :: ToConfig cfg Id
 

Instances

Eq (ToConfig cfg Id) => Eq (Tagged cfg) 
Show (ToConfig cfg Id) => Show (Tagged cfg) 

data TaggedM cfg Source

Constructors

TaggedM 

Fields

fromTaggedM :: ToConfig cfg Maybe
 

Instances

Eq (ToConfig cfg Maybe) => Eq (TaggedM cfg) 
Show (ToConfig cfg Maybe) => Show (TaggedM cfg) 
ToJSON a => ToJSON (TaggedM (Type * a))
instance ToJSON Type
((~) * t (ToConfig cfg Maybe), (~) * (ToConfig (Option * cfg) Maybe) (MaybeO t''), ToJSON (TaggedM cfg)) => ToJSON (TaggedM (Option * cfg))
instance ToJSON Option
((~) * t (ToConfig cfg Maybe), ToJSON (TaggedM cfg)) => ToJSON (TaggedM (List * cfg))
instance ToJSON List
((~) * (ToConfig (Descr * cfg s) Maybe) (ToConfig cfg Maybe), ToJSON (TaggedM cfg)) => ToJSON (TaggedM (Descr * cfg s)) 
(ToJSON (TaggedM cfg), KnownSymbol s) => ToJSON (TaggedM (Label * s cfg))
instance ToJSON Label
((~) * t1 (ToConfig cfg1 Maybe), ToJSON (TaggedM cfg1), (~) * t2 (ToConfig cfg2 Maybe), ToJSON (TaggedM cfg2)) => ToJSON (TaggedM (Record * cfg1 cfg2))
instance ToJSON Record
FromJSON a => FromJSON (TaggedM (Type * a))
instance FromJSON Type
FromJSON (TaggedM cfg) => FromJSON (TaggedM (Option * cfg))
instance ParseJSON Option
FromJSON (TaggedM cfg) => FromJSON (TaggedM (List * cfg))
instance ParseJSON List
((~) * (ToConfig (Descr * cfg s) Maybe) (ToConfig cfg Maybe), FromJSON (TaggedM cfg)) => FromJSON (TaggedM (Descr * cfg s)) 
(FromJSON (TaggedM cfg), KnownSymbol s) => FromJSON (TaggedM (Label * s cfg))

instance FromJSON Label (tolerates unknown fields in json object.)

(FromJSON (TaggedM cfg1), FromJSON (TaggedM cfg2)) => FromJSON (TaggedM (Record * cfg1 cfg2))
instance FromJSON Record
Monoid (TaggedM a) => Monoid (TaggedM (Option * a)) 
Monoid (TaggedM (List * a))

Lists are initialized empty by default. Append overwrites left values with right values. (If we tried to append list elements recursively, there would be awkward questions about matching list lengths.)

((~) * (ToConfig (Descr * a s) Maybe) (ToConfig a Maybe), (~) * (ToConfig a Maybe) (Maybe a'), Monoid (TaggedM a)) => Monoid (TaggedM (Descr * a s)) 
Monoid (TaggedM (Label * s (Type * a)))

There is no instance Monoid (TaggedM (Type a)), since there is no reasonable mempty. Therefore, we offer a specialized instance for labels that map to Type.

Monoid (TaggedM a) => Monoid (TaggedM (Label * s a))

If one of two configs is Nothing, do the expected thing. If both are Just, append the values.

(Monoid (TaggedM a), Monoid (TaggedM b)) => Monoid (TaggedM (Record * a b)) 

results and errors

the main function

configify :: forall cfg tm. (tm ~ TaggedM cfg, Show tm, Monoid tm, Freeze cfg, FromJSON tm, HasParseShellEnv cfg, HasParseCommandLine cfg, CanonicalizePartial cfg) => [Source] -> IO (Tagged cfg) Source

configifyWithDefault :: forall cfg tm. (tm ~ TaggedM cfg, Show tm, Monoid tm, Freeze cfg, FromJSON tm, HasParseShellEnv cfg, HasParseCommandLine cfg, CanonicalizePartial cfg) => tm -> [Source] -> IO (Tagged cfg) Source

IO

defaultSources :: [FilePath] -> IO [Source] Source

From a list of config file paths, construct a source list that (1) reads those files allowing for recursive includes; then (2) processes shell environment variables (with getProgName as prefix), and finally (3) processes command line args, turning --config arguments into further recursive config file loads.

withShellEnvPrefix :: Env -> IO Env Source

Require that all shell env variables start with executable name. (This is just a call to requireShellEnvPrefix' with the result of progName.)

corner cases

readUserConfigFiles :: [Source] -> [Source] Source

Handle `--config=<FILE>`, `--config FILE`: split up CommandLine source on each of these, and inject a YamlFile source with the resp. file name.

withShellEnvPrefix' :: String -> Env -> Env Source

Require prefix for shell env variables. This function will chop off the given prefix of all env entries, and filter all entries that do not have this prefix.

yaml / json

renderConfigFile :: (Freeze cfg, t ~ Tagged cfg, ToJSON (TaggedM cfg)) => t -> SBS Source

shell env

type Env = [(String, String)] Source

class HasParseShellEnv cfg where Source

Instances

(Typeable * a, FromJSON (TaggedM (Type * a))) => HasParseShellEnv (Type * a) 
HasParseShellEnv a => HasParseShellEnv (Option * a) 
HasParseShellEnv a => HasParseShellEnv (List * a)

You can provide a list value via the shell environment by providing a single element. This element will be put into a list implicitly.

(A more general approach that allows for yaml-encoded list values in shell variables is more tricky to design, implement, and use: If you have a list of sub-configs and don't want the entire sub-config to be yaml-encoded, but use a longer shell variable name to go further down to deeper sub-configs, there is a lot of ambiguity. It may be possible to resolve that at run-time, but it's more tricky.)

((~) * (ToConfig (Descr * cfg s) Maybe) (ToConfig cfg Maybe), HasParseShellEnv cfg) => HasParseShellEnv (Descr * cfg s) 
(KnownSymbol path, HasParseShellEnv a) => HasParseShellEnv (Label * path a)

The paths into the recursive structure of the config file are concatenated to shell variable names with separating '_'. (It is still ok to have '_' in your config path names. This parser chops off complete matching names, whether they contain '_' or not, and only then worries about trailing '_'.)

(HasParseShellEnv a, HasParseShellEnv b) => HasParseShellEnv (Record * a b) 

cli

type Args = [String] Source

primitiveParseCommandLine :: HasParseShellEnv cfg => [String] -> Either Error (TaggedM cfg) Source

Very basic first approach: read --(key)(=|s+)(value); construct shell env from keys and names, and use parseShellEnv on the command line. If it doesn't like the syntax used in the command line, it will crash. I hope for this to get much fancier in the future.

accessing config values

(>>.) :: forall cfg ps r. (Sel cfg ps, ToValE cfg ps ~ Done r) => Tagged cfg -> Proxy ps -> r infix 7 Source

Map a Tagged config value and a type-level path to the part of the config value the path points to. Trigger an informative type error if path does not exist.

type family ToVal a p :: Maybe * Source

Map ConfgCode types to the types of config values.

Equations

ToVal (Record a b) [] = Just (ToConfig (Record a b) Id) 
ToVal (Record a b) ps = OrElse (ToVal a ps) (ToVal b ps) 
ToVal (Label p a) (p : ps) = ToVal a ps 
ToVal (Descr a s) ps = ToVal a ps 
ToVal (Option a) ps = ToValueMaybe (ToVal a ps) 
ToVal a [] = Just (ToConfig a Id) 
ToVal a (p : ps) = Nothing 

type family OrElse x y :: Maybe k Source

This is <|> on Maybe lifted to the type level.

Equations

OrElse (Just x) y = Just x 
OrElse Nothing y = y 

data CMaybe a where Source

Compile-time Maybe. Type-level Just / Nothing (as produced by ToVal) are embedded in each constructor, resp.. Since Just and Nothing are different types, CNothing and CJust can be distinguished by the type checker.

Constructors

CNothing :: CMaybe Nothing 
CJust :: a -> CMaybe (Just a) 

orElse :: CMaybe a -> CMaybe b -> CMaybe (OrElse a b) Source

This is a version of <|> on Maybe for CMaybe.

options

type family ToValueMaybe a :: Maybe * Source

class NothingValue a where Source

Instances

cfg traversal

class Sel cfg ps where Source

Methods

sel :: Tagged cfg -> Proxy ps -> CMaybe (ToVal cfg ps) Source

Instances

Sel' cfg ps => Sel cfg ps 
((~) (ConfigCode *) cfg (Option * cfg'), NothingValue (ToVal cfg' ps), Sel cfg' ps) => Sel (Option * cfg') ps 
((~) (ConfigCode *) cfg (Descr * cfg' s), Sel cfg' ps, (~) * (ToConfig (Descr * cfg' s) Id) (ToConfig cfg' Id)) => Sel (Descr * cfg' s) ps 
Sel (Record * cfg' cfg'') ([] Symbol) 
((~) (ConfigCode *) cfg (Label * p cfg'), Sel cfg' ps, KnownSymbol p) => Sel (Label * p cfg') ((:) Symbol p ps) 
((~) (ConfigCode *) cfg (Record * cfg' cfg''), Sel cfg' ((:) Symbol p ps), Sel cfg'' ((:) Symbol p ps)) => Sel (Record * cfg' cfg'') ((:) Symbol p ps) 

class Sel' cfg ps where Source

Helper class for disambiguating overlaps. The trick is that the Sel instance based on the Sel' constraint is more general than all other instances, so OverlappingInstances will ensure it is matched last. This way, no instance of Sel' can wrongly overlap with any instance of Sel.

Methods

sel' :: Tagged cfg -> Proxy ps -> CMaybe (ToVal cfg ps) Source

Instances

((~) * t (ToConfig cfg Id), (~) (Maybe *) (ToVal cfg ([] Symbol)) (Just * t)) => Sel' cfg ([] Symbol) 
(~) (Maybe *) (ToVal cfg ((:) Symbol p ps)) (Nothing *) => Sel' cfg ((:) Symbol p ps) 

static lookup error handling

type ToValE a p = ToExc (LookupFailed a p) (ToVal a p) Source

data Exc a b Source

Constructors

Fail a 
Done b 

type family ToExc a x :: Exc k l Source

Equations

ToExc a Nothing = Fail a 
ToExc a (Just x) = Done x 

merge configs

merge :: forall cfg tm ti. (tm ~ TaggedM cfg, ti ~ Tagged cfg, Freeze cfg, Monoid tm, CanonicalizePartial cfg) => [tm] -> Either Error ti Source

freeze :: forall cfg tm ti. (tm ~ TaggedM cfg, ti ~ Tagged cfg, Freeze cfg) => tm -> Either Error ti Source

thaw :: forall cfg tm ti. (tm ~ TaggedM cfg, ti ~ Tagged cfg, Freeze cfg) => ti -> tm Source

class Freeze c where Source

Instances

Freeze (Type * c) 
((~) * (ToConfig (Option * c) Maybe) (MaybeO tm), (~) * (ToConfig (Option * c) Id) (MaybeO ti), (~) * tm (ToConfig c Maybe), (~) * ti (ToConfig c Id), Freeze c) => Freeze (Option * c)

FIXME: if a non-optional part of an optional sub-config is missing, the FreezeIncomplete error is ignored and the entire sub-config is cleared. it would be better to distinguish between the cases `sub-config missing` and `sub-config provided incompletely`, and still raise an error in the latter.

Freeze c => Freeze (List * c) 
((~) * (ToConfig (Descr * t s) Maybe) (ToConfig t Maybe), (~) * (ToConfig (Descr * t s) Id) (ToConfig t Id), Freeze t) => Freeze (Descr * t s) 
(KnownSymbol s, Freeze t) => Freeze (Label * s t) 
(Freeze a, Freeze b) => Freeze (Record * a b) 

class CanonicalizePartial a where Source

Partials are constructed with every Nothing spelled out, resulting in deep skeletons of Nothings. CanonicalizePartial replaces those with single Nothings at their tops.

Instances

CanonicalizePartial (Type * a) 
((~) (ConfigCode *) cfg (Option * cfg'), CanonicalizePartial cfg') => CanonicalizePartial (Option * cfg') 
((~) (ConfigCode *) cfg (List * cfg'), CanonicalizePartial cfg') => CanonicalizePartial (List * cfg') 
((~) (ConfigCode *) cfg (Descr * cfg' s), CanonicalizePartial cfg') => CanonicalizePartial (Descr * cfg' s) 
((~) (ConfigCode *) cfg (Label * s cfg'), CanonicalizePartial cfg') => CanonicalizePartial (Label * s cfg') 
(CanonicalizePartial cfg, CanonicalizePartial cfg') => CanonicalizePartial (Record * cfg cfg') 

docs

class HasToDoc a where Source

Methods

toDoc :: Proxy a -> Doc Source

Instances

Typeable * a => HasToDoc (Type * a) 
HasToDoc a => HasToDoc (Option * a) 
HasToDoc a => HasToDoc (List * a) 
(HasToDoc a, KnownSymbol path, KnownSymbol descr) => HasToDoc (Descr * (Label * path a) descr) 
(KnownSymbol path, HasToDoc a) => HasToDoc (Label * path a) 
(HasToDoc a, HasToDoc b) => HasToDoc (Record * a b)