extensible-effects-1.11.1.0: An Alternative to Monad Transformers

Safe HaskellSafe
LanguageHaskell2010
Extensions
  • Cpp
  • UndecidableInstances
  • UndecidableSuperClasses
  • PolyKinds
  • DeriveDataTypeable
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • KindSignatures
  • TypeOperators
  • ExplicitNamespaces

Data.OpenUnion

Contents

Description

Original work at http://okmij.org/ftp/Haskell/extensible/OpenUnion1.hs and http://okmij.org/ftp/Haskell/extensible/OpenUnion2.hs. Open unions (type-indexed co-products) for extensible effects.

TODO: see if we can do away with Typeable constraints, perhaps by incorporating ideas from http://okmij.org/ftp/Haskell/extensible/TList.hs

Synopsis

Classes

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`

type Member = MemberImpl OU2 Source #

Monad transformer related

SetMember set t r is used to emulate monad transformers.

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 set t r => SetMember (k -> * -> *) set t r Source # 

Type-indexed co-product

Datatypes

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.

NOTE: exposing the constructor below allows users to bypass the type system. See unsafeReUnion for example.

Instances

Functor (Union r) Source # 

Methods

fmap :: (a -> b) -> Union r a -> Union r b #

(<$) :: a -> Union r b -> Union r a #

data a :> b infixr 1 Source #

A sum data type, for composing effects

Instances

MemberU' k (EQU (* -> *) t1 t2) tag t1 ((:>) t2 r) => MemberUImpl k OU2 tag t1 ((:>) t2 r) 

Functions

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 #