Skip to content

Commit 6975503

Browse files
committed
Log plugin name
1 parent b378de2 commit 6975503

File tree

6 files changed

+44
-49
lines changed

6 files changed

+44
-49
lines changed

plugins/hls-alternate-number-format-plugin/src/Ide/Plugin/AlternateNumberFormat.hs

Lines changed: 12 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -43,11 +43,8 @@ instance Pretty Log where
4343
pretty = \case
4444
LogShake log -> pretty log
4545

46-
alternateNumberFormatId :: IsString a => a
47-
alternateNumberFormatId = "alternateNumberFormat"
48-
49-
descriptor :: Recorder (WithPriority Log) -> PluginDescriptor IdeState
50-
descriptor recorder = (defaultPluginDescriptor alternateNumberFormatId)
46+
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
47+
descriptor recorder pId = (defaultPluginDescriptor pId)
5148
{ pluginHandlers = mkPluginHandler STextDocumentCodeAction codeActionHandler
5249
, pluginRules = collectLiteralsRule recorder
5350
}
@@ -87,10 +84,10 @@ collectLiteralsRule recorder = define (cmapWithPrio LogShake recorder) $ \Collec
8784
getExtensions = map GhcExtension . toList . extensionFlags . ms_hspp_opts . pm_mod_summary
8885

8986
codeActionHandler :: PluginMethodHandler IdeState 'TextDocumentCodeAction
90-
codeActionHandler state _ (CodeActionParams _ _ docId currRange _) = pluginResponse $ do
87+
codeActionHandler state pId (CodeActionParams _ _ docId currRange _) = pluginResponse $ do
9188
nfp <- getNormalizedFilePath (docId ^. L.uri)
92-
CLR{..} <- requestLiterals state nfp
93-
pragma <- getFirstPragma state nfp
89+
CLR{..} <- requestLiterals pId state nfp
90+
pragma <- getFirstPragma pId state nfp
9491
-- remove any invalid literals (see validTarget comment)
9592
let litsInRange = filter inCurrentRange literals
9693
-- generate alternateFormats and zip with the literal that generated the alternates
@@ -145,16 +142,16 @@ contains Range {_start, _end} x = isInsideRealSrcSpan _start x || isInsideRealSr
145142
isInsideRealSrcSpan :: Position -> RealSrcSpan -> Bool
146143
p `isInsideRealSrcSpan` r = let (Range sp ep) = realSrcSpanToRange r in sp <= p && p <= ep
147144

148-
getFirstPragma :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m NextPragmaInfo
149-
getFirstPragma state nfp = handleMaybeM "Error: Could not get NextPragmaInfo" $ do
150-
ghcSession <- liftIO $ runAction (alternateNumberFormatId <> ".GhcSession") state $ useWithStale GhcSession nfp
151-
(_, fileContents) <- liftIO $ runAction (alternateNumberFormatId <> ".GetFileContents") state $ getFileContents nfp
145+
getFirstPragma :: MonadIO m => PluginId -> IdeState -> NormalizedFilePath -> ExceptT String m NextPragmaInfo
146+
getFirstPragma pId state nfp = handleMaybeM "Error: Could not get NextPragmaInfo" $ do
147+
ghcSession <- liftIO $ runAction (show pId <> ".GhcSession") state $ useWithStale GhcSession nfp
148+
(_, fileContents) <- liftIO $ runAction (show pId <> ".GetFileContents") state $ getFileContents nfp
152149
case ghcSession of
153150
Just (hscEnv -> hsc_dflags -> sessionDynFlags, _) -> pure $ Just $ getNextPragmaInfo sessionDynFlags fileContents
154151
Nothing -> pure Nothing
155152

156-
requestLiterals :: MonadIO m => IdeState -> NormalizedFilePath -> ExceptT String m CollectLiteralsResult
157-
requestLiterals state = handleMaybeM "Error: Could not Collect Literals"
153+
requestLiterals :: MonadIO m => PluginId -> IdeState -> NormalizedFilePath -> ExceptT String m CollectLiteralsResult
154+
requestLiterals pId state = handleMaybeM "Error: Could not Collect Literals"
158155
. liftIO
159-
. runAction (alternateNumberFormatId <> ".CollectLiterals") state
156+
. runAction (show pId <> ".CollectLiterals") state
160157
. use CollectLiterals

plugins/hls-alternate-number-format-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,7 +20,7 @@ main :: IO ()
2020
main = defaultTestRunner test
2121

2222
alternateNumberFormatPlugin :: PluginDescriptor IdeState
23-
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty
23+
alternateNumberFormatPlugin = AlternateNumberFormat.descriptor mempty "alternateNumberFormat"
2424

2525
-- NOTE: For whatever reason, this plugin does not play nice with creating Code Actions on time.
2626
-- As a result tests will mostly pass if `import Prelude` is added at the top. We (mostly fendor) surmise this has something

plugins/hls-explicit-fixity-plugin/src/Ide/Plugin/ExplicitFixity.hs

Lines changed: 2 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -36,11 +36,8 @@ import Ide.PluginUtils (getNormalizedFilePath,
3636
import Ide.Types hiding (pluginId)
3737
import Language.LSP.Types
3838

39-
pluginId :: PluginId
40-
pluginId = "explicitFixity"
41-
42-
descriptor :: Recorder (WithPriority Log) -> PluginDescriptor IdeState
43-
descriptor recorder = (defaultPluginDescriptor pluginId)
39+
descriptor :: Recorder (WithPriority Log) -> PluginId -> PluginDescriptor IdeState
40+
descriptor recorder pluginId = (defaultPluginDescriptor pluginId)
4441
{ pluginRules = fixityRule recorder
4542
, pluginHandlers = mkPluginHandler STextDocumentHover hover
4643
-- Make this plugin has a lower priority than ghcide's plugin to ensure

plugins/hls-explicit-fixity-plugin/test/Main.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ import System.FilePath
88
import Test.Hls
99

1010
plugin :: PluginDescriptor IdeState
11-
plugin = descriptor mempty
11+
plugin = descriptor mempty "explicit-fixity"
1212

1313
main :: IO ()
1414
main = defaultTestRunner tests

plugins/hls-module-name-plugin/src/Ide/Plugin/ModuleName.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ import qualified Data.Text as T
3333
import Development.IDE (GetParsedModule (GetParsedModule),
3434
GhcSession (GhcSession),
3535
IdeState, Pretty,
36-
Priority (Debug, Info), Recorder,
36+
Priority (Debug), Recorder,
3737
WithPriority, colon, evalGhcEnv,
3838
hscEnvWithImportPaths, logWith,
3939
realSrcSpanToRange, runAction,
@@ -112,7 +112,7 @@ action recorder state uri =
112112
correctNames <- liftIO $ pathModuleNames recorder state nfp fp
113113
logWith recorder Debug (CorrectNames correctNames)
114114
bestName <- minimumBy (comparing T.length) <$> (MaybeT . pure $ NE.nonEmpty correctNames)
115-
logWith recorder Info (BestName bestName)
115+
logWith recorder Debug (BestName bestName)
116116

117117
statedNameMaybe <- liftIO $ codeModuleName state nfp
118118
logWith recorder Debug (ModuleName $ snd <$> statedNameMaybe)

src/HlsPlugins.hs

Lines changed: 26 additions & 25 deletions
Original file line numberDiff line numberDiff line change
@@ -6,11 +6,12 @@ module HlsPlugins where
66
import Development.IDE.Types.Logger (Pretty (pretty), Recorder,
77
WithPriority, cmapWithPrio)
88
import Ide.PluginUtils (pluginDescToIdePlugins)
9-
import Ide.Types (IdePlugins)
9+
import Ide.Types (IdePlugins, PluginId)
1010

1111
-- fixed plugins
1212
import Development.IDE (IdeState)
1313
import qualified Development.IDE.Plugin.HLS.GhcIde as GhcIde
14+
import GHC.Exts (fromString)
1415

1516
-- haskell-language-server optional plugins
1617
#if hls_qualifyImportedNames
@@ -119,10 +120,10 @@ import qualified Ide.Plugin.Brittany as Brittany
119120
import qualified Development.IDE.Plugin.CodeAction as Refactor
120121
#endif
121122

122-
data Log = forall a. (Pretty a) => Log a
123+
data Log = forall a. (Pretty a) => Log PluginId a
123124

124125
instance Pretty Log where
125-
pretty (Log a) = pretty a
126+
pretty (Log pId a) = fromString (show pId) <> ": " <> pretty a
126127

127128
-- ---------------------------------------------------------------------
128129

@@ -134,8 +135,8 @@ instance Pretty Log where
134135
idePlugins :: Recorder (WithPriority Log) -> IdePlugins IdeState
135136
idePlugins recorder = pluginDescToIdePlugins allPlugins
136137
where
137-
pluginRecorder :: forall log. (Pretty log) => Recorder (WithPriority log)
138-
pluginRecorder = cmapWithPrio Log recorder
138+
pluginRecorder :: forall log. (Pretty log) => PluginId -> Recorder (WithPriority log)
139+
pluginRecorder pluginId = cmapWithPrio (Log pluginId) recorder
139140
allPlugins =
140141
#if hls_pragmas
141142
Pragmas.descriptor "pragmas" :
@@ -144,10 +145,10 @@ idePlugins recorder = pluginDescToIdePlugins allPlugins
144145
Floskell.descriptor "floskell" :
145146
#endif
146147
#if hls_fourmolu
147-
Fourmolu.descriptor pluginRecorder "fourmolu" :
148+
let pId = "fourmolu" in Fourmolu.descriptor (pluginRecorder pId) pId:
148149
#endif
149150
#if hls_tactic
150-
Tactic.descriptor pluginRecorder "tactics" :
151+
let pId = "tactics" in Tactic.descriptor (pluginRecorder pId) pId:
151152
#endif
152153
#if hls_ormolu
153154
Ormolu.descriptor "ormolu" :
@@ -156,7 +157,7 @@ idePlugins recorder = pluginDescToIdePlugins allPlugins
156157
StylishHaskell.descriptor "stylish-haskell" :
157158
#endif
158159
#if hls_rename
159-
Rename.descriptor pluginRecorder "rename" :
160+
let pId = "rename" in Rename.descriptor (pluginRecorder pId) pId:
160161
#endif
161162
#if hls_retrie
162163
Retrie.descriptor "retrie" :
@@ -168,40 +169,40 @@ idePlugins recorder = pluginDescToIdePlugins allPlugins
168169
CallHierarchy.descriptor :
169170
#endif
170171
#if hls_class
171-
Class.descriptor pluginRecorder "class" :
172+
let pId = "class" in Class.descriptor (pluginRecorder pId) pId:
172173
#endif
173174
#if hls_haddockComments
174-
HaddockComments.descriptor pluginRecorder "haddockComments" :
175+
let pId = "haddockComments" in HaddockComments.descriptor (pluginRecorder pId) pId:
175176
#endif
176177
#if hls_eval
177-
Eval.descriptor pluginRecorder "eval" :
178+
let pId = "eval" in Eval.descriptor (pluginRecorder pId) pId:
178179
#endif
179180
#if hls_importLens
180-
ExplicitImports.descriptor pluginRecorder "importLens" :
181+
let pId = "importLens" in ExplicitImports.descriptor (pluginRecorder pId) pId:
181182
#endif
182183
#if hls_qualifyImportedNames
183184
QualifyImportedNames.descriptor "qualifyImportedNames" :
184185
#endif
185186
#if hls_refineImports
186-
RefineImports.descriptor pluginRecorder "refineImports" :
187+
let pId = "refineImports" in RefineImports.descriptor (pluginRecorder pId) pId:
187188
#endif
188189
#if hls_moduleName
189-
ModuleName.descriptor pluginRecorder "moduleName" :
190+
let pId = "moduleName" in ModuleName.descriptor (pluginRecorder pId) pId:
190191
#endif
191192
#if hls_hlint
192-
Hlint.descriptor pluginRecorder "hlint" :
193+
let pId = "hlint" in Hlint.descriptor (pluginRecorder pId) pId:
193194
#endif
194195
#if hls_stan
195-
Stan.descriptor pluginRecorder "stan" :
196+
let pId = "stan" in Stan.descriptor (pluginRecorder pId) pId :
196197
#endif
197198
#if hls_splice
198199
Splice.descriptor "splice" :
199200
#endif
200201
#if hls_alternateNumberFormat
201-
AlternateNumberFormat.descriptor pluginRecorder :
202+
let pId = "alternateNumberFormat" in AlternateNumberFormat.descriptor (pluginRecorder pId) pId :
202203
#endif
203204
#if hls_codeRange
204-
CodeRange.descriptor pluginRecorder "codeRange" :
205+
let pId = "codeRange" in CodeRange.descriptor (pluginRecorder pId) pId:
205206
#endif
206207
#if hls_changeTypeSignature
207208
ChangeTypeSignature.descriptor :
@@ -210,14 +211,14 @@ idePlugins recorder = pluginDescToIdePlugins allPlugins
210211
GADT.descriptor "gadt" :
211212
#endif
212213
#if hls_refactor
213-
Refactor.iePluginDescriptor pluginRecorder "ghcide-code-actions-imports-exports" :
214-
Refactor.typeSigsPluginDescriptor pluginRecorder "ghcide-code-actions-type-signatures" :
215-
Refactor.bindingsPluginDescriptor pluginRecorder "ghcide-code-actions-bindings" :
216-
Refactor.fillHolePluginDescriptor pluginRecorder "ghcide-code-actions-fill-holes" :
217-
Refactor.extendImportPluginDescriptor pluginRecorder "ghcide-extend-import-action" :
214+
let pId = "ghcide-code-actions-imports-exports" in Refactor.iePluginDescriptor (pluginRecorder pId) pId :
215+
let pId = "ghcide-code-actions-type-signatures" in Refactor.typeSigsPluginDescriptor (pluginRecorder pId) pId :
216+
let pId = "ghcide-code-actions-bindings" in Refactor.bindingsPluginDescriptor (pluginRecorder pId) pId :
217+
let pId = "ghcide-code-actions-fill-holes" in Refactor.fillHolePluginDescriptor (pluginRecorder pId) pId :
218+
let pId = "ghcide-extend-import-action" in Refactor.extendImportPluginDescriptor (pluginRecorder pId) pId :
218219
#endif
219-
GhcIde.descriptors pluginRecorder
220+
GhcIde.descriptors (pluginRecorder "ghcide")
220221
#if explicitFixity
221-
++ [ExplicitFixity.descriptor pluginRecorder]
222+
++ [let pId = "explicit-fixity" in ExplicitFixity.descriptor (pluginRecorder pId) pId]
222223
#endif
223224

0 commit comments

Comments
 (0)