hierarchical-env-0.1.0.0: hierarchical environments for dependency injection
LicenseBSD-3
Maintainerautotaker@gmail.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Control.Env.Hierarchical.Internal

Description

 
Synopsis

Documentation

class Environment env Source #

Associated Types

type Fields1 env :: [Type -> Type] Source #

interfaces that are fields of the environment

type Fields env :: [Type] Source #

fields of the environment

Instances

Instances details
Environment Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Associated Types

type Fields1 Root :: [Type -> Type] Source #

type Fields Root :: [Type] Source #

type family Super env Source #

Super env represents the inheritance relation between environments. Every environment must be a descendant of Root.

Instances

Instances details
type Super Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Super Root = TypeError ('Text "No super environment for Root") :: Type

data Root Source #

Root environment that does not have any fields.

Constructors

Root 

Instances

Instances details
Environment Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Associated Types

type Fields1 Root :: [Type -> Type] Source #

type Fields Root :: [Type] Source #

type Super Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Super Root = TypeError ('Text "No super environment for Root") :: Type
type Fields1 Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Fields1 Root = '[] :: [Type -> Type]
type Fields Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

type Fields Root = '[] :: [Type]

class Field a env where Source #

direct field of env

Methods

fieldL :: Lens' env a Source #

Instances

Instances details
Field env env Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Methods

fieldL :: Lens' env env Source #

class Trans a (l :: [Type]) s | a l -> s where Source #

Methods

transL :: Lens' s a Source #

Instances

Instances details
Trans a ('[] :: [Type]) a Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Methods

transL :: Lens' a a Source #

(Field s' s, Trans a l s') => Trans a (s ': l) s Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Methods

transL :: Lens' s a Source #

type (<:) env env' = Trans env' (Addr env env') env Source #

data SomeInterface f env where Source #

Constructors

SomeInterface :: Lens' env' (f env') -> Lens' env env' -> SomeInterface f env 

type family Has a env where ... Source #

Type constraint meaning env contains a as a (including ancestors') field.

An environment env contains unique value for each type T that satisfies Has T env. If you want to depends on multiple values of the same type, please distinguish them by using newtype.

Equations

Has a env = HasAux a env (FindEnv a (Ancestors env)) 

type family Has1 f env where ... Source #

Type constraint meaning env contains f env' for some ancestor env'

Equations

Has1 f env = Has1Aux f env (FindEnv1 f (Ancestors env)) 

getL :: forall a env. Has a env => Lens' env a Source #

Lens to extract a from env

ifaceL :: forall f env. Has1 f env => SomeInterface f env Source #

runIF :: forall f env a. Has1 f env => (forall env'. f env' -> RIO env' a) -> RIO env a Source #

Run action that depends on an interface f. The action must be polymorphic to env', because it will run in some ancestor environment, which may be different from env,