[commit: ghc] master: Typechecker: refactoring only (f745b6e)

git at git.haskell.org git at git.haskell.org
Tue Apr 7 09:49:15 UTC 2015


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

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/f745b6e83647fb14bd80094db63ee087d69f4494/ghc

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

commit f745b6e83647fb14bd80094db63ee087d69f4494
Author: Thomas Miedema <thomasmiedema at gmail.com>
Date:   Tue Apr 7 11:48:35 2015 +0200

    Typechecker: refactoring only
    
    * don't call `nlHsPar`, as `genOpApp` already does so.
    * don't reimplement `isUnboxedTupleTyCon` and `isBoxedTupleTyCon`.
    
    Reviewed By: austin
    
    Differential Revision: https://phabricator.haskell.org/D798


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

f745b6e83647fb14bd80094db63ee087d69f4494
 compiler/typecheck/TcGenDeriv.hs                 | 4 ++--
 compiler/types/TyCon.hs                          | 7 ++-----
 testsuite/tests/deriving/should_run/T9576.stderr | 2 +-
 3 files changed, 5 insertions(+), 8 deletions(-)

diff --git a/compiler/typecheck/TcGenDeriv.hs b/compiler/typecheck/TcGenDeriv.hs
index 6216ec2..3d43935 100644
--- a/compiler/typecheck/TcGenDeriv.hs
+++ b/compiler/typecheck/TcGenDeriv.hs
@@ -1137,8 +1137,8 @@ gen_Show_binds get_fixity loc tycon
          ([a_Pat, con_pat], nlHsPar (nested_compose_Expr show_thingies))
       | otherwise   =
          ([a_Pat, con_pat],
-          showParen_Expr (nlHsPar (genOpApp a_Expr ge_RDR
-                                        (nlHsLit (HsInt "" con_prec_plus_one))))
+          showParen_Expr (genOpApp a_Expr ge_RDR
+                              (nlHsLit (HsInt "" con_prec_plus_one)))
                          (nlHsPar (nested_compose_Expr show_thingies)))
         where
              data_con_RDR  = getRdrName data_con
diff --git a/compiler/types/TyCon.hs b/compiler/types/TyCon.hs
index 8e0175a..ea219c1 100644
--- a/compiler/types/TyCon.hs
+++ b/compiler/types/TyCon.hs
@@ -1189,9 +1189,7 @@ isPrimTyCon _              = False
 -- only be true for primitive and unboxed-tuple 'TyCon's
 isUnLiftedTyCon :: TyCon -> Bool
 isUnLiftedTyCon (PrimTyCon  {isUnLifted = is_unlifted}) = is_unlifted
-isUnLiftedTyCon (TupleTyCon {tyConTupleSort = sort})
-    = not (isBoxed (tupleSortBoxity sort))
-isUnLiftedTyCon _                                       = False
+isUnLiftedTyCon tc = isUnboxedTupleTyCon tc
 
 -- | Returns @True@ if the supplied 'TyCon' resulted from either a
 -- @data@ or @newtype@ declaration
@@ -1217,8 +1215,7 @@ isDataTyCon (AlgTyCon {algTcRhs = rhs})
         NewTyCon {}        -> False
         DataFamilyTyCon {} -> False
         AbstractTyCon {}   -> False      -- We don't know, so return False
-isDataTyCon (TupleTyCon {tyConTupleSort = sort}) = isBoxed (tupleSortBoxity sort)
-isDataTyCon _ = False
+isDataTyCon tc = isBoxedTupleTyCon tc
 
 -- | 'isDistinctTyCon' is true of 'TyCon's that are equal only to
 -- themselves, even via coercions (except for unsafeCoerce).
diff --git a/testsuite/tests/deriving/should_run/T9576.stderr b/testsuite/tests/deriving/should_run/T9576.stderr
index 954b2d9..bc2a0b3 100644
--- a/testsuite/tests/deriving/should_run/T9576.stderr
+++ b/testsuite/tests/deriving/should_run/T9576.stderr
@@ -4,7 +4,7 @@ T9576: T9576.hs:6:31:
     In the second argument of ‘showParen’, namely
       ‘((.) (showString "MkBar ") (showsPrec 11 b1))’
     In the expression:
-      showParen ((a >= 11)) ((.) (showString "MkBar ") (showsPrec 11 b1))
+      showParen (a >= 11) ((.) (showString "MkBar ") (showsPrec 11 b1))
     When typechecking the code for ‘showsPrec’
       in a derived instance for ‘Show Bar’:
       To see the code I am typechecking, use -ddump-deriv



More information about the ghc-commits mailing list