summaryrefslogtreecommitdiff
path: root/compiler/GHC/Hs/Expr.hs
diff options
context:
space:
mode:
authorAlan Zimmerman <alan.zimm@gmail.com>2022-07-01 12:52:29 +0100
committerMarge Bot <ben+marge-bot@smart-cactus.org>2022-08-11 16:19:57 -0400
commitff67c79ee742024ca0ef41a9a7e540e1662d46bd (patch)
tree6588e16a80e86696f7541c483a724903b82ad492 /compiler/GHC/Hs/Expr.hs
parent5c24b1b3a9d6a4c2f471fd7d8ec65141a8b46357 (diff)
downloadhaskell-ff67c79ee742024ca0ef41a9a7e540e1662d46bd.tar.gz
EPA: DotFieldOcc does not have exact print annotations
For the code {-# LANGUAGE OverloadedRecordUpdate #-} operatorUpdate f = f{(+) = 1} There are no exact print annotations for the parens around the + symbol, nor does normal ppr print them. This MR fixes that. Closes #21805 Updates haddock submodule
Diffstat (limited to 'compiler/GHC/Hs/Expr.hs')
-rw-r--r--compiler/GHC/Hs/Expr.hs14
1 files changed, 10 insertions, 4 deletions
diff --git a/compiler/GHC/Hs/Expr.hs b/compiler/GHC/Hs/Expr.hs
index 405b772199..5b2ee9dc73 100644
--- a/compiler/GHC/Hs/Expr.hs
+++ b/compiler/GHC/Hs/Expr.hs
@@ -37,7 +37,7 @@ import GHC.Hs.Decls() -- import instances
import GHC.Hs.Pat
import GHC.Hs.Lit
import Language.Haskell.Syntax.Extension
-import Language.Haskell.Syntax.Basic (FieldLabelString)
+import Language.Haskell.Syntax.Basic (FieldLabelString(..))
import GHC.Hs.Extension
import GHC.Hs.Type
import GHC.Hs.Binds
@@ -46,6 +46,7 @@ import GHC.Parser.Annotation
-- others:
import GHC.Tc.Types.Evidence
import GHC.Types.Name
+import GHC.Types.Name.Reader
import GHC.Types.Name.Set
import GHC.Types.Basic
import GHC.Types.Fixity
@@ -2121,8 +2122,11 @@ pprFieldLabelStrings :: forall p. (UnXRec p, Outputable (XRec p FieldLabelString
pprFieldLabelStrings (FieldLabelStrings flds) =
hcat (punctuate dot (map (ppr . unXRec @p) flds))
-instance Outputable(XRec p FieldLabelString) => Outputable (DotFieldOcc p) where
- ppr (DotFieldOcc _ s) = ppr s
+pprPrefixFastString :: FastString -> SDoc
+pprPrefixFastString fs = pprPrefixOcc (mkVarUnqual fs)
+
+instance UnXRec p => Outputable (DotFieldOcc p) where
+ ppr (DotFieldOcc _ s) = (pprPrefixFastString . field_label . unXRec @p) s
ppr XDotFieldOcc{} = text "XDotFieldOcc"
{-
@@ -2157,8 +2161,10 @@ type instance Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsExpr
type instance Anno [LocatedA (StmtLR (GhcPass pl) (GhcPass pr) (LocatedA (HsCmd (GhcPass pr))))] = SrcSpanAnnL
type instance Anno (FieldLabelStrings (GhcPass p)) = SrcAnn NoEpAnns
+type instance Anno FieldLabelString = SrcSpanAnnN
+
type instance Anno FastString = SrcAnn NoEpAnns
- -- NB: type FieldLabelString = FastString
+ -- Used in HsQuasiQuote and perhaps elsewhere
type instance Anno (DotFieldOcc (GhcPass p)) = SrcAnn NoEpAnns