| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
NoThunks.Class
Synopsis
- class NoThunks a where
- data ThunkInfo = ThunkInfo {- thunkContext :: Context
 
- 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
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 == NoThunks
if and only if
containsThunks 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 UnexpectedThunkInfo for a
 detailed discussion of the type context.
See also discussion of caveats listed for containsThunks.
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.
wNoThunks :: (Generic a, GWNoThunks '[] (Rep a)) => 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.
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.
showTypeOf :: (Generic a, GShowTypeOf (Rep a)) => 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
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 | |
| Fields 
 | |
Helpders 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
| Typeable a => NoThunks (OnlyCheckWhnf a) Source # | |
| Defined in NoThunks.Class Methods noThunks :: Context -> OnlyCheckWhnf a -> IO (Maybe ThunkInfo) Source # wNoThunks :: Context -> OnlyCheckWhnf a -> IO (Maybe ThunkInfo) Source # showTypeOf :: Proxy (OnlyCheckWhnf a) -> String Source # | |
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
| KnownSymbol name => NoThunks (OnlyCheckWhnfNamed name a) Source # | |
| Defined in NoThunks.Class Methods noThunks :: Context -> OnlyCheckWhnfNamed name a -> IO (Maybe ThunkInfo) Source # wNoThunks :: Context -> OnlyCheckWhnfNamed name a -> IO (Maybe ThunkInfo) Source # showTypeOf :: Proxy (OnlyCheckWhnfNamed name a) -> String Source # | |
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
| Typeable a => NoThunks (InspectHeap a) Source # | |
| Defined in NoThunks.Class Methods noThunks :: Context -> InspectHeap a -> IO (Maybe ThunkInfo) Source # wNoThunks :: Context -> InspectHeap a -> IO (Maybe ThunkInfo) Source # showTypeOf :: Proxy (InspectHeap a) -> String Source # | |
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
| KnownSymbol name => NoThunks (InspectHeapNamed name a) Source # | |
| Defined in NoThunks.Class Methods noThunks :: Context -> InspectHeapNamed name a -> IO (Maybe ThunkInfo) Source # wNoThunks :: Context -> InspectHeapNamed name a -> IO (Maybe ThunkInfo) Source # showTypeOf :: Proxy (InspectHeapNamed name a) -> String Source # | |
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
| NoThunks (AllowThunk a) Source # | |
| Defined in NoThunks.Class Methods noThunks :: Context -> AllowThunk a -> IO (Maybe ThunkInfo) Source # wNoThunks :: Context -> AllowThunk a -> IO (Maybe ThunkInfo) Source # showTypeOf :: Proxy (AllowThunk a) -> String Source # | |
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
| (HasFields s a, Generic a, Typeable a, GWNoThunks s (Rep a)) => NoThunks (AllowThunksIn s a) Source # | |
| Defined in NoThunks.Class Methods noThunks :: Context -> AllowThunksIn s a -> IO (Maybe ThunkInfo) Source # wNoThunks :: Context -> AllowThunksIn s a -> IO (Maybe ThunkInfo) Source # showTypeOf :: Proxy (AllowThunksIn s a) -> String Source # | |