@@ -55,6 +55,7 @@ import Development.IDE.Core.Rules (defineNoFil
5555 usePropertyAction )
5656import Development.IDE.Core.Shake (getDiagnostics )
5757import qualified Refact.Apply as Refact
58+ import qualified Refact.Types as Refact
5859
5960#ifdef HLINT_ON_GHC_LIB
6061import Development.IDE.GHC.Compat (BufSpan ,
@@ -84,7 +85,7 @@ import System.IO (IOMode (Wri
8485import System.IO.Temp
8586#else
8687import Development.IDE.GHC.Compat hiding
87- (setEnv )
88+ (setEnv , (<+>) )
8889import GHC.Generics (Associativity (LeftAssociative , NotAssociative , RightAssociative ))
8990import Language.Haskell.GHC.ExactPrint.Delta (deltaOptions )
9091import Language.Haskell.GHC.ExactPrint.Parsers (postParseTransform )
@@ -93,7 +94,6 @@ import Language.Haskell.GhclibParserEx.Fixity as GhclibPar
9394import qualified Refact.Fixity as Refact
9495#endif
9596
96- import Ide.Logger
9797import Ide.Plugin.Config hiding
9898 (Config )
9999import Ide.Plugin.Properties
@@ -125,13 +125,21 @@ import System.Environment (setEnv,
125125import Text.Regex.TDFA.Text ()
126126-- ---------------------------------------------------------------------
127127
128- newtype Log
128+ data Log
129129 = LogShake Shake. Log
130+ | LogApplying NormalizedFilePath (Either String WorkspaceEdit )
131+ | LogGeneratedIdeas NormalizedFilePath [[Refact. Refactoring Refact. SrcSpan ]]
132+ | LogGetIdeas NormalizedFilePath
133+ | LogUsingExtensions NormalizedFilePath [String ] -- Extension is only imported conditionally, so we just stringify them
130134 deriving Show
131135
132136instance Pretty Log where
133137 pretty = \ case
134138 LogShake log -> pretty log
139+ LogApplying fp res -> " Applying hint(s) for" <+> viaShow fp <> " :" <+> viaShow res
140+ LogGeneratedIdeas fp ideas -> " Generated hlint ideas for for" <+> viaShow fp <> " :" <+> viaShow ideas
141+ LogUsingExtensions fp exts -> " Using extensions for " <+> viaShow fp <> " :" <+> pretty exts
142+ LogGetIdeas fp -> " Getting hlint ideas for " <+> viaShow fp
135143
136144#ifdef HLINT_ON_GHC_LIB
137145-- Reimplementing this, since the one in Development.IDE.GHC.Compat isn't for ghc-lib
@@ -148,8 +156,8 @@ descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeSta
148156descriptor recorder plId = (defaultPluginDescriptor plId)
149157 { pluginRules = rules recorder plId
150158 , pluginCommands =
151- [ PluginCommand " applyOne" " Apply a single hint" applyOneCmd
152- , PluginCommand " applyAll" " Apply all hints to the file" applyAllCmd
159+ [ PluginCommand " applyOne" " Apply a single hint" ( applyOneCmd recorder)
160+ , PluginCommand " applyAll" " Apply all hints to the file" ( applyAllCmd recorder)
153161 ]
154162 , pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionProvider
155163 , pluginConfigDescriptor = defaultConfigDescriptor
@@ -179,7 +187,7 @@ rules recorder plugin = do
179187 define (cmapWithPrio LogShake recorder) $ \ GetHlintDiagnostics file -> do
180188 config <- getClientConfigAction def
181189 let hlintOn = pluginEnabledConfig plcDiagnosticsOn plugin config
182- ideas <- if hlintOn then getIdeas file else return (Right [] )
190+ ideas <- if hlintOn then getIdeas recorder file else return (Right [] )
183191 return (diagnostics file ideas, Just () )
184192
185193 defineNoFile (cmapWithPrio LogShake recorder) $ \ GetHlintSettings -> do
@@ -247,9 +255,9 @@ rules recorder plugin = do
247255 }
248256 srcSpanToRange (UnhelpfulSpan _) = noRange
249257
250- getIdeas :: NormalizedFilePath -> Action (Either ParseError [Idea ])
251- getIdeas nfp = do
252- debugm $ " hlint:getIdeas:file: " ++ show nfp
258+ getIdeas :: Recorder ( WithPriority Log ) -> NormalizedFilePath -> Action (Either ParseError [Idea ])
259+ getIdeas recorder nfp = do
260+ logWith recorder Debug $ LogGetIdeas nfp
253261 (flags, classify, hint) <- useNoFile_ GetHlintSettings
254262
255263 let applyHints' (Just (Right modEx)) = Right $ applyHints classify hint [modEx]
@@ -295,7 +303,7 @@ getIdeas nfp = do
295303
296304 setExtensions flags = do
297305 hlintExts <- getExtensions nfp
298- debugm $ " hlint:getIdeas:setExtensions: " ++ show hlintExts
306+ logWith recorder Debug $ LogUsingExtensions $ nfp ( fmap show hlintExts)
299307 return $ flags { enabledExtensions = hlintExts }
300308
301309-- Gets extensions from ModSummary dynflags for the file.
@@ -469,15 +477,14 @@ mkSuppressHintTextEdits dynFlags fileContents hint =
469477 combinedTextEdit : lineSplitTextEditList
470478-- ---------------------------------------------------------------------
471479
472- applyAllCmd :: CommandFunction IdeState Uri
473- applyAllCmd ide uri = do
480+ applyAllCmd :: Recorder ( WithPriority Log ) -> CommandFunction IdeState Uri
481+ applyAllCmd recorder ide uri = do
474482 let file = maybe (error $ show uri ++ " is not a file." )
475483 toNormalizedFilePath'
476484 (uriToFilePath' uri)
477485 withIndefiniteProgress " Applying all hints" Cancellable $ do
478- logm $ " hlint:applyAllCmd:file=" ++ show file
479- res <- liftIO $ applyHint ide file Nothing
480- logm $ " hlint:applyAllCmd:res=" ++ show res
486+ res <- liftIO $ applyHint recorder ide file Nothing
487+ logWith recorder Debug $ LogApplying file res
481488 case res of
482489 Left err -> pure $ Left (responseError (T. pack $ " hlint:applyAll: " ++ show err))
483490 Right fs -> do
@@ -500,34 +507,33 @@ data OneHint = OneHint
500507 , oneHintTitle :: HintTitle
501508 } deriving (Eq , Show )
502509
503- applyOneCmd :: CommandFunction IdeState ApplyOneParams
504- applyOneCmd ide (AOP uri pos title) = do
510+ applyOneCmd :: Recorder ( WithPriority Log ) -> CommandFunction IdeState ApplyOneParams
511+ applyOneCmd recorder ide (AOP uri pos title) = do
505512 let oneHint = OneHint pos title
506513 let file = maybe (error $ show uri ++ " is not a file." ) toNormalizedFilePath'
507514 (uriToFilePath' uri)
508515 let progTitle = " Applying hint: " <> title
509516 withIndefiniteProgress progTitle Cancellable $ do
510- logm $ " hlint:applyOneCmd:file=" ++ show file
511- res <- liftIO $ applyHint ide file (Just oneHint)
512- logm $ " hlint:applyOneCmd:res=" ++ show res
517+ res <- liftIO $ applyHint recorder ide file (Just oneHint)
518+ logWith recorder Debug $ LogApplying file res
513519 case res of
514520 Left err -> pure $ Left (responseError (T. pack $ " hlint:applyOne: " ++ show err))
515521 Right fs -> do
516522 _ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing fs) (\ _ -> pure () )
517523 pure $ Right Null
518524
519- applyHint :: IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
520- applyHint ide nfp mhint =
525+ applyHint :: Recorder ( WithPriority Log ) -> IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
526+ applyHint recorder ide nfp mhint =
521527 runExceptT $ do
522528 let runAction' :: Action a -> IO a
523529 runAction' = runAction " applyHint" ide
524530 let errorHandlers = [ Handler $ \ e -> return (Left (show (e :: IOException )))
525531 , Handler $ \ e -> return (Left (show (e :: ErrorCall )))
526532 ]
527- ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas nfp
533+ ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas recorder nfp
528534 let ideas' = maybe ideas (`filterIdeas` ideas) mhint
529535 let commands = map ideaRefactoring ideas'
530- liftIO $ logm $ " applyHint:apply= " ++ show commands
536+ logWith recorder Debug $ LogGeneratedIdeas nfp commands
531537 let fp = fromNormalizedFilePath nfp
532538 (_, mbOldContent) <- liftIO $ runAction' $ getFileContents nfp
533539 oldContent <- maybe (liftIO $ fmap T. decodeUtf8 (BS. readFile fp)) return mbOldContent
@@ -584,7 +590,6 @@ applyHint ide nfp mhint =
584590 Right appliedFile -> do
585591 let uri = fromNormalizedUri (filePathToUri' nfp)
586592 let wsEdit = diffText' True (uri, oldContent) (T. pack appliedFile) IncludeDeletions
587- liftIO $ logm $ " hlint:applyHint:diff=" ++ show wsEdit
588593 ExceptT $ return (Right wsEdit)
589594 Left err ->
590595 throwE err
0 commit comments