nothunks-0.1.3: Examine values for unexpected thunks
Safe HaskellNone
LanguageHaskell2010

NoThunks.Class

Synopsis

Check a value for unexpected thunks

class NoThunks a where Source #

Check a value for unexpected thunks

Minimal complete definition

Nothing

Methods

noThunks :: Context -> a -> IO (Maybe ThunkInfo) Source #

Check if the argument does not contain any unexpected thunks

For most datatypes, we should have that

noThunks ctxt x == Nothing

if and only if

checkContainsThunks x

For some datatypes however, some thunks are expected. For example, the internal fingertree Sequence might contain thunks (this is important for the asymptotic complexity of this data structure). However, we should still check that the values in the sequence don't contain any unexpected thunks.

This means that we need to traverse the sequence, which might force some of the thunks in the tree. In general, it is acceptable for noThunks to force such "expected thunks", as long as it always reports the unexpected thunks.

The default implementation of noThunks checks that the argument is in WHNF, and if so, adds the type into the context (using showTypeOf), and calls wNoThunks. See ThunkInfo for a detailed discussion of the type context.

See also discussion of caveats listed for checkContainsThunks.

wNoThunks :: Context -> a -> IO (Maybe ThunkInfo) Source #

Check that the argument is in normal form, assuming it is in WHNF.

The context will already have been extended with the type we're looking at, so all that's left is to look at the thunks inside the type. The default implementation uses GHC Generics to do this.

default wNoThunks :: (Generic a, GWNoThunks '[] (Rep a)) => Context -> a -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy a -> String Source #

Show type a (to add to the context)

We try hard to avoid Typeable constraints in this module: there are types with no Typeable instance but with a NoThunks instance (most important example are types such as ST s which rely on parametric polymorphism). By default we should therefore only show the "outer layer"; for example, if we have a type

Seq (ST s ())

then showTypeOf should just give Seq, leaving it up to the instance for ST to decide how to implement showTypeOf; this keeps things compositional. The default implementation does precisely this using the metadata that GHC Generics provides.

For convenience, however, some of the deriving via newtype wrappers we provide do depend on Typeable; see below.

default showTypeOf :: (Generic a, GShowTypeOf (Rep a)) => Proxy a -> String Source #

Instances

Instances details
NoThunks Bool Source # 
Instance details

Defined in NoThunks.Class

NoThunks Char Source # 
Instance details

Defined in NoThunks.Class

NoThunks Double Source # 
Instance details

Defined in NoThunks.Class

NoThunks Float Source # 
Instance details

Defined in NoThunks.Class

NoThunks Int Source # 
Instance details

Defined in NoThunks.Class

NoThunks Int8 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Int16 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Int32 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Int64 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Integer Source # 
Instance details

Defined in NoThunks.Class

NoThunks Natural Source # 
Instance details

Defined in NoThunks.Class

NoThunks Word Source # 
Instance details

Defined in NoThunks.Class

NoThunks Word8 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Word16 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Word32 Source # 
Instance details

Defined in NoThunks.Class

NoThunks Word64 Source # 
Instance details

Defined in NoThunks.Class

NoThunks CallStack Source #

Since CallStacks can't retain application data, we don't want to check them for thunks at all

Instance details

Defined in NoThunks.Class

NoThunks () Source # 
Instance details

Defined in NoThunks.Class

NoThunks Void Source # 
Instance details

Defined in NoThunks.Class

NoThunks ShortByteString Source #

Instance for short bytestrings

We have

data ShortByteString = SBS ByteArray#

Values of this type consist of a tag followed by an _unboxed_ byte array, which can't contain thunks. Therefore we only check WHNF.

Instance details

Defined in NoThunks.Class

NoThunks ByteString Source #

Instance for lazy bytestrings

Defined manually so that it piggy-backs on the one for strict bytestrings.

Instance details

Defined in NoThunks.Class

NoThunks ByteString Source #

Instance for string bytestrings

Strict bytestrings shouldn't contain any thunks, but could, due to https://gitlab.haskell.org/ghc/ghc/issues/17290. However, such thunks can't retain any data that they shouldn't, and so it's safe to ignore such thunks.

Instance details

Defined in NoThunks.Class

NoThunks Text Source # 
Instance details

Defined in NoThunks.Class

NoThunks Text Source # 
Instance details

Defined in NoThunks.Class

NoThunks ZonedTime Source # 
Instance details

Defined in NoThunks.Class

NoThunks TimeLocale Source # 
Instance details

Defined in NoThunks.Class

NoThunks LocalTime Source # 
Instance details

Defined in NoThunks.Class

NoThunks TimeOfDay Source # 
Instance details

Defined in NoThunks.Class

NoThunks TimeZone Source # 
Instance details

Defined in NoThunks.Class

NoThunks UniversalTime Source # 
Instance details

Defined in NoThunks.Class

NoThunks UTCTime Source # 
Instance details

Defined in NoThunks.Class

NoThunks NominalDiffTime Source # 
Instance details

Defined in NoThunks.Class

NoThunks DiffTime Source # 
Instance details

Defined in NoThunks.Class

NoThunks Day Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks [a] Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (Maybe a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (Ratio a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks (IO a) Source #

We do not check IO actions for captured thunks by default

See instance for (a -> b) for detailed discussion.

Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (TVar a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (IORef a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (MVar a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (NonEmpty a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (IntMap a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (Seq a) Source #

Instance for Seq checks elements only

The internal fingertree in Seq might have thunks, which is essential for its asymptotic complexity.

Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (Set a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks (Vector a) Source #

Unboxed vectors can't contain thunks

Implementation note: defined manually rather than using OnlyCheckWhnf due to ghc limitation in deriving via, making it impossible to use with it with data families.

Instance details

Defined in NoThunks.Class

NoThunks a => NoThunks (Vector a) Source # 
Instance details

Defined in NoThunks.Class

Typeable a => NoThunks (InspectHeap a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks (AllowThunk a) Source # 
Instance details

Defined in NoThunks.Class

Typeable a => NoThunks (OnlyCheckWhnf a) Source # 
Instance details

Defined in NoThunks.Class

NoThunks (a -> b) Source #

We do NOT check function closures for captured thunks by default

Since we have no type information about the values captured in a thunk, the only check we could possibly do is checkContainsThunks: we can't recursively call noThunks on those captured values, which is problematic if any of those captured values requires a custom instance (for example, data types that depend on laziness, such as Seq).

By default we therefore only check if the function is in WHNF, and don't check the captured values at all. If you want a stronger check, you can use InspectHeap (a -> b) instead.

Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a -> b) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a -> b) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a -> b) -> String Source #

(NoThunks a, NoThunks b) => NoThunks (Either a b) Source # 
Instance details

Defined in NoThunks.Class

(NoThunks a, NoThunks b) => NoThunks (a, b) Source # 
Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a, b) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a, b) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a, b) -> String Source #

(NoThunks k, NoThunks v) => NoThunks (Map k v) Source # 
Instance details

Defined in NoThunks.Class

KnownSymbol name => NoThunks (InspectHeapNamed name a) Source # 
Instance details

Defined in NoThunks.Class

(HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a)) => NoThunks (AllowThunksIn s a) Source # 
Instance details

Defined in NoThunks.Class

KnownSymbol name => NoThunks (OnlyCheckWhnfNamed name a) Source # 
Instance details

Defined in NoThunks.Class

(NoThunks a, NoThunks b, NoThunks c) => NoThunks (a, b, c) Source # 
Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a, b, c) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a, b, c) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a, b, c) -> String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d) => NoThunks (a, b, c, d) Source # 
Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a, b, c, d) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a, b, c, d) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a, b, c, d) -> String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e) => NoThunks (a, b, c, d, e) Source # 
Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a, b, c, d, e) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a, b, c, d, e) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a, b, c, d, e) -> String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e, NoThunks f) => NoThunks (a, b, c, d, e, f) Source # 
Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a, b, c, d, e, f) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a, b, c, d, e, f) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a, b, c, d, e, f) -> String Source #

(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e, NoThunks f, NoThunks g) => NoThunks (a, b, c, d, e, f, g) Source # 
Instance details

Defined in NoThunks.Class

Methods

noThunks :: Context -> (a, b, c, d, e, f, g) -> IO (Maybe ThunkInfo) Source #

wNoThunks :: Context -> (a, b, c, d, e, f, g) -> IO (Maybe ThunkInfo) Source #

showTypeOf :: Proxy (a, b, c, d, e, f, g) -> String Source #

data ThunkInfo Source #

Information about unexpected thunks

TODO: The ghc-debug work by Matthew Pickering includes some work that allows to get source spans from closures. If we could take advantage of that, we could not only show the type of the unexpected thunk, but also where it got allocated.

Constructors

ThunkInfo 

Instances

Instances details
Show ThunkInfo Source # 
Instance details

Defined in NoThunks.Class

type Context = [String] Source #

Context where a thunk was found

This is intended to give a hint about which thunk was found. For example, a thunk might be reported with context

["Int", "(,)", "Map", "AppState"]

telling you that you have an AppState containing a Map containing a pair, all of which weren't thunks (were in WHNF), but that pair contained an Int which was a thunk.

unsafeNoThunks :: NoThunks a => a -> Maybe ThunkInfo Source #

Call noThunks in a pure context (relies on unsafePerformIO).

Helpers for defining instances

allNoThunks :: [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo) Source #

Short-circuit a list of checks

noThunksInValues :: NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo) Source #

Check that all elements in the list are thunk-free

Does not check the list itself. Useful for checking the elements of a container.

See also noThunksInKeysAndValues

noThunksInKeysAndValues :: (NoThunks k, NoThunks v) => Context -> [(k, v)] -> IO (Maybe ThunkInfo) Source #

Variant on noThunksInValues for keyed containers.

Neither the list nor the tuples are checked for thunks.

Deriving-via wrappers

newtype OnlyCheckWhnf a Source #

Newtype wrapper for use with deriving via to check for WHNF only

For some types we don't want to check for nested thunks, and we only want check if the argument is in WHNF, not in NF. A typical example are functions; see the instance of (a -> b) for detailed discussion. This should be used sparingly.

Example:

deriving via OnlyCheckWhnf T instance NoThunks T

Constructors

OnlyCheckWhnf a 

Instances

Instances details
Typeable a => NoThunks (OnlyCheckWhnf a) Source # 
Instance details

Defined in NoThunks.Class

newtype OnlyCheckWhnfNamed (name :: Symbol) a Source #

Variant on OnlyCheckWhnf that does not depend on Generic

Example:

deriving via OnlyCheckWhnfNamed "T" T instance NoThunks T

Constructors

OnlyCheckWhnfNamed a 

Instances

Instances details
KnownSymbol name => NoThunks (OnlyCheckWhnfNamed name a) Source # 
Instance details

Defined in NoThunks.Class

newtype InspectHeap a Source #

Newtype wrapper for use with deriving via to inspect the heap directly

This bypasses the class instances altogether, and inspects the GHC heap directly, checking that the value does not contain any thunks anywhere. Since we can do this without any type classes instances, this is useful for types that contain fields for which NoThunks instances are not available.

Since the primary use case for InspectHeap then is to give instances for NoThunks from third party libraries, we also don't want to rely on a Generic instance, which may likewise not be available. Instead, we will rely on Typeable, which is available for all types. However, as showTypeOf explains, requiring Typeable may not always be suitable; if it isn't, InspectHeapNamed can be used.

Example:

deriving via InspectHeap T instance NoThunks T

Constructors

InspectHeap a 

Instances

Instances details
Typeable a => NoThunks (InspectHeap a) Source # 
Instance details

Defined in NoThunks.Class

newtype InspectHeapNamed (name :: Symbol) a Source #

Variant on InspectHeap that does not depend on Typeable.

deriving via InspectHeapNamed "T" T instance NoUnexpecedThunks T

Constructors

InspectHeapNamed a 

Instances

Instances details
KnownSymbol name => NoThunks (InspectHeapNamed name a) Source # 
Instance details

Defined in NoThunks.Class

newtype AllowThunk a Source #

Newtype wrapper for values that should be allowed to be a thunk

This should be used VERY sparingly, and should ONLY be used on values (or, even rarer, types) which you are SURE cannot retain any data that they shouldn't. Bear in mind allowing a value of type T to be a thunk might cause a value of type S to be retained if T was computed from S.

Constructors

AllowThunk a 

Instances

Instances details
NoThunks (AllowThunk a) Source # 
Instance details

Defined in NoThunks.Class

newtype AllowThunksIn (fields :: [Symbol]) a Source #

Newtype wrapper for records where some of the fields are allowed to be thunks.

Example:

deriving via AllowThunksIn '["foo","bar"] T instance NoThunks T

This will create an instance that skips the thunk checks for the "foo" and "bar" fields.

Constructors

AllowThunksIn a 

Instances

Instances details
(HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a)) => NoThunks (AllowThunksIn s a) Source # 
Instance details

Defined in NoThunks.Class

Generic class

class GWNoThunks (a :: [Symbol]) f where Source #

Generic infrastructure for checking for unexpected thunks

The a argument records which record fields are allowed to contain thunks; see AllowThunksIn and GWRecordField, below.

Methods

gwNoThunks :: proxy a -> Context -> f x -> IO (Maybe ThunkInfo) Source #

Check that the argument does not contain any unexpected thunks

Precondition: the argument is in WHNF.

Instances

Instances details
GWNoThunks a (V1 :: Type -> Type) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> V1 x -> IO (Maybe ThunkInfo) Source #

GWNoThunks a (U1 :: Type -> Type) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> U1 x -> IO (Maybe ThunkInfo) Source #

GWRecordField f (Elem fieldName a) => GWNoThunks a (S1 ('MetaSel ('Just fieldName) su ss ds) f) Source #

If fieldName is allowed to contain thunks, skip it.

Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> S1 ('MetaSel ('Just fieldName) su ss ds) f x -> IO (Maybe ThunkInfo) Source #

NoThunks c => GWNoThunks a (K1 i c :: Type -> Type) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> K1 i c x -> IO (Maybe ThunkInfo) Source #

(GWNoThunks a f, GWNoThunks a g) => GWNoThunks a (f :+: g) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> (f :+: g) x -> IO (Maybe ThunkInfo) Source #

(GWNoThunks a f, GWNoThunks a g) => GWNoThunks a (f :*: g) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> (f :*: g) x -> IO (Maybe ThunkInfo) Source #

GWNoThunks a f => GWNoThunks a (S1 ('MetaSel ('Nothing :: Maybe Symbol) su ss ds) f) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> S1 ('MetaSel 'Nothing su ss ds) f x -> IO (Maybe ThunkInfo) Source #

GWNoThunks a f => GWNoThunks a (C1 c f) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> C1 c f x -> IO (Maybe ThunkInfo) Source #

GWNoThunks a f => GWNoThunks a (D1 c f) Source # 
Instance details

Defined in NoThunks.Class

Methods

gwNoThunks :: proxy a -> Context -> D1 c f x -> IO (Maybe ThunkInfo) Source #