tagged-transformer-0.8: Provides newtype wrappers for phantom types to avoid unsafely passing dummy arguments

Copyright2011-2013 Edward Kmett
LicenseBSD3
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell98

Data.Functor.Trans.Tagged

Contents

Description

 

Synopsis

Tagged values

newtype TaggedT s m b Source

A Tagged monad parameterized by:

  • s - the phantom type
  • m - the inner monad
  • b - the tagged value

| A TaggedT s m b value is a monadic value m b with an attached phantom type s. This can be used in place of the more traditional but less safe idiom of passing in an undefined value with the type, because unlike an (s -> m b), a TaggedT s m b can't try to use the argument s as a real value.

Moreover, you don't have to rely on the compiler to inline away the extra argument, because the newtype is "free"

Constructors

TagT 

Fields

untagT :: m b
 

Instances

MonadReader r m => MonadReader r (TaggedT k * s m) 
MonadState t m => MonadState t (TaggedT k * s m) 
MonadWriter w m => MonadWriter w (TaggedT k * s m) 
Typeable (k -> (k -> *) -> k -> *) (TaggedT k k) 
ComonadHoist (TaggedT k * s) 
ComonadTrans (TaggedT k * s) 
MonadTrans (TaggedT k * s) 
Alternative m => Alternative (TaggedT k * s m) 
Monad m => Monad (TaggedT k * s m) 
Functor m => Functor (TaggedT k * s m) 
MonadFix m => MonadFix (TaggedT k * s m) 
MonadPlus m => MonadPlus (TaggedT k * s m) 
Applicative m => Applicative (TaggedT k * s m) 
Foldable f => Foldable (TaggedT k * s f) 
Traversable f => Traversable (TaggedT k * s f) 
Comonad w => Comonad (TaggedT k * s w) 
Contravariant m => Contravariant (TaggedT k * s m) 
Distributive f => Distributive (TaggedT k * s f) 
MonadThrow m => MonadThrow (TaggedT k * s m) 
MonadCatch m => MonadCatch (TaggedT k * s m) 
MonadMask m => MonadMask (TaggedT k * s m) 
MonadIO m => MonadIO (TaggedT k * s m) 
MonadCont m => MonadCont (TaggedT k * s m) 
Plus m => Plus (TaggedT k * s m) 
Alt m => Alt (TaggedT k * s m) 
Apply m => Apply (TaggedT k * s m) 
Bind m => Bind (TaggedT k * s m) 
Extend f => Extend (TaggedT k * s f) 
Eq (m b) => Eq (TaggedT k k s m b) 
Ord (m b) => Ord (TaggedT k k s m b) 
Read (m b) => Read (TaggedT k k s m b) 
Show (m b) => Show (TaggedT k k s m b) 

type Tagged s b = TaggedT s Identity b Source

A Tagged s b value is a value b with an attached phantom type s. This can be used in place of the more traditional but less safe idiom of passing in an undefined value with the type, because unlike an (s -> b), a Tagged s b can't try to use the argument s as a real value.

Moreover, you don't have to rely on the compiler to inline away the extra argument, because the newtype is "free"

tag :: b -> Tagged s b Source

Tag a value in Identity monad

tagT :: m b -> TaggedT s m b Source

Easier to type alias for TagT

untag :: Tagged s b -> b Source

Untag a value in Identity monad

retag :: TaggedT s m b -> TaggedT t m b Source

Some times you need to change the tag you have lying around. Idiomatic usage is to make a new combinator for the relationship between the tags that you want to enforce, and define that combinator using retag.

data Succ n
retagSucc :: Tagged n a -> Tagged (Succ n) a
retagSucc = retag

mapTaggedT :: (m a -> n b) -> TaggedT s m a -> TaggedT s n b Source

Lift an operation on underlying monad

reflected :: forall s m a. (Applicative m, Reifies s a) => TaggedT s m a Source

Reflect reified value back in Applicative context

reflectedM :: forall s m a. (Monad m, Reifies s a) => TaggedT s m a Source

Reflect reified value back in Monad context

asTaggedTypeOf :: s -> TaggedT s m b -> s Source

asTaggedTypeOf is a type-restricted version of const. It is usually used as an infix operator, and its typing forces its first argument (which is usually overloaded) to have the same type as the tag of the second.

proxy :: Tagged s b -> Proxy s -> b Source

Convert from a Tagged representation to a representation based on a Proxy.

proxyT :: TaggedT s m b -> Proxy s -> m b Source

Convert from a TaggedT representation to a representation based on a Proxy.

unproxy :: (Proxy s -> a) -> Tagged s a Source

Convert from a representation based on a Proxy to a Tagged representation.

unproxyT :: (Proxy s -> m a) -> TaggedT s m a Source

Convert from a representation based on a Proxy to a TaggedT representation.

tagSelf :: a -> Tagged a a Source

Tag a value with its own type.

tagTSelf :: m a -> TaggedT a m a Source

Tag a value with its own type.

untagSelf :: Tagged a a -> a Source

untagSelf is a type-restricted version of untag.

untagTSelf :: TaggedT a m a -> m a Source

untagSelf is a type-restricted version of untag.

tagWith :: proxy s -> a -> Tagged s a Source

Another way to convert a proxy to a tag.

tagTWith :: proxy s -> m a -> TaggedT s m a Source

Another way to convert a proxy to a tag.

witness :: Tagged a b -> a -> b Source

witnessT :: TaggedT a m b -> a -> m b Source