Skip to content

Commit 757d4a5

Browse files
committed
Unify argument and parameter
Follow LSP specification, we use parameter.
1 parent 8d6b1bb commit 757d4a5

File tree

2 files changed

+48
-48
lines changed

2 files changed

+48
-48
lines changed

plugins/hls-signature-help-plugin/src/Ide/Plugin/SignatureHelp.hs

Lines changed: 39 additions & 39 deletions
Original file line numberDiff line numberDiff line change
@@ -98,26 +98,26 @@ signatureHelpProvider ideState _pluginId (SignatureHelpParams (TextDocumentIdent
9898
( \span hieAst -> do
9999
let functionNode = getLeftMostNode hieAst
100100
(functionName, functionTypes) <- getNodeNameAndTypes hieKind functionNode
101-
argumentNumber <- getArgumentNumber span hieAst
102-
Just (functionName, functionTypes, argumentNumber)
101+
parameterIndex <- getParameterIndex span hieAst
102+
Just (functionName, functionTypes, parameterIndex)
103103
)
104104
(docMap, argDocMap) <- runIdeActionE "signatureHelp.docMap" (shakeExtras ideState) $ do
105105
mResult <- ExceptT $ Right <$> useWithStaleFast GetDocMap nfp
106106
case mResult of
107107
Just (DKMap docMap _tyThingMap argDocMap, _positionMapping) -> pure (docMap, argDocMap)
108108
Nothing -> pure (mempty, mempty)
109109
case results of
110-
[(_functionName, [], _argumentNumber)] -> pure $ InR Null
111-
[(functionName, functionTypes, argumentNumber)] ->
112-
pure $ InL $ mkSignatureHelp mSignatureHelpContext docMap argDocMap (fromIntegral argumentNumber - 1) functionName functionTypes
110+
[(_functionName, [], _parameterIndex)] -> pure $ InR Null
111+
[(functionName, functionTypes, parameterIndex)] ->
112+
pure $ InL $ mkSignatureHelp mSignatureHelpContext docMap argDocMap (fromIntegral parameterIndex - 1) functionName functionTypes
113113
_ -> pure $ InR Null
114114

115115
mkSignatureHelp :: Maybe SignatureHelpContext -> DocMap -> ArgDocMap -> UInt -> Name -> [Type] -> SignatureHelp
116-
mkSignatureHelp mSignatureHelpContext docMap argDocMap argumentNumber functionName functionTypes =
116+
mkSignatureHelp mSignatureHelpContext docMap argDocMap parameterIndex functionName functionTypes =
117117
SignatureHelp
118-
(mkSignatureInformation docMap argDocMap argumentNumber functionName <$> functionTypes)
118+
(mkSignatureInformation docMap argDocMap parameterIndex functionName <$> functionTypes)
119119
activeSignature
120-
(Just $ InL argumentNumber)
120+
(Just $ InL parameterIndex)
121121
where
122122
activeSignature = case mSignatureHelpContext of
123123
Just
@@ -130,7 +130,7 @@ mkSignatureHelp mSignatureHelpContext docMap argDocMap argumentNumber functionNa
130130
_ -> Just 0
131131

132132
mkSignatureInformation :: DocMap -> ArgDocMap -> UInt -> Name -> Type -> SignatureInformation
133-
mkSignatureInformation docMap argDocMap argumentNumber functionName functionType =
133+
mkSignatureInformation docMap argDocMap parameterIndex functionName functionType =
134134
let functionNameLabelPrefix = printOutputableOneLine (ppr functionName) <> " :: "
135135
mFunctionDoc = case lookupNameEnv docMap functionName of
136136
Nothing -> Nothing
@@ -141,19 +141,19 @@ mkSignatureInformation docMap argDocMap argumentNumber functionName functionType
141141
in SignatureInformation
142142
(functionNameLabelPrefix <> printOutputableOneLine functionType)
143143
mFunctionDoc
144-
(Just $ mkArguments thisArgDocMap (fromIntegral $ T.length functionNameLabelPrefix) functionType)
145-
(Just $ InL argumentNumber)
144+
(Just $ mkParameterInformations thisArgDocMap (fromIntegral $ T.length functionNameLabelPrefix) functionType)
145+
(Just $ InL parameterIndex)
146146

147-
mkArguments :: IntMap SpanDoc -> UInt -> Type -> [ParameterInformation]
148-
mkArguments thisArgDocMap offset functionType =
149-
[ ParameterInformation (InR range) mArgDoc
150-
| (argIndex, range) <- zip [0 ..] (bimap (+ offset) (+ offset) <$> findArgumentRanges functionType),
151-
let mArgDoc = case IntMap.lookup argIndex thisArgDocMap of
147+
mkParameterInformations :: IntMap SpanDoc -> UInt -> Type -> [ParameterInformation]
148+
mkParameterInformations thisArgDocMap offset functionType =
149+
[ ParameterInformation (InR range) mParameterDoc
150+
| (parameterIndex, range) <- zip [0 ..] (bimap (+ offset) (+ offset) <$> findParameterRanges functionType),
151+
let mParameterDoc = case IntMap.lookup parameterIndex thisArgDocMap of
152152
Nothing -> Nothing
153153
Just spanDoc -> Just $ InR $ mkMarkdownDoc $ removeUris spanDoc
154154
]
155155
where
156-
-- we already show uris in the function doc, no need to duplicate them in the arg doc
156+
-- we already show uris in the function doc, no need to duplicate them in the parameter doc
157157
removeUris (SpanDocString docs _uris) = SpanDocString docs emptyUris
158158
removeUris (SpanDocText docs _uris) = SpanDocText docs emptyUris
159159

@@ -162,16 +162,16 @@ mkArguments thisArgDocMap offset functionType =
162162
mkMarkdownDoc :: SpanDoc -> MarkupContent
163163
mkMarkdownDoc = spanDocToMarkdown >>> T.unlines >>> MarkupContent MarkupKind_Markdown
164164

165-
findArgumentRanges :: Type -> [(UInt, UInt)]
166-
findArgumentRanges functionType =
165+
findParameterRanges :: Type -> [(UInt, UInt)]
166+
findParameterRanges functionType =
167167
let functionTypeString = printOutputableOneLine functionType
168168
functionTypeStringLength = fromIntegral $ T.length functionTypeString
169169
splitFunctionTypes = filter notTypeConstraint $ splitFunTysIgnoringForAll functionType
170170
splitFunctionTypeStrings = printOutputableOneLine . fst <$> splitFunctionTypes
171171
-- reverse to avoid matching "a" of "forall a" in "forall a. a -> a"
172172
reversedRanges =
173173
drop 1 $ -- do not need the range of the result (last) type
174-
findArgumentStringRanges
174+
findParameterStringRanges
175175
0
176176
(T.reverse functionTypeString)
177177
(T.reverse <$> reverse splitFunctionTypeStrings)
@@ -193,34 +193,34 @@ Some tricky cases are as follows:
193193
f :: forall a. Maybe a -> forall b. (a, b) -> b
194194
- '=>' can appear anywhere in a type
195195
g :: forall a b. Eq a => a -> Num b => b -> b
196-
- ppr the first argument type of '(a -> b) -> a -> b' is 'a -> b' (no parentheses)
196+
- ppr the first parameter type of '(a -> b) -> a -> b' is 'a -> b' (no parentheses)
197197
- 'forall' is not always shown
198198
199199
Alternative method 2: use only unstructured type string
200200
This method is hard to implement because we need to parse the type string.
201201
Some tricky cases are as follows:
202202
- h :: forall a (m :: Type -> Type). Monad m => a -> m a
203203
-}
204-
findArgumentStringRanges :: UInt -> Text -> [Text] -> [(UInt, UInt)]
205-
findArgumentStringRanges _totalPrefixLength _functionTypeString [] = []
206-
findArgumentStringRanges totalPrefixLength functionTypeString (argumentTypeString : restArgumentTypeStrings) =
207-
let (prefix, match) = T.breakOn argumentTypeString functionTypeString
204+
findParameterStringRanges :: UInt -> Text -> [Text] -> [(UInt, UInt)]
205+
findParameterStringRanges _totalPrefixLength _functionTypeString [] = []
206+
findParameterStringRanges totalPrefixLength functionTypeString (parameterTypeString : restParameterTypeStrings) =
207+
let (prefix, match) = T.breakOn parameterTypeString functionTypeString
208208
prefixLength = fromIntegral $ T.length prefix
209-
argumentTypeStringLength = fromIntegral $ T.length argumentTypeString
209+
parameterTypeStringLength = fromIntegral $ T.length parameterTypeString
210210
start = totalPrefixLength + prefixLength
211-
in (start, start + argumentTypeStringLength)
212-
: findArgumentStringRanges
213-
(totalPrefixLength + prefixLength + argumentTypeStringLength)
214-
(T.drop (fromIntegral argumentTypeStringLength) match)
215-
restArgumentTypeStrings
211+
in (start, start + parameterTypeStringLength)
212+
: findParameterStringRanges
213+
(totalPrefixLength + prefixLength + parameterTypeStringLength)
214+
(T.drop (fromIntegral parameterTypeStringLength) match)
215+
restParameterTypeStrings
216216

217217
-- similar to 'splitFunTys' but
218218
-- 1) the result (last) type is included and
219219
-- 2) toplevel foralls are ignored
220220
splitFunTysIgnoringForAll :: Type -> [(Type, Maybe FunTyFlag)]
221221
splitFunTysIgnoringForAll ty = case ty & dropForAlls & splitFunTy_maybe of
222-
Just (funTyFlag, _mult, argumentType, resultType) ->
223-
(argumentType, Just funTyFlag) : splitFunTysIgnoringForAll resultType
222+
Just (funTyFlag, _mult, parameterType, resultType) ->
223+
(parameterType, Just funTyFlag) : splitFunTysIgnoringForAll resultType
224224
Nothing -> [(ty, Nothing)]
225225

226226
notTypeConstraint :: (Type, Maybe FunTyFlag) -> Bool
@@ -287,22 +287,22 @@ getNodeNameAndTypes hieKind hieAst =
287287
isUse :: IdentifierDetails a -> Bool
288288
isUse = identInfo >>> S.member Use
289289

290-
-- Just 1 means the first argument
291-
getArgumentNumber :: RealSrcSpan -> HieAST a -> Maybe Integer
292-
getArgumentNumber span hieAst
290+
-- Just 1 means the first parameter
291+
getParameterIndex :: RealSrcSpan -> HieAST a -> Maybe Integer
292+
getParameterIndex span hieAst
293293
| nodeHasAnnotation ("HsApp", "HsExpr") hieAst =
294294
case nodeChildren hieAst of
295295
[leftChild, _] ->
296296
if span `isRealSubspanOf` nodeSpan leftChild
297297
then Nothing
298-
else getArgumentNumber span leftChild >>= \argumentNumber -> Just (argumentNumber + 1)
298+
else getParameterIndex span leftChild >>= \parameterIndex -> Just (parameterIndex + 1)
299299
_ -> Nothing -- impossible
300300
| nodeHasAnnotation ("HsAppType", "HsExpr") hieAst =
301301
case nodeChildren hieAst of
302-
[leftChild, _] -> getArgumentNumber span leftChild
302+
[leftChild, _] -> getParameterIndex span leftChild
303303
_ -> Nothing -- impossible
304304
| otherwise =
305305
case nodeChildren hieAst of
306306
[] -> Just 0 -- the function is found
307-
[child] -> getArgumentNumber span child -- ignore irrelevant nodes
307+
[child] -> getParameterIndex span child -- ignore irrelevant nodes
308308
_ -> Nothing

plugins/hls-signature-help-plugin/test/Main.hs

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -202,7 +202,7 @@ main =
202202
[ Nothing,
203203
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: forall abcdefghijklmn. Num abcdefghijklmn => abcdefghijklmn -> abcdefghijklmn -> abcdefghijklmn -> abcdefghijklmn -> abcdefghijklmn" Nothing (Just [ParameterInformation (InR (50, 64)) Nothing, ParameterInformation (InR (68, 82)) Nothing, ParameterInformation (InR (86, 100)) Nothing, ParameterInformation (InR (104, 118)) Nothing]) (Just (InL 0)), SignatureInformation "f :: Integer -> Integer -> Integer -> Integer -> Integer" Nothing (Just [ParameterInformation (InR (5, 12)) Nothing, ParameterInformation (InR (16, 23)) Nothing, ParameterInformation (InR (27, 34)) Nothing, ParameterInformation (InR (38, 45)) Nothing]) (Just (InL 0))] (Just 0) (Just (InL 0))
204204
],
205-
-- TODO fix bug of wrong arg range in the function type string
205+
-- TODO fix bug of wrong parameter range in the function type string
206206
-- https://github.com/haskell/haskell-language-server/pull/4626#discussion_r2261133076
207207
mkTestExpectFail
208208
"middle =>"
@@ -233,7 +233,7 @@ main =
233233
]
234234
),
235235
mkTest
236-
"=> in argument"
236+
"=> in parameter"
237237
[__i|
238238
f :: Eq a => a -> (Num b => b -> b) -> a
239239
f = _
@@ -270,7 +270,7 @@ main =
270270
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: forall a. Maybe a -> forall b. (a, b) -> b" Nothing (Just [ParameterInformation (InR (15, 22)) Nothing, ParameterInformation (InR (36, 42)) Nothing]) (Just (InL 0)), SignatureInformation "f :: Maybe Bool -> forall b. (Bool, b) -> b" Nothing (Just [ParameterInformation (InR (5, 15)) Nothing, ParameterInformation (InR (29, 38)) Nothing]) (Just (InL 0))] (Just 0) (Just (InL 0)),
271271
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: forall a. Maybe a -> forall b. (a, b) -> b" Nothing (Just [ParameterInformation (InR (15, 22)) Nothing, ParameterInformation (InR (36, 42)) Nothing]) (Just (InL 0)), SignatureInformation "f :: Maybe Integer -> forall b. (Integer, b) -> b" Nothing (Just [ParameterInformation (InR (5, 18)) Nothing, ParameterInformation (InR (32, 44)) Nothing]) (Just (InL 0))] (Just 0) (Just (InL 0))
272272
],
273-
-- TODO fix bug of wrong arg range in the function type string
273+
-- TODO fix bug of wrong parameter range in the function type string
274274
-- https://github.com/haskell/haskell-language-server/pull/4626#discussion_r2261133076
275275
mkTestExpectFail
276276
"RankNTypes(forall in middle), another"
@@ -290,7 +290,7 @@ main =
290290
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: forall l. l -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (25, 26)) Nothing, ParameterInformation (InR (30, 31)) Nothing]) (Just (InL 0)), SignatureInformation "f :: Integer -> forall a. a -> a" Nothing (Just [ParameterInformation (InR (5, 12)) Nothing, ParameterInformation (InR (26, 27)) Nothing]) (Just (InL 0))] (Just 0) (Just (InL 0))
291291
]
292292
),
293-
-- TODO fix bug of wrong arg range in the function type string
293+
-- TODO fix bug of wrong parameter range in the function type string
294294
-- https://github.com/haskell/haskell-language-server/pull/4626#discussion_r2261133076
295295
mkTestExpectFail
296296
"RankNTypes(forall in middle), again"
@@ -338,13 +338,13 @@ main =
338338
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: Bool -> Bool" (Just $ InR $ MarkupContent MarkupKind_Markdown "The `f` function does something to a bool value") (Just [ParameterInformation (InR (5, 9)) Nothing]) (Just (InL 0))] (Just 0) (Just (InL 0))
339339
],
340340
mkTest
341-
"function and arguments documentation"
341+
"function and parameters documentation"
342342
[__i|
343343
-- |Doc for function 'f'.
344344
f ::
345-
-- | The first 'Bool' argument
345+
-- | The first 'Bool' parameter
346346
Bool ->
347-
-- | The second 'Int' argument
347+
-- | The second 'Int' parameter
348348
Int ->
349349
-- | The return value
350350
Bool
@@ -353,7 +353,7 @@ main =
353353
^ ^
354354
|]
355355
[ Nothing,
356-
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: Bool -> Int -> Bool" (Just $ InR $ MarkupContent MarkupKind_Markdown "Doc for function `f`") (Just [ParameterInformation (InR (5, 9)) (Just $ InR $ MarkupContent MarkupKind_Markdown "The first `Bool` argument"), ParameterInformation (InR (13, 16)) (Just $ InR $ MarkupContent MarkupKind_Markdown "The second `Int` argument")]) (Just (InL 0))] (Just 0) (Just (InL 0))
356+
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "f :: Bool -> Int -> Bool" (Just $ InR $ MarkupContent MarkupKind_Markdown "Doc for function `f`") (Just [ParameterInformation (InR (5, 9)) (Just $ InR $ MarkupContent MarkupKind_Markdown "The first `Bool` parameter"), ParameterInformation (InR (13, 16)) (Just $ InR $ MarkupContent MarkupKind_Markdown "The second `Int` parameter")]) (Just (InL 0))] (Just 0) (Just (InL 0))
357357
],
358358
mkTest
359359
"imported function with no documentation"
@@ -365,7 +365,7 @@ main =
365365
Just $ SimilarSignatureHelp $ SignatureHelp [SignatureInformation "even :: forall a. Integral a => a -> Bool" (Just $ InR $ MarkupContent MarkupKind_Markdown "") (Just [ParameterInformation (InR (32, 33)) Nothing]) (Just (InL 0)), SignatureInformation "even :: Integer -> Bool" (Just $ InR $ MarkupContent MarkupKind_Markdown "") (Just [ParameterInformation (InR (8, 15)) Nothing]) (Just (InL 0))] (Just 0) (Just (InL 0))
366366
],
367367
mkTest
368-
"imported function with argument documentation"
368+
"imported function with parameter documentation"
369369
[__i|
370370
import Language.Haskell.TH.Lib (mkBytes)
371371
x = mkBytes _

0 commit comments

Comments
 (0)