@@ -55,6 +55,7 @@ import Development.IDE.Core.Rules (defineNoFil
55
55
usePropertyAction )
56
56
import Development.IDE.Core.Shake (getDiagnostics )
57
57
import qualified Refact.Apply as Refact
58
+ import qualified Refact.Types as Refact
58
59
59
60
#ifdef HLINT_ON_GHC_LIB
60
61
import Development.IDE.GHC.Compat (BufSpan ,
@@ -84,7 +85,7 @@ import System.IO (IOMode (Wri
84
85
import System.IO.Temp
85
86
#else
86
87
import Development.IDE.GHC.Compat hiding
87
- (setEnv )
88
+ (setEnv , (<+>) )
88
89
import GHC.Generics (Associativity (LeftAssociative , NotAssociative , RightAssociative ))
89
90
import Language.Haskell.GHC.ExactPrint.Delta (deltaOptions )
90
91
import Language.Haskell.GHC.ExactPrint.Parsers (postParseTransform )
@@ -93,7 +94,6 @@ import Language.Haskell.GhclibParserEx.Fixity as GhclibPar
93
94
import qualified Refact.Fixity as Refact
94
95
#endif
95
96
96
- import Ide.Logger
97
97
import Ide.Plugin.Config hiding
98
98
(Config )
99
99
import Ide.Plugin.Properties
@@ -125,13 +125,21 @@ import System.Environment (setEnv,
125
125
import Text.Regex.TDFA.Text ()
126
126
-- ---------------------------------------------------------------------
127
127
128
- newtype Log
128
+ data Log
129
129
= 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
130
134
deriving Show
131
135
132
136
instance Pretty Log where
133
137
pretty = \ case
134
138
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
135
143
136
144
#ifdef HLINT_ON_GHC_LIB
137
145
-- 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
148
156
descriptor recorder plId = (defaultPluginDescriptor plId)
149
157
{ pluginRules = rules recorder plId
150
158
, 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)
153
161
]
154
162
, pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionProvider
155
163
, pluginConfigDescriptor = defaultConfigDescriptor
@@ -179,7 +187,7 @@ rules recorder plugin = do
179
187
define (cmapWithPrio LogShake recorder) $ \ GetHlintDiagnostics file -> do
180
188
config <- getClientConfigAction def
181
189
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 [] )
183
191
return (diagnostics file ideas, Just () )
184
192
185
193
defineNoFile (cmapWithPrio LogShake recorder) $ \ GetHlintSettings -> do
@@ -247,9 +255,9 @@ rules recorder plugin = do
247
255
}
248
256
srcSpanToRange (UnhelpfulSpan _) = noRange
249
257
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
253
261
(flags, classify, hint) <- useNoFile_ GetHlintSettings
254
262
255
263
let applyHints' (Just (Right modEx)) = Right $ applyHints classify hint [modEx]
@@ -295,7 +303,7 @@ getIdeas nfp = do
295
303
296
304
setExtensions flags = do
297
305
hlintExts <- getExtensions nfp
298
- debugm $ " hlint:getIdeas:setExtensions: " ++ show hlintExts
306
+ logWith recorder Debug $ LogUsingExtensions nfp ( fmap show hlintExts)
299
307
return $ flags { enabledExtensions = hlintExts }
300
308
301
309
-- Gets extensions from ModSummary dynflags for the file.
@@ -469,15 +477,14 @@ mkSuppressHintTextEdits dynFlags fileContents hint =
469
477
combinedTextEdit : lineSplitTextEditList
470
478
-- ---------------------------------------------------------------------
471
479
472
- applyAllCmd :: CommandFunction IdeState Uri
473
- applyAllCmd ide uri = do
480
+ applyAllCmd :: Recorder ( WithPriority Log ) -> CommandFunction IdeState Uri
481
+ applyAllCmd recorder ide uri = do
474
482
let file = maybe (error $ show uri ++ " is not a file." )
475
483
toNormalizedFilePath'
476
484
(uriToFilePath' uri)
477
485
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
481
488
case res of
482
489
Left err -> pure $ Left (responseError (T. pack $ " hlint:applyAll: " ++ show err))
483
490
Right fs -> do
@@ -500,34 +507,33 @@ data OneHint = OneHint
500
507
, oneHintTitle :: HintTitle
501
508
} deriving (Eq , Show )
502
509
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
505
512
let oneHint = OneHint pos title
506
513
let file = maybe (error $ show uri ++ " is not a file." ) toNormalizedFilePath'
507
514
(uriToFilePath' uri)
508
515
let progTitle = " Applying hint: " <> title
509
516
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
513
519
case res of
514
520
Left err -> pure $ Left (responseError (T. pack $ " hlint:applyOne: " ++ show err))
515
521
Right fs -> do
516
522
_ <- sendRequest SWorkspaceApplyEdit (ApplyWorkspaceEditParams Nothing fs) (\ _ -> pure () )
517
523
pure $ Right Null
518
524
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 =
521
527
runExceptT $ do
522
528
let runAction' :: Action a -> IO a
523
529
runAction' = runAction " applyHint" ide
524
530
let errorHandlers = [ Handler $ \ e -> return (Left (show (e :: IOException )))
525
531
, Handler $ \ e -> return (Left (show (e :: ErrorCall )))
526
532
]
527
- ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas nfp
533
+ ideas <- bimapExceptT showParseError id $ ExceptT $ runAction' $ getIdeas recorder nfp
528
534
let ideas' = maybe ideas (`filterIdeas` ideas) mhint
529
535
let commands = map ideaRefactoring ideas'
530
- liftIO $ logm $ " applyHint:apply= " ++ show commands
536
+ logWith recorder Debug $ LogGeneratedIdeas nfp commands
531
537
let fp = fromNormalizedFilePath nfp
532
538
(_, mbOldContent) <- liftIO $ runAction' $ getFileContents nfp
533
539
oldContent <- maybe (liftIO $ fmap T. decodeUtf8 (BS. readFile fp)) return mbOldContent
@@ -584,7 +590,6 @@ applyHint ide nfp mhint =
584
590
Right appliedFile -> do
585
591
let uri = fromNormalizedUri (filePathToUri' nfp)
586
592
let wsEdit = diffText' True (uri, oldContent) (T. pack appliedFile) IncludeDeletions
587
- liftIO $ logm $ " hlint:applyHint:diff=" ++ show wsEdit
588
593
ExceptT $ return (Right wsEdit)
589
594
Left err ->
590
595
throwE err
0 commit comments