| 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 | 
Control.DeepSeq.Bounded.Pattern
Contents
Description
- type Pattern = Rose PatNode
 - data PatNode
- = WI !PatNodeAttrs
 - | WR !PatNodeAttrs
 - | WS !PatNodeAttrs
 - | WN !PatNodeAttrs
 - | WW !PatNodeAttrs
 - | TI !PatNodeAttrs
 - | TR !PatNodeAttrs
 - | TN !PatNodeAttrs
 - | TW !PatNodeAttrs
 - | XX
 
 - data PatNodeAttrs = PatNodeAttrs {
- uniqueID :: !Int
 - depth :: !Int
 - doConstrainType :: !Bool
 - typeConstraints :: ![String]
 - doDelay :: !Bool
 - delayus :: !Int
 - doSpark :: !Bool
 - doPseq :: !Bool
 - pseqPerm :: Maybe [Int]
 - doTrace :: !Bool
 - doPing :: !Bool
 - pingParentTID :: Maybe ThreadId
 - doDie :: !Bool
 - doTiming :: !Bool
 - timestamp :: !Int
 - parent_timestamp :: !Int
 - delta_timestamp :: !Int
 
 - isWI :: PatNode -> Bool
 - isWR :: PatNode -> Bool
 - isWS :: PatNode -> Bool
 - isWN :: PatNode -> Bool
 - isWW :: PatNode -> Bool
 - isTI :: PatNode -> Bool
 - isTR :: PatNode -> Bool
 - isTN :: PatNode -> Bool
 - isTW :: PatNode -> Bool
 - emptyPatNodeAttrs :: PatNodeAttrs
 - getPatNodeAttrs :: PatNode -> PatNodeAttrs
 - setPatNodeAttrs :: PatNode -> PatNodeAttrs -> PatNode
 - setPatNodePingParentTID :: ThreadId -> PatNode -> PatNode
 - showPerm :: Maybe [Int] -> String
 - showPatRaw :: Pattern -> String
 - showPatNodeRaw :: PatNode -> String
 - setPatternPatNodeUniqueIDs :: Int -> Pattern -> Pattern
 - data Rose a = Node a [Rose a]
 - data SeqNode
 
Pattern datatype
Only WR and TR allow for explicit recursion.
All other PatNode values are in leaf position when they occur.
Concrete syntax for W* and T* nodes are identical. A T* node
 is simply a W* node bearing a type constraint attribute.
 Please refer to the Grammar further down this page for more details,
 and links to even more information.
Notes:
I've kept the T* types broken out as separate constructors, although they could be handled as special cases of W* types in a way analogous to doSpark (PatNodeAttrs).  These were not "absorbed" because the semantics seems icky, and it's still not clear which W* types even make sense with a type constraint...
I tried parametrising this, but it messed up my Show instance and seemed to be pulling me away from Haskell 98, so reverted.  It looks a bit ugly in the Haddock unfortunately, with the redundant column of PatNodeAttrs. The T* nodes will be absorbed by PatNodeAttrs in version 0.7, and it won't look so bad.
Constructors
| WI !PatNodeAttrs | (Insulate, . ) Don't even unwrap the constructor of this node.  | 
| WR !PatNodeAttrs | (Recurse, (...) )   Continue pattern matching descendants, provided that arity is compatible (else the match fails).  Interior nodes of a pattern are always   | 
| WS !PatNodeAttrs | (Stop, ! )   Stop recursing (nothing more forced down this branch). This is equivalent to   | 
| WN !PatNodeAttrs | (N (depth), *n )     | 
| WW !PatNodeAttrs | (Wild, * )   Fully force (rnf) the whole branch under this node. Note that this is not achievable as a limiting case of   | 
| TI !PatNodeAttrs | Don't even unwrap the constructor of this node, if it's type is in the list; otherwise behave as   | 
| TR !PatNodeAttrs | Match any of the types in the list (and continue pattern matching descendants); behave as   | 
| TN !PatNodeAttrs | 
  | 
| TW !PatNodeAttrs | Fully force (rnf) the whole branch under this node, if the node type matches any of the types in the list; otherwise behave as   | 
| XX | Dummy node type reserved for internal use.  | 
data PatNodeAttrs Source
These attributes can be mixed freely. Certain combinations may seem unuseful, but nothing is prohibited by design.
While this may seem bloated, most of these capabilities can be truly banished from the code via build flags (use_par_patnode, etc.).
In the concrete pattern syntax, all attributes are represented
 as prefix modifiers (prefixing the
 '.', '!', '(' or '*'
 pattern node designator).
 Prefix modifiers may be given in any order.
 NOTE: The depth field in PatNodeAttrs is not really an attribute, 
  it is logically a (mandatory) extra parameter to WN and TN 
  nodes (and only those).  (Whereas attributes are all optional 
  and node-type-agnostic.)  The depth is stored here as a 
  convenient hack only!  Explanation becomes necessary since 
  Haddock makes it visible no matter what, I mention this, in case 
  of confusion, because the depth is always postfix, not prefix. 
Constructors
| PatNodeAttrs | |
Fields 
  | |
Instances
Pattern DSL
Grammar
pat          ->  [ modifiers ] pat'
pat'         ->     .  |  !  |  * [ decimalint ]  |  ( { pat } )
modifiers    ->  zero or one of each of the eight modifier, in any order
modifier     ->     =  |  +  |  ^  |  /  |  %
                 |  : typename { ; typename } :
                 |  @ decimalint
                 |  > permutation
typename     ->  string containing neither : (unless escaped) nor ;
escaped      ->  \\: 
decimalint   ->  digit string not beginning with zero
permutation  ->  of an initial part of the lowercase alphabet, e.g. cdba
Here is the grammar in a more vivid rendering. (Haddock makes it tricky to distinguish between metasyntax and concrete syntax.)
Optional whitespace can go between any two tokens (basically, anyplace there is space shown in the grammar above).
Semicolons never need escaping, because they're already illegal as part of any Haskell type name.
The semantics are given formally in the PatNode and PatNodeAttrs
 documentation, as well as informally in the examples below and from
 the project homepage.
Examples
"(...)" will match any ternary constructor.
rnfp "(!!!)" expr will force evaluation of expr to a depth of two,
 provided the head of expr is a ternary constructor; otherwise it behaves
 as rnfp "." expr (i.e. do nothing).
rnfp "(...)" expr will force it to only a depth of one. That is,
 rnfp "(...)" expr =
 rnfp
 "!" expr when the head of expr
 is a ternary constructor; otherwise it won't perform any evaluation.
rnfp "(***)" expr will rnf (deep) any ternary constructor, but
 will not touch any constructor of other arity.
rnfp "(.(*.).)" expr will match any ternary constructor, then
 match the second subexpression constructor if it is binary, and
 if matching got this far, then the left sub-subexpression
 will be forced (rnf), but not the right.
rnfp "(!:T:*.)" expr will unwrap (shallow seq) the first
 subexpression of expr, and the third subexpression won't be touched.
 As for the second subexpression, if its type is T it will be
 completely evaluated (rnf), but otherwise it won't be touched.
rnfp "(=**)" expr will spark the parallel complete evaluation of
 the two components of any pair. (Whether the computations actually
 run in parallel depends on resource availability, and the discretion
 of the RTS, as usual).
rnfp "(>ba(+*+*)=*)" expr matches a binary constructor, whose first parameter is also a binary constructor. This identifies three main AST branches -- serendipitously symbolised by asterisks -- making up the expression: which branches we'll call A, B and C. So this example will perform rnf, but in a controlled manner: A and B are forced in parallel with C, and furthermore, B is forced before A. A traceline will be printed at the beginning of the forcing of B and then another traceline will be printed at the beginning of the forcing of A. Note that "(=>ba(+*+*)*)" would be a legal equivalent.
I make no claims as to the usefulness of the examples, they are here just to explain the semantics of the DSL.
Details
The present pattern parser ignores any subpatterns of all
 pattern nodes except WR and TR, optionally emitting a warning.
 (XXX In 0.6.0.0, I'm not sure the warning is still possible.)
 Hence, only WR and TR patterns are potentially recursive.
When specifying the list of subpatterns with WR and TR,
 in order for the match to succeed, the number of subpatterns must
 be equal to the arity of the constructor the pattern node is
 matching against. (No other pattern node types accept subpatterns.)
Additionally, in the case of TR, matching (and consequent recursion) will only
 succeed if the term node has constructor name which is listed in the constraints.
It would be possible to have TR nodes interpret the constraint
 as type name rather than constructor name, but this would require sum patterns
 (maybe for version 0.7).  The problem is, no single WR node
 can match multiple constructors of differing arity.  This has the
 feel of an excellent application for SOP generics!...
(As contrasted with TR nodes,) TI, TN and TW nodes interpret
 type constraint strings as type names (not constructor names).
 A moment's reflection will show you why it must be so.
Finally, if you're trying to name a constructor with : in its name, you must escape the colon with a backslash thus \\: because the unescaped colon is used as (opening and) closing character for lists of type and constructor names.
setPatNodeAttrs :: PatNode -> PatNodeAttrs -> PatNode Source
setPatNodePingParentTID :: ThreadId -> PatNode -> PatNode Source
showPatRaw :: Pattern -> String Source
showPatNodeRaw :: PatNode -> String Source
setPatternPatNodeUniqueIDs :: Int -> Pattern -> Pattern Source