Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class NoThunks a where
- newtype ThunkInfo = ThunkInfo {}
- type Context = [String]
- type Info = String
- unsafeNoThunks :: NoThunks a => a -> Maybe ThunkInfo
- allNoThunks :: [IO (Maybe ThunkInfo)] -> IO (Maybe ThunkInfo)
- noThunksInValues :: NoThunks a => Context -> [a] -> IO (Maybe ThunkInfo)
- noThunksInKeysAndValues :: (NoThunks k, NoThunks v) => Context -> [(k, v)] -> IO (Maybe ThunkInfo)
- newtype OnlyCheckWhnf a = OnlyCheckWhnf a
- newtype OnlyCheckWhnfNamed (name :: Symbol) a = OnlyCheckWhnfNamed a
- newtype InspectHeap a = InspectHeap a
- newtype InspectHeapNamed (name :: Symbol) a = InspectHeapNamed a
- newtype AllowThunk a = AllowThunk a
- newtype AllowThunksIn (fields :: [Symbol]) a = AllowThunksIn a
- class GWNoThunks (a :: [Symbol]) f where
- gwNoThunks :: proxy a -> Context -> f x -> IO (Maybe ThunkInfo)
Check a value for unexpected thunks
class NoThunks a where Source #
Check a value for unexpected thunks
Nothing
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
or
whereFrom
if available), 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.
Instances
NoThunks All Source # | |
NoThunks Any Source # | |
NoThunks Void Source # | |
NoThunks ThreadId Source # | |
NoThunks Int16 Source # | |
NoThunks Int32 Source # | |
NoThunks Int64 Source # | |
NoThunks Int8 Source # | |
NoThunks CallStack Source # | Since CallStacks can't retain application data, we don't want to check them for thunks at all |
NoThunks Word16 Source # | |
NoThunks Word32 Source # | |
NoThunks Word64 Source # | |
NoThunks Word8 Source # | |
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. |
Defined in NoThunks.Class | |
NoThunks ByteString Source # | Instance for lazy bytestrings Defined manually so that it piggy-backs on the one for strict bytestrings. |
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. |
Defined in NoThunks.Class | |
NoThunks Text Source # | |
NoThunks Text Source # | |
NoThunks Day Source # | |
NoThunks DiffTime Source # | |
NoThunks NominalDiffTime Source # | |
Defined in NoThunks.Class | |
NoThunks UTCTime Source # | |
NoThunks UniversalTime Source # | |
Defined in NoThunks.Class | |
NoThunks TimeLocale Source # | |
Defined in NoThunks.Class | |
NoThunks LocalTime Source # | |
NoThunks TimeOfDay Source # | |
NoThunks TimeZone Source # | |
NoThunks ZonedTime Source # | |
NoThunks Integer Source # | |
NoThunks Natural Source # | |
NoThunks () Source # | |
NoThunks Bool Source # | |
NoThunks Char Source # | |
NoThunks Double Source # | |
NoThunks Float Source # | |
NoThunks Int Source # | |
NoThunks Word Source # | |
NoThunks a => NoThunks (Identity a) Source # | |
NoThunks a => NoThunks (First a) Source # | |
NoThunks a => NoThunks (Last a) Source # | |
NoThunks a => NoThunks (First a) Source # | |
NoThunks a => NoThunks (Last a) Source # | |
NoThunks a => NoThunks (Max a) Source # | |
NoThunks a => NoThunks (Min a) Source # | |
NoThunks a => NoThunks (WrappedMonoid a) Source # | |
Defined in NoThunks.Class | |
NoThunks a => NoThunks (Dual a) Source # | |
NoThunks a => NoThunks (Product a) Source # | |
NoThunks a => NoThunks (Sum a) Source # | |
NoThunks a => NoThunks (NonEmpty a) Source # | |
NoThunks a => NoThunks (TVar a) Source # | |
NoThunks a => NoThunks (IORef a) Source # | |
NoThunks a => NoThunks (MVar a) Source # | |
NoThunks a => NoThunks (Ratio a) Source # | |
NoThunks a => NoThunks (IntMap a) Source # | |
NoThunks a => NoThunks (Seq a) Source # | Instance for The internal fingertree in |
NoThunks a => NoThunks (Set a) Source # | |
NoThunks (IO a) Source # | We do not check IO actions for captured thunks by default See instance for |
NoThunks (AllowThunk a) Source # | |
Defined in NoThunks.Class | |
Typeable a => NoThunks (InspectHeap a) Source # | |
Defined in NoThunks.Class | |
Typeable a => NoThunks (OnlyCheckWhnf a) Source # | |
Defined in NoThunks.Class | |
NoThunks a => NoThunks (Vector a) Source # | |
NoThunks (Vector a) Source # | Unboxed vectors can't contain thunks Implementation note: defined manually rather than using |
NoThunks a => NoThunks (Maybe a) Source # | |
NoThunks a => NoThunks (a) Source # | |
NoThunks a => NoThunks [a] Source # | |
(NoThunks a, NoThunks b) => NoThunks (Either a b) Source # | |
(NoThunks a, NoThunks b) => NoThunks (Arg a b) Source # | |
(NoThunks k, NoThunks v) => NoThunks (Map k v) Source # | |
(HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a)) => NoThunks (AllowThunksIn s a) Source # | |
Defined in NoThunks.Class | |
KnownSymbol name => NoThunks (InspectHeapNamed name a) Source # | |
Defined in NoThunks.Class | |
KnownSymbol name => NoThunks (OnlyCheckWhnfNamed name a) Source # | |
Defined in NoThunks.Class | |
(NoThunks a, NoThunks b) => NoThunks (a, b) Source # | |
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 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 |
NoThunks (f a) => NoThunks (Ap f a) Source # | |
NoThunks (f a) => NoThunks (Alt f a) Source # | |
(NoThunks a, NoThunks b, NoThunks c) => NoThunks (a, b, c) Source # | |
(NoThunks a, NoThunks b, NoThunks c, NoThunks d) => NoThunks (a, b, c, d) Source # | |
(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e) => NoThunks (a, b, c, d, e) Source # | |
(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e, NoThunks f) => NoThunks (a, b, c, d, e, f) Source # | |
(NoThunks a, NoThunks b, NoThunks c, NoThunks d, NoThunks e, NoThunks f, NoThunks g) => NoThunks (a, b, c, d, e, f, g) Source # | |
Information about unexpected thunks
ThunkInfo contains either precise Info
about the thunk location
or Context
to make it easier to debug space leaks. Info
is available if
GHC-9.4
or newer is used,- the code is compiled with
-finfo-table-map
and is improved if-fdistinct-constructor-tables
is used as well.
The Context
argument is intended to give a clue to add debugging.
For example, suppose we have something of type (Int, [Int])
. The
various contexts we might get are
Context The thunk is.. --------------------------------------------------------------------- ["(,)"] the pair itself ["Int","(,)"] the Int in the pair ["List","(,)"] the [Int] in the pair ["Int","List","(,)"] an Int in the [Int] in the pair
Note: prior to `ghc-9.6` a list was indicated by `[]`.
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.
Binding name, type and location information about the thunk, e.g.
fromModel :: Int @ test/Test/NoThunks/Class.hs:198:53-84
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
Instances
Typeable a => NoThunks (OnlyCheckWhnf a) Source # | |
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
Instances
KnownSymbol name => NoThunks (OnlyCheckWhnfNamed name a) Source # | |
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
Instances
Typeable a => NoThunks (InspectHeap a) Source # | |
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
Instances
KnownSymbol name => NoThunks (InspectHeapNamed name a) Source # | |
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
.
Instances
NoThunks (AllowThunk a) Source # | |
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.
Instances
(HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a)) => NoThunks (AllowThunksIn s a) Source # | |
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.
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
GWNoThunks a (U1 :: Type -> Type) Source # | |
Defined in NoThunks.Class | |
GWNoThunks a (V1 :: Type -> Type) Source # | |
Defined in NoThunks.Class | |
(GWNoThunks a f, GWNoThunks a g) => GWNoThunks a (f :*: g) Source # | |
Defined in NoThunks.Class | |
(GWNoThunks a f, GWNoThunks a g) => GWNoThunks a (f :+: g) Source # | |
Defined in NoThunks.Class | |
GWNoThunks a f => GWNoThunks a (C1 c f) Source # | |
Defined in NoThunks.Class | |
GWNoThunks a f => GWNoThunks a (D1 c f) Source # | |
Defined in NoThunks.Class | |
NoThunks c => GWNoThunks a (K1 i c :: Type -> Type) Source # | |
Defined in NoThunks.Class | |
(GWRecordField f (Elem fieldName a), KnownSymbol fieldName) => GWNoThunks a (S1 ('MetaSel ('Just fieldName) su ss ds) f) Source # | If |
GWNoThunks a f => GWNoThunks a (S1 ('MetaSel ('Nothing :: Maybe Symbol) su ss ds) f) Source # | |