[commit: ghc] wip/T12618: Use ConApp when creating True resp. False (65ba986)

git at git.haskell.org git at git.haskell.org
Thu Oct 6 23:21:04 UTC 2016


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

On branch  : wip/T12618
Link       : http://ghc.haskell.org/trac/ghc/changeset/65ba986828aba20e61ef15b2db09eb40c06259b4/ghc

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

commit 65ba986828aba20e61ef15b2db09eb40c06259b4
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Wed Oct 5 23:23:20 2016 -0400

    Use ConApp when creating True resp. False


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

65ba986828aba20e61ef15b2db09eb40c06259b4
 compiler/deSugar/DsCCall.hs    | 4 ++--
 compiler/deSugar/DsListComp.hs | 8 ++++----
 compiler/deSugar/DsUtils.hs    | 4 ++--
 compiler/prelude/PrelRules.hs  | 4 ++--
 4 files changed, 10 insertions(+), 10 deletions(-)

diff --git a/compiler/deSugar/DsCCall.hs b/compiler/deSugar/DsCCall.hs
index 8f614ba..a5f8658 100644
--- a/compiler/deSugar/DsCCall.hs
+++ b/compiler/deSugar/DsCCall.hs
@@ -331,8 +331,8 @@ resultWrapper result_ty
     return
      (Just intPrimTy, \e -> mkWildCase e intPrimTy
                                    boolTy
-                                   [(DEFAULT                    ,[],Var trueDataConId ),
-                                    (LitAlt (mkMachInt dflags 0),[],Var falseDataConId)])
+                                   [(DEFAULT                    ,[],ConApp trueDataCon []),
+                                    (LitAlt (mkMachInt dflags 0),[],ConApp falseDataCon [])])
 
   -- Newtypes
   | Just (co, rep_ty) <- topNormaliseNewType_maybe result_ty
diff --git a/compiler/deSugar/DsListComp.hs b/compiler/deSugar/DsListComp.hs
index 45320cc..4a65628 100644
--- a/compiler/deSugar/DsListComp.hs
+++ b/compiler/deSugar/DsListComp.hs
@@ -491,8 +491,8 @@ dsPArrComp (BindStmt p e _ _ _ : qs) = do
     filterP <- dsDPHBuiltin filterPVar
     ce <- dsLExpr e
     let ety'ce  = parrElemType ce
-        false   = Var falseDataConId
-        true    = Var trueDataConId
+        false   = ConApp falseDataCon []
+        true    = ConApp trueDataCon []
     v <- newSysLocalDs ety'ce
     pred <- matchSimply (Var v) (StmtCtxt PArrComp) p true false
     let gen | isIrrefutableHsPat p = ce
@@ -552,8 +552,8 @@ dePArrComp (BindStmt p e _ _ _ : qs) pa cea = do
     ce <- dsLExpr e
     let ety'cea = parrElemType cea
         ety'ce  = parrElemType ce
-        false   = Var falseDataConId
-        true    = Var trueDataConId
+        false   = ConApp falseDataCon []
+        true    = ConApp trueDataCon []
     v <- newSysLocalDs ety'ce
     pred <- matchSimply (Var v) (StmtCtxt PArrComp) p true false
     let cef | isIrrefutableHsPat p = ce
diff --git a/compiler/deSugar/DsUtils.hs b/compiler/deSugar/DsUtils.hs
index cc621d5..ebf6aec 100644
--- a/compiler/deSugar/DsUtils.hs
+++ b/compiler/deSugar/DsUtils.hs
@@ -943,8 +943,8 @@ mkBinaryTickBox ixT ixF e = do
        this_mod <- getModule
        let bndr1 = mkSysLocal (fsLit "t1") uq boolTy
        let
-           falseBox = Tick (HpcTick this_mod ixF) (Var falseDataConId)
-           trueBox  = Tick (HpcTick this_mod ixT) (Var trueDataConId)
+           falseBox = Tick (HpcTick this_mod ixF) (ConApp falseDataCon [])
+           trueBox  = Tick (HpcTick this_mod ixT) (ConApp trueDataCon [])
        --
        return $ Case e bndr1 boolTy
                        [ (DataAlt falseDataCon, [], falseBox)
diff --git a/compiler/prelude/PrelRules.hs b/compiler/prelude/PrelRules.hs
index 197ddb3..f637fd3 100644
--- a/compiler/prelude/PrelRules.hs
+++ b/compiler/prelude/PrelRules.hs
@@ -831,8 +831,8 @@ trueValInt  dflags = Lit $ onei  dflags -- see Note [What's true and false]
 falseValInt dflags = Lit $ zeroi dflags
 
 trueValBool, falseValBool :: Expr CoreBndr
-trueValBool   = Var trueDataConId -- see Note [What's true and false]
-falseValBool  = Var falseDataConId
+trueValBool   = ConApp trueDataCon [] -- see Note [What's true and false]
+falseValBool  = ConApp falseDataCon []
 
 ltVal, eqVal, gtVal :: Expr CoreBndr
 ltVal = Var ltDataConId



More information about the ghc-commits mailing list