| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Test.StrictCheck.Demand
Contents
Description
A Demand on some value of type T is shaped like a T, but possibly
    truncated, to represent partial evaluation. This module defines the type of
    demands, and functions to manipulate them for the purpose of constructing
    demand specifications.
A demand for some type T can be represented one of two interconvertible
    ways:
- explicitly, as a recursively interleaved ShapeofT
- implicitly, as a value of Twith specially-tagged bottom values which represent un-evaluated portions of that value
The explicit representation is useful for writing traversals and other such
   manipulations of demand values, while the implicit representation can prove
   convenient for writing demand specifications. The implicit representation is
   the default when writing specifications, but through the use of toDemand
   and fromDemand, either representation can be used wherever it is most
   appropriate.
- data Thunk a
- type Demand = (%) Thunk
- type PosDemand a = Shape a Demand
- pattern E :: Shape a Demand -> Demand a
- pattern T :: Demand a
- evaluateDemand :: forall a. Shaped a => PosDemand a -> a -> ()
- shrinkDemand :: forall a. Shaped a => PosDemand a -> [PosDemand a]
- prettyDemand :: Shaped a => Demand a -> String
- printDemand :: Shaped a => Demand a -> IO ()
- eqDemand :: forall a. Shaped a => Demand a -> Demand a -> Bool
- showPrettyFieldThunkS :: Bool -> String -> Int -> Rendered Thunk -> String -> String
- thunk :: forall a. a
- isThunk :: Shaped a => a -> Bool
- toDemand :: Shaped a => a -> Demand a
- fromDemand :: Shaped a => Demand a -> a
The explicit Demand interface
A Thunk a is either an a or a Thunk
When we interleave this type into the Shape of some type, we get the type
 of demands on that type.
Thunk a is isomorphic to a (strict) Maybe a.
Instances
| Functor Thunk Source # | |
| Applicative Thunk Source # | |
| Shaped a => Eq (Demand a) Source # | 
 | 
| Eq a => Eq (Thunk a) Source # | |
| Num a => Num (Thunk a) Source # | |
| Ord a => Ord (Thunk a) Source # | |
| Show a => Show (Thunk a) Source # | |
| Generic (Thunk a) Source # | |
| type Rep (Thunk a) Source # | |
type Demand = (%) Thunk Source #
A Demand on some type a is the same shape as that original a, but with
 possible Thunks interleaved into it
type PosDemand a = Shape a Demand Source #
A PosDemand is a "strictly positive" demand, i.e. one where the topmost
 level of the demanded value has definitely been forced
This is the one-level unwrapping of Demand, and is useful to express some
 invariants in specifications
pattern E :: Shape a Demand -> Demand a Source #
Pattern synonym to abbreviate demand manipulation: E a = Wrap (Eval a)
Manipulating explicit Demands
evaluateDemand :: forall a. Shaped a => PosDemand a -> a -> () Source #
Evaluate some value of type a to the degree specified by the given demand
If the demand and the value diverge (they pick a different side of a sum),
 evaluation will stop at this point. Usually, evaluateDemand is only called
 on demands which are known to be structurally-compatible with the
 accompanying value, although nothing really goes wrong if this is not true.
shrinkDemand :: forall a. Shaped a => PosDemand a -> [PosDemand a] Source #
Shrink a non-zero demand (analogous to QuickCheck's shrink)
While QuickCheck's typical shrink instances reduce the size of a value by
 slicing off the top-most structure, shrinkDemand reduces the size of a
 demand by pruning it's deepest leaves. This ensures that all resultant
 shrunken demands are strict sub-demands of the original.
printDemand :: Shaped a => Demand a -> IO () Source #
Print a demand to standard output
printDemand = putStrLn . prettyDemand
eqDemand :: forall a. Shaped a => Demand a -> Demand a -> Bool Source #
Determine if two demands are exactly equal
This relies on the match method from the Shaped instance for the two
 demands, and does not require the underlying types to have Eq instances.
 However, this means that types whose match methods are more coarse than
 their equality will be compared differently by eqDemand. In particular,
 the demand representations of functions will all be compared to be equal.
showPrettyFieldThunkS :: Bool -> String -> Int -> Rendered Thunk -> String -> String Source #
A very general showsPrec style function for printing demands
showPrettyFieldThunkS q t p r returns a function (String -> String) which
 appends its input to a pretty-printed representation of a demand.
Specifically:
 * q is a boolean flag determining if names should be printed
 as qualified
 * t is a string which is to be printed when a thunk is encountered
 * p is the precedence context of this function call
 * r is the 'Rendered Thunk' representing some demand
This is very general, but we expose it in its complexity just in case some person wants to build a different pretty-printer.
The precedence-aware pretty-printing algorithm used here is adapted from a solution given by Brian Huffman on StackOverflow: https://stackoverflow.com/questions/27471937/43639618#43639618.
The implicit Demand interface
A bottom value (inhabiting all types) which StrictCheck interprets as an unevaluated subpart of a data structure
toDemand thunk == T fromDemand T == thunk
isThunk :: Shaped a => a -> Bool Source #
Tests if a particular value is an implicit thunk
In order to work, this function evaluates its input to weak-head normal form; keep this in mind if you care about laziness.