[commit: ghc] wip/T14068: Remove modifyJoinResTy (2e513a6)

git at git.haskell.org git at git.haskell.org
Wed Aug 2 03:07:10 UTC 2017


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

On branch  : wip/T14068
Link       : http://ghc.haskell.org/trac/ghc/changeset/2e513a6dbde8308768d793ccf285377e3ed231b8/ghc

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

commit 2e513a6dbde8308768d793ccf285377e3ed231b8
Author: Joachim Breitner <mail at joachim-breitner.de>
Date:   Tue Aug 1 22:27:34 2017 -0400

    Remove modifyJoinResTy
    
    only used in setJoinResTy, so lets just have that one.


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

2e513a6dbde8308768d793ccf285377e3ed231b8
 compiler/types/Type.hs | 24 ++++++++----------------
 1 file changed, 8 insertions(+), 16 deletions(-)

diff --git a/compiler/types/Type.hs b/compiler/types/Type.hs
index b81192f..50a35b0 100644
--- a/compiler/types/Type.hs
+++ b/compiler/types/Type.hs
@@ -61,7 +61,7 @@ module Type (
         filterOutInvisibleTyVars, partitionInvisibles,
         synTyConResKind,
 
-        modifyJoinResTy, setJoinResTy,
+        setJoinResTy,
 
         -- Analyzing types
         TyCoMapper(..), mapType, mapCoercion,
@@ -2439,25 +2439,17 @@ splitVisVarsOfType orig_ty = Pair invis_vars vis_vars
 splitVisVarsOfTypes :: [Type] -> Pair TyCoVarSet
 splitVisVarsOfTypes = foldMap splitVisVarsOfType
 
-modifyJoinResTy :: Int            -- Number of binders to skip
-                -> (Type -> Type) -- Function to apply to result type
-                -> Type           -- Type of join point
-                -> Type           -- New type
+setJoinResTy :: Int  -- Number of binders to skip
+             -> Type -- New result type
+             -> Type -- Type of join point
+             -> Type -- New type
 -- INVARIANT: If any of the first n binders are foralls, those tyvars cannot
 -- appear in the original result type. See isValidJoinPointType.
-modifyJoinResTy orig_ar f orig_ty
+setJoinResTy orig_ar new_res_ty orig_ty
   = go orig_ar orig_ty
   where
-    go 0 ty = f ty
+    go 0 _  = new_res_ty
     go n ty | Just (arg_bndr, res_ty) <- splitPiTy_maybe ty
             = mkPiTy arg_bndr (go (n-1) res_ty)
             | otherwise
-            = pprPanic "modifyJoinResTy" (ppr orig_ar <+> ppr orig_ty)
-
-setJoinResTy :: Int  -- Number of binders to skip
-             -> Type -- New result type
-             -> Type -- Type of join point
-             -> Type -- New type
--- INVARIANT: Same as for modifyJoinResTy
-setJoinResTy ar new_res_ty ty
-  = modifyJoinResTy ar (const new_res_ty) ty
+            = pprPanic "setJoinResTy" (ppr orig_ar <+> ppr orig_ty)



More information about the ghc-commits mailing list