module GHC.Driver.Ppr
( showSDoc
, showSDocUnsafe
, showSDocForUser
, showSDocDebug
, showSDocDump
, showPpr
, showPprUnsafe
, pprDebugAndThen
, printForUser
, printForC
, warnPprTrace
, pprTrace
, pprTraceWithFlags
, pprTraceM
, pprTraceDebug
, pprTraceIt
, pprSTrace
, pprTraceException
)
where
import GHC.Prelude
import GHC.Driver.Session
import GHC.Unit.State
import GHC.Utils.Exception
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.GlobalVars
import GHC.Utils.Ppr ( Mode(..) )
import System.IO ( Handle )
import Control.Monad.IO.Class
showSDoc :: DynFlags -> SDoc -> String
showSDoc dflags sdoc = renderWithContext (initSDocContext dflags defaultUserStyle) sdoc
showSDocUnsafe :: SDoc -> String
showSDocUnsafe sdoc = renderWithContext defaultSDocContext sdoc
showPpr :: Outputable a => DynFlags -> a -> String
showPpr dflags thing = showSDoc dflags (ppr thing)
showPprUnsafe :: Outputable a => a -> String
showPprUnsafe a = renderWithContext defaultSDocContext (ppr a)
showSDocForUser :: DynFlags -> UnitState -> PrintUnqualified -> SDoc -> String
showSDocForUser dflags unit_state unqual doc = renderWithContext (initSDocContext dflags sty) doc'
where
sty = mkUserStyle unqual AllTheWay
doc' = pprWithUnitState unit_state doc
showSDocDump :: SDocContext -> SDoc -> String
showSDocDump ctx d = renderWithContext ctx (withPprStyle defaultDumpStyle d)
showSDocDebug :: DynFlags -> SDoc -> String
showSDocDebug dflags d = renderWithContext ctx d
where
ctx = (initSDocContext dflags defaultDumpStyle)
{ sdocPprDebug = True
}
printForUser :: DynFlags -> Handle -> PrintUnqualified -> Depth -> SDoc -> IO ()
printForUser dflags handle unqual depth doc
= printSDocLn ctx (PageMode False) handle doc
where ctx = initSDocContext dflags (mkUserStyle unqual depth)
printForC :: DynFlags -> Handle -> SDoc -> IO ()
printForC dflags handle doc =
printSDocLn ctx LeftMode handle doc
where ctx = initSDocContext dflags (PprCode CStyle)
pprDebugAndThen :: SDocContext -> (String -> a) -> SDoc -> SDoc -> a
pprDebugAndThen ctx cont heading pretty_msg
= cont (showSDocDump ctx doc)
where
doc = sep [heading, nest 2 pretty_msg]
pprTraceWithFlags :: DynFlags -> String -> SDoc -> a -> a
pprTraceWithFlags dflags str doc x
| hasNoDebugOutput dflags = x
| otherwise = pprDebugAndThen (initSDocContext dflags defaultDumpStyle)
trace (text str) doc x
pprTrace :: String -> SDoc -> a -> a
pprTrace str doc x
| unsafeHasNoDebugOutput = x
| otherwise = pprDebugAndThen defaultSDocContext trace (text str) doc x
pprTraceM :: Applicative f => String -> SDoc -> f ()
pprTraceM str doc = pprTrace str doc (pure ())
pprTraceDebug :: String -> SDoc -> a -> a
pprTraceDebug str doc x
| debugIsOn && unsafeHasPprDebug = pprTrace str doc x
| otherwise = x
pprTraceWith :: String -> (a -> SDoc) -> a -> a
pprTraceWith desc f x = pprTrace desc (f x) x
pprTraceIt :: Outputable a => String -> a -> a
pprTraceIt desc x = pprTraceWith desc ppr x
pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a
pprTraceException heading doc =
handleGhcException $ \exc -> liftIO $ do
putStrLn $ showSDocDump defaultSDocContext (sep [text heading, nest 2 doc])
throwGhcExceptionIO exc
pprSTrace :: HasCallStack => SDoc -> a -> a
pprSTrace doc = pprTrace "" (doc $$ callStackDoc)
warnPprTrace :: HasCallStack => Bool -> String -> Int -> SDoc -> a -> a
warnPprTrace _ _ _ _ x | not debugIsOn = x
warnPprTrace _ _file _line _msg x
| unsafeHasNoDebugOutput = x
warnPprTrace False _file _line _msg x = x
warnPprTrace True file line msg x
= pprDebugAndThen defaultSDocContext trace heading
(msg $$ callStackDoc )
x
where
heading = hsep [text "WARNING: file", text file <> comma, text "line", int line]