ghc-heap-9.11: Functions for walking GHC's heap
Copyright(c) 2012 Joachim Breitner
LicenseBSD3
MaintainerJoachim Breitner <mail@joachim-breitner.de>
Safe HaskellNone
LanguageHaskell2010

GHC.Exts.Heap

Description

With this module, you can investigate the heap representation of Haskell values, i.e. to investigate sharing and lazy evaluation.

Synopsis

Closure types

data GenClosure b Source #

This is the representation of a Haskell value on the heap. It reflects https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/storage/Closures.h

The data type is parametrized by b: the type to store references in. Usually this is a Box with the type synonym Closure.

All Heap objects have the same basic layout. A header containing a pointer to the info table and a payload with various fields. The info field below always refers to the info table pointed to by the header. The remaining fields are the payload.

See https://gitlab.haskell.org/ghc/ghc/wikis/commentary/rts/storage/heap-objects for more information.

Constructors

ConstrClosure

A data constructor

Fields

FunClosure

A function

Fields

ThunkClosure

A thunk, an expression not obviously in head normal form

Fields

SelectorClosure

A thunk which performs a simple selection operation

Fields

PAPClosure

An unsaturated function application

Fields

APClosure

A function application

Fields

APStackClosure

A suspended thunk evaluation

Fields

IndClosure

A pointer to another closure, introduced when a thunk is updated to point at its value

Fields

BCOClosure

A byte-code object (BCO) which can be interpreted by GHC's byte-code interpreter (e.g. as used by GHCi)

Fields

  • info :: !StgInfoTable
     
  • instrs :: !b

    A pointer to an ArrWords of instructions

  • literals :: !b

    A pointer to an ArrWords of literals

  • bcoptrs :: !b

    A pointer to an ArrWords of byte code objects

  • arity :: !HalfWord

    Arity of the partial application

  • size :: !HalfWord

    The size of this BCO in words

  • bitmap :: ![Word]

    An StgLargeBitmap describing the pointerhood of its args/free vars

BlackholeClosure

A thunk under evaluation by another thread

Fields

ArrWordsClosure

A ByteArray#

Fields

MutArrClosure

A MutableByteArray#

Fields

SmallMutArrClosure

A SmallMutableArray#

Since: ghc-heap-8.10.1

Fields

MVarClosure

An MVar#, with a queue of thread state objects blocking on them

Fields

IOPortClosure

An IOPort#, with a queue of thread state objects blocking on them

Fields

MutVarClosure

A MutVar#

Fields

BlockingQueueClosure

An STM blocking queue.

Fields

WeakClosure 

Fields

TSOClosure

Representation of StgTSO: A Thread State Object. The values for what_next, why_blocked and flags are defined in Constants.h.

Fields

StackClosure

Representation of StgStack: The 'tsoStack ' of a TSOClosure.

Fields

IntClosure

Primitive Int

Fields

WordClosure

Primitive Word

Fields

Int64Closure

Primitive Int64

Fields

Word64Closure

Primitive Word64

Fields

AddrClosure

Primitive Addr

Fields

FloatClosure

Primitive Float

Fields

DoubleClosure

Primitive Double

Fields

OtherClosure

Another kind of closure

Fields

UnsupportedClosure 

Fields

UnknownTypeWordSizedPrimitive

A primitive word from a bitmap encoded stack frame payload

The type itself cannot be restored (i.e. it might represent a Word8# or an Int#).

Fields

Instances

Instances details
Functor GenClosure Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

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

(<$) :: a -> GenClosure b -> GenClosure a Source #

Foldable GenClosure Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

fold :: Monoid m => GenClosure m -> m Source #

foldMap :: Monoid m => (a -> m) -> GenClosure a -> m Source #

foldMap' :: Monoid m => (a -> m) -> GenClosure a -> m Source #

foldr :: (a -> b -> b) -> b -> GenClosure a -> b Source #

foldr' :: (a -> b -> b) -> b -> GenClosure a -> b Source #

foldl :: (b -> a -> b) -> b -> GenClosure a -> b Source #

foldl' :: (b -> a -> b) -> b -> GenClosure a -> b Source #

foldr1 :: (a -> a -> a) -> GenClosure a -> a Source #

foldl1 :: (a -> a -> a) -> GenClosure a -> a Source #

toList :: GenClosure a -> [a] Source #

null :: GenClosure a -> Bool Source #

length :: GenClosure a -> Int Source #

elem :: Eq a => a -> GenClosure a -> Bool Source #

maximum :: Ord a => GenClosure a -> a Source #

minimum :: Ord a => GenClosure a -> a Source #

sum :: Num a => GenClosure a -> a Source #

product :: Num a => GenClosure a -> a Source #

Traversable GenClosure Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Methods

traverse :: Applicative f => (a -> f b) -> GenClosure a -> f (GenClosure b) Source #

sequenceA :: Applicative f => GenClosure (f a) -> f (GenClosure a) Source #

mapM :: Monad m => (a -> m b) -> GenClosure a -> m (GenClosure b) Source #

sequence :: Monad m => GenClosure (m a) -> m (GenClosure a) Source #

Generic (GenClosure b) Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep (GenClosure b) 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep (GenClosure b) = D1 ('MetaData "GenClosure" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) ((((C1 ('MetaCons "ConstrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :*: (S1 ('MetaSel ('Just "pkg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "modl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))) :+: (C1 ('MetaCons "FunClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :+: C1 ('MetaCons "ThunkClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))))) :+: ((C1 ('MetaCons "SelectorClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "selectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "PAPClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))))) :+: (C1 ('MetaCons "APClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))) :+: C1 ('MetaCons "APStackClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))))) :+: (((C1 ('MetaCons "IndClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "BCOClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "instrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "literals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "bcoptrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: S1 ('MetaSel ('Just "bitmap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))))) :+: (C1 ('MetaCons "BlackholeClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "ArrWordsClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "bytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "arrWords") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))))) :+: ((C1 ('MetaCons "MutArrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "mccSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "mccPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))) :+: C1 ('MetaCons "SmallMutArrClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "mccPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))) :+: (C1 ('MetaCons "MVarClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "queueHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "queueTail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :+: C1 ('MetaCons "IOPortClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "queueHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "queueTail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))))))) :+: (((C1 ('MetaCons "MutVarClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "var") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: (C1 ('MetaCons "BlockingQueueClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "blackHole") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "owner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "queue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))) :+: C1 ('MetaCons "WeakClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "cfinalizers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "finalizer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "weakLink") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe b))))))) :+: ((C1 ('MetaCons "TSOClosure" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "global_link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "tsoStack") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "trec") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "blocked_exceptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "bq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "thread_label") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe b))))) :*: (((S1 ('MetaSel ('Just "what_next") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WhatNext) :*: S1 ('MetaSel ('Just "why_blocked") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WhyBlocked)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [TsoFlags]) :*: S1 ('MetaSel ('Just "threadId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "saved_errno") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "tso_dirty") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "alloc_limit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "tot_stack_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "prof") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe StgTSOProfInfo))))))) :+: C1 ('MetaCons "StackClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "stack_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "stack_dirty") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "stack_marking") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8)))) :+: (C1 ('MetaCons "IntClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "intVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "WordClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "wordVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word))))) :+: (((C1 ('MetaCons "Int64Closure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "int64Val") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)) :+: C1 ('MetaCons "Word64Closure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "word64Val") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :+: (C1 ('MetaCons "AddrClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "addrVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ptr ()))) :+: C1 ('MetaCons "FloatClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "floatVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Float)))) :+: ((C1 ('MetaCons "DoubleClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "doubleVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "OtherClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "hvalues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "rawWords") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word])))) :+: (C1 ('MetaCons "UnsupportedClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable)) :+: C1 ('MetaCons "UnknownTypeWordSizedPrimitive" 'PrefixI 'True) (S1 ('MetaSel ('Just "wordVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)))))))

Methods

from :: GenClosure b -> Rep (GenClosure b) x Source #

to :: Rep (GenClosure b) x -> GenClosure b Source #

Show b => Show (GenClosure b) Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep (GenClosure b) Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep (GenClosure b) = D1 ('MetaData "GenClosure" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) ((((C1 ('MetaCons "ConstrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :*: (S1 ('MetaSel ('Just "pkg") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: (S1 ('MetaSel ('Just "modl") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 String)))) :+: (C1 ('MetaCons "FunClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))) :+: C1 ('MetaCons "ThunkClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "ptrArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "dataArgs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))))) :+: ((C1 ('MetaCons "SelectorClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "selectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "PAPClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))))) :+: (C1 ('MetaCons "APClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "n_args") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))) :+: C1 ('MetaCons "APStackClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "fun") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "payload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))))) :+: (((C1 ('MetaCons "IndClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "BCOClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "instrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "literals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "bcoptrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "arity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord)) :*: (S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 HalfWord) :*: S1 ('MetaSel ('Just "bitmap") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))))) :+: (C1 ('MetaCons "BlackholeClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "indirectee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: C1 ('MetaCons "ArrWordsClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "bytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "arrWords") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word]))))) :+: ((C1 ('MetaCons "MutArrClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :*: (S1 ('MetaSel ('Just "mccSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "mccPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]))) :+: C1 ('MetaCons "SmallMutArrClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "mccPtrs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word) :*: S1 ('MetaSel ('Just "mccPayload") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b])))) :+: (C1 ('MetaCons "MVarClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "queueHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "queueTail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :+: C1 ('MetaCons "IOPortClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "queueHead") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "queueTail") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))))))) :+: (((C1 ('MetaCons "MutVarClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "var") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :+: (C1 ('MetaCons "BlockingQueueClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "blackHole") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "owner") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "queue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)))) :+: C1 ('MetaCons "WeakClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "cfinalizers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "key") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: (S1 ('MetaSel ('Just "value") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: (S1 ('MetaSel ('Just "finalizer") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "weakLink") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe b))))))) :+: ((C1 ('MetaCons "TSOClosure" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "global_link") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "tsoStack") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b))) :*: ((S1 ('MetaSel ('Just "trec") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "blocked_exceptions") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b)) :*: (S1 ('MetaSel ('Just "bq") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 b) :*: S1 ('MetaSel ('Just "thread_label") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe b))))) :*: (((S1 ('MetaSel ('Just "what_next") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WhatNext) :*: S1 ('MetaSel ('Just "why_blocked") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 WhyBlocked)) :*: (S1 ('MetaSel ('Just "flags") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [TsoFlags]) :*: S1 ('MetaSel ('Just "threadId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "saved_errno") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "tso_dirty") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "alloc_limit") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64) :*: (S1 ('MetaSel ('Just "tot_stack_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "prof") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe StgTSOProfInfo))))))) :+: C1 ('MetaCons "StackClosure" 'PrefixI 'True) ((S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: S1 ('MetaSel ('Just "stack_size") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32)) :*: (S1 ('MetaSel ('Just "stack_dirty") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "stack_marking") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8)))) :+: (C1 ('MetaCons "IntClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "intVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "WordClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "wordVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word))))) :+: (((C1 ('MetaCons "Int64Closure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "int64Val") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int64)) :+: C1 ('MetaCons "Word64Closure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "word64Val") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64))) :+: (C1 ('MetaCons "AddrClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "addrVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ptr ()))) :+: C1 ('MetaCons "FloatClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "floatVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Float)))) :+: ((C1 ('MetaCons "DoubleClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "ptipe") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PrimType) :*: S1 ('MetaSel ('Just "doubleVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Double)) :+: C1 ('MetaCons "OtherClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable) :*: (S1 ('MetaSel ('Just "hvalues") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [b]) :*: S1 ('MetaSel ('Just "rawWords") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Word])))) :+: (C1 ('MetaCons "UnsupportedClosure" 'PrefixI 'True) (S1 ('MetaSel ('Just "info") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StgInfoTable)) :+: C1 ('MetaCons "UnknownTypeWordSizedPrimitive" 'PrefixI 'True) (S1 ('MetaSel ('Just "wordVal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)))))))

data ClosureType Source #

Enum representing closure types This is a mirror of: rtsincludertsstorageClosureTypes.h

Since: ghc-internal-0.1.0.0

Instances

Instances details
Enum ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

Generic ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

Associated Types

type Rep ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

type Rep ClosureType = D1 ('MetaData "ClosureType" "GHC.Internal.ClosureTypes" "ghc-internal" 'False) ((((((C1 ('MetaCons "INVALID_OBJECT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONSTR_1_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_0_1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CONSTR_2_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_1_1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONSTR_0_2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_NOCAF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "FUN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_1_0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FUN_0_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_2_0" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FUN_1_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_0_2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FUN_STATIC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "THUNK_1_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_0_1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "THUNK_2_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_1_1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "THUNK_0_2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_STATIC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "THUNK_SELECTOR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BCO" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PAP" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AP_STACK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IND" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IND_STATIC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RET_BCO" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RET_SMALL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RET_BIG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RET_FUN" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "UPDATE_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CATCH_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UNDERFLOW_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STOP_FRAME" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BLOCKING_QUEUE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BLACKHOLE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MVAR_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MVAR_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "TVAR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARR_WORDS" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_ARR_PTRS_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_ARR_PTRS_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MUT_ARR_PTRS_FROZEN_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_ARR_PTRS_FROZEN_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_VAR_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_VAR_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "WEAK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PRIM" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_PRIM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TSO" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "STACK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TREC_CHUNK" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ATOMICALLY_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CATCH_RETRY_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CATCH_STM_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WHITEHOLE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SMALL_MUT_ARR_PTRS_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMALL_MUT_ARR_PTRS_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SMALL_MUT_ARR_PTRS_FROZEN_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMALL_MUT_ARR_PTRS_FROZEN_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "COMPACT_NFDATA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CONTINUATION" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "N_CLOSURE_TYPES" 'PrefixI 'False) (U1 :: Type -> Type))))))))
Show ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

Eq ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

Ord ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

type Rep ClosureType 
Instance details

Defined in GHC.Internal.ClosureTypes

type Rep ClosureType = D1 ('MetaData "ClosureType" "GHC.Internal.ClosureTypes" "ghc-internal" 'False) ((((((C1 ('MetaCons "INVALID_OBJECT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONSTR_1_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_0_1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "CONSTR_2_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_1_1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CONSTR_0_2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CONSTR_NOCAF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "FUN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_1_0" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FUN_0_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_2_0" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FUN_1_1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FUN_0_2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FUN_STATIC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "THUNK_1_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_0_1" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "THUNK_2_0" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_1_1" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "THUNK_0_2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "THUNK_STATIC" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "THUNK_SELECTOR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BCO" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "AP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PAP" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "AP_STACK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IND" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IND_STATIC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RET_BCO" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RET_SMALL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RET_BIG" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RET_FUN" 'PrefixI 'False) (U1 :: Type -> Type))))))) :+: (((((C1 ('MetaCons "UPDATE_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CATCH_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "UNDERFLOW_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "STOP_FRAME" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BLOCKING_QUEUE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BLACKHOLE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MVAR_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MVAR_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "TVAR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARR_WORDS" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_ARR_PTRS_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_ARR_PTRS_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "MUT_ARR_PTRS_FROZEN_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_ARR_PTRS_FROZEN_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_VAR_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MUT_VAR_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "WEAK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PRIM" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MUT_PRIM" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TSO" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "STACK" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TREC_CHUNK" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ATOMICALLY_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CATCH_RETRY_FRAME" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "CATCH_STM_FRAME" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WHITEHOLE" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SMALL_MUT_ARR_PTRS_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMALL_MUT_ARR_PTRS_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SMALL_MUT_ARR_PTRS_FROZEN_DIRTY" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SMALL_MUT_ARR_PTRS_FROZEN_CLEAN" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "COMPACT_NFDATA" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CONTINUATION" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "N_CLOSURE_TYPES" 'PrefixI 'False) (U1 :: Type -> Type))))))))

data PrimType Source #

Instances

Instances details
Generic PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep PrimType 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep PrimType = D1 ('MetaData "PrimType" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) ((C1 ('MetaCons "PInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PInt64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PWord64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PAddr" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PFloat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PDouble" 'PrefixI 'False) (U1 :: Type -> Type))))
Show PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Eq PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Ord PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep PrimType Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep PrimType = D1 ('MetaData "PrimType" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) ((C1 ('MetaCons "PInt" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "PWord" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PInt64" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "PWord64" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PAddr" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PFloat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PDouble" 'PrefixI 'False) (U1 :: Type -> Type))))

data WhatNext Source #

Instances

Instances details
Generic WhatNext Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhatNext 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep WhatNext = D1 ('MetaData "WhatNext" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) ((C1 ('MetaCons "ThreadRunGHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThreadInterpret" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThreadKilled" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ThreadComplete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WhatNextUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))))
Show WhatNext Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Eq WhatNext Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Ord WhatNext Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep WhatNext Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep WhatNext = D1 ('MetaData "WhatNext" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) ((C1 ('MetaCons "ThreadRunGHC" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThreadInterpret" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThreadKilled" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ThreadComplete" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WhatNextUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16)))))

data WhyBlocked Source #

Instances

Instances details
Generic WhyBlocked Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep WhyBlocked 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep WhyBlocked = D1 ('MetaData "WhyBlocked" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) (((C1 ('MetaCons "NotBlocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockedOnMVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnMVarRead" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BlockedOnBlackHole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnRead" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BlockedOnWrite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnDelay" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BlockedOnSTM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockedOnDoProc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnCCall" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BlockedOnCCall_Interruptible" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnMsgThrowTo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThreadMigrating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WhyBlockedUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))))))
Show WhyBlocked Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Eq WhyBlocked Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Ord WhyBlocked Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep WhyBlocked Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep WhyBlocked = D1 ('MetaData "WhyBlocked" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) (((C1 ('MetaCons "NotBlocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockedOnMVar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnMVarRead" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BlockedOnBlackHole" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnRead" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BlockedOnWrite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnDelay" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "BlockedOnSTM" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BlockedOnDoProc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnCCall" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BlockedOnCCall_Interruptible" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BlockedOnMsgThrowTo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ThreadMigrating" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "WhyBlockedUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word16))))))

data TsoFlags Source #

Instances

Instances details
Generic TsoFlags Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Associated Types

type Rep TsoFlags 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep TsoFlags = D1 ('MetaData "TsoFlags" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) (((C1 ('MetaCons "TsoLocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoBlockx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TsoInterruptible" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoStoppedOnBreakpoint" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TsoMarked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoSqueezed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TsoAllocLimit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoFlagsUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))))
Show TsoFlags Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Eq TsoFlags Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

Ord TsoFlags Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep TsoFlags Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

type Rep TsoFlags = D1 ('MetaData "TsoFlags" "GHC.Exts.Heap.Closures" "ghc-heap-9.11-inplace" 'False) (((C1 ('MetaCons "TsoLocked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoBlockx" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TsoInterruptible" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoStoppedOnBreakpoint" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TsoMarked" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoSqueezed" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TsoAllocLimit" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TsoFlagsUnknownValue" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))))

class HasHeapRep (a :: TYPE rep) where Source #

Methods

getClosureData Source #

Arguments

:: a

Closure to decode.

-> IO Closure

Heap representation of the closure.

Decode a closure to it's heap representation (GenClosure).

Instances

Instances details
Addr# ~ a => HasHeapRep (a :: TYPE 'AddrRep) Source # 
Instance details

Defined in GHC.Exts.Heap

Double# ~ a => HasHeapRep (a :: TYPE 'DoubleRep) Source # 
Instance details

Defined in GHC.Exts.Heap

Float# ~ a => HasHeapRep (a :: TYPE 'FloatRep) Source # 
Instance details

Defined in GHC.Exts.Heap

Int64# ~ a => HasHeapRep (a :: TYPE 'Int64Rep) Source # 
Instance details

Defined in GHC.Exts.Heap

Int# ~ a => HasHeapRep (a :: TYPE 'IntRep) Source # 
Instance details

Defined in GHC.Exts.Heap

HasHeapRep (a :: Type) Source # 
Instance details

Defined in GHC.Exts.Heap

HasHeapRep (a :: UnliftedType) Source # 
Instance details

Defined in GHC.Exts.Heap

Word64# ~ a => HasHeapRep (a :: TYPE 'Word64Rep) Source # 
Instance details

Defined in GHC.Exts.Heap

Word# ~ a => HasHeapRep (a :: TYPE 'WordRep) Source # 
Instance details

Defined in GHC.Exts.Heap

getClosureDataFromHeapRep :: ByteArray# -> Ptr StgInfoTable -> [b] -> IO (GenClosure b) Source #

Convert an unpacked heap object, to a `GenClosure b`. The inputs to this function can be generated from a heap object using unpackClosure#.

getClosureDataFromHeapRepPrim Source #

Arguments

:: IO (String, String, String)

A continuation used to decode the constructor description field, in ghc-debug this code can lead to segfaults because dataConNames will dereference a random part of memory.

-> (Ptr a -> IO (Maybe CostCentreStack))

A continuation which is used to decode a cost centre stack In ghc-debug, this code will need to call back into the debuggee to fetch the representation of the CCS before decoding it. Using peekTopCCS for this argument can lead to segfaults in ghc-debug as the CCS argument will point outside the copied closure.

-> StgInfoTable

The StgInfoTable of the closure, extracted from the heap representation.

-> ByteArray#

Heap representation of the closure as returned by unpackClosure#. This includes all of the object including the header, info table pointer, pointer data, and non-pointer data. The ByteArray# may be pinned or unpinned.

-> [b]

Pointers in the payload of the closure, extracted from the heap representation as returned by `collect_pointers()` in c. The type b is some representation of a pointer e.g. Any or `Ptr Any`.

-> IO (GenClosure b)

Heap representation of the closure.

Info Table types

data StgInfoTable Source #

This is a somewhat faithful representation of an info table. See https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/storage/InfoTables.h for more details on this data structure.

Instances

Instances details
Generic StgInfoTable Source # 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

Show StgInfoTable Source # 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

Eq StgInfoTable Source # 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

type Rep StgInfoTable Source # 
Instance details

Defined in GHC.Exts.Heap.InfoTable.Types

type EntryFunPtr = FunPtr (Ptr () -> IO (Ptr ())) Source #

itblSize :: Int Source #

Size in bytes of a standard InfoTable

peekItbl :: Ptr StgInfoTable -> IO StgInfoTable Source #

Read an InfoTable from the heap into a haskell type. WARNING: This code assumes it is passed a pointer to a "standard" info table. If tables_next_to_code is enabled, it will look 1 byte before the start for the entry field.

Cost Centre (profiling) types

newtype StgTSOProfInfo Source #

This is a somewhat faithful representation of StgTSOProfInfo. See https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/storage/TSO.h for more details on this data structure.

Constructors

StgTSOProfInfo 

Instances

Instances details
Generic StgTSOProfInfo Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep StgTSOProfInfo 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep StgTSOProfInfo = D1 ('MetaData "StgTSOProfInfo" "GHC.Exts.Heap.ProfInfo.Types" "ghc-heap-9.11-inplace" 'True) (C1 ('MetaCons "StgTSOProfInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "cccs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CostCentreStack))))
Show StgTSOProfInfo Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Eq StgTSOProfInfo Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Ord StgTSOProfInfo Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep StgTSOProfInfo Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep StgTSOProfInfo = D1 ('MetaData "StgTSOProfInfo" "GHC.Exts.Heap.ProfInfo.Types" "ghc-heap-9.11-inplace" 'True) (C1 ('MetaCons "StgTSOProfInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "cccs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CostCentreStack))))

data IndexTable Source #

This is a somewhat faithful representation of IndexTable. See https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/prof/CCS.h for more details on this data structure.

Instances

Instances details
Generic IndexTable Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep IndexTable 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Show IndexTable Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Eq IndexTable Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Ord IndexTable Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep IndexTable Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

data CostCentre Source #

This is a somewhat faithful representation of CostCentre. See https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/prof/CCS.h for more details on this data structure.

Instances

Instances details
Generic CostCentre Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Show CostCentre Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Eq CostCentre Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Ord CostCentre Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep CostCentre Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

data CostCentreStack Source #

This is a somewhat faithful representation of CostCentreStack. See https://gitlab.haskell.org/ghc/ghc/blob/master/rts/include/rts/prof/CCS.h for more details on this data structure.

Instances

Instances details
Generic CostCentreStack Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Associated Types

type Rep CostCentreStack 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep CostCentreStack = D1 ('MetaData "CostCentreStack" "GHC.Exts.Heap.ProfInfo.Types" "ghc-heap-9.11-inplace" 'False) (C1 ('MetaCons "CostCentreStack" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ccs_ccsID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "ccs_cc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostCentre) :*: S1 ('MetaSel ('Just "ccs_prevStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CostCentreStack)))) :*: (S1 ('MetaSel ('Just "ccs_indexTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe IndexTable)) :*: (S1 ('MetaSel ('Just "ccs_root") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CostCentreStack)) :*: S1 ('MetaSel ('Just "ccs_depth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))) :*: ((S1 ('MetaSel ('Just "ccs_scc_count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "ccs_selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "ccs_time_ticks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))) :*: (S1 ('MetaSel ('Just "ccs_mem_alloc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "ccs_inherited_alloc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ccs_inherited_ticks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))))))
Show CostCentreStack Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Eq CostCentreStack Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

Ord CostCentreStack Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep CostCentreStack Source # 
Instance details

Defined in GHC.Exts.Heap.ProfInfo.Types

type Rep CostCentreStack = D1 ('MetaData "CostCentreStack" "GHC.Exts.Heap.ProfInfo.Types" "ghc-heap-9.11-inplace" 'False) (C1 ('MetaCons "CostCentreStack" 'PrefixI 'True) (((S1 ('MetaSel ('Just "ccs_ccsID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "ccs_cc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CostCentre) :*: S1 ('MetaSel ('Just "ccs_prevStack") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CostCentreStack)))) :*: (S1 ('MetaSel ('Just "ccs_indexTable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe IndexTable)) :*: (S1 ('MetaSel ('Just "ccs_root") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe CostCentreStack)) :*: S1 ('MetaSel ('Just "ccs_depth") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)))) :*: ((S1 ('MetaSel ('Just "ccs_scc_count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "ccs_selected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word) :*: S1 ('MetaSel ('Just "ccs_time_ticks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))) :*: (S1 ('MetaSel ('Just "ccs_mem_alloc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: (S1 ('MetaSel ('Just "ccs_inherited_alloc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64) :*: S1 ('MetaSel ('Just "ccs_inherited_ticks") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))))))

Closure inspection

getBoxedClosureData :: Box -> IO Closure Source #

Like getClosureData, but taking a Box, so it is easier to work with.

allClosures :: GenClosure b -> [b] Source #

For generic code, this function returns all referenced closures.

Boxes

data Box Source #

An arbitrary Haskell value in a safe Box. The point is that even unevaluated thunks can safely be moved around inside the Box, and when required, e.g. in getBoxedClosureData, the function knows how far it has to evaluate the argument.

Constructors

Box (Any :: Type) 

Instances

Instances details
Show Box Source # 
Instance details

Defined in GHC.Exts.Heap.Closures

asBox :: a -> Box Source #

This takes an arbitrary value and puts it into a box. Note that calls like

asBox (head list)

will put the thunk "head list" into the box, not the element at the head of the list. For that, use careful case expressions:

case list of x:_ -> asBox x

areBoxesEqual :: Box -> Box -> IO Bool Source #

Boxes can be compared, but this is not pure, as different heap objects can, after garbage collection, become the same object.