diff options
-rw-r--r-- | compiler/rename/RnPat.hs | 7 | ||||
-rw-r--r-- | testsuite/tests/th/T12130.hs | 8 | ||||
-rw-r--r-- | testsuite/tests/th/T12130a.hs | 17 | ||||
-rw-r--r-- | testsuite/tests/th/all.T | 2 |
4 files changed, 31 insertions, 3 deletions
diff --git a/compiler/rename/RnPat.hs b/compiler/rename/RnPat.hs index 98ca38bf66..d252f7fef0 100644 --- a/compiler/rename/RnPat.hs +++ b/compiler/rename/RnPat.hs @@ -635,7 +635,7 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) find_tycon :: GlobalRdrEnv -> Name {- DataCon -} -> Maybe Name {- TyCon -} -- Return the parent *type constructor* of the data constructor -- (that is, the parent of the data constructor), - -- or 'Nothing' if it is a pattern synonym. + -- or 'Nothing' if it is a pattern synonym or not in scope. -- That's the parent to use for looking up record fields. find_tycon env con | Just (AConLike (RealDataCon dc)) <- wiredInNameTyThing_maybe con @@ -647,8 +647,9 @@ rnHsRecFields ctxt mk_arg (HsRecFields { rec_flds = flds, rec_dotdot = dotdot }) ParentIs p -> Just p _ -> Nothing - | otherwise - = pprPanic "find_tycon" (ppr con $$ ppr (lookupGRE_Name env con)) + | otherwise = Nothing + -- This can happen if the datacon is not in scope + -- and we are in a TH splice (Trac #12130) dup_flds :: [[RdrName]] -- Each list represents a RdrName that occurred more than once diff --git a/testsuite/tests/th/T12130.hs b/testsuite/tests/th/T12130.hs new file mode 100644 index 0000000000..7ab7492655 --- /dev/null +++ b/testsuite/tests/th/T12130.hs @@ -0,0 +1,8 @@ +{-# Language TemplateHaskell #-} +{-# Language DisambiguateRecordFields #-} + +module T12130 where + +import T12130a hiding (Block) + +b = $(block) diff --git a/testsuite/tests/th/T12130a.hs b/testsuite/tests/th/T12130a.hs new file mode 100644 index 0000000000..f393967e84 --- /dev/null +++ b/testsuite/tests/th/T12130a.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE TemplateHaskell #-} + +module T12130a where + +import Language.Haskell.TH + +data Block = Block + { blockSelector :: () + } + +block :: Q Exp +block = + [| Block { + -- Using record syntax is neccesary to trigger the bug. + blockSelector = () + } + |] diff --git a/testsuite/tests/th/all.T b/testsuite/tests/th/all.T index 75364dca98..bd59c4ee30 100644 --- a/testsuite/tests/th/all.T +++ b/testsuite/tests/th/all.T @@ -407,3 +407,5 @@ test('T11941', normal, compile_fail, ['-v0']) test('T11484', normal, compile, ['-v0']) test('T8761', unless(ghc_dynamic(), expect_broken(12077)), compile, ['-v0 -ddump-splices -dsuppress-uniques']) +test('T12130', extra_clean(['T12130a.hi','T12130a.o']), + multimod_compile, ['T12130', '-v0 ' + config.ghc_th_way_flags]) |