kure-2.0.0: Combinators for Strategic Programming

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

Language.KURE.Translate

Contents

Description

This module defines the main KURE types: Translate, Rewrite and Lens. Rewrite and Lens are just special cases of Translate, and so any function that operates on Translate is also applicable to Rewrite and Lens (although care should be taken in the Lens case).

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

Translate is a translation or strategy that translates from a value in a context to a monadic value.

Constructors

Translate 

Fields

apply :: c -> a -> m b

Apply a Translate to a value and its context.

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.

(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 Rewrite is a Translate that shares the same source and target type.

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.

Lenses

type Lens c m a b = Translate c m a ((c, b), b -> m a)Source

A Lens is a way to focus in on a particular point in a structure.

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

lens is the primitive way of building a Lens.

idL :: Monad m => Lens c m a aSource

Identity Lens.

tryL :: MonadPlus m => Lens c m a a -> Lens c m a aSource

Catch a failing endoLens, making it into an identity.

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

Composition of Lenss.

sequenceL :: MonadPlus m => [Lens c m a a] -> Lens c m a aSource

Sequence a list of endoLenss.

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

Construct a Lens from two pure functions.

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.