extensible-effects-3.0.0.0: An Alternative to Monad Transformers

Safe HaskellTrustworthy
LanguageHaskell2010
Extensions
  • Cpp
  • UndecidableInstances
  • MonoLocalBinds
  • ScopedTypeVariables
  • TypeFamilies
  • GADTs
  • GADTSyntax
  • ConstraintKinds
  • PolyKinds
  • DataKinds
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • KindSignatures
  • RankNTypes
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll

Data.OpenUnion

Description

Open unions (type-indexed co-products) for extensible effects All operations are constant-time, and there is no Typeable constraint

This is a variation of OpenUion5.hs, which relies on overlapping instances instead of closed type families. Closed type families have their problems: overlapping instances can resolve even for unground types, but closed type families are subject to a strict apartness condition.

This implementation is very similar to OpenUnion1.hs, but without the annoying Typeable constraint. We sort of emulate it:

Our list r of open union components is a small Universe. Therefore, we can use the Typeable-like evidence in that universe. We hence can define

data Union r v where
  Union :: t v -> TRep t r -> Union r v -- t is existential

where

data TRep t r where
  T0 :: TRep t (t ': r)
  TS :: TRep t r -> TRep (any ': r)

Then Member is a type class that produces TRep Taken literally it doesn't seem much better than OpenUinion41.hs. However, we can cheat and use the index of the type t in the list r as the TRep. (We will need UnsafeCoerce then).

The interface is the same as of other OpenUnion*.hs

Synopsis

Documentation

data Union (r :: [* -> *]) v Source #

The data constructors of Union are not exported

Strong Sum (Existential with the evidence) is an open union t is can be a GADT and hence not necessarily a Functor. Int is the index of t in the list r; that is, the index of t in the universe r

inj :: Member t r => t v -> Union r v Source #

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

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

class FindElem t r => Member (t :: * -> *) r where Source #

Typeclass that asserts that effect t is contained inside the effect-list r.

The FindElem typeclass is necessary for implementation reasons and is not required for using the effect list.

Minimal complete definition

inj, prj

Methods

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

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

Instances

FindElem [* -> *] t r => Member t r Source # 

Methods

inj :: t v -> Union * r v Source #

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

(~) (* -> *) t s => Member t ((:) (* -> *) s ([] (* -> *))) Source #

Explicit type-level equality condition is a dirty hack to eliminate the type annotation in the trivial case, such as run (runReader () get).

There is no ambiguity when finding instances for Member t (a ': b ': r), which the second instance is selected.

The only case we have to concerned about is Member t '[s]. But, in this case, values of definition is the same (if present), and the first one is chosen according to GHC User Manual, since the latter one is incoherent. This is the optimal choice.

Methods

inj :: t v -> Union * (((* -> *) ': s) [* -> *]) v Source #

prj :: Union * (((* -> *) ': s) [* -> *]) v -> Maybe (t v) Source #

class Member t r => SetMember (tag :: k -> * -> *) (t :: * -> *) r | tag r -> t Source #

This class is used for emulating monad transformers

Instances

(EQU (* -> *) Bool t1 t2 p, MemberU' k p tag t1 ((:) (* -> *) t2 r)) => SetMember k tag t1 ((:) (* -> *) t2 r) Source # 

type family (ms :: [* -> *]) <:: r where ... Source #

A useful operator for reducing boilerplate.

f :: [Reader Int, Writer String] <:: r
  => a -> Eff r b

is equal to

f :: (Member (Reader Int) r, Member (Writer String) r)
  => a -> Eff r b

Equations

'[] <:: r = (() :: Constraint) 
(m ': ms) <:: r = (Member m r, (<::) ms r) 

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