data-forced-0.3.0.0: Specify that lifted values were forced to WHNF or NF.
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Forced

Synopsis

How to use this library

You should use the following imports

  import qualified Data.Forced as DF
  import Data.Forced hiding (pure, fmap, (*), return, (>>=), (>>))

Design the type of your long lived data structure

The main way this library helps you avoid leaks is by specifying the types of your long lived data structures. They should contain new demands on the type variables.

import Data.Map.Lazy -- it is fine, really.
import Data.Vector

-- On insertion of the lazy map, the keys and the values will evaluated.
type MyMap a = Map (ForcedWHNF Char) (ForcedNF (Maybe (Vector Int)))

-- On top, prompt removal of deleted elements.
type MyMap2 a = ForcedWHNF (Map (ForcedWHNF Char) (ForcedNF (Maybe (Vector Int))))

This way it will be a type error to store a thunk that is keeping references alive.

Construct values on the Demand monad

We use the Demand monad to construct values with the correct strictness. You either construct the values by hand, but it is better to use the -XQualifiedDo extension.

The main functions to keep in mind on this monad are: demandWHNF and demandNF.

Once you have the value specified, you need to extract it to the IO environment. Hopefully this will be close to main where your long lived data should be stored. We do this as is the obvious sequence point, so from the PoV of the rest of the program, the action is visible on the default lifted environment.

The ideal code piece looks like this:

{-# Language QualifiedDo #-}

import qualified Data.Forced as DF
import Data.Forced hiding (pure, fmap, (<*>), return, (>>=), (>>))
import Data.Map.Lazy qualified as ML

noThunksForWHNF :: IO ()
noThunksForWHNF = do
    -- map0 actually evaluated on here.
    let map0 :: Demand (ML.Map Char (ForcedWHNF Int))
        map0 = DF.do
          v <- demandWHNF (const (2 + (2 :: Int)) 'a')
          DF.pure $ ML.insert 'a' v ML.empty

    map1 <- extractDemand map0
    go (ML.lookup 'a' map1)

-- pattern matching for de-structuring, no construction allowed.
go :: ForcedWHNF Int -> IO ()
go (ForcedWHNF i) =  print i

Newtypes to be used to specify how evaluated a type should be

data ForcedWHNF a where Source #

Contains a value of type a that has been forced to Weak Head Normal Form. Constructor not exported (so no coerce).

Bundled Patterns

pattern ForcedWHNF :: forall a. a -> ForcedWHNF a

The only way to extract the underlying value.

Instances

Instances details
Show a => Show (ForcedWHNF a) Source # 
Instance details

Defined in Data.Forced

data ForcedNF a where Source #

Contains a value of type a that has been forced to Normal Form. Constructor not exported (so no coerce).

Bundled Patterns

pattern ForcedNF :: forall a. a -> ForcedNF a

The only way to extract the underlying value.

Instances

Instances details
Show a => Show (ForcedNF a) Source # 
Instance details

Defined in Data.Forced

Methods

showsPrec :: Int -> ForcedNF a -> ShowS #

show :: ForcedNF a -> String #

showList :: [ForcedNF a] -> ShowS #

Monadic environment to execute the needed demands.

data Demand (a :: LiftedType) :: UnliftedType Source #

A strict identity monad of UnliftedType kind. To be used via -XQualifiedDo.

demandWHNF :: forall a. a -> Demand (ForcedWHNF a) Source #

This is a CBV function. Evaluates the argument to WHNF before returning.

demandNF :: forall a. NFData a => a -> Demand (ForcedNF a) Source #

This is a CBV function. Evaluates the argument to NF before returning.

extractDemand :: Demand a -> IO a Source #

We don't ship the constructor of Demand. The only way to extract a Demand is to sequence to a know point on IO. From the PoV of the rest of the program, the tagged values with ForcedWHNF or ForcedNF will have been demanded.

Qualified Do support.

These are available to construct value by hand. But they clash with Functor, Applicative and Monad functions. We cannot provide instances to those classes as the Demand monad is UnliftedType kinded. But using -XQualifiedDo, GHC will pick up these names and use it on a DF.do notation that does the right thing.

fmap :: (a -> b) -> Demand a -> Demand b Source #

fmap analogue for Demands which are of the UnliftedType kind.

pure :: a -> Demand a Source #

Places no demand on the value. pure analogue for Demands which are of the UnliftedType kind.

(<*>) :: Demand (a -> b) -> Demand a -> Demand b Source #

<*> analogue for Demands which are of the UnliftedType kind.

return :: a -> Demand a Source #

return analogue for Demands which are of the UnliftedType kind. Same as pure.

(>>=) :: Demand a -> (a -> Demand b) -> Demand b Source #

>>= analogue for Demands which are of the UnliftedType kind.

(>>) :: Demand a -> Demand b -> Demand b Source #

>> analogue for Demands which are of the UnliftedType kind.