diff --git a/compiler/typecheck/TcSimplify.hs b/compiler/typecheck/TcSimplify.hs index 08c781d78c577b0ffa3e72fd89bc084c77b321f9..b92ebfd8626e93c51f878a88b3e2aea959404f82 100644 --- a/compiler/typecheck/TcSimplify.hs +++ b/compiler/typecheck/TcSimplify.hs @@ -649,9 +649,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds psig_givens = mkGivens loc psig_theta_vars ; _ <- solveSimpleGivens psig_givens -- See Note [Add signature contexts as givens] - ; wanteds' <- solveWanteds wanteds - ; TcS.zonkWC wanteds' } - + ; solveWanteds wanteds } -- Find quant_pred_candidates, the predicates that -- we'll consider quantifying over @@ -659,6 +657,7 @@ simplifyInfer rhs_tclvl infer_mode sigs name_taus wanteds -- the psig_theta; it's just the extra bit -- NB2: We do not do any defaulting when inferring a type, this can lead -- to less polymorphic types, see Note [Default while Inferring] + ; wanted_transformed_incl_derivs <- TcM.zonkWC wanted_transformed_incl_derivs ; let definite_error = insolubleWC wanted_transformed_incl_derivs -- See Note [Quantification with errors] -- NB: must include derived errors in this test, diff --git a/testsuite/tests/partial-sigs/should_compile/T14715.hs b/testsuite/tests/partial-sigs/should_compile/T14715.hs new file mode 100644 index 0000000000000000000000000000000000000000..1a902ac44f3ef62f0e398ad886557e087b8f4142 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T14715.hs @@ -0,0 +1,19 @@ +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MultiParamTypeClasses #-} +{-# LANGUAGE PartialTypeSignatures #-} +{-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TypeFamilies #-} +module T14715 (bench_mulPublic) where + +data Cyc r +data CT zp r'q +class Reduce a b +type family LiftOf b + +bench_mulPublic :: forall z zp zq . (z ~ LiftOf zq, _) => Cyc zp -> Cyc z -> IO (zp,zq) +bench_mulPublic pt sk = do + ct :: CT zp (Cyc zq) <- encrypt sk pt + undefined ct + +encrypt :: forall z zp zq. Reduce z zq => Cyc z -> Cyc zp -> IO (CT zp (Cyc zq)) +encrypt = undefined diff --git a/testsuite/tests/partial-sigs/should_compile/T14715.stderr b/testsuite/tests/partial-sigs/should_compile/T14715.stderr new file mode 100644 index 0000000000000000000000000000000000000000..0519ecba6ea913e21689ec692e81e9e4973fbf73 --- /dev/null +++ b/testsuite/tests/partial-sigs/should_compile/T14715.stderr @@ -0,0 +1 @@ + \ No newline at end of file diff --git a/testsuite/tests/partial-sigs/should_compile/all.T b/testsuite/tests/partial-sigs/should_compile/all.T index d13af5ca17a1f3bfc433e030d3bfa272f8d3e478..ebf6338c869b364d0c2c3708142d569e63c4324b 100644 --- a/testsuite/tests/partial-sigs/should_compile/all.T +++ b/testsuite/tests/partial-sigs/should_compile/all.T @@ -73,4 +73,5 @@ test('T13482', normal, compile, ['']) test('T14217', normal, compile_fail, ['']) test('T14643', normal, compile, ['']) test('T14643a', normal, compile, ['']) +test('T14715', normal, compile, [''])