Fix Trac #1759: do not let ticks get in the way of spotting trivially-true guards
[ghc-hetmet.git] / compiler / deSugar / DsGRHSs.lhs
index 55b4f57..265df11 100644 (file)
@@ -6,6 +6,13 @@
 Matching guarded right-hand-sides (GRHSs)
 
 \begin{code}
+{-# OPTIONS -w #-}
+-- The above warning supression flag is a temporary kludge.
+-- While working on this module you are encouraged to remove it and fix
+-- any warnings in the module. See
+--     http://hackage.haskell.org/trac/ghc/wiki/Commentary/CodingStyle#Warnings
+-- for details
+
 module DsGRHSs ( dsGuarded, dsGRHSs ) where
 
 #include "HsVersions.h"
@@ -14,14 +21,12 @@ import {-# SOURCE #-} DsExpr  ( dsLExpr, dsLocalBinds )
 import {-# SOURCE #-} Match   ( matchSinglePat )
 
 import HsSyn
-import HsUtils
 import CoreSyn
 import Var
 import Type
 
 import DsMonad
 import DsUtils
-import Unique
 import PrelInfo
 import TysWiredIn
 import PrelNames
@@ -57,21 +62,16 @@ dsGRHSs :: HsMatchContext Name -> [Pat Id]  -- These are to build a MatchContext
        -> GRHSs Id                             -- Guarded RHSs
        -> Type                                 -- Type of RHS
        -> DsM MatchResult
-dsGRHSs hs_ctx pats grhssa@(GRHSs grhss binds) rhs_ty =
-   bindLocalsDs binders $ do
+dsGRHSs hs_ctx pats grhssa@(GRHSs grhss binds) rhs_ty = do
     match_results <- mappM (dsGRHS hs_ctx pats rhs_ty) grhss
     let 
        match_result1 = foldr1 combineMatchResults match_results
        match_result2 = adjustMatchResultDs 
-                                 (\e -> bindLocalsDs binders $ 
-                                        dsLocalBinds binds e) 
+                                 (\e -> dsLocalBinds binds e) 
                                  match_result1
                -- NB: nested dsLet inside matchResult
     --
     returnDs match_result2
-        where bindsBinders = map unLoc (collectLocalBinders binds)
-              patsBinders  = collectPatsBinders (map (L undefined) pats) 
-              binders = bindsBinders ++ patsBinders
 
 dsGRHS hs_ctx pats rhs_ty (L loc (GRHS guards rhs))
   = matchGuards (map unLoc guards) hs_ctx rhs rhs_ty
@@ -105,10 +105,8 @@ matchGuards [] ctx rhs rhs_ty
        -- NB:  The success of this clause depends on the typechecker not
        --      wrapping the 'otherwise' in empty HsTyApp or HsWrap constructors
        --      If it does, you'll get bogus overlap warnings
-matchGuards (ExprStmt (L _ (HsVar v)) _ _ : stmts) ctx rhs rhs_ty
-  |  v `hasKey` otherwiseIdKey
-  || v `hasKey` getUnique trueDataConId        
-       -- trueDataConId doesn't have the same unique as trueDataCon
+matchGuards (ExprStmt e _ _ : stmts) ctx rhs rhs_ty
+  | isTrueLHsExpr e
   = matchGuards stmts ctx rhs rhs_ty
 
 matchGuards (ExprStmt expr _ _ : stmts) ctx rhs rhs_ty
@@ -117,8 +115,7 @@ matchGuards (ExprStmt expr _ _ : stmts) ctx rhs rhs_ty
     returnDs (mkGuardedMatchResult pred_expr match_result)
 
 matchGuards (LetStmt binds : stmts) ctx rhs rhs_ty
-  = bindLocalsDs (map unLoc $ collectLocalBinders binds) $
-    matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
+  = matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
     returnDs (adjustMatchResultDs (dsLocalBinds binds) match_result)
        -- NB the dsLet occurs inside the match_result
        -- Reason: dsLet takes the body expression as its argument
@@ -126,10 +123,22 @@ matchGuards (LetStmt binds : stmts) ctx rhs rhs_ty
        --         body expression in hand
 
 matchGuards (BindStmt pat bind_rhs _ _ : stmts) ctx rhs rhs_ty
-  = bindLocalsDs (collectPatBinders pat) $
-    matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
+  = matchGuards stmts ctx rhs rhs_ty   `thenDs` \ match_result ->
     dsLExpr bind_rhs                   `thenDs` \ core_rhs ->
     matchSinglePat core_rhs ctx pat rhs_ty match_result
+
+isTrueLHsExpr :: LHsExpr Id -> Bool
+-- Returns True if we're sure that the expression is True
+-- I.e.   * 'True' datacon
+--       * 'otherwise' Id
+--       * Trivial wappings of these
+isTrueLHsExpr (L _ (HsVar v)) =  v `hasKey` otherwiseIdKey
+                             || v `hasKey` getUnique trueDataConId     
+       -- trueDataConId doesn't have the same unique as trueDataCon
+isTrueLHsExpr (L _ (HsTick    _ _ e)) = isTrueLHsExpr e
+isTrueLHsExpr (L _ (HsBinTick _ _ e)) = isTrueLHsExpr e
+isTrueLHsExpr (L _ (HsPar e))         = isTrueLHsExpr e
+isTrueLHsExpr other = False
 \end{code}
 
 Should {\em fail} if @e@ returns @D@