[commit: ghc] wip/T13861: WIP: cleanups (ea8b155)
git at git.haskell.org
git at git.haskell.org
Sat Dec 30 00:30:28 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T13861
Link : http://ghc.haskell.org/trac/ghc/changeset/ea8b155d68ed0a341ec175c90d2bedbc0a1c4325/ghc
>---------------------------------------------------------------
commit ea8b155d68ed0a341ec175c90d2bedbc0a1c4325
Author: Gabor Greif <ggreif at gmail.com>
Date: Sat Dec 30 01:30:13 2017 +0100
WIP: cleanups
of warnings, thinkos
>---------------------------------------------------------------
ea8b155d68ed0a341ec175c90d2bedbc0a1c4325
compiler/simplStg/StgCse.hs | 6 +++---
1 file changed, 3 insertions(+), 3 deletions(-)
diff --git a/compiler/simplStg/StgCse.hs b/compiler/simplStg/StgCse.hs
index ded1761..df3acab 100644
--- a/compiler/simplStg/StgCse.hs
+++ b/compiler/simplStg/StgCse.hs
@@ -1,5 +1,4 @@
{-# LANGUAGE TypeFamilies, LambdaCase #-}
-{-# OPTIONS -Wno-error=unused-imports -Wno-error=unused-top-binds #-}
{-|
Note [CSE for Stg]
@@ -92,11 +91,11 @@ import TrieMap
import NameEnv
import Control.Monad( (>=>) )
import Name (NamedThing (..), mkFCallName)
-import Unique (mkUniqueGrimily, getKey, getUnique)
-import TyCon (tyConFamilySize)
+import Unique (mkUniqueGrimily)
import Data.List (partition, sortBy, groupBy)
import Data.Function (on)
+import Data.Ord (Down(..), comparing)
--------------
-- The Trie --
@@ -431,6 +430,7 @@ mkStgCase scrut bndr ty alts | all isBndr alts = scrut
grouped alts
| (cons@(_:_:_),rest) <- partition (\case (_,_,StgConApp _ [] [])->True; _->False) alts
, let itsCon (_,_,StgConApp c [] []) = c
+ itsCon _ = pprPanic "mkStgCase" (text "not StgConApp")
gcons = groupBy ((==) `on` itsCon) cons
, (((_,_,res):_:_):others) <- sortBy (comparing $ Down . length) gcons
= pprTrace "mkStgCase##" (ppr others) $ Just ((DEFAULT, [], res) : concat others ++ rest)
More information about the ghc-commits
mailing list