1212{-# LANGUAGE TupleSections #-}
1313{-# LANGUAGE TypeFamilies #-}
1414{-# LANGUAGE ViewPatterns #-}
15- {-# OPTIONS_GHC -Wno-orphans #-}
1615{-# LANGUAGE LambdaCase #-}
1716{-# LANGUAGE MultiWayIf #-}
1817{-# LANGUAGE NamedFieldPuns #-}
1918{-# LANGUAGE RecordWildCards #-}
19+ {-# LANGUAGE StrictData #-}
20+
21+ {-# OPTIONS_GHC -Wno-orphans #-}
2022
2123#ifdef HLINT_ON_GHC_LIB
2224#define MIN_GHC_API_VERSION(x,y,z) MIN_VERSION_ghc_lib(x,y,z)
@@ -55,6 +57,7 @@ import Development.IDE.Core.Rules (defineNoFil
5557 usePropertyAction )
5658import Development.IDE.Core.Shake (getDiagnostics )
5759import qualified Refact.Apply as Refact
60+ import qualified Refact.Types as Refact
5861
5962#ifdef HLINT_ON_GHC_LIB
6063import Development.IDE.GHC.Compat (BufSpan ,
@@ -84,7 +87,7 @@ import System.IO (IOMode (Wri
8487import System.IO.Temp
8588#else
8689import Development.IDE.GHC.Compat hiding
87- (setEnv )
90+ (setEnv , (<+>) )
8891import GHC.Generics (Associativity (LeftAssociative , NotAssociative , RightAssociative ))
8992import Language.Haskell.GHC.ExactPrint.Delta (deltaOptions )
9093import Language.Haskell.GHC.ExactPrint.Parsers (postParseTransform )
@@ -93,7 +96,6 @@ import Language.Haskell.GhclibParserEx.Fixity as GhclibPar
9396import qualified Refact.Fixity as Refact
9497#endif
9598
96- import Ide.Logger
9799import Ide.Plugin.Config hiding
98100 (Config )
99101import Ide.Plugin.Properties
@@ -125,13 +127,21 @@ import System.Environment (setEnv,
125127import Text.Regex.TDFA.Text ()
126128-- ---------------------------------------------------------------------
127129
128- newtype Log
130+ data Log
129131 = LogShake Shake. Log
132+ | LogApplying NormalizedFilePath (Either String WorkspaceEdit )
133+ | LogGeneratedIdeas NormalizedFilePath [[Refact. Refactoring Refact. SrcSpan ]]
134+ | LogGetIdeas NormalizedFilePath
135+ | LogUsingExtensions NormalizedFilePath [String ] -- Extension is only imported conditionally, so we just stringify them
130136 deriving Show
131137
132138instance Pretty Log where
133139 pretty = \ case
134140 LogShake log -> pretty log
141+ LogApplying fp res -> " Applying hint(s) for" <+> viaShow fp <> " :" <+> viaShow res
142+ LogGeneratedIdeas fp ideas -> " Generated hlint ideas for for" <+> viaShow fp <> " :" <+> viaShow ideas
143+ LogUsingExtensions fp exts -> " Using extensions for " <+> viaShow fp <> " :" <+> pretty exts
144+ LogGetIdeas fp -> " Getting hlint ideas for " <+> viaShow fp
135145
136146#ifdef HLINT_ON_GHC_LIB
137147-- Reimplementing this, since the one in Development.IDE.GHC.Compat isn't for ghc-lib
@@ -148,8 +158,8 @@ descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeSta
148158descriptor recorder plId = (defaultPluginDescriptor plId)
149159 { pluginRules = rules recorder plId
150160 , pluginCommands =
151- [ PluginCommand " applyOne" " Apply a single hint" applyOneCmd
152- , PluginCommand " applyAll" " Apply all hints to the file" applyAllCmd
161+ [ PluginCommand " applyOne" " Apply a single hint" ( applyOneCmd recorder)
162+ , PluginCommand " applyAll" " Apply all hints to the file" ( applyAllCmd recorder)
153163 ]
154164 , pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionProvider
155165 , pluginConfigDescriptor = defaultConfigDescriptor
@@ -179,7 +189,7 @@ rules recorder plugin = do
179189 define (cmapWithPrio LogShake recorder) $ \ GetHlintDiagnostics file -> do
180190 config <- getClientConfigAction def
181191 let hlintOn = pluginEnabledConfig plcDiagnosticsOn plugin config
182- ideas <- if hlintOn then getIdeas file else return (Right [] )
192+ ideas <- if hlintOn then getIdeas recorder file else return (Right [] )
183193 return (diagnostics file ideas, Just () )
184194
185195 defineNoFile (cmapWithPrio LogShake recorder) $ \ GetHlintSettings -> do
@@ -247,9 +257,9 @@ rules recorder plugin = do
247257 }
248258 srcSpanToRange (UnhelpfulSpan _) = noRange
249259
250- getIdeas :: NormalizedFilePath -> Action (Either ParseError [Idea ])
251- getIdeas nfp = do
252- debugm $ " hlint:getIdeas:file: " ++ show nfp
260+ getIdeas :: Recorder ( WithPriority Log ) -> NormalizedFilePath -> Action (Either ParseError [Idea ])
261+ getIdeas recorder nfp = do
262+ logWith recorder Debug $ LogGetIdeas nfp
253263 (flags, classify, hint) <- useNoFile_ GetHlintSettings
254264
255265 let applyHints' (Just (Right modEx)) = Right $ applyHints classify hint [modEx]
@@ -295,7 +305,7 @@ getIdeas nfp = do
295305
296306 setExtensions flags = do
297307 hlintExts <- getExtensions nfp
298- debugm $ " hlint:getIdeas:setExtensions: " ++ show hlintExts
308+ logWith recorder Debug $ LogUsingExtensions nfp ( fmap show hlintExts)
299309 return $ flags { enabledExtensions = hlintExts }
300310
301311-- Gets extensions from ModSummary dynflags for the file.
@@ -469,15 +479,14 @@ mkSuppressHintTextEdits dynFlags fileContents hint =
469479 combinedTextEdit : lineSplitTextEditList
470480-- ---------------------------------------------------------------------
471481
472- applyAllCmd :: CommandFunction IdeState Uri
473- applyAllCmd ide uri = do
482+ applyAllCmd :: Recorder ( WithPriority Log ) -> CommandFunction IdeState Uri
483+ applyAllCmd recorder ide uri = do
474484 let file = maybe (error $ show uri ++ " is not a file." )
475485 toNormalizedFilePath'
476486 (uriToFilePath' uri)
477487 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
488+ res <- liftIO $ applyHint recorder ide file Nothing
489+ logWith recorder Debug $ LogApplying file res
481490 case res of
482491 Left err -> pure $ Left (responseError (T. pack $ " hlint:applyAll: " ++ show err))
483492 Right fs -> do
@@ -500,34 +509,33 @@ data OneHint = OneHint
500509 , oneHintTitle :: HintTitle
501510 } deriving (Eq , Show )
502511
503- applyOneCmd :: CommandFunction IdeState ApplyOneParams
504- applyOneCmd ide (AOP uri pos title) = do
512+ applyOneCmd :: Recorder ( WithPriority Log ) -> CommandFunction IdeState ApplyOneParams
513+ applyOneCmd recorder ide (AOP uri pos title) = do
505514 let oneHint = OneHint pos title
506515 let file = maybe (error $ show uri ++ " is not a file." ) toNormalizedFilePath'
507516 (uriToFilePath' uri)
508517 let progTitle = " Applying hint: " <> title
509518 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
519+ res <- liftIO $ applyHint recorder ide file (Just oneHint)
520+ logWith recorder Debug $ LogApplying file res
513521 case res of
514522 Left err -> pure $ Left (responseError (T. pack $ " hlint:applyOne: " ++ show err))
515523 Right fs -> do
516524 _ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing fs) (\ _ -> pure () )
517525 pure $ Right Null
518526
519- applyHint :: IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
520- applyHint ide nfp mhint =
527+ applyHint :: Recorder ( WithPriority Log ) -> IdeState -> NormalizedFilePath -> Maybe OneHint -> IO (Either String WorkspaceEdit )
528+ applyHint recorder ide nfp mhint =
521529 runExceptT $ do
522530 let runAction' :: Action a -> IO a
523531 runAction' = runAction " applyHint" ide
524532 let errorHandlers = [ Handler $ \ e -> return (Left (show (e :: IOException )))
525533 , Handler $ \ e -> return (Left (show (e :: ErrorCall )))
526534 ]
527- ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas nfp
535+ ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas recorder nfp
528536 let ideas' = maybe ideas (`filterIdeas` ideas) mhint
529537 let commands = map ideaRefactoring ideas'
530- liftIO $ logm $ " applyHint:apply= " ++ show commands
538+ logWith recorder Debug $ LogGeneratedIdeas nfp commands
531539 let fp = fromNormalizedFilePath nfp
532540 (_, mbOldContent) <- liftIO $ runAction' $ getFileContents nfp
533541 oldContent <- maybe (liftIO $ fmap T. decodeUtf8 (BS. readFile fp)) return mbOldContent
@@ -584,7 +592,6 @@ applyHint ide nfp mhint =
584592 Right appliedFile -> do
585593 let uri = fromNormalizedUri (filePathToUri' nfp)
586594 let wsEdit = diffText' True (uri, oldContent) (T. pack appliedFile) IncludeDeletions
587- liftIO $ logm $ " hlint:applyHint:diff=" ++ show wsEdit
588595 ExceptT $ return (Right wsEdit)
589596 Left err ->
590597 throwE err
0 commit comments