Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
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
- class (Member' t r ~ True) => Member t r
- class Member t r => SetMember set t r | r set -> t
- data Union r v
- data a :> b
- inj :: (Functor t, Typeable t, Member t r) => t v -> Union r v
- prj :: (Typeable t, Member t r) => Union r v -> Maybe (t v)
- prjForce :: (Typeable t, Member t r) => Union r v -> (t v -> a) -> a
- decomp :: Typeable t => Union (t :> r) v -> Either (Union r v) (t v)
- unsafeReUnion :: Union r w -> Union t w
- weaken :: (Typeable t, Functor t) => Union r w -> Union (t :> r) w
Classes
Monad transformer related
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
MemberU k set t r => SetMember (k -> * -> *) set t r |
Type-indexed co-product
Datatypes
Parameter r
is phantom: it just tells what could be in the union.
Where r
is t1 :> t2 ... :> tn
,
can be constructed with a
value of type Union
r vti 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.
Functions
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.