1
+ {-# LANGUAGE ScopedTypeVariables #-}
1
2
{-# LANGUAGE CPP #-}
2
3
{-# LANGUAGE DeriveAnyClass #-}
3
4
{-# LANGUAGE DeriveGeneric #-}
@@ -39,12 +40,16 @@ import Development.IDE.Core.Shake (getDiagnostics)
39
40
#ifdef GHC_LIB
40
41
import Data.List (nub )
41
42
import "ghc-lib" GHC hiding (DynFlags (.. ))
43
+ import "ghc-lib" GHC.LanguageExtension (Extension )
42
44
import "ghc" GHC as RealGHC (DynFlags (.. ))
43
45
import "ghc" HscTypes as RealGHC.HscTypes (hsc_dflags )
44
46
import qualified "ghc" EnumSet as EnumSet
45
47
import Language.Haskell.GhclibParserEx.GHC.Driver.Session as GhclibParserEx (readExtension )
46
48
#else
47
49
import Development.IDE.GHC.Compat hiding (DynFlags (.. ))
50
+ import HscTypes (hsc_dflags )
51
+ import Language.Haskell.GHC.ExactPrint.Parsers (postParseTransform )
52
+ import Language.Haskell.GHC.ExactPrint.Delta (normalLayout )
48
53
#endif
49
54
50
55
import Ide.Logger
@@ -175,7 +180,14 @@ getIdeas nfp = do
175
180
fmap applyHints' (moduleEx flags)
176
181
177
182
where moduleEx :: ParseFlags -> Action (Maybe (Either ParseError ModuleEx ))
178
- #ifdef GHC_LIB
183
+ #ifndef GHC_LIB
184
+ moduleEx _flags = do
185
+ mbpm <- getParsedModule nfp
186
+ return $ createModule <$> mbpm
187
+ where createModule pm = Right (createModuleEx anns modu)
188
+ where anns = pm_annotations pm
189
+ modu = pm_parsed_source pm
190
+ #else
179
191
moduleEx flags = do
180
192
mbpm <- getParsedModule nfp
181
193
-- If ghc was not able to parse the module, we disable hlint diagnostics
@@ -189,20 +201,18 @@ getIdeas nfp = do
189
201
Just <$> (liftIO $ parseModuleEx flags' fp contents')
190
202
191
203
setExtensions flags = do
192
- hsc <- hscEnv <$> use_ GhcSession nfp
193
- let dflags = hsc_dflags hsc
194
- let hscExts = EnumSet. toList (extensionFlags dflags)
195
- let hscExts' = mapMaybe (GhclibParserEx. readExtension . show ) hscExts
196
- let hlintExts = nub $ enabledExtensions flags ++ hscExts'
204
+ hlintExts <- getExtensions
197
205
logm $ " hlint:getIdeas:setExtensions:" ++ show hlintExts
198
206
return $ flags { enabledExtensions = hlintExts }
199
- #else
200
- moduleEx _flags = do
201
- mbpm <- getParsedModule nfp
202
- return $ createModule <$> mbpm
203
- where createModule pm = Right (createModuleEx anns modu)
204
- where anns = pm_annotations pm
205
- modu = pm_parsed_source pm
207
+
208
+ getExtensions :: Action [Extension ]
209
+ getExtensions = do
210
+ hsc <- hscEnv <$> use_ GhcSession nfp
211
+ let dflags = hsc_dflags hsc
212
+ let hscExts = EnumSet. toList (extensionFlags dflags)
213
+ let hscExts' = mapMaybe (GhclibParserEx. readExtension . show ) hscExts
214
+ let hlintExts = nub $ enabledExtensions flags ++ hscExts'
215
+ return hlintExts
206
216
#endif
207
217
208
218
-- ---------------------------------------------------------------------
@@ -333,10 +343,15 @@ applyOneCmd lf ide (AOP uri pos title) = do
333
343
applyHint :: IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
334
344
applyHint ide nfp mhint =
335
345
runExceptT $ do
336
- ideas <- bimapExceptT showParseError id $ ExceptT $ liftIO $ runAction " applyHint" ide $ getIdeas nfp
346
+ let runAction' :: Action a -> IO a
347
+ runAction' = runAction " applyHint" ide
348
+ ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas nfp
337
349
let ideas' = maybe ideas (`filterIdeas` ideas) mhint
338
- let commands = map ( show &&& ideaRefactoring) ideas'
350
+ let commands = map ideaRefactoring ideas'
339
351
liftIO $ logm $ " applyHint:apply=" ++ show commands
352
+ let fp = fromNormalizedFilePath nfp
353
+ (_, mbOldContent) <- liftIO $ runAction' $ getFileContents nfp
354
+ oldContent <- maybe (liftIO $ T. readFile fp) return mbOldContent
340
355
-- set Nothing as "position" for "applyRefactorings" because
341
356
-- applyRefactorings expects the provided position to be _within_ the scope
342
357
-- of each refactoring it will apply.
@@ -352,27 +367,39 @@ applyHint ide nfp mhint =
352
367
-- If we provide "applyRefactorings" with "Just (1,13)" then
353
368
-- the "Redundant bracket" hint will never be executed
354
369
-- because SrcSpan (1,20,??,??) doesn't contain position (1,13).
355
- let fp = fromNormalizedFilePath nfp
356
- (_, mbOldContent) <- liftIO $ runAction " hlint" ide $ getFileContents nfp
357
- oldContent <- maybe (liftIO $ T. readFile fp) return mbOldContent
358
- -- We need to save a file with last edited contents cause `apply-refact`
359
- -- doesn't expose a function taking directly contents instead a file path.
360
- -- Ideally we should try to expose that function upstream and remove this.
361
- res <- liftIO $ withSystemTempFile (takeFileName fp) $ \ temp h -> do
370
+ #ifdef GHC_LIB
371
+ res <-
372
+ liftIO $ withSystemTempFile (takeFileName fp) $ \ temp h -> do
362
373
hClose h
363
374
writeFileUTF8NoNewLineTranslation temp oldContent
364
- (Right <$> applyRefactorings Nothing commands temp) `catches`
375
+ let exts = runAction' getExtensions
376
+ (Right <$> applyRefactorings Nothing commands temp exts)
377
+ `catches`
365
378
[ Handler $ \ e -> return (Left (show (e :: IOException )))
366
379
, Handler $ \ e -> return (Left (show (e :: ErrorCall )))
367
380
]
381
+ #else
382
+ mbParsedModule <- liftIO $ runAction' $ getParsedModule nfp
383
+ res <-
384
+ case mbParsedModule of
385
+ Nothing -> throwE " Apply hint: error parsing the module"
386
+ Just pm -> do
387
+ let anns = pm_annotations pm
388
+ let modu = pm_parsed_source pm
389
+ hsc <- liftIO $ runAction' $ hscEnv <$> use_ GhcSession nfp
390
+ let dflags = hsc_dflags hsc
391
+ (anns', modu') <-
392
+ ExceptT $ return $ postParseTransform (Right (anns, [] , dflags, modu)) normalLayout
393
+ liftIO (Right <$> applyRefactorings' Nothing commands anns' modu')
394
+ #endif
368
395
case res of
369
396
Right appliedFile -> do
370
397
let uri = fromNormalizedUri (filePathToUri' nfp)
371
398
let wsEdit = diffText' True (uri, oldContent) (T. pack appliedFile) IncludeDeletions
372
399
liftIO $ logm $ " hlint:applyHint:diff=" ++ show wsEdit
373
400
ExceptT $ return (Right wsEdit)
374
401
Left err ->
375
- throwE ( show err)
402
+ throwE err
376
403
where
377
404
-- | If we are only interested in applying a particular hint then
378
405
-- let's filter out all the irrelevant ideas
0 commit comments