@@ -98,26 +98,26 @@ signatureHelpProvider ideState _pluginId (SignatureHelpParams (TextDocumentIdent
98
98
( \ span hieAst -> do
99
99
let functionNode = getLeftMostNode hieAst
100
100
(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 )
103
103
)
104
104
(docMap, argDocMap) <- runIdeActionE " signatureHelp.docMap" (shakeExtras ideState) $ do
105
105
mResult <- ExceptT $ Right <$> useWithStaleFast GetDocMap nfp
106
106
case mResult of
107
107
Just (DKMap docMap _tyThingMap argDocMap, _positionMapping) -> pure (docMap, argDocMap)
108
108
Nothing -> pure (mempty , mempty )
109
109
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
113
113
_ -> pure $ InR Null
114
114
115
115
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 =
117
117
SignatureHelp
118
- (mkSignatureInformation docMap argDocMap argumentNumber functionName <$> functionTypes)
118
+ (mkSignatureInformation docMap argDocMap parameterIndex functionName <$> functionTypes)
119
119
activeSignature
120
- (Just $ InL argumentNumber )
120
+ (Just $ InL parameterIndex )
121
121
where
122
122
activeSignature = case mSignatureHelpContext of
123
123
Just
@@ -130,7 +130,7 @@ mkSignatureHelp mSignatureHelpContext docMap argDocMap argumentNumber functionNa
130
130
_ -> Just 0
131
131
132
132
mkSignatureInformation :: DocMap -> ArgDocMap -> UInt -> Name -> Type -> SignatureInformation
133
- mkSignatureInformation docMap argDocMap argumentNumber functionName functionType =
133
+ mkSignatureInformation docMap argDocMap parameterIndex functionName functionType =
134
134
let functionNameLabelPrefix = printOutputableOneLine (ppr functionName) <> " :: "
135
135
mFunctionDoc = case lookupNameEnv docMap functionName of
136
136
Nothing -> Nothing
@@ -141,19 +141,19 @@ mkSignatureInformation docMap argDocMap argumentNumber functionName functionType
141
141
in SignatureInformation
142
142
(functionNameLabelPrefix <> printOutputableOneLine functionType)
143
143
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 )
146
146
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
152
152
Nothing -> Nothing
153
153
Just spanDoc -> Just $ InR $ mkMarkdownDoc $ removeUris spanDoc
154
154
]
155
155
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
157
157
removeUris (SpanDocString docs _uris) = SpanDocString docs emptyUris
158
158
removeUris (SpanDocText docs _uris) = SpanDocText docs emptyUris
159
159
@@ -162,16 +162,16 @@ mkArguments thisArgDocMap offset functionType =
162
162
mkMarkdownDoc :: SpanDoc -> MarkupContent
163
163
mkMarkdownDoc = spanDocToMarkdown >>> T. unlines >>> MarkupContent MarkupKind_Markdown
164
164
165
- findArgumentRanges :: Type -> [(UInt , UInt )]
166
- findArgumentRanges functionType =
165
+ findParameterRanges :: Type -> [(UInt , UInt )]
166
+ findParameterRanges functionType =
167
167
let functionTypeString = printOutputableOneLine functionType
168
168
functionTypeStringLength = fromIntegral $ T. length functionTypeString
169
169
splitFunctionTypes = filter notTypeConstraint $ splitFunTysIgnoringForAll functionType
170
170
splitFunctionTypeStrings = printOutputableOneLine . fst <$> splitFunctionTypes
171
171
-- reverse to avoid matching "a" of "forall a" in "forall a. a -> a"
172
172
reversedRanges =
173
173
drop 1 $ -- do not need the range of the result (last) type
174
- findArgumentStringRanges
174
+ findParameterStringRanges
175
175
0
176
176
(T. reverse functionTypeString)
177
177
(T. reverse <$> reverse splitFunctionTypeStrings)
@@ -193,34 +193,34 @@ Some tricky cases are as follows:
193
193
f :: forall a. Maybe a -> forall b. (a, b) -> b
194
194
- '=>' can appear anywhere in a type
195
195
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)
197
197
- 'forall' is not always shown
198
198
199
199
Alternative method 2: use only unstructured type string
200
200
This method is hard to implement because we need to parse the type string.
201
201
Some tricky cases are as follows:
202
202
- h :: forall a (m :: Type -> Type). Monad m => a -> m a
203
203
-}
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
208
208
prefixLength = fromIntegral $ T. length prefix
209
- argumentTypeStringLength = fromIntegral $ T. length argumentTypeString
209
+ parameterTypeStringLength = fromIntegral $ T. length parameterTypeString
210
210
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
216
216
217
217
-- similar to 'splitFunTys' but
218
218
-- 1) the result (last) type is included and
219
219
-- 2) toplevel foralls are ignored
220
220
splitFunTysIgnoringForAll :: Type -> [(Type , Maybe FunTyFlag )]
221
221
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
224
224
Nothing -> [(ty, Nothing )]
225
225
226
226
notTypeConstraint :: (Type , Maybe FunTyFlag ) -> Bool
@@ -287,22 +287,22 @@ getNodeNameAndTypes hieKind hieAst =
287
287
isUse :: IdentifierDetails a -> Bool
288
288
isUse = identInfo >>> S. member Use
289
289
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
293
293
| nodeHasAnnotation (" HsApp" , " HsExpr" ) hieAst =
294
294
case nodeChildren hieAst of
295
295
[leftChild, _] ->
296
296
if span `isRealSubspanOf` nodeSpan leftChild
297
297
then Nothing
298
- else getArgumentNumber span leftChild >>= \ argumentNumber -> Just (argumentNumber + 1 )
298
+ else getParameterIndex span leftChild >>= \ parameterIndex -> Just (parameterIndex + 1 )
299
299
_ -> Nothing -- impossible
300
300
| nodeHasAnnotation (" HsAppType" , " HsExpr" ) hieAst =
301
301
case nodeChildren hieAst of
302
- [leftChild, _] -> getArgumentNumber span leftChild
302
+ [leftChild, _] -> getParameterIndex span leftChild
303
303
_ -> Nothing -- impossible
304
304
| otherwise =
305
305
case nodeChildren hieAst of
306
306
[] -> Just 0 -- the function is found
307
- [child] -> getArgumentNumber span child -- ignore irrelevant nodes
307
+ [child] -> getParameterIndex span child -- ignore irrelevant nodes
308
308
_ -> Nothing
0 commit comments