Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Printing related functions that depend on session state (DynFlags)
Synopsis
- showSDoc :: DynFlags -> SDoc -> String
- showSDocForUser :: DynFlags -> UnitState -> PrintUnqualified -> SDoc -> String
- showSDocDebug :: DynFlags -> SDoc -> String
- showSDocDump :: SDocContext -> SDoc -> String
- showPpr :: Outputable a => DynFlags -> a -> String
- pprDebugAndThen :: SDocContext -> (String -> a) -> SDoc -> SDoc -> a
- printForUser :: DynFlags -> Handle -> PrintUnqualified -> Depth -> SDoc -> IO ()
- printForC :: DynFlags -> Handle -> SDoc -> IO ()
- warnPprTrace :: HasCallStack => Bool -> String -> Int -> SDoc -> a -> a
- pprTrace :: String -> SDoc -> a -> a
- pprTraceWithFlags :: DynFlags -> String -> SDoc -> a -> a
- pprTraceM :: Applicative f => String -> SDoc -> f ()
- pprTraceDebug :: String -> SDoc -> a -> a
- pprTraceIt :: Outputable a => String -> a -> a
- pprSTrace :: HasCallStack => SDoc -> a -> a
- pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a
Documentation
showSDocForUser :: DynFlags -> UnitState -> PrintUnqualified -> SDoc -> String Source #
Allows caller to specify the PrintUnqualified to use
showSDocDump :: SDocContext -> SDoc -> String Source #
pprDebugAndThen :: SDocContext -> (String -> a) -> SDoc -> SDoc -> a Source #
printForUser :: DynFlags -> Handle -> PrintUnqualified -> Depth -> SDoc -> IO () Source #
printForC :: DynFlags -> Handle -> SDoc -> IO () Source #
Like printSDocLn
but specialized with LeftMode
and
. This is typically used to output C-- code.PprCode
CStyle
Trace
warnPprTrace :: HasCallStack => Bool -> String -> Int -> SDoc -> a -> a Source #
Just warn about an assertion failure, recording the given file and line number. Should typically be accessed with the WARN macros
pprTraceWithFlags :: DynFlags -> String -> SDoc -> a -> a Source #
If debug output is on, show some SDoc
on the screen
pprTraceDebug :: String -> SDoc -> a -> a Source #
pprTraceIt :: Outputable a => String -> a -> a Source #
pprTraceIt desc x
is equivalent to pprTrace desc (ppr x) x
pprSTrace :: HasCallStack => SDoc -> a -> a Source #
If debug output is on, show some SDoc
on the screen along
with a call stack when available.
pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a Source #
pprTraceException desc x action
runs action, printing a message
if it throws an exception.