ghc-7.8.4: The GHC API

Safe HaskellNone
LanguageHaskell98

RtClosureInspect

Synopsis

Documentation

cvObtainTerm :: HscEnv -> Int -> Bool -> RttiType -> HValue -> IO Term Source

cvReconstructType :: HscEnv -> Int -> GhciType -> HValue -> IO (Maybe Type) Source

improveRTTIType :: HscEnv -> RttiType -> RttiType -> Maybe TvSubst Source

data Term Source

Constructors

Term 

Fields

ty :: RttiType
 
dc :: Either String DataCon
 
val :: HValue
 
subTerms :: [Term]
 
Prim 

Fields

ty :: RttiType
 
value :: [Word]
 
Suspension 

Fields

ctype :: ClosureType
 
ty :: RttiType
 
val :: HValue
 
bound_to :: Maybe Name
 
NewtypeWrap 

Fields

ty :: RttiType
 
dc :: Either String DataCon
 
wrapped_term :: Term
 
RefWrap 

Fields

ty :: RttiType
 
wrapped_term :: Term
 

Instances

termType :: Term -> RttiType Source

mapTermType :: (RttiType -> Type) -> Term -> Term Source

data TermFold a Source

Constructors

TermFold 

Fields

fTerm :: TermProcessor a a
 
fPrim :: RttiType -> [Word] -> a
 
fSuspension :: ClosureType -> RttiType -> HValue -> Maybe Name -> a
 
fNewtypeWrap :: RttiType -> Either String DataCon -> a -> a
 
fRefWrap :: RttiType -> a -> a
 

foldTermM :: Monad m => TermFoldM m a -> Term -> m a Source

data TermFoldM m a Source

Constructors

TermFoldM 

Fields

fTermM :: TermProcessor a (m a)
 
fPrimM :: RttiType -> [Word] -> m a
 
fSuspensionM :: ClosureType -> RttiType -> HValue -> Maybe Name -> m a
 
fNewtypeWrapM :: RttiType -> Either String DataCon -> a -> m a
 
fRefWrapM :: RttiType -> a -> m a
 

pprTerm :: TermPrinter -> TermPrinter Source

cPprTerm :: Monad m => CustomTermPrinter m -> Term -> m SDoc Source

Takes a list of custom printers with a explicit recursion knot and a term, and returns the output of the first successful printer, or the default printer

type CustomTermPrinter m = TermPrinterM m -> [Precedence -> Term -> m (Maybe SDoc)] Source