summaryrefslogtreecommitdiff
path: root/compiler/GHC/Driver
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/GHC/Driver')
-rw-r--r--compiler/GHC/Driver/CmdLine.hs3
-rw-r--r--compiler/GHC/Driver/Env.hs2
-rw-r--r--compiler/GHC/Driver/Main.hs5
-rw-r--r--compiler/GHC/Driver/Make.hs14
-rw-r--r--compiler/GHC/Driver/MakeFile.hs3
-rw-r--r--compiler/GHC/Driver/Pipeline.hs7
-rw-r--r--compiler/GHC/Driver/Ppr.hs19
-rw-r--r--compiler/GHC/Driver/Ppr.hs-boot2
-rw-r--r--compiler/GHC/Driver/Session.hs1
9 files changed, 30 insertions, 26 deletions
diff --git a/compiler/GHC/Driver/CmdLine.hs b/compiler/GHC/Driver/CmdLine.hs
index 568e83e795..1283723e05 100644
--- a/compiler/GHC/Driver/CmdLine.hs
+++ b/compiler/GHC/Driver/CmdLine.hs
@@ -30,6 +30,7 @@ import GHC.Prelude
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
+import GHC.Utils.Panic.Plain
import GHC.Data.Bag
import GHC.Types.SrcLoc
import GHC.Utils.Json
@@ -224,7 +225,7 @@ processOneArg opt_kind rest arg args
= let dash_arg = '-' : arg
rest_no_eq = dropEq rest
in case opt_kind of
- NoArg a -> ASSERT(null rest) Right (a, args)
+ NoArg a -> assert (null rest) Right (a, args)
HasArg f | notNull rest_no_eq -> Right (f rest_no_eq, args)
| otherwise -> case args of
diff --git a/compiler/GHC/Driver/Env.hs b/compiler/GHC/Driver/Env.hs
index 79d9e47088..3d59e72468 100644
--- a/compiler/GHC/Driver/Env.hs
+++ b/compiler/GHC/Driver/Env.hs
@@ -263,7 +263,7 @@ lookupType hsc_env name = do
let pte = eps_PTE eps
hpt = hsc_HPT hsc_env
- mod = ASSERT2( isExternalName name, ppr name )
+ mod = assertPpr (isExternalName name) (ppr name) $
if isHoleName name
then mkHomeModule (hsc_home_unit hsc_env) (moduleName (nameModule name))
else nameModule name
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index 3f4844b57c..4768c17f9f 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -207,6 +207,7 @@ import GHC.Types.HpcInfo
import GHC.Utils.Fingerprint ( Fingerprint )
import GHC.Utils.Panic
+import GHC.Utils.Panic.Plain
import GHC.Utils.Error
import GHC.Utils.Outputable
import GHC.Utils.Misc
@@ -333,7 +334,7 @@ ioMsgMaybe ioA = do
logDiagnostics warns
case mb_r of
Nothing -> throwErrors errs
- Just r -> ASSERT( isEmptyMessages errs ) return r
+ Just r -> assert (isEmptyMessages errs ) return r
-- | like ioMsgMaybe, except that we ignore error messages and return
-- 'Nothing' instead.
@@ -540,7 +541,7 @@ hsc_typecheck keep_rn mod_summary mb_rdr_module = do
src_filename = ms_hspp_file mod_summary
real_loc = realSrcLocSpan $ mkRealSrcLoc (mkFastString src_filename) 1 1
keep_rn' = gopt Opt_WriteHie dflags || keep_rn
- MASSERT( isHomeModule home_unit outer_mod )
+ massert (isHomeModule home_unit outer_mod)
tc_result <- if hsc_src == HsigFile && not (isHoleModule inner_mod)
then ioMsgMaybe $ hoistTcRnMessage $ tcRnInstantiateSignature hsc_env outer_mod' real_loc
else
diff --git a/compiler/GHC/Driver/Make.hs b/compiler/GHC/Driver/Make.hs
index 654ba697a1..4181e13ab5 100644
--- a/compiler/GHC/Driver/Make.hs
+++ b/compiler/GHC/Driver/Make.hs
@@ -82,6 +82,7 @@ import GHC.Utils.Exception ( tryIO, AsyncException(..), evaluate )
import GHC.Utils.Monad ( allM )
import GHC.Utils.Outputable
import GHC.Utils.Panic
+import GHC.Utils.Panic.Plain
import GHC.Utils.Misc
import GHC.Utils.Error
import GHC.Utils.Logger
@@ -425,7 +426,7 @@ load' how_much mHscMessage mod_graph = do
-- files without corresponding hs files.
-- bad_boot_mods = [s | s <- mod_graph, isBootSummary s,
-- not (ms_mod_name s `elem` all_home_mods)]
- -- ASSERT( null bad_boot_mods ) return ()
+ -- assert (null bad_boot_mods ) return ()
-- check that the module given in HowMuch actually exists, otherwise
-- topSortModuleGraph will bomb later.
@@ -519,8 +520,9 @@ load' how_much mHscMessage mod_graph = do
-- is stable).
partial_mg
| LoadDependenciesOf _mod <- how_much
- = ASSERT( case last partial_mg0 of
- AcyclicSCC (ModuleNode (ExtendedModSummary ms _)) -> ms_mod_name ms == _mod; _ -> False )
+ = assert (case last partial_mg0 of
+ AcyclicSCC (ModuleNode (ExtendedModSummary ms _)) -> ms_mod_name ms == _mod
+ _ -> False) $
List.init partial_mg0
| otherwise
= partial_mg0
@@ -658,7 +660,7 @@ load' how_much mHscMessage mod_graph = do
|| allHpt (isJust.hm_linkable)
(filterHpt ((== HsSrcFile).mi_hsc_src.hm_iface)
hpt5)
- ASSERT( just_linkables ) do
+ assert just_linkables $ do
-- Link everything together
hsc_env <- getSession
@@ -1765,7 +1767,7 @@ upsweep_mod hsc_env mHscMessage old_hpt (stable_obj, stable_bco) summary mod_ind
| not (backendProducesObject bcknd), is_stable_bco,
(bcknd /= NoBackend) `implies` not is_fake_linkable ->
- ASSERT(isJust old_hmi) -- must be in the old_hpt
+ assert (isJust old_hmi) $ -- must be in the old_hpt
let Just hmi = old_hmi in do
debug_trace 5 (text "skipping stable BCO mod:" <+> ppr this_mod_name)
return hmi
@@ -2893,7 +2895,7 @@ cyclicModuleErr :: [ModuleGraphNode] -> SDoc
-- From a strongly connected component we find
-- a single cycle to report
cyclicModuleErr mss
- = ASSERT( not (null mss) )
+ = assert (not (null mss)) $
case findCycle graph of
Nothing -> text "Unexpected non-cycle" <+> ppr mss
Just path0 -> vcat
diff --git a/compiler/GHC/Driver/MakeFile.hs b/compiler/GHC/Driver/MakeFile.hs
index f49dca22ad..bffeb65850 100644
--- a/compiler/GHC/Driver/MakeFile.hs
+++ b/compiler/GHC/Driver/MakeFile.hs
@@ -28,6 +28,7 @@ import qualified GHC.SysTools as SysTools
import GHC.Data.Graph.Directed ( SCC(..) )
import GHC.Utils.Outputable
import GHC.Utils.Panic
+import GHC.Utils.Panic.Plain
import GHC.Types.SourceError
import GHC.Types.SrcLoc
import Data.List (partition)
@@ -418,7 +419,7 @@ pprCycle summaries = pp_group (CyclicSCC summaries)
pp_group (AcyclicSCC ms) = pp_ms ms
pp_group (CyclicSCC mss)
- = ASSERT( not (null boot_only) )
+ = assert (not (null boot_only)) $
-- The boot-only list must be non-empty, else there would
-- be an infinite chain of non-boot imports, and we've
-- already checked for that in processModDeps
diff --git a/compiler/GHC/Driver/Pipeline.hs b/compiler/GHC/Driver/Pipeline.hs
index 5496fe31a2..b116c30693 100644
--- a/compiler/GHC/Driver/Pipeline.hs
+++ b/compiler/GHC/Driver/Pipeline.hs
@@ -73,6 +73,7 @@ import GHC.Linker.Types
import GHC.Utils.Outputable
import GHC.Utils.Error
import GHC.Utils.Panic
+import GHC.Utils.Panic.Plain
import GHC.Utils.Misc
import GHC.Utils.Monad
import GHC.Utils.Exception as Exception
@@ -136,7 +137,7 @@ preprocess hsc_env input_fn mb_input_buf mb_phase =
handleSourceError (\err -> return $ Left $ to_driver_messages $ srcErrorMessages err) $
MC.handle handler $
fmap Right $ do
- MASSERT2(isJust mb_phase || isHaskellSrcFilename input_fn, text input_fn)
+ massertPpr (isJust mb_phase || isHaskellSrcFilename input_fn) (text input_fn)
(dflags, fp, mb_iface) <- runPipeline anyHsc hsc_env (input_fn, mb_input_buf, fmap RealPhase mb_phase)
Nothing
-- We keep the processed file for the whole session to save on
@@ -145,7 +146,7 @@ preprocess hsc_env input_fn mb_input_buf mb_phase =
Nothing{-no ModLocation-}
[]{-no foreign objects-}
-- We stop before Hsc phase so we shouldn't generate an interface
- MASSERT(isNothing mb_iface)
+ massert (isNothing mb_iface)
return (dflags, fp)
where
srcspan = srcLocSpan $ mkSrcLoc (mkFastString input_fn) 1 1
@@ -228,7 +229,7 @@ compileOne' m_tc_result mHscMessage
case (status, bcknd) of
(HscUpToDate iface hmi_details, _) ->
-- TODO recomp014 triggers this assert. What's going on?!
- -- ASSERT( isJust mb_old_linkable || isNoLink (ghcLink dflags) )
+ -- assert (isJust mb_old_linkable || isNoLink (ghcLink dflags) )
return $! HomeModInfo iface hmi_details mb_old_linkable
(HscNotGeneratingCode iface hmi_details, NoBackend) ->
let mb_linkable = if isHsBootOrSig src_flavour
diff --git a/compiler/GHC/Driver/Ppr.hs b/compiler/GHC/Driver/Ppr.hs
index b6dee0f8e3..b663e8bbff 100644
--- a/compiler/GHC/Driver/Ppr.hs
+++ b/compiler/GHC/Driver/Ppr.hs
@@ -28,6 +28,7 @@ import {-# SOURCE #-} GHC.Driver.Session
import {-# SOURCE #-} GHC.Unit.State
import GHC.Utils.Exception
+import GHC.Utils.Constants (debugIsOn)
import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
@@ -123,16 +124,12 @@ pprTraceException heading doc =
pprSTrace :: HasCallStack => SDoc -> a -> a
pprSTrace doc = pprTrace "" (doc $$ callStackDoc)
-warnPprTrace :: HasCallStack => Bool -> String -> Int -> SDoc -> a -> a
--- ^ Just warn about an assertion failure, recording the given file and line number.
--- Should typically be accessed with the WARN macros
-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
+-- | Just warn about an assertion failure, recording the given file and line number.
+warnPprTrace :: HasCallStack => Bool -> SDoc -> a -> a
+warnPprTrace _ _ x | not debugIsOn = x
+warnPprTrace _ _msg x | unsafeHasNoDebugOutput = x
+warnPprTrace False _msg x = x
+warnPprTrace True msg x
+ = pprDebugAndThen defaultSDocContext trace (text "WARNING:")
(msg $$ callStackDoc )
x
- where
- heading = hsep [text "WARNING: file", text file <> comma, text "line", int line]
diff --git a/compiler/GHC/Driver/Ppr.hs-boot b/compiler/GHC/Driver/Ppr.hs-boot
index a1f864bda8..58f812d6d8 100644
--- a/compiler/GHC/Driver/Ppr.hs-boot
+++ b/compiler/GHC/Driver/Ppr.hs-boot
@@ -6,4 +6,4 @@ import {-# SOURCE #-} GHC.Driver.Session
import {-# SOURCE #-} GHC.Utils.Outputable
showSDoc :: DynFlags -> SDoc -> String
-warnPprTrace :: HasCallStack => Bool -> String -> Int -> SDoc -> a -> a
+warnPprTrace :: HasCallStack => Bool -> SDoc -> a -> a
diff --git a/compiler/GHC/Driver/Session.hs b/compiler/GHC/Driver/Session.hs
index 2673840100..25c55819c5 100644
--- a/compiler/GHC/Driver/Session.hs
+++ b/compiler/GHC/Driver/Session.hs
@@ -240,6 +240,7 @@ import GHC.Settings.Constants
import GHC.Utils.Panic
import qualified GHC.Utils.Ppr.Colour as Col
import GHC.Utils.Misc
+import GHC.Utils.Constants (debugIsOn)
import GHC.Utils.GlobalVars
import GHC.Data.Maybe
import GHC.Utils.Monad