forked from haskell/haskell-language-server
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathParser.hs
176 lines (164 loc) · 5.34 KB
/
Parser.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
{-# LANGUAGE CPP #-}
{-# LANGUAGE PatternSynonyms #-}
{-# HLINT ignore "Unused LANGUAGE pragma" #-}
-- | Parser compatibility module.
module Development.IDE.GHC.Compat.Parser (
initParserOpts,
initParserState,
#if MIN_VERSION_ghc(9,0,0) && !MIN_VERSION_ghc(9,2,0)
-- in GHC == 9.2 the type doesn't exist
-- In GHC == 9.0 it is a data-type
-- and GHC < 9.0 it is type-def
--
-- Export data-type here, otherwise only the simple type.
Anno.ApiAnns(..),
#else
ApiAnns,
#endif
#if MIN_VERSION_ghc(9,0,0)
PsSpan(..),
#endif
#if MIN_VERSION_ghc(9,2,0)
pattern HsParsedModule,
type GHC.HsParsedModule,
Development.IDE.GHC.Compat.Parser.hpm_module,
Development.IDE.GHC.Compat.Parser.hpm_src_files,
Development.IDE.GHC.Compat.Parser.hpm_annotations,
pattern ParsedModule,
Development.IDE.GHC.Compat.Parser.pm_parsed_source,
type GHC.ParsedModule,
Development.IDE.GHC.Compat.Parser.pm_mod_summary,
Development.IDE.GHC.Compat.Parser.pm_extra_src_files,
Development.IDE.GHC.Compat.Parser.pm_annotations,
#else
GHC.HsParsedModule(..),
GHC.ParsedModule(..),
#endif
mkApiAnns,
-- * API Annotations
Anno.AnnKeywordId(..),
#if !MIN_VERSION_ghc(9,2,0)
Anno.AnnotationComment(..),
#endif
pattern EpaLineComment,
pattern EpaBlockComment
) where
#if MIN_VERSION_ghc(9,0,0)
#if !MIN_VERSION_ghc(9,2,0)
import qualified GHC.Driver.Types as GHC
#endif
import qualified GHC.Parser.Annotation as Anno
import qualified GHC.Parser.Lexer as Lexer
import GHC.Types.SrcLoc (PsSpan (..))
#if MIN_VERSION_ghc(9,2,0)
import GHC (Anchor (anchor),
EpAnnComments (priorComments),
EpaComment (EpaComment),
EpaCommentTok (..),
epAnnComments,
pm_extra_src_files,
pm_mod_summary,
pm_parsed_source)
import qualified GHC
#if MIN_VERSION_ghc(9,3,0)
import qualified GHC.Driver.Config.Parser as Config
#else
import qualified GHC.Driver.Config as Config
#endif
import GHC.Hs (LEpaComment, hpm_module,
hpm_src_files)
import GHC.Parser.Lexer hiding (initParserState)
#endif
#else
import qualified ApiAnnotation as Anno
import qualified HscTypes as GHC
import Lexer
import qualified SrcLoc
#endif
import Development.IDE.GHC.Compat.Core
import Development.IDE.GHC.Compat.Util
#if !MIN_VERSION_ghc(9,2,0)
import qualified Data.Map as Map
import qualified GHC
#endif
#if !MIN_VERSION_ghc(9,0,0)
type ParserOpts = DynFlags
#elif !MIN_VERSION_ghc(9,2,0)
type ParserOpts = Lexer.ParserFlags
#endif
initParserOpts :: DynFlags -> ParserOpts
initParserOpts =
#if MIN_VERSION_ghc(9,2,0)
Config.initParserOpts
#elif MIN_VERSION_ghc(9,0,0)
Lexer.mkParserFlags
#else
id
#endif
initParserState :: ParserOpts -> StringBuffer -> RealSrcLoc -> PState
initParserState =
#if MIN_VERSION_ghc(9,2,0)
Lexer.initParserState
#elif MIN_VERSION_ghc(9,0,0)
Lexer.mkPStatePure
#else
Lexer.mkPState
#endif
#if MIN_VERSION_ghc(9,2,0)
-- GHC 9.2 does not have ApiAnns anymore packaged in ParsedModule. Now the
-- annotations are found in the ast.
type ApiAnns = ()
#else
type ApiAnns = Anno.ApiAnns
#endif
#if MIN_VERSION_ghc(9,2,0)
pattern HsParsedModule :: Located HsModule -> [FilePath] -> ApiAnns -> GHC.HsParsedModule
pattern HsParsedModule
{ hpm_module
, hpm_src_files
, hpm_annotations
} <- ( (,()) -> (GHC.HsParsedModule{..}, hpm_annotations))
where
HsParsedModule hpm_module hpm_src_files hpm_annotations =
GHC.HsParsedModule hpm_module hpm_src_files
#endif
#if MIN_VERSION_ghc(9,2,0)
pattern ParsedModule :: ModSummary -> ParsedSource -> [FilePath] -> ApiAnns -> GHC.ParsedModule
pattern ParsedModule
{ pm_mod_summary
, pm_parsed_source
, pm_extra_src_files
, pm_annotations
} <- ( (,()) -> (GHC.ParsedModule{..}, pm_annotations))
where
ParsedModule ms parsed extra_src_files _anns =
GHC.ParsedModule
{ pm_mod_summary = ms
, pm_parsed_source = parsed
, pm_extra_src_files = extra_src_files
}
{-# COMPLETE ParsedModule :: GHC.ParsedModule #-}
#endif
mkApiAnns :: PState -> ApiAnns
#if MIN_VERSION_ghc(9,2,0)
mkApiAnns = const ()
#else
mkApiAnns pst =
#if MIN_VERSION_ghc(9,0,1)
-- Copied from GHC.Driver.Main
Anno.ApiAnns {
apiAnnItems = Map.fromListWith (++) $ annotations pst,
apiAnnEofPos = eof_pos pst,
apiAnnComments = Map.fromList (annotations_comments pst),
apiAnnRogueComments = comment_q pst
}
#else
(Map.fromListWith (++) $ annotations pst,
Map.fromList ((SrcLoc.noSrcSpan,comment_q pst)
:annotations_comments pst))
#endif
#endif
#if !MIN_VERSION_ghc(9,2,0)
pattern EpaLineComment a = Anno.AnnLineComment a
pattern EpaBlockComment a = Anno.AnnBlockComment a
#endif