{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE UndecidableInstances #-}
module Ide.Types
    where
#ifdef mingw32_HOST_OS
import qualified System.Win32.Process                    as P (getCurrentProcessId)
#else
import           System.Posix.Signals
import qualified System.Posix.Process                    as P (getProcessID)
#endif
import           Data.Aeson                    hiding (defaultOptions)
import           GHC.Generics
import qualified Data.Map  as Map
import           Data.String
import qualified Data.Text                     as T
import           Development.Shake hiding (command)
import           Ide.Plugin.Config
import           Language.LSP.Types
import           Language.LSP.VFS
import           Language.LSP.Types.Lens as J hiding (id)
import           Language.LSP.Types.Capabilities
import           Language.LSP.Server (LspM, getVirtualFile)
import           Text.Regex.TDFA.Text()
import           Data.Dependent.Map (DMap)
import qualified Data.Dependent.Map as DMap
import Data.List.NonEmpty (NonEmpty(..), toList)
import Data.GADT.Compare
import Data.Maybe
import Data.Semigroup
import Control.Lens ((^.))
import qualified Data.DList as DList
import qualified Data.Default
import System.IO.Unsafe
import Control.Monad
import OpenTelemetry.Eventlog
import Data.Text.Encoding (encodeUtf8)
newtype IdePlugins ideState = IdePlugins
  { IdePlugins ideState -> Map PluginId (PluginDescriptor ideState)
ipMap :: Map.Map PluginId (PluginDescriptor ideState)}
data PluginDescriptor ideState =
  PluginDescriptor { PluginDescriptor ideState -> PluginId
pluginId          :: !PluginId
                   , PluginDescriptor ideState -> Rules ()
pluginRules       :: !(Rules ())
                   , PluginDescriptor ideState -> [PluginCommand ideState]
pluginCommands    :: ![PluginCommand ideState]
                   , PluginDescriptor ideState -> PluginHandlers ideState
pluginHandlers    :: PluginHandlers ideState
                   }
class HasTracing (MessageParams m) => PluginMethod m where
  
  pluginEnabled :: SMethod m -> PluginId -> Config -> Bool
  
  combineResponses
    :: SMethod m
    -> Config 
    -> ClientCapabilities
    -> MessageParams m
    -> NonEmpty (ResponseResult m) -> ResponseResult m
  default combineResponses :: Semigroup (ResponseResult m)
    => SMethod m -> Config -> ClientCapabilities -> MessageParams m -> NonEmpty (ResponseResult m) -> ResponseResult m
  combineResponses SMethod m
_method Config
_config ClientCapabilities
_caps MessageParams m
_params = NonEmpty (ResponseResult m) -> ResponseResult m
forall a. Semigroup a => NonEmpty a -> a
sconcat
instance PluginMethod TextDocumentCodeAction where
  pluginEnabled :: SMethod 'TextDocumentCodeAction -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentCodeAction
_ = (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
plcCodeActionsOn
  combineResponses :: SMethod 'TextDocumentCodeAction
-> Config
-> ClientCapabilities
-> MessageParams 'TextDocumentCodeAction
-> NonEmpty (ResponseResult 'TextDocumentCodeAction)
-> ResponseResult 'TextDocumentCodeAction
combineResponses SMethod 'TextDocumentCodeAction
_method Config
_config (ClientCapabilities Maybe WorkspaceClientCapabilities
_ Maybe TextDocumentClientCapabilities
textDocCaps Maybe WindowClientCapabilities
_ Maybe Object
_) (CodeActionParams _ _ _ _ context) NonEmpty (ResponseResult 'TextDocumentCodeAction)
resps =
      ((Command |? CodeAction) -> Command |? CodeAction)
-> List (Command |? CodeAction) -> List (Command |? CodeAction)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Command |? CodeAction) -> Command |? CodeAction
compat (List (Command |? CodeAction) -> List (Command |? CodeAction))
-> List (Command |? CodeAction) -> List (Command |? CodeAction)
forall a b. (a -> b) -> a -> b
$ [Command |? CodeAction] -> List (Command |? CodeAction)
forall a. [a] -> List a
List ([Command |? CodeAction] -> List (Command |? CodeAction))
-> [Command |? CodeAction] -> List (Command |? CodeAction)
forall a b. (a -> b) -> a -> b
$ ((Command |? CodeAction) -> Bool)
-> [Command |? CodeAction] -> [Command |? CodeAction]
forall a. (a -> Bool) -> [a] -> [a]
filter (Command |? CodeAction) -> Bool
wasRequested ([Command |? CodeAction] -> [Command |? CodeAction])
-> [Command |? CodeAction] -> [Command |? CodeAction]
forall a b. (a -> b) -> a -> b
$ (\(List [Command |? CodeAction]
x) -> [Command |? CodeAction]
x) (List (Command |? CodeAction) -> [Command |? CodeAction])
-> List (Command |? CodeAction) -> [Command |? CodeAction]
forall a b. (a -> b) -> a -> b
$ NonEmpty (List (Command |? CodeAction))
-> List (Command |? CodeAction)
forall a. Semigroup a => NonEmpty a -> a
sconcat NonEmpty (ResponseResult 'TextDocumentCodeAction)
NonEmpty (List (Command |? CodeAction))
resps
    where
      compat :: (Command |? CodeAction) -> (Command |? CodeAction)
      compat :: (Command |? CodeAction) -> Command |? CodeAction
compat x :: Command |? CodeAction
x@(InL Command
_) = Command |? CodeAction
x
      compat x :: Command |? CodeAction
x@(InR CodeAction
action)
        | Just CodeActionLiteralSupport
_ <- Maybe TextDocumentClientCapabilities
textDocCaps Maybe TextDocumentClientCapabilities
-> (TextDocumentClientCapabilities
    -> Maybe CodeActionClientCapabilities)
-> Maybe CodeActionClientCapabilities
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TextDocumentClientCapabilities
-> Maybe CodeActionClientCapabilities
_codeAction Maybe CodeActionClientCapabilities
-> (CodeActionClientCapabilities -> Maybe CodeActionLiteralSupport)
-> Maybe CodeActionLiteralSupport
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CodeActionClientCapabilities -> Maybe CodeActionLiteralSupport
_codeActionLiteralSupport
        = Command |? CodeAction
x
        | Bool
otherwise = Command -> Command |? CodeAction
forall a b. a -> a |? b
InL Command
cmd
        where
          cmd :: Command
cmd = PluginId -> CommandId -> Text -> Maybe [Value] -> Command
mkLspCommand PluginId
"hls" CommandId
"fallbackCodeAction" (CodeAction
action CodeAction -> Getting Text CodeAction Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text CodeAction Text
forall s a. HasTitle s a => Lens' s a
title) ([Value] -> Maybe [Value]
forall a. a -> Maybe a
Just [Value]
cmdParams)
          cmdParams :: [Value]
cmdParams = [FallbackCodeActionParams -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe WorkspaceEdit -> Maybe Command -> FallbackCodeActionParams
FallbackCodeActionParams (CodeAction
action CodeAction
-> Getting (Maybe WorkspaceEdit) CodeAction (Maybe WorkspaceEdit)
-> Maybe WorkspaceEdit
forall s a. s -> Getting a s a -> a
^. Getting (Maybe WorkspaceEdit) CodeAction (Maybe WorkspaceEdit)
forall s a. HasEdit s a => Lens' s a
edit) (CodeAction
action CodeAction
-> Getting (Maybe Command) CodeAction (Maybe Command)
-> Maybe Command
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Command) CodeAction (Maybe Command)
forall s a. HasCommand s a => Lens' s a
command))]
      wasRequested :: (Command |? CodeAction) -> Bool
      wasRequested :: (Command |? CodeAction) -> Bool
wasRequested (InL Command
_) = Bool
True
      wasRequested (InR CodeAction
ca)
        | Maybe (List CodeActionKind)
Nothing <- CodeActionContext -> Maybe (List CodeActionKind)
_only CodeActionContext
context = Bool
True
        | Just (List [CodeActionKind]
allowed) <- CodeActionContext -> Maybe (List CodeActionKind)
_only CodeActionContext
context
        , Just CodeActionKind
caKind <- CodeAction
ca CodeAction
-> Getting (Maybe CodeActionKind) CodeAction (Maybe CodeActionKind)
-> Maybe CodeActionKind
forall s a. s -> Getting a s a -> a
^. Getting (Maybe CodeActionKind) CodeAction (Maybe CodeActionKind)
forall s a. HasKind s a => Lens' s a
kind = CodeActionKind
caKind CodeActionKind -> [CodeActionKind] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [CodeActionKind]
allowed
        | Bool
otherwise = Bool
False
instance PluginMethod TextDocumentCodeLens where
  pluginEnabled :: SMethod 'TextDocumentCodeLens -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentCodeLens
_ = (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
plcCodeLensOn
instance PluginMethod TextDocumentRename where
  pluginEnabled :: SMethod 'TextDocumentRename -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentRename
_ = (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
plcRenameOn
instance PluginMethod TextDocumentHover where
  pluginEnabled :: SMethod 'TextDocumentHover -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentHover
_ = (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
plcHoverOn
  combineResponses :: SMethod 'TextDocumentHover
-> Config
-> ClientCapabilities
-> MessageParams 'TextDocumentHover
-> NonEmpty (ResponseResult 'TextDocumentHover)
-> ResponseResult 'TextDocumentHover
combineResponses SMethod 'TextDocumentHover
_ Config
_ ClientCapabilities
_ MessageParams 'TextDocumentHover
_ ([Maybe Hover] -> [Hover]
forall a. [Maybe a] -> [a]
catMaybes ([Maybe Hover] -> [Hover])
-> (NonEmpty (Maybe Hover) -> [Maybe Hover])
-> NonEmpty (Maybe Hover)
-> [Hover]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (Maybe Hover) -> [Maybe Hover]
forall a. NonEmpty a -> [a]
toList -> [Hover]
hs) = Maybe Hover
ResponseResult 'TextDocumentHover
h
    where
      r :: Maybe Range
r = [Range] -> Maybe Range
forall a. [a] -> Maybe a
listToMaybe ([Range] -> Maybe Range) -> [Range] -> Maybe Range
forall a b. (a -> b) -> a -> b
$ (Hover -> Maybe Range) -> [Hover] -> [Range]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Hover -> Getting (Maybe Range) Hover (Maybe Range) -> Maybe Range
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Range) Hover (Maybe Range)
forall s a. HasRange s a => Lens' s a
range) [Hover]
hs
      h :: Maybe Hover
h = case (Hover -> HoverContents) -> [Hover] -> HoverContents
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (Hover -> Getting HoverContents Hover HoverContents -> HoverContents
forall s a. s -> Getting a s a -> a
^. Getting HoverContents Hover HoverContents
forall s a. HasContents s a => Lens' s a
contents) [Hover]
hs of
            HoverContentsMS (List []) -> Maybe Hover
forall a. Maybe a
Nothing
            HoverContents
hh                        -> Hover -> Maybe Hover
forall a. a -> Maybe a
Just (Hover -> Maybe Hover) -> Hover -> Maybe Hover
forall a b. (a -> b) -> a -> b
$ HoverContents -> Maybe Range -> Hover
Hover HoverContents
hh Maybe Range
r
instance PluginMethod TextDocumentDocumentSymbol where
  pluginEnabled :: SMethod 'TextDocumentDocumentSymbol -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentDocumentSymbol
_ = (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
plcSymbolsOn
  combineResponses :: SMethod 'TextDocumentDocumentSymbol
-> Config
-> ClientCapabilities
-> MessageParams 'TextDocumentDocumentSymbol
-> NonEmpty (ResponseResult 'TextDocumentDocumentSymbol)
-> ResponseResult 'TextDocumentDocumentSymbol
combineResponses SMethod 'TextDocumentDocumentSymbol
_ Config
_ (ClientCapabilities Maybe WorkspaceClientCapabilities
_ Maybe TextDocumentClientCapabilities
tdc Maybe WindowClientCapabilities
_ Maybe Object
_) MessageParams 'TextDocumentDocumentSymbol
params NonEmpty (ResponseResult 'TextDocumentDocumentSymbol)
xs = ResponseResult 'TextDocumentDocumentSymbol
List DocumentSymbol |? List SymbolInformation
res
    where
      uri' :: Uri
uri' = MessageParams 'TextDocumentDocumentSymbol
DocumentSymbolParams
params DocumentSymbolParams -> Getting Uri DocumentSymbolParams Uri -> Uri
forall s a. s -> Getting a s a -> a
^. (TextDocumentIdentifier -> Const Uri TextDocumentIdentifier)
-> DocumentSymbolParams -> Const Uri DocumentSymbolParams
forall s a. HasTextDocument s a => Lens' s a
textDocument ((TextDocumentIdentifier -> Const Uri TextDocumentIdentifier)
 -> DocumentSymbolParams -> Const Uri DocumentSymbolParams)
-> ((Uri -> Const Uri Uri)
    -> TextDocumentIdentifier -> Const Uri TextDocumentIdentifier)
-> Getting Uri DocumentSymbolParams Uri
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Uri -> Const Uri Uri)
-> TextDocumentIdentifier -> Const Uri TextDocumentIdentifier
forall s a. HasUri s a => Lens' s a
uri
      supportsHierarchy :: Bool
supportsHierarchy = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
True Maybe Bool -> Maybe Bool -> Bool
forall a. Eq a => a -> a -> Bool
== (Maybe TextDocumentClientCapabilities
tdc Maybe TextDocumentClientCapabilities
-> (TextDocumentClientCapabilities
    -> Maybe DocumentSymbolClientCapabilities)
-> Maybe DocumentSymbolClientCapabilities
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= TextDocumentClientCapabilities
-> Maybe DocumentSymbolClientCapabilities
_documentSymbol Maybe DocumentSymbolClientCapabilities
-> (DocumentSymbolClientCapabilities -> Maybe Bool) -> Maybe Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= DocumentSymbolClientCapabilities -> Maybe Bool
_hierarchicalDocumentSymbolSupport)
      dsOrSi :: NonEmpty (Either (List DocumentSymbol) (List SymbolInformation))
dsOrSi = ((List DocumentSymbol |? List SymbolInformation)
 -> Either (List DocumentSymbol) (List SymbolInformation))
-> NonEmpty (List DocumentSymbol |? List SymbolInformation)
-> NonEmpty (Either (List DocumentSymbol) (List SymbolInformation))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (List DocumentSymbol |? List SymbolInformation)
-> Either (List DocumentSymbol) (List SymbolInformation)
forall a b. (a |? b) -> Either a b
toEither NonEmpty (ResponseResult 'TextDocumentDocumentSymbol)
NonEmpty (List DocumentSymbol |? List SymbolInformation)
xs
      res :: List DocumentSymbol |? List SymbolInformation
res
        | Bool
supportsHierarchy = List DocumentSymbol
-> List DocumentSymbol |? List SymbolInformation
forall a b. a -> a |? b
InL (List DocumentSymbol
 -> List DocumentSymbol |? List SymbolInformation)
-> List DocumentSymbol
-> List DocumentSymbol |? List SymbolInformation
forall a b. (a -> b) -> a -> b
$ NonEmpty (List DocumentSymbol) -> List DocumentSymbol
forall a. Semigroup a => NonEmpty a -> a
sconcat (NonEmpty (List DocumentSymbol) -> List DocumentSymbol)
-> NonEmpty (List DocumentSymbol) -> List DocumentSymbol
forall a b. (a -> b) -> a -> b
$ (Either (List DocumentSymbol) (List SymbolInformation)
 -> List DocumentSymbol)
-> NonEmpty (Either (List DocumentSymbol) (List SymbolInformation))
-> NonEmpty (List DocumentSymbol)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((List DocumentSymbol -> List DocumentSymbol)
-> (List SymbolInformation -> List DocumentSymbol)
-> Either (List DocumentSymbol) (List SymbolInformation)
-> List DocumentSymbol
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either List DocumentSymbol -> List DocumentSymbol
forall a. a -> a
id ((SymbolInformation -> DocumentSymbol)
-> List SymbolInformation -> List DocumentSymbol
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SymbolInformation -> DocumentSymbol
siToDs)) NonEmpty (Either (List DocumentSymbol) (List SymbolInformation))
dsOrSi
        | Bool
otherwise = List SymbolInformation
-> List DocumentSymbol |? List SymbolInformation
forall a b. b -> a |? b
InR (List SymbolInformation
 -> List DocumentSymbol |? List SymbolInformation)
-> List SymbolInformation
-> List DocumentSymbol |? List SymbolInformation
forall a b. (a -> b) -> a -> b
$ NonEmpty (List SymbolInformation) -> List SymbolInformation
forall a. Semigroup a => NonEmpty a -> a
sconcat (NonEmpty (List SymbolInformation) -> List SymbolInformation)
-> NonEmpty (List SymbolInformation) -> List SymbolInformation
forall a b. (a -> b) -> a -> b
$ (Either (List DocumentSymbol) (List SymbolInformation)
 -> List SymbolInformation)
-> NonEmpty (Either (List DocumentSymbol) (List SymbolInformation))
-> NonEmpty (List SymbolInformation)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((List DocumentSymbol -> List SymbolInformation)
-> (List SymbolInformation -> List SymbolInformation)
-> Either (List DocumentSymbol) (List SymbolInformation)
-> List SymbolInformation
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either ([SymbolInformation] -> List SymbolInformation
forall a. [a] -> List a
List ([SymbolInformation] -> List SymbolInformation)
-> (List DocumentSymbol -> [SymbolInformation])
-> List DocumentSymbol
-> List SymbolInformation
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (DocumentSymbol -> [SymbolInformation])
-> List DocumentSymbol -> [SymbolInformation]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap DocumentSymbol -> [SymbolInformation]
dsToSi) List SymbolInformation -> List SymbolInformation
forall a. a -> a
id) NonEmpty (Either (List DocumentSymbol) (List SymbolInformation))
dsOrSi
      siToDs :: SymbolInformation -> DocumentSymbol
siToDs (SymbolInformation Text
name SymbolKind
kind Maybe Bool
dep (Location Uri
_uri Range
range) Maybe Text
cont)
        = Text
-> Maybe Text
-> SymbolKind
-> Maybe Bool
-> Range
-> Range
-> Maybe (List DocumentSymbol)
-> DocumentSymbol
DocumentSymbol Text
name Maybe Text
cont SymbolKind
kind Maybe Bool
dep Range
range Range
range Maybe (List DocumentSymbol)
forall a. Maybe a
Nothing
      dsToSi :: DocumentSymbol -> [SymbolInformation]
dsToSi = Maybe Text -> DocumentSymbol -> [SymbolInformation]
go Maybe Text
forall a. Maybe a
Nothing
      go :: Maybe T.Text -> DocumentSymbol -> [SymbolInformation]
      go :: Maybe Text -> DocumentSymbol -> [SymbolInformation]
go Maybe Text
parent DocumentSymbol
ds =
        let children' :: [SymbolInformation]
            children' :: [SymbolInformation]
children' = (DocumentSymbol -> [SymbolInformation])
-> List DocumentSymbol -> [SymbolInformation]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (Maybe Text -> DocumentSymbol -> [SymbolInformation]
go (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
name')) (List DocumentSymbol
-> Maybe (List DocumentSymbol) -> List DocumentSymbol
forall a. a -> Maybe a -> a
fromMaybe List DocumentSymbol
forall a. Monoid a => a
mempty (DocumentSymbol
ds DocumentSymbol
-> Getting
     (Maybe (List DocumentSymbol))
     DocumentSymbol
     (Maybe (List DocumentSymbol))
-> Maybe (List DocumentSymbol)
forall s a. s -> Getting a s a -> a
^. Getting
  (Maybe (List DocumentSymbol))
  DocumentSymbol
  (Maybe (List DocumentSymbol))
forall s a. HasChildren s a => Lens' s a
children))
            loc :: Location
loc = Uri -> Range -> Location
Location Uri
uri' (DocumentSymbol
ds DocumentSymbol -> Getting Range DocumentSymbol Range -> Range
forall s a. s -> Getting a s a -> a
^. Getting Range DocumentSymbol Range
forall s a. HasRange s a => Lens' s a
range)
            name' :: Text
name' = DocumentSymbol
ds DocumentSymbol -> Getting Text DocumentSymbol Text -> Text
forall s a. s -> Getting a s a -> a
^. Getting Text DocumentSymbol Text
forall s a. HasName s a => Lens' s a
name
            si :: SymbolInformation
si = Text
-> SymbolKind
-> Maybe Bool
-> Location
-> Maybe Text
-> SymbolInformation
SymbolInformation Text
name' (DocumentSymbol
ds DocumentSymbol
-> Getting SymbolKind DocumentSymbol SymbolKind -> SymbolKind
forall s a. s -> Getting a s a -> a
^. Getting SymbolKind DocumentSymbol SymbolKind
forall s a. HasKind s a => Lens' s a
kind) (DocumentSymbol
ds DocumentSymbol
-> Getting (Maybe Bool) DocumentSymbol (Maybe Bool) -> Maybe Bool
forall s a. s -> Getting a s a -> a
^. Getting (Maybe Bool) DocumentSymbol (Maybe Bool)
forall s a. HasDeprecated s a => Lens' s a
deprecated) Location
loc Maybe Text
parent
        in [SymbolInformation
si] [SymbolInformation] -> [SymbolInformation] -> [SymbolInformation]
forall a. Semigroup a => a -> a -> a
<> [SymbolInformation]
children'
instance PluginMethod TextDocumentCompletion where
  pluginEnabled :: SMethod 'TextDocumentCompletion -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentCompletion
_ = (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
plcCompletionOn
  combineResponses :: SMethod 'TextDocumentCompletion
-> Config
-> ClientCapabilities
-> MessageParams 'TextDocumentCompletion
-> NonEmpty (ResponseResult 'TextDocumentCompletion)
-> ResponseResult 'TextDocumentCompletion
combineResponses SMethod 'TextDocumentCompletion
_ Config
conf ClientCapabilities
_ MessageParams 'TextDocumentCompletion
_ (NonEmpty (ResponseResult 'TextDocumentCompletion)
-> [List CompletionItem |? CompletionList]
forall a. NonEmpty a -> [a]
toList -> [List CompletionItem |? CompletionList]
xs) = (Int, List CompletionItem |? CompletionList)
-> List CompletionItem |? CompletionList
forall a b. (a, b) -> b
snd ((Int, List CompletionItem |? CompletionList)
 -> List CompletionItem |? CompletionList)
-> (Int, List CompletionItem |? CompletionList)
-> List CompletionItem |? CompletionList
forall a b. (a -> b) -> a -> b
$ Int
-> (List CompletionItem |? CompletionList)
-> (Int, List CompletionItem |? CompletionList)
consumeCompletionResponse Int
limit ((List CompletionItem |? CompletionList)
 -> (Int, List CompletionItem |? CompletionList))
-> (List CompletionItem |? CompletionList)
-> (Int, List CompletionItem |? CompletionList)
forall a b. (a -> b) -> a -> b
$ [List CompletionItem |? CompletionList]
-> List CompletionItem |? CompletionList
combine [List CompletionItem |? CompletionList]
xs
      where
        limit :: Int
limit = Config -> Int
maxCompletions Config
conf
        combine :: [List CompletionItem |? CompletionList] -> ((List CompletionItem) |? CompletionList)
        combine :: [List CompletionItem |? CompletionList]
-> List CompletionItem |? CompletionList
combine [List CompletionItem |? CompletionList]
cs = Bool
-> DList CompletionItem
-> [List CompletionItem |? CompletionList]
-> List CompletionItem |? CompletionList
forall a.
Bool
-> DList CompletionItem
-> [List CompletionItem |? CompletionList]
-> a |? CompletionList
go Bool
True DList CompletionItem
forall a. Monoid a => a
mempty [List CompletionItem |? CompletionList]
cs
        go :: Bool
-> DList CompletionItem
-> [List CompletionItem |? CompletionList]
-> a |? CompletionList
go !Bool
comp DList CompletionItem
acc [] =
          CompletionList -> a |? CompletionList
forall a b. b -> a |? b
InR (Bool -> List CompletionItem -> CompletionList
CompletionList Bool
comp ([CompletionItem] -> List CompletionItem
forall a. [a] -> List a
List ([CompletionItem] -> List CompletionItem)
-> [CompletionItem] -> List CompletionItem
forall a b. (a -> b) -> a -> b
$ DList CompletionItem -> [CompletionItem]
forall a. DList a -> [a]
DList.toList DList CompletionItem
acc))
        go Bool
comp DList CompletionItem
acc (InL (List [CompletionItem]
ls) : [List CompletionItem |? CompletionList]
rest) =
          Bool
-> DList CompletionItem
-> [List CompletionItem |? CompletionList]
-> a |? CompletionList
go Bool
comp (DList CompletionItem
acc DList CompletionItem
-> DList CompletionItem -> DList CompletionItem
forall a. Semigroup a => a -> a -> a
<> [CompletionItem] -> DList CompletionItem
forall a. [a] -> DList a
DList.fromList [CompletionItem]
ls) [List CompletionItem |? CompletionList]
rest
        go Bool
comp DList CompletionItem
acc (InR (CompletionList Bool
comp' (List [CompletionItem]
ls)) : [List CompletionItem |? CompletionList]
rest) =
          Bool
-> DList CompletionItem
-> [List CompletionItem |? CompletionList]
-> a |? CompletionList
go (Bool
comp Bool -> Bool -> Bool
&& Bool
comp') (DList CompletionItem
acc DList CompletionItem
-> DList CompletionItem -> DList CompletionItem
forall a. Semigroup a => a -> a -> a
<> [CompletionItem] -> DList CompletionItem
forall a. [a] -> DList a
DList.fromList [CompletionItem]
ls) [List CompletionItem |? CompletionList]
rest
        
        isCompleteResponse, isIncompleteResponse :: Bool
        isIncompleteResponse :: Bool
isIncompleteResponse = Bool
True
        isCompleteResponse :: Bool
isCompleteResponse = Bool
False
        consumeCompletionResponse :: Int
-> (List CompletionItem |? CompletionList)
-> (Int, List CompletionItem |? CompletionList)
consumeCompletionResponse Int
limit it :: List CompletionItem |? CompletionList
it@(InR (CompletionList Bool
_ (List [CompletionItem]
xx))) =
          case Int -> [CompletionItem] -> ([CompletionItem], [CompletionItem])
forall a. Int -> [a] -> ([a], [a])
splitAt Int
limit [CompletionItem]
xx of
            
            ([CompletionItem]
_, []) -> (Int
limit Int -> Int -> Int
forall a. Num a => a -> a -> a
- [CompletionItem] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [CompletionItem]
xx, List CompletionItem |? CompletionList
it)
            
            ([CompletionItem]
xx', [CompletionItem]
_) -> (Int
0, CompletionList -> List CompletionItem |? CompletionList
forall a b. b -> a |? b
InR (Bool -> List CompletionItem -> CompletionList
CompletionList Bool
isIncompleteResponse ([CompletionItem] -> List CompletionItem
forall a. [a] -> List a
List [CompletionItem]
xx')))
        consumeCompletionResponse Int
n (InL (List [CompletionItem]
xx)) =
          Int
-> (List CompletionItem |? CompletionList)
-> (Int, List CompletionItem |? CompletionList)
consumeCompletionResponse Int
n (CompletionList -> List CompletionItem |? CompletionList
forall a b. b -> a |? b
InR (Bool -> List CompletionItem -> CompletionList
CompletionList Bool
isCompleteResponse ([CompletionItem] -> List CompletionItem
forall a. [a] -> List a
List [CompletionItem]
xx)))
instance PluginMethod TextDocumentFormatting where
  pluginEnabled :: SMethod 'TextDocumentFormatting -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentFormatting
_ PluginId
pid Config
conf = (Text -> PluginId
PluginId (Text -> PluginId) -> Text -> PluginId
forall a b. (a -> b) -> a -> b
$ Config -> Text
formattingProvider Config
conf) PluginId -> PluginId -> Bool
forall a. Eq a => a -> a -> Bool
== PluginId
pid
  combineResponses :: SMethod 'TextDocumentFormatting
-> Config
-> ClientCapabilities
-> MessageParams 'TextDocumentFormatting
-> NonEmpty (ResponseResult 'TextDocumentFormatting)
-> ResponseResult 'TextDocumentFormatting
combineResponses SMethod 'TextDocumentFormatting
_ Config
_ ClientCapabilities
_ MessageParams 'TextDocumentFormatting
_ (ResponseResult 'TextDocumentFormatting
x :| [ResponseResult 'TextDocumentFormatting]
_) = ResponseResult 'TextDocumentFormatting
x
instance PluginMethod TextDocumentRangeFormatting where
  pluginEnabled :: SMethod 'TextDocumentRangeFormatting -> PluginId -> Config -> Bool
pluginEnabled SMethod 'TextDocumentRangeFormatting
_ PluginId
pid Config
conf = (Text -> PluginId
PluginId (Text -> PluginId) -> Text -> PluginId
forall a b. (a -> b) -> a -> b
$ Config -> Text
formattingProvider Config
conf) PluginId -> PluginId -> Bool
forall a. Eq a => a -> a -> Bool
== PluginId
pid
  combineResponses :: SMethod 'TextDocumentRangeFormatting
-> Config
-> ClientCapabilities
-> MessageParams 'TextDocumentRangeFormatting
-> NonEmpty (ResponseResult 'TextDocumentRangeFormatting)
-> ResponseResult 'TextDocumentRangeFormatting
combineResponses SMethod 'TextDocumentRangeFormatting
_ Config
_ ClientCapabilities
_ MessageParams 'TextDocumentRangeFormatting
_ (ResponseResult 'TextDocumentRangeFormatting
x :| [ResponseResult 'TextDocumentRangeFormatting]
_) = ResponseResult 'TextDocumentRangeFormatting
x
data IdeMethod (m :: Method FromClient Request) = PluginMethod m => IdeMethod (SMethod m)
instance GEq IdeMethod where
  geq :: IdeMethod a -> IdeMethod b -> Maybe (a :~: b)
geq (IdeMethod SMethod a
a) (IdeMethod SMethod b
b) = SMethod a -> SMethod b -> Maybe (a :~: b)
forall k (f :: k -> *) (a :: k) (b :: k).
GEq f =>
f a -> f b -> Maybe (a :~: b)
geq SMethod a
a SMethod b
b
instance GCompare IdeMethod where
  gcompare :: IdeMethod a -> IdeMethod b -> GOrdering a b
gcompare (IdeMethod SMethod a
a) (IdeMethod SMethod b
b) = SMethod a -> SMethod b -> GOrdering a b
forall k (f :: k -> *) (a :: k) (b :: k).
GCompare f =>
f a -> f b -> GOrdering a b
gcompare SMethod a
a SMethod b
b
newtype PluginHandler a (m :: Method FromClient Request)
  = PluginHandler (PluginId -> a -> MessageParams m -> LspM Config (NonEmpty (Either ResponseError (ResponseResult m))))
newtype PluginHandlers a = PluginHandlers (DMap IdeMethod (PluginHandler a))
instance Semigroup (PluginHandlers a) where
  (PluginHandlers DMap IdeMethod (PluginHandler a)
a) <> :: PluginHandlers a -> PluginHandlers a -> PluginHandlers a
<> (PluginHandlers DMap IdeMethod (PluginHandler a)
b) = DMap IdeMethod (PluginHandler a) -> PluginHandlers a
forall a. DMap IdeMethod (PluginHandler a) -> PluginHandlers a
PluginHandlers (DMap IdeMethod (PluginHandler a) -> PluginHandlers a)
-> DMap IdeMethod (PluginHandler a) -> PluginHandlers a
forall a b. (a -> b) -> a -> b
$ (forall (v :: Method 'FromClient 'Request).
 IdeMethod v
 -> PluginHandler a v -> PluginHandler a v -> PluginHandler a v)
-> DMap IdeMethod (PluginHandler a)
-> DMap IdeMethod (PluginHandler a)
-> DMap IdeMethod (PluginHandler a)
forall k1 (k2 :: k1 -> *) (f :: k1 -> *).
GCompare k2 =>
(forall (v :: k1). k2 v -> f v -> f v -> f v)
-> DMap k2 f -> DMap k2 f -> DMap k2 f
DMap.unionWithKey forall (v :: Method 'FromClient 'Request).
IdeMethod v
-> PluginHandler a v -> PluginHandler a v -> PluginHandler a v
forall (m :: Method 'FromClient 'Request)
       (m :: Method 'FromClient 'Request)
       (m :: Method 'FromClient 'Request) p a.
(ResponseResult m ~ ResponseResult m,
 ResponseResult m ~ ResponseResult m,
 MessageParams m ~ MessageParams m,
 MessageParams m ~ MessageParams m) =>
p -> PluginHandler a m -> PluginHandler a m -> PluginHandler a m
go DMap IdeMethod (PluginHandler a)
a DMap IdeMethod (PluginHandler a)
b
    where
      go :: p -> PluginHandler a m -> PluginHandler a m -> PluginHandler a m
go p
_ (PluginHandler PluginId
-> a
-> MessageParams m
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
f) (PluginHandler PluginId
-> a
-> MessageParams m
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
g) = (PluginId
 -> a
 -> MessageParams m
 -> LspM
      Config (NonEmpty (Either ResponseError (ResponseResult m))))
-> PluginHandler a m
forall a (m :: Method 'FromClient 'Request).
(PluginId
 -> a
 -> MessageParams m
 -> LspM
      Config (NonEmpty (Either ResponseError (ResponseResult m))))
-> PluginHandler a m
PluginHandler ((PluginId
  -> a
  -> MessageParams m
  -> LspM
       Config (NonEmpty (Either ResponseError (ResponseResult m))))
 -> PluginHandler a m)
-> (PluginId
    -> a
    -> MessageParams m
    -> LspM
         Config (NonEmpty (Either ResponseError (ResponseResult m))))
-> PluginHandler a m
forall a b. (a -> b) -> a -> b
$ \PluginId
pid a
ide MessageParams m
params ->
        NonEmpty (Either ResponseError (ResponseResult m))
-> NonEmpty (Either ResponseError (ResponseResult m))
-> NonEmpty (Either ResponseError (ResponseResult m))
forall a. Semigroup a => a -> a -> a
(<>) (NonEmpty (Either ResponseError (ResponseResult m))
 -> NonEmpty (Either ResponseError (ResponseResult m))
 -> NonEmpty (Either ResponseError (ResponseResult m)))
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
-> LspT
     Config
     IO
     (NonEmpty (Either ResponseError (ResponseResult m))
      -> NonEmpty (Either ResponseError (ResponseResult m)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PluginId
-> a
-> MessageParams m
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
f PluginId
pid a
ide MessageParams m
MessageParams m
params LspT
  Config
  IO
  (NonEmpty (Either ResponseError (ResponseResult m))
   -> NonEmpty (Either ResponseError (ResponseResult m)))
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> PluginId
-> a
-> MessageParams m
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
g PluginId
pid a
ide MessageParams m
MessageParams m
params
instance Monoid (PluginHandlers a) where
  mempty :: PluginHandlers a
mempty = DMap IdeMethod (PluginHandler a) -> PluginHandlers a
forall a. DMap IdeMethod (PluginHandler a) -> PluginHandlers a
PluginHandlers DMap IdeMethod (PluginHandler a)
forall a. Monoid a => a
mempty
type PluginMethodHandler a m = a -> PluginId -> MessageParams m -> LspM Config (Either ResponseError (ResponseResult m))
mkPluginHandler
  :: PluginMethod m
  => SClientMethod m
  -> PluginMethodHandler ideState m
  -> PluginHandlers ideState
mkPluginHandler :: SClientMethod m
-> PluginMethodHandler ideState m -> PluginHandlers ideState
mkPluginHandler SClientMethod m
m PluginMethodHandler ideState m
f = DMap IdeMethod (PluginHandler ideState) -> PluginHandlers ideState
forall a. DMap IdeMethod (PluginHandler a) -> PluginHandlers a
PluginHandlers (DMap IdeMethod (PluginHandler ideState)
 -> PluginHandlers ideState)
-> DMap IdeMethod (PluginHandler ideState)
-> PluginHandlers ideState
forall a b. (a -> b) -> a -> b
$ IdeMethod m
-> PluginHandler ideState m
-> DMap IdeMethod (PluginHandler ideState)
forall k1 (k2 :: k1 -> *) (v :: k1) (f :: k1 -> *).
k2 v -> f v -> DMap k2 f
DMap.singleton (SClientMethod m -> IdeMethod m
forall (m :: Method 'FromClient 'Request).
PluginMethod m =>
SMethod m -> IdeMethod m
IdeMethod SClientMethod m
m) ((PluginId
 -> ideState
 -> MessageParams m
 -> LspM
      Config (NonEmpty (Either ResponseError (ResponseResult m))))
-> PluginHandler ideState m
forall a (m :: Method 'FromClient 'Request).
(PluginId
 -> a
 -> MessageParams m
 -> LspM
      Config (NonEmpty (Either ResponseError (ResponseResult m))))
-> PluginHandler a m
PluginHandler PluginId
-> ideState
-> MessageParams m
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
f')
  where
    f' :: PluginId
-> ideState
-> MessageParams m
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
f' PluginId
pid ideState
ide MessageParams m
params = Either ResponseError (ResponseResult m)
-> NonEmpty (Either ResponseError (ResponseResult m))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ResponseError (ResponseResult m)
 -> NonEmpty (Either ResponseError (ResponseResult m)))
-> LspT Config IO (Either ResponseError (ResponseResult m))
-> LspM Config (NonEmpty (Either ResponseError (ResponseResult m)))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PluginMethodHandler ideState m
f ideState
ide PluginId
pid MessageParams m
params
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
defaultPluginDescriptor :: PluginId -> PluginDescriptor ideState
defaultPluginDescriptor PluginId
plId =
  PluginId
-> Rules ()
-> [PluginCommand ideState]
-> PluginHandlers ideState
-> PluginDescriptor ideState
forall ideState.
PluginId
-> Rules ()
-> [PluginCommand ideState]
-> PluginHandlers ideState
-> PluginDescriptor ideState
PluginDescriptor
    PluginId
plId
    Rules ()
forall a. Monoid a => a
mempty
    [PluginCommand ideState]
forall a. Monoid a => a
mempty
    PluginHandlers ideState
forall a. Monoid a => a
mempty
newtype CommandId = CommandId T.Text
  deriving (Int -> CommandId -> ShowS
[CommandId] -> ShowS
CommandId -> String
(Int -> CommandId -> ShowS)
-> (CommandId -> String)
-> ([CommandId] -> ShowS)
-> Show CommandId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CommandId] -> ShowS
$cshowList :: [CommandId] -> ShowS
show :: CommandId -> String
$cshow :: CommandId -> String
showsPrec :: Int -> CommandId -> ShowS
$cshowsPrec :: Int -> CommandId -> ShowS
Show, ReadPrec [CommandId]
ReadPrec CommandId
Int -> ReadS CommandId
ReadS [CommandId]
(Int -> ReadS CommandId)
-> ReadS [CommandId]
-> ReadPrec CommandId
-> ReadPrec [CommandId]
-> Read CommandId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CommandId]
$creadListPrec :: ReadPrec [CommandId]
readPrec :: ReadPrec CommandId
$creadPrec :: ReadPrec CommandId
readList :: ReadS [CommandId]
$creadList :: ReadS [CommandId]
readsPrec :: Int -> ReadS CommandId
$creadsPrec :: Int -> ReadS CommandId
Read, CommandId -> CommandId -> Bool
(CommandId -> CommandId -> Bool)
-> (CommandId -> CommandId -> Bool) -> Eq CommandId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CommandId -> CommandId -> Bool
$c/= :: CommandId -> CommandId -> Bool
== :: CommandId -> CommandId -> Bool
$c== :: CommandId -> CommandId -> Bool
Eq, Eq CommandId
Eq CommandId
-> (CommandId -> CommandId -> Ordering)
-> (CommandId -> CommandId -> Bool)
-> (CommandId -> CommandId -> Bool)
-> (CommandId -> CommandId -> Bool)
-> (CommandId -> CommandId -> Bool)
-> (CommandId -> CommandId -> CommandId)
-> (CommandId -> CommandId -> CommandId)
-> Ord CommandId
CommandId -> CommandId -> Bool
CommandId -> CommandId -> Ordering
CommandId -> CommandId -> CommandId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: CommandId -> CommandId -> CommandId
$cmin :: CommandId -> CommandId -> CommandId
max :: CommandId -> CommandId -> CommandId
$cmax :: CommandId -> CommandId -> CommandId
>= :: CommandId -> CommandId -> Bool
$c>= :: CommandId -> CommandId -> Bool
> :: CommandId -> CommandId -> Bool
$c> :: CommandId -> CommandId -> Bool
<= :: CommandId -> CommandId -> Bool
$c<= :: CommandId -> CommandId -> Bool
< :: CommandId -> CommandId -> Bool
$c< :: CommandId -> CommandId -> Bool
compare :: CommandId -> CommandId -> Ordering
$ccompare :: CommandId -> CommandId -> Ordering
$cp1Ord :: Eq CommandId
Ord)
instance IsString CommandId where
  fromString :: String -> CommandId
fromString = Text -> CommandId
CommandId (Text -> CommandId) -> (String -> Text) -> String -> CommandId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
data PluginCommand ideState = forall a. (FromJSON a) =>
  PluginCommand { PluginCommand ideState -> CommandId
commandId   :: CommandId
                , PluginCommand ideState -> Text
commandDesc :: T.Text
                , ()
commandFunc :: CommandFunction ideState a
                }
type CommandFunction ideState a
  = ideState
  -> a
  -> LspM Config (Either ResponseError Value)
newtype WithSnippets = WithSnippets Bool
newtype PluginId = PluginId T.Text
  deriving (Int -> PluginId -> ShowS
[PluginId] -> ShowS
PluginId -> String
(Int -> PluginId -> ShowS)
-> (PluginId -> String) -> ([PluginId] -> ShowS) -> Show PluginId
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PluginId] -> ShowS
$cshowList :: [PluginId] -> ShowS
show :: PluginId -> String
$cshow :: PluginId -> String
showsPrec :: Int -> PluginId -> ShowS
$cshowsPrec :: Int -> PluginId -> ShowS
Show, ReadPrec [PluginId]
ReadPrec PluginId
Int -> ReadS PluginId
ReadS [PluginId]
(Int -> ReadS PluginId)
-> ReadS [PluginId]
-> ReadPrec PluginId
-> ReadPrec [PluginId]
-> Read PluginId
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PluginId]
$creadListPrec :: ReadPrec [PluginId]
readPrec :: ReadPrec PluginId
$creadPrec :: ReadPrec PluginId
readList :: ReadS [PluginId]
$creadList :: ReadS [PluginId]
readsPrec :: Int -> ReadS PluginId
$creadsPrec :: Int -> ReadS PluginId
Read, PluginId -> PluginId -> Bool
(PluginId -> PluginId -> Bool)
-> (PluginId -> PluginId -> Bool) -> Eq PluginId
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PluginId -> PluginId -> Bool
$c/= :: PluginId -> PluginId -> Bool
== :: PluginId -> PluginId -> Bool
$c== :: PluginId -> PluginId -> Bool
Eq, Eq PluginId
Eq PluginId
-> (PluginId -> PluginId -> Ordering)
-> (PluginId -> PluginId -> Bool)
-> (PluginId -> PluginId -> Bool)
-> (PluginId -> PluginId -> Bool)
-> (PluginId -> PluginId -> Bool)
-> (PluginId -> PluginId -> PluginId)
-> (PluginId -> PluginId -> PluginId)
-> Ord PluginId
PluginId -> PluginId -> Bool
PluginId -> PluginId -> Ordering
PluginId -> PluginId -> PluginId
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PluginId -> PluginId -> PluginId
$cmin :: PluginId -> PluginId -> PluginId
max :: PluginId -> PluginId -> PluginId
$cmax :: PluginId -> PluginId -> PluginId
>= :: PluginId -> PluginId -> Bool
$c>= :: PluginId -> PluginId -> Bool
> :: PluginId -> PluginId -> Bool
$c> :: PluginId -> PluginId -> Bool
<= :: PluginId -> PluginId -> Bool
$c<= :: PluginId -> PluginId -> Bool
< :: PluginId -> PluginId -> Bool
$c< :: PluginId -> PluginId -> Bool
compare :: PluginId -> PluginId -> Ordering
$ccompare :: PluginId -> PluginId -> Ordering
$cp1Ord :: Eq PluginId
Ord)
instance IsString PluginId where
  fromString :: String -> PluginId
fromString = Text -> PluginId
PluginId (Text -> PluginId) -> (String -> Text) -> String -> PluginId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
configForPlugin :: Config -> PluginId -> PluginConfig
configForPlugin :: Config -> PluginId -> PluginConfig
configForPlugin Config
config (PluginId Text
plugin)
    = PluginConfig -> Text -> Map Text PluginConfig -> PluginConfig
forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault PluginConfig
forall a. Default a => a
Data.Default.def Text
plugin (Config -> Map Text PluginConfig
plugins Config
config)
pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig :: (PluginConfig -> Bool) -> PluginId -> Config -> Bool
pluginEnabledConfig PluginConfig -> Bool
f PluginId
pid Config
config = PluginConfig -> Bool
plcGlobalOn PluginConfig
pluginConfig Bool -> Bool -> Bool
&& PluginConfig -> Bool
f PluginConfig
pluginConfig
  where
    pluginConfig :: PluginConfig
pluginConfig = Config -> PluginId -> PluginConfig
configForPlugin Config
config PluginId
pid
data FormattingType = FormatText
                    | FormatRange Range
type FormattingMethod m =
  ( J.HasOptions (MessageParams m) FormattingOptions
  , J.HasTextDocument (MessageParams m) TextDocumentIdentifier
  , ResponseResult m ~ List TextEdit
  )
type FormattingHandler a
  =  a
  -> FormattingType
  -> T.Text
  -> NormalizedFilePath
  -> FormattingOptions
  -> LspM Config (Either ResponseError (List TextEdit))
mkFormattingHandlers :: forall a. FormattingHandler a -> PluginHandlers a
mkFormattingHandlers :: FormattingHandler a -> PluginHandlers a
mkFormattingHandlers FormattingHandler a
f = SMethod 'TextDocumentFormatting
-> PluginMethodHandler a 'TextDocumentFormatting
-> PluginHandlers a
forall (m :: Method 'FromClient 'Request) ideState.
PluginMethod m =>
SClientMethod m
-> PluginMethodHandler ideState m -> PluginHandlers ideState
mkPluginHandler SMethod 'TextDocumentFormatting
STextDocumentFormatting (SMethod 'TextDocumentFormatting
-> PluginMethodHandler a 'TextDocumentFormatting
forall (f :: From) (m :: Method f 'Request).
FormattingMethod m =>
SMethod m -> PluginMethodHandler a m
provider SMethod 'TextDocumentFormatting
STextDocumentFormatting)
                      PluginHandlers a -> PluginHandlers a -> PluginHandlers a
forall a. Semigroup a => a -> a -> a
<> SMethod 'TextDocumentRangeFormatting
-> PluginMethodHandler a 'TextDocumentRangeFormatting
-> PluginHandlers a
forall (m :: Method 'FromClient 'Request) ideState.
PluginMethod m =>
SClientMethod m
-> PluginMethodHandler ideState m -> PluginHandlers ideState
mkPluginHandler SMethod 'TextDocumentRangeFormatting
STextDocumentRangeFormatting (SMethod 'TextDocumentRangeFormatting
-> PluginMethodHandler a 'TextDocumentRangeFormatting
forall (f :: From) (m :: Method f 'Request).
FormattingMethod m =>
SMethod m -> PluginMethodHandler a m
provider SMethod 'TextDocumentRangeFormatting
STextDocumentRangeFormatting)
  where
    provider :: forall m. FormattingMethod m => SMethod m -> PluginMethodHandler a m
    provider :: SMethod m -> PluginMethodHandler a m
provider SMethod m
m a
ide PluginId
_pid MessageParams m
params
      | Just NormalizedFilePath
nfp <- NormalizedUri -> Maybe NormalizedFilePath
uriToNormalizedFilePath (NormalizedUri -> Maybe NormalizedFilePath)
-> NormalizedUri -> Maybe NormalizedFilePath
forall a b. (a -> b) -> a -> b
$ Uri -> NormalizedUri
toNormalizedUri Uri
uri = do
        Maybe VirtualFile
mf <- NormalizedUri -> LspT Config IO (Maybe VirtualFile)
forall config (m :: * -> *).
MonadLsp config m =>
NormalizedUri -> m (Maybe VirtualFile)
getVirtualFile (NormalizedUri -> LspT Config IO (Maybe VirtualFile))
-> NormalizedUri -> LspT Config IO (Maybe VirtualFile)
forall a b. (a -> b) -> a -> b
$ Uri -> NormalizedUri
toNormalizedUri Uri
uri
        case Maybe VirtualFile
mf of
          Just VirtualFile
vf -> do
            let typ :: FormattingType
typ = case SMethod m
m of
                  SMethod m
STextDocumentFormatting -> FormattingType
FormatText
                  SMethod m
STextDocumentRangeFormatting -> Range -> FormattingType
FormatRange (MessageParams m
DocumentRangeFormattingParams
params DocumentRangeFormattingParams
-> Getting Range DocumentRangeFormattingParams Range -> Range
forall s a. s -> Getting a s a -> a
^. Getting Range DocumentRangeFormattingParams Range
forall s a. HasRange s a => Lens' s a
J.range)
                  SMethod m
_ -> String -> FormattingType
forall a. HasCallStack => String -> a
error String
"mkFormattingHandlers: impossible"
            FormattingHandler a
f a
ide FormattingType
typ (VirtualFile -> Text
virtualFileText VirtualFile
vf) NormalizedFilePath
nfp FormattingOptions
opts
          Maybe VirtualFile
Nothing -> Either ResponseError (List TextEdit)
-> LspT Config IO (Either ResponseError (List TextEdit))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ResponseError (List TextEdit)
 -> LspT Config IO (Either ResponseError (List TextEdit)))
-> Either ResponseError (List TextEdit)
-> LspT Config IO (Either ResponseError (List TextEdit))
forall a b. (a -> b) -> a -> b
$ ResponseError -> Either ResponseError (List TextEdit)
forall a b. a -> Either a b
Left (ResponseError -> Either ResponseError (List TextEdit))
-> ResponseError -> Either ResponseError (List TextEdit)
forall a b. (a -> b) -> a -> b
$ Text -> ResponseError
responseError (Text -> ResponseError) -> Text -> ResponseError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Formatter plugin: could not get file contents for " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Uri -> String
forall a. Show a => a -> String
show Uri
uri
      | Bool
otherwise = Either ResponseError (List TextEdit)
-> LspT Config IO (Either ResponseError (List TextEdit))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either ResponseError (List TextEdit)
 -> LspT Config IO (Either ResponseError (List TextEdit)))
-> Either ResponseError (List TextEdit)
-> LspT Config IO (Either ResponseError (List TextEdit))
forall a b. (a -> b) -> a -> b
$ ResponseError -> Either ResponseError (List TextEdit)
forall a b. a -> Either a b
Left (ResponseError -> Either ResponseError (List TextEdit))
-> ResponseError -> Either ResponseError (List TextEdit)
forall a b. (a -> b) -> a -> b
$ Text -> ResponseError
responseError (Text -> ResponseError) -> Text -> ResponseError
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ String
"Formatter plugin: uriToFilePath failed for: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Uri -> String
forall a. Show a => a -> String
show Uri
uri
      where
        uri :: Uri
uri = MessageParams m
params MessageParams m -> Getting Uri (MessageParams m) Uri -> Uri
forall s a. s -> Getting a s a -> a
^. (TextDocumentIdentifier -> Const Uri TextDocumentIdentifier)
-> MessageParams m -> Const Uri (MessageParams m)
forall s a. HasTextDocument s a => Lens' s a
J.textDocument ((TextDocumentIdentifier -> Const Uri TextDocumentIdentifier)
 -> MessageParams m -> Const Uri (MessageParams m))
-> ((Uri -> Const Uri Uri)
    -> TextDocumentIdentifier -> Const Uri TextDocumentIdentifier)
-> Getting Uri (MessageParams m) Uri
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Uri -> Const Uri Uri)
-> TextDocumentIdentifier -> Const Uri TextDocumentIdentifier
forall s a. HasUri s a => Lens' s a
J.uri
        opts :: FormattingOptions
opts = MessageParams m
params MessageParams m
-> Getting FormattingOptions (MessageParams m) FormattingOptions
-> FormattingOptions
forall s a. s -> Getting a s a -> a
^. Getting FormattingOptions (MessageParams m) FormattingOptions
forall s a. HasOptions s a => Lens' s a
J.options
responseError :: T.Text -> ResponseError
responseError :: Text -> ResponseError
responseError Text
txt = ErrorCode -> Text -> Maybe Value -> ResponseError
ResponseError ErrorCode
InvalidParams Text
txt Maybe Value
forall a. Maybe a
Nothing
data FallbackCodeActionParams =
  FallbackCodeActionParams
    { FallbackCodeActionParams -> Maybe WorkspaceEdit
fallbackWorkspaceEdit :: Maybe WorkspaceEdit
    , FallbackCodeActionParams -> Maybe Command
fallbackCommand       :: Maybe Command
    }
  deriving ((forall x.
 FallbackCodeActionParams -> Rep FallbackCodeActionParams x)
-> (forall x.
    Rep FallbackCodeActionParams x -> FallbackCodeActionParams)
-> Generic FallbackCodeActionParams
forall x.
Rep FallbackCodeActionParams x -> FallbackCodeActionParams
forall x.
FallbackCodeActionParams -> Rep FallbackCodeActionParams x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep FallbackCodeActionParams x -> FallbackCodeActionParams
$cfrom :: forall x.
FallbackCodeActionParams -> Rep FallbackCodeActionParams x
Generic, [FallbackCodeActionParams] -> Encoding
[FallbackCodeActionParams] -> Value
FallbackCodeActionParams -> Encoding
FallbackCodeActionParams -> Value
(FallbackCodeActionParams -> Value)
-> (FallbackCodeActionParams -> Encoding)
-> ([FallbackCodeActionParams] -> Value)
-> ([FallbackCodeActionParams] -> Encoding)
-> ToJSON FallbackCodeActionParams
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [FallbackCodeActionParams] -> Encoding
$ctoEncodingList :: [FallbackCodeActionParams] -> Encoding
toJSONList :: [FallbackCodeActionParams] -> Value
$ctoJSONList :: [FallbackCodeActionParams] -> Value
toEncoding :: FallbackCodeActionParams -> Encoding
$ctoEncoding :: FallbackCodeActionParams -> Encoding
toJSON :: FallbackCodeActionParams -> Value
$ctoJSON :: FallbackCodeActionParams -> Value
ToJSON, Value -> Parser [FallbackCodeActionParams]
Value -> Parser FallbackCodeActionParams
(Value -> Parser FallbackCodeActionParams)
-> (Value -> Parser [FallbackCodeActionParams])
-> FromJSON FallbackCodeActionParams
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [FallbackCodeActionParams]
$cparseJSONList :: Value -> Parser [FallbackCodeActionParams]
parseJSON :: Value -> Parser FallbackCodeActionParams
$cparseJSON :: Value -> Parser FallbackCodeActionParams
FromJSON)
otSetUri :: SpanInFlight -> Uri -> IO ()
otSetUri :: SpanInFlight -> Uri -> IO ()
otSetUri SpanInFlight
sp (Uri Text
t) = SpanInFlight -> ByteString -> ByteString -> IO ()
forall (m :: * -> *).
MonadIO m =>
SpanInFlight -> ByteString -> ByteString -> m ()
setTag SpanInFlight
sp ByteString
"uri" (Text -> ByteString
encodeUtf8 Text
t)
class HasTracing a where
  traceWithSpan :: SpanInFlight -> a -> IO ()
  traceWithSpan SpanInFlight
_ a
_ = () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
instance {-# OVERLAPPABLE #-} (HasTextDocument a doc, HasUri doc Uri) => HasTracing a where
  traceWithSpan :: SpanInFlight -> a -> IO ()
traceWithSpan SpanInFlight
sp a
a = SpanInFlight -> Uri -> IO ()
otSetUri SpanInFlight
sp (a
a a -> Getting Uri a Uri -> Uri
forall s a. s -> Getting a s a -> a
^. (doc -> Const Uri doc) -> a -> Const Uri a
forall s a. HasTextDocument s a => Lens' s a
J.textDocument ((doc -> Const Uri doc) -> a -> Const Uri a)
-> ((Uri -> Const Uri Uri) -> doc -> Const Uri doc)
-> Getting Uri a Uri
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Uri -> Const Uri Uri) -> doc -> Const Uri doc
forall s a. HasUri s a => Lens' s a
J.uri)
instance HasTracing Value
instance HasTracing ExecuteCommandParams
instance HasTracing DidChangeWatchedFilesParams
instance HasTracing DidChangeWorkspaceFoldersParams
instance HasTracing DidChangeConfigurationParams
instance HasTracing InitializeParams
instance HasTracing (Maybe InitializedParams)
instance HasTracing WorkspaceSymbolParams where
  traceWithSpan :: SpanInFlight -> WorkspaceSymbolParams -> IO ()
traceWithSpan SpanInFlight
sp (WorkspaceSymbolParams Maybe ProgressToken
_ Maybe ProgressToken
_ Text
query) = SpanInFlight -> ByteString -> ByteString -> IO ()
forall (m :: * -> *).
MonadIO m =>
SpanInFlight -> ByteString -> ByteString -> m ()
setTag SpanInFlight
sp ByteString
"query" (Text -> ByteString
encodeUtf8 Text
query)
{-# NOINLINE pROCESS_ID #-}
pROCESS_ID :: T.Text
pROCESS_ID :: Text
pROCESS_ID = IO Text -> Text
forall a. IO a -> a
unsafePerformIO IO Text
getPid
mkLspCommand :: PluginId -> CommandId -> T.Text -> Maybe [Value] -> Command
mkLspCommand :: PluginId -> CommandId -> Text -> Maybe [Value] -> Command
mkLspCommand PluginId
plid CommandId
cn Text
title Maybe [Value]
args' = Text -> Text -> Maybe (List Value) -> Command
Command Text
title Text
cmdId Maybe (List Value)
args
  where
    cmdId :: Text
cmdId = Text -> PluginId -> CommandId -> Text
mkLspCmdId Text
pROCESS_ID PluginId
plid CommandId
cn
    args :: Maybe (List Value)
args = [Value] -> List Value
forall a. [a] -> List a
List ([Value] -> List Value) -> Maybe [Value] -> Maybe (List Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe [Value]
args'
mkLspCmdId :: T.Text -> PluginId -> CommandId -> T.Text
mkLspCmdId :: Text -> PluginId -> CommandId -> Text
mkLspCmdId Text
pid (PluginId Text
plid) (CommandId Text
cid)
  = Text
pid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
plid Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
":" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
cid
getPid :: IO T.Text
getPid :: IO Text
getPid = String -> Text
T.pack (String -> Text) -> (Int -> String) -> Int -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> String
forall a. Show a => a -> String
show (Int -> Text) -> IO Int -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Int
getProcessID
getProcessID :: IO Int
installSigUsr1Handler :: IO () -> IO ()
#ifdef mingw32_HOST_OS
getProcessID = fromIntegral <$> P.getCurrentProcessId
installSigUsr1Handler _ = return ()
#else
getProcessID :: IO Int
getProcessID = ProcessID -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ProcessID -> Int) -> IO ProcessID -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO ProcessID
P.getProcessID
installSigUsr1Handler :: IO () -> IO ()
installSigUsr1Handler IO ()
h = IO Handler -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Handler -> IO ()) -> IO Handler -> IO ()
forall a b. (a -> b) -> a -> b
$ Signal -> Handler -> Maybe SignalSet -> IO Handler
installHandler Signal
sigUSR1 (IO () -> Handler
Catch IO ()
h) Maybe SignalSet
forall a. Maybe a
Nothing
#endif