freer-simple-1.2.1.2: A friendly effect system for Haskell.
Copyright(c) 2016 Allele Dev; 2017 Ixperta Solutions s.r.o.; 2017 Alexis King
LicenseBSD3
MaintainerAlexis King <lexi.lambda@gmail.com>
Stabilityexperimental
PortabilityGHC specific language extensions.
Safe HaskellNone
LanguageHaskell2010

Data.OpenUnion

Description

Open unions (type-indexed co-products, i.e. type-indexed sums) for extensible effects All operations are constant-time.

Synopsis

Open Union

data Union (r :: [Type -> Type]) a Source #

Open union is a strong sum (existential with an evidence).

Open Union Operations

class Weakens q where Source #

Methods

weakens :: Union r a -> Union (q :++: r) a Source #

Instances

Instances details
Weakens ('[] :: [Type -> Type]) Source # 
Instance details

Defined in Data.OpenUnion.Internal

Methods

weakens :: forall k (r :: [Type -> Type]) (a :: k). Union r a -> Union ('[] :++: r) a Source #

Weakens xs => Weakens (x ': xs) Source # 
Instance details

Defined in Data.OpenUnion.Internal

Methods

weakens :: forall k (r :: [Type -> Type]) (a :: k). Union r a -> Union ((x ': xs) :++: r) a Source #

type family xs :++: ys where ... infixr 5 Source #

Equations

'[] :++: ys = ys 
(x ': xs) :++: ys = x ': (xs :++: ys) 

decomp :: Union (t ': r) a -> Either (Union r a) (t a) Source #

Orthogonal decomposition of a Union (t ': r) :: * -> *. Right value is returned if the Union (t ': r) :: * -> * contains t :: * -> *, and Left when it doesn't. Notice that Left value contains Union r :: * -> *, i.e. it can not contain t :: * -> *.

O(1)

weaken :: Union r a -> Union (any ': r) a Source #

Inject whole Union r into a weaker Union (any ': r) that has one more summand.

O(1)

extract :: Union '[t] a -> t a Source #

Specialised version of prj/decomp that works on an Union '[t] :: * -> * which contains only one specific summand. Hence the absence of Maybe, and Either.

O(1)

Open Union Membership Constraints

class FindElem eff effs => Member (eff :: Type -> Type) effs where Source #

A constraint that requires that a particular effect, eff, is a member of the type-level list effs. This is used to parameterize an Eff computation over an arbitrary list of effects, so long as eff is somewhere in the list.

For example, a computation that only needs access to a cell of mutable state containing an Integer would likely use the following type:

Member (State Integer) effs => Eff effs ()

Methods

inj :: eff a -> Union effs a Source #

Takes a request of type t :: * -> *, and injects it into the Union.

O(1)

prj :: Union effs a -> Maybe (eff a) Source #

Project a value of type Union (t ': r) :: * -> * into a possible summand of the type t :: * -> *. Nothing means that t :: * -> * is not the value stored in the Union (t ': r) :: * -> *.

O(1)

Instances

Instances details
(FindElem t r, IfNotFound t r r) => Member t r Source # 
Instance details

Defined in Data.OpenUnion.Internal

Methods

inj :: t a -> Union r a Source #

prj :: Union r a -> Maybe (t a) Source #

type family Members effs effs' :: Constraint where ... Source #

A shorthand constraint that represents a combination of multiple Member constraints. That is, the following Members constraint:

Members '[Foo, Bar, Baz] effs

…is equivalent to the following set of Member constraints:

(Member Foo effs, Member Bar effs, Member baz effs)

Note that, since each effect is translated into a separate Member constraint, the order of the effects does not matter.

Equations

Members (eff ': effs) effs' = (Member eff effs', Members effs effs') 
Members '[] effs' = () 

class Member m effs => LastMember m effs | effs -> m Source #

Like Member, LastMember eff effs is a constraint that requires that eff is in the type-level list effs. However, unlike Member, LastMember requires m be the final effect in effs.

Generally, this is not especially useful, since it is preferable for computations to be agnostic to the order of effects, but it is quite useful in combination with sendM or liftBase to embed ordinary monadic effects within an Eff computation.

Instances

Instances details
LastMember m '[m] Source # 
Instance details

Defined in Data.OpenUnion

LastMember m effs => LastMember m (eff ': effs) Source # 
Instance details

Defined in Data.OpenUnion