[commit: ghc] wip/cross-constr-cse: better comment out some lines that gen warnings (9460748)

git at git.haskell.org git at git.haskell.org
Sun Jul 30 21:22:48 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/cross-constr-cse
Link       : http://ghc.haskell.org/trac/ghc/changeset/9460748ddf3267f9509e6a37e5c61800ac8e9127/ghc

>---------------------------------------------------------------

commit 9460748ddf3267f9509e6a37e5c61800ac8e9127
Author: Gabor Greif <ggreif at gmail.com>
Date:   Sun Jul 30 18:15:19 2017 +0200

    better comment out some lines that gen warnings


>---------------------------------------------------------------

9460748ddf3267f9509e6a37e5c61800ac8e9127
 compiler/simplStg/StgCse.hs | 7 +++----
 1 file changed, 3 insertions(+), 4 deletions(-)

diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs
index 91a96ec..6d845b3 100644
--- a/compiler/simplStg/StgCse.hs
+++ b/compiler/simplStg/StgCse.hs
@@ -1,5 +1,4 @@
 {-# LANGUAGE TypeFamilies, LambdaCase #-}
-{-# OPTIONS_GHC -Wno-unused-matches -Wno-missing-signatures #-}
 
 {-|
 Note [CSE for Stg]
@@ -124,15 +123,15 @@ instance NamedThing LaxDataCon where
 instance TrieMap ConAppMap where
     type Key ConAppMap = (LaxDataCon, [StgArg])
     emptyTM  = CAM emptyTM
-    lookupTM (dataCon, args) | traceLookup dataCon = undefined
+    --lookupTM (dataCon, args) | traceLookup dataCon = undefined
     lookupTM (dataCon, args) = un_cam >.> lkDNamed dataCon >=> lookupTM args
     alterTM  (dataCon, args) f m =
         m { un_cam = un_cam m |> xtDNamed dataCon |>> alterTM args f }
     foldTM k = un_cam >.> foldTM (foldTM k)
     mapTM f  = un_cam >.> mapTM (mapTM f) >.> CAM
 
-traceLookup (Lax dc) = pprTrace "lookupTM" (ppr dc) False
-{-# NOINLINE traceLookup #-}
+--traceLookup (Lax dc) = pprTrace "lookupTM" (ppr dc) False
+--{-# NOINLINE traceLookup #-}
 
 -----------------
 -- The CSE Env --



More information about the ghc-commits mailing list