Skip to content

Commit 6f6f75b

Browse files
Add Goto Definition for cabal common sections (#4375)
* Add goto-definitions for cabal common sections * Add default direct cradle hie.yaml file to testdata * incorporate changes requested in #4375 * add tests for cabal goto-definition
1 parent 9565d0b commit 6f6f75b

File tree

5 files changed

+268
-4
lines changed

5 files changed

+268
-4
lines changed

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal.hs

Lines changed: 32 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -17,12 +17,14 @@ import qualified Data.ByteString as BS
1717
import Data.Hashable
1818
import Data.HashMap.Strict (HashMap)
1919
import qualified Data.HashMap.Strict as HashMap
20+
import Data.List (find)
2021
import qualified Data.List.NonEmpty as NE
2122
import qualified Data.Maybe as Maybe
2223
import qualified Data.Text as T
2324
import qualified Data.Text.Encoding as Encoding
2425
import Data.Typeable
2526
import Development.IDE as D
27+
import Development.IDE.Core.PluginUtils
2628
import Development.IDE.Core.Shake (restartShakeSession)
2729
import qualified Development.IDE.Core.Shake as Shake
2830
import Development.IDE.Graph (Key, alwaysRerun)
@@ -31,6 +33,7 @@ import Development.IDE.Types.Shake (toKey)
3133
import qualified Distribution.Fields as Syntax
3234
import qualified Distribution.Parsec.Position as Syntax
3335
import GHC.Generics
36+
import Ide.Plugin.Cabal.Completion.CabalFields as CabalFields
3437
import qualified Ide.Plugin.Cabal.Completion.Completer.Types as CompleterTypes
3538
import qualified Ide.Plugin.Cabal.Completion.Completions as Completions
3639
import Ide.Plugin.Cabal.Completion.Types (ParseCabalCommonSections (ParseCabalCommonSections),
@@ -43,6 +46,7 @@ import qualified Ide.Plugin.Cabal.LicenseSuggest as LicenseSuggest
4346
import Ide.Plugin.Cabal.Orphans ()
4447
import Ide.Plugin.Cabal.Outline
4548
import qualified Ide.Plugin.Cabal.Parse as Parse
49+
import Ide.Plugin.Error
4650
import Ide.Types
4751
import qualified Language.LSP.Protocol.Lens as JL
4852
import qualified Language.LSP.Protocol.Message as LSP
@@ -93,6 +97,7 @@ descriptor recorder plId =
9397
, mkPluginHandler LSP.SMethod_TextDocumentCompletion $ completion recorder
9498
, mkPluginHandler LSP.SMethod_TextDocumentDocumentSymbol moduleOutline
9599
, mkPluginHandler LSP.SMethod_TextDocumentCodeAction $ fieldSuggestCodeAction recorder
100+
, mkPluginHandler LSP.SMethod_TextDocumentDefinition gotoDefinition
96101
]
97102
, pluginNotificationHandlers =
98103
mconcat
@@ -277,6 +282,33 @@ fieldSuggestCodeAction recorder ide _ (CodeActionParams _ _ (TextDocumentIdentif
277282
let completionTexts = fmap (^. JL.label) completions
278283
pure $ FieldSuggest.fieldErrorAction uri fieldName completionTexts _range
279284

285+
-- | CodeActions for going to definitions.
286+
--
287+
-- Provides a CodeAction for going to a definition when clicking on an identifier.
288+
-- The definition is found by traversing the sections and comparing their name to
289+
-- the clicked identifier.
290+
--
291+
-- TODO: Support more definitions than sections.
292+
gotoDefinition :: PluginMethodHandler IdeState LSP.Method_TextDocumentDefinition
293+
gotoDefinition ideState _ msgParam = do
294+
nfp <- getNormalizedFilePathE uri
295+
cabalFields <- runActionE "cabal-plugin.commonSections" ideState $ useE ParseCabalFields nfp
296+
case CabalFields.findTextWord cursor cabalFields of
297+
Nothing ->
298+
pure $ InR $ InR Null
299+
Just cursorText -> do
300+
commonSections <- runActionE "cabal-plugin.commonSections" ideState $ useE ParseCabalCommonSections nfp
301+
case find (isSectionArgName cursorText) commonSections of
302+
Nothing ->
303+
pure $ InR $ InR Null
304+
Just commonSection -> do
305+
pure $ InL $ Definition $ InL $ Location uri $ CabalFields.getFieldLSPRange commonSection
306+
where
307+
cursor = Types.lspPositionToCabalPosition (msgParam ^. JL.position)
308+
uri = msgParam ^. JL.textDocument . JL.uri
309+
isSectionArgName name (Syntax.Section _ sectionArgName _) = name == CabalFields.onelineSectionArgs sectionArgName
310+
isSectionArgName _ _ = False
311+
280312
-- ----------------------------------------------------------------
281313
-- Cabal file of Interest rules and global variable
282314
-- ----------------------------------------------------------------

plugins/hls-cabal-plugin/src/Ide/Plugin/Cabal/Completion/CabalFields.hs

Lines changed: 116 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,29 @@
1-
module Ide.Plugin.Cabal.Completion.CabalFields (findStanzaForColumn, findFieldSection, getOptionalSectionName, getAnnotation, getFieldName, onelineSectionArgs) where
1+
module Ide.Plugin.Cabal.Completion.CabalFields
2+
( findStanzaForColumn,
3+
findFieldSection,
4+
findTextWord,
5+
findFieldLine,
6+
getOptionalSectionName,
7+
getAnnotation,
8+
getFieldName,
9+
onelineSectionArgs,
10+
getFieldEndPosition,
11+
getSectionArgEndPosition,
12+
getNameEndPosition,
13+
getFieldLineEndPosition,
14+
getFieldLSPRange
15+
) where
216

17+
import qualified Data.ByteString as BS
18+
import Data.List (find)
319
import Data.List.NonEmpty (NonEmpty)
420
import qualified Data.List.NonEmpty as NE
521
import qualified Data.Text as T
622
import qualified Data.Text.Encoding as T
723
import qualified Distribution.Fields as Syntax
824
import qualified Distribution.Parsec.Position as Syntax
925
import Ide.Plugin.Cabal.Completion.Types
26+
import qualified Language.LSP.Protocol.Types as LSP
1027

1128
-- ----------------------------------------------------------------
1229
-- Cabal-syntax utilities I don't really want to write myself
@@ -28,7 +45,7 @@ findStanzaForColumn col ctx = case NE.uncons ctx of
2845
--
2946
-- The result is said field and its starting position
3047
-- or Nothing if the passed list of fields is empty.
31-
48+
--
3249
-- This only looks at the row of the cursor and not at the cursor's
3350
-- position within the row.
3451
--
@@ -46,6 +63,71 @@ findFieldSection cursor (x:y:ys)
4663
where
4764
cursorLine = Syntax.positionRow cursor
4865

66+
-- | Determine the field line the cursor is currently a part of.
67+
--
68+
-- The result is said field line and its starting position
69+
-- or Nothing if the passed list of fields is empty.
70+
--
71+
-- This function assumes that elements in a field's @FieldLine@ list
72+
-- do not share the same row.
73+
findFieldLine :: Syntax.Position -> [Syntax.Field Syntax.Position] -> Maybe (Syntax.FieldLine Syntax.Position)
74+
findFieldLine _cursor [] = Nothing
75+
findFieldLine cursor fields =
76+
case findFieldSection cursor fields of
77+
Nothing -> Nothing
78+
Just (Syntax.Field _ fieldLines) -> find filterLineFields fieldLines
79+
Just (Syntax.Section _ _ fields) -> findFieldLine cursor fields
80+
where
81+
cursorLine = Syntax.positionRow cursor
82+
-- In contrast to `Field` or `Section`, `FieldLine` must have the exact
83+
-- same line position as the cursor.
84+
filterLineFields (Syntax.FieldLine pos _) = Syntax.positionRow pos == cursorLine
85+
86+
-- | Determine the exact word at the current cursor position.
87+
--
88+
-- The result is said word or Nothing if the passed list is empty
89+
-- or the cursor position is not next to, or on a word.
90+
-- For this function, a word is a sequence of consecutive characters
91+
-- that are not a space or column.
92+
--
93+
-- This function currently only considers words inside of a @FieldLine@.
94+
findTextWord :: Syntax.Position -> [Syntax.Field Syntax.Position] -> Maybe T.Text
95+
findTextWord _cursor [] = Nothing
96+
findTextWord cursor fields =
97+
case findFieldLine cursor fields of
98+
Nothing -> Nothing
99+
Just (Syntax.FieldLine pos byteString) ->
100+
let decodedText = T.decodeUtf8 byteString
101+
lineFieldCol = Syntax.positionCol pos
102+
lineFieldLen = T.length decodedText
103+
offset = cursorCol - lineFieldCol in
104+
-- Range check if cursor is inside or or next to found line.
105+
-- The latter comparison includes the length of the line as offset,
106+
-- which is done to also include cursors that are at the end of a line.
107+
-- e.g. "foo,bar|"
108+
-- ^
109+
-- cursor
110+
--
111+
-- Having an offset which is outside of the line is possible because of `splitAt`.
112+
if offset >= 0 && lineFieldLen >= offset
113+
then
114+
let (lhs, rhs) = T.splitAt offset decodedText
115+
strippedLhs = T.takeWhileEnd isAllowedChar lhs
116+
strippedRhs = T.takeWhile isAllowedChar rhs
117+
resultText = T.concat [strippedLhs, strippedRhs] in
118+
-- It could be possible that the cursor was in-between separators, in this
119+
-- case the resulting text would be empty, which should result in `Nothing`.
120+
-- e.g. " foo ,| bar"
121+
-- ^
122+
-- cursor
123+
if not $ T.null resultText then Just resultText else Nothing
124+
else
125+
Nothing
126+
where
127+
cursorCol = Syntax.positionCol cursor
128+
separators = [',', ' ']
129+
isAllowedChar = (`notElem` separators)
130+
49131
type FieldName = T.Text
50132

51133
getAnnotation :: Syntax.Field ann -> ann
@@ -73,12 +155,42 @@ getOptionalSectionName (x:xs) = case x of
73155
--
74156
-- For example, @flag@ @(@ @pedantic@ @)@ will be joined in
75157
-- one line, instead of four @SectionArg@s separately.
76-
onelineSectionArgs :: [Syntax.SectionArg Syntax.Position] -> T.Text
158+
onelineSectionArgs :: [Syntax.SectionArg ann] -> T.Text
77159
onelineSectionArgs sectionArgs = joinedName
78160
where
79161
joinedName = T.unwords $ map getName sectionArgs
80162

81-
getName :: Syntax.SectionArg Syntax.Position -> T.Text
163+
getName :: Syntax.SectionArg ann -> T.Text
82164
getName (Syntax.SecArgName _ identifier) = T.decodeUtf8 identifier
83165
getName (Syntax.SecArgStr _ quotedString) = T.decodeUtf8 quotedString
84166
getName (Syntax.SecArgOther _ string) = T.decodeUtf8 string
167+
168+
169+
-- | Returns the end position of a provided field
170+
getFieldEndPosition :: Syntax.Field Syntax.Position -> Syntax.Position
171+
getFieldEndPosition (Syntax.Field name []) = getNameEndPosition name
172+
getFieldEndPosition (Syntax.Field _ (x:xs)) = getFieldLineEndPosition $ NE.last (x NE.:| xs)
173+
getFieldEndPosition (Syntax.Section name [] []) = getNameEndPosition name
174+
getFieldEndPosition (Syntax.Section _ (x:xs) []) = getSectionArgEndPosition $ NE.last (x NE.:| xs)
175+
getFieldEndPosition (Syntax.Section _ _ (x:xs)) = getFieldEndPosition $ NE.last (x NE.:| xs)
176+
177+
-- | Returns the end position of a provided section arg
178+
getSectionArgEndPosition :: Syntax.SectionArg Syntax.Position -> Syntax.Position
179+
getSectionArgEndPosition (Syntax.SecArgName (Syntax.Position row col) byteString) = Syntax.Position row (col + BS.length byteString)
180+
getSectionArgEndPosition (Syntax.SecArgStr (Syntax.Position row col) byteString) = Syntax.Position row (col + BS.length byteString)
181+
getSectionArgEndPosition (Syntax.SecArgOther (Syntax.Position row col) byteString) = Syntax.Position row (col + BS.length byteString)
182+
183+
-- | Returns the end position of a provided name
184+
getNameEndPosition :: Syntax.Name Syntax.Position -> Syntax.Position
185+
getNameEndPosition (Syntax.Name (Syntax.Position row col) byteString) = Syntax.Position row (col + BS.length byteString)
186+
187+
-- | Returns the end position of a provided field line
188+
getFieldLineEndPosition :: Syntax.FieldLine Syntax.Position -> Syntax.Position
189+
getFieldLineEndPosition (Syntax.FieldLine (Syntax.Position row col) byteString) = Syntax.Position row (col + BS.length byteString)
190+
191+
-- | Returns an LSP compatible range for a provided field
192+
getFieldLSPRange :: Syntax.Field Syntax.Position -> LSP.Range
193+
getFieldLSPRange field = LSP.Range startLSPPos endLSPPos
194+
where
195+
startLSPPos = cabalPositionToLSPPosition $ getAnnotation field
196+
endLSPPos = cabalPositionToLSPPosition $ getFieldEndPosition field

plugins/hls-cabal-plugin/test/Main.hs

Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ import qualified Data.Text as Text
2020
import Ide.Plugin.Cabal.LicenseSuggest (licenseErrorSuggestion)
2121
import qualified Ide.Plugin.Cabal.Parse as Lib
2222
import qualified Language.LSP.Protocol.Lens as L
23+
import qualified Language.LSP.Protocol.Types as LSP
2324
import Outline (outlineTests)
2425
import System.FilePath
2526
import Test.Hls
@@ -36,6 +37,7 @@ main = do
3637
, contextTests
3738
, outlineTests
3839
, codeActionTests
40+
, gotoDefinitionTests
3941
]
4042

4143
-- ------------------------------------------------------------------------
@@ -227,3 +229,56 @@ codeActionTests = testGroup "Code Actions"
227229
InR action@CodeAction{_title} <- codeActions
228230
guard (_title == "Replace with " <> license)
229231
pure action
232+
233+
-- ----------------------------------------------------------------------------
234+
-- Goto Definition Tests
235+
-- ----------------------------------------------------------------------------
236+
237+
gotoDefinitionTests :: TestTree
238+
gotoDefinitionTests = testGroup "Goto Definition"
239+
[ positiveTest "middle of identifier" (mkP 27 16) (mkR 6 0 7 22)
240+
, positiveTest "left of identifier" (mkP 30 12) (mkR 10 0 17 40)
241+
, positiveTest "right of identifier" (mkP 33 22) (mkR 20 0 23 34)
242+
, positiveTest "left of '-' in identifier" (mkP 36 20) (mkR 6 0 7 22)
243+
, positiveTest "right of '-' in identifier" (mkP 39 19) (mkR 10 0 17 40)
244+
, positiveTest "identifier in identifier list" (mkP 42 16) (mkR 20 0 23 34)
245+
, positiveTest "left of ',' right of identifier" (mkP 45 33) (mkR 10 0 17 40)
246+
, positiveTest "right of ',' left of identifier" (mkP 48 34) (mkR 6 0 7 22)
247+
248+
, negativeTest "right of ',' left of space" (mkP 51 23)
249+
, negativeTest "right of ':' left of space" (mkP 54 11)
250+
, negativeTest "not a definition" (mkP 57 8)
251+
, negativeTest "empty space" (mkP 59 7)
252+
]
253+
where
254+
mkP :: UInt -> UInt -> Position
255+
mkP x1 y1 = Position x1 y1
256+
257+
mkR :: UInt -> UInt -> UInt -> UInt -> Range
258+
mkR x1 y1 x2 y2 = Range (mkP x1 y1) (mkP x2 y2)
259+
260+
getDefinition :: Show b => (Definition |? b) -> Range
261+
getDefinition (InL (Definition (InL loc))) = loc^.L.range
262+
getDefinition unk = error $ "Unexpected pattern '" ++ show unk ++ "' , expected '(InL (Definition (InL loc))'"
263+
264+
-- A positive test checks if the provided range is equal
265+
-- to the expected range from the definition in the test file.
266+
-- The test emulates a goto-definition request of an actual definition.
267+
positiveTest :: TestName -> Position -> Range -> TestTree
268+
positiveTest testName cursorPos expectedRange =
269+
runCabalTestCaseSession testName "goto-definition" $ do
270+
doc <- openDoc "simple-with-common.cabal" "cabal"
271+
definitions <- getDefinitions doc cursorPos
272+
let locationRange = getDefinition definitions
273+
liftIO $ locationRange @?= expectedRange
274+
275+
-- A negative test checks if the request failed and
276+
-- the provided result is empty, i.e. `InR $ InR Null`.
277+
-- The test emulates a goto-definition request of anything but an
278+
-- actual definition.
279+
negativeTest :: TestName -> Position -> TestTree
280+
negativeTest testName cursorPos =
281+
runCabalTestCaseSession testName "goto-definition" $ do
282+
doc <- openDoc "simple-with-common.cabal" "cabal"
283+
empty <- getDefinitions doc cursorPos
284+
liftIO $ empty @?= (InR $ InR LSP.Null)
Lines changed: 62 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,62 @@
1+
cabal-version: 3.0
2+
name: simple-cabal
3+
version: 0.1.0.0
4+
license: MIT
5+
6+
-- Range : (6, 0) - (7, 22)
7+
common warnings-0
8+
ghc-options: -Wall
9+
10+
-- Range : (10, 0) - (17, 40)
11+
common warnings-1
12+
ghc-options: -Wall
13+
-Wredundant-constraints
14+
-Wunused-packages
15+
16+
-Wno-name-shadowing
17+
18+
-Wno-unticked-promoted-constructors
19+
20+
-- Range : (20, 0) - (23, 34)
21+
common warnings-2
22+
ghc-options: -Wall
23+
-Wredundant-constraints
24+
-Wunused-packages
25+
26+
library
27+
28+
import: warnings-0
29+
-- ^ Position: (27, 16), middle of identifier
30+
31+
import: warnings-1
32+
-- ^ Position: (30, 12), left of identifier
33+
34+
import: warnings-2
35+
-- ^ Position: (33, 22), right of identifier
36+
37+
import: warnings-0
38+
-- ^ Position: (36, 20), left of '-' in identifier
39+
40+
import: warnings-1
41+
-- ^ Position: (39, 19), right of "-" in identifier
42+
43+
import: warnings-2,warnings-1,warnings-0
44+
-- ^ Position: (42, 16), identifier in identifier list
45+
46+
import: warnings-2,warnings-1,warnings-0
47+
-- ^ Position: (45, 33), left of ',' right of identifier
48+
49+
import: warnings-2,warnings-1,warnings-0
50+
-- ^ Position: (48, 34), right of ',' left of identifier
51+
52+
import: warnings-2, warnings-1,warnings-0
53+
-- ^ Position: (51, 37), right of ',' left of space
54+
55+
import: warnings-0
56+
-- ^ Position: (54, 11), right of ':' left of space
57+
58+
import: warnings-0
59+
-- ^ Position: (57, 8), not a definition
60+
61+
-- EOL
62+
-- ^ Position: (59, 7), empty space
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
cradle:
2+
direct:
3+
arguments: []

0 commit comments

Comments
 (0)