| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Generics.BiGUL.TH
Description
A higher-level syntax for programming in BiGUL, implemented in Template Haskell.
- deriveBiGULGeneric :: Name -> Q [InstanceDec]
- rearrS :: Q Exp -> Q Exp
- rearrV :: Q Exp -> Q Exp
- update :: Q Pat -> Q Pat -> Q [Dec] -> Q Exp
- normal :: ExpOrPat a => Q Exp -> a -> Q Exp
- normalSV :: (ExpOrPat a, ExpOrPat b, ExpOrPat c) => a -> b -> c -> Q Exp
- adaptive :: Q Exp -> Q Exp
- adaptiveSV :: (ExpOrPat a, ExpOrPat b) => a -> b -> Q Exp
Generic instance derivation
deriveBiGULGeneric :: Name -> Q [InstanceDec] Source #
Generate a Generic instance for a named datatype
so that its constructors can be used in rearranging lambda-expressions.
Invoke this function on a datatype T by putting
deriveBiGULGeneric ''T
at the top level of a source file (say, after the definition of T).
Only simple datatypes and newtypes are supported (no GADTs, for example);
type parameters and named fields (record syntax) are supported.
Rearrangement
- BiGUL does not support pattern matching for n-tuples where n >= 3.
For convenience (but possibly confusingly),
the programmer can use n-tuple patterns with the Template Haskell rearrangement syntax,
but these patterns are translated into ones for right-nested pairs.
For example, a 3-tuple pattern
(x, y, z)used in a rearrangement is in fact translated into(x, (y, z)). - In a rearranging lambda-expression, if a pattern variable is used more than once in the body,
the type of the pattern variable will be required to be an instance of
Eq. If an error message
‘C’ is not in the type environment at a reify
is reported where
Cis a constructor used in a rearrangement, perhaps you forget to invokederiveBiGULGenericonC’s datatype.
A higher-level syntax for RearrV,
allowing its first and second arguments to be specified in terms of a simple lambda-expression.
The usual way of using rearrV is
$(rearrV [| f |]) b :: BiGUL s v
where f :: v -> v' is a simple lambda-expression and b :: BiGUL s v' an inner program.
In f, wildcard ‘_’ is not allowed, and all pattern variables must be used in the body.
(This is for ensuring that the view information is fully embedded into the source.)
Arguments
| :: Q Pat | source pattern |
| -> Q Pat | view pattern |
| -> Q [Dec] | named updates (as a declaration list) |
| -> Q Exp |
A succinct syntax dealing with the frequently occurring situation where both the source and view are rearranged into products and their components further synchronised by inner updates. For example, the program
$(update [p| x:xs |] [p| x:xs |] [d| x = Replace; xs = b |]) :: BiGUL [a] [a]
matches both the source and view lists with a cons pattern, marking their head and tail as x and xs respectively,
and synchronises the heads using Replace (which is the program associated with x in the declaration list)
and the tails using some b :: BiGUL [a] [a]. In short, the program is equivalent to
$(rearrS [| \(x:xs) -> (x, xs) |])$
$(rearrV [| \(x:xs) -> (x, xs) |])$
Replace `Prod` b(Admittedly, it is an abuse of syntax to represent a list of named BiGUL programs in terms of a declaration list, but it is the closest thing we can find that works directly with Template Haskell.)
Case branch construction
In the following branch construction syntax, the meaning of a boolean-valued pattern-matching lambda-expression is redefined as a total function which computes to
Falsewhen an input does not match the pattern; this meaning is different from that of a general pattern-matching lambda-expression, which fails to compute when the pattern is not matched. For example, in general the lambda-expression\(s:ss) (v:vs) -> s == v
will fail to compute if one of its inputs is an empty list; when used in branch construction, however, the lambda-expression will compute to
Falseupon encountering an empty list.- An argument whose type is an instance of
ExpOrPat(a typeclass not exported) can be either a quoted expression (of typeQExp), which should describe a unary or binary predicate (boolean-valued function), or a quoted pattern (of typeQPat), which is translated into a unary predicate that computes toTrueif the pattern is matched, orFalseotherwise.
Arguments
| :: ExpOrPat a | |
| => Q Exp | main condition (binary predicate on the source and view) |
| -> a | exit condition (unary predicate on the source) |
| -> Q Exp |
Construct a normal branch, for which a main condition on the source and view and
an exit condition on the source should be specified. The usual way of using normal is
$(normal [| p |] [| q |]) b :: CaseBranch s v
where
p :: s -> v -> Bool,q :: s -> Bool, andb :: BiGUL s v, which is the branch body.
Arguments
| :: (ExpOrPat a, ExpOrPat b, ExpOrPat c) | |
| => a | main source condition (unary predicate on the source) |
| -> b | main view condition (unary predicate on the view) |
| -> c | exit condition (unary predicate on the source) |
| -> Q Exp |
A special case of normal where the main condition is specified as the conjunction of two unary predicates
on the source and view respectively. The usual way of using normalSV is
$(normalSV [| ps |] [| pv |] [| q |]) b :: CaseBranch s v
where
ps :: s -> Bool,pv :: v -> Bool,q :: s -> Bool, andb :: BiGUL s v, which is the branch body.
Construct an adaptive branch, for which a main condition on the source and view should be specified.
The usual way of using adaptive is
$(adaptive [| p |]) f :: CaseBranch s v
where
p :: s -> v -> Boolandf :: s -> v -> s, which is the adaptation function.
Arguments
| :: (ExpOrPat a, ExpOrPat b) | |
| => a | main source condition (unary predicate on the source) |
| -> b | main view condition (unary predicate on the view) |
| -> Q Exp |
A special case of adaptive where the main condition is specified as the conjunction of two unary predicates
on the source and view respectively. The usual way of using adaptiveSV is
$(adaptiveSV [| ps |] [| pv |]) f :: CaseBranch s v
where
ps :: s -> Bool,pv :: v -> Bool, andf :: s -> v -> s, which is the adaptation function.