[Git][ghc/ghc][master] Remove unused Unique field from StgFCallOp

Marge Bot gitlab at gitlab.haskell.org
Fri Jun 14 03:35:24 UTC 2019



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
71e75ba6 by Ömer Sinan Ağacan at 2019-06-14T03:35:19Z
Remove unused Unique field from StgFCallOp

Fixes #16696

- - - - -


4 changed files:

- compiler/codeGen/StgCmmExpr.hs
- compiler/codeGen/StgCmmPrim.hs
- compiler/stgSyn/CoreToStg.hs
- compiler/stgSyn/StgSyn.hs


Changes:

=====================================
compiler/codeGen/StgCmmExpr.hs
=====================================
@@ -577,7 +577,7 @@ isSimpleScrut _                _           = return False
 
 isSimpleOp :: StgOp -> [StgArg] -> FCode Bool
 -- True iff the op cannot block or allocate
-isSimpleOp (StgFCallOp (CCall (CCallSpec _ _ safe)) _ _) _ = return $! not (playSafe safe)
+isSimpleOp (StgFCallOp (CCall (CCallSpec _ _ safe)) _) _ = return $! not (playSafe safe)
 -- dataToTag# evalautes its argument, see Note [dataToTag#] in primops.txt.pp
 isSimpleOp (StgPrimOp DataToTagOp) _ = return False
 isSimpleOp (StgPrimOp op) stg_args                  = do


=====================================
compiler/codeGen/StgCmmPrim.hs
=====================================
@@ -71,7 +71,7 @@ cgOpApp :: StgOp        -- The op
         -> FCode ReturnKind
 
 -- Foreign calls
-cgOpApp (StgFCallOp fcall ty _) stg_args res_ty
+cgOpApp (StgFCallOp fcall ty) stg_args res_ty
   = cgForeignCall fcall ty stg_args res_ty
       -- Note [Foreign call results]
 


=====================================
compiler/stgSyn/CoreToStg.hs
=====================================
@@ -539,7 +539,7 @@ coreToStgApp _ f args ticks = do
 
                 -- A regular foreign call.
                 FCallId call     -> ASSERT( saturated )
-                                    StgOpApp (StgFCallOp call (idType f) (idUnique f)) args' res_ty
+                                    StgOpApp (StgFCallOp call (idType f)) args' res_ty
 
                 TickBoxOpId {}   -> pprPanic "coreToStg TickBox" $ ppr (f,args')
                 _other           -> StgApp f args'


=====================================
compiler/stgSyn/StgSyn.hs
=====================================
@@ -82,7 +82,6 @@ import PrimOp      ( PrimOp, PrimCall )
 import TyCon       ( PrimRep(..), TyCon )
 import Type        ( Type )
 import RepType     ( typePrimRep1 )
-import Unique      ( Unique )
 import Util
 
 import Data.List.NonEmpty ( NonEmpty, toList )
@@ -686,14 +685,11 @@ data StgOp
 
   | StgPrimCallOp PrimCall
 
-  | StgFCallOp ForeignCall Type Unique
-        -- The Unique is occasionally needed by the C pretty-printer
-        -- (which lacks a unique supply), notably when generating a
-        -- typedef for foreign-export-dynamic. The Type, which is
-        -- obtained from the foreign import declaration itself, is
-        -- needed by the stg-to-cmm pass to determine the offset to
-        -- apply to unlifted boxed arguments in StgCmmForeign.
-        -- See Note [Unlifted boxed arguments to foreign calls]
+  | StgFCallOp ForeignCall Type
+        -- The Type, which is obtained from the foreign import declaration
+        -- itself, is needed by the stg-to-cmm pass to determine the offset to
+        -- apply to unlifted boxed arguments in StgCmmForeign. See Note
+        -- [Unlifted boxed arguments to foreign calls]
 
 {-
 ************************************************************************
@@ -864,7 +860,7 @@ pprStgAlt indent (con, params, expr)
 pprStgOp :: StgOp -> SDoc
 pprStgOp (StgPrimOp  op)   = ppr op
 pprStgOp (StgPrimCallOp op)= ppr op
-pprStgOp (StgFCallOp op _ _) = ppr op
+pprStgOp (StgFCallOp op _) = ppr op
 
 instance Outputable AltType where
   ppr PolyAlt         = text "Polymorphic"



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/71e75ba6d892e8dfb6794f0ce70d01c9521b77c5

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/commit/71e75ba6d892e8dfb6794f0ce70d01c9521b77c5
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20190613/34424c29/attachment-0001.html>


More information about the ghc-commits mailing list