| Copyright | (c) 2012--2021 The University of Kansas | 
|---|---|
| License | BSD3 | 
| Maintainer | Neil Sculthorpe <neil.sculthorpe@ntu.ac.uk> | 
| Stability | beta | 
| Portability | ghc | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
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
- data Transform c m a b
- type Translate c m a b = Transform c m a b
- type Rewrite c m a = Transform c m a a
- applyT :: Transform c m a b -> c -> a -> m b
- applyR :: Rewrite c m a -> c -> a -> m a
- apply :: Transform c m a b -> c -> a -> m b
- transform :: (c -> a -> m b) -> Transform c m a b
- translate :: (c -> a -> m b) -> Translate c m a b
- rewrite :: (c -> a -> m a) -> Rewrite c m a
- contextfreeT :: (a -> m b) -> Transform c m a b
- contextonlyT :: (c -> m b) -> Transform c m a b
- constT :: m b -> Transform c m a b
- effectfreeT :: Monad m => (c -> a -> b) -> Transform c m a b
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 :: Type -> Type -> Type) Source # | The  | 
| Monad m => Arrow (Transform c m) Source # | The  | 
| Defined in Language.KURE.Transform Methods arr :: (b -> c0) -> Transform c m b c0 # first :: Transform c m b c0 -> Transform c m (b, d) (c0, d) # second :: Transform c m b c0 -> Transform c m (d, b) (d, c0) # (***) :: Transform c m b c0 -> Transform c m b' c' -> Transform c m (b, b') (c0, c') # (&&&) :: Transform c m b c0 -> Transform c m b c' -> Transform c m b (c0, c') # | |
| MonadPlus m => ArrowZero (Transform c m) Source # | The  | 
| Defined in Language.KURE.Transform | |
| MonadPlus m => ArrowPlus (Transform c m) Source # | The  | 
| Monad m => ArrowApply (Transform c m) Source # | The  | 
| Defined in Language.KURE.Transform | |
| Monad m => Monad (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| Functor m => Functor (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| MonadFail m => MonadFail (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| Defined in Language.KURE.Transform | |
| Applicative m => Applicative (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| Defined in Language.KURE.Transform Methods pure :: a0 -> Transform c m a a0 # (<*>) :: Transform c m a (a0 -> b) -> Transform c m a a0 -> Transform c m a b # liftA2 :: (a0 -> b -> c0) -> Transform c m a a0 -> Transform c m a b -> Transform c m a c0 # (*>) :: Transform c m a a0 -> Transform c m a b -> Transform c m a b # (<*) :: Transform c m a a0 -> Transform c m a b -> Transform c m a a0 # | |
| MonadIO m => MonadIO (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| Defined in Language.KURE.Transform | |
| Alternative m => Alternative (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| MonadPlus m => MonadPlus (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| MonadCatch m => MonadCatch (Transform c m a) Source # | Lifting through a Reader transformer, where (c,a) is the read-only environment. | 
| (Applicative m, Semigroup b) => Semigroup (Transform c m a b) Source # | Lifting through the  | 
| (Monad m, Monoid b) => Monoid (Transform c m a b) Source # | Lifting through the  | 
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.
transform :: (c -> a -> m b) -> Transform c m a b Source #
The primitive way of building a transformation.
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.