{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
module Language.LSP.Types.SemanticTokens where
import qualified Data.Aeson as A
import Data.Aeson.TH
import Data.Text (Text)
import Control.Monad.Except
import Language.LSP.Types.Common
import Language.LSP.Types.Location
import Language.LSP.Types.Progress
import Language.LSP.Types.StaticRegistrationOptions
import Language.LSP.Types.TextDocument
import Language.LSP.Types.Utils
import qualified Data.Algorithm.Diff as Diff
import qualified Data.Bits as Bits
import qualified Data.DList as DList
import Data.Default
import Data.Foldable hiding (length)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe,
maybeToList)
import Data.String
data SemanticTokenTypes =
SttNamespace
| SttType
| SttClass
| SttEnum
| SttInterface
| SttStruct
| SttTypeParameter
| SttParameter
| SttVariable
| SttProperty
| SttEnumMember
| SttEvent
| SttFunction
| SttMethod
| SttMacro
| SttKeyword
| SttModifier
|
| SttString
| SttNumber
| SttRegexp
| SttOperator
| SttUnknown Text
deriving (Int -> SemanticTokenTypes -> ShowS
[SemanticTokenTypes] -> ShowS
SemanticTokenTypes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokenTypes] -> ShowS
$cshowList :: [SemanticTokenTypes] -> ShowS
show :: SemanticTokenTypes -> String
$cshow :: SemanticTokenTypes -> String
showsPrec :: Int -> SemanticTokenTypes -> ShowS
$cshowsPrec :: Int -> SemanticTokenTypes -> ShowS
Show, ReadPrec [SemanticTokenTypes]
ReadPrec SemanticTokenTypes
Int -> ReadS SemanticTokenTypes
ReadS [SemanticTokenTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokenTypes]
$creadListPrec :: ReadPrec [SemanticTokenTypes]
readPrec :: ReadPrec SemanticTokenTypes
$creadPrec :: ReadPrec SemanticTokenTypes
readList :: ReadS [SemanticTokenTypes]
$creadList :: ReadS [SemanticTokenTypes]
readsPrec :: Int -> ReadS SemanticTokenTypes
$creadsPrec :: Int -> ReadS SemanticTokenTypes
Read, SemanticTokenTypes -> SemanticTokenTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
$c/= :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
== :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
$c== :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
Eq, Eq SemanticTokenTypes
SemanticTokenTypes -> SemanticTokenTypes -> Bool
SemanticTokenTypes -> SemanticTokenTypes -> Ordering
SemanticTokenTypes -> SemanticTokenTypes -> SemanticTokenTypes
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 :: SemanticTokenTypes -> SemanticTokenTypes -> SemanticTokenTypes
$cmin :: SemanticTokenTypes -> SemanticTokenTypes -> SemanticTokenTypes
max :: SemanticTokenTypes -> SemanticTokenTypes -> SemanticTokenTypes
$cmax :: SemanticTokenTypes -> SemanticTokenTypes -> SemanticTokenTypes
>= :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
$c>= :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
> :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
$c> :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
<= :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
$c<= :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
< :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
$c< :: SemanticTokenTypes -> SemanticTokenTypes -> Bool
compare :: SemanticTokenTypes -> SemanticTokenTypes -> Ordering
$ccompare :: SemanticTokenTypes -> SemanticTokenTypes -> Ordering
Ord)
instance A.ToJSON SemanticTokenTypes where
toJSON :: SemanticTokenTypes -> Value
toJSON SemanticTokenTypes
SttNamespace = Text -> Value
A.String Text
"namespace"
toJSON SemanticTokenTypes
SttType = Text -> Value
A.String Text
"type"
toJSON SemanticTokenTypes
SttClass = Text -> Value
A.String Text
"class"
toJSON SemanticTokenTypes
SttEnum = Text -> Value
A.String Text
"enum"
toJSON SemanticTokenTypes
SttInterface = Text -> Value
A.String Text
"interface"
toJSON SemanticTokenTypes
SttStruct = Text -> Value
A.String Text
"struct"
toJSON SemanticTokenTypes
SttTypeParameter = Text -> Value
A.String Text
"typeParameter"
toJSON SemanticTokenTypes
SttParameter = Text -> Value
A.String Text
"parameter"
toJSON SemanticTokenTypes
SttVariable = Text -> Value
A.String Text
"variable"
toJSON SemanticTokenTypes
SttProperty = Text -> Value
A.String Text
"property"
toJSON SemanticTokenTypes
SttEnumMember = Text -> Value
A.String Text
"enumMember"
toJSON SemanticTokenTypes
SttEvent = Text -> Value
A.String Text
"event"
toJSON SemanticTokenTypes
SttFunction = Text -> Value
A.String Text
"function"
toJSON SemanticTokenTypes
SttMethod = Text -> Value
A.String Text
"method"
toJSON SemanticTokenTypes
SttMacro = Text -> Value
A.String Text
"macro"
toJSON SemanticTokenTypes
SttKeyword = Text -> Value
A.String Text
"keyword"
toJSON SemanticTokenTypes
SttModifier = Text -> Value
A.String Text
"modifier"
toJSON SemanticTokenTypes
SttComment = Text -> Value
A.String Text
"comment"
toJSON SemanticTokenTypes
SttString = Text -> Value
A.String Text
"string"
toJSON SemanticTokenTypes
SttNumber = Text -> Value
A.String Text
"number"
toJSON SemanticTokenTypes
SttRegexp = Text -> Value
A.String Text
"regexp"
toJSON SemanticTokenTypes
SttOperator = Text -> Value
A.String Text
"operator"
toJSON (SttUnknown Text
t) = Text -> Value
A.String Text
t
instance A.FromJSON SemanticTokenTypes where
parseJSON :: Value -> Parser SemanticTokenTypes
parseJSON (A.String Text
"namespace") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttNamespace
parseJSON (A.String Text
"type") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttType
parseJSON (A.String Text
"class") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttClass
parseJSON (A.String Text
"enum") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttEnum
parseJSON (A.String Text
"interface") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttInterface
parseJSON (A.String Text
"struct") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttStruct
parseJSON (A.String Text
"typeParameter") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttTypeParameter
parseJSON (A.String Text
"parameter") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttParameter
parseJSON (A.String Text
"variable") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttVariable
parseJSON (A.String Text
"property") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttProperty
parseJSON (A.String Text
"enumMember") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttEnumMember
parseJSON (A.String Text
"event") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttEvent
parseJSON (A.String Text
"function") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttFunction
parseJSON (A.String Text
"method") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttMethod
parseJSON (A.String Text
"macro") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttMacro
parseJSON (A.String Text
"keyword") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttKeyword
parseJSON (A.String Text
"modifier") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttModifier
parseJSON (A.String Text
"comment") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttComment
parseJSON (A.String Text
"string") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttString
parseJSON (A.String Text
"number") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttNumber
parseJSON (A.String Text
"regexp") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttRegexp
parseJSON (A.String Text
"operator") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenTypes
SttOperator
parseJSON (A.String Text
t) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Text -> SemanticTokenTypes
SttUnknown Text
t
parseJSON Value
_ = forall a. Monoid a => a
mempty
knownSemanticTokenTypes :: [SemanticTokenTypes]
knownSemanticTokenTypes :: [SemanticTokenTypes]
knownSemanticTokenTypes = [
SemanticTokenTypes
SttNamespace
, SemanticTokenTypes
SttType
, SemanticTokenTypes
SttClass
, SemanticTokenTypes
SttEnum
, SemanticTokenTypes
SttInterface
, SemanticTokenTypes
SttStruct
, SemanticTokenTypes
SttTypeParameter
, SemanticTokenTypes
SttParameter
, SemanticTokenTypes
SttVariable
, SemanticTokenTypes
SttProperty
, SemanticTokenTypes
SttEnumMember
, SemanticTokenTypes
SttEvent
, SemanticTokenTypes
SttFunction
, SemanticTokenTypes
SttMethod
, SemanticTokenTypes
SttMacro
, SemanticTokenTypes
SttKeyword
, SemanticTokenTypes
SttModifier
, SemanticTokenTypes
SttComment
, SemanticTokenTypes
SttString
, SemanticTokenTypes
SttNumber
, SemanticTokenTypes
SttRegexp
, SemanticTokenTypes
SttOperator
]
data SemanticTokenModifiers =
StmDeclaration
| StmDefinition
| StmReadonly
| StmStatic
| StmDeprecated
| StmAbstract
| StmAsync
| StmModification
| StmDocumentation
| StmDefaultLibrary
| StmUnknown Text
deriving (Int -> SemanticTokenModifiers -> ShowS
[SemanticTokenModifiers] -> ShowS
SemanticTokenModifiers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokenModifiers] -> ShowS
$cshowList :: [SemanticTokenModifiers] -> ShowS
show :: SemanticTokenModifiers -> String
$cshow :: SemanticTokenModifiers -> String
showsPrec :: Int -> SemanticTokenModifiers -> ShowS
$cshowsPrec :: Int -> SemanticTokenModifiers -> ShowS
Show, ReadPrec [SemanticTokenModifiers]
ReadPrec SemanticTokenModifiers
Int -> ReadS SemanticTokenModifiers
ReadS [SemanticTokenModifiers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokenModifiers]
$creadListPrec :: ReadPrec [SemanticTokenModifiers]
readPrec :: ReadPrec SemanticTokenModifiers
$creadPrec :: ReadPrec SemanticTokenModifiers
readList :: ReadS [SemanticTokenModifiers]
$creadList :: ReadS [SemanticTokenModifiers]
readsPrec :: Int -> ReadS SemanticTokenModifiers
$creadsPrec :: Int -> ReadS SemanticTokenModifiers
Read, SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
$c/= :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
== :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
$c== :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
Eq, Eq SemanticTokenModifiers
SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
SemanticTokenModifiers -> SemanticTokenModifiers -> Ordering
SemanticTokenModifiers
-> SemanticTokenModifiers -> SemanticTokenModifiers
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 :: SemanticTokenModifiers
-> SemanticTokenModifiers -> SemanticTokenModifiers
$cmin :: SemanticTokenModifiers
-> SemanticTokenModifiers -> SemanticTokenModifiers
max :: SemanticTokenModifiers
-> SemanticTokenModifiers -> SemanticTokenModifiers
$cmax :: SemanticTokenModifiers
-> SemanticTokenModifiers -> SemanticTokenModifiers
>= :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
$c>= :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
> :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
$c> :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
<= :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
$c<= :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
< :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
$c< :: SemanticTokenModifiers -> SemanticTokenModifiers -> Bool
compare :: SemanticTokenModifiers -> SemanticTokenModifiers -> Ordering
$ccompare :: SemanticTokenModifiers -> SemanticTokenModifiers -> Ordering
Ord)
instance A.ToJSON SemanticTokenModifiers where
toJSON :: SemanticTokenModifiers -> Value
toJSON SemanticTokenModifiers
StmDeclaration = Text -> Value
A.String Text
"declaration"
toJSON SemanticTokenModifiers
StmDefinition = Text -> Value
A.String Text
"definition"
toJSON SemanticTokenModifiers
StmReadonly = Text -> Value
A.String Text
"readonly"
toJSON SemanticTokenModifiers
StmStatic = Text -> Value
A.String Text
"static"
toJSON SemanticTokenModifiers
StmDeprecated = Text -> Value
A.String Text
"deprecated"
toJSON SemanticTokenModifiers
StmAbstract = Text -> Value
A.String Text
"abstract"
toJSON SemanticTokenModifiers
StmAsync = Text -> Value
A.String Text
"async"
toJSON SemanticTokenModifiers
StmModification = Text -> Value
A.String Text
"modification"
toJSON SemanticTokenModifiers
StmDocumentation = Text -> Value
A.String Text
"documentation"
toJSON SemanticTokenModifiers
StmDefaultLibrary = Text -> Value
A.String Text
"defaultLibrary"
toJSON (StmUnknown Text
t) = Text -> Value
A.String Text
t
instance A.FromJSON SemanticTokenModifiers where
parseJSON :: Value -> Parser SemanticTokenModifiers
parseJSON (A.String Text
"declaration") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmDeclaration
parseJSON (A.String Text
"definition") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmDefinition
parseJSON (A.String Text
"readonly") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmReadonly
parseJSON (A.String Text
"static") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmStatic
parseJSON (A.String Text
"deprecated") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmDeprecated
parseJSON (A.String Text
"abstract") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmAbstract
parseJSON (A.String Text
"async") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmAsync
parseJSON (A.String Text
"modification") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmModification
parseJSON (A.String Text
"documentation") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmDocumentation
parseJSON (A.String Text
"defaultLibrary") = forall (f :: * -> *) a. Applicative f => a -> f a
pure SemanticTokenModifiers
StmDefaultLibrary
parseJSON (A.String Text
t) = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Text -> SemanticTokenModifiers
StmUnknown Text
t
parseJSON Value
_ = forall a. Monoid a => a
mempty
knownSemanticTokenModifiers :: [SemanticTokenModifiers]
knownSemanticTokenModifiers :: [SemanticTokenModifiers]
knownSemanticTokenModifiers = [
SemanticTokenModifiers
StmDeclaration
, SemanticTokenModifiers
StmDefinition
, SemanticTokenModifiers
StmReadonly
, SemanticTokenModifiers
StmStatic
, SemanticTokenModifiers
StmDeprecated
, SemanticTokenModifiers
StmAbstract
, SemanticTokenModifiers
StmAsync
, SemanticTokenModifiers
StmModification
, SemanticTokenModifiers
StmDocumentation
, SemanticTokenModifiers
StmDefaultLibrary
]
data TokenFormat = TokenFormatRelative
deriving (Int -> TokenFormat -> ShowS
[TokenFormat] -> ShowS
TokenFormat -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TokenFormat] -> ShowS
$cshowList :: [TokenFormat] -> ShowS
show :: TokenFormat -> String
$cshow :: TokenFormat -> String
showsPrec :: Int -> TokenFormat -> ShowS
$cshowsPrec :: Int -> TokenFormat -> ShowS
Show, ReadPrec [TokenFormat]
ReadPrec TokenFormat
Int -> ReadS TokenFormat
ReadS [TokenFormat]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TokenFormat]
$creadListPrec :: ReadPrec [TokenFormat]
readPrec :: ReadPrec TokenFormat
$creadPrec :: ReadPrec TokenFormat
readList :: ReadS [TokenFormat]
$creadList :: ReadS [TokenFormat]
readsPrec :: Int -> ReadS TokenFormat
$creadsPrec :: Int -> ReadS TokenFormat
Read, TokenFormat -> TokenFormat -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TokenFormat -> TokenFormat -> Bool
$c/= :: TokenFormat -> TokenFormat -> Bool
== :: TokenFormat -> TokenFormat -> Bool
$c== :: TokenFormat -> TokenFormat -> Bool
Eq)
instance A.ToJSON TokenFormat where
toJSON :: TokenFormat -> Value
toJSON TokenFormat
TokenFormatRelative = Text -> Value
A.String Text
"relative"
instance A.FromJSON TokenFormat where
parseJSON :: Value -> Parser TokenFormat
parseJSON (A.String Text
"relative") = forall (f :: * -> *) a. Applicative f => a -> f a
pure TokenFormat
TokenFormatRelative
parseJSON Value
_ = forall a. Monoid a => a
mempty
data SemanticTokensLegend = SemanticTokensLegend {
SemanticTokensLegend -> List SemanticTokenTypes
_tokenTypes :: List SemanticTokenTypes,
SemanticTokensLegend -> List SemanticTokenModifiers
_tokenModifiers :: List SemanticTokenModifiers
} deriving (Int -> SemanticTokensLegend -> ShowS
[SemanticTokensLegend] -> ShowS
SemanticTokensLegend -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensLegend] -> ShowS
$cshowList :: [SemanticTokensLegend] -> ShowS
show :: SemanticTokensLegend -> String
$cshow :: SemanticTokensLegend -> String
showsPrec :: Int -> SemanticTokensLegend -> ShowS
$cshowsPrec :: Int -> SemanticTokensLegend -> ShowS
Show, ReadPrec [SemanticTokensLegend]
ReadPrec SemanticTokensLegend
Int -> ReadS SemanticTokensLegend
ReadS [SemanticTokensLegend]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensLegend]
$creadListPrec :: ReadPrec [SemanticTokensLegend]
readPrec :: ReadPrec SemanticTokensLegend
$creadPrec :: ReadPrec SemanticTokensLegend
readList :: ReadS [SemanticTokensLegend]
$creadList :: ReadS [SemanticTokensLegend]
readsPrec :: Int -> ReadS SemanticTokensLegend
$creadsPrec :: Int -> ReadS SemanticTokensLegend
Read, SemanticTokensLegend -> SemanticTokensLegend -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensLegend -> SemanticTokensLegend -> Bool
$c/= :: SemanticTokensLegend -> SemanticTokensLegend -> Bool
== :: SemanticTokensLegend -> SemanticTokensLegend -> Bool
$c== :: SemanticTokensLegend -> SemanticTokensLegend -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensLegend
instance Default SemanticTokensLegend where
def :: SemanticTokensLegend
def = List SemanticTokenTypes
-> List SemanticTokenModifiers -> SemanticTokensLegend
SemanticTokensLegend (forall a. [a] -> List a
List [SemanticTokenTypes]
knownSemanticTokenTypes) (forall a. [a] -> List a
List [SemanticTokenModifiers]
knownSemanticTokenModifiers)
data SemanticTokensRangeClientCapabilities = SemanticTokensRangeBool Bool | SemanticTokensRangeObj A.Value
deriving (Int -> SemanticTokensRangeClientCapabilities -> ShowS
[SemanticTokensRangeClientCapabilities] -> ShowS
SemanticTokensRangeClientCapabilities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensRangeClientCapabilities] -> ShowS
$cshowList :: [SemanticTokensRangeClientCapabilities] -> ShowS
show :: SemanticTokensRangeClientCapabilities -> String
$cshow :: SemanticTokensRangeClientCapabilities -> String
showsPrec :: Int -> SemanticTokensRangeClientCapabilities -> ShowS
$cshowsPrec :: Int -> SemanticTokensRangeClientCapabilities -> ShowS
Show, ReadPrec [SemanticTokensRangeClientCapabilities]
ReadPrec SemanticTokensRangeClientCapabilities
Int -> ReadS SemanticTokensRangeClientCapabilities
ReadS [SemanticTokensRangeClientCapabilities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensRangeClientCapabilities]
$creadListPrec :: ReadPrec [SemanticTokensRangeClientCapabilities]
readPrec :: ReadPrec SemanticTokensRangeClientCapabilities
$creadPrec :: ReadPrec SemanticTokensRangeClientCapabilities
readList :: ReadS [SemanticTokensRangeClientCapabilities]
$creadList :: ReadS [SemanticTokensRangeClientCapabilities]
readsPrec :: Int -> ReadS SemanticTokensRangeClientCapabilities
$creadsPrec :: Int -> ReadS SemanticTokensRangeClientCapabilities
Read, SemanticTokensRangeClientCapabilities
-> SemanticTokensRangeClientCapabilities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensRangeClientCapabilities
-> SemanticTokensRangeClientCapabilities -> Bool
$c/= :: SemanticTokensRangeClientCapabilities
-> SemanticTokensRangeClientCapabilities -> Bool
== :: SemanticTokensRangeClientCapabilities
-> SemanticTokensRangeClientCapabilities -> Bool
$c== :: SemanticTokensRangeClientCapabilities
-> SemanticTokensRangeClientCapabilities -> Bool
Eq)
deriveJSON lspOptionsUntagged ''SemanticTokensRangeClientCapabilities
data SemanticTokensDeltaClientCapabilities = SemanticTokensDeltaClientCapabilities {
SemanticTokensDeltaClientCapabilities -> Maybe Bool
_delta :: Maybe Bool
} deriving (Int -> SemanticTokensDeltaClientCapabilities -> ShowS
[SemanticTokensDeltaClientCapabilities] -> ShowS
SemanticTokensDeltaClientCapabilities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensDeltaClientCapabilities] -> ShowS
$cshowList :: [SemanticTokensDeltaClientCapabilities] -> ShowS
show :: SemanticTokensDeltaClientCapabilities -> String
$cshow :: SemanticTokensDeltaClientCapabilities -> String
showsPrec :: Int -> SemanticTokensDeltaClientCapabilities -> ShowS
$cshowsPrec :: Int -> SemanticTokensDeltaClientCapabilities -> ShowS
Show, ReadPrec [SemanticTokensDeltaClientCapabilities]
ReadPrec SemanticTokensDeltaClientCapabilities
Int -> ReadS SemanticTokensDeltaClientCapabilities
ReadS [SemanticTokensDeltaClientCapabilities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensDeltaClientCapabilities]
$creadListPrec :: ReadPrec [SemanticTokensDeltaClientCapabilities]
readPrec :: ReadPrec SemanticTokensDeltaClientCapabilities
$creadPrec :: ReadPrec SemanticTokensDeltaClientCapabilities
readList :: ReadS [SemanticTokensDeltaClientCapabilities]
$creadList :: ReadS [SemanticTokensDeltaClientCapabilities]
readsPrec :: Int -> ReadS SemanticTokensDeltaClientCapabilities
$creadsPrec :: Int -> ReadS SemanticTokensDeltaClientCapabilities
Read, SemanticTokensDeltaClientCapabilities
-> SemanticTokensDeltaClientCapabilities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensDeltaClientCapabilities
-> SemanticTokensDeltaClientCapabilities -> Bool
$c/= :: SemanticTokensDeltaClientCapabilities
-> SemanticTokensDeltaClientCapabilities -> Bool
== :: SemanticTokensDeltaClientCapabilities
-> SemanticTokensDeltaClientCapabilities -> Bool
$c== :: SemanticTokensDeltaClientCapabilities
-> SemanticTokensDeltaClientCapabilities -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensDeltaClientCapabilities
data SemanticTokensFullClientCapabilities = SemanticTokensFullBool Bool | SemanticTokensFullDelta SemanticTokensDeltaClientCapabilities
deriving (Int -> SemanticTokensFullClientCapabilities -> ShowS
[SemanticTokensFullClientCapabilities] -> ShowS
SemanticTokensFullClientCapabilities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensFullClientCapabilities] -> ShowS
$cshowList :: [SemanticTokensFullClientCapabilities] -> ShowS
show :: SemanticTokensFullClientCapabilities -> String
$cshow :: SemanticTokensFullClientCapabilities -> String
showsPrec :: Int -> SemanticTokensFullClientCapabilities -> ShowS
$cshowsPrec :: Int -> SemanticTokensFullClientCapabilities -> ShowS
Show, ReadPrec [SemanticTokensFullClientCapabilities]
ReadPrec SemanticTokensFullClientCapabilities
Int -> ReadS SemanticTokensFullClientCapabilities
ReadS [SemanticTokensFullClientCapabilities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensFullClientCapabilities]
$creadListPrec :: ReadPrec [SemanticTokensFullClientCapabilities]
readPrec :: ReadPrec SemanticTokensFullClientCapabilities
$creadPrec :: ReadPrec SemanticTokensFullClientCapabilities
readList :: ReadS [SemanticTokensFullClientCapabilities]
$creadList :: ReadS [SemanticTokensFullClientCapabilities]
readsPrec :: Int -> ReadS SemanticTokensFullClientCapabilities
$creadsPrec :: Int -> ReadS SemanticTokensFullClientCapabilities
Read, SemanticTokensFullClientCapabilities
-> SemanticTokensFullClientCapabilities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensFullClientCapabilities
-> SemanticTokensFullClientCapabilities -> Bool
$c/= :: SemanticTokensFullClientCapabilities
-> SemanticTokensFullClientCapabilities -> Bool
== :: SemanticTokensFullClientCapabilities
-> SemanticTokensFullClientCapabilities -> Bool
$c== :: SemanticTokensFullClientCapabilities
-> SemanticTokensFullClientCapabilities -> Bool
Eq)
deriveJSON lspOptionsUntagged ''SemanticTokensFullClientCapabilities
data SemanticTokensRequestsClientCapabilities = SemanticTokensRequestsClientCapabilities {
SemanticTokensRequestsClientCapabilities
-> Maybe SemanticTokensRangeClientCapabilities
_range :: Maybe SemanticTokensRangeClientCapabilities,
SemanticTokensRequestsClientCapabilities
-> Maybe SemanticTokensFullClientCapabilities
_full :: Maybe SemanticTokensFullClientCapabilities
} deriving (Int -> SemanticTokensRequestsClientCapabilities -> ShowS
[SemanticTokensRequestsClientCapabilities] -> ShowS
SemanticTokensRequestsClientCapabilities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensRequestsClientCapabilities] -> ShowS
$cshowList :: [SemanticTokensRequestsClientCapabilities] -> ShowS
show :: SemanticTokensRequestsClientCapabilities -> String
$cshow :: SemanticTokensRequestsClientCapabilities -> String
showsPrec :: Int -> SemanticTokensRequestsClientCapabilities -> ShowS
$cshowsPrec :: Int -> SemanticTokensRequestsClientCapabilities -> ShowS
Show, ReadPrec [SemanticTokensRequestsClientCapabilities]
ReadPrec SemanticTokensRequestsClientCapabilities
Int -> ReadS SemanticTokensRequestsClientCapabilities
ReadS [SemanticTokensRequestsClientCapabilities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensRequestsClientCapabilities]
$creadListPrec :: ReadPrec [SemanticTokensRequestsClientCapabilities]
readPrec :: ReadPrec SemanticTokensRequestsClientCapabilities
$creadPrec :: ReadPrec SemanticTokensRequestsClientCapabilities
readList :: ReadS [SemanticTokensRequestsClientCapabilities]
$creadList :: ReadS [SemanticTokensRequestsClientCapabilities]
readsPrec :: Int -> ReadS SemanticTokensRequestsClientCapabilities
$creadsPrec :: Int -> ReadS SemanticTokensRequestsClientCapabilities
Read, SemanticTokensRequestsClientCapabilities
-> SemanticTokensRequestsClientCapabilities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensRequestsClientCapabilities
-> SemanticTokensRequestsClientCapabilities -> Bool
$c/= :: SemanticTokensRequestsClientCapabilities
-> SemanticTokensRequestsClientCapabilities -> Bool
== :: SemanticTokensRequestsClientCapabilities
-> SemanticTokensRequestsClientCapabilities -> Bool
$c== :: SemanticTokensRequestsClientCapabilities
-> SemanticTokensRequestsClientCapabilities -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensRequestsClientCapabilities
data SemanticTokensClientCapabilities = SemanticTokensClientCapabilities {
SemanticTokensClientCapabilities -> Maybe Bool
_dynamicRegistration :: Maybe Bool,
SemanticTokensClientCapabilities
-> SemanticTokensRequestsClientCapabilities
_requests :: SemanticTokensRequestsClientCapabilities,
SemanticTokensClientCapabilities -> List SemanticTokenTypes
_tokenTypes :: List SemanticTokenTypes,
SemanticTokensClientCapabilities -> List SemanticTokenModifiers
_tokenModifiers :: List SemanticTokenModifiers,
SemanticTokensClientCapabilities -> List TokenFormat
_formats :: List TokenFormat,
SemanticTokensClientCapabilities -> Maybe Bool
_overlappingTokenSupport :: Maybe Bool,
SemanticTokensClientCapabilities -> Maybe Bool
_multilineTokenSupport :: Maybe Bool
} deriving (Int -> SemanticTokensClientCapabilities -> ShowS
[SemanticTokensClientCapabilities] -> ShowS
SemanticTokensClientCapabilities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensClientCapabilities] -> ShowS
$cshowList :: [SemanticTokensClientCapabilities] -> ShowS
show :: SemanticTokensClientCapabilities -> String
$cshow :: SemanticTokensClientCapabilities -> String
showsPrec :: Int -> SemanticTokensClientCapabilities -> ShowS
$cshowsPrec :: Int -> SemanticTokensClientCapabilities -> ShowS
Show, ReadPrec [SemanticTokensClientCapabilities]
ReadPrec SemanticTokensClientCapabilities
Int -> ReadS SemanticTokensClientCapabilities
ReadS [SemanticTokensClientCapabilities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensClientCapabilities]
$creadListPrec :: ReadPrec [SemanticTokensClientCapabilities]
readPrec :: ReadPrec SemanticTokensClientCapabilities
$creadPrec :: ReadPrec SemanticTokensClientCapabilities
readList :: ReadS [SemanticTokensClientCapabilities]
$creadList :: ReadS [SemanticTokensClientCapabilities]
readsPrec :: Int -> ReadS SemanticTokensClientCapabilities
$creadsPrec :: Int -> ReadS SemanticTokensClientCapabilities
Read, SemanticTokensClientCapabilities
-> SemanticTokensClientCapabilities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensClientCapabilities
-> SemanticTokensClientCapabilities -> Bool
$c/= :: SemanticTokensClientCapabilities
-> SemanticTokensClientCapabilities -> Bool
== :: SemanticTokensClientCapabilities
-> SemanticTokensClientCapabilities -> Bool
$c== :: SemanticTokensClientCapabilities
-> SemanticTokensClientCapabilities -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensClientCapabilities
makeExtendingDatatype "SemanticTokensOptions" [''WorkDoneProgressOptions]
[ ("_legend", [t| SemanticTokensLegend |])
, ("_range", [t| Maybe SemanticTokensRangeClientCapabilities |])
, ("_full", [t| Maybe SemanticTokensFullClientCapabilities |])
]
deriveJSON lspOptions ''SemanticTokensOptions
makeExtendingDatatype "SemanticTokensRegistrationOptions"
[ ''TextDocumentRegistrationOptions
, ''SemanticTokensOptions
, ''StaticRegistrationOptions] []
deriveJSON lspOptions ''SemanticTokensRegistrationOptions
makeExtendingDatatype "SemanticTokensParams"
[''WorkDoneProgressParams
, ''PartialResultParams]
[ ("_textDocument", [t| TextDocumentIdentifier |]) ]
deriveJSON lspOptions ''SemanticTokensParams
data SemanticTokens = SemanticTokens {
SemanticTokens -> Maybe Text
_resultId :: Maybe Text,
SemanticTokens -> List UInt
_xdata :: List UInt
} deriving (Int -> SemanticTokens -> ShowS
[SemanticTokens] -> ShowS
SemanticTokens -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokens] -> ShowS
$cshowList :: [SemanticTokens] -> ShowS
show :: SemanticTokens -> String
$cshow :: SemanticTokens -> String
showsPrec :: Int -> SemanticTokens -> ShowS
$cshowsPrec :: Int -> SemanticTokens -> ShowS
Show, ReadPrec [SemanticTokens]
ReadPrec SemanticTokens
Int -> ReadS SemanticTokens
ReadS [SemanticTokens]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokens]
$creadListPrec :: ReadPrec [SemanticTokens]
readPrec :: ReadPrec SemanticTokens
$creadPrec :: ReadPrec SemanticTokens
readList :: ReadS [SemanticTokens]
$creadList :: ReadS [SemanticTokens]
readsPrec :: Int -> ReadS SemanticTokens
$creadsPrec :: Int -> ReadS SemanticTokens
Read, SemanticTokens -> SemanticTokens -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokens -> SemanticTokens -> Bool
$c/= :: SemanticTokens -> SemanticTokens -> Bool
== :: SemanticTokens -> SemanticTokens -> Bool
$c== :: SemanticTokens -> SemanticTokens -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokens
data SemanticTokensPartialResult = SemanticTokensPartialResult {
SemanticTokensPartialResult -> List UInt
_xdata :: List UInt
}
deriveJSON lspOptions ''SemanticTokensPartialResult
makeExtendingDatatype "SemanticTokensDeltaParams"
[''WorkDoneProgressParams
, ''PartialResultParams]
[ ("_textDocument", [t| TextDocumentIdentifier |])
, ("_previousResultId", [t| Text |])
]
deriveJSON lspOptions ''SemanticTokensDeltaParams
data SemanticTokensEdit = SemanticTokensEdit {
SemanticTokensEdit -> UInt
_start :: UInt,
SemanticTokensEdit -> UInt
_deleteCount :: UInt,
SemanticTokensEdit -> Maybe (List UInt)
_xdata :: Maybe (List UInt)
} deriving (Int -> SemanticTokensEdit -> ShowS
[SemanticTokensEdit] -> ShowS
SemanticTokensEdit -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensEdit] -> ShowS
$cshowList :: [SemanticTokensEdit] -> ShowS
show :: SemanticTokensEdit -> String
$cshow :: SemanticTokensEdit -> String
showsPrec :: Int -> SemanticTokensEdit -> ShowS
$cshowsPrec :: Int -> SemanticTokensEdit -> ShowS
Show, ReadPrec [SemanticTokensEdit]
ReadPrec SemanticTokensEdit
Int -> ReadS SemanticTokensEdit
ReadS [SemanticTokensEdit]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensEdit]
$creadListPrec :: ReadPrec [SemanticTokensEdit]
readPrec :: ReadPrec SemanticTokensEdit
$creadPrec :: ReadPrec SemanticTokensEdit
readList :: ReadS [SemanticTokensEdit]
$creadList :: ReadS [SemanticTokensEdit]
readsPrec :: Int -> ReadS SemanticTokensEdit
$creadsPrec :: Int -> ReadS SemanticTokensEdit
Read, SemanticTokensEdit -> SemanticTokensEdit -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensEdit -> SemanticTokensEdit -> Bool
$c/= :: SemanticTokensEdit -> SemanticTokensEdit -> Bool
== :: SemanticTokensEdit -> SemanticTokensEdit -> Bool
$c== :: SemanticTokensEdit -> SemanticTokensEdit -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensEdit
data SemanticTokensDelta = SemanticTokensDelta {
SemanticTokensDelta -> Maybe Text
_resultId :: Maybe Text,
SemanticTokensDelta -> List SemanticTokensEdit
_edits :: List SemanticTokensEdit
} deriving (Int -> SemanticTokensDelta -> ShowS
[SemanticTokensDelta] -> ShowS
SemanticTokensDelta -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensDelta] -> ShowS
$cshowList :: [SemanticTokensDelta] -> ShowS
show :: SemanticTokensDelta -> String
$cshow :: SemanticTokensDelta -> String
showsPrec :: Int -> SemanticTokensDelta -> ShowS
$cshowsPrec :: Int -> SemanticTokensDelta -> ShowS
Show, ReadPrec [SemanticTokensDelta]
ReadPrec SemanticTokensDelta
Int -> ReadS SemanticTokensDelta
ReadS [SemanticTokensDelta]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensDelta]
$creadListPrec :: ReadPrec [SemanticTokensDelta]
readPrec :: ReadPrec SemanticTokensDelta
$creadPrec :: ReadPrec SemanticTokensDelta
readList :: ReadS [SemanticTokensDelta]
$creadList :: ReadS [SemanticTokensDelta]
readsPrec :: Int -> ReadS SemanticTokensDelta
$creadsPrec :: Int -> ReadS SemanticTokensDelta
Read, SemanticTokensDelta -> SemanticTokensDelta -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensDelta -> SemanticTokensDelta -> Bool
$c/= :: SemanticTokensDelta -> SemanticTokensDelta -> Bool
== :: SemanticTokensDelta -> SemanticTokensDelta -> Bool
$c== :: SemanticTokensDelta -> SemanticTokensDelta -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensDelta
data SemanticTokensDeltaPartialResult = SemantictokensDeltaPartialResult {
SemanticTokensDeltaPartialResult -> List SemanticTokensEdit
_edits :: List SemanticTokensEdit
} deriving (Int -> SemanticTokensDeltaPartialResult -> ShowS
[SemanticTokensDeltaPartialResult] -> ShowS
SemanticTokensDeltaPartialResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensDeltaPartialResult] -> ShowS
$cshowList :: [SemanticTokensDeltaPartialResult] -> ShowS
show :: SemanticTokensDeltaPartialResult -> String
$cshow :: SemanticTokensDeltaPartialResult -> String
showsPrec :: Int -> SemanticTokensDeltaPartialResult -> ShowS
$cshowsPrec :: Int -> SemanticTokensDeltaPartialResult -> ShowS
Show, ReadPrec [SemanticTokensDeltaPartialResult]
ReadPrec SemanticTokensDeltaPartialResult
Int -> ReadS SemanticTokensDeltaPartialResult
ReadS [SemanticTokensDeltaPartialResult]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensDeltaPartialResult]
$creadListPrec :: ReadPrec [SemanticTokensDeltaPartialResult]
readPrec :: ReadPrec SemanticTokensDeltaPartialResult
$creadPrec :: ReadPrec SemanticTokensDeltaPartialResult
readList :: ReadS [SemanticTokensDeltaPartialResult]
$creadList :: ReadS [SemanticTokensDeltaPartialResult]
readsPrec :: Int -> ReadS SemanticTokensDeltaPartialResult
$creadsPrec :: Int -> ReadS SemanticTokensDeltaPartialResult
Read, SemanticTokensDeltaPartialResult
-> SemanticTokensDeltaPartialResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensDeltaPartialResult
-> SemanticTokensDeltaPartialResult -> Bool
$c/= :: SemanticTokensDeltaPartialResult
-> SemanticTokensDeltaPartialResult -> Bool
== :: SemanticTokensDeltaPartialResult
-> SemanticTokensDeltaPartialResult -> Bool
$c== :: SemanticTokensDeltaPartialResult
-> SemanticTokensDeltaPartialResult -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensDeltaPartialResult
makeExtendingDatatype "SemanticTokensRangeParams"
[''WorkDoneProgressParams
, ''PartialResultParams]
[ ("_textDocument", [t| TextDocumentIdentifier |])
, ("_range", [t| Range |])
]
deriveJSON lspOptions ''SemanticTokensRangeParams
data SemanticTokensWorkspaceClientCapabilities = SemanticTokensWorkspaceClientCapabilities {
SemanticTokensWorkspaceClientCapabilities -> Maybe Bool
_refreshSupport :: Maybe Bool
} deriving (Int -> SemanticTokensWorkspaceClientCapabilities -> ShowS
[SemanticTokensWorkspaceClientCapabilities] -> ShowS
SemanticTokensWorkspaceClientCapabilities -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokensWorkspaceClientCapabilities] -> ShowS
$cshowList :: [SemanticTokensWorkspaceClientCapabilities] -> ShowS
show :: SemanticTokensWorkspaceClientCapabilities -> String
$cshow :: SemanticTokensWorkspaceClientCapabilities -> String
showsPrec :: Int -> SemanticTokensWorkspaceClientCapabilities -> ShowS
$cshowsPrec :: Int -> SemanticTokensWorkspaceClientCapabilities -> ShowS
Show, ReadPrec [SemanticTokensWorkspaceClientCapabilities]
ReadPrec SemanticTokensWorkspaceClientCapabilities
Int -> ReadS SemanticTokensWorkspaceClientCapabilities
ReadS [SemanticTokensWorkspaceClientCapabilities]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokensWorkspaceClientCapabilities]
$creadListPrec :: ReadPrec [SemanticTokensWorkspaceClientCapabilities]
readPrec :: ReadPrec SemanticTokensWorkspaceClientCapabilities
$creadPrec :: ReadPrec SemanticTokensWorkspaceClientCapabilities
readList :: ReadS [SemanticTokensWorkspaceClientCapabilities]
$creadList :: ReadS [SemanticTokensWorkspaceClientCapabilities]
readsPrec :: Int -> ReadS SemanticTokensWorkspaceClientCapabilities
$creadsPrec :: Int -> ReadS SemanticTokensWorkspaceClientCapabilities
Read, SemanticTokensWorkspaceClientCapabilities
-> SemanticTokensWorkspaceClientCapabilities -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokensWorkspaceClientCapabilities
-> SemanticTokensWorkspaceClientCapabilities -> Bool
$c/= :: SemanticTokensWorkspaceClientCapabilities
-> SemanticTokensWorkspaceClientCapabilities -> Bool
== :: SemanticTokensWorkspaceClientCapabilities
-> SemanticTokensWorkspaceClientCapabilities -> Bool
$c== :: SemanticTokensWorkspaceClientCapabilities
-> SemanticTokensWorkspaceClientCapabilities -> Bool
Eq)
deriveJSON lspOptions ''SemanticTokensWorkspaceClientCapabilities
data SemanticTokenAbsolute = SemanticTokenAbsolute {
SemanticTokenAbsolute -> UInt
line :: UInt,
SemanticTokenAbsolute -> UInt
startChar :: UInt,
SemanticTokenAbsolute -> UInt
length :: UInt,
SemanticTokenAbsolute -> SemanticTokenTypes
tokenType :: SemanticTokenTypes,
SemanticTokenAbsolute -> [SemanticTokenModifiers]
tokenModifiers :: [SemanticTokenModifiers]
} deriving (Int -> SemanticTokenAbsolute -> ShowS
[SemanticTokenAbsolute] -> ShowS
SemanticTokenAbsolute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokenAbsolute] -> ShowS
$cshowList :: [SemanticTokenAbsolute] -> ShowS
show :: SemanticTokenAbsolute -> String
$cshow :: SemanticTokenAbsolute -> String
showsPrec :: Int -> SemanticTokenAbsolute -> ShowS
$cshowsPrec :: Int -> SemanticTokenAbsolute -> ShowS
Show, ReadPrec [SemanticTokenAbsolute]
ReadPrec SemanticTokenAbsolute
Int -> ReadS SemanticTokenAbsolute
ReadS [SemanticTokenAbsolute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokenAbsolute]
$creadListPrec :: ReadPrec [SemanticTokenAbsolute]
readPrec :: ReadPrec SemanticTokenAbsolute
$creadPrec :: ReadPrec SemanticTokenAbsolute
readList :: ReadS [SemanticTokenAbsolute]
$creadList :: ReadS [SemanticTokenAbsolute]
readsPrec :: Int -> ReadS SemanticTokenAbsolute
$creadsPrec :: Int -> ReadS SemanticTokenAbsolute
Read, SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
$c/= :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
== :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
$c== :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
Eq, Eq SemanticTokenAbsolute
SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
SemanticTokenAbsolute -> SemanticTokenAbsolute -> Ordering
SemanticTokenAbsolute
-> SemanticTokenAbsolute -> SemanticTokenAbsolute
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 :: SemanticTokenAbsolute
-> SemanticTokenAbsolute -> SemanticTokenAbsolute
$cmin :: SemanticTokenAbsolute
-> SemanticTokenAbsolute -> SemanticTokenAbsolute
max :: SemanticTokenAbsolute
-> SemanticTokenAbsolute -> SemanticTokenAbsolute
$cmax :: SemanticTokenAbsolute
-> SemanticTokenAbsolute -> SemanticTokenAbsolute
>= :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
$c>= :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
> :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
$c> :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
<= :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
$c<= :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
< :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
$c< :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Bool
compare :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Ordering
$ccompare :: SemanticTokenAbsolute -> SemanticTokenAbsolute -> Ordering
Ord)
data SemanticTokenRelative = SemanticTokenRelative {
SemanticTokenRelative -> UInt
deltaLine :: UInt,
SemanticTokenRelative -> UInt
deltaStartChar :: UInt,
SemanticTokenRelative -> UInt
length :: UInt,
SemanticTokenRelative -> SemanticTokenTypes
tokenType :: SemanticTokenTypes,
SemanticTokenRelative -> [SemanticTokenModifiers]
tokenModifiers :: [SemanticTokenModifiers]
} deriving (Int -> SemanticTokenRelative -> ShowS
[SemanticTokenRelative] -> ShowS
SemanticTokenRelative -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SemanticTokenRelative] -> ShowS
$cshowList :: [SemanticTokenRelative] -> ShowS
show :: SemanticTokenRelative -> String
$cshow :: SemanticTokenRelative -> String
showsPrec :: Int -> SemanticTokenRelative -> ShowS
$cshowsPrec :: Int -> SemanticTokenRelative -> ShowS
Show, ReadPrec [SemanticTokenRelative]
ReadPrec SemanticTokenRelative
Int -> ReadS SemanticTokenRelative
ReadS [SemanticTokenRelative]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SemanticTokenRelative]
$creadListPrec :: ReadPrec [SemanticTokenRelative]
readPrec :: ReadPrec SemanticTokenRelative
$creadPrec :: ReadPrec SemanticTokenRelative
readList :: ReadS [SemanticTokenRelative]
$creadList :: ReadS [SemanticTokenRelative]
readsPrec :: Int -> ReadS SemanticTokenRelative
$creadsPrec :: Int -> ReadS SemanticTokenRelative
Read, SemanticTokenRelative -> SemanticTokenRelative -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
$c/= :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
== :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
$c== :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
Eq, Eq SemanticTokenRelative
SemanticTokenRelative -> SemanticTokenRelative -> Bool
SemanticTokenRelative -> SemanticTokenRelative -> Ordering
SemanticTokenRelative
-> SemanticTokenRelative -> SemanticTokenRelative
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 :: SemanticTokenRelative
-> SemanticTokenRelative -> SemanticTokenRelative
$cmin :: SemanticTokenRelative
-> SemanticTokenRelative -> SemanticTokenRelative
max :: SemanticTokenRelative
-> SemanticTokenRelative -> SemanticTokenRelative
$cmax :: SemanticTokenRelative
-> SemanticTokenRelative -> SemanticTokenRelative
>= :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
$c>= :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
> :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
$c> :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
<= :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
$c<= :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
< :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
$c< :: SemanticTokenRelative -> SemanticTokenRelative -> Bool
compare :: SemanticTokenRelative -> SemanticTokenRelative -> Ordering
$ccompare :: SemanticTokenRelative -> SemanticTokenRelative -> Ordering
Ord)
relativizeTokens :: [SemanticTokenAbsolute] -> [SemanticTokenRelative]
relativizeTokens :: [SemanticTokenAbsolute] -> [SemanticTokenRelative]
relativizeTokens [SemanticTokenAbsolute]
xs = forall a. DList a -> [a]
DList.toList forall a b. (a -> b) -> a -> b
$ UInt
-> UInt
-> [SemanticTokenAbsolute]
-> DList SemanticTokenRelative
-> DList SemanticTokenRelative
go UInt
0 UInt
0 [SemanticTokenAbsolute]
xs forall a. Monoid a => a
mempty
where
go :: UInt -> UInt -> [SemanticTokenAbsolute] -> DList.DList SemanticTokenRelative -> DList.DList SemanticTokenRelative
go :: UInt
-> UInt
-> [SemanticTokenAbsolute]
-> DList SemanticTokenRelative
-> DList SemanticTokenRelative
go UInt
_ UInt
_ [] DList SemanticTokenRelative
acc = DList SemanticTokenRelative
acc
go UInt
lastLine UInt
lastChar (SemanticTokenAbsolute UInt
l UInt
c UInt
len SemanticTokenTypes
ty [SemanticTokenModifiers]
mods:[SemanticTokenAbsolute]
ts) DList SemanticTokenRelative
acc =
let
lastCharInLine :: UInt
lastCharInLine = if UInt
l forall a. Eq a => a -> a -> Bool
== UInt
lastLine then UInt
lastChar else UInt
0
dl :: UInt
dl = UInt
l forall a. Num a => a -> a -> a
- UInt
lastLine
dc :: UInt
dc = UInt
c forall a. Num a => a -> a -> a
- UInt
lastCharInLine
in UInt
-> UInt
-> [SemanticTokenAbsolute]
-> DList SemanticTokenRelative
-> DList SemanticTokenRelative
go UInt
l UInt
c [SemanticTokenAbsolute]
ts (forall a. DList a -> a -> DList a
DList.snoc DList SemanticTokenRelative
acc (UInt
-> UInt
-> UInt
-> SemanticTokenTypes
-> [SemanticTokenModifiers]
-> SemanticTokenRelative
SemanticTokenRelative UInt
dl UInt
dc UInt
len SemanticTokenTypes
ty [SemanticTokenModifiers]
mods))
absolutizeTokens :: [SemanticTokenRelative] -> [SemanticTokenAbsolute]
absolutizeTokens :: [SemanticTokenRelative] -> [SemanticTokenAbsolute]
absolutizeTokens [SemanticTokenRelative]
xs = forall a. DList a -> [a]
DList.toList forall a b. (a -> b) -> a -> b
$ UInt
-> UInt
-> [SemanticTokenRelative]
-> DList SemanticTokenAbsolute
-> DList SemanticTokenAbsolute
go UInt
0 UInt
0 [SemanticTokenRelative]
xs forall a. Monoid a => a
mempty
where
go :: UInt -> UInt -> [SemanticTokenRelative] -> DList.DList SemanticTokenAbsolute -> DList.DList SemanticTokenAbsolute
go :: UInt
-> UInt
-> [SemanticTokenRelative]
-> DList SemanticTokenAbsolute
-> DList SemanticTokenAbsolute
go UInt
_ UInt
_ [] DList SemanticTokenAbsolute
acc = DList SemanticTokenAbsolute
acc
go UInt
lastLine UInt
lastChar (SemanticTokenRelative UInt
dl UInt
dc UInt
len SemanticTokenTypes
ty [SemanticTokenModifiers]
mods:[SemanticTokenRelative]
ts) DList SemanticTokenAbsolute
acc =
let
lastCharInLine :: UInt
lastCharInLine = if UInt
dl forall a. Eq a => a -> a -> Bool
== UInt
0 then UInt
lastChar else UInt
0
l :: UInt
l = UInt
lastLine forall a. Num a => a -> a -> a
+ UInt
dl
c :: UInt
c = UInt
lastCharInLine forall a. Num a => a -> a -> a
+ UInt
dc
in UInt
-> UInt
-> [SemanticTokenRelative]
-> DList SemanticTokenAbsolute
-> DList SemanticTokenAbsolute
go UInt
l UInt
c [SemanticTokenRelative]
ts (forall a. DList a -> a -> DList a
DList.snoc DList SemanticTokenAbsolute
acc (UInt
-> UInt
-> UInt
-> SemanticTokenTypes
-> [SemanticTokenModifiers]
-> SemanticTokenAbsolute
SemanticTokenAbsolute UInt
l UInt
c UInt
len SemanticTokenTypes
ty [SemanticTokenModifiers]
mods))
encodeTokens :: SemanticTokensLegend -> [SemanticTokenRelative] -> Either Text [UInt]
encodeTokens :: SemanticTokensLegend
-> [SemanticTokenRelative] -> Either Text [UInt]
encodeTokens SemanticTokensLegend{$sel:_tokenTypes:SemanticTokensLegend :: SemanticTokensLegend -> List SemanticTokenTypes
_tokenTypes=List [SemanticTokenTypes]
tts,$sel:_tokenModifiers:SemanticTokensLegend :: SemanticTokensLegend -> List SemanticTokenModifiers
_tokenModifiers=List [SemanticTokenModifiers]
tms} [SemanticTokenRelative]
sts =
forall a. DList a -> [a]
DList.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [DList a] -> DList a
DList.concat forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse SemanticTokenRelative -> Either Text (DList UInt)
encodeToken [SemanticTokenRelative]
sts
where
tyMap :: Map.Map SemanticTokenTypes UInt
tyMap :: Map SemanticTokenTypes UInt
tyMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [SemanticTokenTypes]
tts [UInt
0..]
modMap :: Map.Map SemanticTokenModifiers Int
modMap :: Map SemanticTokenModifiers Int
modMap = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall a b. (a -> b) -> a -> b
$ forall a b. [a] -> [b] -> [(a, b)]
zip [SemanticTokenModifiers]
tms [Int
0..]
lookupTy :: SemanticTokenTypes -> Either Text UInt
lookupTy :: SemanticTokenTypes -> Either Text UInt
lookupTy SemanticTokenTypes
ty = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup SemanticTokenTypes
ty Map SemanticTokenTypes UInt
tyMap of
Just UInt
tycode -> forall (f :: * -> *) a. Applicative f => a -> f a
pure UInt
tycode
Maybe UInt
Nothing -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall a b. (a -> b) -> a -> b
$ Text
"Semantic token type " forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall a. Show a => a -> String
show SemanticTokenTypes
ty) forall a. Semigroup a => a -> a -> a
<> Text
" did not appear in the legend"
lookupMod :: SemanticTokenModifiers -> Either Text Int
lookupMod :: SemanticTokenModifiers -> Either Text Int
lookupMod SemanticTokenModifiers
modifier = case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup SemanticTokenModifiers
modifier Map SemanticTokenModifiers Int
modMap of
Just Int
modcode -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
modcode
Maybe Int
Nothing -> forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError forall a b. (a -> b) -> a -> b
$ Text
"Semantic token modifier " forall a. Semigroup a => a -> a -> a
<> forall a. IsString a => String -> a
fromString (forall a. Show a => a -> String
show SemanticTokenModifiers
modifier) forall a. Semigroup a => a -> a -> a
<> Text
" did not appear in the legend"
encodeToken :: SemanticTokenRelative -> Either Text (DList.DList UInt)
encodeToken :: SemanticTokenRelative -> Either Text (DList UInt)
encodeToken (SemanticTokenRelative UInt
dl UInt
dc UInt
len SemanticTokenTypes
ty [SemanticTokenModifiers]
mods) = do
UInt
tycode <- SemanticTokenTypes -> Either Text UInt
lookupTy SemanticTokenTypes
ty
[Int]
modcodes <- forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse SemanticTokenModifiers -> Either Text Int
lookupMod [SemanticTokenModifiers]
mods
let Int
combinedModcode :: Int = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' forall a. Bits a => a -> Int -> a
Bits.setBit forall a. Bits a => a
Bits.zeroBits [Int]
modcodes
forall (f :: * -> *) a. Applicative f => a -> f a
pure [UInt
dl, UInt
dc, UInt
len, UInt
tycode, forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
combinedModcode ]
data Edit a = Edit { forall a. Edit a -> UInt
editStart :: UInt, forall a. Edit a -> UInt
editDeleteCount :: UInt, forall a. Edit a -> [a]
editInsertions :: [a] }
deriving (ReadPrec [Edit a]
ReadPrec (Edit a)
ReadS [Edit a]
forall a. Read a => ReadPrec [Edit a]
forall a. Read a => ReadPrec (Edit a)
forall a. Read a => Int -> ReadS (Edit a)
forall a. Read a => ReadS [Edit a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Edit a]
$creadListPrec :: forall a. Read a => ReadPrec [Edit a]
readPrec :: ReadPrec (Edit a)
$creadPrec :: forall a. Read a => ReadPrec (Edit a)
readList :: ReadS [Edit a]
$creadList :: forall a. Read a => ReadS [Edit a]
readsPrec :: Int -> ReadS (Edit a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Edit a)
Read, Int -> Edit a -> ShowS
forall a. Show a => Int -> Edit a -> ShowS
forall a. Show a => [Edit a] -> ShowS
forall a. Show a => Edit a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Edit a] -> ShowS
$cshowList :: forall a. Show a => [Edit a] -> ShowS
show :: Edit a -> String
$cshow :: forall a. Show a => Edit a -> String
showsPrec :: Int -> Edit a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Edit a -> ShowS
Show, Edit a -> Edit a -> Bool
forall a. Eq a => Edit a -> Edit a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Edit a -> Edit a -> Bool
$c/= :: forall a. Eq a => Edit a -> Edit a -> Bool
== :: Edit a -> Edit a -> Bool
$c== :: forall a. Eq a => Edit a -> Edit a -> Bool
Eq, Edit a -> Edit a -> Bool
Edit a -> Edit a -> Ordering
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
forall {a}. Ord a => Eq (Edit a)
forall a. Ord a => Edit a -> Edit a -> Bool
forall a. Ord a => Edit a -> Edit a -> Ordering
forall a. Ord a => Edit a -> Edit a -> Edit a
min :: Edit a -> Edit a -> Edit a
$cmin :: forall a. Ord a => Edit a -> Edit a -> Edit a
max :: Edit a -> Edit a -> Edit a
$cmax :: forall a. Ord a => Edit a -> Edit a -> Edit a
>= :: Edit a -> Edit a -> Bool
$c>= :: forall a. Ord a => Edit a -> Edit a -> Bool
> :: Edit a -> Edit a -> Bool
$c> :: forall a. Ord a => Edit a -> Edit a -> Bool
<= :: Edit a -> Edit a -> Bool
$c<= :: forall a. Ord a => Edit a -> Edit a -> Bool
< :: Edit a -> Edit a -> Bool
$c< :: forall a. Ord a => Edit a -> Edit a -> Bool
compare :: Edit a -> Edit a -> Ordering
$ccompare :: forall a. Ord a => Edit a -> Edit a -> Ordering
Ord)
computeEdits :: Eq a => [a] -> [a] -> [Edit a]
computeEdits :: forall a. Eq a => [a] -> [a] -> [Edit a]
computeEdits [a]
l [a]
r = forall a. DList a -> [a]
DList.toList forall a b. (a -> b) -> a -> b
$ forall a.
UInt
-> Maybe (Edit a) -> [Diff [a]] -> DList (Edit a) -> DList (Edit a)
go UInt
0 forall a. Maybe a
Nothing (forall a. Eq a => [a] -> [a] -> [Diff [a]]
Diff.getGroupedDiff [a]
l [a]
r) forall a. Monoid a => a
mempty
where
go :: UInt -> Maybe (Edit a) -> [Diff.Diff [a]] -> DList.DList (Edit a) -> DList.DList (Edit a)
go :: forall a.
UInt
-> Maybe (Edit a) -> [Diff [a]] -> DList (Edit a) -> DList (Edit a)
go UInt
_ Maybe (Edit a)
e [] DList (Edit a)
acc = DList (Edit a)
acc forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> DList a
DList.fromList (forall a. Maybe a -> [a]
maybeToList Maybe (Edit a)
e)
go UInt
ix Maybe (Edit a)
e (Diff.First [a]
ds : [Diff [a]]
rest) DList (Edit a)
acc =
let
deleteCount :: UInt
deleteCount = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length [a]
ds
edit :: Edit a
edit = forall a. a -> Maybe a -> a
fromMaybe (forall a. UInt -> UInt -> [a] -> Edit a
Edit UInt
ix UInt
0 []) Maybe (Edit a)
e
in forall a.
UInt
-> Maybe (Edit a) -> [Diff [a]] -> DList (Edit a) -> DList (Edit a)
go (UInt
ix forall a. Num a => a -> a -> a
+ UInt
deleteCount) (forall a. a -> Maybe a
Just (Edit a
edit{$sel:editDeleteCount:Edit :: UInt
editDeleteCount=forall a. Edit a -> UInt
editDeleteCount Edit a
edit forall a. Num a => a -> a -> a
+ UInt
deleteCount})) [Diff [a]]
rest DList (Edit a)
acc
go UInt
ix Maybe (Edit a)
e (Diff.Second [a]
as : [Diff [a]]
rest) DList (Edit a)
acc =
let edit :: Edit a
edit = forall a. a -> Maybe a -> a
fromMaybe (forall a. UInt -> UInt -> [a] -> Edit a
Edit UInt
ix UInt
0 []) Maybe (Edit a)
e
in forall a.
UInt
-> Maybe (Edit a) -> [Diff [a]] -> DList (Edit a) -> DList (Edit a)
go UInt
ix (forall a. a -> Maybe a
Just (Edit a
edit{$sel:editInsertions:Edit :: [a]
editInsertions=forall a. Edit a -> [a]
editInsertions Edit a
edit forall a. Semigroup a => a -> a -> a
<> [a]
as})) [Diff [a]]
rest DList (Edit a)
acc
go UInt
ix Maybe (Edit a)
e (Diff.Both [a]
bs [a]
_bs : [Diff [a]]
rest) DList (Edit a)
acc =
let bothCount :: UInt
bothCount = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => t a -> Int
Prelude.length [a]
bs
in forall a.
UInt
-> Maybe (Edit a) -> [Diff [a]] -> DList (Edit a) -> DList (Edit a)
go (UInt
ix forall a. Num a => a -> a -> a
+ UInt
bothCount) forall a. Maybe a
Nothing [Diff [a]]
rest (DList (Edit a)
acc forall a. Semigroup a => a -> a -> a
<> forall a. [a] -> DList a
DList.fromList (forall a. Maybe a -> [a]
maybeToList Maybe (Edit a)
e))
makeSemanticTokens :: SemanticTokensLegend -> [SemanticTokenAbsolute] -> Either Text SemanticTokens
makeSemanticTokens :: SemanticTokensLegend
-> [SemanticTokenAbsolute] -> Either Text SemanticTokens
makeSemanticTokens SemanticTokensLegend
legend [SemanticTokenAbsolute]
sts = do
[UInt]
encoded <- SemanticTokensLegend
-> [SemanticTokenRelative] -> Either Text [UInt]
encodeTokens SemanticTokensLegend
legend forall a b. (a -> b) -> a -> b
$ [SemanticTokenAbsolute] -> [SemanticTokenRelative]
relativizeTokens [SemanticTokenAbsolute]
sts
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Maybe Text -> List UInt -> SemanticTokens
SemanticTokens forall a. Maybe a
Nothing (forall a. [a] -> List a
List [UInt]
encoded)
makeSemanticTokensDelta :: SemanticTokens -> SemanticTokens -> SemanticTokensDelta
makeSemanticTokensDelta :: SemanticTokens -> SemanticTokens -> SemanticTokensDelta
makeSemanticTokensDelta SemanticTokens{$sel:_xdata:SemanticTokens :: SemanticTokens -> List UInt
_xdata=List [UInt]
prevTokens} SemanticTokens{$sel:_xdata:SemanticTokens :: SemanticTokens -> List UInt
_xdata=List [UInt]
curTokens} =
let edits :: [Edit UInt]
edits = forall a. Eq a => [a] -> [a] -> [Edit a]
computeEdits [UInt]
prevTokens [UInt]
curTokens
stEdits :: [SemanticTokensEdit]
stEdits = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(Edit UInt
s UInt
ds [UInt]
as) -> UInt -> UInt -> Maybe (List UInt) -> SemanticTokensEdit
SemanticTokensEdit UInt
s UInt
ds (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall a. [a] -> List a
List [UInt]
as)) [Edit UInt]
edits
in Maybe Text -> List SemanticTokensEdit -> SemanticTokensDelta
SemanticTokensDelta forall a. Maybe a
Nothing (forall a. [a] -> List a
List [SemanticTokensEdit]
stEdits)