{-# LANGUAGE BangPatterns    #-}
{-# LANGUAGE CPP             #-}
{-# LANGUAGE RankNTypes      #-}
{-# LANGUAGE ViewPatterns    #-}
module GHC.Utils.Error (
        
        Validity(..), andValid, allValid, isValid, getInvalids, orValid,
        Severity(..),
        
        WarnMsg,
        MsgEnvelope(..),
        SDoc,
        DecoratedSDoc(unDecorated),
        Messages, ErrorMessages, WarningMessages,
        unionMessages,
        errorsFound, isEmptyMessages,
        
        pprMessageBag, pprMsgEnvelopeBagWithLoc,
        pprLocMsgEnvelope,
        formatBulleted,
        
        emptyMessages, mkDecorated, mkLocMessage, mkLocMessageAnn, makeIntoWarning,
        mkMsgEnvelope, mkPlainMsgEnvelope, mkErr, mkLongMsgEnvelope, mkWarnMsg,
        mkPlainWarnMsg,
        mkLongWarnMsg,
        
        doIfSet, doIfSet_dyn,
        getCaretDiagnostic,
        
        putMsg, printInfoForUser, printOutputForUser,
        logInfo, logOutput,
        errorMsg, warningMsg,
        fatalErrorMsg, fatalErrorMsg'',
        compilationProgressMsg,
        showPass,
        withTiming, withTimingSilent,
        debugTraceMsg,
        ghcExit,
        prettyPrintGhcErrors,
        traceCmd,
        sortMsgBag
    ) where
#include "HsVersions.h"
import GHC.Prelude
import GHC.Driver.Session
import GHC.Driver.Ppr
import GHC.Data.Bag
import GHC.Utils.Exception
import GHC.Utils.Outputable as Outputable
import GHC.Utils.Panic
import GHC.Utils.Logger
import GHC.Types.Error
import GHC.Types.SrcLoc as SrcLoc
import System.Exit      ( ExitCode(..), exitWith )
import Data.List        ( sortBy )
import Data.Maybe       ( fromMaybe )
import Data.Function
import Debug.Trace
import Control.Monad
import Control.Monad.IO.Class
import Control.Monad.Catch as MC (handle)
import GHC.Conc         ( getAllocationCounter )
import System.CPUTime
data Validity
  = IsValid            
  | NotValid SDoc    
isValid :: Validity -> Bool
isValid :: Validity -> Bool
isValid Validity
IsValid       = Bool
True
isValid (NotValid {}) = Bool
False
andValid :: Validity -> Validity -> Validity
andValid :: Validity -> Validity -> Validity
andValid Validity
IsValid Validity
v = Validity
v
andValid Validity
v Validity
_       = Validity
v
allValid :: [Validity] -> Validity
allValid :: [Validity] -> Validity
allValid []       = Validity
IsValid
allValid (Validity
v : [Validity]
vs) = Validity
v Validity -> Validity -> Validity
`andValid` [Validity] -> Validity
allValid [Validity]
vs
getInvalids :: [Validity] -> [SDoc]
getInvalids :: [Validity] -> [SDoc]
getInvalids [Validity]
vs = [SDoc
d | NotValid SDoc
d <- [Validity]
vs]
orValid :: Validity -> Validity -> Validity
orValid :: Validity -> Validity -> Validity
orValid Validity
IsValid Validity
_ = Validity
IsValid
orValid Validity
_       Validity
v = Validity
v
formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc
formatBulleted :: SDocContext -> DecoratedSDoc -> SDoc
formatBulleted SDocContext
ctx (DecoratedSDoc -> [SDoc]
unDecorated -> [SDoc]
docs)
  = case [SDoc]
msgs of
        []    -> SDoc
Outputable.empty
        [SDoc
msg] -> SDoc
msg
        [SDoc]
_     -> [SDoc] -> SDoc
vcat ([SDoc] -> SDoc) -> [SDoc] -> SDoc
forall a b. (a -> b) -> a -> b
$ (SDoc -> SDoc) -> [SDoc] -> [SDoc]
forall a b. (a -> b) -> [a] -> [b]
map SDoc -> SDoc
starred [SDoc]
msgs
    where
    msgs :: [SDoc]
msgs    = (SDoc -> Bool) -> [SDoc] -> [SDoc]
forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not (Bool -> Bool) -> (SDoc -> Bool) -> SDoc -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SDocContext -> SDoc -> Bool
Outputable.isEmpty SDocContext
ctx) [SDoc]
docs
    starred :: SDoc -> SDoc
starred = (SDoc
bulletSDoc -> SDoc -> SDoc
<+>)
pprMsgEnvelopeBagWithLoc :: Bag (MsgEnvelope DecoratedSDoc) -> [SDoc]
pprMsgEnvelopeBagWithLoc :: Bag (MsgEnvelope DecoratedSDoc) -> [SDoc]
pprMsgEnvelopeBagWithLoc Bag (MsgEnvelope DecoratedSDoc)
bag = [ MsgEnvelope DecoratedSDoc -> SDoc
forall e. RenderableDiagnostic e => MsgEnvelope e -> SDoc
pprLocMsgEnvelope MsgEnvelope DecoratedSDoc
item | MsgEnvelope DecoratedSDoc
item <- Maybe DynFlags
-> Bag (MsgEnvelope DecoratedSDoc) -> [MsgEnvelope DecoratedSDoc]
forall e. Maybe DynFlags -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
sortMsgBag Maybe DynFlags
forall a. Maybe a
Nothing Bag (MsgEnvelope DecoratedSDoc)
bag ]
pprLocMsgEnvelope :: RenderableDiagnostic e => MsgEnvelope e -> SDoc
pprLocMsgEnvelope :: forall e. RenderableDiagnostic e => MsgEnvelope e -> SDoc
pprLocMsgEnvelope (MsgEnvelope { errMsgSpan :: forall e. MsgEnvelope e -> SrcSpan
errMsgSpan      = SrcSpan
s
                               , errMsgDiagnostic :: forall e. MsgEnvelope e -> e
errMsgDiagnostic = e
e
                               , errMsgSeverity :: forall e. MsgEnvelope e -> Severity
errMsgSeverity  = Severity
sev
                               , errMsgContext :: forall e. MsgEnvelope e -> PrintUnqualified
errMsgContext   = PrintUnqualified
unqual })
  = (SDocContext -> SDoc) -> SDoc
sdocWithContext ((SDocContext -> SDoc) -> SDoc) -> (SDocContext -> SDoc) -> SDoc
forall a b. (a -> b) -> a -> b
$ \SDocContext
ctx ->
    PrintUnqualified -> SDoc -> SDoc
withErrStyle PrintUnqualified
unqual (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ Severity -> SrcSpan -> SDoc -> SDoc
mkLocMessage Severity
sev SrcSpan
s (SDocContext -> DecoratedSDoc -> SDoc
formatBulleted SDocContext
ctx (DecoratedSDoc -> SDoc) -> DecoratedSDoc -> SDoc
forall a b. (a -> b) -> a -> b
$ e -> DecoratedSDoc
forall a. RenderableDiagnostic a => a -> DecoratedSDoc
renderDiagnostic e
e)
sortMsgBag :: Maybe DynFlags -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
sortMsgBag :: forall e. Maybe DynFlags -> Bag (MsgEnvelope e) -> [MsgEnvelope e]
sortMsgBag Maybe DynFlags
dflags = [MsgEnvelope e] -> [MsgEnvelope e]
maybeLimit ([MsgEnvelope e] -> [MsgEnvelope e])
-> (Bag (MsgEnvelope e) -> [MsgEnvelope e])
-> Bag (MsgEnvelope e)
-> [MsgEnvelope e]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (MsgEnvelope e -> MsgEnvelope e -> Ordering)
-> [MsgEnvelope e] -> [MsgEnvelope e]
forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (SrcSpan -> SrcSpan -> Ordering
cmp (SrcSpan -> SrcSpan -> Ordering)
-> (MsgEnvelope e -> SrcSpan)
-> MsgEnvelope e
-> MsgEnvelope e
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` MsgEnvelope e -> SrcSpan
forall e. MsgEnvelope e -> SrcSpan
errMsgSpan) ([MsgEnvelope e] -> [MsgEnvelope e])
-> (Bag (MsgEnvelope e) -> [MsgEnvelope e])
-> Bag (MsgEnvelope e)
-> [MsgEnvelope e]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bag (MsgEnvelope e) -> [MsgEnvelope e]
forall a. Bag a -> [a]
bagToList
  where cmp :: SrcSpan -> SrcSpan -> Ordering
cmp
          | Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False ((DynFlags -> Bool) -> Maybe DynFlags -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DynFlags -> Bool
reverseErrors Maybe DynFlags
dflags) = SrcSpan -> SrcSpan -> Ordering
SrcLoc.rightmost_smallest
          | Bool
otherwise                                   = SrcSpan -> SrcSpan -> Ordering
SrcLoc.leftmost_smallest
        maybeLimit :: [MsgEnvelope e] -> [MsgEnvelope e]
maybeLimit = case Maybe (Maybe Int) -> Maybe Int
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join ((DynFlags -> Maybe Int) -> Maybe DynFlags -> Maybe (Maybe Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap DynFlags -> Maybe Int
maxErrors Maybe DynFlags
dflags) of
          Maybe Int
Nothing        -> [MsgEnvelope e] -> [MsgEnvelope e]
forall a. a -> a
id
          Just Int
err_limit -> Int -> [MsgEnvelope e] -> [MsgEnvelope e]
forall a. Int -> [a] -> [a]
take Int
err_limit
ghcExit :: Logger -> DynFlags -> Int -> IO ()
ghcExit :: Logger -> DynFlags -> Int -> IO ()
ghcExit Logger
logger DynFlags
dflags Int
val
  | Int
val Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0  = ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith ExitCode
ExitSuccess
  | Bool
otherwise = do Logger -> DynFlags -> SDoc -> IO ()
errorMsg Logger
logger DynFlags
dflags (String -> SDoc
text String
"\nCompilation had errors\n\n")
                   ExitCode -> IO ()
forall a. ExitCode -> IO a
exitWith (Int -> ExitCode
ExitFailure Int
val)
doIfSet :: Bool -> IO () -> IO ()
doIfSet :: Bool -> IO () -> IO ()
doIfSet Bool
flag IO ()
action | Bool
flag      = IO ()
action
                    | Bool
otherwise = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO()
doIfSet_dyn :: DynFlags -> GeneralFlag -> IO () -> IO ()
doIfSet_dyn DynFlags
dflags GeneralFlag
flag IO ()
action | GeneralFlag -> DynFlags -> Bool
gopt GeneralFlag
flag DynFlags
dflags = IO ()
action
                               | Bool
otherwise        = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
ifVerbose :: DynFlags -> Int -> IO () -> IO ()
ifVerbose :: DynFlags -> Int -> IO () -> IO ()
ifVerbose DynFlags
dflags Int
val IO ()
act
  | DynFlags -> Int
verbosity DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
val = IO ()
act
  | Bool
otherwise               = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
{-# INLINE ifVerbose #-}  
errorMsg :: Logger -> DynFlags -> SDoc -> IO ()
errorMsg :: Logger -> DynFlags -> SDoc -> IO ()
errorMsg Logger
logger DynFlags
dflags SDoc
msg
   = Logger -> LogAction
putLogMsg Logger
logger DynFlags
dflags WarnReason
NoReason Severity
SevError SrcSpan
noSrcSpan (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultErrStyle SDoc
msg
warningMsg :: Logger -> DynFlags -> SDoc -> IO ()
warningMsg :: Logger -> DynFlags -> SDoc -> IO ()
warningMsg Logger
logger DynFlags
dflags SDoc
msg
   = Logger -> LogAction
putLogMsg Logger
logger DynFlags
dflags WarnReason
NoReason Severity
SevWarning SrcSpan
noSrcSpan (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultErrStyle SDoc
msg
fatalErrorMsg :: Logger -> DynFlags -> SDoc -> IO ()
fatalErrorMsg :: Logger -> DynFlags -> SDoc -> IO ()
fatalErrorMsg Logger
logger DynFlags
dflags SDoc
msg =
    Logger -> LogAction
putLogMsg Logger
logger DynFlags
dflags WarnReason
NoReason Severity
SevFatal SrcSpan
noSrcSpan (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultErrStyle SDoc
msg
fatalErrorMsg'' :: FatalMessager -> String -> IO ()
fatalErrorMsg'' :: FatalMessager -> FatalMessager
fatalErrorMsg'' FatalMessager
fm String
msg = FatalMessager
fm String
msg
compilationProgressMsg :: Logger -> DynFlags -> SDoc -> IO ()
compilationProgressMsg :: Logger -> DynFlags -> SDoc -> IO ()
compilationProgressMsg Logger
logger DynFlags
dflags SDoc
msg = do
    let str :: String
str = DynFlags -> SDoc -> String
showSDoc DynFlags
dflags SDoc
msg
    FatalMessager
traceEventIO FatalMessager -> FatalMessager
forall a b. (a -> b) -> a -> b
$ String
"GHC progress: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
str
    DynFlags -> Int -> IO () -> IO ()
ifVerbose DynFlags
dflags Int
1 (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
        Logger -> DynFlags -> SDoc -> IO ()
logOutput Logger
logger DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle SDoc
msg
showPass :: Logger -> DynFlags -> String -> IO ()
showPass :: Logger -> DynFlags -> FatalMessager
showPass Logger
logger DynFlags
dflags String
what
  = DynFlags -> Int -> IO () -> IO ()
ifVerbose DynFlags
dflags Int
2 (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
    Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle (String -> SDoc
text String
"***" SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
what SDoc -> SDoc -> SDoc
<> SDoc
colon)
data PrintTimings = PrintTimings | DontPrintTimings
  deriving (PrintTimings -> PrintTimings -> Bool
(PrintTimings -> PrintTimings -> Bool)
-> (PrintTimings -> PrintTimings -> Bool) -> Eq PrintTimings
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PrintTimings -> PrintTimings -> Bool
$c/= :: PrintTimings -> PrintTimings -> Bool
== :: PrintTimings -> PrintTimings -> Bool
$c== :: PrintTimings -> PrintTimings -> Bool
Eq, Int -> PrintTimings -> String -> String
[PrintTimings] -> String -> String
PrintTimings -> String
(Int -> PrintTimings -> String -> String)
-> (PrintTimings -> String)
-> ([PrintTimings] -> String -> String)
-> Show PrintTimings
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PrintTimings] -> String -> String
$cshowList :: [PrintTimings] -> String -> String
show :: PrintTimings -> String
$cshow :: PrintTimings -> String
showsPrec :: Int -> PrintTimings -> String -> String
$cshowsPrec :: Int -> PrintTimings -> String -> String
Show)
withTiming :: MonadIO m
           => Logger
           -> DynFlags     
           -> SDoc         
           -> (a -> ())    
                           
           -> m a          
           -> m a
withTiming :: forall (m :: * -> *) a.
MonadIO m =>
Logger -> DynFlags -> SDoc -> (a -> ()) -> m a -> m a
withTiming Logger
logger DynFlags
dflags SDoc
what a -> ()
force m a
action =
  Logger
-> DynFlags -> SDoc -> (a -> ()) -> PrintTimings -> m a -> m a
forall (m :: * -> *) a.
MonadIO m =>
Logger
-> DynFlags -> SDoc -> (a -> ()) -> PrintTimings -> m a -> m a
withTiming' Logger
logger DynFlags
dflags SDoc
what a -> ()
force PrintTimings
PrintTimings m a
action
withTimingSilent
  :: MonadIO m
  => Logger
  -> DynFlags   
  -> SDoc       
  -> (a -> ())  
                
  -> m a        
  -> m a
withTimingSilent :: forall (m :: * -> *) a.
MonadIO m =>
Logger -> DynFlags -> SDoc -> (a -> ()) -> m a -> m a
withTimingSilent Logger
logger DynFlags
dflags SDoc
what a -> ()
force m a
action =
  Logger
-> DynFlags -> SDoc -> (a -> ()) -> PrintTimings -> m a -> m a
forall (m :: * -> *) a.
MonadIO m =>
Logger
-> DynFlags -> SDoc -> (a -> ()) -> PrintTimings -> m a -> m a
withTiming' Logger
logger DynFlags
dflags SDoc
what a -> ()
force PrintTimings
DontPrintTimings m a
action
withTiming' :: MonadIO m
            => Logger
            -> DynFlags   
            -> SDoc         
            -> (a -> ())    
                            
            -> PrintTimings 
            -> m a          
            -> m a
withTiming' :: forall (m :: * -> *) a.
MonadIO m =>
Logger
-> DynFlags -> SDoc -> (a -> ()) -> PrintTimings -> m a -> m a
withTiming' Logger
logger DynFlags
dflags SDoc
what a -> ()
force_result PrintTimings
prtimings m a
action
  = if DynFlags -> Int
verbosity DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 Bool -> Bool -> Bool
|| DumpFlag -> DynFlags -> Bool
dopt DumpFlag
Opt_D_dump_timings DynFlags
dflags
    then do IO () -> m ()
whenPrintTimings (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
              Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle (SDoc -> SDoc) -> SDoc -> SDoc
forall a b. (a -> b) -> a -> b
$
                String -> SDoc
text String
"***" SDoc -> SDoc -> SDoc
<+> SDoc
what SDoc -> SDoc -> SDoc
<> SDoc
colon
            let ctx :: SDocContext
ctx = DynFlags -> SDocContext
initDefaultSDocContext DynFlags
dflags
            Int64
alloc0 <- IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Int64
getAllocationCounter
            Integer
start <- IO Integer -> m Integer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Integer
getCPUTime
            SDocContext -> SDoc -> m ()
eventBegins SDocContext
ctx SDoc
what
            Int64 -> m ()
forall {m :: * -> *} {a}. (MonadIO m, Show a) => a -> m ()
recordAllocs Int64
alloc0
            !a
r <- m a
action
            () <- () -> m ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure (() -> m ()) -> () -> m ()
forall a b. (a -> b) -> a -> b
$ a -> ()
force_result a
r
            SDocContext -> SDoc -> m ()
eventEnds SDocContext
ctx SDoc
what
            Integer
end <- IO Integer -> m Integer
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Integer
getCPUTime
            Int64
alloc1 <- IO Int64 -> m Int64
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO IO Int64
getAllocationCounter
            Int64 -> m ()
forall {m :: * -> *} {a}. (MonadIO m, Show a) => a -> m ()
recordAllocs Int64
alloc1
            
            let alloc :: Int64
alloc = Int64
alloc0 Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
alloc1
                time :: Double
time = Integer -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac (Integer
end Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
- Integer
start) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
1e-9
            Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (DynFlags -> Int
verbosity DynFlags
dflags Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
2 Bool -> Bool -> Bool
&& PrintTimings
prtimings PrintTimings -> PrintTimings -> Bool
forall a. Eq a => a -> a -> Bool
== PrintTimings
PrintTimings)
                (m () -> m ()) -> m () -> m ()
forall a b. (a -> b) -> a -> b
$ IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle
                    (String -> SDoc
text String
"!!!" SDoc -> SDoc -> SDoc
<+> SDoc
what SDoc -> SDoc -> SDoc
<> SDoc
colon SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"finished in"
                     SDoc -> SDoc -> SDoc
<+> Int -> Double -> SDoc
doublePrec Int
2 Double
time
                     SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"milliseconds"
                     SDoc -> SDoc -> SDoc
<> SDoc
comma
                     SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"allocated"
                     SDoc -> SDoc -> SDoc
<+> Int -> Double -> SDoc
doublePrec Int
3 (Int64 -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac Int64
alloc Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1024 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
1024)
                     SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
"megabytes")
            IO () -> m ()
whenPrintTimings (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$
                Logger
-> DynFlags -> DumpFlag -> String -> DumpFormat -> SDoc -> IO ()
dumpIfSet_dyn Logger
logger DynFlags
dflags DumpFlag
Opt_D_dump_timings String
"" DumpFormat
FormatText
                    (SDoc -> IO ()) -> SDoc -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text (String -> SDoc) -> String -> SDoc
forall a b. (a -> b) -> a -> b
$ SDocContext -> SDoc -> String
showSDocOneLine SDocContext
ctx
                    (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$ [SDoc] -> SDoc
hsep [ SDoc
what SDoc -> SDoc -> SDoc
<> SDoc
colon
                           , String -> SDoc
text String
"alloc=" SDoc -> SDoc -> SDoc
<> Int64 -> SDoc
forall a. Outputable a => a -> SDoc
ppr Int64
alloc
                           , String -> SDoc
text String
"time=" SDoc -> SDoc -> SDoc
<> Int -> Double -> SDoc
doublePrec Int
3 Double
time
                           ]
            a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
r
     else m a
action
    where whenPrintTimings :: IO () -> m ()
whenPrintTimings = IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> (IO () -> IO ()) -> IO () -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (PrintTimings
prtimings PrintTimings -> PrintTimings -> Bool
forall a. Eq a => a -> a -> Bool
== PrintTimings
PrintTimings)
          recordAllocs :: a -> m ()
recordAllocs a
alloc =
            IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FatalMessager
traceMarkerIO FatalMessager -> FatalMessager
forall a b. (a -> b) -> a -> b
$ String
"GHC:allocs:" String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
alloc
          eventBegins :: SDocContext -> SDoc -> m ()
eventBegins SDocContext
ctx SDoc
w = do
            let doc :: String
doc = SDocContext -> SDoc -> String
eventBeginsDoc SDocContext
ctx SDoc
w
            IO () -> m ()
whenPrintTimings (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FatalMessager
traceMarkerIO String
doc
            IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FatalMessager
traceEventIO String
doc
          eventEnds :: SDocContext -> SDoc -> m ()
eventEnds SDocContext
ctx SDoc
w = do
            let doc :: String
doc = SDocContext -> SDoc -> String
eventEndsDoc SDocContext
ctx SDoc
w
            IO () -> m ()
whenPrintTimings (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FatalMessager
traceMarkerIO String
doc
            IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ FatalMessager
traceEventIO String
doc
          eventBeginsDoc :: SDocContext -> SDoc -> String
eventBeginsDoc SDocContext
ctx SDoc
w = SDocContext -> SDoc -> String
showSDocOneLine SDocContext
ctx (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"GHC:started:" SDoc -> SDoc -> SDoc
<+> SDoc
w
          eventEndsDoc :: SDocContext -> SDoc -> String
eventEndsDoc   SDocContext
ctx SDoc
w = SDocContext -> SDoc -> String
showSDocOneLine SDocContext
ctx (SDoc -> String) -> SDoc -> String
forall a b. (a -> b) -> a -> b
$ String -> SDoc
text String
"GHC:finished:" SDoc -> SDoc -> SDoc
<+> SDoc
w
debugTraceMsg :: Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg :: Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
val SDoc
msg =
   DynFlags -> Int -> IO () -> IO ()
ifVerbose DynFlags
dflags Int
val (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
      Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags (PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultDumpStyle SDoc
msg)
{-# INLINE debugTraceMsg #-}  
putMsg :: Logger -> DynFlags -> SDoc -> IO ()
putMsg :: Logger -> DynFlags -> SDoc -> IO ()
putMsg Logger
logger DynFlags
dflags SDoc
msg = Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags (PprStyle -> SDoc -> SDoc
withPprStyle PprStyle
defaultUserStyle SDoc
msg)
printInfoForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
printInfoForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
printInfoForUser Logger
logger DynFlags
dflags PrintUnqualified
print_unqual SDoc
msg
  = Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags (PrintUnqualified -> Depth -> SDoc -> SDoc
withUserStyle PrintUnqualified
print_unqual Depth
AllTheWay SDoc
msg)
printOutputForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
printOutputForUser :: Logger -> DynFlags -> PrintUnqualified -> SDoc -> IO ()
printOutputForUser Logger
logger DynFlags
dflags PrintUnqualified
print_unqual SDoc
msg
  = Logger -> DynFlags -> SDoc -> IO ()
logOutput Logger
logger DynFlags
dflags (PrintUnqualified -> Depth -> SDoc -> SDoc
withUserStyle PrintUnqualified
print_unqual Depth
AllTheWay SDoc
msg)
logInfo :: Logger -> DynFlags -> SDoc -> IO ()
logInfo :: Logger -> DynFlags -> SDoc -> IO ()
logInfo Logger
logger DynFlags
dflags SDoc
msg
  = Logger -> LogAction
putLogMsg Logger
logger DynFlags
dflags WarnReason
NoReason Severity
SevInfo SrcSpan
noSrcSpan SDoc
msg
logOutput :: Logger -> DynFlags -> SDoc -> IO ()
logOutput :: Logger -> DynFlags -> SDoc -> IO ()
logOutput Logger
logger DynFlags
dflags SDoc
msg
  = Logger -> LogAction
putLogMsg Logger
logger DynFlags
dflags WarnReason
NoReason Severity
SevOutput SrcSpan
noSrcSpan SDoc
msg
prettyPrintGhcErrors :: ExceptionMonad m => DynFlags -> m a -> m a
prettyPrintGhcErrors :: forall (m :: * -> *) a. ExceptionMonad m => DynFlags -> m a -> m a
prettyPrintGhcErrors DynFlags
dflags
    = (GhcException -> m a) -> m a -> m a
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
MC.handle ((GhcException -> m a) -> m a -> m a)
-> (GhcException -> m a) -> m a -> m a
forall a b. (a -> b) -> a -> b
$ \GhcException
e -> case GhcException
e of
                      PprPanic String
str SDoc
doc ->
                          SDocContext -> (String -> m a) -> SDoc -> SDoc -> m a
forall a. SDocContext -> (String -> a) -> SDoc -> SDoc -> a
pprDebugAndThen SDocContext
ctx String -> m a
forall a. String -> a
panic (String -> SDoc
text String
str) SDoc
doc
                      PprSorry String
str SDoc
doc ->
                          SDocContext -> (String -> m a) -> SDoc -> SDoc -> m a
forall a. SDocContext -> (String -> a) -> SDoc -> SDoc -> a
pprDebugAndThen SDocContext
ctx String -> m a
forall a. String -> a
sorry (String -> SDoc
text String
str) SDoc
doc
                      PprProgramError String
str SDoc
doc ->
                          SDocContext -> (String -> m a) -> SDoc -> SDoc -> m a
forall a. SDocContext -> (String -> a) -> SDoc -> SDoc -> a
pprDebugAndThen SDocContext
ctx String -> m a
forall a. String -> a
pgmError (String -> SDoc
text String
str) SDoc
doc
                      GhcException
_ ->
                          IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ GhcException -> IO a
forall e a. Exception e => e -> IO a
throwIO GhcException
e
      where
         ctx :: SDocContext
ctx = DynFlags -> PprStyle -> SDocContext
initSDocContext DynFlags
dflags PprStyle
defaultUserStyle
traceCmd :: Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd :: forall a. Logger -> DynFlags -> String -> String -> IO a -> IO a
traceCmd Logger
logger DynFlags
dflags String
phase_name String
cmd_line IO a
action
 = do   { let verb :: Int
verb = DynFlags -> Int
verbosity DynFlags
dflags
        ; Logger -> DynFlags -> FatalMessager
showPass Logger
logger DynFlags
dflags String
phase_name
        ; Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
3 (String -> SDoc
text String
cmd_line)
        ; case DynFlags -> FlushErr
flushErr DynFlags
dflags of
              FlushErr IO ()
io -> IO ()
io
           
        ; IO a
action IO a -> (IOException -> IO a) -> IO a
forall a. IO a -> (IOException -> IO a) -> IO a
`catchIO` Int -> IOException -> IO a
handle_exn Int
verb
        }
  where
    handle_exn :: Int -> IOException -> IO a
handle_exn Int
_verb IOException
exn = do { Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
2 (Char -> SDoc
char Char
'\n')
                              ; Logger -> DynFlags -> Int -> SDoc -> IO ()
debugTraceMsg Logger
logger DynFlags
dflags Int
2
                                (String -> SDoc
text String
"Failed:"
                                 SDoc -> SDoc -> SDoc
<+> String -> SDoc
text String
cmd_line
                                 SDoc -> SDoc -> SDoc
<+> String -> SDoc
text (IOException -> String
forall a. Show a => a -> String
show IOException
exn))
                              ; GhcException -> IO a
forall a. GhcException -> IO a
throwGhcExceptionIO (String -> GhcException
ProgramError (IOException -> String
forall a. Show a => a -> String
show IOException
exn))}