ether-0.3.0.0: Monad transformers and classes

Safe HaskellNone
LanguageHaskell2010

Control.Ether.Wrapped

Description

Annotating monads with tags to turn untagged constraints into tagged ones.

import qualified Control.Monad.State as T
import Control.Ether.TH (ethereal)
import Control.Monad.Ether.State (MonadState)
import Control.Ether.Wrapped (ethered)

ethereal "Foo" "foo"

f :: T.MonadState Int m => m String
f = fmap show T.get

g :: MonadState Foo Int m => m String
g = ethered foo f

Synopsis

Documentation

newtype WrappedEther tag m a Source

Wrap a monad to attach a tag to it.

Constructors

WrapEther 

Fields

unwrapEther :: m a
 

Instances

MonadReader tag r m => MonadReader tag r (WrappedEther tag' m) 
MonadWriter tag w m => MonadWriter tag w (WrappedEther tag' m) 
MonadState tag s m => MonadState tag s (WrappedEther tag' m) 
MonadExcept tag e m => MonadExcept tag e (WrappedEther tag' m) 
MonadExcept tag e m => MonadError e (WrappedEther tag m) 
MonadReader tag r m => MonadReader r (WrappedEther tag m) 
MonadState tag s m => MonadState s (WrappedEther tag m) 
MonadWriter tag w m => MonadWriter w (WrappedEther tag m) 
Alternative m => Alternative (WrappedEther tag m) 
Monad m => Monad (WrappedEther tag m) 
Functor m => Functor (WrappedEther tag m) 
MonadFix m => MonadFix (WrappedEther tag m) 
MonadPlus m => MonadPlus (WrappedEther tag m) 
Applicative m => Applicative (WrappedEther tag m) 
MonadIO m => MonadIO (WrappedEther tag m) 
Generic (WrappedEther tag m a) 
Newtype (WrappedEther tag m a) 
type Rep (WrappedEther tag m a) 
type O (WrappedEther tag m a) = GO (Rep (WrappedEther tag m a)) 

ethered :: proxy tag -> WrappedEther tag m a -> m a Source

Annotate a polymorphic monadic computation with a tag.