Safe Haskell | None |
---|---|
Language | Haskell2010 |
Control.Ether.Tagged
Description
Type-level machinery for tag manipulation.
- class Taggable m where
- class (Taggable m, Tag m ~ Just tag) => Tagged m tag | m -> tag where
- type Tags m = MaybeToList (Tag m) ++ ListMapTag (Inners m)
- type Inners m = Inners' (Inner m)
- class UniqueTag a
- type family UniqueTags m :: Constraint
- ensureUniqueTags :: UniqueTags m => m a -> m a
Documentation
The Taggable
class defines the type families to manage tags in monad
transformer stacks. Its kind is restricted to * -> *
to prevent incorrect
instances.
Associated Types
The Tag
type family equals Nothing
for most types, but for tagged
monad transformers it equals Just tag
.
type Inner m :: Maybe (* -> *) Source
The Inner
type family equals Nothing
for most types, but for
monad transformers with inner monad m
it equals Just m
.
Instances
Taggable IO Source | |
Taggable Identity Source | |
Taggable STM Source | |
Taggable First Source | |
Taggable Last Source | |
Taggable Maybe Source | |
Taggable ((->) r) Source | |
Taggable (Either e) Source | |
Taggable (ST s) Source | |
Taggable (ST s) Source | |
Taggable (Proxy *) Source | |
Taggable (ListT m) Source | |
Taggable (MaybeT m) Source | |
Taggable (IdentityT m) Source | |
Taggable (ContT r m) Source | |
Taggable (ReaderT r m) Source | |
Taggable (StateT s m) Source | |
Taggable (StateT s m) Source | |
Taggable (ExceptT e m) Source | |
Taggable (WriterT w m) Source | |
Taggable (WriterT w m) Source | |
Taggable (ReaderT tag r m) Source | |
Taggable (WriterT tag w m) Source | |
Taggable (StateT tag s m) Source | |
Taggable (StateT tag s m) Source | |
Taggable (ExceptT tag e m) Source |
class (Taggable m, Tag m ~ Just tag) => Tagged m tag | m -> tag where Source
The Tagged
type class establishes a relationship between a tagged
monad transformer and its untagged counterpart.
Minimal complete definition
Nothing
The main purpose of the UniqueTag
class is to provide clear error
messages when the tag uniqueness property is violated. You should never
write instances for it unless you know what you're doing.
type family UniqueTags m :: Constraint Source
The UniqueTags
constraint placed on a type variable representing a
monad transformer stack ensures that every tag in the stack appears
only once.
Equations
UniqueTags m = Unique (Tags m) |
ensureUniqueTags :: UniqueTags m => m a -> m a Source
Type-restricted version of id
that adds a UniqueTags
constraint to
the provided monadic value.