guarded-rewriting-0.1: Datatype-generic rewriting with preconditions

Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org

Generics.Instant.Rewriting

Contents

Description

This is the top module for the rewriting library. All functionality is implemented in this module. For examples of how to use the library, see the included files in the directory examples, or the benchmark in the directory performance.

Synopsis

The class to signal availability of rewriting for a type

class (Representable a, Typeable a, Eq a, Empty (Rep a), Extensible (Rep a), Matchable (Rep a), Substitutable (Rep a), Sampleable (Rep a), Diffable (Rep a), Validatable (Rep a)) => Rewritable a Source

The Rewritable class is used to signal types that can be rewritten and to ``tie the recursive knot'' of the generic functions.

Top-level functions

rewrite :: Rewritable a => Rule a -> a -> aSource

Rewrite a term. The term is unchanged if the rule cannot be applied.

rewriteM :: (Rewritable a, Monad m) => Rule a -> a -> m aSource

Rewrite a term. Monad fail is used if the rule cannot be applied.

validate :: Rewritable a => Rule a -> BoolSource

Validate a rewrite rule

synthesise :: (IsRule a, Nillable (Env a), Recordable (Env a), Testable (Env a), FiniteEnv (Env a) ~ True) => a -> Rule (Obj a)Source

Synthesise a function into a rewrite rule

Building rewrite rules

data Template a Source

Templates

Constructors

Template a a Bool 

Instances

Rewritable a => IsRule (Template a) 

(+->) :: a -> a -> Template aSource

data Rule a Source

Rules

Internal classes: might be necessary to add new base types

class Extensible a whereSource

Schemes

Associated Types

data Ext a :: * -> *Source

Methods

toExt :: a -> Ext a USource

class Matchable a whereSource

Matching

Methods

match' :: (Nillable gam, Monad m) => Ext a gam -> a -> m (Subst gam)Source

class Sampleable a whereSource

Sampling

Methods

left' :: aSource

right' :: aSource

class Empty a whereSource

Type level validation for the datatypes to be rewritten: there can be no recursive calls on the leftmost constructor

Methods

empty' :: aSource

Instances

Empty Char 
Empty Float 
Empty Int 
Empty U 
Rewritable a => Empty (Var a) 
Rewritable a => Empty (Rec a) 
(HasRec a, Empty a, Empty b) => Empty (:+: a b) 
(Empty a, Empty b) => Empty (:*: a b) 
Empty a => Empty (C c a) 

class HasRec a whereSource

Methods

hasRec' :: a -> BoolSource

Instances

HasRec Char 
HasRec Float 
HasRec Int 
HasRec U 
HasRec (Var a) 
HasRec (Rec a) 
(HasRec a, HasRec b) => HasRec (:+: a b) 
(HasRec a, HasRec b) => HasRec (:*: a b) 
HasRec a => HasRec (C c a) 

type family Finite a :: *Source

class Diffable a whereSource

Diff

Methods

diff' :: Typeable b => Ext a gam -> Ext a gam -> Maybe (Ext a (b :*: gam))Source

class Validatable a whereSource

Validating synthesised rules

Methods

record :: Ext a gam -> Record gam -> Record gamSource

class Nillable gam whereSource

Methods

empty :: Subst gamSource

Instances

Nillable U 
(Rewritable a, Nillable gam) => Nillable (:*: a gam) 

Re-exported for convenience

class Typeable a

The class Typeable allows a concrete representation of a type to be calculated.