10
10
{-# LANGUAGE NamedFieldPuns #-}
11
11
{-# LANGUAGE OverloadedLabels #-}
12
12
{-# LANGUAGE OverloadedStrings #-}
13
- {-# LANGUAGE PackageImports #-}
14
13
{-# LANGUAGE PatternSynonyms #-}
15
14
{-# LANGUAGE RecordWildCards #-}
16
15
{-# LANGUAGE ScopedTypeVariables #-}
26
25
-- lots of CPP, we just disable the warning until later.
27
26
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
28
27
29
- #ifdef HLINT_ON_GHC_LIB
28
+ #ifdef GHC_LIB
30
29
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib_parser(x,y,z)
31
30
#else
32
31
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc(x,y,z)
@@ -69,7 +68,6 @@ import Development.IDE.Core.Shake (getDiagnost
69
68
import qualified Refact.Apply as Refact
70
69
import qualified Refact.Types as Refact
71
70
72
- #ifdef HLINT_ON_GHC_LIB
73
71
import Development.IDE.GHC.Compat (DynFlags ,
74
72
WarningFlag (Opt_WarnUnrecognisedPragmas ),
75
73
extensionFlags ,
@@ -79,18 +77,18 @@ import Development.IDE.GHC.Compat (DynFlags,
79
77
import qualified Development.IDE.GHC.Compat.Util as EnumSet
80
78
81
79
#if MIN_GHC_API_VERSION(9,4,0)
82
- import qualified "ghc-lib-parser" GHC.Data.Strict as Strict
80
+ import qualified GHC.Data.Strict as Strict
83
81
#endif
84
82
#if MIN_GHC_API_VERSION(9,0,0)
85
- import "ghc-lib-parser" GHC.Types.SrcLoc hiding
83
+ import GHC.Types.SrcLoc hiding
86
84
(RealSrcSpan )
87
- import qualified "ghc-lib-parser" GHC.Types.SrcLoc as GHC
85
+ import qualified GHC.Types.SrcLoc as GHC
88
86
#else
89
- import "ghc-lib-parser" SrcLoc hiding
87
+ import qualified SrcLoc as GHC
88
+ import SrcLoc hiding
90
89
(RealSrcSpan )
91
- import qualified "ghc-lib-parser" SrcLoc as GHC
92
90
#endif
93
- import "ghc-lib-parser" GHC.LanguageExtensions (Extension )
91
+ import GHC.LanguageExtensions (Extension )
94
92
import Language.Haskell.GhclibParserEx.GHC.Driver.Session as GhclibParserEx (readExtension )
95
93
import System.FilePath (takeFileName )
96
94
import System.IO (IOMode (WriteMode ),
@@ -102,21 +100,7 @@ import System.IO (IOMode (Wri
102
100
utf8 ,
103
101
withFile )
104
102
import System.IO.Temp
105
- #else
106
- import Development.IDE.GHC.Compat hiding
107
- (setEnv ,
108
- (<+>) )
109
- import GHC.Generics (Associativity (LeftAssociative , NotAssociative , RightAssociative ))
110
- #if MIN_GHC_API_VERSION(9,2,0)
111
- import Language.Haskell.GHC.ExactPrint.ExactPrint (deltaOptions )
112
- #else
113
- import Language.Haskell.GHC.ExactPrint.Delta (deltaOptions )
114
- #endif
115
- import Language.Haskell.GHC.ExactPrint.Parsers (postParseTransform )
116
- import Language.Haskell.GHC.ExactPrint.Types (Rigidity (.. ))
117
- import Language.Haskell.GhclibParserEx.Fixity as GhclibParserEx (applyFixities )
118
- import qualified Refact.Fixity as Refact
119
- #endif
103
+
120
104
import Ide.Plugin.Config hiding
121
105
(Config )
122
106
import Ide.Plugin.Error
@@ -169,7 +153,6 @@ instance Pretty Log where
169
153
LogGetIdeas fp -> " Getting hlint ideas for " <+> viaShow fp
170
154
LogResolve msg -> pretty msg
171
155
172
- #ifdef HLINT_ON_GHC_LIB
173
156
-- Reimplementing this, since the one in Development.IDE.GHC.Compat isn't for ghc-lib
174
157
#if !MIN_GHC_API_VERSION(9,0,0)
175
158
type BufSpan = ()
@@ -183,7 +166,6 @@ pattern RealSrcSpan x y = GHC.RealSrcSpan x y
183
166
pattern RealSrcSpan x y <- ((,Nothing ) -> (GHC. RealSrcSpan x, y))
184
167
#endif
185
168
{-# COMPLETE RealSrcSpan, UnhelpfulSpan #-}
186
- #endif
187
169
188
170
#if MIN_GHC_API_VERSION(9,4,0)
189
171
fromStrictMaybe :: Strict. Maybe a -> Maybe a
@@ -310,28 +292,6 @@ getIdeas recorder nfp = do
310
292
fmap applyHints' (moduleEx flags)
311
293
312
294
where moduleEx :: ParseFlags -> Action (Maybe (Either ParseError ModuleEx ))
313
- #ifndef HLINT_ON_GHC_LIB
314
- moduleEx _flags = do
315
- mbpm <- getParsedModuleWithComments nfp
316
- return $ createModule <$> mbpm
317
- where
318
- createModule pm = Right (createModuleEx anns (applyParseFlagsFixities modu))
319
- where anns = pm_annotations pm
320
- modu = pm_parsed_source pm
321
-
322
- applyParseFlagsFixities :: ParsedSource -> ParsedSource
323
- applyParseFlagsFixities modul = GhclibParserEx. applyFixities (parseFlagsToFixities _flags) modul
324
-
325
- parseFlagsToFixities :: ParseFlags -> [(String , Fixity )]
326
- parseFlagsToFixities = map toFixity . Hlint. fixities
327
-
328
- toFixity :: FixityInfo -> (String , Fixity )
329
- toFixity (name, dir, i) = (name, Fixity NoSourceText i $ f dir)
330
- where
331
- f LeftAssociative = InfixL
332
- f RightAssociative = InfixR
333
- f NotAssociative = InfixN
334
- #else
335
295
moduleEx flags = do
336
296
mbpm <- getParsedModuleWithComments nfp
337
297
-- If ghc was not able to parse the module, we disable hlint diagnostics
@@ -354,11 +314,6 @@ getIdeas recorder nfp = do
354
314
-- and the ModSummary dynflags. However using the parsedFlags extensions
355
315
-- can sometimes interfere with the hlint parsing of the file.
356
316
-- See https://github.com/haskell/haskell-language-server/issues/1279
357
- --
358
- -- Note: this is used when HLINT_ON_GHC_LIB is defined. We seem to need
359
- -- these extensions to construct dynflags to parse the file again. Therefore
360
- -- using hlint default extensions doesn't seem to be a problem when
361
- -- HLINT_ON_GHC_LIB is not defined because we don't parse the file again.
362
317
getExtensions :: NormalizedFilePath -> Action [Extension ]
363
318
getExtensions nfp = do
364
319
dflags <- getFlags
@@ -369,7 +324,6 @@ getExtensions nfp = do
369
324
getFlags = do
370
325
modsum <- use_ GetModSummary nfp
371
326
return $ ms_hspp_opts $ msrModSummary modsum
372
- #endif
373
327
374
328
-- ---------------------------------------------------------------------
375
329
@@ -567,7 +521,6 @@ applyHint recorder ide nfp mhint verTxtDocId =
567
521
-- But "Idea"s returned by HLint point to starting position of the expressions
568
522
-- that contain refactorings, so they are often outside the refactorings' boundaries.
569
523
let position = Nothing
570
- #ifdef HLINT_ON_GHC_LIB
571
524
let writeFileUTF8NoNewLineTranslation file txt =
572
525
withFile file WriteMode $ \ h -> do
573
526
hSetEncoding h utf8
@@ -583,22 +536,6 @@ applyHint recorder ide nfp mhint verTxtDocId =
583
536
let refactExts = map show $ enabled ++ disabled
584
537
(Right <$> applyRefactorings (topDir dflags) position commands temp refactExts)
585
538
`catches` errorHandlers
586
- #else
587
- mbParsedModule <- liftIO $ runAction' $ getParsedModuleWithComments nfp
588
- res <-
589
- case mbParsedModule of
590
- Nothing -> throwError " Apply hint: error parsing the module"
591
- Just pm -> do
592
- let anns = pm_annotations pm
593
- let modu = pm_parsed_source pm
594
- -- apply-refact uses RigidLayout
595
- let rigidLayout = deltaOptions RigidLayout
596
- (anns', modu') <-
597
- ExceptT $ mapM (uncurry Refact. applyFixities)
598
- $ postParseTransform (Right (anns, [] , dflags, modu)) rigidLayout
599
- liftIO $ (Right <$> Refact. applyRefactorings' position commands anns' modu')
600
- `catches` errorHandlers
601
- #endif
602
539
case res of
603
540
Right appliedFile -> do
604
541
let wsEdit = diffText' True (verTxtDocId, oldContent) (T. pack appliedFile) IncludeDeletions
0 commit comments