diff --git a/compiler/GHC/HsToCore/GuardedRHSs.hs b/compiler/GHC/HsToCore/GuardedRHSs.hs
index 24db0f064935c74209f83e2bf70cb6e4510ff4e6..07f94906cddc2bdd34e3db9a79c077043d069f0c 100644
--- a/compiler/GHC/HsToCore/GuardedRHSs.hs
+++ b/compiler/GHC/HsToCore/GuardedRHSs.hs
@@ -130,7 +130,7 @@ matchGuards (BindStmt _ pat bind_rhs : stmts) ctx rhs rhs_ty = do
     core_rhs <- dsLExpr bind_rhs
     match_result' <- matchSinglePatVar match_var (StmtCtxt ctx) pat rhs_ty
                                        match_result
-    pure $ adjustMatchResult (bindNonRec match_var core_rhs) match_result'
+    pure $ bindNonRec match_var core_rhs <$> match_result'
 
 matchGuards (LastStmt  {} : _) _ _ _ = panic "matchGuards LastStmt"
 matchGuards (ParStmt   {} : _) _ _ _ = panic "matchGuards ParStmt"
diff --git a/compiler/GHC/HsToCore/Match.hs b/compiler/GHC/HsToCore/Match.hs
index dbdd24cbac749d7d1335a2eee143ccc38cdc5808..875542d4f898739ea27d4c285adc1b582991711e 100644
--- a/compiler/GHC/HsToCore/Match.hs
+++ b/compiler/GHC/HsToCore/Match.hs
@@ -198,8 +198,9 @@ match (v:vs) ty eqns    -- Eqns *can* be empty
         ; whenDOptM Opt_D_dump_view_pattern_commoning (debug grouped)
 
         ; match_results <- match_groups grouped
-        ; return (adjustMatchResult (foldr (.) id aux_binds) $
-                  foldr1 combineMatchResults match_results) }
+        ; return $ foldr (.) id aux_binds <$>
+            foldr1 combineMatchResults match_results
+        }
   where
     vars = v :| vs
 
@@ -844,7 +845,8 @@ matchSinglePat (Var var) ctx pat ty match_result
 matchSinglePat scrut hs_ctx pat ty match_result
   = do { var           <- selectSimpleMatchVarL pat
        ; match_result' <- matchSinglePatVar var hs_ctx pat ty match_result
-       ; return (adjustMatchResult (bindNonRec var scrut) match_result') }
+       ; return $ bindNonRec var scrut <$> match_result'
+       }
 
 matchSinglePatVar :: Id   -- See Note [Match Ids]
                   -> HsMatchContext GhcRn -> LPat GhcTc
diff --git a/compiler/GHC/HsToCore/Match/Constructor.hs b/compiler/GHC/HsToCore/Match/Constructor.hs
index 779d893eaf5b05fa33269ae4b24f6a867e9c2c1e..b3c639ca8633cec549319a1407fc44768a05fabf 100644
--- a/compiler/GHC/HsToCore/Match/Constructor.hs
+++ b/compiler/GHC/HsToCore/Match/Constructor.hs
@@ -141,7 +141,8 @@ matchOneConLike vars ty (eqn1 :| eqns)   -- All eqns for a single constructor
                   do { (wraps, eqns') <- liftM unzip (mapM shift arg_eqn_prs)
                      ; let group_arg_vars = select_arg_vars arg_vars arg_eqn_prs
                      ; match_result <- match (group_arg_vars ++ vars) ty eqns'
-                     ; return (adjustMatchResult (foldr1 (.) wraps) match_result) }
+                     ; return $ foldr1 (.) wraps <$> match_result
+                     }
 
               shift (_, eqn@(EqnInfo { eqn_pats = ConPatOut{ pat_tvs = tvs, pat_dicts = ds,
                                                              pat_binds = bind, pat_args = args
diff --git a/compiler/GHC/HsToCore/Match/Literal.hs b/compiler/GHC/HsToCore/Match/Literal.hs
index d835e62e42b9c73a4a50d0eee36baefd02cbd732..acb5be40f404c4e6d45c6d602aa2197505f0167f 100644
--- a/compiler/GHC/HsToCore/Match/Literal.hs
+++ b/compiler/GHC/HsToCore/Match/Literal.hs
@@ -515,7 +515,7 @@ matchNPlusKPats (var :| vars) ty (eqn1 :| eqns)
         ; match_result <- match vars ty eqns'
         ; return  (mkGuardedMatchResult pred_expr               $
                    mkCoLetMatchResult (NonRec n1 minusk_expr)   $
-                   adjustMatchResult (foldr1 (.) wraps)         $
+                   fmap (foldr1 (.) wraps)                      $
                    match_result) }
   where
     shift n1 eqn@(EqnInfo { eqn_pats = NPlusKPat _ (L _ n) _ _ _ _ : pats })
diff --git a/compiler/GHC/HsToCore/Utils.hs b/compiler/GHC/HsToCore/Utils.hs
index 5982a07dde7c7fe37cd1eda2fd9529dd6c134fd2..308f0a14f54ee03c3bec58b0bdc539dde890b7a6 100644
--- a/compiler/GHC/HsToCore/Utils.hs
+++ b/compiler/GHC/HsToCore/Utils.hs
@@ -22,7 +22,7 @@ module GHC.HsToCore.Utils (
         MatchResult'(..), MatchResult, CaseAlt(..),
         cantFailMatchResult, alwaysFailMatchResult,
         extractMatchResult, combineMatchResults,
-        adjustMatchResult,  adjustMatchResultDs,
+        adjustMatchResultDs,
         shareFailureHandler,
         mkCoLetMatchResult, mkViewMatchResult, mkGuardedMatchResult,
         matchCanFail, mkEvalMatchResult,
@@ -225,9 +225,6 @@ combineMatchResults match_result1 match_result2 =
       -- Before actually failing, try the next match arm.
       body_fn1 =<< runMatchResult fail_expr match_result2
 
-adjustMatchResult :: (a -> b) -> MatchResult' a -> MatchResult' b
-adjustMatchResult = fmap
-
 adjustMatchResultDs :: (a -> DsM b) -> MatchResult' a -> MatchResult' b
 adjustMatchResultDs encl_fn = \case
   MR_Infallible body_fn -> MR_Infallible $
@@ -248,17 +245,16 @@ seqVar :: Var -> CoreExpr -> CoreExpr
 seqVar var body = mkDefaultCase (Var var) var body
 
 mkCoLetMatchResult :: CoreBind -> MatchResult -> MatchResult
-mkCoLetMatchResult bind = adjustMatchResult (mkCoreLet bind)
+mkCoLetMatchResult bind = fmap (mkCoreLet bind)
 
 -- (mkViewMatchResult var' viewExpr mr) makes the expression
 -- let var' = viewExpr in mr
 mkViewMatchResult :: Id -> CoreExpr -> MatchResult -> MatchResult
-mkViewMatchResult var' viewExpr =
-    adjustMatchResult (mkCoreLet (NonRec var' viewExpr))
+mkViewMatchResult var' viewExpr = fmap $ mkCoreLet $ NonRec var' viewExpr
 
 mkEvalMatchResult :: Id -> Type -> MatchResult -> MatchResult
-mkEvalMatchResult var ty
-  = adjustMatchResult (\e -> Case (Var var) var ty [(DEFAULT, [], e)])
+mkEvalMatchResult var ty = fmap $ \e ->
+  Case (Var var) var ty [(DEFAULT, [], e)]
 
 mkGuardedMatchResult :: CoreExpr -> MatchResult -> MatchResult
 mkGuardedMatchResult pred_expr mr = MR_Fallible $ \fail -> do