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 |
A bi-directional transformation is a transformation that can be applied in either direction.
Synopsis
- data BiTransform c m a b
- type BiTranslate c m a b = BiTransform c m a b
- type BiRewrite c m a = BiTransform c m a a
- bidirectional :: Transform c m a b -> Transform c m b a -> BiTransform c m a b
- forwardT :: BiTransform c m a b -> Transform c m a b
- backwardT :: BiTransform c m a b -> Transform c m b a
- whicheverR :: MonadCatch m => BiRewrite c m a -> Rewrite c m a
- invertBiT :: BiTransform c m a b -> BiTransform c m b a
- beforeBiR :: Monad m => Transform c m a b -> (b -> BiRewrite c m a) -> BiRewrite c m a
- afterBiR :: Monad m => BiRewrite c m a -> Rewrite c m a -> BiRewrite c m a
- extractBiT :: (MonadFail m, Injection a u, Injection b u) => BiTransform c m u u -> BiTransform c m a b
- promoteBiT :: (MonadFail m, Injection a u, Injection b u) => BiTransform c m a b -> BiTransform c m u u
- extractBiR :: (MonadFail m, Injection a u) => BiRewrite c m u -> BiRewrite c m a
- promoteBiR :: (MonadFail m, Injection a u) => BiRewrite c m a -> BiRewrite c m u
- extractWithFailMsgBiT :: (MonadFail m, Injection a u, Injection b u) => String -> BiTransform c m u u -> BiTransform c m a b
- promoteWithFailMsgBiT :: (MonadFail m, Injection a u, Injection b u) => String -> BiTransform c m a b -> BiTransform c m u u
- extractWithFailMsgBiR :: (MonadFail m, Injection a u) => String -> BiRewrite c m u -> BiRewrite c m a
- promoteWithFailMsgBiR :: (MonadFail m, Injection a u) => String -> BiRewrite c m a -> BiRewrite c m u
Bi-directional Transformations
data BiTransform c m a b Source #
An undirected Transform
.
Instances
Monad m => Category (BiTransform c m :: Type -> Type -> Type) Source # | |
Defined in Language.KURE.BiTransform id :: forall (a :: k). BiTransform c m a a # (.) :: forall (b :: k) (c0 :: k) (a :: k). BiTransform c m b c0 -> BiTransform c m a b -> BiTransform c m a c0 # |
type BiTranslate c m a b = BiTransform c m a b Source #
A deprecated synonym for BiTranslate
.
type BiRewrite c m a = BiTransform c m a a Source #
A BiTransform
that shares the same source and target type.
bidirectional :: Transform c m a b -> Transform c m b a -> BiTransform c m a b Source #
Construct a BiTransform
from two opposite Transform
s.
forwardT :: BiTransform c m a b -> Transform c m a b Source #
Extract the forward Transform
from a BiTransform
.
backwardT :: BiTransform c m a b -> Transform c m b a Source #
Extract the backward Transform
from a BiTransform
.
whicheverR :: MonadCatch m => BiRewrite c m a -> Rewrite c m a Source #
Try the BiRewrite
forwards, then backwards if that fails.
Useful when you know which rule you want to apply, but not which direction to apply it in.
invertBiT :: BiTransform c m a b -> BiTransform c m b a Source #
Invert the forwards and backwards directions of a BiTransform
.
beforeBiR :: Monad m => Transform c m a b -> (b -> BiRewrite c m a) -> BiRewrite c m a Source #
Perform the argument transformation before either direction of the bidirectional rewrite.
afterBiR :: Monad m => BiRewrite c m a -> Rewrite c m a -> BiRewrite c m a Source #
Apply the argument rewrite to the result of either direction of the bidirectional rewrite.
Bi-directional Injections
extractBiT :: (MonadFail m, Injection a u, Injection b u) => BiTransform c m u u -> BiTransform c m a b Source #
Convert a bidirectional transformation over an injected value into a bidirectional transformation over non-injected values, (failing if an injected value cannot be projected).
promoteBiT :: (MonadFail m, Injection a u, Injection b u) => BiTransform c m a b -> BiTransform c m u u Source #
Promote a bidirectional transformation from value to value into a transformation over an injection of those values, (failing if an injected value cannot be projected).
extractBiR :: (MonadFail m, Injection a u) => BiRewrite c m u -> BiRewrite c m a Source #
Convert a bidirectional rewrite over an injected value into a bidirectional rewrite over a projection of that value, (failing if an injected value cannot be projected).
promoteBiR :: (MonadFail m, Injection a u) => BiRewrite c m a -> BiRewrite c m u Source #
Promote a bidirectional rewrite over a value into a bidirectional rewrite over an injection of that value, (failing if an injected value cannot be projected).
extractWithFailMsgBiT :: (MonadFail m, Injection a u, Injection b u) => String -> BiTransform c m u u -> BiTransform c m a b Source #
As extractBiT
, but takes a custom error message to use if extraction fails.
promoteWithFailMsgBiT :: (MonadFail m, Injection a u, Injection b u) => String -> BiTransform c m a b -> BiTransform c m u u Source #
As promoteBiT
, but takes a custom error message to use if promotion fails.
extractWithFailMsgBiR :: (MonadFail m, Injection a u) => String -> BiRewrite c m u -> BiRewrite c m a Source #
As extractBiR
, but takes a custom error message to use if extraction fails.
promoteWithFailMsgBiR :: (MonadFail m, Injection a u) => String -> BiRewrite c m a -> BiRewrite c m u Source #
As promoteBiR
, but takes a custom error message to use if promotion fails.