elevator-0.2.3: Immediately lifts to a desired level

Copyright(c) Fumiaki Kinoshita 2015
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Elevator

Contents

Description

Automated effect elevator

Synopsis

Documentation

type Elevate f g = (Tower g, f Floors1 g) Source

f can be lifted to g

elevate :: Elevate f g => f a -> g a Source

Lift a thing, automatically.

Construction kit

class Tower f where Source

A class of types which have bases.

Minimal complete definition

Nothing

Associated Types

type Floors f :: [* -> *] Source

Methods

stairs :: Gondola f :* Floors f Source

The product of all ways to lift.

Instances

Tower [] 
Tower IO 
Tower Maybe 
Tower Identity 
Tower ((->) r) 
Tower (Either e) 
Tower (ST s) 
(Monad m, Tower m) => Tower (MaybeT m) 
(Monad m, Tower m) => Tower (ListT m) 
Generate (* -> *) xs => Tower (Union * xs) 
(Monoid w, Monad m, Tower m) => Tower (WriterT w m) 
(Monoid w, Monad m, Tower m) => Tower (WriterT w m) 
(Monad m, Tower m) => Tower (StateT s m) 
(Monad m, Tower m) => Tower (StateT s m) 
(Monad m, Tower m) => Tower (ReaderT r m) 
(Error e, Monad m, Tower m) => Tower (ErrorT e m) 
(Monad m, Tower m, Monoid w) => Tower (RWST r w s m) 
(Monad m, Tower m, Monoid w) => Tower (RWST r w s m) 

type Floors1 f = f : Floors f Source

The parents and itself.

newtype Gondola f g :: (k -> *) -> (k -> *) -> *

Transformation between effects

Constructors

Gondola 

Fields

runGondola :: forall a. g a -> f a
 

rung :: (forall x. f x -> g x) -> (:*) (k -> *) (Gondola k g) fs -> (:*) (k -> *) (Gondola k g) ((:) (k -> *) f fs) infixr 0

Add a new transformation.

data h :* s :: (k -> *) -> [k] -> * where

The type of extensible products.

Constructors

Nil :: (:*) k h ([] k) 

Instances

Typeable ((k -> *) -> [k] -> *) ((:*) k) 
WrapForall k * Eq h xs => Eq ((:*) k h xs) 
(Eq ((:*) k h xs), WrapForall k * Ord h xs) => Ord ((:*) k h xs) 
WrapForall k * Show h xs => Show ((:*) k h xs) 
WrapForall k * Monoid h xs => Monoid ((:*) k h xs) 
WrapForall k * Binary h xs => Binary ((:*) k h xs) 

(*++*) :: (:*) k h xs -> (:*) k h ys -> (:*) k h ((++) k xs ys) infixr 0

Combine products.

mapGondolas :: (forall x. m x -> n x) -> (Gondola m :* xs) -> Gondola n :* xs Source

Open unions

newtype Union xs a :: [k -> *] -> k -> *

Constructors

Union 

Fields

getUnion :: (:|) (k -> *) (K1 k a) xs
 

Instances

Generate (* -> *) xs => Tower (Union * xs) 
type Floors (Union * xs) = xs 

reunion :: (:*) (k -> *) (Gondola k m) xs -> Union k xs a -> m a