summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
authorGHC GitLab CI <ghc-ci@gitlab-haskell.org>2021-03-23 08:32:31 +0000
committerMarge Bot <ben+marge-bot@smart-cactus.org>2021-03-25 04:53:16 -0400
commit1350a5cd730f1cbbe306b849def26bfcd119c103 (patch)
tree45c8b4ef2cd4b09d6f9a24da905a1be5ff5ee616 /compiler
parent0029df2bd52aa7f93e2254a369428e4261e5d3ae (diff)
downloadhaskell-1350a5cd730f1cbbe306b849def26bfcd119c103.tar.gz
EPA : Remove ApiAnn from ParsedModule
All the comments are now captured in the AST, there is no need for a side-channel structure for them.
Diffstat (limited to 'compiler')
-rw-r--r--compiler/GHC.hs12
-rw-r--r--compiler/GHC/Driver/Backpack.hs6
-rw-r--r--compiler/GHC/Driver/Main.hs10
-rw-r--r--compiler/GHC/Hs.hs5
-rw-r--r--compiler/GHC/Hs/Dump.hs4
-rw-r--r--compiler/GHC/Parser.y2
-rw-r--r--compiler/GHC/Parser/Annotation.hs10
-rw-r--r--compiler/GHC/Parser/Lexer.x6
-rw-r--r--compiler/GHC/Parser/PostProcess.hs2
9 files changed, 20 insertions, 37 deletions
diff --git a/compiler/GHC.hs b/compiler/GHC.hs
index 7a237b2146..0c55bfbea1 100644
--- a/compiler/GHC.hs
+++ b/compiler/GHC.hs
@@ -283,7 +283,7 @@ module GHC (
parser,
-- * API Annotations
- ApiAnns(..),AnnKeywordId(..),AnnotationComment(..),
+ AnnKeywordId(..),AnnotationComment(..),
-- * Miscellaneous
--sessionHscEnv,
@@ -1021,9 +1021,7 @@ class TypecheckedMod m => DesugaredMod m where
data ParsedModule =
ParsedModule { pm_mod_summary :: ModSummary
, pm_parsed_source :: ParsedSource
- , pm_extra_src_files :: [FilePath]
- , pm_annotations :: ApiAnns }
- -- See Note [Api annotations] in GHC.Parser.Annotation
+ , pm_extra_src_files :: [FilePath] }
instance ParsedMod ParsedModule where
modSummary m = pm_mod_summary m
@@ -1115,8 +1113,7 @@ parseModule ms = do
hsc_env <- getSession
let hsc_env_tmp = hsc_env { hsc_dflags = ms_hspp_opts ms }
hpm <- liftIO $ hscParse hsc_env_tmp ms
- return (ParsedModule ms (hpm_module hpm) (hpm_src_files hpm)
- (hpm_annotations hpm))
+ return (ParsedModule ms (hpm_module hpm) (hpm_src_files hpm))
-- See Note [Api annotations] in GHC.Parser.Annotation
-- | Typecheck and rename a parsed module.
@@ -1130,8 +1127,7 @@ typecheckModule pmod = do
(tc_gbl_env, rn_info)
<- liftIO $ hscTypecheckRename hsc_env_tmp ms $
HsParsedModule { hpm_module = parsedSource pmod,
- hpm_src_files = pm_extra_src_files pmod,
- hpm_annotations = pm_annotations pmod }
+ hpm_src_files = pm_extra_src_files pmod }
details <- liftIO $ makeSimpleDetails hsc_env_tmp tc_gbl_env
safe <- liftIO $ finalSafeMode (ms_hspp_opts ms) tc_gbl_env
diff --git a/compiler/GHC/Driver/Backpack.hs b/compiler/GHC/Driver/Backpack.hs
index daf53a502f..07c56bb36a 100644
--- a/compiler/GHC/Driver/Backpack.hs
+++ b/compiler/GHC/Driver/Backpack.hs
@@ -773,8 +773,7 @@ summariseRequirement pn mod_name = do
hsmodDeprecMessage = Nothing,
hsmodHaddockModHeader = Nothing
}),
- hpm_src_files = [],
- hpm_annotations = ApiAnns []
+ hpm_src_files = []
}),
ms_hspp_file = "", -- none, it came inline
ms_hspp_opts = dflags,
@@ -884,8 +883,7 @@ hsModuleToModSummary pn hsc_src modname
-- This is our hack to get the parse tree to the right spot
ms_parsed_mod = Just (HsParsedModule {
hpm_module = hsmod,
- hpm_src_files = [], -- TODO if we preprocessed it
- hpm_annotations = ApiAnns [] -- BOGUS
+ hpm_src_files = [] -- TODO if we preprocessed it
}),
ms_hs_date = time,
ms_obj_date = Nothing, -- TODO do this, but problem: hi_timestamp is BOGUS
diff --git a/compiler/GHC/Driver/Main.hs b/compiler/GHC/Driver/Main.hs
index c060f69c87..0ef4f10719 100644
--- a/compiler/GHC/Driver/Main.hs
+++ b/compiler/GHC/Driver/Main.hs
@@ -217,7 +217,7 @@ import qualified GHC.Data.Stream as Stream
import GHC.Data.Stream (Stream)
import Data.Data hiding (Fixity, TyCon)
-import Data.Maybe ( fromJust, fromMaybe )
+import Data.Maybe ( fromJust )
import Data.List ( nub, isPrefixOf, partition )
import Control.Monad
import Data.IORef
@@ -462,13 +462,9 @@ hscParse' mod_summary
-- filter them out:
srcs2 <- liftIO $ filterM doesFileExist srcs1
- let api_anns = ApiAnns {
- apiAnnRogueComments = (fromMaybe [] (header_comments pst)) ++ comment_q pst
- }
- res = HsParsedModule {
+ let res = HsParsedModule {
hpm_module = rdr_module,
- hpm_src_files = srcs2,
- hpm_annotations = api_anns
+ hpm_src_files = srcs2
}
-- apply parse transformation of plugins
diff --git a/compiler/GHC/Hs.hs b/compiler/GHC/Hs.hs
index 95cf14a616..26022e96de 100644
--- a/compiler/GHC/Hs.hs
+++ b/compiler/GHC/Hs.hs
@@ -166,13 +166,10 @@ pp_nonnull xs = vcat (map ppr xs)
data HsParsedModule = HsParsedModule {
hpm_module :: Located HsModule,
- hpm_src_files :: [FilePath],
+ hpm_src_files :: [FilePath]
-- ^ extra source files (e.g. from #includes). The lexer collects
-- these from '# <file> <line>' pragmas, which the C preprocessor
-- leaves behind. These files and their timestamps are stored in
-- the .hi file, so that we can force recompilation if any of
-- them change (#3589)
- hpm_annotations :: ApiAnns
- -- See note [Api annotations] in GHC.Parser.Annotation
}
-
diff --git a/compiler/GHC/Hs/Dump.hs b/compiler/GHC/Hs/Dump.hs
index 329b2d9308..18605d3532 100644
--- a/compiler/GHC/Hs/Dump.hs
+++ b/compiler/GHC/Hs/Dump.hs
@@ -57,6 +57,7 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
`extQ` annotationAddApiAnn
`extQ` annotationGrhsAnn
`extQ` annotationApiAnnHsCase
+ `extQ` annotationApiAnnHsLet
`extQ` annotationAnnList
`extQ` annotationApiAnnImportDecl
`extQ` annotationAnnParen
@@ -237,6 +238,9 @@ showAstData bs ba a0 = blankLine $$ showAstData' a0
annotationApiAnnHsCase :: ApiAnn' ApiAnnHsCase -> SDoc
annotationApiAnnHsCase = annotation' (text "ApiAnn' ApiAnnHsCase")
+ annotationApiAnnHsLet :: ApiAnn' AnnsLet -> SDoc
+ annotationApiAnnHsLet = annotation' (text "ApiAnn' AnnsLet")
+
annotationAnnList :: ApiAnn' AnnList -> SDoc
annotationAnnList = annotation' (text "ApiAnn' AnnList")
diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y
index f786940591..b9bae7a1f7 100644
--- a/compiler/GHC/Parser.y
+++ b/compiler/GHC/Parser.y
@@ -1197,6 +1197,8 @@ topdecls_cs_semi :: { OrdList (LHsDecl GhcPs) }
: topdecls_cs_semi topdecl_cs semis1 {% do { t <- amsA $2 $3
; return ($1 `snocOL` t) }}
| {- empty -} { nilOL }
+
+-- Each topdecl accumulates prior comments
topdecl_cs :: { LHsDecl GhcPs }
topdecl_cs : topdecl {% commentsPA $1 }
diff --git a/compiler/GHC/Parser/Annotation.hs b/compiler/GHC/Parser/Annotation.hs
index 3dd3b3302b..a860e3edb9 100644
--- a/compiler/GHC/Parser/Annotation.hs
+++ b/compiler/GHC/Parser/Annotation.hs
@@ -4,10 +4,6 @@
{-# LANGUAGE FlexibleInstances #-}
module GHC.Parser.Annotation (
- -- * Out-of-tree API Annotations. Exist for the duration of !5158,
- -- * will be removed by !2418
- ApiAnns(..),
-
-- * Core API Annotation types
AnnKeywordId(..),
AnnotationComment(..), AnnotationCommentTok(..),
@@ -162,12 +158,6 @@ The wiki page describing this feature is
https://gitlab.haskell.org/ghc/ghc/wikis/api-annotations
-}
--- ---------------------------------------------------------------------
-
-data ApiAnns =
- ApiAnns
- { apiAnnRogueComments :: [LAnnotationComment]
- }
-- --------------------------------------------------------------------
diff --git a/compiler/GHC/Parser/Lexer.x b/compiler/GHC/Parser/Lexer.x
index bfebbfa411..634cd10207 100644
--- a/compiler/GHC/Parser/Lexer.x
+++ b/compiler/GHC/Parser/Lexer.x
@@ -2932,7 +2932,7 @@ instance MonadP P where
POk s {
header_comments = header_comments',
comment_q = comment_q'
- } (AnnCommentsBalanced [] (reverse newAnns))
+ } (AnnCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns))
getCommentsFor :: (MonadP m) => SrcSpan -> m ApiAnnComments
getCommentsFor (RealSrcSpan l _) = allocateCommentsP l
@@ -3496,8 +3496,8 @@ allocateFinalComments ss comment_q mheader_comments =
comment_q'= before
in
case mheader_comments of
- Nothing -> (Just newAnns, comment_q', [])
- Just _ -> (mheader_comments, comment_q', newAnns)
+ Nothing -> (Just newAnns, [], comment_q')
+ Just _ -> (mheader_comments, [], comment_q' ++ newAnns)
commentToAnnotation :: RealLocated Token -> LAnnotationComment
commentToAnnotation (L l (ITdocCommentNext s ll)) = mkLAnnotationComment l ll (AnnDocCommentNext s)
diff --git a/compiler/GHC/Parser/PostProcess.hs b/compiler/GHC/Parser/PostProcess.hs
index 9dde6faeb8..9ac689c4d4 100644
--- a/compiler/GHC/Parser/PostProcess.hs
+++ b/compiler/GHC/Parser/PostProcess.hs
@@ -2826,7 +2826,7 @@ instance MonadP PV where
PV_Ok s {
pv_header_comments = header_comments',
pv_comment_q = comment_q'
- } (AnnCommentsBalanced [] (reverse newAnns))
+ } (AnnCommentsBalanced (fromMaybe [] header_comments') (reverse newAnns))
{- Note [Parser-Validator Hint]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~