[Git][ghc/ghc][wip/int-index/p2tp] Comments, style, tests
Vladislav Zavialov (@int-index)
gitlab at gitlab.haskell.org
Wed Nov 29 22:58:15 UTC 2023
Vladislav Zavialov pushed to branch wip/int-index/p2tp at Glasgow Haskell Compiler / GHC
Commits:
08669455 by Vladislav Zavialov at 2023-11-30T01:57:18+03:00
Comments, style, tests
- - - - -
5 changed files:
- compiler/GHC/Tc/Errors/Types/PromotionErr.hs
- compiler/GHC/Tc/Gen/Head.hs
- compiler/GHC/Tc/Gen/Pat.hs
- + testsuite/tests/vdq-rta/should_compile/T23739_nested.hs
- testsuite/tests/vdq-rta/should_compile/all.T
Changes:
=====================================
compiler/GHC/Tc/Errors/Types/PromotionErr.hs
=====================================
@@ -56,9 +56,9 @@ peCategory TypeVariablePE = "type variable"
-- The opposite of a promotion error (a demotion error, in a sense).
data TermLevelUseErr
- = TyConTE -- Type constructor used at term level, e.g. x = Int
- | ClassTE -- Class used at the term level, e.g. x = Functor
- | TyVarTE -- Type variable used at the term level, e.g. f (Proxy :: Proxy a) = a
+ = TyConTE -- Type constructor used at the term level, e.g. x = Int
+ | ClassTE -- Class used at the term level, e.g. x = Functor
+ | TyVarTE -- Type variable used at the term level, e.g. f (Proxy :: Proxy a) = a
deriving (Generic)
teCategory :: TermLevelUseErr -> String
=====================================
compiler/GHC/Tc/Gen/Head.hs
=====================================
@@ -1233,9 +1233,9 @@ result in the same error. And it especially shouldn't suggest using `nap`
instead of `nap`, which is absurd.
The proper solution is to overhaul the hint system to consider what a name
-stands for instead of looking at its namespace alone. As a temporary measure,
-we avoid those potentially misleading hints by suppressing entirely them if
-RequiredTypeArguments is in effect.
+stands for instead of looking at its namespace alone. This is tracked in #24231.
+As a temporary measure, we avoid those potentially misleading hints by
+suppressing them entirely if RequiredTypeArguments is in effect.
-}
check_local_id :: Id -> TcM ()
=====================================
compiler/GHC/Tc/Gen/Pat.hs
=====================================
@@ -399,14 +399,20 @@ tc_forall_pat _ (pat, tv) thing_inside
; return (pat', result) }
-- Convert a Pat into the equivalent HsTyPat.
+-- See `expr_to_type` (GHC.Tc.Gen.App) for the HsExpr counterpart.
+-- The `TcM` monad is only used to fail on ill-formed type patterns.
pat_to_type_pat :: Pat GhcRn -> TcM (HsTyPat GhcRn)
pat_to_type_pat (EmbTyPat _ _ tp) = return tp
pat_to_type_pat (VarPat _ lname) = return (HsTP x b)
- where x = HsTPRn [] [] [unLoc lname]
- b = noLocA (HsTyVar noAnn NotPromoted lname)
+ where b = noLocA (HsTyVar noAnn NotPromoted lname)
+ x = HsTPRn { hstp_nwcs = []
+ , hstp_imp_tvs = []
+ , hstp_exp_tvs = [unLoc lname] }
pat_to_type_pat (WildPat _) = return (HsTP x b)
- where x = HsTPRn [] [] []
- b = noLocA (HsWildCardTy noExtField)
+ where b = noLocA (HsWildCardTy noExtField)
+ x = HsTPRn { hstp_nwcs = []
+ , hstp_imp_tvs = []
+ , hstp_exp_tvs = [] }
pat_to_type_pat (SigPat _ pat sig_ty)
= do { HsTP x_hstp t <- pat_to_type_pat (unLoc pat)
; let { !(HsPS x_hsps k) = sig_ty
@@ -424,7 +430,20 @@ pat_to_type_pat (SigPat _ pat sig_ty)
pat_to_type_pat (ParPat _ _ pat _)
= do { HsTP x t <- pat_to_type_pat (unLoc pat)
; return (HsTP x (noLocA (HsParTy noAnn t))) }
-pat_to_type_pat pat = failWith $ TcRnIllformedTypePattern pat
+pat_to_type_pat pat =
+ -- There are other cases to handle (ConPat, ListPat, TuplePat, etc), but these
+ -- would always be rejected by the unification in `tcHsTyPat`, so it's fine to
+ -- skip them here. This won't continue to be the case when visible forall is
+ -- permitted in data constructors:
+ --
+ -- data T a where { Typed :: forall a -> a -> T a }
+ -- g :: T Int -> Int
+ -- g (Typed Int x) = x -- Note the `Int` type pattern
+ --
+ -- See ticket #18389. When this feature lands, it would be best to extend
+ -- `pat_to_type_pat` to handle as many pattern forms as possible.
+ failWith $ TcRnIllformedTypePattern pat
+ -- This failure is the only use of the TcM monad in `pat_to_type_pat`
tc_ty_pat :: HsTyPat GhcRn -> TcTyVar -> TcM r -> TcM (TcType, r)
tc_ty_pat tp tv thing_inside
=====================================
testsuite/tests/vdq-rta/should_compile/T23739_nested.hs
=====================================
@@ -0,0 +1,9 @@
+{-# LANGUAGE ExplicitNamespaces #-}
+{-# LANGUAGE RequiredTypeArguments #-}
+
+module T23739_nested where
+
+import Data.Kind
+
+f :: forall a -> a -> a
+f ((type t) :: Type) x = x :: t
\ No newline at end of file
=====================================
testsuite/tests/vdq-rta/should_compile/all.T
=====================================
@@ -21,6 +21,7 @@ test('T23739_sig', normal, compile, [''])
test('T23739_sizeOf', normal, compile, [''])
test('T23739_symbolVal', normal, compile, [''])
test('T23739_typeRep', normal, compile, [''])
+test('T23739_nested', normal, compile, [''])
test('T22326_th_dump1', req_th, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T23739_th_dump1', req_th, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/086694557072fe853066c2cecf9e36d080669aa4
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/086694557072fe853066c2cecf9e36d080669aa4
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/20231129/4b12dff4/attachment-0001.html>
More information about the ghc-commits
mailing list