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

Safe HaskellNone
LanguageHaskell2010

Data.Configifier

Contents

Synopsis

type combinators

data s :> t infixr 9 Source

the equivalent of record field selectors.

Constructors

L t 

Instances

(KnownSymbol path, KnownSymbol descr, HasToDoc * v) => HasToDoc * ((:>:) ((:>) path v) descr) 
(KnownSymbol path, HasToDoc * v) => HasToDoc * ((:>) path v) 
(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>:) ((:>) path v) descr) o) 
(KnownSymbol path, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>) path v) o) 
(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v) => HasParseShellEnv * ((:>:) ((:>) path v) descr) 
(KnownSymbol path, HasParseShellEnv * v) => HasParseShellEnv * ((:>) path v)

the sub-object structure of the config file is represented by '_' in the shell variable names. (i think it's still ok to have '_' in your config variable names instead of caml case; this parser first chops off matching names, then worries about trailing '_'.)

Entry a b => Entry a ((:>) s b) 
Eq t => Eq ((:>) s t) 
Ord t => Ord ((:>) s t) 
Show t => Show ((:>) s t) 
(KnownSymbol path, KnownSymbol descr, ToJSON v) => ToJSON ((:>:) ((:>) path v) descr) 
(KnownSymbol path, ToJSON v) => ToJSON ((:>) path v) 
(KnownSymbol path, KnownSymbol descr, FromJSON v) => FromJSON ((:>:) ((:>) path v) descr) 
(KnownSymbol path, FromJSON v) => FromJSON ((:>) path v) 
Typeable (Symbol -> * -> *) (:>) 
Sel t ps => Sel ((:>) p t) ((:) Symbol p ps) 

data a :>: s infixr 8 Source

descriptive strings for documentation. (the way we use this is still a little awkward. use tuple of name string and descr string? or a type class "path" with a type family that translates both "" :>: "" and "" to ""?)

Constructors

D a 

Instances

(KnownSymbol path, KnownSymbol descr, HasToDoc * v) => HasToDoc * ((:>:) ((:>) path v) descr) 
(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>:) ((:>) path v) descr) o) 
(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v) => HasParseShellEnv * ((:>:) ((:>) path v) descr) 
Entry a b => Entry a ((:>:) b s) 
Eq a => Eq ((:>:) a s) 
Ord a => Ord ((:>:) a s) 
Show a => Show ((:>:) a s) 
(KnownSymbol path, KnownSymbol descr, ToJSON v) => ToJSON ((:>:) ((:>) path v) descr) 
(KnownSymbol path, KnownSymbol descr, FromJSON v) => FromJSON ((:>:) ((:>) path v) descr) 
Typeable (* -> Symbol -> *) (:>:) 
Sel a ((:) Symbol p ps) => Sel ((:>:) a s) ((:) Symbol p ps) 

data a :| b infixr 6 Source

cons for record fields.

Constructors

a :| b infixr 6 

Instances

(HasToDoc * o1, HasToDoc * o2) => HasToDoc * ((:|) o1 o2) 
(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>:) ((:>) path v) descr) o) 
(KnownSymbol path, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>) path v) o) 
(Eq a, Eq b) => Eq ((:|) a b) 
(Ord a, Ord b) => Ord ((:|) a b) 
(Show a, Show b) => Show ((:|) a b) 
(ToJSON o1, ToJSON o2) => ToJSON ((:|) o1 o2) 
(FromJSON o1, FromJSON o2) => FromJSON ((:|) o1 o2) 
Typeable (* -> * -> *) (:|) 
(Sel a ((:) Symbol p ps), Sel b ((:) Symbol p ps)) => Sel ((:|) a b) ((:) Symbol p ps) 

constructing config values

class Entry a b where Source

Methods

entry :: a -> b Source

Instances

(~) * a b => Entry a b 
Entry a b => Entry a ((:>:) b s) 
Entry a b => Entry a ((:>) s b) 

sources

json / yaml

class HasParseConfigFile cfg where Source

Instances

shell env.

type Env = [(String, String)] Source

class HasParseShellEnv a where Source

Instances

HasParseShellEnv * Bool 
HasParseShellEnv * Int 
HasParseShellEnv * ST 
HasParseShellEnv * a => HasParseShellEnv * [a]

since shell env is not ideally suitable for providing arbitrary-length lists of sub-configs, we cheat: if a value is fed into a place where a list of values is expected, a singleton list is constructed implicitly.

(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>:) ((:>) path v) descr) o) 
(KnownSymbol path, HasParseShellEnv * v, HasParseShellEnv * o) => HasParseShellEnv * ((:|) ((:>) path v) o) 
(KnownSymbol path, KnownSymbol descr, HasParseShellEnv * v) => HasParseShellEnv * ((:>:) ((:>) path v) descr) 
(KnownSymbol path, HasParseShellEnv * v) => HasParseShellEnv * ((:>) path v)

the sub-object structure of the config file is represented by '_' in the shell variable names. (i think it's still ok to have '_' in your config variable names instead of caml case; this parser first chops off matching names, then worries about trailing '_'.)

cli

type Args = [String] Source

primitiveParseCommandLine :: HasParseShellEnv cfg => Proxy cfg -> [String] -> Either Error Value Source

Very basic fist 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

data types

type family Val a p :: Maybe * Source

Type-level lookup of a path in a configuration type. A path is represented as a list of symbols.

Equations

Val a [] = Just a 
Val (a :| b) (p : ps) = OrElse (Val a (p : ps)) (Val b (p : ps)) 
Val (a :>: s) (p : ps) = Val a (p : ps) 
Val (p :> t) (p : ps) = Val t ps 
Val a p = 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

A CMaybe is a static version of Maybe, i.e., we know at compile time whether we have Just or Nothing.

Constructors

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

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

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

exposed interface

(>.) :: forall a p r. (Sel a p, ValE a p ~ Done r) => a -> Proxy p -> r Source

This is a wrapper around sel that hides the interal use of CMaybe. As we expect, this version will just cause a type error if it is applied to an illegal path.

class Sel a p where Source

FIXME: is it possible to remove CMaybe from the signature and return Val a p instead?

Methods

sel :: a -> Proxy p -> CMaybe (Val a p) Source

Instances

(~) (Maybe *) (Val a ps) (Nothing *) => Sel a ps

We need the Val constraint here because overlapping instances and closed type families aren't fully compatible. GHC won't be able to recognize that we've already excluded the other cases and not reduce Val automatically. But the constraint should always resolve, unless we've made a mistake, and the worst outcome if we did are extra type errors, not run-time errors.

Sel a ([] Symbol) 
(Sel a ((:) Symbol p ps), Sel b ((:) Symbol p ps)) => Sel ((:|) a b) ((:) Symbol p ps) 
Sel a ((:) Symbol p ps) => Sel ((:>:) a s) ((:) Symbol p ps) 
Sel t ps => Sel ((:>) p t) ((:) Symbol p ps) 

implementation of Sel

better errors

data Exc a b Source

Constructors

Fail a 
Done b 

type ValE a p = ToExc (LookupFailed a p) (Val a p) Source

type family ToExc a x :: Exc k l Source

Equations

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

merge configs

(<<>>) :: Value -> Value -> Value Source

Merge two json trees such that the latter overwrites nodes in the former. Null is considered as non-existing. Otherwise, right values overwrite left values.

docs.

class HasToDoc a where Source

Methods

toDoc :: Proxy a -> Doc Source

Instances

HasToDoc * Bool 
HasToDoc * Int 
HasToDoc * ST 
HasToDoc * a => HasToDoc * [a] 
(HasToDoc * o1, HasToDoc * o2) => HasToDoc * ((:|) o1 o2) 
(KnownSymbol path, KnownSymbol descr, HasToDoc * v) => HasToDoc * ((:>:) ((:>) path v) descr) 
(KnownSymbol path, HasToDoc * v) => HasToDoc * ((:>) path v) 

_makeDocPair :: (KnownSymbol path, KnownSymbol descr, HasToDoc v) => Proxy path -> Maybe (Proxy descr) -> Proxy v -> Doc Source