
Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC Commits: 8adfc222 by sheaf at 2025-08-28T19:47:17-04:00 Fix orientation in HsWrapper composition (<.>) This commit fixes the order in which WpCast HsWrappers are composed, fixing a bug introduced in commit 56b32c5a2d5d7cad89a12f4d74dc940e086069d1. Fixes #26350 - - - - - 4 changed files: - compiler/GHC/Tc/Gen/App.hs - compiler/GHC/Tc/Types/Evidence.hs - + testsuite/tests/typecheck/should_compile/T26350.hs - testsuite/tests/typecheck/should_compile/all.T Changes: ===================================== compiler/GHC/Tc/Gen/App.hs ===================================== @@ -430,7 +430,7 @@ tcApp rn_expr exp_res_ty -- Step 5.2: typecheck the arguments, and monomorphise -- any un-unified instantiation variables ; tc_args <- tcValArgs DoQL inst_args - -- Step 5.3: zonk to expose the polymophism hidden under + -- Step 5.3: zonk to expose the polymorphism hidden under -- QuickLook instantiation variables in `app_res_rho` ; app_res_rho <- liftZonkM $ zonkTcType app_res_rho -- Step 5.4: subsumption check against the expected type ===================================== compiler/GHC/Tc/Types/Evidence.hs ===================================== @@ -206,9 +206,15 @@ instance Monoid HsWrapper where (<.>) :: HsWrapper -> HsWrapper -> HsWrapper WpHole <.> c = c c <.> WpHole = c -WpCast c1 <.> WpCast c2 = WpCast (c1 `mkTransCo` c2) +WpCast c1 <.> WpCast c2 = WpCast (c2 `mkTransCo` c1) -- If we can represent the HsWrapper as a cast, try to do so: this may avoid -- unnecessary eta-expansion (see 'mkWpFun'). + -- + -- NB: <.> behaves like function composition: + -- + -- WpCast c1 <.> WpCast c2 :: coercionLKind c2 ~> coercionRKind c1 + -- + -- This is thus the same as WpCast (c2 ; c1) and not WpCast (c1 ; c2). c1 <.> c2 = c1 `WpCompose` c2 -- | Smart constructor to create a 'WpFun' 'HsWrapper', which avoids introducing ===================================== testsuite/tests/typecheck/should_compile/T26350.hs ===================================== @@ -0,0 +1,18 @@ +{-# LANGUAGE DeepSubsumption #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE TypeOperators #-} + +{-# OPTIONS_GHC -dcore-lint #-} + +module T26350 where + +import Control.Arrow (first) + +infix 6 .-. + +class AffineSpace p where + type Diff p + (.-.) :: p -> p -> Diff p + +affineCombo :: (AffineSpace p, v ~ Diff p) => p -> (p,v) -> (v,v) +affineCombo z l = first (.-. z) l ===================================== testsuite/tests/typecheck/should_compile/all.T ===================================== @@ -862,6 +862,7 @@ test('DeepSubsumption06', normal, compile, ['-XHaskell98']) test('DeepSubsumption07', normal, compile, ['-XHaskell2010']) test('DeepSubsumption08', normal, compile, ['']) test('DeepSubsumption09', normal, compile, ['']) +test('T26350', normal, compile, ['']) test('T26225', normal, compile, ['']) test('T26225b', normal, compile, ['']) test('T21765', normal, compile, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8adfc22242b068417acc43cc682b79ff... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8adfc22242b068417acc43cc682b79ff... You're receiving this email because of your account on gitlab.haskell.org.