extensible-effects-1.7.2.1: An Alternative to Monad Transformers

Safe HaskellTrustworthy
LanguageHaskell2010

Data.OpenUnion1

Description

Original work at http://okmij.org/ftp/Haskell/extensible/OpenUnion1.hs. Open unions (type-indexed co-products) for extensible effects. This implementation relies on _closed_ overlapping instances (or closed type function overlapping soon to be added to GHC).

TODO: re-evaluate https://github.com/bfops/extensible-effects/issues/13

Synopsis

Documentation

data Union r v Source

Parameter r is phantom: it just tells what could be in the union. Where r is t1 :> t2 ... :> tn, Union r v can be constructed with a value of type ti v. Ideally, we should be able to add the constraint Member t r.

Constructors

forall t . (Functor t, Typeable t) => Union (t v) 

Instances

class Member t r Source

The Member t r specifies whether t is present anywhere in the sum type r, where t is some effectful type, e.g. Lift IO, State Int`.

Instances

Member * t r => Member * t ((:>) t' r) 
Member * t ((:>) t r) 

class Member t r => SetMember set t r | r set -> t Source

SetMember is similar to Member, but it allows types to belong to a "set". For every set, only one member can be in r at any given time. This allows us to specify exclusivity and uniqueness among arbitrary effects:

-- Terminal effects (effects which must be run last)
data Terminal

-- Make Lifts part of the Terminal effects set.
-- The fundep assures that there can only be one Terminal effect for any r.
instance Member (Lift m) r => SetMember Terminal (Lift m) r

-- Only allow a single unique Lift effect, by making a "Lift" set.
instance Member (Lift m) r => SetMember Lift (Lift m) r

Instances

MemberU k k1 set t r => SetMember (k -> * -> *) k set t r 

data a :> b infixr 1 Source

A sum data type, for composing effects

Instances

MemberU k * tag t r => MemberU k * tag t ((:>) t' r) 
MemberU k * tag (tag e) ((:>) (tag e) r) 
Member * t r => Member * t ((:>) t' r) 
Member * t ((:>) t r) 

inj :: (Functor t, Typeable t, Member t r) => t v -> Union r v Source

Construct a Union.

prj :: (Typeable t, Member t r) => Union r v -> Maybe (t v) Source

Try extracting the contents of a Union as a given type.

prjForce :: (Typeable t, Member t r) => Union r v -> (t v -> a) -> a Source

Extract the contents of a Union as a given type. If the Union isn't of that type, a runtime error occurs.

decomp :: Typeable t => Union (t :> r) v -> Either (Union r v) (t v) Source

Try extracting the contents of a Union as a given type. If we can't, return a reduced Union that excludes the type we just checked.

unsafeReUnion :: Union r w -> Union t w Source

Juggle types for a Union. Use cautiously.

weaken :: (Typeable t, Functor t) => Union r w -> Union (t :> r) w Source