summaryrefslogtreecommitdiff
path: root/testsuite/tests/th
diff options
context:
space:
mode:
authorsheaf <sam.derbyshire@gmail.com>2023-03-17 12:48:21 +0100
committersheaf <sam.derbyshire@gmail.com>2023-03-29 13:57:33 +0200
commit3f374399e2dbebcdfe5bc31f94fc502b46d0cf4f (patch)
treea5103e3d597c2d724173e070a22759ce50a9d2e7 /testsuite/tests/th
parent76bb4c586084d7fdcf0e5ce52623abbfca527c55 (diff)
downloadhaskell-3f374399e2dbebcdfe5bc31f94fc502b46d0cf4f.tar.gz
Handle records in the renamer
This patch moves the field-based logic for disambiguating record updates to the renamer. The type-directed logic, scheduled for removal, remains in the typechecker. To do this properly (and fix the myriad of bugs surrounding the treatment of duplicate record fields), we took the following main steps: 1. Create GREInfo, a renamer-level equivalent to TyThing which stores information pertinent to the renamer. This allows us to uniformly treat imported and local Names in the renamer, as described in Note [GREInfo]. 2. Remove GreName. Instead of a GlobalRdrElt storing GreNames, which distinguished between normal names and field names, we now store simple Names in GlobalRdrElt, along with the new GREInfo information which allows us to recover the FieldLabel for record fields. 3. Add namespacing for record fields, within the OccNames themselves. This allows us to remove the mangling of duplicate field selectors. This change ensures we don't print mangled names to the user in error messages, and allows us to handle duplicate record fields in Template Haskell. 4. Move record disambiguation to the renamer, and operate on the level of data constructors instead, to handle #21443. The error message text for ambiguous record updates has also been changed to reflect that type-directed disambiguation is on the way out. (3) means that OccEnv is now a bit more complex: we first key on the textual name, which gives an inner map keyed on NameSpace: OccEnv a ~ FastStringEnv (UniqFM NameSpace a) Note that this change, along with (2), both increase the memory residency of GlobalRdrEnv = OccEnv [GlobalRdrElt], which causes a few tests to regress somewhat in compile-time allocation. Even though (3) simplified a lot of code (in particular the treatment of field selectors within Template Haskell and in error messages), it came with one important wrinkle: in the situation of -- M.hs-boot module M where { data A; foo :: A -> Int } -- M.hs module M where { data A = MkA { foo :: Int } } we have that M.hs-boot exports a variable foo, which is supposed to match with the record field foo that M exports. To solve this issue, we add a new impedance-matching binding to M foo{var} = foo{fld} This mimics the logic that existed already for impedance-binding DFunIds, but getting it right was a bit tricky. See Note [Record field impedance matching] in GHC.Tc.Module. We also needed to be careful to avoid introducing space leaks in GHCi. So we dehydrate the GlobalRdrEnv before storing it anywhere, e.g. in ModIface. This means stubbing out all the GREInfo fields, with the function forceGlobalRdrEnv. When we read it back in, we rehydrate with rehydrateGlobalRdrEnv. This robustly avoids any space leaks caused by retaining old type environments. Fixes #13352 #14848 #17381 #17551 #19664 #21443 #21444 #21720 #21898 #21946 #21959 #22125 #22160 #23010 #23062 #23063 Updates haddock submodule ------------------------- Metric Increase: MultiComponentModules MultiLayerModules MultiLayerModulesDefsGhci MultiLayerModulesNoCode T13701 T14697 hard_hole_fits -------------------------
Diffstat (limited to 'testsuite/tests/th')
-rw-r--r--testsuite/tests/th/T10279.stderr7
-rw-r--r--testsuite/tests/th/T10828.hs5
-rw-r--r--testsuite/tests/th/T10828b.hs3
-rw-r--r--testsuite/tests/th/T10828b.stderr2
-rw-r--r--testsuite/tests/th/T11345.hs5
-rw-r--r--testsuite/tests/th/T11941.stderr8
-rw-r--r--testsuite/tests/th/T17379a.hs8
-rw-r--r--testsuite/tests/th/T17379a.stderr4
-rw-r--r--testsuite/tests/th/T17379b.hs8
-rw-r--r--testsuite/tests/th/T17379b.stderr4
-rw-r--r--testsuite/tests/th/all.T2
11 files changed, 18 insertions, 38 deletions
diff --git a/testsuite/tests/th/T10279.stderr b/testsuite/tests/th/T10279.stderr
index 5993cdbf82..4a06b1d775 100644
--- a/testsuite/tests/th/T10279.stderr
+++ b/testsuite/tests/th/T10279.stderr
@@ -4,5 +4,8 @@ T10279.hs:10:9: error: [GHC-52243]
no unit id matching ‘rts-1.0.2’ was found
(This unit ID looks like the source package ID;
the real unit ID is ‘rts’)
- • In the expression: rts-1.0.2:A.Foo
- In an equation for ‘blah’: blah = (rts-1.0.2:A.Foo)
+ • In the untyped splice:
+ $(conE
+ (Name
+ (mkOccName "Foo")
+ (NameG VarName (mkPkgName "rts-1.0.2") (mkModName "A"))))
diff --git a/testsuite/tests/th/T10828.hs b/testsuite/tests/th/T10828.hs
index ffb4525f6a..d73b5015ae 100644
--- a/testsuite/tests/th/T10828.hs
+++ b/testsuite/tests/th/T10828.hs
@@ -6,6 +6,7 @@ module T10828 where
import Language.Haskell.TH hiding (Type)
import System.IO
import Data.Kind (Type)
+import qualified Data.List.NonEmpty as NE ( singleton )
$( do { decl <- [d| data family D a :: Type -> Type
data instance D Int Bool :: Type where
@@ -33,7 +34,7 @@ $( return
[ DataD [] (mkName "T")
[ PlainTV (mkName "a") () ]
(Just StarT)
- [ GadtC [(mkName "MkT")]
+ [ GadtC (NE.singleton (mkName "MkT"))
[ ( Bang NoSourceUnpackedness NoSourceStrictness
, VarT (mkName "a")
)
@@ -46,7 +47,7 @@ $( return
, ForallC [PlainTV (mkName "a") SpecifiedSpec, PlainTV (mkName "b") SpecifiedSpec]
[AppT (AppT EqualityT (VarT $ mkName "a" ) )
(ConT $ mkName "Int") ] $
- RecGadtC [(mkName "MkC")]
+ RecGadtC (NE.singleton (mkName "MkC"))
[ ( mkName "foo"
, Bang NoSourceUnpackedness NoSourceStrictness
, VarT (mkName "a")
diff --git a/testsuite/tests/th/T10828b.hs b/testsuite/tests/th/T10828b.hs
index 03706d6b7c..36e91eb11a 100644
--- a/testsuite/tests/th/T10828b.hs
+++ b/testsuite/tests/th/T10828b.hs
@@ -4,6 +4,7 @@ module T10828b where
import Language.Haskell.TH
import System.IO
+import qualified Data.List.NonEmpty as NE ( singleton )
-- attempting to mix GADT and normal constructors
$( return
@@ -23,7 +24,7 @@ $( return
[AppT (AppT EqualityT (VarT $ mkName "a" ) )
(ConT $ mkName "Int") ] $
RecGadtC
- [ (mkName "MkC")]
+ (NE.singleton (mkName "MkC"))
[ ( mkName "foo"
, Bang NoSourceUnpackedness NoSourceStrictness
, VarT (mkName "a")
diff --git a/testsuite/tests/th/T10828b.stderr b/testsuite/tests/th/T10828b.stderr
index 357c86c458..6e78ca9087 100644
--- a/testsuite/tests/th/T10828b.stderr
+++ b/testsuite/tests/th/T10828b.stderr
@@ -1,5 +1,5 @@
-T10828b.hs:9:2: error: [GHC-24104]
+T10828b.hs:10:2: error: [GHC-24104]
Cannot mix GADT constructors with Haskell 98 constructors
When splicing a TH declaration:
data T a :: *
diff --git a/testsuite/tests/th/T11345.hs b/testsuite/tests/th/T11345.hs
index 2288cdad15..11de6d8bd5 100644
--- a/testsuite/tests/th/T11345.hs
+++ b/testsuite/tests/th/T11345.hs
@@ -5,6 +5,7 @@
module Main (main) where
import Language.Haskell.TH
+import qualified Data.List.NonEmpty as NE ( singleton )
infixr 7 :***:
data GADT a where
@@ -16,11 +17,11 @@ $(do gadtName <- newName "GADT2"
infixName <- newName ":****:"
a <- newName "a"
return [ DataD [] gadtName [KindedTV a () StarT] Nothing
- [ GadtC [prefixName]
+ [ GadtC (NE.singleton prefixName)
[ (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
, (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
] (AppT (ConT gadtName) (ConT ''Int))
- , GadtC [infixName]
+ , GadtC (NE.singleton infixName)
[ (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
, (Bang NoSourceUnpackedness NoSourceStrictness,ConT ''Int)
] (AppT (ConT gadtName) (ConT ''Int))
diff --git a/testsuite/tests/th/T11941.stderr b/testsuite/tests/th/T11941.stderr
index 39a25c7425..7a66251092 100644
--- a/testsuite/tests/th/T11941.stderr
+++ b/testsuite/tests/th/T11941.stderr
@@ -1,7 +1,7 @@
-T11941.hs:7:30: error: [GHC-76037]
- Not in scope: ‘getFrst’
+T11941.hs:7:30: error: [GHC-22385]
+ Not in scope: record field ‘getFrst’
Suggested fix:
Perhaps use one of these:
- ‘getFirst’ (imported from Data.Monoid),
- ‘getLast’ (imported from Data.Monoid)
+ record field of First ‘getFirst’ (imported from Data.Monoid),
+ record field of Last ‘getLast’ (imported from Data.Monoid)
diff --git a/testsuite/tests/th/T17379a.hs b/testsuite/tests/th/T17379a.hs
deleted file mode 100644
index 66702bb9b8..0000000000
--- a/testsuite/tests/th/T17379a.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE GADTSyntax #-}
-
-module T17379a where
-
-import Language.Haskell.TH
-
-$(let typ = mkName "T" in pure [ DataD [] typ [] Nothing [GadtC [] [] (ConT typ)] [] ])
diff --git a/testsuite/tests/th/T17379a.stderr b/testsuite/tests/th/T17379a.stderr
deleted file mode 100644
index ebb899e750..0000000000
--- a/testsuite/tests/th/T17379a.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-T17379a.hs:8:2: error: [GHC-38140]
- GadtC must have at least one constructor name
- When splicing a TH declaration: data T where :: T
diff --git a/testsuite/tests/th/T17379b.hs b/testsuite/tests/th/T17379b.hs
deleted file mode 100644
index c83d180d18..0000000000
--- a/testsuite/tests/th/T17379b.hs
+++ /dev/null
@@ -1,8 +0,0 @@
-{-# LANGUAGE TemplateHaskell #-}
-{-# LANGUAGE GADTSyntax #-}
-
-module T17379b where
-
-import Language.Haskell.TH
-
-$(let typ = mkName "T" in pure [ DataD [] typ [] Nothing [RecGadtC [] [] (ConT typ)] [] ])
diff --git a/testsuite/tests/th/T17379b.stderr b/testsuite/tests/th/T17379b.stderr
deleted file mode 100644
index 9a4aabc250..0000000000
--- a/testsuite/tests/th/T17379b.stderr
+++ /dev/null
@@ -1,4 +0,0 @@
-
-T17379b.hs:8:2: error: [GHC-18816]
- RecGadtC must have at least one constructor name
- When splicing a TH declaration: data T where :: {} -> T
diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T
index a4f948bc76..2b792da6e2 100644
--- a/testsuite/tests/th/all.T
+++ b/testsuite/tests/th/all.T
@@ -504,8 +504,6 @@ test('T17296', normal, compile, ['-v0'])
test('T17305', normal, compile, ['-v0'])
test('T17380', normal, compile_fail, [''])
test('T17394', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
-test('T17379a', normal, compile_fail, [''])
-test('T17379b', normal, compile_fail, [''])
test('T17461', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])
test('T17511', normal, compile, [''])
test('T17608', normal, compile, ['-v0 -ddump-splices -dsuppress-uniques'])