kure-2.14.0: Combinators for Strategic Programming

Portabilityghc
Stabilitybeta
MaintainerNeil Sculthorpe <neil@ittc.ku.edu>
Safe HaskellSafe-Inferred

Language.KURE.Translate

Contents

Description

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

Translate is an instance of the Monad and Arrow type-class families, and consequently many of the desirable combinators over Translate 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

Translations and Rewrites

data Translate 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 Translate type is the basis of the entire KURE library.

Instances

Monad m => Arrow (Translate c m)

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

MonadPlus m => ArrowZero (Translate c m)

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

MonadPlus m => ArrowPlus (Translate c m)

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

Monad m => ArrowApply (Translate c m)

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

Monad m => Category (Translate c m)

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

Monad m => Monad (Translate c m a)

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

Functor m => Functor (Translate c m a)

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

MonadPlus m => MonadPlus (Translate c m a)

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

Applicative m => Applicative (Translate c m a)

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

Alternative m => Alternative (Translate c m a)

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

MonadIO m => MonadIO (Translate c m a)

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

MonadCatch m => MonadCatch (Translate c m a)

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

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

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

type Rewrite c m a = Translate c m a aSource

A Translate that shares the same source and target type.

apply :: Translate c m a b -> c -> a -> m bSource

Apply a Translate to a value and its context.

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

The primitive way of building a Translate.

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

The primitive way of building a Rewrite.

contextfreeT :: (a -> m b) -> Translate c m a bSource

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

contextonlyT :: (c -> m b) -> Translate c m a bSource

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

constT :: m b -> Translate c m a bSource

Build a constant Translate from a monadic computation.