[commit: ghc] master: Replace debugging trace with a proper WARN (9297c6f)
git at git.haskell.org
git at git.haskell.org
Mon Mar 13 18:34:48 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/9297c6f3177f549f230cac33a79ec0dc9d8bee70/ghc
>---------------------------------------------------------------
commit 9297c6f3177f549f230cac33a79ec0dc9d8bee70
Author: Matthew Pickering <matthewtpickering at gmail.com>
Date: Sun Mar 12 15:15:05 2017 -0400
Replace debugging trace with a proper WARN
Reviewers: austin, bgamari
Reviewed By: bgamari
Subscribers: rwbarton, thomie
Differential Revision: https://phabricator.haskell.org/D3326
>---------------------------------------------------------------
9297c6f3177f549f230cac33a79ec0dc9d8bee70
compiler/utils/Outputable.hs-boot | 4 ++++
compiler/utils/Util.hs | 8 ++++++--
2 files changed, 10 insertions(+), 2 deletions(-)
diff --git a/compiler/utils/Outputable.hs-boot b/compiler/utils/Outputable.hs-boot
index e5e8895..980c186 100644
--- a/compiler/utils/Outputable.hs-boot
+++ b/compiler/utils/Outputable.hs-boot
@@ -3,3 +3,7 @@ module Outputable where
data SDoc
showSDocUnsafe :: SDoc -> String
+
+warnPprTrace :: Bool -> String -> Int -> SDoc -> a -> a
+
+text :: String -> SDoc
diff --git a/compiler/utils/Util.hs b/compiler/utils/Util.hs
index 5c09959..30026c5 100644
--- a/compiler/utils/Util.hs
+++ b/compiler/utils/Util.hs
@@ -164,6 +164,10 @@ import qualified Data.Set as Set
import Data.Time
+#ifdef DEBUG
+import {-# SOURCE #-} Outputable ( warnPprTrace, text )
+#endif
+
infixr 9 `thenCmp`
{-
@@ -558,7 +562,7 @@ isIn msg x ys
elem100 :: Eq a => Int -> a -> [a] -> Bool
elem100 _ _ [] = False
elem100 i x (y:ys)
- | i > 100 = trace ("Over-long elem in " ++ msg) (x `elem` (y:ys))
+ | i > 100 = WARN(True, text ("Over-long elem in " ++ msg)) (x `elem` (y:ys))
| otherwise = x == y || elem100 (i + 1) x ys
isn'tIn msg x ys
@@ -567,7 +571,7 @@ isn'tIn msg x ys
notElem100 :: Eq a => Int -> a -> [a] -> Bool
notElem100 _ _ [] = True
notElem100 i x (y:ys)
- | i > 100 = trace ("Over-long notElem in " ++ msg) (x `notElem` (y:ys))
+ | i > 100 = WARN(True, text ("Over-long notElem in " ++ msg)) (x `notElem` (y:ys))
| otherwise = x /= y && notElem100 (i + 1) x ys
# endif /* DEBUG */
More information about the ghc-commits
mailing list