ghc-9.2.4: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Utils.Logger

Description

Logger

Synopsis

Documentation

class HasLogger m where Source #

Methods

getLogger :: m Logger Source #

Instances

Instances details
HasLogger LlvmM Source # 
Instance details

Defined in GHC.CmmToLlvm.Base

HasLogger CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

HasLogger SimplM Source # 
Instance details

Defined in GHC.Core.Opt.Simplify.Monad

HasLogger Hsc Source # 
Instance details

Defined in GHC.Driver.Env.Types

HasLogger Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

HasLogger CompPipeline Source # 
Instance details

Defined in GHC.Driver.Pipeline.Monad

ContainsLogger env => HasLogger (IOEnv env) Source # 
Instance details

Defined in GHC.Data.IOEnv

Methods

getLogger :: IOEnv env Logger Source #

MonadIO m => HasLogger (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

class ContainsLogger t where Source #

Methods

extractLogger :: t -> Logger Source #

Instances

Instances details
ContainsLogger (Env gbl lcl) Source # 
Instance details

Defined in GHC.Tc.Types

Methods

extractLogger :: Env gbl lcl -> Logger Source #

type TraceAction a = DynFlags -> String -> SDoc -> a -> a Source #

data DumpFormat Source #

Format of a dump

Dump formats are loosely defined: dumps may contain various additional headers and annotations and they may be partial. DumpFormat is mainly a hint (e.g. for syntax highlighters).

Constructors

FormatHaskell

Haskell

FormatCore

Core

FormatSTG

STG

FormatByteCode

ByteCode

FormatCMM

Cmm

FormatASM

Assembly code

FormatC

C code/header

FormatLLVM

LLVM bytecode

FormatText

Unstructured dump

Instances

Instances details
Show DumpFormat Source # 
Instance details

Defined in GHC.Utils.Logger

Eq DumpFormat Source # 
Instance details

Defined in GHC.Utils.Logger

putLogMsg :: Logger -> LogAction Source #

Log something

putDumpMsg :: Logger -> DumpAction Source #

Dump something

putTraceMsg :: Logger -> TraceAction a Source #

Trace something

Hooks

popLogHook :: Logger -> Logger Source #

Pop a log hook

pushLogHook :: (LogAction -> LogAction) -> Logger -> Logger Source #

Push a log hook

popDumpHook :: Logger -> Logger Source #

Pop a dump hook

pushDumpHook :: (DumpAction -> DumpAction) -> Logger -> Logger Source #

Push a dump hook

popTraceHook :: Logger -> Logger Source #

Pop a trace hook

pushTraceHook :: (forall a. TraceAction a -> TraceAction a) -> Logger -> Logger Source #

Push a trace hook

makeThreadSafe :: Logger -> IO Logger Source #

Make the logger thread-safe

Logging

defaultLogActionHPrintDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () Source #

Like defaultLogActionHPutStrDoc but appends an extra newline.

defaultLogActionHPutStrDoc :: DynFlags -> Bool -> Handle -> SDoc -> IO () Source #

The boolean arguments let's the pretty printer know if it can optimize indent by writing ascii ' ' characters without going through decoding.

Dumping

defaultDumpAction :: DumpCache -> LogAction -> DumpAction Source #

Default action for dumpAction hook

withDumpFileHandle :: DumpCache -> DynFlags -> DumpFlag -> (Maybe Handle -> IO ()) -> IO () Source #

Run an action with the handle of a DumpFlag if we are outputting to a file, otherwise Nothing.

touchDumpFile :: Logger -> DynFlags -> DumpFlag -> IO () Source #

Ensure that a dump file is created even if it stays empty

dumpIfSet_dyn :: Logger -> DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO () Source #

A wrapper around dumpAction. First check whether the dump flag is set Do nothing if it is unset

dumpIfSet_dyn_printer :: PrintUnqualified -> Logger -> DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO () Source #

A wrapper around putDumpMsg. First check whether the dump flag is set Do nothing if it is unset

Unlike dumpIfSet_dyn, has a printer argument

Tracing

defaultTraceAction :: TraceAction a Source #

Default action for traceAction hook