Copyright | Andrew G. Seniuk 2014-2015 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Andrew Seniuk <rasfar@gmail.com> |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
- unionPats :: [Pattern] -> Pattern
- intersectPats :: [Pattern] -> Pattern
- subPat :: Pattern -> Pattern -> Bool
- mkPat :: forall d. Data d => d -> Pattern
- mkPatN :: forall d. Data d => Int -> d -> Pattern
- growPat :: forall d. Data d => Pattern -> d -> Pattern
- truncatePat :: Int -> Pattern -> Pattern
- shrinkPat :: Pattern -> Pattern
- emptyPat :: Pattern
- liftPats :: [Pattern] -> Pattern
- splicePats :: Pattern -> [Int] -> [(Int, Pattern)] -> Pattern
- elidePats :: Pattern -> [Int] -> [Int] -> Pattern
- erodePat :: StdGen -> [Int] -> Pattern -> (Pattern, StdGen)
- module Control.DeepSeq.Bounded.Pattern
- type Shape = Rose ()
- shapeOf :: forall d. Data d => d -> Shape
- ghom :: forall r d. Data d => GenericQ r -> d -> Rose r
- probDensRose :: Rose r -> Rose (r, Double)
- weightedRose :: Rose r -> Rose (r, Int)
- unzipRose :: Rose (r, s) -> (Rose r, Rose s)
- showRose :: Show r => Rose r -> String
Basic operations on Patterns
unionPats :: [Pattern] -> Pattern Source
Compute the union of a list of Pattern
s.
Note that unionPats is undefined when homologous nodes
specify incompatible arities (only possible when
WR
or TR
are involved).
XXX Support for the various attributes is work in progress. It may be impossible to arrive at a consistent treatment for all attributes under unions. This is work in progress, but the five un-modified W*
node types should be safe.
intersectPats :: [Pattern] -> Pattern Source
Compute the intersection of a list of Pattern
s.
Where two (or more) homologous WR
nodes disagree in arity,
the intersection at that position becomes WI
.
XXX This doesn't yet handle type-constrained PatNode
s (TI
, TR
, TN
or TW
). Other attributes are handled in a haphazard fashion. This is work in progress, but the five un-modified W*
node types should be safe.
subPat :: Pattern -> Pattern -> Bool Source
Return True
if the first pattern matches the second (and False
otherwise).
Arities must correspond (or the second pattern's node must be wild) for the match to succeed at each recursive PatNode
(i.e. WR
or TR
).
Matching does not imply spanning;
would work for that.flip
subPat
XXX This doesn't yet handle type-constrained PatNode
s (TI
, TR
, TN
or TW
), because intersectPats
doesn't. Generally speaking, it is difficult to arrive at a good policy for subpattern, union and intersection, when mixed types of nodes with various attribute values are considered! Other attributes are handled in a haphazard fashion. This is work in progress, but the five un-modified W*
node types should be safe.
More formally, we have two "Subpattern Axioms":
- Not More Specifc A subpattern (of a pattern) is never more specific (i.e. less permissive), in terms of what values it will match.
- Not More Forcing A subpattern never has greater forcing potential.
And a proper subpattern will always be strictly more permissive or less forcing (or both).
Operations for obtaining and modifying Patterns based on a term
mkPat :: forall d. Data d => d -> Pattern Source
Obtain a lazy, potentially infinite pattern, matching the shape of an arbitrary term (value expression).
There is only one kind of PatNode
employed here, WR
.
The Pattern
is extended indefinitely on demand. In case the
term has leaves, these will be WR
nodes with empty child lists
in the corresponding pattern.
Caveat: Note that mkPat
gives counter-intuitive results when used
on rose trees, in particular on Pattern
itself.
For example, a rose tree with a single node will have a 3-node /\ shape.)
Formally, mkPat
is not idempotent on Pattern
s, but rather grows
without bound when iterated. This shouldn't be an issue in practise.
mkPatN :: forall d. Data d => Int -> d -> Pattern Source
Obtain a lazy, finite pattern, matching the shape of
an arbitrary term, but only down to at most depth n
.
Satisfies
. (Later: I kinda doubt that is true in full generality?... Although it does convey the idea.)forcep
. mkPatN
n = forcen
n
Unlike mkPat
, three pattern node contexts arise here:
- those corresponding to actual leaf (nullary) nodes of the term
- these are
Node WR []
- these are
- interior nodes of the pattern corresponding to interior nodes of the term
- these are
Node WR chs
wherechs
are the child subpatterns of this interior pattern node
- these are
- leaf nodes of the pattern corresponding to interior nodes of the term, that is, non-leaf nodes of the term which are at a depth
n
of nested constructor applications.- these are
Node WR chs'
wherechs' = map (const $ Node WI []) chs = map (const emptyPat) chs
- this essentially says we're allowed to know the arity of the node, but aside from this cardinal number we know nothing whatsoever concerning the child subpatterns and are not even permitted to evaluate their heads
- these are
All interior nodes are WR
, and all leaf nodes are WI
; WS
never arise.
See caveat in the mkPat
documentation.
growPat :: forall d. Data d => Pattern -> d -> Pattern Source
Grow all leaves by one level within the shape of the provided value.
This is intended to be used with "plain" patterns, i.e. those
containing only WR
and WI
nodes. (There is no code enforcing this.)
A new growth node always replaces a WI
(leaf) node with a WR
node
bearing the suitable number of WI
children to encode arity (see
mkPat
for general commentary about this).
Operations for obtaining subpatterns (in the subPat
sense)
truncatePat :: Int -> Pattern -> Pattern Source
Given an integer depth and a pattern, truncate the pattern to extend to at most this requested depth.
Nodes in the truncated pattern which were WR
and are now leaves,
are changed to WI
.
XXX Note that *N
and *W
nodes are retained, so if you are using those then "extend to at most this depth" does not mean the forcing potential of the pattern is at most that depth... It would be quite possible to improve this, so *N
(and *W
nodes, obviously) are "weakened" (depth is reduced) so that they end at the truncation depth, regardless of how far up they reside. In particular, any *N
or *W
node at truncation depth could be replaced by WS
. This works well as all these node types are arity-agnostic.
shrinkPat :: Pattern -> Pattern Source
Elide all leaves which have no non-leaf sibling. We want the pattern to still match the same value, only less of it. Merely eliding all leaves would, in most cases, cause match failure, so we have to be a bit more subtle. There are some arbitrary decisions about the relaxation route through the lattice. (Refer to the source for details.)
More formally, we have some "Shrinkage Axioms". The first
two are really just the "Subpattern Axioms" again, that is,
shrinkage is always to a subpattern in our sense of the
word (see also subPat
):
- Not More Specifc Shrinkage is never towards a more specific (i.e. less permissive) pattern.
- Not More Forcing Shrinkage is never towards a pattern with greater forcing potential.
And additionally, for finite patterns only:
- Non-Constancy A finite pattern is constant under shrinkage iff the pattern is trivial (emptyPat, ".", Node WI []). However, infinite patterns have other limits. For instance, the infinite pattern
(yes you can do that!) is already stationary under shrinkage.concat
$repeat
"(." - Convergence On iteration, shrinkage of finite patterns reaches the trivial pattern in a number of steps proportional to the size of the initial pattern argument. (Actually,
*N
and*W
nodes can make this larger.) However, in the case of infinite patterns, all bets are off: Simple examples exist which converge immediately, or which continue shrinking indefinitely.)
Operations for the direct construction and perturbation of Patterns
There is no Nil
in the Pattern
type, but a single WI
node as
empty pattern is a dependable way to ensure that the empty pattern
never forces anything. This sets PatNodeAttrs
to emptyPatNodeAttrs
.
liftPats :: [Pattern] -> Pattern Source
This creates a new WR
node, the common root, with PatNodeAttrs
set
to emptyPatNodeAttrs
. The argument patterns become the children of
the root (order is preserved).
splicePats :: Pattern -> [Int] -> [(Int, Pattern)] -> Pattern Source
Add children to a node (interior or leaf) of the target.
The first argument is target pattern, the second is a path (0-based
indexing) from the root of the target to any choice node,
and the third is a list of subpatterns for insertion, along with the
indices of the insertion slots.
Indices range through -1,0..n
, where n
is the number of
existing children, and -1
is short for n
(so you don't need
to count off the children to append!).
Indices are always relative to the original target as it was received.
elidePats :: Pattern -> [Int] -> [Int] -> Pattern Source
Elide children of a node (interior or leaf) of the target.
The first argument is target pattern, the second is a path (0-based
indexing) from the root of the target to any choice node,
and the third is a list of child indices for elision.
Indices range through -1,0..n-1
, where n
is the number of
existing children, and -1
is short for n-1
(so you don't need
to count off the children to elide the rightmost).
Indices are always relative to the original target as it was received.
erodePat :: StdGen -> [Int] -> Pattern -> (Pattern, StdGen) Source
Select a leaf at random, and elide it. In order to achieve fairness, the node probabilities are weighted by nodes in branch. The path arg can "focus" the stochastic erosion to only consider leaves beneath a given node.
Re-exported for convenience
Debugging convenience
probDensRose :: Rose r -> Rose (r, Double) Source
weightedRose :: Rose r -> Rose (r, Int) Source