Skip to content

Commit ce0a26e

Browse files
committed
Leverage apply-refact improvements
* applyRefactoring accepts ghc extensions to parse the file * new applyRefactoring' function accepts the parsed module Thanks @zliu41!
1 parent d7bba2d commit ce0a26e

File tree

1 file changed

+51
-24
lines changed
  • plugins/hls-hlint-plugin/src/Ide/Plugin

1 file changed

+51
-24
lines changed

plugins/hls-hlint-plugin/src/Ide/Plugin/Hlint.hs

Lines changed: 51 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
12
{-# LANGUAGE CPP #-}
23
{-# LANGUAGE DeriveAnyClass #-}
34
{-# LANGUAGE DeriveGeneric #-}
@@ -39,12 +40,16 @@ import Development.IDE.Core.Shake (getDiagnostics)
3940
#ifdef GHC_LIB
4041
import Data.List (nub)
4142
import "ghc-lib" GHC hiding (DynFlags(..))
43+
import "ghc-lib" GHC.LanguageExtension (Extension)
4244
import "ghc" GHC as RealGHC (DynFlags(..))
4345
import "ghc" HscTypes as RealGHC.HscTypes (hsc_dflags)
4446
import qualified "ghc" EnumSet as EnumSet
4547
import Language.Haskell.GhclibParserEx.GHC.Driver.Session as GhclibParserEx (readExtension)
4648
#else
4749
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)
4853
#endif
4954

5055
import Ide.Logger
@@ -175,7 +180,14 @@ getIdeas nfp = do
175180
fmap applyHints' (moduleEx flags)
176181

177182
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
179191
moduleEx flags = do
180192
mbpm <- getParsedModule nfp
181193
-- If ghc was not able to parse the module, we disable hlint diagnostics
@@ -189,20 +201,18 @@ getIdeas nfp = do
189201
Just <$> (liftIO $ parseModuleEx flags' fp contents')
190202

191203
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
197205
logm $ "hlint:getIdeas:setExtensions:" ++ show hlintExts
198206
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
206216
#endif
207217

208218
-- ---------------------------------------------------------------------
@@ -333,10 +343,15 @@ applyOneCmd lf ide (AOP uri pos title) = do
333343
applyHint :: IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit)
334344
applyHint ide nfp mhint =
335345
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
337349
let ideas' = maybe ideas (`filterIdeas` ideas) mhint
338-
let commands = map (show &&& ideaRefactoring) ideas'
350+
let commands = map ideaRefactoring ideas'
339351
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
340355
-- set Nothing as "position" for "applyRefactorings" because
341356
-- applyRefactorings expects the provided position to be _within_ the scope
342357
-- of each refactoring it will apply.
@@ -352,27 +367,39 @@ applyHint ide nfp mhint =
352367
-- If we provide "applyRefactorings" with "Just (1,13)" then
353368
-- the "Redundant bracket" hint will never be executed
354369
-- 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
362373
hClose h
363374
writeFileUTF8NoNewLineTranslation temp oldContent
364-
(Right <$> applyRefactorings Nothing commands temp) `catches`
375+
let exts = runAction' getExtensions
376+
(Right <$> applyRefactorings Nothing commands temp exts)
377+
`catches`
365378
[ Handler $ \e -> return (Left (show (e :: IOException)))
366379
, Handler $ \e -> return (Left (show (e :: ErrorCall)))
367380
]
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
368395
case res of
369396
Right appliedFile -> do
370397
let uri = fromNormalizedUri (filePathToUri' nfp)
371398
let wsEdit = diffText' True (uri, oldContent) (T.pack appliedFile) IncludeDeletions
372399
liftIO $ logm $ "hlint:applyHint:diff=" ++ show wsEdit
373400
ExceptT $ return (Right wsEdit)
374401
Left err ->
375-
throwE (show err)
402+
throwE err
376403
where
377404
-- | If we are only interested in applying a particular hint then
378405
-- let's filter out all the irrelevant ideas

0 commit comments

Comments
 (0)