@@ -21,6 +21,7 @@ module Ide.Plugin
2121import Control.Lens ( (^.) )
2222import Control.Monad
2323import qualified Data.Aeson as J
24+ import qualified Data.Default
2425import Data.Either
2526import qualified Data.List as List
2627import qualified Data.Map as Map
@@ -44,6 +45,7 @@ import Language.Haskell.LSP.Types
4445import qualified Language.Haskell.LSP.Types as J
4546import qualified Language.Haskell.LSP.Types.Capabilities as C
4647import Language.Haskell.LSP.Types.Lens as L hiding (formatting , rangeFormatting )
48+ import qualified Language.Haskell.LSP.VFS as VFS
4749import Text.Regex.TDFA.Text ()
4850
4951-- ---------------------------------------------------------------------
@@ -59,10 +61,9 @@ asGhcIdePlugin mp =
5961 mkPlugin codeLensPlugins pluginCodeLensProvider <>
6062 -- Note: diagnostics are provided via Rules from pluginDiagnosticProvider
6163 mkPlugin hoverPlugins pluginHoverProvider <>
62- -- TODO: symbols via pluginSymbolProvider
63- mkPlugin symbolsPlugin pluginSymbolsProvider <>
64- mkPlugin formatterPlugins pluginFormattingProvider
65- -- TODO: completions
64+ mkPlugin symbolsPlugins pluginSymbolsProvider <>
65+ mkPlugin formatterPlugins pluginFormattingProvider <>
66+ mkPlugin completionsPlugins pluginCompletionProvider
6667 where
6768 justs (p, Just x) = [(p, x)]
6869 justs (_, Nothing ) = []
@@ -403,8 +404,8 @@ makeHover hps _lf ideState params
403404-- ---------------------------------------------------------------------
404405-- ---------------------------------------------------------------------
405406
406- symbolsPlugin :: [(PluginId , SymbolsProvider )] -> Plugin Config
407- symbolsPlugin hs = Plugin symbolsRules (symbolsHandlers hs)
407+ symbolsPlugins :: [(PluginId , SymbolsProvider )] -> Plugin Config
408+ symbolsPlugins hs = Plugin symbolsRules (symbolsHandlers hs)
408409
409410symbolsRules :: Rules ()
410411symbolsRules = mempty
@@ -463,3 +464,85 @@ formatterHandlers providers = PartialHandlers $ \WithMessage{..} x -> return x
463464 }
464465
465466-- ---------------------------------------------------------------------
467+ -- ---------------------------------------------------------------------
468+
469+ completionsPlugins :: [(PluginId , CompletionProvider )] -> Plugin Config
470+ completionsPlugins cs = Plugin completionsRules (completionsHandlers cs)
471+
472+ completionsRules :: Rules ()
473+ completionsRules = mempty
474+
475+ completionsHandlers :: [(PluginId , CompletionProvider )] -> PartialHandlers Config
476+ completionsHandlers cps = PartialHandlers $ \ WithMessage {.. } x ->
477+ return x {LSP. completionHandler = withResponse RspCompletion (makeCompletions cps)}
478+
479+ makeCompletions :: [(PluginId , CompletionProvider )]
480+ -> LSP. LspFuncs Config
481+ -> IdeState
482+ -> CompletionParams
483+ -> IO (Either ResponseError CompletionResponseResult )
484+ makeCompletions sps lf ideState params@ (CompletionParams (TextDocumentIdentifier doc) pos _context _mt)
485+ = do
486+ mprefix <- getPrefixAtPos lf doc pos
487+ _snippets <- WithSnippets <$> completionSnippetsOn <$> (getClientConfig lf)
488+
489+ let
490+ combine :: [CompletionResponseResult ] -> CompletionResponseResult
491+ combine cs = go (Completions $ List [] ) cs
492+ where
493+ go acc [] = acc
494+ go (Completions (List ls)) (Completions (List ls2): rest)
495+ = go (Completions (List (ls <> ls2))) rest
496+ go (Completions (List ls)) (CompletionList (CompletionListType complete (List ls2)): rest)
497+ = go (CompletionList $ CompletionListType complete (List (ls <> ls2))) rest
498+ go (CompletionList (CompletionListType complete (List ls))) (CompletionList (CompletionListType complete2 (List ls2)): rest)
499+ = go (CompletionList $ CompletionListType (complete || complete2) (List (ls <> ls2))) rest
500+ go (CompletionList (CompletionListType complete (List ls))) (Completions (List ls2): rest)
501+ = go (CompletionList $ CompletionListType complete (List (ls <> ls2))) rest
502+
503+ case mprefix of
504+ Nothing -> return $ Right $ Completions $ List []
505+ Just _prefix -> do
506+ mhs <- mapM (\ (_,p) -> p ideState params) sps
507+ case rights mhs of
508+ [] -> return $ Left $ responseError $ T. pack $ show $ lefts mhs
509+ hs -> return $ Right $ combine hs
510+
511+ {-
512+ ReqCompletion req -> do
513+ liftIO $ U.logs $ "reactor:got CompletionRequest:" ++ show req
514+ let (_, doc, pos) = reqParams req
515+
516+ mprefix <- getPrefixAtPos doc pos
517+
518+ let callback compls = do
519+ let rspMsg = Core.makeResponseMessage req
520+ $ J.Completions $ J.List compls
521+ reactorSend $ RspCompletion rspMsg
522+ case mprefix of
523+ Nothing -> callback []
524+ Just prefix -> do
525+ snippets <- Completions.WithSnippets <$> configVal completionSnippetsOn
526+ let hreq = IReq tn "completion" (req ^. J.id) callback
527+ $ lift $ Completions.getCompletions doc prefix snippets
528+ makeRequest hreq
529+ -}
530+
531+ getPrefixAtPos :: LSP. LspFuncs Config -> Uri -> Position -> IO (Maybe VFS. PosPrefixInfo )
532+ getPrefixAtPos lf uri pos = do
533+ mvf <- (LSP. getVirtualFileFunc lf) (J. toNormalizedUri uri)
534+ case mvf of
535+ Just vf -> VFS. getCompletionPrefix pos vf
536+ Nothing -> return Nothing
537+
538+ -- ---------------------------------------------------------------------
539+ -- | Returns the current client configuration. It is not wise to permanently
540+ -- cache the returned value of this function, as clients can at runitime change
541+ -- their configuration.
542+ --
543+ -- If no custom configuration has been set by the client, this function returns
544+ -- our own defaults.
545+ getClientConfig :: LSP. LspFuncs Config -> IO Config
546+ getClientConfig lf = fromMaybe Data.Default. def <$> LSP. config lf
547+
548+ -- ---------------------------------------------------------------------
0 commit comments