| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Strict.Wrapper
Synopsis
- pattern Strict :: Strictly t => t -> Strict t
 - data family Strict t
 - strict :: Strictly t => t -> Strict t
 - unstrict :: Strictly t => Strict t -> t
 - class Strictly t where
- matchStrict :: Strict t -> t
 - constructStrict :: t -> Strict t
 
 - type family AlreadyStrict t :: Constraint
 - type family CannotBeStrict t :: Constraint
 - type family NestedStrict t :: Constraint
 - type family NotYetImplemented t :: Constraint
 
Introduction
Background
To avoid space leaks it is important to ensure that strictness annotations are inserted appropriately. For example, instead of writing
pairFoldBad :: (Integer, Integer) pairFoldBad = foldl' f (0, 0) [1..million] where f (count, theSum) x = (count + 1, theSum + x)
we could write
pairFoldBangs :: (Integer, Integer) pairFoldBangs = foldl' f (0, 0) [1..million] where f (!count, !theSum) x = (count + 1, theSum + x)
The downside of avoiding the space leak by inserting those bang patterns is that we have to remember to do so. Nothing in the types guides us to insert them. One way of addressing that problem is to define a type of "strict pairs" and use it instead of Haskell's built-in (lazy) pair.
data StrictPair a b = StrictPair !a !b pairFoldStrictPair :: StrictPair Integer Integer pairFoldStrictPair = foldl' f (StrictPair 0 0) [1..million] where f (StrictPair count theSum) x = StrictPair (count + 1) (theSum + x)
The strictness annotations on the fields of the StrictPair
 constructor cause the compiler to evaluate the fields before the
 pair is constructed.  The syntax above desugars to the form
 below:
pairFoldStrictPair_Desugared :: StrictPair Integer Integer
pairFoldStrictPair_Desugared = foldl' f (StrictPair 0 0) [1..million]
 where f (StrictPair count theSum) x = let !count'  = count + 1
                                           !theSum' = theSum + x
                                       in StrictPair count' theSum'
(pairFoldStrictPair_Desugared forces the fields at construction
 time and pairFoldBangs forces the fields when the pair is
 pattern matched but the consequences are the same: the space leak
 is avoided.)
Using StrictPair is helpful because we can't forget to evaluate
 the components.  It happens automatically.
If we take the "define strict data types" approach to solving space leaks then we need a strict version of every basic data type. For example, to fix the space leak in the following:
maybeFoldBad :: (Integer, Maybe Integer)
maybeFoldBad = foldl' f (0, Nothing) [1..million]
 where f (i, Nothing) x = (i + 1, Just x)
       f (i, Just j)  x = (i + 2, Just (j + x))
we need to define StrictMaybe and use it as below:
data StrictMaybe a = StrictNothing | StrictJust !a
maybeFoldStrictMaybe :: StrictPair Integer (StrictMaybe Integer)
maybeFoldStrictMaybe = foldl' f (StrictPair 0 StrictNothing) [1..million]
 where f (StrictPair i StrictNothing)  x = StrictPair (i + 1) (StrictJust x)
       f (StrictPair i (StrictJust j)) x = StrictPair (i + 2) (StrictJust (j + x))
The "define strict data types" approach requires a whole "parallel universe" of strict versions of basic types and is likely to become very tedious very quickly. (strict is one library providing such functionality.)
strict-wrapper
strict-wrapper provides a convenient way of using strict
 versions of basic data types without requiring a strict "parallel
 universe".  It provides a data family Strict that maps basic
 types to their strict versions
data instanceStrict(a, b) = StrictPair !a !b data instanceStrict(Maybe a) = StrictNothing | StrictJust !a ...
and a bidirectional pattern synonym, also called Strict, for
 mapping between the lazy and strict versions.  By using
 strict-wrapper the example above, maybeFoldStrictMaybe, can
 be written as
maybeFoldStrict :: Strict (Integer, Strict (Maybe Integer))
maybeFoldStrict = foldl' f (strict (0, Strict Nothing)) [1..million]
 where f (Strict (i, Strict Nothing))  x = Strict (i + 1, Strict (Just x))
       f (Strict (i, Strict (Just j))) x = Strict (i + 2, Strict (Just (j + x)))
When using strict-wrapper there is no need to have a parallel
 universe of strict types with new names that we must remember
 (StrictPair, StrictMaybe, StrictJust, StrictNothing,
 ...).  All that we need to do is to insert the Strict
 constructor or pattern in the places that we are guided to do so
 by the type checker.
Nested strict data
It is common in the Haskell world to see strict data field definitions like
data MyData = MyData { field1 :: !(Maybe Bool)
                     , field2 :: !(Either (Int, Double) Float)
                     }
Those strict fields probably don't do what the author hoped!
 They are almost entirely pointless.  The bang annotations on the
 Maybe ensure only that is is evaluated to a Nothing or
 Just.  The Bool is left unevaluated.  Similarly the Either
 is evaluated only as far as a Left or Right.  The pair and
 Float inside are left unevaluated.  strict-wrapper can help
 here.  Wrap both the Maybe and the pair in Strict and the
 type becomes fully strict!
data MyDataStrict = MyDataStrict { field1 :: !(Strict (Maybe Bool))
                                 , field2 :: !(Strict (Either (Strict (Int, Double)) Float))
                                 }
The API
To use strict-wrapper all that you need is the data family
 Strict and the bidirectional pattern synonym Strict.  For
 example, instead of using StrictPair a b as defined above, use
 Strict (a, b).  To create a Strict (a, b) wrap an (a, b) in
 the Strict constructor; to extract an (a, b), pattern match
 with Strict.
Efficiency considerations
Using strict-wrapper should be zero-cost relative to inserting
 seq or bang patterns manually.  In some cases matching the
 baseline cost will require using the functions strict and
 unstrict.  They provide the same functionality as the Strict
 pattern/constructor synonym but can be more efficient in
 particular circumstances. We suggest just using Strict until
 and unless you find a performance problem.
Further reading
You can read the blog post by Tom Ellis where the design of this library was first proposed.
Strict constructor and pattern
The Strict constructor and pattern are the easiest way to get
 started with strict-wrapper.
pattern Strict :: Strictly t => t -> Strict t Source #
Use the Strict pattern if you want to subsequently match on the
  t it contains (otherwise it is more efficient to use strict).
printIt :: Strict (Maybe Int) -> IO () printIt (Strict (Just i)) = print i printIt (Strict Nothing) = putStrLn "Nothing there"
Make a Strict t using the Strict constructor if you are
 constructing it from its individual fields (otherwise it is more
 efficient to use unstrict).
makeStrict :: Int -> Strict (Int, String) makeStrict i = Strict (i + 1, show i)
Types that have a strict version
Isomorphic to the type t, except that when it is evaulated its
 immediate children are evaluated too.
Instances
| NestedStrict t => Strictly (Strict t) Source # | |
| data Strict (Maybe t) Source # | |
Defined in Data.Strict.Wrapper  | |
| data Strict (Either t1 t2) Source # | |
Defined in Data.Strict.Wrapper  | |
| data Strict (t1, t2) Source # | |
Defined in Data.Strict.Wrapper  | |
| data Strict (t1, t2, t3) Source # | |
Defined in Data.Strict.Wrapper  | |
| data Strict (t1, t2, t3, t4) Source # | |
Defined in Data.Strict.Wrapper  | |
Accessor functions
The accessor functions can be more efficient than the Strict
 constructor and pattern in some circumstances but we don't
 recommend that you use them unless you are experiencing
 performance problems.
unstrict :: Strictly t => Strict t -> t Source #
Access the contents of a Strict t, but not its fields, using
 unstrict (if you want access to the fields then it is more
 efficient to use the Strict pattern).
strictMaybe :: r -> (a -> r) -> Strict (Maybe a) -> r strictMaybe r f sm = maybe r f (unstrict sm)
Class
class Strictly t where Source #
A type t can be given a Strictly instance when it has a very
 cheap conversion to and from a strict type, Strict t.
Minimal complete definition
Methods
matchStrict :: Strict t -> t Source #
Used to implement the Strict pattern synonym.  You should
 never need to use matchStrict unless you are defining your own
 instance of Strictly.
constructStrict :: t -> Strict t Source #
Used to implement the Strict constructor.  You should never
 need to use constructStrict unless you are defining your own
 instance of Strictly.
Instances
Error messages
These diagnostic error messages can appear when you try to use
 Strict on a type that doesn't support it.
type family AlreadyStrict t :: Constraint Source #
Some data types, such as Int and Double, are already as
 strict as they can be.  There is no need to wrap them in Strict!
Instances
| type AlreadyStrict t Source # | |
type family CannotBeStrict t :: Constraint Source #
Some data types, such as [a], can't be made strict in a
 zero-cost way.
Instances
| type CannotBeStrict t Source # | |
Defined in Data.Strict.Wrapper  | |
type family NestedStrict t :: Constraint Source #
Instances
| type NestedStrict t Source # | |
type family NotYetImplemented t :: Constraint Source #
Some Strictly instances are not yet implemented.  Please file
 an issue if you need them.
Instances
| type NotYetImplemented t Source # | |
Defined in Data.Strict.Wrapper type NotYetImplemented t = TypeError (('Text "Strict is not yet implemented for " :<>: 'ShowType t) :$$: 'Text "Please file an issue if you need it") :: Constraint  | |