Skip to content

Commit 75c4ebc

Browse files
authored
Merge pull request #480 from tittoassini/moduleNamePlugin
Module Name Plugin
2 parents 93fcf93 + 7f748a9 commit 75c4ebc

File tree

11 files changed

+381
-49
lines changed

11 files changed

+381
-49
lines changed

Diff for: exe/Main.hs

+24-21
Original file line numberDiff line numberDiff line change
@@ -1,31 +1,33 @@
11
-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22
-- SPDX-License-Identifier: Apache-2.0
3-
{-# LANGUAGE CPP #-}
3+
{-# LANGUAGE CPP #-}
44
{-# LANGUAGE OverloadedStrings #-}
5-
{-# LANGUAGE RecordWildCards #-}
5+
{-# LANGUAGE RecordWildCards #-}
66
module Main(main) where
77

8-
import Ide.Arguments (Arguments(..), LspArguments(..), getArguments)
9-
import Ide.Main (defaultMain)
10-
import Ide.Types (IdePlugins)
8+
import Ide.Arguments (Arguments (..), LspArguments (..),
9+
getArguments)
10+
import Ide.Main (defaultMain)
11+
import Ide.Types (IdePlugins)
1112

1213
-- haskell-language-server plugins
13-
import Ide.Plugin.Eval as Eval
14-
import Ide.Plugin.Example as Example
15-
import Ide.Plugin.Example2 as Example2
16-
import Ide.Plugin.GhcIde as GhcIde
17-
import Ide.Plugin.Floskell as Floskell
18-
import Ide.Plugin.Fourmolu as Fourmolu
19-
import Ide.Plugin.ImportLens as ImportLens
20-
import Ide.Plugin.Ormolu as Ormolu
21-
import Ide.Plugin.StylishHaskell as StylishHaskell
22-
import Ide.Plugin.Retrie as Retrie
23-
import Ide.Plugin.Tactic as Tactic
14+
import Ide.Plugin.Eval as Eval
15+
import Ide.Plugin.Example as Example
16+
import Ide.Plugin.Example2 as Example2
17+
import Ide.Plugin.Floskell as Floskell
18+
import Ide.Plugin.Fourmolu as Fourmolu
19+
import Ide.Plugin.GhcIde as GhcIde
20+
import Ide.Plugin.ImportLens as ImportLens
21+
import Ide.Plugin.Ormolu as Ormolu
22+
import Ide.Plugin.Retrie as Retrie
23+
import Ide.Plugin.StylishHaskell as StylishHaskell
24+
import Ide.Plugin.Tactic as Tactic
2425
#if AGPL
25-
import Ide.Plugin.Brittany as Brittany
26+
import Ide.Plugin.Brittany as Brittany
2627
#endif
27-
import Ide.Plugin.Pragmas as Pragmas
28-
import Ide.Plugin (pluginDescToIdePlugins)
28+
import Ide.Plugin (pluginDescToIdePlugins)
29+
import Ide.Plugin.ModuleName as ModuleName
30+
import Ide.Plugin.Pragmas as Pragmas
2931

3032

3133
-- ---------------------------------------------------------------------
@@ -57,6 +59,7 @@ idePlugins includeExamples = pluginDescToIdePlugins allPlugins
5759
#endif
5860
, Eval.descriptor "eval"
5961
, ImportLens.descriptor "importLens"
62+
, ModuleName.descriptor "moduleName"
6063
]
6164
examplePlugins =
6265
[Example.descriptor "eg"
@@ -69,9 +72,9 @@ main :: IO ()
6972
main = do
7073
args <- getArguments "haskell-language-server"
7174

72-
let withExamples =
75+
let withExamples =
7376
case args of
7477
LspMode (LspArguments{..}) -> argsExamplePlugin
75-
_ -> False
78+
_ -> False
7679

7780
defaultMain args (idePlugins withExamples)

Diff for: haskell-language-server.cabal

+2
Original file line numberDiff line numberDiff line change
@@ -88,6 +88,7 @@ executable haskell-language-server
8888
Ide.Plugin.Floskell
8989
Ide.Plugin.Fourmolu
9090
Ide.Plugin.ImportLens
91+
Ide.Plugin.ModuleName
9192
Ide.Plugin.Ormolu
9293
Ide.Plugin.Pragmas
9394
Ide.Plugin.Retrie
@@ -262,6 +263,7 @@ test-suite func-test
262263
FunctionalLiquid
263264
HieBios
264265
Highlight
266+
ModuleName
265267
Progress
266268
Reference
267269
Rename

Diff for: hls-plugin-api/src/Ide/Plugin.hs

+1
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Ide.Plugin
1212
asGhcIdePlugin
1313
, pluginDescToIdePlugins
1414
, mkLspCommand
15+
, mkLspCmdId
1516
, allLspCmdIds
1617
, allLspCmdIds'
1718
, getPid

Diff for: plugins/default/src/Ide/Plugin/ModuleName.hs

+246
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,246 @@
1+
{-# OPTIONS_GHC -Wwarn -fno-warn-type-defaults -fno-warn-unused-binds -fno-warn-unused-imports #-}
2+
{-# LANGUAGE NamedFieldPuns #-}
3+
{-# LANGUAGE NoMonomorphismRestriction #-}
4+
{-# LANGUAGE OverloadedStrings #-}
5+
{-# LANGUAGE RecordWildCards #-}
6+
{-# LANGUAGE ScopedTypeVariables #-}
7+
8+
{-| Keep the module name in sync with its file path.
9+
10+
Provide CodeLenses to:
11+
* Add a module header ("module /moduleName/ where") to empty Haskell files
12+
* Fix the module name if incorrect
13+
-}
14+
module Ide.Plugin.ModuleName
15+
( descriptor
16+
)
17+
where
18+
19+
import Control.Monad ( join )
20+
import Control.Monad.IO.Class ( MonadIO(liftIO) )
21+
import Control.Monad.Trans.Maybe ( )
22+
import Data.Aeson ( ToJSON(toJSON)
23+
, Value(Null)
24+
)
25+
import qualified Data.HashMap.Strict as Map
26+
import Data.List ( isPrefixOf )
27+
import Data.List.Extra ( replace )
28+
import Data.Maybe ( listToMaybe )
29+
import Data.String ( IsString )
30+
import Data.Text ( Text )
31+
import qualified Data.Text as T
32+
import Development.IDE ( hscEnvWithImportPaths
33+
, GetParsedModule
34+
( GetParsedModule
35+
)
36+
, GhcSession(GhcSession)
37+
, HscEnvEq
38+
, IdeState
39+
, List(..)
40+
, NormalizedFilePath
41+
, Position(Position)
42+
, Range(Range)
43+
, evalGhcEnv
44+
, realSrcSpanToRange
45+
, runAction
46+
, toNormalizedUri
47+
, uriToFilePath'
48+
, use
49+
, use_
50+
)
51+
import Development.IDE.Plugin ( getPid )
52+
import GHC ( DynFlags(importPaths)
53+
, GenLocated(L)
54+
, HsModule(hsmodName)
55+
, ParsedModule(pm_parsed_source)
56+
, SrcSpan(RealSrcSpan)
57+
, unLoc
58+
, getSessionDynFlags
59+
)
60+
import Ide.Types ( CommandFunction
61+
, PluginCommand(..)
62+
, PluginDescriptor(..)
63+
, PluginId(..)
64+
, defaultPluginDescriptor
65+
)
66+
import Language.Haskell.LSP.Core ( LspFuncs
67+
, getVirtualFileFunc
68+
)
69+
import Language.Haskell.LSP.Types ( ApplyWorkspaceEditParams(..)
70+
, CAResult(CACodeAction)
71+
, CodeAction(CodeAction)
72+
, CodeActionKind
73+
( CodeActionQuickFix
74+
)
75+
, CodeLens(CodeLens)
76+
, CodeLensParams(CodeLensParams)
77+
, Command(Command)
78+
, ServerMethod(..)
79+
, TextDocumentIdentifier
80+
( TextDocumentIdentifier
81+
)
82+
, TextEdit(TextEdit)
83+
, Uri
84+
, WorkspaceEdit(..)
85+
, uriToNormalizedFilePath
86+
)
87+
import Language.Haskell.LSP.VFS ( virtualFileText )
88+
import System.FilePath ( splitDirectories
89+
, dropExtension
90+
)
91+
import Ide.Plugin ( mkLspCmdId )
92+
import Development.IDE.Types.Logger
93+
import Development.IDE.Core.Shake
94+
import Data.Text ( pack )
95+
import System.Directory ( canonicalizePath )
96+
import Data.List
97+
import Ide.Plugin.Tactic.Debug ( unsafeRender )
98+
-- |Plugin descriptor
99+
descriptor :: PluginId -> PluginDescriptor
100+
descriptor plId = (defaultPluginDescriptor plId)
101+
{ pluginId = plId
102+
, pluginCodeLensProvider = Just codeLens
103+
, pluginCommands = [PluginCommand editCommandName editCommandName editCmd]
104+
-- pluginCodeActionProvider = Just codeAction
105+
}
106+
107+
-- | Generate code lenses
108+
codeLens
109+
:: LspFuncs c
110+
-> IdeState
111+
-> PluginId
112+
-> CodeLensParams
113+
-> IO (Either a2 (List CodeLens))
114+
codeLens lsp state pluginId (CodeLensParams (TextDocumentIdentifier uri) _) =
115+
do
116+
pid <- getPid
117+
actions (asCodeLens (mkLspCmdId pid pluginId editCommandName)) lsp state uri
118+
119+
-- | Generate code actions.
120+
-- NOTE: Not invoked on an empty module (but codeLens is, why?)
121+
codeAction
122+
:: LspFuncs c
123+
-> IdeState
124+
-> p1
125+
-> TextDocumentIdentifier
126+
-> p2
127+
-> p3
128+
-> IO (Either a (List CAResult))
129+
codeAction lsp state _plId (TextDocumentIdentifier uri) _range _ =
130+
actions asCodeAction lsp state uri
131+
132+
editCommandName :: IsString p => p
133+
editCommandName = "edit"
134+
135+
-- | Generic command to apply a group of edits
136+
editCmd :: CommandFunction WorkspaceEdit
137+
editCmd _lf _ide workspaceEdits = return
138+
( Right Null
139+
, Just $ (WorkspaceApplyEdit, ApplyWorkspaceEditParams workspaceEdits)
140+
)
141+
142+
-- | Required actions (actually, at most one) that can be converted to either CodeLenses or CodeActions
143+
actions
144+
:: Show a1
145+
=> (Action -> a1)
146+
-> LspFuncs c
147+
-> IdeState
148+
-> Uri
149+
-> IO (Either a2 (List a1))
150+
actions convert lsp state uri = do
151+
let Just nfp = uriToNormalizedFilePath $ toNormalizedUri uri
152+
let Just fp = uriToFilePath' uri
153+
154+
contents <- liftIO $ getVirtualFileFunc lsp $ toNormalizedUri uri
155+
let emptyModule =
156+
maybe True ((== 0) . T.length . T.strip . virtualFileText) contents
157+
158+
correctNameMaybe <- pathModuleName state nfp fp
159+
statedNameMaybe <- codeModuleName state nfp
160+
out state ["correct", show correctNameMaybe, "stated", show statedNameMaybe]
161+
162+
let act = Action uri
163+
let
164+
actions = case (correctNameMaybe, statedNameMaybe) of
165+
(Just correctName, Just (nameRange, statedName))
166+
| correctName /= statedName
167+
-> [ convert $ act nameRange
168+
("Set module name to " <> correctName)
169+
correctName
170+
]
171+
(Just correctName, _) | emptyModule ->
172+
let code = T.unwords ["module", correctName, "where\n"]
173+
in [convert $ act (Range (Position 0 0) (Position 0 0)) code code]
174+
_ -> []
175+
176+
out state ["actions", show actions]
177+
pure . Right . List $ actions
178+
179+
-- | The module name, as derived by the position of the module in its source directory
180+
pathModuleName :: IdeState -> NormalizedFilePath -> String -> IO (Maybe Text)
181+
pathModuleName state normFilePath filePath = do
182+
session :: HscEnvEq <- runAction "ModuleName.ghcSession" state
183+
$ use_ GhcSession normFilePath
184+
185+
srcPaths <-
186+
evalGhcEnv (hscEnvWithImportPaths session)
187+
$ importPaths
188+
<$> getSessionDynFlags
189+
out state ["import paths", show srcPaths]
190+
paths <- mapM canonicalizePath srcPaths
191+
mdlPath <- canonicalizePath filePath
192+
out state ["canonic paths", show paths, "mdlPath", mdlPath]
193+
let maybePrefix = listToMaybe . filter (`isPrefixOf` mdlPath) $ paths
194+
out state ["prefix", show maybePrefix]
195+
196+
let maybeMdlName =
197+
(\prefix ->
198+
intercalate "."
199+
. splitDirectories
200+
. drop (length prefix + 1)
201+
$ dropExtension mdlPath
202+
)
203+
<$> maybePrefix
204+
out state ["mdlName", show maybeMdlName]
205+
return $ T.pack <$> maybeMdlName
206+
207+
-- | The module name, as stated in the module
208+
codeModuleName :: IdeState -> NormalizedFilePath -> IO (Maybe (Range, Text))
209+
codeModuleName state nfp =
210+
((\(L (RealSrcSpan l) m) -> (realSrcSpanToRange l, T.pack . show $ m)) <$>)
211+
. join
212+
. (hsmodName . unLoc . pm_parsed_source <$>)
213+
<$> runAction "ModuleName.GetParsedModule" state (use GetParsedModule nfp)
214+
215+
-- | A source code change
216+
data Action = Action {aUri::Uri,aRange::Range,aTitle::Text,aCode::Text} deriving Show
217+
218+
-- | Convert an Action to a CodeLens
219+
asCodeLens :: Text -> Action -> CodeLens
220+
asCodeLens cid act@Action {..} = CodeLens
221+
aRange
222+
(Just $ Command aTitle cid (Just (List [toJSON $ asEdit act])))
223+
Nothing
224+
225+
-- | Convert an Action to a CodeAction
226+
asCodeAction :: Action -> CAResult
227+
asCodeAction act@Action {..} = CACodeAction $ CodeAction
228+
aTitle
229+
(Just CodeActionQuickFix)
230+
(Just $ List [])
231+
(Just $ asEdit act)
232+
Nothing
233+
234+
asEdit :: Action -> WorkspaceEdit
235+
asEdit act@Action {..} =
236+
WorkspaceEdit (Just $ Map.singleton aUri $ List (asTextEdits act)) Nothing
237+
238+
asTextEdits :: Action -> [TextEdit]
239+
asTextEdits Action {..} = [TextEdit aRange aCode]
240+
241+
out :: IdeState -> [String] -> IO ()
242+
out state =
243+
logPriority (ideLogger state) Debug
244+
. pack
245+
. unwords
246+
. ("Plugin ModuleName " :)

0 commit comments

Comments
 (0)