deepseq-bounded-0.7.0.2: Bounded deepseq, including support for generic deriving

CopyrightAndrew G. Seniuk 2014-2015
LicenseBSD-style (see the file LICENSE)
MaintainerAndrew Seniuk <rasfar@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.DeepSeq.Bounded.Pattern

Contents

Description

 

Synopsis

Pattern datatype

data PatNode Source

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 WR, i.e. WR is the only PatNode offering explicit recursion. The rest (?S, ?N, and ?W) are implicitly recursive, but control is only as powerful as NFDataN.

WS !PatNodeAttrs

(Stop, ! )   Stop recursing (nothing more forced down this branch). This is equivalent to WN at a depth of 1. WS is somewhat vestigial, and may be removed in 0.7.

WN !PatNodeAttrs

(N (depth), *n )   rnfn n the branch under this node.

WW !PatNodeAttrs

(Wild, * )   Fully force (rnf) the whole branch under this node. Note that this is not achievable as a limiting case of WN, so the existence of WW is formally justifiable in a way that WS is not. Having said that, for all practical purposes, a WN with depth = maxBound::Int could be used for WW...

TI !PatNodeAttrs

Don't even unwrap the constructor of this node, if it's type is in the list; otherwise behave as WW. (Note this behaviour is the complement of TW behaviour.)

TR !PatNodeAttrs

Match any of the types in the list (and continue pattern matching descendants); behave as WI for nodes of type not in the list.

TN !PatNodeAttrs

rnfn n the branch under this node, if the node type matches any of the types in the list; otherwise behave as WI.

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 WI. (Note this behaviour is the complement of TI behaviour.)

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

uniqueID :: !Int

Optional for convenience; set up with setPatternPatNodeUniqueIDs. Beware that this function is not called automatically (or if it happens to be at the moment, this behaviour shouldn't be relied upon). For example, if you were to call growPat, the added nodes would all have "uniqueID" of 0.

depth :: !Int

(*n)   Depth of forcing for WN and TN nodes (n is decimal integer depth). (This is not an attribute, it's a displaced mandatory parameter, specific to these two node types.)

doConstrainType :: !Bool

(:)   Constrain pattern to match only types named in typeConstraints. XXX This should be considered experimental still in 0.6. This and the NFDataPDyn aspects lost attention to seqaid.

typeConstraints :: ![String]

The list of type rep strings used in the type constraint (when doConstrainType is True).

doDelay :: !Bool

(@)   Delay (current thread) for delayus microseconds. XXX Still buggy?

delayus :: !Int

Microseconds of delay (when doDelay is True).

doSpark :: !Bool

(=)   Spark matching for parallel evaluation.

doPseq :: !Bool

(>perm)   Sequence child subpattern matching, according to the permutation in pseqPerm.

pseqPerm :: Maybe [Int]

Lowercase alphabetic sequence is used in the concrete pattern syntax. >cdba(wxyz) will cause subpattern matching recursion on a quaternary constructor, with the subpattern computations sequenced y then z then x then w (order corresponds to cdba).

doTrace :: !Bool

(+)   Output a traceline to stderr.

doPing :: !Bool

(^)   Raise informative (asynchronous? support is not strong for it, throwTo blocks...) exception en passant, for benefit of upstream. The exception is thrown in a new thread, so that the pattern matching continues; for a terminating version, see doDie.

pingParentTID :: Maybe ThreadId

Needed as argument for throwTo call.

doDie :: !Bool

(/)   Kill (just this) thread.

doTiming :: !Bool

(%)   Note time passed since pattern-matched parent node. XXX Work in progress.

timestamp :: !Int
 
parent_timestamp :: !Int
 
delta_timestamp :: !Int
 

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 = rnf expr.

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.

Why depend on whole containers package, when we only want a rose tree

data Rose a Source

Constructors

Node a [Rose a] 

Instances

Functor Rose 
FF Pattern 
Eq a => Eq (Rose a) 
Show a => Show (Rose a) 
NFData a => NFData (Rose a) 
Typeable (* -> *) Rose 
data F Pattern = FPattern v 

Preferred to have this in Seqable, but had cyclical dependency issues

data SeqNode Source

Constructors

Insulate 
Propagate 
Spark 

Instances