Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data s :> t = L t
- data a :>: s = D a
- data a :| b = a :| b
- class Entry a b where
- entry :: a -> b
- data Source
- = ConfigFileYaml SBS
- | ShellEnv [(String, String)]
- | CommandLine [String]
- data ConfigFile
- data ShellEnv
- data CommandLine
- data Error
- configify :: forall cfg. (FromJSON cfg, HasParseConfigFile cfg, HasParseShellEnv cfg, HasParseCommandLine cfg) => [Source] -> Either Error cfg
- class HasParseConfigFile cfg where
- type Env = [(String, String)]
- class HasParseShellEnv a where
- class HasParseShellEnv' a where
- type Args = [String]
- class HasParseCommandLine cfg where
- primitiveParseCommandLine :: HasParseShellEnv cfg => Proxy cfg -> [String] -> Either Error Value
- parseArgs :: Args -> Either String Env
- parseArgsWithEqSign :: String -> Either String Env
- parseArgsWithSpace :: String -> String -> Either String Env
- type family Val a p :: Maybe *
- type family OrElse x y :: Maybe k
- data CMaybe a where
- combine :: CMaybe a -> CMaybe b -> CMaybe (OrElse a b)
- (>.) :: forall a p r. (Sel a p, ValE a p ~ Done r) => a -> Proxy p -> r
- class Sel a p where
- data Exc a b
- data LookupFailed a p
- type ValE a p = ToExc (LookupFailed a p) (Val a p)
- type family ToExc a x :: Exc k l
- (<<>>) :: Value -> Value -> Value
- merge :: [Value] -> Value
- mergeAndCatch :: [Either Error Value] -> Either Error Value
- docs :: (HasToDoc a, HasRenderDoc ConfigFile, HasRenderDoc ShellEnv, HasRenderDoc CommandLine) => Proxy a -> ST
- data Doc
- concatDoc :: Doc -> Doc -> Doc
- class HasToDoc a where
- _makeDocPair :: (KnownSymbol path, KnownSymbol descr, HasToDoc v) => Proxy path -> Maybe (Proxy descr) -> Proxy v -> Doc
- class HasRenderDoc t where
type combinators
the equivalent of record field selectors.
L t |
(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) |
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 ""
?)
D a |
(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) |
cons
for record fields.
a :| b infixr 6 |
(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
sources
configify :: forall cfg. (FromJSON cfg, HasParseConfigFile cfg, HasParseShellEnv cfg, HasParseCommandLine cfg) => [Source] -> Either Error cfg Source
json / yaml
class HasParseConfigFile cfg where Source
HasParseConfigFile k cfg |
shell env.
class HasParseShellEnv a where Source
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 '_'.) |
class HasParseShellEnv' a where Source
cli
class HasParseCommandLine cfg where Source
HasParseShellEnv k cfg => HasParseCommandLine k cfg |
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.
exposed interface
FIXME: is it possible to remove CMaybe
from the signature and
return Val a p
instead?
(~) (Maybe *) (Val a ps) (Nothing *) => Sel a ps | We need the |
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 LookupFailed a p Source
type ValE a p = ToExc (LookupFailed a p) (Val a p) Source
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.
docs :: (HasToDoc a, HasRenderDoc ConfigFile, HasRenderDoc ShellEnv, HasRenderDoc CommandLine) => Proxy a -> ST Source
_makeDocPair :: (KnownSymbol path, KnownSymbol descr, HasToDoc v) => Proxy path -> Maybe (Proxy descr) -> Proxy v -> Doc Source
class HasRenderDoc t where Source