1
- {-# LANGUAGE CPP #-}
2
- {-# LANGUAGE DeriveAnyClass #-}
3
- {-# LANGUAGE DeriveGeneric #-}
4
- {-# LANGUAGE DuplicateRecordFields #-}
5
- {-# LANGUAGE FlexibleContexts #-}
6
- {-# LANGUAGE FlexibleInstances #-}
7
- {-# LANGUAGE LambdaCase #-}
8
- {-# LANGUAGE MultiWayIf #-}
9
- {-# LANGUAGE NamedFieldPuns #-}
10
- {-# LANGUAGE OverloadedLabels #-}
11
- {-# LANGUAGE OverloadedStrings #-}
12
- {-# LANGUAGE PackageImports #-}
13
- {-# LANGUAGE PatternSynonyms #-}
14
- {-# LANGUAGE RecordWildCards #-}
15
- {-# LANGUAGE ScopedTypeVariables #-}
16
- {-# LANGUAGE StrictData #-}
17
- {-# LANGUAGE TupleSections #-}
18
- {-# LANGUAGE TypeFamilies #-}
19
- {-# LANGUAGE ViewPatterns #-}
20
-
1
+ {-# LANGUAGE CPP #-}
2
+ {-# LANGUAGE DeriveAnyClass #-}
3
+ {-# LANGUAGE DeriveGeneric #-}
4
+ {-# LANGUAGE DuplicateRecordFields #-}
5
+ {-# LANGUAGE ExistentialQuantification #-}
6
+ {-# LANGUAGE FlexibleContexts #-}
7
+ {-# LANGUAGE FlexibleInstances #-}
8
+ {-# LANGUAGE LambdaCase #-}
9
+ {-# LANGUAGE MultiWayIf #-}
10
+ {-# LANGUAGE NamedFieldPuns #-}
11
+ {-# LANGUAGE OverloadedLabels #-}
12
+ {-# LANGUAGE OverloadedStrings #-}
13
+ {-# LANGUAGE PatternSynonyms #-}
14
+ {-# LANGUAGE RecordWildCards #-}
15
+ {-# LANGUAGE ScopedTypeVariables #-}
16
+ {-# LANGUAGE StrictData #-}
17
+ {-# LANGUAGE TupleSections #-}
18
+ {-# LANGUAGE TypeApplications #-}
19
+ {-# LANGUAGE TypeFamilies #-}
20
+ {-# LANGUAGE ViewPatterns #-}
21
21
{-# OPTIONS_GHC -Wno-orphans #-}
22
22
23
23
-- On 9.4 we get a new redundant constraint warning, but deleting the
24
24
-- constraint breaks the build on earlier versions. Rather than apply
25
25
-- lots of CPP, we just disable the warning until later.
26
26
{-# OPTIONS_GHC -Wno-redundant-constraints #-}
27
27
28
- #ifdef HLINT_ON_GHC_LIB
28
+ #ifdef GHC_LIB
29
29
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib_parser(x,y,z)
30
30
#else
31
31
#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc(x,y,z)
@@ -63,7 +63,6 @@ import Development.IDE.Core.Shake (getDiagnost
63
63
import qualified Refact.Apply as Refact
64
64
import qualified Refact.Types as Refact
65
65
66
- #ifdef HLINT_ON_GHC_LIB
67
66
import Development.IDE.GHC.Compat (DynFlags ,
68
67
WarningFlag (Opt_WarnUnrecognisedPragmas ),
69
68
extensionFlags ,
@@ -73,18 +72,18 @@ import Development.IDE.GHC.Compat (DynFlags,
73
72
import qualified Development.IDE.GHC.Compat.Util as EnumSet
74
73
75
74
#if MIN_GHC_API_VERSION(9,4,0)
76
- import qualified "ghc-lib-parser" GHC.Data.Strict as Strict
75
+ import qualified GHC.Data.Strict as Strict
77
76
#endif
78
77
#if MIN_GHC_API_VERSION(9,0,0)
79
- import "ghc-lib-parser" GHC.Types.SrcLoc hiding
78
+ import GHC.Types.SrcLoc hiding
80
79
(RealSrcSpan )
81
- import qualified "ghc-lib-parser" GHC.Types.SrcLoc as GHC
80
+ import qualified GHC.Types.SrcLoc as GHC
82
81
#else
83
- import "ghc-lib-parser" SrcLoc hiding
82
+ import qualified SrcLoc as GHC
83
+ import SrcLoc hiding
84
84
(RealSrcSpan )
85
- import qualified "ghc-lib-parser" SrcLoc as GHC
86
85
#endif
87
- import "ghc-lib-parser" GHC.LanguageExtensions (Extension )
86
+ import GHC.LanguageExtensions (Extension )
88
87
import Language.Haskell.GhclibParserEx.GHC.Driver.Session as GhclibParserEx (readExtension )
89
88
import System.FilePath (takeFileName )
90
89
import System.IO (IOMode (WriteMode ),
@@ -96,21 +95,6 @@ import System.IO (IOMode (Wri
96
95
utf8 ,
97
96
withFile )
98
97
import System.IO.Temp
99
- #else
100
- import Development.IDE.GHC.Compat hiding
101
- (setEnv ,
102
- (<+>) )
103
- import GHC.Generics (Associativity (LeftAssociative , NotAssociative , RightAssociative ))
104
- #if MIN_GHC_API_VERSION(9,2,0)
105
- import Language.Haskell.GHC.ExactPrint.ExactPrint (deltaOptions )
106
- #else
107
- import Language.Haskell.GHC.ExactPrint.Delta (deltaOptions )
108
- #endif
109
- import Language.Haskell.GHC.ExactPrint.Parsers (postParseTransform )
110
- import Language.Haskell.GHC.ExactPrint.Types (Rigidity (.. ))
111
- import Language.Haskell.GhclibParserEx.Fixity as GhclibParserEx (applyFixities )
112
- import qualified Refact.Fixity as Refact
113
- #endif
114
98
115
99
import Ide.Plugin.Config hiding
116
100
(Config )
@@ -163,7 +147,6 @@ instance Pretty Log where
163
147
LogUsingExtensions fp exts -> " Using extensions for " <+> viaShow fp <> " :" <+> pretty exts
164
148
LogGetIdeas fp -> " Getting hlint ideas for " <+> viaShow fp
165
149
166
- #ifdef HLINT_ON_GHC_LIB
167
150
-- Reimplementing this, since the one in Development.IDE.GHC.Compat isn't for ghc-lib
168
151
#if !MIN_GHC_API_VERSION(9,0,0)
169
152
type BufSpan = ()
@@ -177,7 +160,6 @@ pattern RealSrcSpan x y = GHC.RealSrcSpan x y
177
160
pattern RealSrcSpan x y <- ((,Nothing ) -> (GHC. RealSrcSpan x, y))
178
161
#endif
179
162
{-# COMPLETE RealSrcSpan, UnhelpfulSpan #-}
180
- #endif
181
163
182
164
#if MIN_GHC_API_VERSION(9,4,0)
183
165
fromStrictMaybe :: Strict. Maybe a -> Maybe a
@@ -300,28 +282,6 @@ getIdeas recorder nfp = do
300
282
fmap applyHints' (moduleEx flags)
301
283
302
284
where moduleEx :: ParseFlags -> Action (Maybe (Either ParseError ModuleEx ))
303
- #ifndef HLINT_ON_GHC_LIB
304
- moduleEx _flags = do
305
- mbpm <- getParsedModuleWithComments nfp
306
- return $ createModule <$> mbpm
307
- where
308
- createModule pm = Right (createModuleEx anns (applyParseFlagsFixities modu))
309
- where anns = pm_annotations pm
310
- modu = pm_parsed_source pm
311
-
312
- applyParseFlagsFixities :: ParsedSource -> ParsedSource
313
- applyParseFlagsFixities modul = GhclibParserEx. applyFixities (parseFlagsToFixities _flags) modul
314
-
315
- parseFlagsToFixities :: ParseFlags -> [(String , Fixity )]
316
- parseFlagsToFixities = map toFixity . Hlint. fixities
317
-
318
- toFixity :: FixityInfo -> (String , Fixity )
319
- toFixity (name, dir, i) = (name, Fixity NoSourceText i $ f dir)
320
- where
321
- f LeftAssociative = InfixL
322
- f RightAssociative = InfixR
323
- f NotAssociative = InfixN
324
- #else
325
285
moduleEx flags = do
326
286
mbpm <- getParsedModuleWithComments nfp
327
287
-- If ghc was not able to parse the module, we disable hlint diagnostics
@@ -344,11 +304,6 @@ getIdeas recorder nfp = do
344
304
-- and the ModSummary dynflags. However using the parsedFlags extensions
345
305
-- can sometimes interfere with the hlint parsing of the file.
346
306
-- See https://github.com/haskell/haskell-language-server/issues/1279
347
- --
348
- -- Note: this is used when HLINT_ON_GHC_LIB is defined. We seem to need
349
- -- these extensions to construct dynflags to parse the file again. Therefore
350
- -- using hlint default extensions doesn't seem to be a problem when
351
- -- HLINT_ON_GHC_LIB is not defined because we don't parse the file again.
352
307
getExtensions :: NormalizedFilePath -> Action [Extension ]
353
308
getExtensions nfp = do
354
309
dflags <- getFlags
@@ -359,7 +314,6 @@ getExtensions nfp = do
359
314
getFlags = do
360
315
modsum <- use_ GetModSummary nfp
361
316
return $ ms_hspp_opts $ msrModSummary modsum
362
- #endif
363
317
364
318
-- ---------------------------------------------------------------------
365
319
@@ -580,7 +534,6 @@ applyHint recorder ide nfp mhint =
580
534
-- But "Idea"s returned by HLint point to starting position of the expressions
581
535
-- that contain refactorings, so they are often outside the refactorings' boundaries.
582
536
let position = Nothing
583
- #ifdef HLINT_ON_GHC_LIB
584
537
let writeFileUTF8NoNewLineTranslation file txt =
585
538
withFile file WriteMode $ \ h -> do
586
539
hSetEncoding h utf8
@@ -596,22 +549,6 @@ applyHint recorder ide nfp mhint =
596
549
let refactExts = map show $ enabled ++ disabled
597
550
(Right <$> applyRefactorings (topDir dflags) position commands temp refactExts)
598
551
`catches` errorHandlers
599
- #else
600
- mbParsedModule <- liftIO $ runAction' $ getParsedModuleWithComments nfp
601
- res <-
602
- case mbParsedModule of
603
- Nothing -> throwE " Apply hint: error parsing the module"
604
- Just pm -> do
605
- let anns = pm_annotations pm
606
- let modu = pm_parsed_source pm
607
- -- apply-refact uses RigidLayout
608
- let rigidLayout = deltaOptions RigidLayout
609
- (anns', modu') <-
610
- ExceptT $ mapM (uncurry Refact. applyFixities)
611
- $ postParseTransform (Right (anns, [] , dflags, modu)) rigidLayout
612
- liftIO $ (Right <$> Refact. applyRefactorings' position commands anns' modu')
613
- `catches` errorHandlers
614
- #endif
615
552
case res of
616
553
Right appliedFile -> do
617
554
let uri = fromNormalizedUri (filePathToUri' nfp)
0 commit comments