BiGUL-1.0.1: The Bidirectional Generic Update Language

Safe HaskellNone
LanguageHaskell2010

Generics.BiGUL

Contents

Description

This is the main module defining the syntax of BiGUL. Generics.BiGUL.TH provides some higher-level syntax for writing BiGUL programs. See Generics.BiGUL.Lib.HuStudies for some small, illustrative examples. To execute BiGUL programs, use put and get from Generics.BiGUL.Interpreter.

Synopsis

Main syntax

data BiGUL s v where Source #

This is the datatype of BiGUL programs, as a GADT indexed with the source and view types. Most of the types appearing in a BiGUL program should be instances of Show to enable error reporting.

Constructors

Fail :: String -> BiGUL s v

Abort computation and emit an error message.

Skip :: Eq v => (s -> v) -> BiGUL s v

Keep the source unchanged, with the side condition that the view can be completely determined from the source. Use skip when the view is a constant.

Replace :: BiGUL s s

Replace the source with the view (which should have the same type as the source).

Prod :: (Show s, Show s', Show v, Show v') => BiGUL s v -> BiGUL s' v' -> BiGUL (s, s') (v, v') infixr 1

When the source and view are both pairs, perform update on the first/second source and view components using the first/second inner program.

RearrS :: (Show s', Show v) => Pat s env con -> Expr env s' -> BiGUL s' v -> BiGUL s v

Rearrange the source into an intermediate form, which is updated by the inner program, and then invert the rearrangement. Instead of using RearrS directly, use rearrS instead, which offers a more intuitive syntax. Note that the inner program should make sure that the updated source still retains the intermediate form (so the inversion can succeed).

RearrV :: (Show s, Show v') => Pat v env con -> Expr env v' -> BiGUL s v' -> BiGUL s v

Rearrange the view into a new one before continuing with the remaining program. To guarantee well-behavedness, the expression should use all variables in the pattern. Instead of using RearrV directly, use rearrV instead, which offers a more intuitive syntax and checks whether all pattern variables are used.

Dep :: (Eq v', Show s, Show v) => (v -> v') -> BiGUL s v -> BiGUL s (v, v')

When the view is a pair and the second component depends entirely on the first one, discard the second component and continue with the remaining program.

Case :: [(s -> v -> Bool, CaseBranch s v)] -> BiGUL s v

Case analysis on both the source and view.

Compose :: (Show s, Show m, Show v) => BiGUL s m -> BiGUL m v -> BiGUL s v infixr 1

Standard composition of bidirectional transformations.

Checkpoint :: (Show s, Show v) => String -> BiGUL s v -> BiGUL s v

Display a programmer-supplied message prefixed with “checkpoint:” in error traces.

data CaseBranch s v Source #

A branch used in Case (whose type is parametrised by the source and view types) can be either Normal or Adaptive. The exit conditions specified in Normal branches should (ideally) be disjoint. Overlapping exit conditions are still allowed for fast prototyping, though — the putback semantics of Case will compute successfully as long as the ranges of the branches are disjoint (regardless of whether the exit conditions are specified precisely enough).

Constructors

Normal (BiGUL s v) (s -> Bool)

A Normal branch contains an inner program, which should update the source such that both the main condition (on both the source and view) and the exit condition (on the source) are satisfied.

Adaptive (s -> v -> s)

An Adaptive branch contains an adaptation function, which should modify the source such that a Normal branch is applicable.

Rearrangement syntax

The following pattern and expression syntax for rearrangement operations are designed to be type-safe but not intended to be programmer-friendly. The programmer is expected to use the higher-level syntax from Generics.BiGUL.TH, which desugars into the following raw syntax. For more detail about patterns and expressions, see Generics.BiGUL.PatternMatching.

data Pat a env con where Source #

The datatype of patterns is indexed by three types: the type of values to which a pattern is applicable, the type of environments resulting from pattern matching, and the type of containers used during inverse evaluation of expressions.

Constructors

PVar :: Eq a => Pat a (Var a) (Maybe a)

Variable pattern, the value extracted from which can be duplicated.

PVar' :: Pat a (Var a) (Maybe a)

Variable pattern, the value extracted from which cannot be duplicated.

PConst :: Eq a => a -> Pat a () ()

Constant pattern.

PProd :: Pat a a' a'' -> Pat b b' b'' -> Pat (a, b) (a', b') (a'', b'') infixr 1

Product pattern.

PLeft :: Pat a a' a'' -> Pat (Either a b) a' a''

Left pattern, matching values of shape `Left x :: Either a b` for some `x :: a`.

PRight :: Pat b b' b'' -> Pat (Either a b) b' b''

Right pattern, matching values of shape `Right y :: Either a b` for some `y :: b`.

PIn :: InOut a => Pat (F a) b c -> Pat a b c

Constructor pattern, unwrapping a value to its sum-of-products representation. (Invoke deriveBiGULGenerics on the datatype involved first.)

newtype Var a Source #

A marker for variable positions in environment types.

Constructors

Var a 

Instances

Show a => Show (Var a) Source # 

Methods

showsPrec :: Int -> Var a -> ShowS #

show :: Var a -> String #

showList :: [Var a] -> ShowS #

data Direction env a where Source #

Directions point to a variable position (marked by Var) in an environment. Their type is indexed by the environment type and the type of the variable position being pointed to.

Constructors

DVar :: Direction (Var a) a

Point to the current variable position.

DLeft :: Direction a t -> Direction (a, b) t

Point to the left part of the environment.

DRight :: Direction b t -> Direction (a, b) t

Point to the right part of the environment.

data Expr env a where Source #

Expressions are patterns whose variable positions contain directions pointing into some environment. Their type is indexed by the environment type and the type of the expressed value.

Constructors

EDir :: Direction env a -> Expr env a

Direction expression, referring to a value in the environment.

EConst :: Eq a => a -> Expr env a

Constant expression.

EProd :: Expr env a -> Expr env b -> Expr env (a, b) infixr 1

Product expression.

ELeft :: Expr env a -> Expr env (Either a b)

Left expression (producing an Either-value).

ERight :: Expr env b -> Expr env (Either a b)

Right expression (producing an Either-value).

EIn :: InOut a => Expr env (F a) -> Expr env a

Constructor expression, wrapping a sum-of-products representation into data. (Invoke deriveBiGULGenerics on the datatype involved first.)