@@ -7,7 +7,7 @@ module Development.IDE.Core.Completions (
7
7
) where
8
8
9
9
import Control.Applicative
10
- import Data.Char (isSpace )
10
+ import Data.Char (isSpace , isUpper )
11
11
import Data.Generics
12
12
import Data.List as List hiding (stripPrefix )
13
13
import qualified Data.Map as Map
@@ -33,6 +33,9 @@ import Language.Haskell.LSP.Types.Capabilities
33
33
import qualified Language.Haskell.LSP.VFS as VFS
34
34
import Development.IDE.Core.CompletionsTypes
35
35
import Development.IDE.Spans.Documentation
36
+ import Development.IDE.GHC.Util
37
+ import Development.IDE.GHC.Error
38
+ import Development.IDE.Types.Options
36
39
37
40
-- From haskell-ide-engine/src/Haskell/Ide/Engine/Support/HieExtras.hs
38
41
@@ -41,6 +44,12 @@ safeTyThingId (AnId i) = Just i
41
44
safeTyThingId (AConLike (RealDataCon dc)) = Just $ dataConWrapId dc
42
45
safeTyThingId _ = Nothing
43
46
47
+ safeTyThingType :: TyThing -> Maybe Type
48
+ safeTyThingType thing
49
+ | Just i <- safeTyThingId thing = Just (varType i)
50
+ safeTyThingType (ATyCon tycon) = Just (tyConKind tycon)
51
+ safeTyThingType _ = Nothing
52
+
44
53
-- From haskell-ide-engine/hie-plugin-api/Haskell/Ide/Engine/Context.hs
45
54
46
55
-- | A context of a declaration in the program
@@ -135,20 +144,26 @@ getCContext pos pm
135
144
| otherwise = Nothing
136
145
importInline _ _ = Nothing
137
146
138
- occNameToComKind :: OccName -> CompletionItemKind
139
- occNameToComKind oc
140
- | isVarOcc oc = CiFunction
141
- | isTcOcc oc = CiClass
147
+ occNameToComKind :: Maybe T. Text -> OccName -> CompletionItemKind
148
+ occNameToComKind ty oc
149
+ | isVarOcc oc = case occNameString oc of
150
+ i: _ | isUpper i -> CiConstructor
151
+ _ -> CiFunction
152
+ | isTcOcc oc = case ty of
153
+ Just t
154
+ | " Constraint" `T.isSuffixOf` t
155
+ -> CiClass
156
+ _ -> CiStruct
142
157
| isDataOcc oc = CiConstructor
143
158
| otherwise = CiVariable
144
159
145
- mkCompl :: CompItem -> CompletionItem
146
- mkCompl CI {origName,importedFrom,thingType,label,isInfix,docs} =
147
- CompletionItem label kind (Just $ maybe " " ( <> " \n " ) typeText <> importedFrom )
148
- (Just $ CompletionDocMarkup $ MarkupContent MkMarkdown $ T. intercalate sectionSeparator docs)
160
+ mkCompl :: IdeOptions -> CompItem -> CompletionItem
161
+ mkCompl IdeOptions { .. } CI {origName,importedFrom,thingType,label,isInfix,docs} =
162
+ CompletionItem label kind ((colon <> ) <$> typeText )
163
+ (Just $ CompletionDocMarkup $ MarkupContent MkMarkdown $ T. intercalate sectionSeparator docs' )
149
164
Nothing Nothing Nothing Nothing (Just insertText) (Just Snippet )
150
165
Nothing Nothing Nothing Nothing Nothing
151
- where kind = Just $ occNameToComKind $ occName origName
166
+ where kind = Just $ occNameToComKind typeText $ occName origName
152
167
insertText = case isInfix of
153
168
Nothing -> case getArgText <$> thingType of
154
169
Nothing -> label
@@ -159,6 +174,8 @@ mkCompl CI{origName,importedFrom,thingType,label,isInfix,docs} =
159
174
typeText
160
175
| Just t <- thingType = Just . stripForall $ T. pack (showGhc t)
161
176
| otherwise = Nothing
177
+ docs' = (" *Defined in '" <> importedFrom <> " '*\n " ) : docs
178
+ colon = if optNewColonConvention then " : " else " :: "
162
179
163
180
stripForall :: T. Text -> T. Text
164
181
stripForall t
@@ -215,8 +232,8 @@ mkPragmaCompl label insertText =
215
232
Nothing Nothing Nothing Nothing Nothing (Just insertText) (Just Snippet )
216
233
Nothing Nothing Nothing Nothing Nothing
217
234
218
- cacheDataProducer :: DynFlags -> TypecheckedModule -> [TypecheckedModule ] -> IO CachedCompletions
219
- cacheDataProducer dflags tm tcs = do
235
+ cacheDataProducer :: HscEnv -> DynFlags -> TypecheckedModule -> [TypecheckedModule ] -> IO CachedCompletions
236
+ cacheDataProducer packageState dflags tm tcs = do
220
237
let parsedMod = tm_parsed_module tm
221
238
curMod = moduleName $ ms_mod $ pm_mod_summary parsedMod
222
239
Just (_,limports,_,_) = tm_renamed_source tm
@@ -242,42 +259,50 @@ cacheDataProducer dflags tm tcs = do
242
259
rdrEnv = tcg_rdr_env $ fst $ tm_internals_ tm
243
260
rdrElts = globalRdrEnvElts rdrEnv
244
261
245
- getCompls :: [GlobalRdrElt ] -> ([CompItem ],QualCompls )
246
- getCompls = foldMap getComplsForOne
262
+ foldMapM :: (Foldable f , Monad m , Monoid b ) => (a -> m b ) -> f a -> m b
263
+ foldMapM f xs = foldr step return xs mempty where
264
+ step x r z = f x >>= \ y -> r $! z `mappend` y
265
+
266
+ getCompls :: [GlobalRdrElt ] -> IO ([CompItem ],QualCompls )
267
+ getCompls = foldMapM getComplsForOne
247
268
248
- getComplsForOne :: GlobalRdrElt -> ([CompItem ],QualCompls )
269
+ getComplsForOne :: GlobalRdrElt -> IO ([CompItem ],QualCompls )
249
270
getComplsForOne (GRE n _ True _) =
250
271
case lookupTypeEnv typeEnv n of
251
272
Just tt -> case safeTyThingId tt of
252
- Just var -> ([varToCompl var ],mempty )
253
- Nothing -> ([toCompItem curMod n ],mempty )
254
- Nothing -> ([toCompItem curMod n ],mempty )
273
+ Just var -> (\ x -> ([x ],mempty )) <$> varToCompl var
274
+ Nothing -> (\ x -> ([x ],mempty )) <$> toCompItem curMod n
275
+ Nothing -> (\ x -> ([x ],mempty )) <$> toCompItem curMod n
255
276
getComplsForOne (GRE n _ False prov) =
256
- flip foldMap (map is_decl prov) $ \ spec ->
277
+ flip foldMapM (map is_decl prov) $ \ spec -> do
278
+ compItem <- toCompItem (is_mod spec) n
257
279
let unqual
258
280
| is_qual spec = []
259
- | otherwise = compItem
281
+ | otherwise = [ compItem]
260
282
qual
261
- | is_qual spec = Map. singleton asMod compItem
262
- | otherwise = Map. fromList [(asMod,compItem),(origMod,compItem)]
263
- compItem = [toCompItem (is_mod spec) n]
283
+ | is_qual spec = Map. singleton asMod [compItem]
284
+ | otherwise = Map. fromList [(asMod,[compItem]),(origMod,[compItem])]
264
285
asMod = showModName (is_as spec)
265
286
origMod = showModName (is_mod spec)
266
- in (unqual,QualCompls qual)
267
-
268
- varToCompl :: Var -> CompItem
269
- varToCompl var = CI name (showModName curMod) typ label Nothing docs
270
- where
271
- typ = Just $ varType var
272
- name = Var. varName var
273
- label = T. pack $ showGhc name
274
- docs = getDocumentation tcs name
275
-
276
- toCompItem :: ModuleName -> Name -> CompItem
277
- toCompItem mn n =
278
- CI n (showModName mn) Nothing (T. pack $ showGhc n) Nothing (getDocumentation tcs n)
279
-
280
- (unquals,quals) = getCompls rdrElts
287
+ return (unqual,QualCompls qual)
288
+
289
+ varToCompl :: Var -> IO CompItem
290
+ varToCompl var = do
291
+ let typ = Just $ varType var
292
+ name = Var. varName var
293
+ label = T. pack $ showGhc name
294
+ docs <- getDocumentationTryGhc packageState (tm: tcs) name
295
+ return $ CI name (showModName curMod) typ label Nothing docs
296
+
297
+ toCompItem :: ModuleName -> Name -> IO CompItem
298
+ toCompItem mn n = do
299
+ docs <- getDocumentationTryGhc packageState (tm: tcs) n
300
+ ty <- runGhcEnv packageState $ catchSrcErrors " completion" $ do
301
+ name' <- lookupName n
302
+ return $ name' >>= safeTyThingType
303
+ return $ CI n (showModName mn) (either (const Nothing ) id ty) (T. pack $ showGhc n) Nothing docs
304
+
305
+ (unquals,quals) <- getCompls rdrElts
281
306
282
307
return $ CC
283
308
{ allModNamesAsNS = allModNamesAsNS
@@ -297,8 +322,8 @@ toggleSnippets ClientCapabilities { _textDocument } (WithSnippets with) x
297
322
where supported = fromMaybe False (_textDocument >>= _completion >>= _completionItem >>= _snippetSupport)
298
323
299
324
-- | Returns the cached completions for the given module and position.
300
- getCompletions :: CachedCompletions -> TypecheckedModule -> VFS. PosPrefixInfo -> ClientCapabilities -> WithSnippets -> IO [CompletionItem ]
301
- getCompletions CC { allModNamesAsNS, unqualCompls, qualCompls, importableModules }
325
+ getCompletions :: IdeOptions -> CachedCompletions -> TypecheckedModule -> VFS. PosPrefixInfo -> ClientCapabilities -> WithSnippets -> IO [CompletionItem ]
326
+ getCompletions ideOpts CC { allModNamesAsNS, unqualCompls, qualCompls, importableModules }
302
327
tm prefixInfo caps withSnippets = do
303
328
let VFS. PosPrefixInfo { VFS. fullLine, VFS. prefixModule, VFS. prefixText } = prefixInfo
304
329
enteredQual = if T. null prefixModule then " " else prefixModule <> " ."
@@ -382,7 +407,7 @@ getCompletions CC { allModNamesAsNS, unqualCompls, qualCompls, importableModules
382
407
= filtPragmaCompls (pragmaSuffix fullLine)
383
408
| otherwise
384
409
= filtModNameCompls ++ map (toggleSnippets caps withSnippets
385
- . mkCompl . stripAutoGenerated) filtCompls
410
+ . mkCompl ideOpts . stripAutoGenerated) filtCompls
386
411
387
412
return result
388
413
0 commit comments