kure-2.16.6: Combinators for Strategic Programming

Copyright(c) 2012--2014 The University of Kansas
LicenseBSD3
MaintainerNeil Sculthorpe <neil@ittc.ku.edu>
Stabilitybeta
Portabilityghc
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.KURE.Transform

Contents

Description

This module defines Transform and Rewrite, the main KURE types. Rewrite is just a special case of Transform, and so any function that operates on Transform is also applicable to Rewrite.

Transform is an instance of the Monad and Arrow type-class families, and consequently many of the desirable combinators over Transform and Rewrite are special cases of existing monadic or arrow combinators. Language.KURE.Combinators provides some additional combinators that aren't in the standard libraries.

Synopsis

Transformations and Rewrites

data Transform c m a b Source

An abstract representation of a transformation from a value of type a in a context c to a monadic value of type m b. The Transform type is the basis of the entire KURE library.

Instances

Monad m => Category * (Transform c m)

The Kleisli Category induced by m, lifting through a Reader transformer, where c is the read-only environment.

Monad m => Arrow (Transform c m)

The Kleisli Arrow induced by m, lifting through a Reader transformer, where c is the read-only environment.

MonadPlus m => ArrowZero (Transform c m)

The Kleisli Arrow induced by m, lifting through a Reader transformer, where c is the read-only environment.

MonadPlus m => ArrowPlus (Transform c m)

The Kleisli Arrow induced by m, lifting through a Reader transformer, where c is the read-only environment.

Monad m => ArrowApply (Transform c m)

The Kleisli Arrow induced by m, lifting through a Reader transformer, where c is the read-only environment.

Alternative m => Alternative (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

Monad m => Monad (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

Functor m => Functor (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

MonadPlus m => MonadPlus (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

Applicative m => Applicative (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

MonadIO m => MonadIO (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

MonadCatch m => MonadCatch (Transform c m a)

Lifting through a Reader transformer, where (c,a) is the read-only environment.

(Monad m, Monoid b) => Monoid (Transform c m a b)

Lifting through the Monad and a Reader transformer, where (c,a) is the read-only environment.

type Translate c m a b = Transform c m a b Source

A deprecated synonym for Transform.

type Rewrite c m a = Transform c m a a Source

A transformation that shares the same source and target type.

applyT :: Transform c m a b -> c -> a -> m b Source

Apply a transformation to a value and its context.

applyR :: Rewrite c m a -> c -> a -> m a Source

Apply a rewrite to a value and its context.

apply :: Transform c m a b -> c -> a -> m b Source

Deprecated: Please use applyT instead.

A deprecated synonym for applyT.

transform :: (c -> a -> m b) -> Transform c m a b Source

The primitive way of building a transformation.

translate :: (c -> a -> m b) -> Translate c m a b Source

Deprecated: Please use transform instead.

A deprecated synonym for transform.

rewrite :: (c -> a -> m a) -> Rewrite c m a Source

The primitive way of building a rewrite.

contextfreeT :: (a -> m b) -> Transform c m a b Source

Build a Transform that doesn't depend on the context.

contextonlyT :: (c -> m b) -> Transform c m a b Source

Build a Transform that doesn't depend on the value.

constT :: m b -> Transform c m a b Source

Build a constant Transform from a monadic computation.

effectfreeT :: Monad m => (c -> a -> b) -> Transform c m a b Source

Build a Transform that doesn't perform any monadic effects.