writer-cps-monads-tf-0.1.0.1: MonadWriter orphan instances for writer-cps-transformers

Copyright(c) Daniel Mendler 2016
(c) Andy Gill 2001
(c) Oregon Graduate Institute of Science and Technology 2001
LicenseBSD-style (see the file LICENSE)
Maintainermail@daniel-mendler.de
Stabilityexperimental
Portabilitynon-portable (type families)
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Writer.CPS

Contents

Description

Stricter writer monad using continuation-passing-style for the writer output.

Inspired by the paper Functional Programming with Overloading and Higher-Order Polymorphism, Mark P Jones (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html) Advanced School of Functional Programming, 1995.

Synopsis

The Writer monad

type Writer w = WriterT w Identity #

A writer monad parameterized by the type w of output to accumulate.

The return function produces the output mempty, while >>= combines the outputs of the subcomputations using mappend.

runWriter :: Monoid w => Writer w a -> (a, w) #

Unwrap a writer computation as a (result, output) pair. (The inverse of writer.)

execWriter :: Monoid w => Writer w a -> w #

Extract the output from a writer computation.

mapWriter :: (Monoid w, Monoid w') => ((a, w) -> (b, w')) -> Writer w a -> Writer w' b #

Map both the return value and output of a computation using the given function.

The WriterT monad transformer

data WriterT w m a :: * -> (* -> *) -> * -> * #

A writer monad parameterized by:

  • w - the output to accumulate.
  • m - The inner monad.

The return function produces the output mempty, while >>= combines the outputs of the subcomputations using mappend.

Instances

MonadTrans (WriterT w) 

Methods

lift :: Monad m => m a -> WriterT w m a #

Monad m => Monad (WriterT w m) 

Methods

(>>=) :: WriterT w m a -> (a -> WriterT w m b) -> WriterT w m b #

(>>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

return :: a -> WriterT w m a #

fail :: String -> WriterT w m a #

Functor m => Functor (WriterT w m) 

Methods

fmap :: (a -> b) -> WriterT w m a -> WriterT w m b #

(<$) :: a -> WriterT w m b -> WriterT w m a #

MonadFix m => MonadFix (WriterT w m) 

Methods

mfix :: (a -> WriterT w m a) -> WriterT w m a #

MonadFail m => MonadFail (WriterT w m) 

Methods

fail :: String -> WriterT w m a #

(Functor m, Monad m) => Applicative (WriterT w m) 

Methods

pure :: a -> WriterT w m a #

(<*>) :: WriterT w m (a -> b) -> WriterT w m a -> WriterT w m b #

(*>) :: WriterT w m a -> WriterT w m b -> WriterT w m b #

(<*) :: WriterT w m a -> WriterT w m b -> WriterT w m a #

MonadIO m => MonadIO (WriterT w m) 

Methods

liftIO :: IO a -> WriterT w m a #

(Functor m, MonadPlus m) => Alternative (WriterT w m) 

Methods

empty :: WriterT w m a #

(<|>) :: WriterT w m a -> WriterT w m a -> WriterT w m a #

some :: WriterT w m a -> WriterT w m [a] #

many :: WriterT w m a -> WriterT w m [a] #

(Functor m, MonadPlus m) => MonadPlus (WriterT w m) 

Methods

mzero :: WriterT w m a #

mplus :: WriterT w m a -> WriterT w m a -> WriterT w m a #

type WriterType (WriterT w m) # 
type WriterType (WriterT w m) = w

writerT :: (Functor m, Monoid w) => m (a, w) -> WriterT w m a #

runWriterT :: Monoid w => WriterT w m a -> m (a, w) #

Unwrap a writer computation.

execWriterT :: (Monad m, Monoid w) => WriterT w m a -> m w #

Extract the output from a writer computation.

mapWriterT :: (Monad n, Monoid w, Monoid w') => (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b #

Map both the return value and output of a computation using the given function.

Orphan instances

(Monoid w, Monad m) => MonadWriter (WriterT w m) Source # 

Associated Types

type WriterType (WriterT w m :: * -> *) :: * #

Methods

tell :: WriterType (WriterT w m) -> WriterT w m () #

listen :: WriterT w m a -> WriterT w m (a, WriterType (WriterT w m)) #

pass :: WriterT w m (a, WriterType (WriterT w m) -> WriterType (WriterT w m)) -> WriterT w m a #