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

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

Control.DeepSeq.Bounded.NFDataP

Contents

Description

This module provides an overloaded function, deepseqp, for partially (or fully) evaluating data structures to bounded depth via pattern matching on term shape, and on class, type, and constructor names.

There are two ways to use this API.

  1. You can use the PatNode constructors directly.
  2. You can compile your patterns from strings in a concise embedded language.

There's no difference in expressive power, but use of the DSL is recommended, because the embedded Pattern compiler can catch some errors that GHC cannot (using PatNode constructors explicitly). Also, the pattern strings are easier to read and write.

Motivation

A typical use is to ensure any exceptions hidden within lazy fields of a data structure do not leak outside the scope of the exception handler; another is to force evaluation of a data structure in one thread, before passing it to another thread (preventing work moving to the wrong threads). Unlike DeepSeq, potentially infinite coinductive data types are supported by principled bounding of deep evaluation.

It is also useful for diagnostic purposes when trying to understand and manipulate space/time trade-offs in lazy code, and as an optimal substitute for deepseq (where "optimal" doesn't include changing the code to remove the need for artificial forcing!).

deepseqp with optimal patterns is usually a better solution even than stict fields in your data structures, because the latter will behave strictly everywhere the constructors are used, instead of just where its laziness is problematic.

There may be possible applications to the prevention of resource leaks in lazy streaming, but I'm not certain.

Semantics

(For additional details, see Control.DeepSeq.Bounded.Pattern.)

deepseqp and friends artifically force evaluation of a term so long as the pattern matches.

A mismatch occurs at a pattern node when the corresponding constructor node either:

  • has arity different than the number of subpatterns (only when subpatterns given)
  • has class/type/name not named in the constraint (only when constraint given)

A mismatch will cause evaluation down that branch to stop, but any upstream matching/forcing will continue uninterrupted. Note that patterns may extend beyond the values they match against, without incurring any mismatch. This semantics is not the only possible, but bear in mind that order of evaluation is nondeterministic, barring further measures.

See also NFDataPDyn for another approach, which dynamically generates forcing patterns, and can depend on value info (in addition to type info).

Synopsis

Pattern-bounded analogues of deepseq and force

deepseqp :: NFDataP a => String -> a -> b -> b Source

deepseqp: evaluates the first argument to the depth specified by a Pattern, before returning the second.

Quoting from the DeepSeq.hs (deepseq package):

"deepseq can be useful for forcing pending exceptions, eradicating space leaks, or forcing lazy I/O to happen. It is also useful in conjunction with parallel Strategies (see the parallel package).

There is no guarantee about the ordering of evaluation. The implementation may evaluate the components of the structure in any order or in parallel. To impose an actual order on evaluation, use pseq from Control.Parallel in the parallel package."

Composition fuses (see deepseqp_).

forcep :: NFDataP a => String -> a -> a Source

a variant of deepseqp that is sometimes convenient:

forcep pat x = x `deepseqp pat` x

forcep pat x evaluates x to the depth determined by pat, and then returns x. Note that forcep pat x only takes effect when the value of forcep pat x itself is demanded, so essentially it turns shallow evaluation into evaluation to arbitrary bounded depth.

Composition fuses (see forcep_).

Avoid DSL compilation overhead

deepseqp_ :: NFDataP a => Pattern -> a -> b -> b Source

Self-composition fuses via

    "deepseqp_/composition"
       forall p1 p2 x1 x2.
           (.) (deepseqp_ p2 x2) (deepseqp_ p1 x1)
         = deepseqp_ ( liftPats [p1, p2] ) (x1,x2)

(Other fusion rules, not yet documented, may also be in effect.)

forcep_ :: NFDataP a => Pattern -> a -> a Source

Self-composition fuses via

    "forcep_/composition"
       forall p1 p2 x.
           (.) (forcep_ p2) (forcep_ p1) x
         = forcep_ ( unionPats [p1, p2] ) x

(Other fusion rules, not yet documented, may also be in effect.)

Related modules re-exported

Class of things that can be evaluated over an arbitrary finite pattern

class (Typeable a, NFDataN a, NFData a) => NFDataP a where Source

A class of types that can be evaluated over an arbitrary finite pattern.

Minimal complete definition

Nothing

Methods

rnfp :: Pattern -> a -> () Source

Self-composition fuses via

    "rnfp/composition"
       forall p1 p2 x.
           (.) (rnfp p2) (rnfp p1) x
         = rnfp ( unionPats [p1, p2] ) x

(Other fusion rules, not yet documented, may also be in effect.)

Instances

NFDataP Bool 
NFDataP Char 
NFDataP Double 
NFDataP Float 
NFDataP Int 
NFDataP Int8 
NFDataP Int16 
NFDataP Int32 
NFDataP Int64 
NFDataP Integer 
NFDataP Word 
NFDataP Word8 
NFDataP Word16 
NFDataP Word32 
NFDataP Word64 
NFDataP () 
NFDataP Version 
NFDataP a => NFDataP [a] 
(Integral a, NFDataP a) => NFDataP (Ratio a) 
Typeable * a => NFDataP (Fixed a) 
(RealFloat a, NFDataP a) => NFDataP (Complex a) 
NFDataP a => NFDataP (Maybe a) 
(Typeable * a, Typeable * b) => NFDataP (a -> b) 
(NFDataP a, NFDataP b) => NFDataP (Either a b) 
(Typeable * a, NFDataP a, Typeable * b, NFDataP b) => NFDataP (a, b) 
(Ix a, NFDataP a, NFDataP b) => NFDataP (Array a b) 
(Typeable * a, NFDataP a, Typeable * b, NFDataP b, Typeable * c, NFDataP c) => NFDataP (a, b, c) 
(Typeable * a, NFDataP a, Typeable * b, NFDataP b, Typeable * c, NFDataP c, Typeable * d, NFDataP d) => NFDataP (a, b, c, d) 
(Typeable * a1, NFDataP a1, Typeable * a2, NFDataP a2, Typeable * a3, NFDataP a3, Typeable * a4, NFDataP a4, Typeable * a5, NFDataP a5) => NFDataP (a1, a2, a3, a4, a5) 
(Typeable * a1, NFDataP a1, Typeable * a2, NFDataP a2, Typeable * a3, NFDataP a3, Typeable * a4, NFDataP a4, Typeable * a5, NFDataP a5, Typeable * a6, NFDataP a6) => NFDataP (a1, a2, a3, a4, a5, a6) 
(Typeable * a1, NFDataP a1, Typeable * a2, NFDataP a2, Typeable * a3, NFDataP a3, Typeable * a4, NFDataP a4, Typeable * a5, NFDataP a5, Typeable * a6, NFDataP a6, Typeable * a7, NFDataP a7) => NFDataP (a1, a2, a3, a4, a5, a6, a7)