Shpadoinkle-0.3.1.0: A programming model for declarative, high performance user interface.
Safe HaskellNone
LanguageHaskell2010

Shpadoinkle.Continuation

Description

Shpadoinkle Continuation is the abstract structure of Shpadoinkle's event handling system. It allows for asynchronous effects in event handlers by providing a model for atomic updates of application state.

Synopsis

The Continuation Type

data Continuation m a Source #

A Continuation builds up an atomic state update incrementally in a series of stages. For each stage we perform a monadic IO computation and we may get a pure state updating function. When all of the stages have been executed we are left with a composition of the resulting pure state updating functions, and this composition is applied atomically to the state.

Additionally, a Continuation stage may feature a Rollback action which cancels all state updates generated so far but allows for further state updates to be generated based on further monadic IO computation.

The functions generating each stage of the Continuation are called with states which reflect the current state of the app, with all the pure state updating functions generated so far having been applied to it, so that each stage "sees" both the current state (even if it changed since the start of computing the Continuation), and the updates made so far, although those updates are not committed to the real state until the Continuation finishes and they are all done atomically together.

Constructors

Continuation (a -> a) (a -> m (Continuation m a)) 
Rollback (Continuation m a) 
Merge (Continuation m a) 
Pure (a -> a) 

Instances

Instances details
Continuous Continuation Source # 
Instance details

Defined in Shpadoinkle.Continuation

Methods

mapC :: forall (m :: Type -> Type) a b. (Continuation m a -> Continuation m b) -> Continuation m a -> Continuation m b Source #

Applicative m => Functor EndoIso EndoIso (Continuation m :: Type -> Type) Source #

Continuation m is a Functor in the EndoIso category (where the objects are types and the morphisms are EndoIsos).

Instance details

Defined in Shpadoinkle.Continuation

Methods

map :: forall (a :: α) (b :: α). EndoIso a b -> EndoIso (Continuation m a) (Continuation m b) #

Applicative m => Semigroup (Continuation m a) Source #

You can combine multiple Continuations homogeneously using the Monoid typeclass instance. The resulting Continuation will execute all the subcontinuations in parallel, allowing them to see each other's state updates and roll back each other's updates, applying all of the unmerged updates generated by all the subcontinuations atomically once all of them are done. A merge in any one of the branches will cause all of the changes that branch can see to be merged.

Instance details

Defined in Shpadoinkle.Continuation

Methods

(<>) :: Continuation m a -> Continuation m a -> Continuation m a #

sconcat :: NonEmpty (Continuation m a) -> Continuation m a #

stimes :: Integral b => b -> Continuation m a -> Continuation m a #

Applicative m => Monoid (Continuation m a) Source #

Since combining Continuations homogeneously is an associative operation, and this operation has a unit element (done), Continuations are a Monoid.

Instance details

Defined in Shpadoinkle.Continuation

runContinuation :: Monad m => Continuation m a -> a -> m (a -> a) Source #

runContinuation takes a Continuation and a state value and runs the whole Continuation as if the real state was frozen at the value given to runContinuation. It performs all the IO actions in the stages of the Continuation and returns a pure state updating function which is the composition of all the pure state updating functions generated by the non-rolled-back stages of the Continuation. If you are trying to update a Continuous territory, then you should probably be using writeUpdate instead of runContinuation, because writeUpdate will allow each stage of the Continuation to see any extant updates made to the territory after the Continuation started running.

done :: Continuation m a Source #

A Continuation which doesn't touch the state and doesn't have any side effects

pur :: (a -> a) -> Continuation m a Source #

A pure state updating function can be turned into a Continuation. This function is here so that users of the Continuation API can do basic things without needing to depend on the internal structure of the type.

impur :: Applicative m => m (a -> a) -> Continuation m a Source #

A monadic computation of a pure state updating function can be turned into a Continuation.

kleisli :: (a -> m (Continuation m a)) -> Continuation m a Source #

This turns a Kleisli arrow for computing a Continuation into the Continuation which reads the state, runs the monadic computation specified by the arrow on that state, and runs the resulting Continuation.

causes :: Applicative m => m () -> Continuation m a Source #

A monadic computation can be turned into a Continuation which does not touch the state.

merge :: Continuation m a -> Continuation m a Source #

A continuation can be forced to write its changes midflight.

contIso :: Functor m => (a -> b) -> (b -> a) -> Continuation m a -> Continuation m b Source #

Transform the type of a Continuation using an isomorphism.

before :: Applicative m => Continuation m a -> Continuation m a -> Continuation m a Source #

Sequences two continuations one after the other.

The Class

class Continuous f where Source #

f is a Functor to Hask from the category where the objects are Continuation types and the morphisms are functions.

Methods

mapC :: (Continuation m a -> Continuation m b) -> f m a -> f m b Source #

Instances

Instances details
Continuous Continuation Source # 
Instance details

Defined in Shpadoinkle.Continuation

Methods

mapC :: forall (m :: Type -> Type) a b. (Continuation m a -> Continuation m b) -> Continuation m a -> Continuation m b Source #

Continuous Props Source #

Given a lens, you can change the type of a Props by using the lens to convert the types of the Continuations inside.

Instance details

Defined in Shpadoinkle.Core

Methods

mapC :: forall (m :: Type -> Type) a b. (Continuation m a -> Continuation m b) -> Props m a -> Props m b Source #

Continuous Prop Source #

Given a lens, you can change the type of a Prop by using the lens to convert the types of the Continuations which it contains if it is a listener.

Instance details

Defined in Shpadoinkle.Core

Methods

mapC :: forall (m :: Type -> Type) a b. (Continuation m a -> Continuation m b) -> Prop m a -> Prop m b Source #

Continuous Html Source #

Given a lens, you can change the type of an Html by using the lens to convert the types of the Continuations inside it.

Instance details

Defined in Shpadoinkle.Core

Methods

mapC :: forall (m :: Type -> Type) a b. (Continuation m a -> Continuation m b) -> Html m a -> Html m b Source #

Hoist

hoist :: Functor m => (forall b. m b -> n b) -> Continuation m a -> Continuation n a Source #

Given a natural transformation, change a Continuation's underlying functor.

Forgetting

voidC' :: Monad m => Continuation m () -> Continuation m a Source #

Change a void continuation into any other type of Continuation.

voidC :: Monad m => Continuous f => f m () -> f m a Source #

Change the type of the f-embedded void Continuations into any other type of Continuation.

forgetC :: Continuous f => f m a -> f m b Source #

Forget about the Continuations.

Lifts

liftC' :: Functor m => (a -> b -> b) -> (b -> a) -> Continuation m a -> Continuation m b Source #

Apply a lens inside a Continuation to change the Continuation's type.

liftCMay' :: Applicative m => (a -> b -> b) -> (b -> Maybe a) -> Continuation m a -> Continuation m b Source #

Apply a traversal inside a Continuation to change the Continuation's type.

liftC :: Functor m => Continuous f => (a -> b -> b) -> (b -> a) -> f m a -> f m b Source #

Given a lens, change the value type of f by applying the lens in the Continuations inside f.

liftCMay :: Applicative m => Continuous f => (a -> b -> b) -> (b -> Maybe a) -> f m a -> f m b Source #

Given a traversal, change the value of f by apply the traversal in the Continuations inside f.

Utilities

Product

leftC :: Functor m => Continuous f => f m a -> f m (a, b) Source #

Change the type of f by applying the Continuations inside f to the left coordinate of a tuple.

rightC' :: Functor m => Continuation m b -> Continuation m (a, b) Source #

Change the type of a Continuation by applying it to the right coordinate of a tuple.

rightC :: Functor m => Continuous f => f m b -> f m (a, b) Source #

Change the value type of f by applying the Continuations inside f to the right coordinate of a tuple.

Coproduct

eitherC' :: Applicative m => Continuation m a -> Continuation m b -> Continuation m (Either a b) Source #

Combine Continuations heterogeneously into coproduct Continuations. The first value the Continuation sees determines which of the two input Continuation branches it follows. If the coproduct Continuation sees the state change to a different Either-branch, then it cancels itself. If the state is in a different Either-branch when the Continuation completes than it was when the Continuation started, then the coproduct Continuation will have no effect on the state.

eitherC :: Applicative m => Continuous f => (a -> f m a) -> (b -> f m b) -> Either a b -> f m (Either a b) Source #

Create a structure containing coproduct Continuations using two case alternatives which generate structures containing Continuations of the types inside the coproduct. The Continuations in the resulting structure will only have effect on the state while it is in the branch of the coproduct selected by the input value used to create the structure.

Maybe

maybeC' :: Applicative m => Continuation m a -> Continuation m (Maybe a) Source #

Transform a Continuation to work on Maybes. If it encounters Nothing, then it cancels itself.

maybeC :: Applicative m => Continuous f => f m a -> f m (Maybe a) Source #

Change the value type of f by transforming the Continuations inside f to work on Maybes using maybeC'.

comaybe :: (Maybe a -> Maybe a) -> a -> a Source #

Turn a Maybe a updating function into an a updating function which acts as the identity function when the input function outputs Nothing.

comaybeC' :: Functor m => Continuation m (Maybe a) -> Continuation m a Source #

Change the type of a Maybe-valued Continuation into the Maybe-wrapped type. The resulting Continuation acts like the input Continuation except that when the input Continuation would replace the current value with Nothing, instead the current value is retained.

comaybeC :: Functor m => Continuous f => f m (Maybe a) -> f m a Source #

Transform the Continuations inside f using comaybeC'.

Updates

writeUpdate :: MonadUnliftIO m => NFData a => TVar a -> Continuation m a -> m () Source #

Run a Continuation on a state variable. This may update the state. This is a synchronous, non-blocking operation for pure updates, and an asynchronous, non-blocking operation for impure updates.

shouldUpdate :: forall a b m. MonadJSM m => MonadUnliftIO m => Eq a => (b -> a -> m b) -> b -> TVar a -> m () Source #

Execute a fold by watching a state variable and executing the next step of the fold each time it changes.

constUpdate :: a -> Continuation m a Source #

Create an update to a constant value.

Monad Transformer

newtype ContinuationT model m a Source #

A monad transformer for building up a Continuation in a series of steps in a monadic computation

Constructors

ContinuationT 

Fields

Instances

Instances details
MonadTrans (ContinuationT model) Source # 
Instance details

Defined in Shpadoinkle.Continuation

Methods

lift :: Monad m => m a -> ContinuationT model m a #

Monad m => Monad (ContinuationT model m) Source # 
Instance details

Defined in Shpadoinkle.Continuation

Methods

(>>=) :: ContinuationT model m a -> (a -> ContinuationT model m b) -> ContinuationT model m b #

(>>) :: ContinuationT model m a -> ContinuationT model m b -> ContinuationT model m b #

return :: a -> ContinuationT model m a #

Functor m => Functor (ContinuationT model m) Source # 
Instance details

Defined in Shpadoinkle.Continuation

Methods

fmap :: (a -> b) -> ContinuationT model m a -> ContinuationT model m b #

(<$) :: a -> ContinuationT model m b -> ContinuationT model m a #

Applicative m => Applicative (ContinuationT model m) Source # 
Instance details

Defined in Shpadoinkle.Continuation

Methods

pure :: a -> ContinuationT model m a #

(<*>) :: ContinuationT model m (a -> b) -> ContinuationT model m a -> ContinuationT model m b #

liftA2 :: (a -> b -> c) -> ContinuationT model m a -> ContinuationT model m b -> ContinuationT model m c #

(*>) :: ContinuationT model m a -> ContinuationT model m b -> ContinuationT model m b #

(<*) :: ContinuationT model m a -> ContinuationT model m b -> ContinuationT model m a #

voidRunContinuationT :: Functor m => ContinuationT model m a -> Continuation m model Source #

This turns a monadic computation to build up a Continuation into the Continuation which it represents. The actions inside the monadic computation will be run when the Continuation is run. The return value of the monadic computation will be discarded.

kleisliT :: Applicative m => (model -> ContinuationT model m a) -> Continuation m model Source #

This turns a function for building a Continuation in a monadic computation which is parameterized by the current state of the model into a Continuation which reads the current state of the model, runs the resulting monadic computation, and runs the Continuation resulting from that computation.

commit :: Applicative m => Continuation m model -> ContinuationT model m () Source #

This adds the given Continuation to the Continuation being built up in the monadic context where this function is invoked.

Re-exports

class NFData a where #

A class of types that can be fully evaluated.

Since: deepseq-1.1.0.0

Minimal complete definition

Nothing

Methods

rnf :: a -> () #

rnf should reduce its argument to normal form (that is, fully evaluate all sub-components), and then return ().

Generic NFData deriving

Starting with GHC 7.2, you can automatically derive instances for types possessing a Generic instance.

Note: Generic1 can be auto-derived starting with GHC 7.4

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics (Generic, Generic1)
import Control.DeepSeq

data Foo a = Foo a String
             deriving (Eq, Generic, Generic1)

instance NFData a => NFData (Foo a)
instance NFData1 Foo

data Colour = Red | Green | Blue
              deriving Generic

instance NFData Colour

Starting with GHC 7.10, the example above can be written more concisely by enabling the new DeriveAnyClass extension:

{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}

import GHC.Generics (Generic)
import Control.DeepSeq

data Foo a = Foo a String
             deriving (Eq, Generic, Generic1, NFData, NFData1)

data Colour = Red | Green | Blue
              deriving (Generic, NFData)

Compatibility with previous deepseq versions

Prior to version 1.4.0.0, the default implementation of the rnf method was defined as

rnf a = seq a ()

However, starting with deepseq-1.4.0.0, the default implementation is based on DefaultSignatures allowing for more accurate auto-derived NFData instances. If you need the previously used exact default rnf method implementation semantics, use

instance NFData Colour where rnf x = seq x ()

or alternatively

instance NFData Colour where rnf = rwhnf

or

{-# LANGUAGE BangPatterns #-}
instance NFData Colour where rnf !_ = ()

Instances

Instances details
NFData Bool 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Bool -> () #

NFData Char 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Char -> () #

NFData Double 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Double -> () #

NFData Float 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Float -> () #

NFData Int 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int -> () #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

NFData Integer 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Integer -> () #

NFData Natural

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Natural -> () #

NFData Ordering 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ordering -> () #

NFData Word 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word -> () #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

NFData Word64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word64 -> () #

NFData CallStack

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CallStack -> () #

NFData () 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: () -> () #

NFData TyCon

NOTE: Prior to deepseq-1.4.4.0 this instance was only defined for base-4.8.0.0 and later.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: TyCon -> () #

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

NFData Scientific 
Instance details

Defined in Data.Scientific

Methods

rnf :: Scientific -> () #

NFData JSONPathElement 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: JSONPathElement -> () #

NFData Value 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Value -> () #

NFData ThreadId

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ThreadId -> () #

NFData Void

Defined as rnf = absurd.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Void -> () #

NFData Unique

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Unique -> () #

NFData Version

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Version -> () #

NFData ExitCode

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ExitCode -> () #

NFData MaskingState

Since: deepseq-1.4.4.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: MaskingState -> () #

NFData TypeRep

NOTE: Prior to deepseq-1.4.4.0 this instance was only defined for base-4.8.0.0 and later.

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: TypeRep -> () #

NFData All

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: All -> () #

NFData Any

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Any -> () #

NFData CChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CChar -> () #

NFData CSChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSChar -> () #

NFData CUChar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUChar -> () #

NFData CShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CShort -> () #

NFData CUShort

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUShort -> () #

NFData CInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CInt -> () #

NFData CUInt

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUInt -> () #

NFData CLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLong -> () #

NFData CULong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULong -> () #

NFData CLLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CLLong -> () #

NFData CULLong

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CULLong -> () #

NFData CBool

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CBool -> () #

NFData CFloat

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFloat -> () #

NFData CDouble

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CDouble -> () #

NFData CPtrdiff

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CPtrdiff -> () #

NFData CSize

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSize -> () #

NFData CWchar

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CWchar -> () #

NFData CSigAtomic

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSigAtomic -> () #

NFData CClock

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CClock -> () #

NFData CTime

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CTime -> () #

NFData CUSeconds

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUSeconds -> () #

NFData CSUSeconds

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CSUSeconds -> () #

NFData CFile

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFile -> () #

NFData CFpos

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CFpos -> () #

NFData CJmpBuf

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CJmpBuf -> () #

NFData CIntPtr

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CIntPtr -> () #

NFData CUIntPtr

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUIntPtr -> () #

NFData CIntMax

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CIntMax -> () #

NFData CUIntMax

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CUIntMax -> () #

NFData Fingerprint

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fingerprint -> () #

NFData SrcLoc

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: SrcLoc -> () #

NFData JSValueForSend 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: JSValueForSend -> () #

NFData JSObjectForSend 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: JSObjectForSend -> () #

NFData JSStringForSend 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: JSStringForSend -> () #

NFData AsyncCommand 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: AsyncCommand -> () #

NFData Command 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: Command -> () #

NFData Batch 
Instance details

Defined in Language.Javascript.JSaddle.Types

Methods

rnf :: Batch -> () #

NFData JSVal 
Instance details

Defined in GHCJS.Prim.Internal

Methods

rnf :: JSVal -> () #

NFData Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

rnf :: Doc -> () #

NFData TextDetails 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnf :: TextDetails -> () #

NFData ByteArray 
Instance details

Defined in Data.Primitive.ByteArray

Methods

rnf :: ByteArray -> () #

NFData StdGen 
Instance details

Defined in System.Random.Internal

Methods

rnf :: StdGen -> () #

NFData ZonedTime 
Instance details

Defined in Data.Time.LocalTime.Internal.ZonedTime

Methods

rnf :: ZonedTime -> () #

NFData LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnf :: LocalTime -> () #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

NFData a => NFData [a] 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: [a] -> () #

NFData a => NFData (Maybe a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Maybe a -> () #

NFData a => NFData (Ratio a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ratio a -> () #

NFData (Ptr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ptr a -> () #

NFData (FunPtr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: FunPtr a -> () #

NFData a => NFData (IResult a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: IResult a -> () #

NFData a => NFData (Result a) 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Result a -> () #

NFData a => NFData (Complex a) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Complex a -> () #

NFData a => NFData (Min a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Min a -> () #

NFData a => NFData (Max a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Max a -> () #

NFData a => NFData (First a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Last a -> () #

NFData m => NFData (WrappedMonoid m)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: WrappedMonoid m -> () #

NFData a => NFData (Option a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Option a -> () #

NFData (StableName a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: StableName a -> () #

NFData a => NFData (ZipList a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: ZipList a -> () #

NFData a => NFData (Identity a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Identity a -> () #

NFData (IORef a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: IORef a -> () #

NFData a => NFData (First a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: First a -> () #

NFData a => NFData (Last a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Last a -> () #

NFData a => NFData (Dual a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Dual a -> () #

NFData a => NFData (Sum a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Sum a -> () #

NFData a => NFData (Product a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Product a -> () #

NFData a => NFData (Down a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Down a -> () #

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: MVar a -> () #

NFData a => NFData (NonEmpty a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: NonEmpty a -> () #

NFData1 f => NFData (Fix f) 
Instance details

Defined in Data.Fix

Methods

rnf :: Fix f -> () #

NFData a => NFData (DNonEmpty a) 
Instance details

Defined in Data.DList.DNonEmpty.Internal

Methods

rnf :: DNonEmpty a -> () #

NFData a => NFData (DList a) 
Instance details

Defined in Data.DList.Internal

Methods

rnf :: DList a -> () #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Primitive

Methods

rnf :: Vector a -> () #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Storable

Methods

rnf :: Vector a -> () #

NFData (Vector a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: Vector a -> () #

NFData a => NFData (HashSet a) 
Instance details

Defined in Data.HashSet.Internal

Methods

rnf :: HashSet a -> () #

NFData a => NFData (Vector a) 
Instance details

Defined in Data.Vector

Methods

rnf :: Vector a -> () #

NFData a => NFData (Doc a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnf :: Doc a -> () #

NFData a => NFData (AnnotDetails a) 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

rnf :: AnnotDetails a -> () #

NFData (PrimArray a) 
Instance details

Defined in Data.Primitive.PrimArray

Methods

rnf :: PrimArray a -> () #

NFData (MutableByteArray s) 
Instance details

Defined in Data.Primitive.ByteArray

Methods

rnf :: MutableByteArray s -> () #

NFData a => NFData (SmallArray a) 
Instance details

Defined in Data.Primitive.SmallArray

Methods

rnf :: SmallArray a -> () #

NFData a => NFData (Array a) 
Instance details

Defined in Data.Primitive.Array

Methods

rnf :: Array a -> () #

NFData g => NFData (AtomicGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnf :: AtomicGen g -> () #

NFData g => NFData (IOGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnf :: IOGen g -> () #

NFData g => NFData (STGen g) 
Instance details

Defined in System.Random.Stateful

Methods

rnf :: STGen g -> () #

NFData g => NFData (StateGen g) 
Instance details

Defined in System.Random.Internal

Methods

rnf :: StateGen g -> () #

NFData a => NFData (Maybe a) 
Instance details

Defined in Data.Strict.Maybe

Methods

rnf :: Maybe a -> () #

NFData (a -> b)

This instance is for convenience and consistency with seq. This assumes that WHNF is equivalent to NF for functions.

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a -> b) -> () #

(NFData a, NFData b) => NFData (Either a b) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (a, b) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a, b) -> () #

(NFData k, NFData v) => NFData (HashMap k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

rnf :: HashMap k v -> () #

(NFData k, NFData a) => NFData (Map k a) 
Instance details

Defined in Data.Map.Internal

Methods

rnf :: Map k a -> () #

(NFData a, NFData b) => NFData (Array a b) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Array a b -> () #

(NFData i, NFData r) => NFData (IResult i r) 
Instance details

Defined in Data.Attoparsec.Internal.Types

Methods

rnf :: IResult i r -> () #

NFData (Fixed a)

Since: deepseq-1.3.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Fixed a -> () #

(NFData a, NFData b) => NFData (Arg a b)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Arg a b -> () #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

NFData (STRef s a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: STRef s a -> () #

NFData (MutablePrimArray s a) 
Instance details

Defined in Data.Primitive.PrimArray

Methods

rnf :: MutablePrimArray s a -> () #

(NFData a, NFData b) => NFData (Pair a b) 
Instance details

Defined in Data.Strict.Tuple

Methods

rnf :: Pair a b -> () #

(NFData a, NFData b) => NFData (These a b) 
Instance details

Defined in Data.Strict.These

Methods

rnf :: These a b -> () #

(NFData a, NFData b) => NFData (Either a b) 
Instance details

Defined in Data.Strict.Either

Methods

rnf :: Either a b -> () #

(NFData a, NFData b) => NFData (These a b)

Since: these-0.7.1

Instance details

Defined in Data.These

Methods

rnf :: These a b -> () #

(NFData k, NFData v) => NFData (Leaf k v) 
Instance details

Defined in Data.HashMap.Internal

Methods

rnf :: Leaf k v -> () #

NFData (MVector s a) 
Instance details

Defined in Data.Vector.Unboxed.Base

Methods

rnf :: MVector s a -> () #

(NFData a1, NFData a2, NFData a3) => NFData (a1, a2, a3) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3) -> () #

NFData a => NFData (Const a b)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Const a b -> () #

NFData (a :~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a :~: b) -> () #

NFData b => NFData (Tagged s b) 
Instance details

Defined in Data.Tagged

Methods

rnf :: Tagged s b -> () #

(NFData1 f, NFData1 g, NFData a) => NFData (These1 f g a)

This instance is available only with deepseq >= 1.4.3.0

Instance details

Defined in Data.Functor.These

Methods

rnf :: These1 f g a -> () #

(NFData a1, NFData a2, NFData a3, NFData a4) => NFData (a1, a2, a3, a4) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3, a4) -> () #

(NFData1 f, NFData1 g, NFData a) => NFData (Product f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Product f g a -> () #

(NFData1 f, NFData1 g, NFData a) => NFData (Sum f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Sum f g a -> () #

NFData (a :~~: b)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a :~~: b) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5) => NFData (a1, a2, a3, a4, a5) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3, a4, a5) -> () #

(NFData1 f, NFData1 g, NFData a) => NFData (Compose f g a)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Compose f g a -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6) => NFData (a1, a2, a3, a4, a5, a6) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3, a4, a5, a6) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7) => NFData (a1, a2, a3, a4, a5, a6, a7) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8) => NFData (a1, a2, a3, a4, a5, a6, a7, a8) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8) -> () #

(NFData a1, NFData a2, NFData a3, NFData a4, NFData a5, NFData a6, NFData a7, NFData a8, NFData a9) => NFData (a1, a2, a3, a4, a5, a6, a7, a8, a9) 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: (a1, a2, a3, a4, a5, a6, a7, a8, a9) -> () #

force :: NFData a => a -> a #

a variant of deepseq that is useful in some circumstances:

force x = x `deepseq` x

force x fully evaluates x, and then returns it. Note that force x only performs evaluation when the value of force x itself is demanded, so essentially it turns shallow evaluation into deep evaluation.

force can be conveniently used in combination with ViewPatterns:

{-# LANGUAGE BangPatterns, ViewPatterns #-}
import Control.DeepSeq

someFun :: ComplexData -> SomeResult
someFun (force -> !arg) = {- 'arg' will be fully evaluated -}

Another useful application is to combine force with evaluate in order to force deep evaluation relative to other IO operations:

import Control.Exception (evaluate)
import Control.DeepSeq

main = do
  result <- evaluate $ force $ pureComputation
  {- 'result' will be fully evaluated at this point -}
  return ()

Finally, here's an exception safe variant of the readFile' example:

readFile' :: FilePath -> IO String
readFile' fn = bracket (openFile fn ReadMode) hClose $ \h ->
                       evaluate . force =<< hGetContents h

Since: deepseq-1.2.0.0