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

Control.Env.Hierarchical.Internal

Description

 
Synopsis

Documentation

class Environment env where Source #

Minimal complete definition

Nothing

Associated Types

type Super env Source #

Super env represents the inheritance relation between environments.

  • If env owns a field of the form Extends T, then T is the super environment.
  • If env owns no field of the form Extends T, then Root is the super environment.
  • Every env must have at most one field of the form Extends T because multiple inheritance is not supported.

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

interfaces that are fields of the environment

type Fields env :: [Type] Source #

fields of the environment

Methods

superL :: Lens' env (Super env) Source #

Lens to super environment

default superL :: Field (Extends (Super env)) env => Lens' env (Super env) Source #

Instances

Instances details
Environment Root Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Associated Types

type Super Root Source #

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

type Fields Root :: [Type] Source #

newtype Extends env Source #

Wrapper that represents the super environment.

Constructors

Extends env 

Instances

Instances details
Eq env => Eq (Extends env) Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Methods

(==) :: Extends env -> Extends env -> Bool #

(/=) :: Extends env -> Extends env -> Bool #

Ord env => Ord (Extends env) Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Methods

compare :: Extends env -> Extends env -> Ordering #

(<) :: Extends env -> Extends env -> Bool #

(<=) :: Extends env -> Extends env -> Bool #

(>) :: Extends env -> Extends env -> Bool #

(>=) :: Extends env -> Extends env -> Bool #

max :: Extends env -> Extends env -> Extends env #

min :: Extends env -> Extends env -> Extends env #

Show env => Show (Extends env) Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Methods

showsPrec :: Int -> Extends env -> ShowS #

show :: Extends env -> String #

showList :: [Extends env] -> ShowS #

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 Super Root Source #

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 s (l :: [Type]) where Source #

Associated Types

type Target s l Source #

Methods

transL :: Lens' s (Target s l) Source #

Instances

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

Defined in Control.Env.Hierarchical.Internal

Associated Types

type Target s '[] Source #

Methods

transL :: Lens' s (Target s '[]) Source #

(Environment s, Super s ~ t, Trans t l) => Trans s (t ': l) Source # 
Instance details

Defined in Control.Env.Hierarchical.Internal

Associated Types

type Target s (t ': l) Source #

Methods

transL :: Lens' s (Target s (t ': l)) 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 env (Addr 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 env (Addr 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,