Skip to content
GitLab
Projects
Groups
Snippets
/
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
GHC
Commits
f8c52d7f
Commit
f8c52d7f
authored
Sep 08, 2007
by
Ian Lynagh
Browse files
Make various assertions work when !DEBUG
parent
907c44ca
Changes
12
Hide whitespace changes
Inline
Side-by-side
compiler/HsVersions.h
View file @
f8c52d7f
...
...
@@ -48,8 +48,9 @@ name = Util.global (value) :: IORef (ty); \
#define ASSERT(e) if False && (not (e)) then panic "ASSERT" else
#define ASSERT2(e,msg) if False && (not (e)) then pprPanic "ASSERT2" (msg) else
#define ASSERTM(e) do { let { _mbool = (e) } }
#define ASSERTM2(e,msg) do { let { _mbool = (e) }; when False (panic "ASSERTM2") }
#define WARN(e,msg) if False && (e) then pprPanic "WARN" msg else
--
Here
we
deliberately
don
'
t
use
when
as
Control
.
Monad
might
not
be
imported
#define ASSERTM2(e,msg) do { let { _mbool = (e) }; if False then panic "ASSERTM2" else return () }
#define WARN(e,msg) if False && (e) then pprPanic "WARN" (msg) else
#endif
--
This
#
ifndef
lets
us
switch
off
the
"import FastString"
...
...
compiler/basicTypes/Var.lhs
View file @
f8c52d7f
...
...
@@ -47,9 +47,7 @@ import {-# SOURCE #-} TypeRep( Type, Kind )
import {-# SOURCE #-} TcType( TcTyVarDetails, pprTcTyVarDetails )
import {-# SOURCE #-} IdInfo( GlobalIdDetails, notGlobalId,
IdInfo, seqIdInfo )
#ifdef DEBUG
import {-# SOURCE #-} TypeRep( isCoercionKind )
#endif
import Name hiding (varName)
import Unique
...
...
compiler/codeGen/CgCon.lhs
View file @
f8c52d7f
...
...
@@ -51,9 +51,7 @@ import Type
import PrelInfo
import Outputable
import ListSetOps
#ifdef DEBUG
import Util ( lengthIs )
#endif
import Util
\end{code}
...
...
compiler/codeGen/CgUtils.hs
View file @
f8c52d7f
...
...
@@ -74,9 +74,7 @@ import Util
import
DynFlags
import
FastString
import
PackageConfig
#
ifdef
DEBUG
import
Outputable
#
endif
import
Data.Char
import
Data.Bits
...
...
compiler/codeGen/CodeGen.lhs
View file @
f8c52d7f
...
...
@@ -54,10 +54,7 @@ import OccName
import TyCon
import Module
import ErrUtils
#ifdef DEBUG
import Panic
#endif
\end{code}
\begin{code}
...
...
compiler/coreSyn/CoreLint.lhs
View file @
f8c52d7f
...
...
@@ -44,11 +44,7 @@ import BasicTypes
import StaticFlags
import DynFlags
import Outputable
#ifdef DEBUG
import Util ( notNull )
#endif
import Util
import Data.Maybe
\end{code}
...
...
compiler/main/CmdLineParser.hs
View file @
f8c52d7f
...
...
@@ -24,9 +24,7 @@ module CmdLineParser (
#
include
"HsVersions.h"
import
Util
(
maybePrefixMatch
,
notNull
,
removeSpaces
)
#
ifdef
DEBUG
import
Panic
(
assertPanic
)
#
endif
import
Panic
data
OptKind
m
-- Suppose the flag is -f
=
NoArg
(
m
()
)
-- -f all by itself
...
...
compiler/main/GHC.hs
View file @
f8c52d7f
...
...
@@ -562,10 +562,8 @@ load2 s@(Session ref) how_much mod_graph = do
-- (see msDeps)
let
all_home_mods
=
[
ms_mod_name
s
|
s
<-
mod_graph
,
not
(
isBootSummary
s
)]
#
ifdef
DEBUG
bad_boot_mods
=
[
s
|
s
<-
mod_graph
,
isBootSummary
s
,
not
(
ms_mod_name
s
`
elem
`
all_home_mods
)]
#
endif
ASSERT
(
null
bad_boot_mods
)
return
()
-- mg2_with_srcimps drops the hi-boot nodes, returning a
...
...
compiler/nativeGen/RegAllocLinear.hs
View file @
f8c52d7f
...
...
@@ -102,11 +102,9 @@ import UniqSupply
import
Outputable
import
State
#
ifndef
DEBUG
import
Data.Maybe
(
fromJust
)
#
endif
import
Data.List
(
nub
,
partition
,
foldl'
)
import
Control.Monad
(
when
)
import
Data.Maybe
import
Data.List
import
Control.Monad
import
Data.Word
import
Data.Bits
...
...
@@ -293,10 +291,8 @@ save it in a spill location, but mark it as InBoth because the current
instruction might still want to read it.
-}
#
ifdef
DEBUG
instance
Outputable
Loc
where
ppr
l
=
text
(
show
l
)
#
endif
-- | Do register allocation on some basic blocks.
...
...
compiler/specialise/SpecConstr.lhs
View file @
f8c52d7f
...
...
@@ -1249,12 +1249,10 @@ samePat (vs1, as1) (vs2, as2)
same e1 e2 = WARN( bad e1 || bad e2, ppr e1 $$ ppr e2)
False -- Let, lambda, case should not occur
#ifdef DEBUG
bad (Case {}) = True
bad (Let {}) = True
bad (Lam {}) = True
bad other = False
#endif
\end{code}
Note [Ignore type differences]
...
...
compiler/stgSyn/CoreToStg.lhs
View file @
f8c52d7f
...
...
@@ -215,7 +215,6 @@ coreTopBindToStg this_pkg env body_fvs (Rec pairs)
ASSERT2(consistentCafInfo (head binders) bind, ppr binders)
(env', fvs' `unionFVInfo` body_fvs, bind)
#ifdef DEBUG
-- Assertion helper: this checks that the CafInfo on the Id matches
-- what CoreToStg has figured out about the binding's SRT. The
-- CafInfo will be exact in all cases except when CorePrep has
...
...
@@ -230,7 +229,6 @@ consistentCafInfo id bind
exact = id_marked_caffy == binding_is_caffy
id_marked_caffy = mayHaveCafRefs (idCafInfo id)
binding_is_caffy = stgBindHasCafRefs bind
#endif
\end{code}
\begin{code}
...
...
@@ -1074,7 +1072,6 @@ plusFVInfo (id1,hb1,info1) (id2,hb2,info2)
= ASSERT (id1 == id2 && hb1 `check_eq_how_bound` hb2)
(id1, hb1, combineStgBinderInfo info1 info2)
#ifdef DEBUG
-- The HowBound info for a variable in the FVInfo should be consistent
check_eq_how_bound ImportBound ImportBound = True
check_eq_how_bound LambdaBound LambdaBound = True
...
...
@@ -1084,7 +1081,6 @@ check_eq_how_bound hb1 hb2 = False
check_eq_li (NestedLet _) (NestedLet _) = True
check_eq_li TopLet TopLet = True
check_eq_li li1 li2 = False
#endif
\end{code}
Misc.
...
...
compiler/typecheck/TcGadt.lhs
View file @
f8c52d7f
...
...
@@ -39,11 +39,8 @@ import Maybes
import Control.Monad
import Outputable
import TcType
#ifdef DEBUG
import Unique
import UniqFM
#endif
\end{code}
...
...
@@ -261,7 +258,6 @@ tryToBind tv_set tv | tv `elemVarSet` tv_set = BindMe
%************************************************************************
\begin{code}
#ifdef DEBUG
badReftElts :: InternalReft -> [(Unique, (Coercion,Type))]
-- Return the BAD elements of the refinement
-- Should be empty; used in asserions only
...
...
@@ -274,7 +270,6 @@ badReftElts env
| otherwise = False
where
(ty1,ty2) = coercionKind co
#endif
emptyInternalReft :: InternalReft
emptyInternalReft = emptyVarEnv
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment