kure-2.4.2: Combinators for Strategic Programming

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

Language.KURE.Translate

Contents

Description

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

This module also contains Translate instance declarations for the Monad and Arrow type-class families. Given these instances, 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

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

(Category (Translate c m), Monad m) => Arrow (Translate c m)

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

(Arrow (Translate c m), MonadPlus m) => ArrowZero (Translate c m)

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

(ArrowZero (Translate c m), MonadPlus m) => ArrowPlus (Translate c m)

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

(Arrow (Translate c m), 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.

(Category (Translate c m), MonadCatch m) => CategoryCatch (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.

(Monad (Translate c m a), MonadPlus m) => MonadPlus (Translate c m a)

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

(Functor (Translate c m a), Applicative m) => Applicative (Translate c m a)

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

(Applicative (Translate c m a), Alternative m) => Alternative (Translate c m a)

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

(Monad (Translate c m a), 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.

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

Build a constant Translate from a monadic computation.

contextT :: Monad m => Translate c m a cSource

Extract the current context.

exposeT :: Monad m => Translate c m a (c, a)Source

Expose the current context and value.

mapT :: Monad m => Translate c m a b -> Translate c m [a] [b]Source

Map a Translate over a list.

sideEffectR :: Monad m => (c -> a -> m ()) -> Rewrite c m aSource

An identity Rewrite with side-effects.

Bi-directional Translations

data BiTranslate c m a b Source

An undirected Translate.

Instances

type BiRewrite c m a = BiTranslate c m a aSource

A BiTranslate that shares the same source and target type.

bidirectional :: Translate c m a b -> Translate c m b a -> BiTranslate c m a bSource

Construct a BiTranslate from two opposite Translates.

forewardT :: BiTranslate c m a b -> Translate c m a bSource

Extract the foreward Translate from a BiTranslate.

backwardT :: BiTranslate c m a b -> Translate c m b aSource

Extract the backward Translate from a BiTranslate.

whicheverR :: MonadCatch m => BiRewrite c m a -> Rewrite c m aSource

Try the BiRewrite forewards, then backwards if that fails. Useful when you know which rule you want to apply, but not which direction to apply it in.

invert :: BiTranslate c m a b -> BiTranslate c m b aSource

Invert the forewards and backwards directions of a BiTranslate.

Lenses

data Lens c m a b Source

A Lens is a way to focus on a sub-structure of type b from a structure of type a.

Instances

Monad m => Category (Lens c m) 
(Category (Lens c m), MonadCatch m) => CategoryCatch (Lens c m)

A Lens is deemed to have failed (and thus can be caught) if either it fails on the way down, or, crucially, if it would fail on the way up for an unmodified value. However, actual failure on the way up is not caught (as by then it is too late to use an alternative Lens). This means that, in theory, a use of catch could cause a succeeding Lens application to fail. But provided lens is used correctly, this should never happen.

lens :: Translate c m a ((c, b), b -> m a) -> Lens c m a bSource

The primitive way of building a Lens. If the unfocussing function is applied to the value focussed on then it should succeed, and produce the same value as the original argument (of type a).

lensT :: Lens c m a b -> Translate c m a ((c, b), b -> m a)Source

Convert a Lens into a Translate that produces a sub-structure (and its context) and an unfocussing function.

focusR :: Monad m => Lens c m a b -> Rewrite c m b -> Rewrite c m aSource

Apply a Rewrite at a point specified by a Lens.

focusT :: Monad m => Lens c m a b -> Translate c m b d -> Translate c m a dSource

Apply a Translate at a point specified by a Lens.

testLensT :: MonadCatch m => Lens c m a b -> Translate c m a BoolSource

Check if the focusing succeeds, and additionally whether unfocussing from an unchanged value would succeed.

bidirectionalL :: Monad m => BiTranslate c m a b -> Lens c m a bSource

Construct a Lens from a BiTranslate.

pureL :: Monad m => (a -> b) -> (b -> a) -> Lens c m a bSource

Construct a Lens from two pure functions.