[commit: ghc] master: Move isVoidRep, isGcPtrRep to TyCon to join primRepSizeW etc (b83666d)

git at git.haskell.org git at git.haskell.org
Fri Nov 22 20:05:14 UTC 2013


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

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

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

commit b83666d4813b62b0b2da9b8238af6909c9f1dae0
Author: Simon Peyton Jones <simonpj at microsoft.com>
Date:   Fri Nov 22 15:05:39 2013 +0000

    Move isVoidRep, isGcPtrRep to TyCon to join primRepSizeW etc
    
    This is just a modest refactoring


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

b83666d4813b62b0b2da9b8238af6909c9f1dae0
 compiler/codeGen/StgCmmClosure.hs |   11 ++---------
 compiler/codeGen/StgCmmEnv.hs     |    5 +----
 compiler/codeGen/StgCmmExpr.hs    |    2 +-
 compiler/types/TyCon.lhs          |   10 +++++++++-
 4 files changed, 13 insertions(+), 15 deletions(-)

diff --git a/compiler/codeGen/StgCmmClosure.hs b/compiler/codeGen/StgCmmClosure.hs
index 627c189..037ba97 100644
--- a/compiler/codeGen/StgCmmClosure.hs
+++ b/compiler/codeGen/StgCmmClosure.hs
@@ -123,9 +123,10 @@ isKnownFun _ = False
 
 -- Why are these here?
 
--- NB: this is reliable because by StgCmm no Ids have unboxed tuple type
 idPrimRep :: Id -> PrimRep
 idPrimRep id = typePrimRep (idType id)
+    -- NB: typePrimRep fails on unboxed tuples,
+    --     but by StgCmm no Ids have unboxed tuple type
 
 addIdReps :: [Id] -> [(PrimRep, Id)]
 addIdReps ids = [(idPrimRep id, id) | id <- ids]
@@ -136,14 +137,6 @@ addArgReps args = [(argPrimRep arg, arg) | arg <- args]
 argPrimRep :: StgArg -> PrimRep
 argPrimRep arg = typePrimRep (stgArgType arg)
 
-isVoidRep :: PrimRep -> Bool
-isVoidRep VoidRep = True
-isVoidRep _other  = False
-
-isGcPtrRep :: PrimRep -> Bool
-isGcPtrRep PtrRep = True
-isGcPtrRep _      = False
-
 
 -----------------------------------------------------------------------------
 --                LambdaFormInfo
diff --git a/compiler/codeGen/StgCmmEnv.hs b/compiler/codeGen/StgCmmEnv.hs
index 353fec5..2b8677c 100644
--- a/compiler/codeGen/StgCmmEnv.hs
+++ b/compiler/codeGen/StgCmmEnv.hs
@@ -11,7 +11,7 @@ module StgCmmEnv (
         litIdInfo, lneIdInfo, rhsIdInfo, mkRhsInit,
         idInfoToAmode,
 
-        NonVoid(..), unsafe_stripNV, isVoidId, nonVoidIds,
+        NonVoid(..), unsafe_stripNV, nonVoidIds,
 
         addBindC, addBindsC,
 
@@ -60,9 +60,6 @@ unsafe_stripNV (NonVoid a) = a
 instance (Outputable a) => Outputable (NonVoid a) where
   ppr (NonVoid a) = ppr a
 
-isVoidId :: Id -> Bool
-isVoidId = isVoidRep . idPrimRep
-
 nonVoidIds :: [Id] -> [NonVoid Id]
 nonVoidIds ids = [NonVoid id | id <- ids, not (isVoidRep (idPrimRep id))]
 
diff --git a/compiler/codeGen/StgCmmExpr.hs b/compiler/codeGen/StgCmmExpr.hs
index 51578b1..cc32a14 100644
--- a/compiler/codeGen/StgCmmExpr.hs
+++ b/compiler/codeGen/StgCmmExpr.hs
@@ -638,7 +638,7 @@ cgConApp con stg_args
         ; emitReturn [idInfoToAmode idinfo] }
 
 cgIdApp :: Id -> [StgArg] -> FCode ReturnKind
-cgIdApp fun_id [] | isVoidId fun_id = emitReturn []
+cgIdApp fun_id [] | isVoidTy (idType fun_id) = emitReturn []
 cgIdApp fun_id args = do
     dflags         <- getDynFlags
     fun_info       <- getCgIdInfo fun_id
diff --git a/compiler/types/TyCon.lhs b/compiler/types/TyCon.lhs
index ccc78a2..bb489b3 100644
--- a/compiler/types/TyCon.lhs
+++ b/compiler/types/TyCon.lhs
@@ -84,7 +84,7 @@ module TyCon(
 
         -- * Primitive representations of Types
         PrimRep(..), PrimElemRep(..),
-        tyConPrimRep,
+        tyConPrimRep, isVoidRep, isGcPtrRep,
         primRepSizeW, primElemRepSizeB,
 
         -- * Recursion breaking
@@ -857,6 +857,14 @@ instance Outputable PrimRep where
 instance Outputable PrimElemRep where
   ppr r = text (show r)
 
+isVoidRep :: PrimRep -> Bool
+isVoidRep VoidRep = True
+isVoidRep _other  = False
+
+isGcPtrRep :: PrimRep -> Bool
+isGcPtrRep PtrRep = True
+isGcPtrRep _      = False
+
 -- | Find the size of a 'PrimRep', in words
 primRepSizeW :: DynFlags -> PrimRep -> Int
 primRepSizeW _      IntRep           = 1



More information about the ghc-commits mailing list