diff --git a/flake.nix b/flake.nix index 1002eb87b5..b2373b7891 100644 --- a/flake.nix +++ b/flake.nix @@ -69,6 +69,7 @@ # Compiler toolchain hpkgs.ghc hpkgs.haskell-language-server + pkgs.stack pkgs.haskellPackages.cabal-install # Dependencies needed to build some parts of Hackage gmp zlib ncurses diff --git a/ghcide/src/Development/IDE/GHC/Compat/Core.hs b/ghcide/src/Development/IDE/GHC/Compat/Core.hs index 42f654b609..114e55d509 100644 --- a/ghcide/src/Development/IDE/GHC/Compat/Core.hs +++ b/ghcide/src/Development/IDE/GHC/Compat/Core.hs @@ -630,11 +630,53 @@ instance HasSrcSpan SrcSpan where instance HasSrcSpan (SrcLoc.GenLocated SrcSpan a) where getLoc = GHC.getLoc +#if MIN_VERSION_ghc(9,11,0) +instance HasSrcSpan (GHC.EpToken sym) where + getLoc = GHC.getHasLoc +instance HasSrcSpan (GHC.EpUniToken sym sym') where + getLoc = GHC.getHasLoc +#elif MIN_VERSION_ghc(9,9,0) +instance HasSrcSpan (GHC.EpToken sym) where + getLoc = GHC.getHasLoc . \case + GHC.NoEpTok -> Nothing + GHC.EpTok loc -> Just loc +instance HasSrcSpan (GHC.EpUniToken sym sym') where + getLoc = GHC.getHasLoc . \case + GHC.NoEpUniTok -> Nothing + GHC.EpUniTok loc _ -> Just loc +#endif + #if MIN_VERSION_ghc(9,9,0) instance HasSrcSpan (EpAnn a) where getLoc = GHC.getHasLoc #endif +#if !MIN_VERSION_ghc(9,11,0) +instance HasSrcSpan GHC.AddEpAnn where + getLoc (GHC.AddEpAnn _ loc) = getLoc loc + +instance HasSrcSpan GHC.EpaLocation where +#if MIN_VERSION_ghc(9,9,0) + getLoc loc = GHC.getHasLoc loc +#else + getLoc loc = case loc of + GHC.EpaSpan span bufspan -> RealSrcSpan span $ case bufspan of Strict.Nothing -> Nothing; Strict.Just a -> Just a + GHC.EpaDelta {} -> panic "compiler inserted epadelta in EpaLocation" +#endif +#endif + +instance HasSrcSpan GHC.LEpaComment where +#if MIN_VERSION_ghc(9,9,0) + getLoc :: GHC.LEpaComment -> SrcSpan + getLoc (GHC.L l _) = case l of + SrcLoc.EpaDelta {} -> panic "compiler inserted epadelta into NoCommentsLocation" + SrcLoc.EpaSpan span -> span +#else + getLoc :: GHC.LEpaComment -> SrcSpan + getLoc c = case c of + SrcLoc.L (GHC.Anchor realSpan _) _ -> RealSrcSpan realSpan Nothing +#endif + #if MIN_VERSION_ghc(9,9,0) instance HasSrcSpan (SrcLoc.GenLocated (EpAnn ann) a) where getLoc (L l _) = getLoc l diff --git a/haskell-language-server.cabal b/haskell-language-server.cabal index f4066dca94..5d1a5ea905 100644 --- a/haskell-language-server.cabal +++ b/haskell-language-server.cabal @@ -1729,6 +1729,7 @@ library hls-semantic-tokens-plugin , containers , extra , text-rope + , ghc , mtl >= 2.2 , ghcide == 2.11.0.0 , hls-plugin-api == 2.11.0.0 diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens.hs index 28e05f5e8c..6171c8ea33 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens.hs @@ -15,10 +15,10 @@ descriptor recorder plId = { Ide.Types.pluginHandlers = mkPluginHandler SMethod_TextDocumentSemanticTokensFull (Internal.semanticTokensFull recorder) <> mkPluginHandler SMethod_TextDocumentSemanticTokensFullDelta (Internal.semanticTokensFullDelta recorder), - Ide.Types.pluginRules = Internal.getSemanticTokensRule recorder, + Ide.Types.pluginRules = Internal.getSemanticTokensRule recorder <> Internal.getSyntacticTokensRule recorder, pluginConfigDescriptor = defaultConfigDescriptor - { configInitialGenericConfig = (configInitialGenericConfig defaultConfigDescriptor) {plcGlobalOn = False} + { configInitialGenericConfig = (configInitialGenericConfig defaultConfigDescriptor) {plcGlobalOn = True} , configCustomConfig = mkCustomConfig Internal.semanticConfigProperties } } diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Internal.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Internal.hs index b8b07e667f..716f8a5e10 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Internal.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Internal.hs @@ -1,16 +1,23 @@ -{-# LANGUAGE DataKinds #-} -{-# LANGUAGE DerivingStrategies #-} -{-# LANGUAGE OverloadedLabels #-} -{-# LANGUAGE OverloadedRecordDot #-} -{-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RecordWildCards #-} -{-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE UnicodeSyntax #-} +{-# LANGUAGE BlockArguments #-} +{-# LANGUAGE CPP #-} +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE DerivingStrategies #-} +{-# LANGUAGE ImpredicativeTypes #-} +{-# LANGUAGE LiberalTypeSynonyms #-} +{-# LANGUAGE MultiWayIf #-} +{-# LANGUAGE OverloadedLabels #-} +{-# LANGUAGE OverloadedRecordDot #-} +{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE PatternSynonyms #-} +{-# LANGUAGE QuantifiedConstraints #-} +{-# LANGUAGE RecordWildCards #-} +{-# LANGUAGE TemplateHaskell #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UnicodeSyntax #-} -- | -- This module provides the core functionality of the plugin. -module Ide.Plugin.SemanticTokens.Internal (semanticTokensFull, getSemanticTokensRule, semanticConfigProperties, semanticTokensFullDelta) where +module Ide.Plugin.SemanticTokens.Internal (semanticTokensFull, getSemanticTokensRule, getSyntacticTokensRule, semanticConfigProperties, semanticTokensFullDelta) where import Control.Concurrent.STM (stateTVar) import Control.Concurrent.STM.Stats (atomically) @@ -20,22 +27,29 @@ import Control.Monad.Except (ExceptT, liftEither, import Control.Monad.IO.Class (MonadIO (..)) import Control.Monad.Trans (lift) import Control.Monad.Trans.Except (runExceptT) +import Control.Monad.Trans.Maybe +import Data.Data (Data (..)) +import Data.List import qualified Data.Map.Strict as M +import Data.Maybe import Data.Text (Text) import qualified Data.Text as T import Development.IDE (Action, GetDocMap (GetDocMap), GetHieAst (GetHieAst), + GetParsedModuleWithComments (..), HieAstResult (HAR, hieAst, hieModule, refMap), IdeResult, IdeState, Priority (..), Recorder, Rules, WithPriority, cmapWithPrio, define, - fromNormalizedFilePath, - hieKind) + hieKind, + srcSpanToRange, + useWithStale) import Development.IDE.Core.PluginUtils (runActionE, useE, useWithStaleE) +import Development.IDE.Core.PositionMapping import Development.IDE.Core.Rules (toIdeResult) import Development.IDE.Core.RuleTypes (DocAndTyThingMap (..)) import Development.IDE.Core.Shake (ShakeExtras (..), @@ -43,8 +57,9 @@ import Development.IDE.Core.Shake (ShakeExtras (..), getVirtualFile) import Development.IDE.GHC.Compat hiding (Warning) import Development.IDE.GHC.Compat.Util (mkFastString) +import GHC.Parser.Annotation import Ide.Logger (logWith) -import Ide.Plugin.Error (PluginError (PluginInternalError), +import Ide.Plugin.Error (PluginError (PluginInternalError, PluginRuleFailed), getNormalizedFilePathE, handleMaybe, handleMaybeM) @@ -58,10 +73,17 @@ import qualified Language.LSP.Protocol.Lens as L import Language.LSP.Protocol.Message (MessageResult, Method (Method_TextDocumentSemanticTokensFull, Method_TextDocumentSemanticTokensFullDelta)) import Language.LSP.Protocol.Types (NormalizedFilePath, + Range, SemanticTokens, + fromNormalizedFilePath, type (|?) (InL, InR)) import Prelude hiding (span) import qualified StmContainers.Map as STM +import Type.Reflection (Typeable, eqTypeRep, + pattern App, + type (:~~:) (HRefl), + typeOf, typeRep, + withTypeable) $mkSemanticConfigFunctions @@ -75,8 +97,17 @@ computeSemanticTokens recorder pid _ nfp = do config <- lift $ useSemanticConfigAction pid logWith recorder Debug (LogConfig config) semanticId <- lift getAndIncreaseSemanticTokensId - (RangeHsSemanticTokenTypes {rangeSemanticList}, mapping) <- useWithStaleE GetSemanticTokens nfp - withExceptT PluginInternalError $ liftEither $ rangeSemanticsSemanticTokens semanticId config mapping rangeSemanticList + + tokenList <- sortOn fst <$> do + rangesyntacticTypes <- lift $ useWithStale GetSyntacticTokens nfp + rangesemanticTypes <- lift $ useWithStale GetSemanticTokens nfp + let mk w u (toks, mapping) = map (\(ran, tok) -> (toCurrentRange mapping ran, w tok)) $ u toks + maybeToExceptT (PluginRuleFailed "no syntactic nor semantic tokens") $ hoistMaybe $ + (mk HsSyntacticTokenType rangeSyntacticList <$> rangesyntacticTypes) + <> (mk HsSemanticTokenType rangeSemanticList <$> rangesemanticTypes) + + -- NOTE: rangeSemanticsSemanticTokens actually assumes that the tokesn are in order. that means they have to be sorted by position + withExceptT PluginInternalError $ liftEither $ rangeSemanticsSemanticTokens semanticId config tokenList semanticTokensFull :: Recorder (WithPriority SemanticLog) -> PluginMethodHandler IdeState 'Method_TextDocumentSemanticTokensFull semanticTokensFull recorder state pid param = runActionE "SemanticTokens.semanticTokensFull" state computeSemanticTokensFull @@ -130,6 +161,132 @@ getSemanticTokensRule recorder = let hsFinder = idSemantic getTyThingMap (hieKindFunMasksKind hieKind) refMap return $ computeRangeHsSemanticTokenTypeList hsFinder virtualFile ast +getSyntacticTokensRule :: Recorder (WithPriority SemanticLog) -> Rules () +getSyntacticTokensRule recorder = + define (cmapWithPrio LogShake recorder) $ \GetSyntacticTokens nfp -> handleError recorder $ do + (parsedModule, _) <- withExceptT LogDependencyError $ useWithStaleE GetParsedModuleWithComments nfp + pure $ computeRangeHsSyntacticTokenTypeList parsedModule + +astTraversalWith :: forall b r. Data b => b -> (forall a. Data a => a -> [r]) -> [r] +astTraversalWith ast f = mconcat $ flip gmapQ ast \y -> f y <> astTraversalWith y f + +{-# inline extractTyToTyToTy #-} +extractTyToTyToTy :: forall f a. (Typeable f, Data a) => a -> Maybe (forall r. (forall b c. (Typeable b, Typeable c) => f b c -> r) -> r) +extractTyToTyToTy node + | App (App conRep argRep1) argRep2 <- typeOf node + , Just HRefl <- eqTypeRep conRep (typeRep @f) + = Just $ withTypeable argRep1 $ withTypeable argRep2 \k -> k node + | otherwise = Nothing + +{-# inline extractTyToTy #-} +extractTyToTy :: forall f a. (Typeable f, Data a) => a -> Maybe (forall r. (forall b. Typeable b => f b -> r) -> r) +extractTyToTy node + | App conRep argRep <- typeOf node + , Just HRefl <- eqTypeRep conRep (typeRep @f) + = Just $ withTypeable argRep \k -> k node + | otherwise = Nothing + +{-# inline extractTy #-} +extractTy :: forall b a. (Typeable b, Data a) => a -> Maybe b +extractTy node + | Just HRefl <- eqTypeRep (typeRep @b) (typeOf node) + = Just node + | otherwise = Nothing + +computeRangeHsSyntacticTokenTypeList :: ParsedModule -> RangeHsSyntacticTokenTypes +computeRangeHsSyntacticTokenTypeList ParsedModule {pm_parsed_source} = + let toks = astTraversalWith pm_parsed_source \node -> mconcat + [ +#if MIN_VERSION_ghc(9,9,0) + maybeToList $ mkFromLocatable TKeyword . (\k -> k \x k' -> k' x) =<< extractTyToTy @EpToken node, + maybeToList $ mkFromLocatable TKeyword . (\k -> k \x k' -> k' x) =<< extractTyToTyToTy @EpUniToken node, + do + AnnContext {ac_darrow, ac_open, ac_close} <- maybeToList $ extractTy node + let mkFromTok :: (Foldable f, HasSrcSpan a) => f a -> [(Range,HsSyntacticTokenType)] + mkFromTok = foldMap (\tok -> maybeToList $ mkFromLocatable TKeyword \k -> k tok) + mconcat +#if MIN_VERSION_ghc(9,11,0) + [ mkFromTok ac_darrow +#else + [ foldMap (\(_, loc) -> maybeToList $ mkFromLocatable TKeyword \k -> k loc) ac_darrow +#endif + , mkFromTok ac_open + , mkFromTok ac_close + ], +#endif + +#if !MIN_VERSION_ghc(9,11,0) + maybeToList $ mkFromLocatable TKeyword . (\x k -> k x) =<< extractTy @AddEpAnn node, + do + EpAnnImportDecl i p s q pkg a <- maybeToList $ extractTy @EpAnnImportDecl node + mapMaybe (mkFromLocatable TKeyword . (\x k -> k x)) $ catMaybes $ [Just i, s, q, pkg, a] <> foldMap (\(l, l') -> [Just l, Just l']) p, +#endif + maybeToList do + comment <- extractTy @LEpaComment node +#if !MIN_VERSION_ghc(9,7,0) + -- NOTE: on ghc 9.6 there's an empty comment that is supposed to + -- located the end of file + case comment of + L _ (EpaComment {ac_tok = EpaEofComment}) -> Nothing + _ -> pure () +#endif + mkFromLocatable TComment \k -> k comment, + do + L loc expr <- maybeToList $ extractTy @(LHsExpr GhcPs) node + let fromSimple = maybeToList . flip mkFromLocatable \k -> k loc + case expr of + HsOverLabel {} -> fromSimple TStringLit + HsOverLit _ (OverLit _ lit) -> fromSimple case lit of + HsIntegral {} -> TNumberLit + HsFractional {} -> TNumberLit + + HsIsString {} -> TStringLit + HsLit _ lit -> fromSimple case lit of + -- NOTE: unfortunately, lsp semantic tokens doesn't have a notion of char literals + HsChar {} -> TStringLit + HsCharPrim {} -> TStringLit + + HsInt {} -> TNumberLit + HsInteger {} -> TNumberLit + HsIntPrim {} -> TNumberLit + HsWordPrim {} -> TNumberLit +#if MIN_VERSION_ghc(9,9,0) + HsWord8Prim {} -> TNumberLit + HsWord16Prim {} -> TNumberLit + HsWord32Prim {} -> TNumberLit +#endif + HsWord64Prim {} -> TNumberLit +#if MIN_VERSION_ghc(9,9,0) + HsInt8Prim {} -> TNumberLit + HsInt16Prim {} -> TNumberLit + HsInt32Prim {} -> TNumberLit +#endif + HsInt64Prim {} -> TNumberLit + HsFloatPrim {} -> TNumberLit + HsDoublePrim {} -> TNumberLit + HsRat {} -> TNumberLit + + HsString {} -> TStringLit + HsStringPrim {} -> TStringLit +#if MIN_VERSION_ghc(9,11,0) + HsMultilineString {} -> TStringLit +#endif + HsGetField _ _ field -> maybeToList $ mkFromLocatable TRecordSelector \k -> k field +#if MIN_VERSION_ghc(9,11,0) + HsProjection _ projs -> foldMap (\dotFieldOcc -> maybeToList $ mkFromLocatable TRecordSelector \k -> k dotFieldOcc.dfoLabel) projs +#else + HsProjection _ projs -> foldMap (\proj -> maybeToList $ mkFromLocatable TRecordSelector \k -> k proj) projs +#endif + _ -> [] + ] + in RangeHsSyntacticTokenTypes toks + +{-# inline mkFromLocatable #-} +mkFromLocatable + :: HsSyntacticTokenType + -> (forall r. (forall a. HasSrcSpan a => a -> r) -> r) + -> Maybe (Range, HsSyntacticTokenType) +mkFromLocatable tt w = w \tok -> let mrange = srcSpanToRange $ getLoc tok in fmap (, tt) mrange -- taken from /haskell-language-server/plugins/hls-code-range-plugin/src/Ide/Plugin/CodeRange/Rules.hs diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Mappings.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Mappings.hs index d9bfc4449d..d5716597c4 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Mappings.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Mappings.hs @@ -12,23 +12,26 @@ -- 4. Mapping from LSP tokens to SemanticTokenOriginal. module Ide.Plugin.SemanticTokens.Mappings where -import qualified Data.Array as A -import Data.List.Extra (chunksOf, (!?)) -import qualified Data.Map.Strict as Map -import Data.Maybe (mapMaybe) -import qualified Data.Set as Set -import Data.Text (Text, unpack) -import Development.IDE (HieKind (HieFresh, HieFromDisk)) +import qualified Data.Array as A +import Data.Function +import Data.List.Extra (chunksOf, (!?)) +import qualified Data.Map.Strict as Map +import Data.Maybe (mapMaybe) +import qualified Data.Set as Set +import Data.Text (Text, unpack) +import Development.IDE (HieKind (HieFresh, HieFromDisk)) import Development.IDE.GHC.Compat +import Ide.Plugin.SemanticTokens.SemanticConfig (allHsTokenTypes) import Ide.Plugin.SemanticTokens.Types -import Ide.Plugin.SemanticTokens.Utils (mkRange) -import Language.LSP.Protocol.Types (LspEnum (knownValues), - SemanticTokenAbsolute (SemanticTokenAbsolute), - SemanticTokenRelative (SemanticTokenRelative), - SemanticTokenTypes (..), - SemanticTokens (SemanticTokens), - UInt, absolutizeTokens) -import Language.LSP.VFS hiding (line) +import Ide.Plugin.SemanticTokens.Utils (mkRange) +import Language.LSP.Protocol.Types (LspEnum (knownValues), + SemanticTokenAbsolute (SemanticTokenAbsolute), + SemanticTokenRelative (SemanticTokenRelative), + SemanticTokenTypes (..), + SemanticTokens (SemanticTokens), + UInt, + absolutizeTokens) +import Language.LSP.VFS hiding (line) -- * 0. Mapping name to Hs semantic token type. @@ -39,31 +42,34 @@ nameInfixOperator _ = Nothing -- * 1. Mapping semantic token type to and from the LSP default token type. -- | map from haskell semantic token type to LSP default token type -toLspTokenType :: SemanticTokensConfig -> HsSemanticTokenType -> SemanticTokenTypes -toLspTokenType conf tk = case tk of - TFunction -> stFunction conf - TVariable -> stVariable conf - TClassMethod -> stClassMethod conf - TTypeVariable -> stTypeVariable conf - TDataConstructor -> stDataConstructor conf - TClass -> stClass conf - TTypeConstructor -> stTypeConstructor conf - TTypeSynonym -> stTypeSynonym conf - TTypeFamily -> stTypeFamily conf - TRecordField -> stRecordField conf - TPatternSynonym -> stPatternSynonym conf - TModule -> stModule conf - TOperator -> stOperator conf - -lspTokenReverseMap :: SemanticTokensConfig -> Map.Map SemanticTokenTypes HsSemanticTokenType -lspTokenReverseMap config - | length xs /= Map.size mr = error "lspTokenReverseMap: token type mapping is not bijection" - | otherwise = mr - where xs = enumFrom minBound - mr = Map.fromList $ map (\x -> (toLspTokenType config x, x)) xs - -lspTokenTypeHsTokenType :: SemanticTokensConfig -> SemanticTokenTypes -> Maybe HsSemanticTokenType -lspTokenTypeHsTokenType cf tk = Map.lookup tk (lspTokenReverseMap cf) +toLspTokenType :: SemanticTokensConfig -> HsTokenType -> SemanticTokenTypes +toLspTokenType conf tk = conf & case tk of + HsSemanticTokenType TFunction -> stFunction + HsSemanticTokenType TVariable -> stVariable + HsSemanticTokenType TClassMethod -> stClassMethod + HsSemanticTokenType TTypeVariable -> stTypeVariable + HsSemanticTokenType TDataConstructor -> stDataConstructor + HsSemanticTokenType TClass -> stClass + HsSemanticTokenType TTypeConstructor -> stTypeConstructor + HsSemanticTokenType TTypeSynonym -> stTypeSynonym + HsSemanticTokenType TTypeFamily -> stTypeFamily + HsSemanticTokenType TRecordField -> stRecordField + HsSemanticTokenType TPatternSynonym -> stPatternSynonym + HsSemanticTokenType TModule -> stModule + HsSemanticTokenType TOperator -> stOperator + HsSyntacticTokenType TKeyword -> stKeyword + HsSyntacticTokenType TComment -> stComment + HsSyntacticTokenType TStringLit -> stStringLit + HsSyntacticTokenType TNumberLit -> stNumberLit + HsSyntacticTokenType TRecordSelector -> stRecordSelector + +lspTokenReverseMap :: SemanticTokensConfig -> Map.Map SemanticTokenTypes [HsTokenType] +lspTokenReverseMap config = mr + where xs = allHsTokenTypes + mr = Map.fromListWith (<>) $ map (\x -> (toLspTokenType config x, [x])) xs + +lspTokenTypeHsTokenType :: SemanticTokensConfig -> SemanticTokenTypes -> [HsTokenType] +lspTokenTypeHsTokenType cf tk = Map.findWithDefault [] tk (lspTokenReverseMap cf) -- * 2. Mapping from GHC type and tyThing to semantic token type. @@ -179,20 +185,20 @@ infoTokenType x = case x of -- this function is used to recover the original tokens(with token in haskell token type zoon) -- from the lsp semantic tokens(with token in lsp token type zoon) -- the `SemanticTokensConfig` used should be a map with bijection property -recoverSemanticTokens :: SemanticTokensConfig -> VirtualFile -> SemanticTokens -> Either Text [SemanticTokenOriginal HsSemanticTokenType] +recoverSemanticTokens :: SemanticTokensConfig -> VirtualFile -> SemanticTokens -> Either Text [SemanticTokenOriginal HsTokenType] recoverSemanticTokens config v s = do tks <- recoverLspSemanticTokens v s - return $ map (lspTokenHsToken config) tks + return $ foldMap (lspTokenHsToken config) tks -- | lspTokenHsToken -- for debug and test. -- use the `SemanticTokensConfig` to convert lsp token type to haskell token type -- the `SemanticTokensConfig` used should be a map with bijection property -lspTokenHsToken :: SemanticTokensConfig -> SemanticTokenOriginal SemanticTokenTypes -> SemanticTokenOriginal HsSemanticTokenType +lspTokenHsToken :: SemanticTokensConfig -> SemanticTokenOriginal SemanticTokenTypes -> [SemanticTokenOriginal HsTokenType] lspTokenHsToken config (SemanticTokenOriginal tokenType location name) = case lspTokenTypeHsTokenType config tokenType of - Just t -> SemanticTokenOriginal t location name - Nothing -> error "recoverSemanticTokens: unknown lsp token type" + [] -> error "recoverSemanticTokens: unknown lsp token type" + ts -> map (\t -> SemanticTokenOriginal t location name) ts -- | recoverLspSemanticTokens -- for debug and test. diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Query.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Query.hs index fb7fdd9e71..f4a8fe8d2d 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Query.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Query.hs @@ -14,6 +14,7 @@ import Development.IDE.GHC.Compat import Ide.Plugin.SemanticTokens.Mappings import Ide.Plugin.SemanticTokens.Types (HieFunMaskKind, HsSemanticTokenType (TModule), + HsTokenType, RangeSemanticTokenTypeList, SemanticTokenId, SemanticTokensConfig) @@ -66,11 +67,11 @@ nameSemanticFromHie hieKind rm n = idSemanticFromRefMap rm (Right n) ------------------------------------------------- -rangeSemanticsSemanticTokens :: SemanticTokenId -> SemanticTokensConfig -> PositionMapping -> RangeSemanticTokenTypeList -> Either Text SemanticTokens -rangeSemanticsSemanticTokens sid stc mapping = - makeSemanticTokensWithId (Just sid) . mapMaybe (\(ran, tk) -> toAbsSemanticToken <$> toCurrentRange mapping ran <*> return tk) +rangeSemanticsSemanticTokens :: SemanticTokenId -> SemanticTokensConfig -> [(Maybe Range, HsTokenType)] -> Either Text SemanticTokens +rangeSemanticsSemanticTokens sid stc = + makeSemanticTokensWithId (Just sid) . mapMaybe (\(ran, tk) -> toAbsSemanticToken <$> ran <*> return tk) where - toAbsSemanticToken :: Range -> HsSemanticTokenType -> SemanticTokenAbsolute + toAbsSemanticToken :: Range -> HsTokenType -> SemanticTokenAbsolute toAbsSemanticToken (Range (Position startLine startColumn) (Position _endLine endColumn)) tokenType = let len = endColumn - startColumn in SemanticTokenAbsolute diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/SemanticConfig.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/SemanticConfig.hs index e9e8034ce3..548d0f3bd6 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/SemanticConfig.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/SemanticConfig.hs @@ -26,21 +26,26 @@ import Language.Haskell.TH import Language.LSP.Protocol.Types (LspEnum (..), SemanticTokenTypes) -docName :: HsSemanticTokenType -> T.Text +docName :: HsTokenType -> T.Text docName tt = case tt of - TVariable -> "variables" - TFunction -> "functions" - TDataConstructor -> "data constructors" - TTypeVariable -> "type variables" - TClassMethod -> "typeclass methods" - TPatternSynonym -> "pattern synonyms" - TTypeConstructor -> "type constructors" - TClass -> "typeclasses" - TTypeSynonym -> "type synonyms" - TTypeFamily -> "type families" - TRecordField -> "record fields" - TModule -> "modules" - TOperator -> "operators" + HsSemanticTokenType TVariable -> "variables" + HsSemanticTokenType TFunction -> "functions" + HsSemanticTokenType TDataConstructor -> "data constructors" + HsSemanticTokenType TTypeVariable -> "type variables" + HsSemanticTokenType TClassMethod -> "typeclass methods" + HsSemanticTokenType TPatternSynonym -> "pattern synonyms" + HsSemanticTokenType TTypeConstructor -> "type constructors" + HsSemanticTokenType TClass -> "typeclasses" + HsSemanticTokenType TTypeSynonym -> "type synonyms" + HsSemanticTokenType TTypeFamily -> "type families" + HsSemanticTokenType TRecordField -> "record fields" + HsSemanticTokenType TModule -> "modules" + HsSemanticTokenType TOperator -> "operators" + HsSyntacticTokenType TKeyword -> "keyword" + HsSyntacticTokenType TStringLit -> "string literal" + HsSyntacticTokenType TComment -> "comment" + HsSyntacticTokenType TNumberLit -> "number literal" + HsSyntacticTokenType TRecordSelector -> "record selector" toConfigName :: String -> String toConfigName = ("st" <>) @@ -55,15 +60,21 @@ lspTokenTypeDescriptions = ) $ S.toList knownValues -allHsTokenTypes :: [HsSemanticTokenType] -allHsTokenTypes = enumFrom minBound +allHsTokenTypes :: [HsTokenType] +allHsTokenTypes = map HsSemanticTokenType (enumFrom minBound) <> map HsSyntacticTokenType (enumFrom minBound) lowerFirst :: String -> String lowerFirst [] = [] lowerFirst (x : xs) = toLower x : xs +-- TODO: drop the "syntax/semanticness" before showing allHsTokenNameStrings :: [String] -allHsTokenNameStrings = map (drop 1 . show) allHsTokenTypes +allHsTokenNameStrings = map (unwrap $ drop 1 . show) allHsTokenTypes + where + unwrap :: (forall a. Show a => a -> String) -> HsTokenType -> String + unwrap k tt' = case tt' of + HsSemanticTokenType tt -> k tt + HsSyntacticTokenType tt -> k tt defineSemanticProperty :: (NotElem s r, KnownSymbol s) => diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Tokenize.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Tokenize.hs index 2ed11be333..398cc8d90d 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Tokenize.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Tokenize.hs @@ -3,11 +3,10 @@ module Ide.Plugin.SemanticTokens.Tokenize (computeRangeHsSemanticTokenTypeList) where -import Control.Lens (Identity (runIdentity)) import Control.Monad (foldM, guard) import Control.Monad.State.Strict (MonadState (get), - MonadTrans (lift), - evalStateT, modify, put) + MonadTrans (lift), evalState, + modify, put) import Control.Monad.Trans.State.Strict (StateT, runStateT) import Data.Char (isAlphaNum) import Data.DList (DList) @@ -72,7 +71,7 @@ foldMapM f ta = foldM (\b a -> mappend b <$> f a) mempty ta computeRangeHsSemanticTokenTypeList :: HsSemanticLookup -> VirtualFile -> HieAST a -> RangeHsSemanticTokenTypes computeRangeHsSemanticTokenTypeList lookupHsTokenType vf ast = - RangeHsSemanticTokenTypes $ DL.toList $ runIdentity $ evalStateT (foldAst lookupHsTokenType ast) (mkPTokenState vf) + RangeHsSemanticTokenTypes $ DL.toList $ evalState (foldAst lookupHsTokenType ast) (mkPTokenState vf) -- | foldAst -- visit every leaf node in the ast in depth first order foldAst :: (Monad m) => HsSemanticLookup -> HieAST t -> Tokenizer m (DList (Range, HsSemanticTokenType)) diff --git a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Types.hs b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Types.hs index 7f445bf7ac..6524666155 100644 --- a/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Types.hs +++ b/plugins/hls-semantic-tokens-plugin/src/Ide/Plugin/SemanticTokens/Types.hs @@ -1,4 +1,5 @@ {-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} @@ -39,12 +40,31 @@ data HsSemanticTokenType | TRecordField -- from match bind | TOperator-- operator | TModule -- module name - deriving (Eq, Ord, Show, Enum, Bounded, Generic, Lift) + deriving stock (Eq, Ord, Show, Enum, Bounded, Generic, Lift) + +data HsSyntacticTokenType + = TKeyword + | TComment + | TStringLit + | TNumberLit + | TRecordSelector + deriving stock (Eq, Ord, Show, Enum, Bounded, Generic, Lift) + +data HsTokenType + = HsSyntacticTokenType HsSyntacticTokenType + | HsSemanticTokenType HsSemanticTokenType + deriving stock (Eq, Ord, Show, Generic, Lift) -- type SemanticTokensConfig = SemanticTokensConfig_ Identity instance Default SemanticTokensConfig where def = STC - { stFunction = SemanticTokenTypes_Function + { stKeyword = SemanticTokenTypes_Keyword + , stRecordSelector = SemanticTokenTypes_Property + , stComment = SemanticTokenTypes_Comment + , stStringLit = SemanticTokenTypes_String + , stNumberLit = SemanticTokenTypes_Number + , stCharLit = SemanticTokenTypes_String + , stFunction = SemanticTokenTypes_Function , stVariable = SemanticTokenTypes_Variable , stDataConstructor = SemanticTokenTypes_EnumMember , stTypeVariable = SemanticTokenTypes_TypeParameter @@ -65,7 +85,13 @@ instance Default SemanticTokensConfig where -- | SemanticTokensConfig_ is a configuration for the semantic tokens plugin. -- it contains map between the hs semantic token type and default token type. data SemanticTokensConfig = STC - { stFunction :: !SemanticTokenTypes + { stStringLit :: !SemanticTokenTypes + , stCharLit :: !SemanticTokenTypes + , stNumberLit :: !SemanticTokenTypes + , stComment :: !SemanticTokenTypes + , stKeyword :: !SemanticTokenTypes + , stRecordSelector :: !SemanticTokenTypes + , stFunction :: !SemanticTokenTypes , stVariable :: !SemanticTokenTypes , stDataConstructor :: !SemanticTokenTypes , stTypeVariable :: !SemanticTokenTypes @@ -113,6 +139,18 @@ instance Hashable GetSemanticTokens instance NFData GetSemanticTokens +data GetSyntacticTokens = GetSyntacticTokens + deriving stock (Eq, Show, Generic) + deriving anyclass (Hashable, NFData) + +newtype RangeHsSyntacticTokenTypes = RangeHsSyntacticTokenTypes {rangeSyntacticList :: [(Range, HsSyntacticTokenType)]} +instance NFData RangeHsSyntacticTokenTypes where rnf = rwhnf + +instance Show RangeHsSyntacticTokenTypes where + show = unlines . map (\(r, tk) -> showRange r <> " " <> show tk) . rangeSyntacticList + +type instance RuleResult GetSyntacticTokens = RangeHsSyntacticTokenTypes + type RangeSemanticTokenTypeList = [(Range, HsSemanticTokenType)] newtype RangeHsSemanticTokenTypes = RangeHsSemanticTokenTypes {rangeSemanticList :: RangeSemanticTokenTypeList} @@ -156,5 +194,4 @@ instance Pretty SemanticLog where <> " previousIdFromCache: " <> pretty previousIdFromCache LogDependencyError err -> "SemanticTokens' dependency error: " <> pretty err - type SemanticTokenId = Text diff --git a/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs b/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs index a0d1648fb3..08613fbe91 100644 --- a/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs +++ b/plugins/hls-semantic-tokens-plugin/test/SemanticTokensTest.hs @@ -162,8 +162,12 @@ semanticTokensConfigTest = void waitForBuildQueue result1 <- docLspSemanticTokensString doc liftIO $ unlines (map show result1) @?= - T.unlines (["1:8-13 SemanticTokenTypes_Namespace \"Hello\"" | compilerVersion >= Version [9, 10] []] - ++ ["2:1-3 SemanticTokenTypes_Variable \"go\""]) + T.unlines ( [ "1:1-7 SemanticTokenTypes_Keyword \"module\"" ] + ++ ["1:8-13 SemanticTokenTypes_Namespace \"Hello\"" | compilerVersion >= Version [9, 10] []] + ++ [ "1:14-19 SemanticTokenTypes_Keyword \"where\"" + , "2:1-3 SemanticTokenTypes_Variable \"go\"" + , "2:6-7 SemanticTokenTypes_Keyword \"=\"" + , "2:8-9 SemanticTokenTypes_Number \"1\"" ]) ] @@ -182,8 +186,8 @@ semanticTokensFullDeltaTests = testCase "add tokens" $ do let file1 = "TModuleA.hs" let expectDelta - | compilerVersion >= Version [9, 10] [] = InR (InL (SemanticTokensDelta (Just "1") [SemanticTokensEdit 25 0 (Just [2, 0, 3, 8, 0])])) - | otherwise = InR (InL (SemanticTokensDelta (Just "1") [SemanticTokensEdit 20 0 (Just [2, 0, 3, 8, 0])])) + | compilerVersion >= Version [9, 10] [] = InR (InL (SemanticTokensDelta (Just "1") [SemanticTokensEdit {_start = 60, _deleteCount = 0, _data_ = Just [2,0,3,8,0,0,4,1,15,0,0,2,1,19,0]}])) + | otherwise = InR (InL (SemanticTokensDelta {_resultId = Just "1", _edits = [SemanticTokensEdit {_start = 55, _deleteCount = 0, _data_ = Just [2,0,3,8,0,0,4,1,15,0,0,2,1,19,0]}]})) -- r c l t m -- where r = row, c = column, l = length, t = token, m = modifier Test.Hls.runSessionWithServerInTmpDir def semanticTokensPlugin (mkFs $ FS.directProjectMulti [file1]) $ do @@ -203,8 +207,8 @@ semanticTokensFullDeltaTests = testCase "remove tokens" $ do let file1 = "TModuleA.hs" let expectDelta - | compilerVersion >= Version [9, 10] [] = InR (InL (SemanticTokensDelta (Just "1") [SemanticTokensEdit 5 20 (Just [])])) - | otherwise = InR (InL (SemanticTokensDelta (Just "1") [SemanticTokensEdit 0 20 (Just [])])) + | compilerVersion >= Version [9, 10] [] = InR (InL (SemanticTokensDelta {_resultId = Just "1", _edits = [SemanticTokensEdit {_start = 21, _deleteCount = 12, _data_ = Just []},SemanticTokensEdit {_start = 34, _deleteCount = 3, _data_ = Just []},SemanticTokensEdit {_start = 41, _deleteCount = 0, _data_ = Just [7]},SemanticTokensEdit {_start = 42, _deleteCount = 2, _data_ = Just [15]},SemanticTokensEdit {_start = 46, _deleteCount = 1, _data_ = Just [5]},SemanticTokensEdit {_start = 51, _deleteCount = 6, _data_ = Just [6]}]})) + | otherwise = InR (InL (SemanticTokensDelta {_resultId = Just "1", _edits = [SemanticTokensEdit {_start = 16, _deleteCount = 12, _data_ = Just []},SemanticTokensEdit {_start = 29, _deleteCount = 3, _data_ = Just []},SemanticTokensEdit {_start = 36, _deleteCount = 0, _data_ = Just [7]},SemanticTokensEdit {_start = 37, _deleteCount = 2, _data_ = Just [15]},SemanticTokensEdit {_start = 41, _deleteCount = 1, _data_ = Just [5]},SemanticTokensEdit {_start = 46, _deleteCount = 6, _data_ = Just [6]}]})) -- delete all tokens Test.Hls.runSessionWithServerInTmpDir def semanticTokensPlugin (mkFs $ FS.directProjectMulti [file1]) $ do doc1 <- openDoc file1 "haskell" @@ -244,19 +248,26 @@ semanticTokensTests = let expect = unlines ( + [ "[1:1-7 HsSyntacticTokenType TKeyword \"module\"]" ] -- > 9.10 have module name in the token - (["1:8-16 TModule \"TModuleB\"" | compilerVersion >= Version [9, 10] []]) - ++ - [ - "3:8-16 TModule \"TModuleA\"", - "4:18-26 TModule \"TModuleA\"", - "6:1-3 TVariable \"go\"", - "6:6-10 TDataConstructor \"Game\"", - "8:1-5 TVariable \"a\\66560bb\"", - "8:8-17 TModule \"TModuleA.\"", - "8:17-20 TRecordField \"a\\66560b\"", - "8:21-23 TVariable \"go\"" - ]) + ++ ["[1:8-16 HsSemanticTokenType TModule \"TModuleB\"]" | compilerVersion >= Version [9, 10] []] + ++ [ "[1:17-22 HsSyntacticTokenType TKeyword \"where\"]" + , "[3:1-7 HsSyntacticTokenType TKeyword \"import\"]" + , "[3:8-16 HsSemanticTokenType TModule \"TModuleA\"]" + , "[4:1-7 HsSyntacticTokenType TKeyword \"import\"]" + , "[4:8-17 HsSyntacticTokenType TKeyword \"qualified\"]" + , "[4:18-26 HsSemanticTokenType TModule \"TModuleA\"]" + , "[6:1-3 HsSemanticTokenType TVariable \"go\"]" + , "[6:4-5 HsSyntacticTokenType TKeyword \"=\"]" + , "[6:6-10 HsSemanticTokenType TDataConstructor \"Game\"]" + , "[6:11-12 HsSyntacticTokenType TNumberLit \"1\"]" + , "[8:1-5 HsSemanticTokenType TVariable \"a\\66560bb\"]" + , "[8:5-6 HsSyntacticTokenType TKeyword \" \"]" + , "[8:8-17 HsSemanticTokenType TModule \"TModuleA.\"]" + , "[8:17-20 HsSyntacticTokenType TRecordSelector \"a\\66560b\",8:17-20 HsSemanticTokenType TRecordField \"a\\66560b\"]" + , "[8:21-23 HsSemanticTokenType TVariable \"go\"]" + ] + ) liftIO $ result @?= expect, goldenWithSemanticTokensWithDefaultConfig "mixed constancy test result generated from one ghc version" "T1", goldenWithSemanticTokensWithDefaultConfig "pattern bind" "TPatternSynonym", diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/T1.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/T1.expected index eff5c79768..991dd03174 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/T1.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/T1.expected @@ -1,82 +1,168 @@ -4:8-12 TModule "Main" -9:6-9 TTypeConstructor "Foo" -9:12-15 TDataConstructor "Foo" -9:18-21 TRecordField "foo" -9:25-28 TTypeConstructor "Int" -11:7-10 TClass "Boo" -11:11-12 TTypeVariable "a" -12:3-6 TClassMethod "boo" -12:10-11 TTypeVariable "a" -12:15-16 TTypeVariable "a" -14:10-13 TClass "Boo" -14:14-17 TTypeConstructor "Int" -15:5-8 TClassMethod "boo" -15:9-10 TVariable "x" -15:13-14 TVariable "x" -15:15-16 TOperator "+" -17:6-8 TTypeConstructor "Dd" -17:11-13 TDataConstructor "Dd" -17:14-17 TTypeConstructor "Int" -19:9-12 TPatternSynonym "One" -19:15-18 TDataConstructor "Foo" -21:1-4 TVariable "ggg" -21:7-10 TPatternSynonym "One" -23:6-9 TTypeConstructor "Doo" -23:12-15 TDataConstructor "Doo" -23:16-24 TModule "Prelude." -23:24-27 TTypeConstructor "Int" -24:6-10 TTypeSynonym "Bar1" -24:13-16 TTypeConstructor "Int" -25:6-10 TTypeSynonym "Bar2" -25:13-16 TTypeConstructor "Doo" -27:1-3 TFunction "bb" -27:8-11 TClass "Boo" -27:12-13 TTypeVariable "a" -27:18-19 TTypeVariable "a" -27:23-24 TTypeVariable "a" -28:1-3 TFunction "bb" -28:4-5 TVariable "x" -28:9-12 TClassMethod "boo" -28:13-14 TVariable "x" -29:1-3 TFunction "aa" -29:7-11 TTypeVariable "cool" -29:15-18 TTypeConstructor "Int" -29:22-26 TTypeVariable "cool" -30:1-3 TFunction "aa" -30:4-5 TVariable "x" -30:9-10 TVariable "c" -30:14-16 TFunction "aa" -30:17-18 TVariable "x" -30:19-20 TVariable "c" -31:12-14 TVariable "xx" -31:16-18 TVariable "yy" -32:11-13 TVariable "dd" -34:2-4 TVariable "zz" -34:6-8 TVariable "kk" -35:1-3 TFunction "cc" -35:7-10 TTypeConstructor "Foo" -35:15-18 TTypeConstructor "Int" -35:20-23 TTypeConstructor "Int" -35:28-31 TTypeConstructor "Int" -36:1-3 TFunction "cc" -36:4-5 TVariable "f" -36:7-9 TVariable "gg" -36:11-13 TVariable "vv" -37:10-12 TVariable "gg" -38:14-17 TRecordField "foo" -38:18-19 TOperator "$" -38:20-21 TVariable "f" -38:24-27 TRecordField "foo" -39:14-17 TRecordField "foo" -39:18-19 TOperator "$" -39:20-21 TVariable "f" -39:24-27 TRecordField "foo" -41:1-3 TFunction "go" -41:6-9 TRecordField "foo" -42:1-4 TFunction "add" -42:8-16 TModule "Prelude." -42:16-17 TOperator "+" -47:1-5 TVariable "main" -47:9-11 TTypeConstructor "IO" -48:1-5 TVariable "main" -48:8-16 TFunction "putStrLn" +[1:1-14 HsSyntacticTokenType TComment "-- patter syn"] +[2:1-33 HsSyntacticTokenType TComment "{-# LANGUAGE PatternSynonyms #-}"] +[4:1-7 HsSyntacticTokenType TKeyword "module"] +[4:8-12 HsSemanticTokenType TModule "Main"] +[4:13-18 HsSyntacticTokenType TKeyword "where"] +[6:1-33 HsSyntacticTokenType TComment "-- import Data.Set (Set, insert)"] +[9:1-5 HsSyntacticTokenType TKeyword "data"] +[9:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[9:10-11 HsSyntacticTokenType TKeyword "="] +[9:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[9:16-17 HsSyntacticTokenType TKeyword "{"] +[9:18-21 HsSyntacticTokenType TRecordSelector "foo",9:18-21 HsSemanticTokenType TRecordField "foo"] +[9:22-24 HsSyntacticTokenType TKeyword "::"] +[9:25-28 HsSemanticTokenType TTypeConstructor "Int"] +[9:29-30 HsSyntacticTokenType TKeyword "}"] +[11:1-6 HsSyntacticTokenType TKeyword "class"] +[11:7-10 HsSemanticTokenType TClass "Boo"] +[11:11-12 HsSemanticTokenType TTypeVariable "a"] +[11:13-18 HsSyntacticTokenType TKeyword "where"] +[12:3-6 HsSemanticTokenType TClassMethod "boo"] +[12:7-9 HsSyntacticTokenType TKeyword "::"] +[12:10-11 HsSemanticTokenType TTypeVariable "a"] +[12:12-14 HsSyntacticTokenType TKeyword "->"] +[12:15-16 HsSemanticTokenType TTypeVariable "a"] +[14:1-9 HsSyntacticTokenType TKeyword "instance"] +[14:10-13 HsSemanticTokenType TClass "Boo"] +[14:14-17 HsSemanticTokenType TTypeConstructor "Int"] +[14:18-23 HsSyntacticTokenType TKeyword "where"] +[15:5-8 HsSemanticTokenType TClassMethod "boo"] +[15:9-10 HsSemanticTokenType TVariable "x"] +[15:11-12 HsSyntacticTokenType TKeyword "="] +[15:13-14 HsSemanticTokenType TVariable "x"] +[15:15-16 HsSemanticTokenType TOperator "+"] +[15:17-18 HsSyntacticTokenType TNumberLit "1"] +[17:1-5 HsSyntacticTokenType TKeyword "data"] +[17:6-8 HsSemanticTokenType TTypeConstructor "Dd"] +[17:9-10 HsSyntacticTokenType TKeyword "="] +[17:11-13 HsSemanticTokenType TDataConstructor "Dd"] +[17:14-17 HsSemanticTokenType TTypeConstructor "Int"] +[19:1-8 HsSyntacticTokenType TKeyword "pattern"] +[19:9-12 HsSemanticTokenType TPatternSynonym "One"] +[19:13-14 HsSyntacticTokenType TKeyword "="] +[19:15-18 HsSemanticTokenType TDataConstructor "Foo"] +[21:1-4 HsSemanticTokenType TVariable "ggg"] +[21:5-6 HsSyntacticTokenType TKeyword "="] +[21:7-10 HsSemanticTokenType TPatternSynonym "One"] +[23:1-5 HsSyntacticTokenType TKeyword "data"] +[23:6-9 HsSemanticTokenType TTypeConstructor "Doo"] +[23:10-11 HsSyntacticTokenType TKeyword "="] +[23:12-15 HsSemanticTokenType TDataConstructor "Doo"] +[23:16-24 HsSemanticTokenType TModule "Prelude."] +[23:24-27 HsSemanticTokenType TTypeConstructor "Int"] +[24:1-5 HsSyntacticTokenType TKeyword "type"] +[24:6-10 HsSemanticTokenType TTypeSynonym "Bar1"] +[24:11-12 HsSyntacticTokenType TKeyword "="] +[24:13-16 HsSemanticTokenType TTypeConstructor "Int"] +[25:1-5 HsSyntacticTokenType TKeyword "type"] +[25:6-10 HsSemanticTokenType TTypeSynonym "Bar2"] +[25:11-12 HsSyntacticTokenType TKeyword "="] +[25:13-16 HsSemanticTokenType TTypeConstructor "Doo"] +[27:1-3 HsSemanticTokenType TFunction "bb"] +[27:4-6 HsSyntacticTokenType TKeyword "::"] +[27:7-8 HsSyntacticTokenType TKeyword "("] +[27:8-11 HsSemanticTokenType TClass "Boo"] +[27:12-13 HsSemanticTokenType TTypeVariable "a"] +[27:13-14 HsSyntacticTokenType TKeyword ")"] +[27:15-17 HsSyntacticTokenType TKeyword "=>"] +[27:15-17 HsSyntacticTokenType TKeyword "=>"] +[27:18-19 HsSemanticTokenType TTypeVariable "a"] +[27:20-22 HsSyntacticTokenType TKeyword "->"] +[27:23-24 HsSemanticTokenType TTypeVariable "a"] +[28:1-3 HsSemanticTokenType TFunction "bb"] +[28:4-5 HsSemanticTokenType TVariable "x"] +[28:7-8 HsSyntacticTokenType TKeyword "="] +[28:9-12 HsSemanticTokenType TClassMethod "boo"] +[28:13-14 HsSemanticTokenType TVariable "x"] +[29:1-3 HsSemanticTokenType TFunction "aa"] +[29:4-6 HsSyntacticTokenType TKeyword "::"] +[29:7-11 HsSemanticTokenType TTypeVariable "cool"] +[29:12-14 HsSyntacticTokenType TKeyword "->"] +[29:15-18 HsSemanticTokenType TTypeConstructor "Int"] +[29:19-21 HsSyntacticTokenType TKeyword "->"] +[29:22-26 HsSemanticTokenType TTypeVariable "cool"] +[30:1-3 HsSemanticTokenType TFunction "aa"] +[30:4-5 HsSemanticTokenType TVariable "x"] +[30:6-7 HsSyntacticTokenType TKeyword "="] +[30:8-9 HsSyntacticTokenType TKeyword "\\"] +[30:9-10 HsSemanticTokenType TVariable "c"] +[30:11-13 HsSyntacticTokenType TKeyword "->"] +[30:14-16 HsSemanticTokenType TFunction "aa"] +[30:17-18 HsSemanticTokenType TVariable "x"] +[30:19-20 HsSemanticTokenType TVariable "c"] +[31:5-10 HsSyntacticTokenType TKeyword "where"] +[31:12-14 HsSemanticTokenType TVariable "xx"] +[31:14-15 HsSyntacticTokenType TKeyword ","] +[31:16-18 HsSemanticTokenType TVariable "yy"] +[31:20-21 HsSyntacticTokenType TKeyword "="] +[31:23-24 HsSyntacticTokenType TNumberLit "1"] +[31:24-25 HsSyntacticTokenType TKeyword ","] +[31:26-27 HsSyntacticTokenType TNumberLit "2"] +[32:11-13 HsSemanticTokenType TVariable "dd"] +[32:14-15 HsSyntacticTokenType TKeyword "="] +[32:16-17 HsSyntacticTokenType TNumberLit "1"] +[34:2-4 HsSemanticTokenType TVariable "zz"] +[34:4-5 HsSyntacticTokenType TKeyword ","] +[34:6-8 HsSemanticTokenType TVariable "kk"] +[34:10-11 HsSyntacticTokenType TKeyword "="] +[34:13-14 HsSyntacticTokenType TNumberLit "1"] +[34:14-15 HsSyntacticTokenType TKeyword ","] +[34:16-17 HsSyntacticTokenType TNumberLit "2"] +[35:1-3 HsSemanticTokenType TFunction "cc"] +[35:4-6 HsSyntacticTokenType TKeyword "::"] +[35:7-10 HsSemanticTokenType TTypeConstructor "Foo"] +[35:11-13 HsSyntacticTokenType TKeyword "->"] +[35:14-15 HsSyntacticTokenType TKeyword "("] +[35:15-18 HsSemanticTokenType TTypeConstructor "Int"] +[35:18-19 HsSyntacticTokenType TKeyword ","] +[35:20-23 HsSemanticTokenType TTypeConstructor "Int"] +[35:23-24 HsSyntacticTokenType TKeyword ")"] +[35:25-27 HsSyntacticTokenType TKeyword "->"] +[35:28-31 HsSemanticTokenType TTypeConstructor "Int"] +[36:1-3 HsSemanticTokenType TFunction "cc"] +[36:4-5 HsSemanticTokenType TVariable "f"] +[36:7-9 HsSemanticTokenType TVariable "gg"] +[36:9-10 HsSyntacticTokenType TKeyword ","] +[36:11-13 HsSemanticTokenType TVariable "vv"] +[36:14-15 HsSyntacticTokenType TKeyword "="] +[37:5-9 HsSyntacticTokenType TKeyword "case"] +[37:10-12 HsSemanticTokenType TVariable "gg"] +[37:13-15 HsSyntacticTokenType TKeyword "of"] +[38:11-13 HsSyntacticTokenType TKeyword "->"] +[38:14-17 HsSyntacticTokenType TRecordSelector "foo",38:14-17 HsSemanticTokenType TRecordField "foo"] +[38:18-19 HsSemanticTokenType TOperator "$"] +[38:20-21 HsSemanticTokenType TVariable "f"] +[38:22-23 HsSyntacticTokenType TKeyword "{"] +[38:24-27 HsSyntacticTokenType TRecordSelector "foo",38:24-27 HsSemanticTokenType TRecordField "foo"] +[38:28-29 HsSyntacticTokenType TKeyword "="] +[38:30-31 HsSyntacticTokenType TNumberLit "1"] +[38:32-33 HsSyntacticTokenType TKeyword "}"] +[39:11-13 HsSyntacticTokenType TKeyword "->"] +[39:14-17 HsSyntacticTokenType TRecordSelector "foo",39:14-17 HsSemanticTokenType TRecordField "foo"] +[39:18-19 HsSemanticTokenType TOperator "$"] +[39:20-21 HsSemanticTokenType TVariable "f"] +[39:22-23 HsSyntacticTokenType TKeyword "{"] +[39:24-27 HsSyntacticTokenType TRecordSelector "foo",39:24-27 HsSemanticTokenType TRecordField "foo"] +[39:28-29 HsSyntacticTokenType TKeyword "="] +[39:30-31 HsSyntacticTokenType TNumberLit "1"] +[39:32-33 HsSyntacticTokenType TKeyword "}"] +[41:1-3 HsSemanticTokenType TFunction "go"] +[41:4-5 HsSyntacticTokenType TKeyword "="] +[41:6-9 HsSyntacticTokenType TRecordSelector "foo",41:6-9 HsSemanticTokenType TRecordField "foo"] +[42:1-4 HsSemanticTokenType TFunction "add"] +[42:5-6 HsSyntacticTokenType TKeyword "="] +[42:7-8 HsSyntacticTokenType TKeyword "("] +[42:8-16 HsSemanticTokenType TModule "Prelude."] +[42:16-17 HsSemanticTokenType TOperator "+"] +[42:17-18 HsSyntacticTokenType TKeyword ")"] +[44:1-28 HsSyntacticTokenType TComment "-- sub :: Int -> Int -> Int"] +[45:1-21 HsSyntacticTokenType TComment "-- sub x y = add x y"] +[47:1-5 HsSemanticTokenType TVariable "main"] +[47:6-8 HsSyntacticTokenType TKeyword "::"] +[47:9-11 HsSemanticTokenType TTypeConstructor "IO"] +[47:12-13 HsSyntacticTokenType TKeyword "("] +[47:13-14 HsSyntacticTokenType TKeyword ")"] +[48:1-5 HsSemanticTokenType TVariable "main"] +[48:6-7 HsSyntacticTokenType TKeyword "="] +[48:8-16 HsSemanticTokenType TFunction "putStrLn"] +[48:17-34 HsSyntacticTokenType TStringLit "\"Hello, Haskell!\""] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClass.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClass.expected index f7bb4cd513..5f7a12eba4 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClass.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClass.expected @@ -1,6 +1,12 @@ -1:8-14 TModule "TClass" -4:7-10 TClass "Foo" -4:11-12 TTypeVariable "a" -5:3-6 TClassMethod "foo" -5:10-11 TTypeVariable "a" -5:15-18 TTypeConstructor "Int" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-14 HsSemanticTokenType TModule "TClass"] +[1:15-20 HsSyntacticTokenType TKeyword "where"] +[4:1-6 HsSyntacticTokenType TKeyword "class"] +[4:7-10 HsSemanticTokenType TClass "Foo"] +[4:11-12 HsSemanticTokenType TTypeVariable "a"] +[4:13-18 HsSyntacticTokenType TKeyword "where"] +[5:3-6 HsSemanticTokenType TClassMethod "foo"] +[5:7-9 HsSyntacticTokenType TKeyword "::"] +[5:10-11 HsSemanticTokenType TTypeVariable "a"] +[5:12-14 HsSyntacticTokenType TKeyword "->"] +[5:15-18 HsSemanticTokenType TTypeConstructor "Int"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClassImportedDeriving.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClassImportedDeriving.expected index 9ca97d9082..4ec40136a6 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClassImportedDeriving.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TClassImportedDeriving.expected @@ -1,4 +1,19 @@ -2:8-30 TModule "TClassImportedDeriving" -4:6-9 TTypeConstructor "Foo" -4:12-15 TDataConstructor "Foo" -4:26-30 TClass "Show" +[1:1-36 HsSyntacticTokenType TComment "{-# LANGUAGE StandaloneDeriving #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:8-30 HsSemanticTokenType TModule "TClassImportedDeriving"] +[2:31-36 HsSyntacticTokenType TKeyword "where"] +[3:1-50 HsSyntacticTokenType TComment "-- deriving method source span of Show occurrence"] +[4:1-5 HsSyntacticTokenType TKeyword "data"] +[4:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[4:10-11 HsSyntacticTokenType TKeyword "="] +[4:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[4:16-24 HsSyntacticTokenType TKeyword "deriving"] +[4:25-26 HsSyntacticTokenType TKeyword "("] +[4:25-26 HsSyntacticTokenType TKeyword "("] +[4:26-30 HsSemanticTokenType TClass "Show"] +[4:30-31 HsSyntacticTokenType TKeyword ")"] +[4:30-31 HsSyntacticTokenType TKeyword ")"] +[6:1-55 HsSyntacticTokenType TComment "-- standalone deriving method not in the same position"] +[7:1-28 HsSyntacticTokenType TComment "-- deriving instance Eq Foo"] +[9:1-27 HsSyntacticTokenType TComment "-- a :: Foo -> Foo -> Bool"] +[10:1-12 HsSyntacticTokenType TComment "-- a = (==)"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataFamily.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataFamily.expected index b3b477e541..ebf69a0e25 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataFamily.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataFamily.expected @@ -1,13 +1,32 @@ -2:8-19 TModule "TDatafamily" -5:13-18 TTypeFamily "XList" -5:19-20 TTypeVariable "a" -8:15-20 TTypeFamily "XList" -8:21-25 TTypeConstructor "Char" -8:28-33 TDataConstructor "XCons" -8:35-39 TTypeConstructor "Char" -8:42-47 TTypeFamily "XList" -8:48-52 TTypeConstructor "Char" -8:56-60 TDataConstructor "XNil" -11:15-20 TTypeFamily "XList" -11:26-35 TDataConstructor "XListUnit" -11:37-40 TTypeConstructor "Int" +[1:1-30 HsSyntacticTokenType TComment "{-# LANGUAGE TypeFamilies #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:8-19 HsSemanticTokenType TModule "TDatafamily"] +[2:20-25 HsSyntacticTokenType TKeyword "where"] +[4:1-35 HsSyntacticTokenType TComment "-- Declare a list-like data family"] +[5:1-5 HsSyntacticTokenType TKeyword "data"] +[5:6-12 HsSyntacticTokenType TKeyword "family"] +[5:13-18 HsSemanticTokenType TTypeFamily "XList"] +[5:19-20 HsSemanticTokenType TTypeVariable "a"] +[7:1-41 HsSyntacticTokenType TComment "-- Declare a list-like instance for Char"] +[8:1-5 HsSyntacticTokenType TKeyword "data"] +[8:6-14 HsSyntacticTokenType TKeyword "instance"] +[8:15-20 HsSemanticTokenType TTypeFamily "XList"] +[8:21-25 HsSemanticTokenType TTypeConstructor "Char"] +[8:26-27 HsSyntacticTokenType TKeyword "="] +[8:28-33 HsSemanticTokenType TDataConstructor "XCons"] +[8:35-39 HsSemanticTokenType TTypeConstructor "Char"] +[8:41-42 HsSyntacticTokenType TKeyword "("] +[8:42-47 HsSemanticTokenType TTypeFamily "XList"] +[8:48-52 HsSemanticTokenType TTypeConstructor "Char"] +[8:52-53 HsSyntacticTokenType TKeyword ")"] +[8:54-55 HsSyntacticTokenType TKeyword "|"] +[8:56-60 HsSemanticTokenType TDataConstructor "XNil"] +[10:1-41 HsSyntacticTokenType TComment "-- Declare a number-like instance for ()"] +[11:1-5 HsSyntacticTokenType TKeyword "data"] +[11:6-14 HsSyntacticTokenType TKeyword "instance"] +[11:15-20 HsSemanticTokenType TTypeFamily "XList"] +[11:21-22 HsSyntacticTokenType TKeyword "("] +[11:22-23 HsSyntacticTokenType TKeyword ")"] +[11:24-25 HsSyntacticTokenType TKeyword "="] +[11:26-35 HsSemanticTokenType TDataConstructor "XListUnit"] +[11:37-40 HsSemanticTokenType TTypeConstructor "Int"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataType.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataType.expected index 7f03f4ed54..00437d2a6c 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataType.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDataType.expected @@ -1,5 +1,14 @@ -1:8-17 TModule "TDataType" -3:6-9 TTypeConstructor "Foo" -3:12-15 TDataConstructor "Foo" -3:16-19 TTypeConstructor "Int" -3:30-32 TClass "Eq" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-17 HsSemanticTokenType TModule "TDataType"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-5 HsSyntacticTokenType TKeyword "data"] +[3:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[3:10-11 HsSyntacticTokenType TKeyword "="] +[3:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[3:16-19 HsSemanticTokenType TTypeConstructor "Int"] +[3:20-28 HsSyntacticTokenType TKeyword "deriving"] +[3:29-30 HsSyntacticTokenType TKeyword "("] +[3:29-30 HsSyntacticTokenType TKeyword "("] +[3:30-32 HsSemanticTokenType TClass "Eq"] +[3:32-33 HsSyntacticTokenType TKeyword ")"] +[3:32-33 HsSyntacticTokenType TKeyword ")"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDatatypeImported.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDatatypeImported.expected index 78ebf2bc22..e7d6b08f41 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDatatypeImported.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDatatypeImported.expected @@ -1,6 +1,14 @@ -1:8-25 TModule "TDatatypeImported" -3:8-17 TModule "System.IO" -5:1-3 TVariable "go" -5:7-9 TTypeConstructor "IO" -6:1-3 TVariable "go" -6:6-11 TFunction "print" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-25 HsSemanticTokenType TModule "TDatatypeImported"] +[1:26-31 HsSyntacticTokenType TKeyword "where"] +[3:1-7 HsSyntacticTokenType TKeyword "import"] +[3:8-17 HsSemanticTokenType TModule "System.IO"] +[5:1-3 HsSemanticTokenType TVariable "go"] +[5:4-6 HsSyntacticTokenType TKeyword "::"] +[5:7-9 HsSemanticTokenType TTypeConstructor "IO"] +[5:10-11 HsSyntacticTokenType TKeyword "("] +[5:11-12 HsSyntacticTokenType TKeyword ")"] +[6:1-3 HsSemanticTokenType TVariable "go"] +[6:4-5 HsSyntacticTokenType TKeyword "="] +[6:6-11 HsSemanticTokenType TFunction "print"] +[6:12-13 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDoc.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDoc.expected index 30b1cdb345..537e72b671 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDoc.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TDoc.expected @@ -1,6 +1,13 @@ -1:8-12 TModule "TDoc" -4:5-10 TVariable "hello" -5:1-6 TVariable "hello" -5:10-13 TTypeConstructor "Int" -6:1-6 TVariable "hello" -6:9-15 TClassMethod "length" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-12 HsSemanticTokenType TModule "TDoc"] +[1:13-18 HsSyntacticTokenType TKeyword "where"] +[3:1-5 HsSyntacticTokenType TComment "-- |"] +[4:1-11 HsSyntacticTokenType TComment "-- `hello`"] +[4:5-10 HsSemanticTokenType TVariable "hello"] +[5:1-6 HsSemanticTokenType TVariable "hello"] +[5:7-9 HsSyntacticTokenType TKeyword "::"] +[5:10-13 HsSemanticTokenType TTypeConstructor "Int"] +[6:1-6 HsSemanticTokenType TVariable "hello"] +[6:7-8 HsSyntacticTokenType TKeyword "="] +[6:9-15 HsSemanticTokenType TClassMethod "length"] +[6:16-33 HsSyntacticTokenType TStringLit "\"Hello, Haskell!\""] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunction.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunction.expected index 2b715e0a40..ed8b6e6b1b 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunction.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunction.expected @@ -1,12 +1,21 @@ -1:8-17 TModule "TFunction" -3:1-2 TFunction "f" -3:13-14 TTypeVariable "a" -3:16-17 TTypeVariable "a" -3:21-22 TTypeVariable "a" -4:1-2 TFunction "f" -4:3-4 TVariable "x" -4:7-8 TVariable "x" -6:1-2 TVariable "x" -6:6-7 TTypeVariable "a" -7:1-2 TVariable "x" -7:5-14 TVariable "undefined" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-17 HsSemanticTokenType TModule "TFunction"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TFunction "f"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-12 HsSyntacticTokenType TKeyword "forall"] +[3:13-14 HsSemanticTokenType TTypeVariable "a"] +[3:14-15 HsSyntacticTokenType TKeyword "."] +[3:16-17 HsSemanticTokenType TTypeVariable "a"] +[3:18-20 HsSyntacticTokenType TKeyword "->"] +[3:21-22 HsSemanticTokenType TTypeVariable "a"] +[4:1-2 HsSemanticTokenType TFunction "f"] +[4:3-4 HsSemanticTokenType TVariable "x"] +[4:5-6 HsSyntacticTokenType TKeyword "="] +[4:7-8 HsSemanticTokenType TVariable "x"] +[6:1-2 HsSemanticTokenType TVariable "x"] +[6:3-5 HsSyntacticTokenType TKeyword "::"] +[6:6-7 HsSemanticTokenType TTypeVariable "a"] +[7:1-2 HsSemanticTokenType TVariable "x"] +[7:3-4 HsSyntacticTokenType TKeyword "="] +[7:5-14 HsSemanticTokenType TVariable "undefined"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLet.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLet.expected index f51938a712..dd0d41ac65 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLet.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLet.expected @@ -1,6 +1,15 @@ -1:8-20 TModule "TFunctionLet" -3:1-2 TVariable "y" -3:6-9 TTypeConstructor "Int" -4:1-2 TVariable "y" -4:9-10 TFunction "f" -4:11-12 TVariable "x" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-20 HsSemanticTokenType TModule "TFunctionLet"] +[1:21-26 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TVariable "y"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-9 HsSemanticTokenType TTypeConstructor "Int"] +[4:1-2 HsSemanticTokenType TVariable "y"] +[4:3-4 HsSyntacticTokenType TKeyword "="] +[4:5-8 HsSyntacticTokenType TKeyword "let"] +[4:9-10 HsSemanticTokenType TFunction "f"] +[4:11-12 HsSemanticTokenType TVariable "x"] +[4:13-14 HsSyntacticTokenType TKeyword "="] +[4:15-16 HsSyntacticTokenType TNumberLit "1"] +[4:17-19 HsSyntacticTokenType TKeyword "in"] +[4:20-21 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLocal.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLocal.expected index 34e040d641..2592fa1de8 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLocal.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionLocal.expected @@ -1,8 +1,17 @@ -1:8-22 TModule "TFunctionLocal" -3:1-2 TFunction "f" -3:6-9 TTypeConstructor "Int" -3:13-16 TTypeConstructor "Int" -4:1-2 TFunction "f" -4:7-8 TFunction "g" -6:5-6 TFunction "g" -6:7-8 TVariable "x" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-22 HsSemanticTokenType TModule "TFunctionLocal"] +[1:23-28 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TFunction "f"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-9 HsSemanticTokenType TTypeConstructor "Int"] +[3:10-12 HsSyntacticTokenType TKeyword "->"] +[3:13-16 HsSemanticTokenType TTypeConstructor "Int"] +[4:1-2 HsSemanticTokenType TFunction "f"] +[4:5-6 HsSyntacticTokenType TKeyword "="] +[4:7-8 HsSemanticTokenType TFunction "g"] +[4:9-10 HsSyntacticTokenType TNumberLit "1"] +[5:3-8 HsSyntacticTokenType TKeyword "where"] +[6:5-6 HsSemanticTokenType TFunction "g"] +[6:7-8 HsSemanticTokenType TVariable "x"] +[6:9-10 HsSyntacticTokenType TKeyword "="] +[6:11-12 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionUnderTypeSynonym.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionUnderTypeSynonym.expected index 0779402a83..ff57a898e0 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionUnderTypeSynonym.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TFunctionUnderTypeSynonym.expected @@ -1,18 +1,32 @@ -1:8-33 TModule "TFunctionUnderTypeSynonym" -3:6-8 TTypeSynonym "T1" -3:11-14 TTypeConstructor "Int" -3:18-21 TTypeConstructor "Int" -4:6-8 TTypeSynonym "T2" -4:18-19 TTypeVariable "a" -4:21-22 TTypeVariable "a" -4:26-27 TTypeVariable "a" -5:1-3 TFunction "f1" -5:7-9 TTypeSynonym "T1" -6:1-3 TFunction "f1" -6:4-5 TVariable "x" -6:8-9 TVariable "x" -7:1-3 TFunction "f2" -7:7-9 TTypeSynonym "T2" -8:1-3 TFunction "f2" -8:4-5 TVariable "x" -8:8-9 TVariable "x" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-33 HsSemanticTokenType TModule "TFunctionUnderTypeSynonym"] +[1:34-39 HsSyntacticTokenType TKeyword "where"] +[3:1-5 HsSyntacticTokenType TKeyword "type"] +[3:6-8 HsSemanticTokenType TTypeSynonym "T1"] +[3:9-10 HsSyntacticTokenType TKeyword "="] +[3:11-14 HsSemanticTokenType TTypeConstructor "Int"] +[3:15-17 HsSyntacticTokenType TKeyword "->"] +[3:18-21 HsSemanticTokenType TTypeConstructor "Int"] +[4:1-5 HsSyntacticTokenType TKeyword "type"] +[4:6-8 HsSemanticTokenType TTypeSynonym "T2"] +[4:9-10 HsSyntacticTokenType TKeyword "="] +[4:11-17 HsSyntacticTokenType TKeyword "forall"] +[4:18-19 HsSemanticTokenType TTypeVariable "a"] +[4:19-20 HsSyntacticTokenType TKeyword "."] +[4:21-22 HsSemanticTokenType TTypeVariable "a"] +[4:23-25 HsSyntacticTokenType TKeyword "->"] +[4:26-27 HsSemanticTokenType TTypeVariable "a"] +[5:1-3 HsSemanticTokenType TFunction "f1"] +[5:4-6 HsSyntacticTokenType TKeyword "::"] +[5:7-9 HsSemanticTokenType TTypeSynonym "T1"] +[6:1-3 HsSemanticTokenType TFunction "f1"] +[6:4-5 HsSemanticTokenType TVariable "x"] +[6:6-7 HsSyntacticTokenType TKeyword "="] +[6:8-9 HsSemanticTokenType TVariable "x"] +[7:1-3 HsSemanticTokenType TFunction "f2"] +[7:4-6 HsSyntacticTokenType TKeyword "::"] +[7:7-9 HsSemanticTokenType TTypeSynonym "T2"] +[8:1-3 HsSemanticTokenType TFunction "f2"] +[8:4-5 HsSemanticTokenType TVariable "x"] +[8:6-7 HsSyntacticTokenType TKeyword "="] +[8:8-9 HsSemanticTokenType TVariable "x"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TGADT.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TGADT.expected index 3f07298543..98896be8a4 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TGADT.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TGADT.expected @@ -1,14 +1,34 @@ -3:8-13 TModule "TGADT" -5:6-9 TTypeConstructor "Lam" -6:3-7 TDataConstructor "Lift" -6:11-12 TTypeVariable "a" -6:36-39 TTypeConstructor "Lam" -6:40-41 TTypeVariable "a" -7:3-6 TDataConstructor "Lam" -7:12-15 TTypeConstructor "Lam" -7:16-17 TTypeVariable "a" -7:21-24 TTypeConstructor "Lam" -7:25-26 TTypeVariable "b" -7:36-39 TTypeConstructor "Lam" -7:41-42 TTypeVariable "a" -7:46-47 TTypeVariable "b" +[1:1-30 HsSyntacticTokenType TComment "{-# LANGUAGE TypeFamilies #-}"] +[2:1-23 HsSyntacticTokenType TComment "{-# LANGUAGE GADTs #-}"] +[3:1-7 HsSyntacticTokenType TKeyword "module"] +[3:8-13 HsSemanticTokenType TModule "TGADT"] +[3:14-19 HsSyntacticTokenType TKeyword "where"] +[5:1-5 HsSyntacticTokenType TKeyword "data"] +[5:6-9 HsSemanticTokenType TTypeConstructor "Lam"] +[5:10-12 HsSyntacticTokenType TKeyword "::"] +[5:15-17 HsSyntacticTokenType TKeyword "->"] +[5:20-25 HsSyntacticTokenType TKeyword "where"] +[6:3-7 HsSemanticTokenType TDataConstructor "Lift"] +[6:8-10 HsSyntacticTokenType TKeyword "::"] +[6:11-12 HsSemanticTokenType TTypeVariable "a"] +[6:33-35 HsSyntacticTokenType TKeyword "->"] +[6:36-39 HsSemanticTokenType TTypeConstructor "Lam"] +[6:40-41 HsSemanticTokenType TTypeVariable "a"] +[6:49-66 HsSyntacticTokenType TComment "-- ^ lifted value"] +[7:3-6 HsSemanticTokenType TDataConstructor "Lam"] +[7:8-10 HsSyntacticTokenType TKeyword "::"] +[7:11-12 HsSyntacticTokenType TKeyword "("] +[7:12-15 HsSemanticTokenType TTypeConstructor "Lam"] +[7:16-17 HsSemanticTokenType TTypeVariable "a"] +[7:18-20 HsSyntacticTokenType TKeyword "->"] +[7:21-24 HsSemanticTokenType TTypeConstructor "Lam"] +[7:25-26 HsSemanticTokenType TTypeVariable "b"] +[7:26-27 HsSyntacticTokenType TKeyword ")"] +[7:33-35 HsSyntacticTokenType TKeyword "->"] +[7:36-39 HsSemanticTokenType TTypeConstructor "Lam"] +[7:40-41 HsSyntacticTokenType TKeyword "("] +[7:41-42 HsSemanticTokenType TTypeVariable "a"] +[7:43-45 HsSyntacticTokenType TKeyword "->"] +[7:46-47 HsSemanticTokenType TTypeVariable "b"] +[7:47-48 HsSyntacticTokenType TKeyword ")"] +[7:49-72 HsSyntacticTokenType TComment "-- ^ lambda abstraction"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodBind.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodBind.expected index b93e340ac3..5fc43701c4 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodBind.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodBind.expected @@ -1,8 +1,15 @@ -1:8-32 TModule "TInstanceClassMethodBind" -4:6-9 TTypeConstructor "Foo" -4:12-15 TDataConstructor "Foo" -4:16-19 TTypeConstructor "Int" -5:10-14 TClass "Show" -5:15-18 TTypeConstructor "Foo" -6:5-9 TClassMethod "show" -6:12-21 TVariable "undefined" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-32 HsSemanticTokenType TModule "TInstanceClassMethodBind"] +[1:33-38 HsSyntacticTokenType TKeyword "where"] +[4:1-5 HsSyntacticTokenType TKeyword "data"] +[4:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[4:10-11 HsSyntacticTokenType TKeyword "="] +[4:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[4:16-19 HsSemanticTokenType TTypeConstructor "Int"] +[5:1-9 HsSyntacticTokenType TKeyword "instance"] +[5:10-14 HsSemanticTokenType TClass "Show"] +[5:15-18 HsSemanticTokenType TTypeConstructor "Foo"] +[5:19-24 HsSyntacticTokenType TKeyword "where"] +[6:5-9 HsSemanticTokenType TClassMethod "show"] +[6:10-11 HsSyntacticTokenType TKeyword "="] +[6:12-21 HsSemanticTokenType TVariable "undefined"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodUse.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodUse.expected index 3fc60caab3..982d3abf25 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodUse.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TInstanceClassMethodUse.expected @@ -1,3 +1,6 @@ -1:8-31 TModule "TInstanceClassMethodUse" -4:1-3 TFunction "go" -4:8-12 TClassMethod "show" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-31 HsSemanticTokenType TModule "TInstanceClassMethodUse"] +[1:32-37 HsSyntacticTokenType TKeyword "where"] +[4:1-3 HsSemanticTokenType TFunction "go"] +[4:5-6 HsSyntacticTokenType TKeyword "="] +[4:8-12 HsSemanticTokenType TClassMethod "show"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TNoneFunctionWithConstraint.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TNoneFunctionWithConstraint.expected index a004142952..41bd638c80 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TNoneFunctionWithConstraint.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TNoneFunctionWithConstraint.expected @@ -1,7 +1,15 @@ -1:8-35 TModule "TNoneFunctionWithConstraint" -3:1-2 TVariable "x" -3:7-9 TClass "Eq" -3:10-11 TTypeVariable "a" -3:16-17 TTypeVariable "a" -4:1-2 TVariable "x" -4:5-14 TVariable "undefined" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-35 HsSemanticTokenType TModule "TNoneFunctionWithConstraint"] +[1:36-41 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TVariable "x"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-7 HsSyntacticTokenType TKeyword "("] +[3:7-9 HsSemanticTokenType TClass "Eq"] +[3:10-11 HsSemanticTokenType TTypeVariable "a"] +[3:11-12 HsSyntacticTokenType TKeyword ")"] +[3:13-15 HsSyntacticTokenType TKeyword "=>"] +[3:13-15 HsSyntacticTokenType TKeyword "=>"] +[3:16-17 HsSemanticTokenType TTypeVariable "a"] +[4:1-2 HsSemanticTokenType TVariable "x"] +[4:3-4 HsSyntacticTokenType TKeyword "="] +[4:5-14 HsSemanticTokenType TVariable "undefined"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TOperator.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TOperator.expected index c8b2ecb29d..e406751b41 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TOperator.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TOperator.expected @@ -1,34 +1,62 @@ -1:8-17 TModule "TOperator" -4:1-3 TFunction "go" -4:4-5 TFunction "f" -4:6-7 TVariable "x" -4:10-11 TFunction "f" -4:11-12 TOperator "$" -4:12-13 TVariable "x" -6:2-6 TOperator "$$$$" -7:1-2 TVariable "x" -7:7-11 TOperator "$$$$" -8:6-7 TTypeVariable "a" -8:8-11 TOperator ":+:" -8:12-13 TTypeVariable "b" -8:16-19 TDataConstructor "Add" -8:20-21 TTypeVariable "a" -8:22-23 TTypeVariable "b" -9:7-10 TOperator ":-:" -9:12-13 TTypeVariable "a" -9:14-15 TTypeVariable "b" -9:19-20 TTypeVariable "a" -9:22-23 TTypeVariable "b" -11:1-4 TFunction "add" -11:8-11 TTypeConstructor "Int" -11:12-15 TOperator ":+:" -11:16-19 TTypeConstructor "Int" -11:23-26 TTypeConstructor "Int" -11:27-30 TOperator ":-:" -11:31-34 TTypeConstructor "Int" -13:1-4 TFunction "add" -13:6-9 TDataConstructor "Add" -13:10-11 TVariable "x" -13:12-13 TVariable "y" -13:18-19 TVariable "x" -13:21-22 TVariable "y" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-17 HsSemanticTokenType TModule "TOperator"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-21 HsSyntacticTokenType TComment "-- imported operator"] +[4:1-3 HsSemanticTokenType TFunction "go"] +[4:4-5 HsSemanticTokenType TFunction "f"] +[4:6-7 HsSemanticTokenType TVariable "x"] +[4:8-9 HsSyntacticTokenType TKeyword "="] +[4:10-11 HsSemanticTokenType TFunction "f"] +[4:11-12 HsSemanticTokenType TOperator "$"] +[4:12-13 HsSemanticTokenType TVariable "x"] +[5:1-36 HsSyntacticTokenType TComment "-- operator defined in local module"] +[6:1-2 HsSyntacticTokenType TKeyword "("] +[6:2-6 HsSemanticTokenType TOperator "$$$$"] +[6:6-7 HsSyntacticTokenType TKeyword ")"] +[6:8-9 HsSyntacticTokenType TKeyword "="] +[7:1-2 HsSemanticTokenType TVariable "x"] +[7:3-4 HsSyntacticTokenType TKeyword "="] +[7:5-6 HsSyntacticTokenType TNumberLit "1"] +[7:7-11 HsSemanticTokenType TOperator "$$$$"] +[7:12-13 HsSyntacticTokenType TNumberLit "2"] +[8:1-5 HsSyntacticTokenType TKeyword "data"] +[8:6-7 HsSemanticTokenType TTypeVariable "a"] +[8:8-11 HsSemanticTokenType TOperator ":+:"] +[8:12-13 HsSemanticTokenType TTypeVariable "b"] +[8:14-15 HsSyntacticTokenType TKeyword "="] +[8:16-19 HsSemanticTokenType TDataConstructor "Add"] +[8:20-21 HsSemanticTokenType TTypeVariable "a"] +[8:22-23 HsSemanticTokenType TTypeVariable "b"] +[9:1-5 HsSyntacticTokenType TKeyword "type"] +[9:6-7 HsSyntacticTokenType TKeyword "("] +[9:7-10 HsSemanticTokenType TOperator ":-:"] +[9:10-11 HsSyntacticTokenType TKeyword ")"] +[9:12-13 HsSemanticTokenType TTypeVariable "a"] +[9:14-15 HsSemanticTokenType TTypeVariable "b"] +[9:16-17 HsSyntacticTokenType TKeyword "="] +[9:18-19 HsSyntacticTokenType TKeyword "("] +[9:19-20 HsSemanticTokenType TTypeVariable "a"] +[9:20-21 HsSyntacticTokenType TKeyword ","] +[9:22-23 HsSemanticTokenType TTypeVariable "b"] +[9:23-24 HsSyntacticTokenType TKeyword ")"] +[10:1-38 HsSyntacticTokenType TComment "-- type take precedence over operator"] +[11:1-4 HsSemanticTokenType TFunction "add"] +[11:5-7 HsSyntacticTokenType TKeyword "::"] +[11:8-11 HsSemanticTokenType TTypeConstructor "Int"] +[11:12-15 HsSemanticTokenType TOperator ":+:"] +[11:16-19 HsSemanticTokenType TTypeConstructor "Int"] +[11:20-22 HsSyntacticTokenType TKeyword "->"] +[11:23-26 HsSemanticTokenType TTypeConstructor "Int"] +[11:27-30 HsSemanticTokenType TOperator ":-:"] +[11:31-34 HsSemanticTokenType TTypeConstructor "Int"] +[12:1-46 HsSyntacticTokenType TComment "-- class method take precedence over operator"] +[13:1-4 HsSemanticTokenType TFunction "add"] +[13:5-6 HsSyntacticTokenType TKeyword "("] +[13:6-9 HsSemanticTokenType TDataConstructor "Add"] +[13:10-11 HsSemanticTokenType TVariable "x"] +[13:12-13 HsSemanticTokenType TVariable "y"] +[13:13-14 HsSyntacticTokenType TKeyword ")"] +[13:15-16 HsSyntacticTokenType TKeyword "="] +[13:18-19 HsSemanticTokenType TVariable "x"] +[13:19-20 HsSyntacticTokenType TKeyword ","] +[13:21-22 HsSemanticTokenType TVariable "y"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternMatch.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternMatch.expected index b17e52e27f..c2718e2e50 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternMatch.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternMatch.expected @@ -1,3 +1,8 @@ -1:8-21 TModule "TPatternMatch" -4:1-2 TFunction "g" -4:4-11 TDataConstructor "Nothing" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-21 HsSemanticTokenType TModule "TPatternMatch"] +[1:22-27 HsSyntacticTokenType TKeyword "where"] +[4:1-2 HsSemanticTokenType TFunction "g"] +[4:4-11 HsSemanticTokenType TDataConstructor "Nothing"] +[4:11-12 HsSyntacticTokenType TKeyword ","] +[4:16-17 HsSyntacticTokenType TKeyword "="] +[4:18-19 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternSynonym.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternSynonym.expected index b9cff7321a..b12f84f4dc 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternSynonym.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternSynonym.expected @@ -1,2 +1,7 @@ -2:8-23 TModule "TPatternSynonym" -5:9-12 TPatternSynonym "Foo" +[1:1-33 HsSyntacticTokenType TComment "{-# LANGUAGE PatternSynonyms #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:8-23 HsSemanticTokenType TModule "TPatternSynonym"] +[2:24-29 HsSyntacticTokenType TKeyword "where"] +[5:1-8 HsSyntacticTokenType TKeyword "pattern"] +[5:9-12 HsSemanticTokenType TPatternSynonym "Foo"] +[5:13-14 HsSyntacticTokenType TKeyword "="] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternbind.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternbind.expected index ab12539d12..f3fca0a19f 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternbind.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TPatternbind.expected @@ -1,8 +1,16 @@ -1:8-17 TModule "TVariable" -3:2-3 TVariable "a" -3:5-6 TVariable "b" -5:1-2 TFunction "f" -5:3-4 TFunction "g" -5:5-6 TVariable "y" -5:9-10 TFunction "g" -5:11-12 TVariable "y" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-17 HsSemanticTokenType TModule "TVariable"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:2-3 HsSemanticTokenType TVariable "a"] +[3:3-4 HsSyntacticTokenType TKeyword ","] +[3:5-6 HsSemanticTokenType TVariable "b"] +[3:8-9 HsSyntacticTokenType TKeyword "="] +[3:11-12 HsSyntacticTokenType TNumberLit "1"] +[3:12-13 HsSyntacticTokenType TKeyword ","] +[3:14-15 HsSyntacticTokenType TNumberLit "2"] +[5:1-2 HsSemanticTokenType TFunction "f"] +[5:3-4 HsSemanticTokenType TFunction "g"] +[5:5-6 HsSemanticTokenType TVariable "y"] +[5:7-8 HsSyntacticTokenType TKeyword "="] +[5:9-10 HsSemanticTokenType TFunction "g"] +[5:11-12 HsSemanticTokenType TVariable "y"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TQualifiedName.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TQualifiedName.expected index df305195ed..e8d9255a59 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TQualifiedName.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TQualifiedName.expected @@ -1,13 +1,37 @@ -1:8-22 TModule "TQualifiedName" -3:18-27 TModule "Data.List" -6:1-2 TVariable "a" -6:5-13 TModule "Prelude." -6:13-22 TVariable "undefined" -7:1-2 TVariable "b" -7:8-18 TModule "Data.List." -7:18-22 TClassMethod "elem" -8:1-2 TVariable "c" -8:6-14 TModule "Prelude." -8:14-15 TOperator "+" -9:1-2 TVariable "d" -9:6-7 TOperator "+" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-22 HsSemanticTokenType TModule "TQualifiedName"] +[1:23-28 HsSyntacticTokenType TKeyword "where"] +[3:1-7 HsSyntacticTokenType TKeyword "import"] +[3:8-17 HsSyntacticTokenType TKeyword "qualified"] +[3:18-27 HsSemanticTokenType TModule "Data.List"] +[6:1-2 HsSemanticTokenType TVariable "a"] +[6:3-4 HsSyntacticTokenType TKeyword "="] +[6:5-13 HsSemanticTokenType TModule "Prelude."] +[6:13-22 HsSemanticTokenType TVariable "undefined"] +[7:1-2 HsSemanticTokenType TVariable "b"] +[7:3-4 HsSyntacticTokenType TKeyword "="] +[7:5-6 HsSyntacticTokenType TNumberLit "1"] +[7:7-8 HsSyntacticTokenType TKeyword "`"] +[7:8-18 HsSemanticTokenType TModule "Data.List."] +[7:18-22 HsSemanticTokenType TClassMethod "elem"] +[7:22-23 HsSyntacticTokenType TKeyword "`"] +[7:24-25 HsSyntacticTokenType TKeyword "["] +[7:25-26 HsSyntacticTokenType TNumberLit "1"] +[7:26-27 HsSyntacticTokenType TKeyword ","] +[7:28-29 HsSyntacticTokenType TNumberLit "2"] +[7:29-30 HsSyntacticTokenType TKeyword "]"] +[8:1-2 HsSemanticTokenType TVariable "c"] +[8:3-4 HsSyntacticTokenType TKeyword "="] +[8:5-6 HsSyntacticTokenType TKeyword "("] +[8:6-14 HsSemanticTokenType TModule "Prelude."] +[8:14-15 HsSemanticTokenType TOperator "+"] +[8:15-16 HsSyntacticTokenType TKeyword ")"] +[8:17-18 HsSyntacticTokenType TNumberLit "1"] +[8:19-20 HsSyntacticTokenType TNumberLit "1"] +[9:1-2 HsSemanticTokenType TVariable "d"] +[9:3-4 HsSyntacticTokenType TKeyword "="] +[9:5-6 HsSyntacticTokenType TKeyword "("] +[9:6-7 HsSemanticTokenType TOperator "+"] +[9:7-8 HsSyntacticTokenType TKeyword ")"] +[9:9-10 HsSyntacticTokenType TNumberLit "1"] +[9:11-12 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecord.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecord.expected index 5be40a4a39..ec1b633e6c 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecord.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecord.expected @@ -1,5 +1,12 @@ -1:8-15 TModule "TRecord" -4:6-9 TTypeConstructor "Foo" -4:12-15 TDataConstructor "Foo" -4:18-21 TRecordField "foo" -4:25-28 TTypeConstructor "Int" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-15 HsSemanticTokenType TModule "TRecord"] +[1:16-21 HsSyntacticTokenType TKeyword "where"] +[4:1-5 HsSyntacticTokenType TKeyword "data"] +[4:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[4:10-11 HsSyntacticTokenType TKeyword "="] +[4:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[4:16-17 HsSyntacticTokenType TKeyword "{"] +[4:18-21 HsSyntacticTokenType TRecordSelector "foo",4:18-21 HsSemanticTokenType TRecordField "foo"] +[4:22-24 HsSyntacticTokenType TKeyword "::"] +[4:25-28 HsSemanticTokenType TTypeConstructor "Int"] +[4:29-30 HsSyntacticTokenType TKeyword "}"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecordDuplicateRecordFields.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecordDuplicateRecordFields.expected index 04ef050ab0..61d6fcd969 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecordDuplicateRecordFields.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TRecordDuplicateRecordFields.expected @@ -1,5 +1,13 @@ -3:8-36 TModule "TRecordDuplicateRecordFields" -5:6-9 TTypeConstructor "Foo" -5:12-15 TDataConstructor "Foo" -5:18-21 TRecordField "boo" -5:26-32 TTypeSynonym "String" +[1:1-44 HsSyntacticTokenType TComment "{-# LANGUAGE DuplicateRecordFields #-}"] +[3:1-7 HsSyntacticTokenType TKeyword "module"] +[3:8-36 HsSemanticTokenType TModule "TRecordDuplicateRecordFields"] +[3:37-42 HsSyntacticTokenType TKeyword "where"] +[5:1-5 HsSyntacticTokenType TKeyword "data"] +[5:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[5:10-11 HsSyntacticTokenType TKeyword "="] +[5:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[5:16-17 HsSyntacticTokenType TKeyword "{"] +[5:18-21 HsSyntacticTokenType TRecordSelector "boo",5:18-21 HsSemanticTokenType TRecordField "boo"] +[5:22-24 HsSyntacticTokenType TKeyword "::"] +[5:26-32 HsSemanticTokenType TTypeSynonym "String"] +[5:33-34 HsSyntacticTokenType TKeyword "}"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TTypefamily.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TTypefamily.expected index 1aa6bf4687..12086ada99 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TTypefamily.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TTypefamily.expected @@ -1,9 +1,17 @@ -2:8-19 TModule "TTypefamily" -4:13-16 TTypeFamily "Foo" -4:17-18 TTypeVariable "a" -5:3-6 TTypeFamily "Foo" -5:7-10 TTypeConstructor "Int" -5:13-16 TTypeConstructor "Int" -6:3-6 TTypeFamily "Foo" -6:7-8 TTypeVariable "a" -6:11-17 TTypeSynonym "String" +[1:1-30 HsSyntacticTokenType TComment "{-# LANGUAGE TypeFamilies #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:8-19 HsSemanticTokenType TModule "TTypefamily"] +[2:20-25 HsSyntacticTokenType TKeyword "where"] +[4:1-5 HsSyntacticTokenType TKeyword "type"] +[4:6-12 HsSyntacticTokenType TKeyword "family"] +[4:13-16 HsSemanticTokenType TTypeFamily "Foo"] +[4:17-18 HsSemanticTokenType TTypeVariable "a"] +[4:19-24 HsSyntacticTokenType TKeyword "where"] +[5:3-6 HsSemanticTokenType TTypeFamily "Foo"] +[5:7-10 HsSemanticTokenType TTypeConstructor "Int"] +[5:11-12 HsSyntacticTokenType TKeyword "="] +[5:13-16 HsSemanticTokenType TTypeConstructor "Int"] +[6:3-6 HsSemanticTokenType TTypeFamily "Foo"] +[6:7-8 HsSemanticTokenType TTypeVariable "a"] +[6:9-10 HsSyntacticTokenType TKeyword "="] +[6:11-17 HsSemanticTokenType TTypeSynonym "String"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TUnicodeSyntax.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TUnicodeSyntax.expected index ad9f6ea762..971a212d46 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TUnicodeSyntax.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TUnicodeSyntax.expected @@ -1,2 +1,6 @@ -1:8-22 TModule "TUnicodeSyntax" -3:1-4 TVariable "a\66560b" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-22 HsSemanticTokenType TModule "TUnicodeSyntax"] +[1:23-28 HsSyntacticTokenType TKeyword "where"] +[3:1-4 HsSemanticTokenType TVariable "a\66560b"] +[3:4-5 HsSyntacticTokenType TKeyword " "] +[3:6-10 HsSyntacticTokenType TStringLit " \"a\66560"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TValBind.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TValBind.expected index 700509c968..cd29b0dc38 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TValBind.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/after_9_10/TValBind.expected @@ -1,5 +1,10 @@ -1:8-16 TModule "TValBind" -4:1-6 TVariable "hello" -4:10-13 TTypeConstructor "Int" -5:1-6 TVariable "hello" -5:9-15 TClassMethod "length" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:8-16 HsSemanticTokenType TModule "TValBind"] +[1:17-22 HsSyntacticTokenType TKeyword "where"] +[4:1-6 HsSemanticTokenType TVariable "hello"] +[4:7-9 HsSyntacticTokenType TKeyword "::"] +[4:10-13 HsSemanticTokenType TTypeConstructor "Int"] +[5:1-6 HsSemanticTokenType TVariable "hello"] +[5:7-8 HsSyntacticTokenType TKeyword "="] +[5:9-15 HsSemanticTokenType TClassMethod "length"] +[5:16-33 HsSyntacticTokenType TStringLit "\"Hello, Haskell!\""] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/T1.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/T1.expected index cbf7699f19..608e1cbc77 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/T1.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/T1.expected @@ -1,81 +1,153 @@ -9:6-9 TTypeConstructor "Foo" -9:12-15 TDataConstructor "Foo" -9:18-21 TRecordField "foo" -9:25-28 TTypeConstructor "Int" -11:7-10 TClass "Boo" -11:11-12 TTypeVariable "a" -12:3-6 TClassMethod "boo" -12:10-11 TTypeVariable "a" -12:15-16 TTypeVariable "a" -14:10-13 TClass "Boo" -14:14-17 TTypeConstructor "Int" -15:5-8 TClassMethod "boo" -15:9-10 TVariable "x" -15:13-14 TVariable "x" -15:15-16 TOperator "+" -17:6-8 TTypeConstructor "Dd" -17:11-13 TDataConstructor "Dd" -17:14-17 TTypeConstructor "Int" -19:9-12 TPatternSynonym "One" -19:15-18 TDataConstructor "Foo" -21:1-4 TVariable "ggg" -21:7-10 TPatternSynonym "One" -23:6-9 TTypeConstructor "Doo" -23:12-15 TDataConstructor "Doo" -23:16-24 TModule "Prelude." -23:24-27 TTypeConstructor "Int" -24:6-10 TTypeSynonym "Bar1" -24:13-16 TTypeConstructor "Int" -25:6-10 TTypeSynonym "Bar2" -25:13-16 TTypeConstructor "Doo" -27:1-3 TFunction "bb" -27:8-11 TClass "Boo" -27:12-13 TTypeVariable "a" -27:18-19 TTypeVariable "a" -27:23-24 TTypeVariable "a" -28:1-3 TFunction "bb" -28:4-5 TVariable "x" -28:9-12 TClassMethod "boo" -28:13-14 TVariable "x" -29:1-3 TFunction "aa" -29:7-11 TTypeVariable "cool" -29:15-18 TTypeConstructor "Int" -29:22-26 TTypeVariable "cool" -30:1-3 TFunction "aa" -30:4-5 TVariable "x" -30:9-10 TVariable "c" -30:14-16 TFunction "aa" -30:17-18 TVariable "x" -30:19-20 TVariable "c" -31:12-14 TVariable "xx" -31:16-18 TVariable "yy" -32:11-13 TVariable "dd" -34:2-4 TVariable "zz" -34:6-8 TVariable "kk" -35:1-3 TFunction "cc" -35:7-10 TTypeConstructor "Foo" -35:15-18 TTypeConstructor "Int" -35:20-23 TTypeConstructor "Int" -35:28-31 TTypeConstructor "Int" -36:1-3 TFunction "cc" -36:4-5 TVariable "f" -36:7-9 TVariable "gg" -36:11-13 TVariable "vv" -37:10-12 TVariable "gg" -38:14-17 TRecordField "foo" -38:18-19 TOperator "$" -38:20-21 TVariable "f" -38:24-27 TRecordField "foo" -39:14-17 TRecordField "foo" -39:18-19 TOperator "$" -39:20-21 TVariable "f" -39:24-27 TRecordField "foo" -41:1-3 TFunction "go" -41:6-9 TRecordField "foo" -42:1-4 TFunction "add" -42:8-16 TModule "Prelude." -42:16-17 TOperator "+" -47:1-5 TVariable "main" -47:9-11 TTypeConstructor "IO" -48:1-5 TVariable "main" -48:8-16 TFunction "putStrLn" +[1:1-14 HsSyntacticTokenType TComment "-- patter syn"] +[2:1-33 HsSyntacticTokenType TComment "{-# LANGUAGE PatternSynonyms #-}"] +[4:1-7 HsSyntacticTokenType TKeyword "module"] +[4:13-18 HsSyntacticTokenType TKeyword "where"] +[6:1-33 HsSyntacticTokenType TComment "-- import Data.Set (Set, insert)"] +[9:1-5 HsSyntacticTokenType TKeyword "data"] +[9:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[9:10-11 HsSyntacticTokenType TKeyword "="] +[9:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[9:16-17 HsSyntacticTokenType TKeyword "{"] +[9:18-21 HsSyntacticTokenType TRecordSelector "foo",9:18-21 HsSemanticTokenType TRecordField "foo"] +[9:22-24 HsSyntacticTokenType TKeyword "::"] +[9:25-28 HsSemanticTokenType TTypeConstructor "Int"] +[9:29-30 HsSyntacticTokenType TKeyword "}"] +[11:1-6 HsSyntacticTokenType TKeyword "class"] +[11:7-10 HsSemanticTokenType TClass "Boo"] +[11:11-12 HsSemanticTokenType TTypeVariable "a"] +[11:13-18 HsSyntacticTokenType TKeyword "where"] +[12:3-6 HsSemanticTokenType TClassMethod "boo"] +[12:7-9 HsSyntacticTokenType TKeyword "::"] +[12:10-11 HsSemanticTokenType TTypeVariable "a"] +[12:15-16 HsSemanticTokenType TTypeVariable "a"] +[14:1-9 HsSyntacticTokenType TKeyword "instance"] +[14:10-13 HsSemanticTokenType TClass "Boo"] +[14:14-17 HsSemanticTokenType TTypeConstructor "Int"] +[14:18-23 HsSyntacticTokenType TKeyword "where"] +[15:5-8 HsSemanticTokenType TClassMethod "boo"] +[15:9-10 HsSemanticTokenType TVariable "x"] +[15:11-12 HsSyntacticTokenType TKeyword "="] +[15:13-14 HsSemanticTokenType TVariable "x"] +[15:15-16 HsSemanticTokenType TOperator "+"] +[15:17-18 HsSyntacticTokenType TNumberLit "1"] +[17:1-5 HsSyntacticTokenType TKeyword "data"] +[17:6-8 HsSemanticTokenType TTypeConstructor "Dd"] +[17:9-10 HsSyntacticTokenType TKeyword "="] +[17:11-13 HsSemanticTokenType TDataConstructor "Dd"] +[17:14-17 HsSemanticTokenType TTypeConstructor "Int"] +[19:1-8 HsSyntacticTokenType TKeyword "pattern"] +[19:9-12 HsSemanticTokenType TPatternSynonym "One"] +[19:13-14 HsSyntacticTokenType TKeyword "="] +[19:15-18 HsSemanticTokenType TDataConstructor "Foo"] +[21:1-4 HsSemanticTokenType TVariable "ggg"] +[21:5-6 HsSyntacticTokenType TKeyword "="] +[21:7-10 HsSemanticTokenType TPatternSynonym "One"] +[23:1-5 HsSyntacticTokenType TKeyword "data"] +[23:6-9 HsSemanticTokenType TTypeConstructor "Doo"] +[23:10-11 HsSyntacticTokenType TKeyword "="] +[23:12-15 HsSemanticTokenType TDataConstructor "Doo"] +[23:16-24 HsSemanticTokenType TModule "Prelude."] +[23:24-27 HsSemanticTokenType TTypeConstructor "Int"] +[24:1-5 HsSyntacticTokenType TKeyword "type"] +[24:6-10 HsSemanticTokenType TTypeSynonym "Bar1"] +[24:11-12 HsSyntacticTokenType TKeyword "="] +[24:13-16 HsSemanticTokenType TTypeConstructor "Int"] +[25:1-5 HsSyntacticTokenType TKeyword "type"] +[25:6-10 HsSemanticTokenType TTypeSynonym "Bar2"] +[25:11-12 HsSyntacticTokenType TKeyword "="] +[25:13-16 HsSemanticTokenType TTypeConstructor "Doo"] +[27:1-3 HsSemanticTokenType TFunction "bb"] +[27:4-6 HsSyntacticTokenType TKeyword "::"] +[27:8-11 HsSemanticTokenType TClass "Boo"] +[27:12-13 HsSemanticTokenType TTypeVariable "a"] +[27:18-19 HsSemanticTokenType TTypeVariable "a"] +[27:23-24 HsSemanticTokenType TTypeVariable "a"] +[28:1-3 HsSemanticTokenType TFunction "bb"] +[28:4-5 HsSemanticTokenType TVariable "x"] +[28:7-8 HsSyntacticTokenType TKeyword "="] +[28:9-12 HsSemanticTokenType TClassMethod "boo"] +[28:13-14 HsSemanticTokenType TVariable "x"] +[29:1-3 HsSemanticTokenType TFunction "aa"] +[29:4-6 HsSyntacticTokenType TKeyword "::"] +[29:7-11 HsSemanticTokenType TTypeVariable "cool"] +[29:15-18 HsSemanticTokenType TTypeConstructor "Int"] +[29:22-26 HsSemanticTokenType TTypeVariable "cool"] +[30:1-3 HsSemanticTokenType TFunction "aa"] +[30:4-5 HsSemanticTokenType TVariable "x"] +[30:6-7 HsSyntacticTokenType TKeyword "="] +[30:8-9 HsSyntacticTokenType TKeyword "\\"] +[30:9-10 HsSemanticTokenType TVariable "c"] +[30:11-13 HsSyntacticTokenType TKeyword "->"] +[30:14-16 HsSemanticTokenType TFunction "aa"] +[30:17-18 HsSemanticTokenType TVariable "x"] +[30:19-20 HsSemanticTokenType TVariable "c"] +[31:5-10 HsSyntacticTokenType TKeyword "where"] +[31:11-12 HsSyntacticTokenType TKeyword "("] +[31:12-14 HsSemanticTokenType TVariable "xx"] +[31:16-18 HsSemanticTokenType TVariable "yy"] +[31:18-19 HsSyntacticTokenType TKeyword ")"] +[31:20-21 HsSyntacticTokenType TKeyword "="] +[31:22-23 HsSyntacticTokenType TKeyword "("] +[31:23-24 HsSyntacticTokenType TNumberLit "1"] +[31:26-27 HsSyntacticTokenType TNumberLit "2"] +[31:27-28 HsSyntacticTokenType TKeyword ")"] +[32:11-13 HsSemanticTokenType TVariable "dd"] +[32:14-15 HsSyntacticTokenType TKeyword "="] +[32:16-17 HsSyntacticTokenType TNumberLit "1"] +[34:1-2 HsSyntacticTokenType TKeyword "("] +[34:2-4 HsSemanticTokenType TVariable "zz"] +[34:6-8 HsSemanticTokenType TVariable "kk"] +[34:8-9 HsSyntacticTokenType TKeyword ")"] +[34:10-11 HsSyntacticTokenType TKeyword "="] +[34:12-13 HsSyntacticTokenType TKeyword "("] +[34:13-14 HsSyntacticTokenType TNumberLit "1"] +[34:16-17 HsSyntacticTokenType TNumberLit "2"] +[34:17-18 HsSyntacticTokenType TKeyword ")"] +[35:1-3 HsSemanticTokenType TFunction "cc"] +[35:4-6 HsSyntacticTokenType TKeyword "::"] +[35:7-10 HsSemanticTokenType TTypeConstructor "Foo"] +[35:15-18 HsSemanticTokenType TTypeConstructor "Int"] +[35:20-23 HsSemanticTokenType TTypeConstructor "Int"] +[35:28-31 HsSemanticTokenType TTypeConstructor "Int"] +[36:1-3 HsSemanticTokenType TFunction "cc"] +[36:4-5 HsSemanticTokenType TVariable "f"] +[36:6-7 HsSyntacticTokenType TKeyword "("] +[36:7-9 HsSemanticTokenType TVariable "gg"] +[36:11-13 HsSemanticTokenType TVariable "vv"] +[36:13-14 HsSyntacticTokenType TKeyword ")"] +[36:14-15 HsSyntacticTokenType TKeyword "="] +[37:10-12 HsSemanticTokenType TVariable "gg"] +[38:11-13 HsSyntacticTokenType TKeyword "->"] +[38:14-17 HsSyntacticTokenType TRecordSelector "foo",38:14-17 HsSemanticTokenType TRecordField "foo"] +[38:18-19 HsSemanticTokenType TOperator "$"] +[38:20-21 HsSemanticTokenType TVariable "f"] +[38:22-23 HsSyntacticTokenType TKeyword "{"] +[38:24-27 HsSyntacticTokenType TRecordSelector "foo",38:24-27 HsSemanticTokenType TRecordField "foo"] +[38:28-29 HsSyntacticTokenType TKeyword "="] +[38:30-31 HsSyntacticTokenType TNumberLit "1"] +[38:32-33 HsSyntacticTokenType TKeyword "}"] +[39:11-13 HsSyntacticTokenType TKeyword "->"] +[39:14-17 HsSyntacticTokenType TRecordSelector "foo",39:14-17 HsSemanticTokenType TRecordField "foo"] +[39:18-19 HsSemanticTokenType TOperator "$"] +[39:20-21 HsSemanticTokenType TVariable "f"] +[39:22-23 HsSyntacticTokenType TKeyword "{"] +[39:24-27 HsSyntacticTokenType TRecordSelector "foo",39:24-27 HsSemanticTokenType TRecordField "foo"] +[39:28-29 HsSyntacticTokenType TKeyword "="] +[39:30-31 HsSyntacticTokenType TNumberLit "1"] +[39:32-33 HsSyntacticTokenType TKeyword "}"] +[41:1-3 HsSemanticTokenType TFunction "go"] +[41:4-5 HsSyntacticTokenType TKeyword "="] +[41:6-9 HsSyntacticTokenType TRecordSelector "foo",41:6-9 HsSemanticTokenType TRecordField "foo"] +[42:1-4 HsSemanticTokenType TFunction "add"] +[42:5-6 HsSyntacticTokenType TKeyword "="] +[42:8-16 HsSemanticTokenType TModule "Prelude."] +[42:16-17 HsSemanticTokenType TOperator "+"] +[44:1-28 HsSyntacticTokenType TComment "-- sub :: Int -> Int -> Int"] +[45:1-21 HsSyntacticTokenType TComment "-- sub x y = add x y"] +[47:1-5 HsSemanticTokenType TVariable "main"] +[47:6-8 HsSyntacticTokenType TKeyword "::"] +[47:9-11 HsSemanticTokenType TTypeConstructor "IO"] +[48:1-5 HsSemanticTokenType TVariable "main"] +[48:6-7 HsSyntacticTokenType TKeyword "="] +[48:8-16 HsSemanticTokenType TFunction "putStrLn"] +[48:17-34 HsSyntacticTokenType TStringLit "\"Hello, Haskell!\""] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClass.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClass.expected index e369963b0e..36d91b0374 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClass.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClass.expected @@ -1,5 +1,10 @@ -4:7-10 TClass "Foo" -4:11-12 TTypeVariable "a" -5:3-6 TClassMethod "foo" -5:10-11 TTypeVariable "a" -5:15-18 TTypeConstructor "Int" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:15-20 HsSyntacticTokenType TKeyword "where"] +[4:1-6 HsSyntacticTokenType TKeyword "class"] +[4:7-10 HsSemanticTokenType TClass "Foo"] +[4:11-12 HsSemanticTokenType TTypeVariable "a"] +[4:13-18 HsSyntacticTokenType TKeyword "where"] +[5:3-6 HsSemanticTokenType TClassMethod "foo"] +[5:7-9 HsSyntacticTokenType TKeyword "::"] +[5:10-11 HsSemanticTokenType TTypeVariable "a"] +[5:15-18 HsSemanticTokenType TTypeConstructor "Int"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClassImportedDeriving.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClassImportedDeriving.expected index 3bbeb3e66c..631925cf5e 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClassImportedDeriving.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TClassImportedDeriving.expected @@ -1,3 +1,14 @@ -4:6-9 TTypeConstructor "Foo" -4:12-15 TDataConstructor "Foo" -4:26-30 TClass "Show" +[1:1-36 HsSyntacticTokenType TComment "{-# LANGUAGE StandaloneDeriving #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:31-36 HsSyntacticTokenType TKeyword "where"] +[3:1-50 HsSyntacticTokenType TComment "-- deriving method source span of Show occurrence"] +[4:1-5 HsSyntacticTokenType TKeyword "data"] +[4:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[4:10-11 HsSyntacticTokenType TKeyword "="] +[4:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[4:16-24 HsSyntacticTokenType TKeyword "deriving"] +[4:26-30 HsSemanticTokenType TClass "Show"] +[6:1-55 HsSyntacticTokenType TComment "-- standalone deriving method not in the same position"] +[7:1-28 HsSyntacticTokenType TComment "-- deriving instance Eq Foo"] +[9:1-27 HsSyntacticTokenType TComment "-- a :: Foo -> Foo -> Bool"] +[10:1-12 HsSyntacticTokenType TComment "-- a = (==)"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataFamily.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataFamily.expected index c95c0689f0..e816a3db66 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataFamily.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataFamily.expected @@ -1,12 +1,29 @@ -5:13-18 TTypeFamily "XList" -5:19-20 TTypeVariable "a" -8:15-20 TTypeFamily "XList" -8:21-25 TTypeConstructor "Char" -8:28-33 TDataConstructor "XCons" -8:35-39 TTypeConstructor "Char" -8:42-47 TTypeFamily "XList" -8:48-52 TTypeConstructor "Char" -8:56-60 TDataConstructor "XNil" -11:15-20 TTypeFamily "XList" -11:26-35 TDataConstructor "XListUnit" -11:37-40 TTypeConstructor "Int" +[1:1-30 HsSyntacticTokenType TComment "{-# LANGUAGE TypeFamilies #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:20-25 HsSyntacticTokenType TKeyword "where"] +[4:1-35 HsSyntacticTokenType TComment "-- Declare a list-like data family"] +[5:1-5 HsSyntacticTokenType TKeyword "data"] +[5:6-12 HsSyntacticTokenType TKeyword "family"] +[5:13-18 HsSemanticTokenType TTypeFamily "XList"] +[5:19-20 HsSemanticTokenType TTypeVariable "a"] +[7:1-41 HsSyntacticTokenType TComment "-- Declare a list-like instance for Char"] +[8:1-5 HsSyntacticTokenType TKeyword "data"] +[8:6-14 HsSyntacticTokenType TKeyword "instance"] +[8:15-20 HsSemanticTokenType TTypeFamily "XList"] +[8:21-25 HsSemanticTokenType TTypeConstructor "Char"] +[8:26-27 HsSyntacticTokenType TKeyword "="] +[8:28-33 HsSemanticTokenType TDataConstructor "XCons"] +[8:34-35 HsSyntacticTokenType TKeyword "!"] +[8:35-39 HsSemanticTokenType TTypeConstructor "Char"] +[8:40-41 HsSyntacticTokenType TKeyword "!"] +[8:42-47 HsSemanticTokenType TTypeFamily "XList"] +[8:48-52 HsSemanticTokenType TTypeConstructor "Char"] +[8:56-60 HsSemanticTokenType TDataConstructor "XNil"] +[10:1-41 HsSyntacticTokenType TComment "-- Declare a number-like instance for ()"] +[11:1-5 HsSyntacticTokenType TKeyword "data"] +[11:6-14 HsSyntacticTokenType TKeyword "instance"] +[11:15-20 HsSemanticTokenType TTypeFamily "XList"] +[11:24-25 HsSyntacticTokenType TKeyword "="] +[11:26-35 HsSemanticTokenType TDataConstructor "XListUnit"] +[11:36-37 HsSyntacticTokenType TKeyword "!"] +[11:37-40 HsSemanticTokenType TTypeConstructor "Int"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataType.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataType.expected index bdf280c45e..a2719f9035 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataType.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDataType.expected @@ -1,4 +1,9 @@ -3:6-9 TTypeConstructor "Foo" -3:12-15 TDataConstructor "Foo" -3:16-19 TTypeConstructor "Int" -3:30-32 TClass "Eq" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-5 HsSyntacticTokenType TKeyword "data"] +[3:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[3:10-11 HsSyntacticTokenType TKeyword "="] +[3:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[3:16-19 HsSemanticTokenType TTypeConstructor "Int"] +[3:20-28 HsSyntacticTokenType TKeyword "deriving"] +[3:30-32 HsSemanticTokenType TClass "Eq"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDatatypeImported.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDatatypeImported.expected index 2c2cd492a0..85268775f7 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDatatypeImported.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDatatypeImported.expected @@ -1,5 +1,11 @@ -3:8-17 TModule "System.IO" -5:1-3 TVariable "go" -5:7-9 TTypeConstructor "IO" -6:1-3 TVariable "go" -6:6-11 TFunction "print" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:26-31 HsSyntacticTokenType TKeyword "where"] +[3:1-7 HsSyntacticTokenType TKeyword "import"] +[3:8-17 HsSemanticTokenType TModule "System.IO"] +[5:1-3 HsSemanticTokenType TVariable "go"] +[5:4-6 HsSyntacticTokenType TKeyword "::"] +[5:7-9 HsSemanticTokenType TTypeConstructor "IO"] +[6:1-3 HsSemanticTokenType TVariable "go"] +[6:4-5 HsSyntacticTokenType TKeyword "="] +[6:6-11 HsSemanticTokenType TFunction "print"] +[6:12-13 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDoc.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDoc.expected index 405308c3c8..668d88ae43 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDoc.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TDoc.expected @@ -1,5 +1,12 @@ -4:5-10 TVariable "hello" -5:1-6 TVariable "hello" -5:10-13 TTypeConstructor "Int" -6:1-6 TVariable "hello" -6:9-15 TClassMethod "length" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:13-18 HsSyntacticTokenType TKeyword "where"] +[3:1-5 HsSyntacticTokenType TComment "-- |"] +[4:1-11 HsSyntacticTokenType TComment "-- `hello`"] +[4:5-10 HsSemanticTokenType TVariable "hello"] +[5:1-6 HsSemanticTokenType TVariable "hello"] +[5:7-9 HsSyntacticTokenType TKeyword "::"] +[5:10-13 HsSemanticTokenType TTypeConstructor "Int"] +[6:1-6 HsSemanticTokenType TVariable "hello"] +[6:7-8 HsSyntacticTokenType TKeyword "="] +[6:9-15 HsSemanticTokenType TClassMethod "length"] +[6:16-33 HsSyntacticTokenType TStringLit "\"Hello, Haskell!\""] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunction.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunction.expected index f34510728b..511f09f78b 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunction.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunction.expected @@ -1,11 +1,19 @@ -3:1-2 TFunction "f" -3:13-14 TTypeVariable "a" -3:16-17 TTypeVariable "a" -3:21-22 TTypeVariable "a" -4:1-2 TFunction "f" -4:3-4 TVariable "x" -4:7-8 TVariable "x" -6:1-2 TVariable "x" -6:6-7 TTypeVariable "a" -7:1-2 TVariable "x" -7:5-14 TVariable "undefined" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TFunction "f"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-12 HsSyntacticTokenType TKeyword "forall"] +[3:13-14 HsSemanticTokenType TTypeVariable "a"] +[3:14-15 HsSyntacticTokenType TKeyword "."] +[3:16-17 HsSemanticTokenType TTypeVariable "a"] +[3:21-22 HsSemanticTokenType TTypeVariable "a"] +[4:1-2 HsSemanticTokenType TFunction "f"] +[4:3-4 HsSemanticTokenType TVariable "x"] +[4:5-6 HsSyntacticTokenType TKeyword "="] +[4:7-8 HsSemanticTokenType TVariable "x"] +[6:1-2 HsSemanticTokenType TVariable "x"] +[6:3-5 HsSyntacticTokenType TKeyword "::"] +[6:6-7 HsSemanticTokenType TTypeVariable "a"] +[7:1-2 HsSemanticTokenType TVariable "x"] +[7:3-4 HsSyntacticTokenType TKeyword "="] +[7:5-14 HsSemanticTokenType TVariable "undefined"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLet.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLet.expected index 3f27b723db..9830a147eb 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLet.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLet.expected @@ -1,5 +1,12 @@ -3:1-2 TVariable "y" -3:6-9 TTypeConstructor "Int" -4:1-2 TVariable "y" -4:9-10 TFunction "f" -4:11-12 TVariable "x" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:21-26 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TVariable "y"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-9 HsSemanticTokenType TTypeConstructor "Int"] +[4:1-2 HsSemanticTokenType TVariable "y"] +[4:3-4 HsSyntacticTokenType TKeyword "="] +[4:9-10 HsSemanticTokenType TFunction "f"] +[4:11-12 HsSemanticTokenType TVariable "x"] +[4:13-14 HsSyntacticTokenType TKeyword "="] +[4:15-16 HsSyntacticTokenType TNumberLit "1"] +[4:20-21 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLocal.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLocal.expected index 176606e396..99717d4294 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLocal.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionLocal.expected @@ -1,7 +1,15 @@ -3:1-2 TFunction "f" -3:6-9 TTypeConstructor "Int" -3:13-16 TTypeConstructor "Int" -4:1-2 TFunction "f" -4:7-8 TFunction "g" -6:5-6 TFunction "g" -6:7-8 TVariable "x" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:23-28 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TFunction "f"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:6-9 HsSemanticTokenType TTypeConstructor "Int"] +[3:13-16 HsSemanticTokenType TTypeConstructor "Int"] +[4:1-2 HsSemanticTokenType TFunction "f"] +[4:5-6 HsSyntacticTokenType TKeyword "="] +[4:7-8 HsSemanticTokenType TFunction "g"] +[4:9-10 HsSyntacticTokenType TNumberLit "1"] +[5:3-8 HsSyntacticTokenType TKeyword "where"] +[6:5-6 HsSemanticTokenType TFunction "g"] +[6:7-8 HsSemanticTokenType TVariable "x"] +[6:9-10 HsSyntacticTokenType TKeyword "="] +[6:11-12 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionUnderTypeSynonym.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionUnderTypeSynonym.expected index 010cf0c613..434227b838 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionUnderTypeSynonym.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TFunctionUnderTypeSynonym.expected @@ -1,17 +1,29 @@ -3:6-8 TTypeSynonym "T1" -3:11-14 TTypeConstructor "Int" -3:18-21 TTypeConstructor "Int" -4:6-8 TTypeSynonym "T2" -4:18-19 TTypeVariable "a" -4:21-22 TTypeVariable "a" -4:26-27 TTypeVariable "a" -5:1-3 TFunction "f1" -5:7-9 TTypeSynonym "T1" -6:1-3 TFunction "f1" -6:4-5 TVariable "x" -6:8-9 TVariable "x" -7:1-3 TFunction "f2" -7:7-9 TTypeSynonym "T2" -8:1-3 TFunction "f2" -8:4-5 TVariable "x" -8:8-9 TVariable "x" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:34-39 HsSyntacticTokenType TKeyword "where"] +[3:1-5 HsSyntacticTokenType TKeyword "type"] +[3:6-8 HsSemanticTokenType TTypeSynonym "T1"] +[3:9-10 HsSyntacticTokenType TKeyword "="] +[3:11-14 HsSemanticTokenType TTypeConstructor "Int"] +[3:18-21 HsSemanticTokenType TTypeConstructor "Int"] +[4:1-5 HsSyntacticTokenType TKeyword "type"] +[4:6-8 HsSemanticTokenType TTypeSynonym "T2"] +[4:9-10 HsSyntacticTokenType TKeyword "="] +[4:11-17 HsSyntacticTokenType TKeyword "forall"] +[4:18-19 HsSemanticTokenType TTypeVariable "a"] +[4:19-20 HsSyntacticTokenType TKeyword "."] +[4:21-22 HsSemanticTokenType TTypeVariable "a"] +[4:26-27 HsSemanticTokenType TTypeVariable "a"] +[5:1-3 HsSemanticTokenType TFunction "f1"] +[5:4-6 HsSyntacticTokenType TKeyword "::"] +[5:7-9 HsSemanticTokenType TTypeSynonym "T1"] +[6:1-3 HsSemanticTokenType TFunction "f1"] +[6:4-5 HsSemanticTokenType TVariable "x"] +[6:6-7 HsSyntacticTokenType TKeyword "="] +[6:8-9 HsSemanticTokenType TVariable "x"] +[7:1-3 HsSemanticTokenType TFunction "f2"] +[7:4-6 HsSyntacticTokenType TKeyword "::"] +[7:7-9 HsSemanticTokenType TTypeSynonym "T2"] +[8:1-3 HsSemanticTokenType TFunction "f2"] +[8:4-5 HsSemanticTokenType TVariable "x"] +[8:6-7 HsSyntacticTokenType TKeyword "="] +[8:8-9 HsSemanticTokenType TVariable "x"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TGADT.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TGADT.expected index ad3ac0f086..5800cf44da 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TGADT.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TGADT.expected @@ -1,13 +1,22 @@ -5:6-9 TTypeConstructor "Lam" -6:3-7 TDataConstructor "Lift" -6:11-12 TTypeVariable "a" -6:36-39 TTypeConstructor "Lam" -6:40-41 TTypeVariable "a" -7:3-6 TDataConstructor "Lam" -7:12-15 TTypeConstructor "Lam" -7:16-17 TTypeVariable "a" -7:21-24 TTypeConstructor "Lam" -7:25-26 TTypeVariable "b" -7:36-39 TTypeConstructor "Lam" -7:41-42 TTypeVariable "a" -7:46-47 TTypeVariable "b" +[1:1-30 HsSyntacticTokenType TComment "{-# LANGUAGE TypeFamilies #-}"] +[2:1-23 HsSyntacticTokenType TComment "{-# LANGUAGE GADTs #-}"] +[3:1-7 HsSyntacticTokenType TKeyword "module"] +[3:14-19 HsSyntacticTokenType TKeyword "where"] +[5:1-5 HsSyntacticTokenType TKeyword "data"] +[5:6-9 HsSemanticTokenType TTypeConstructor "Lam"] +[5:10-12 HsSyntacticTokenType TKeyword "::"] +[5:20-25 HsSyntacticTokenType TKeyword "where"] +[6:3-7 HsSemanticTokenType TDataConstructor "Lift"] +[6:11-12 HsSemanticTokenType TTypeVariable "a"] +[6:36-39 HsSemanticTokenType TTypeConstructor "Lam"] +[6:40-41 HsSemanticTokenType TTypeVariable "a"] +[6:49-66 HsSyntacticTokenType TComment "-- ^ lifted value"] +[7:3-6 HsSemanticTokenType TDataConstructor "Lam"] +[7:12-15 HsSemanticTokenType TTypeConstructor "Lam"] +[7:16-17 HsSemanticTokenType TTypeVariable "a"] +[7:21-24 HsSemanticTokenType TTypeConstructor "Lam"] +[7:25-26 HsSemanticTokenType TTypeVariable "b"] +[7:36-39 HsSemanticTokenType TTypeConstructor "Lam"] +[7:41-42 HsSemanticTokenType TTypeVariable "a"] +[7:46-47 HsSemanticTokenType TTypeVariable "b"] +[7:49-72 HsSyntacticTokenType TComment "-- ^ lambda abstraction"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodBind.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodBind.expected index a4a6ef98e0..723468732d 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodBind.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodBind.expected @@ -1,7 +1,14 @@ -4:6-9 TTypeConstructor "Foo" -4:12-15 TDataConstructor "Foo" -4:16-19 TTypeConstructor "Int" -5:10-14 TClass "Show" -5:15-18 TTypeConstructor "Foo" -6:5-9 TClassMethod "show" -6:12-21 TVariable "undefined" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:33-38 HsSyntacticTokenType TKeyword "where"] +[4:1-5 HsSyntacticTokenType TKeyword "data"] +[4:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[4:10-11 HsSyntacticTokenType TKeyword "="] +[4:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[4:16-19 HsSemanticTokenType TTypeConstructor "Int"] +[5:1-9 HsSyntacticTokenType TKeyword "instance"] +[5:10-14 HsSemanticTokenType TClass "Show"] +[5:15-18 HsSemanticTokenType TTypeConstructor "Foo"] +[5:19-24 HsSyntacticTokenType TKeyword "where"] +[6:5-9 HsSemanticTokenType TClassMethod "show"] +[6:10-11 HsSyntacticTokenType TKeyword "="] +[6:12-21 HsSemanticTokenType TVariable "undefined"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodUse.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodUse.expected index 2bf39be435..c611ab0fe1 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodUse.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TInstanceClassMethodUse.expected @@ -1,2 +1,5 @@ -4:1-3 TFunction "go" -4:8-12 TClassMethod "show" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:32-37 HsSyntacticTokenType TKeyword "where"] +[4:1-3 HsSemanticTokenType TFunction "go"] +[4:5-6 HsSyntacticTokenType TKeyword "="] +[4:8-12 HsSemanticTokenType TClassMethod "show"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TNoneFunctionWithConstraint.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TNoneFunctionWithConstraint.expected index 2dd89fd1da..f938c07fef 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TNoneFunctionWithConstraint.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TNoneFunctionWithConstraint.expected @@ -1,6 +1,10 @@ -3:1-2 TVariable "x" -3:7-9 TClass "Eq" -3:10-11 TTypeVariable "a" -3:16-17 TTypeVariable "a" -4:1-2 TVariable "x" -4:5-14 TVariable "undefined" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:36-41 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSemanticTokenType TVariable "x"] +[3:3-5 HsSyntacticTokenType TKeyword "::"] +[3:7-9 HsSemanticTokenType TClass "Eq"] +[3:10-11 HsSemanticTokenType TTypeVariable "a"] +[3:16-17 HsSemanticTokenType TTypeVariable "a"] +[4:1-2 HsSemanticTokenType TVariable "x"] +[4:3-4 HsSyntacticTokenType TKeyword "="] +[4:5-14 HsSemanticTokenType TVariable "undefined"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TOperator.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TOperator.expected index c19e7cb904..a66ea8787e 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TOperator.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TOperator.expected @@ -1,33 +1,52 @@ -4:1-3 TFunction "go" -4:4-5 TFunction "f" -4:6-7 TVariable "x" -4:10-11 TFunction "f" -4:11-12 TOperator "$" -4:12-13 TVariable "x" -6:2-6 TOperator "$$$$" -7:1-2 TVariable "x" -7:7-11 TOperator "$$$$" -8:6-7 TTypeVariable "a" -8:8-11 TOperator ":+:" -8:12-13 TTypeVariable "b" -8:16-19 TDataConstructor "Add" -8:20-21 TTypeVariable "a" -8:22-23 TTypeVariable "b" -9:7-10 TOperator ":-:" -9:12-13 TTypeVariable "a" -9:14-15 TTypeVariable "b" -9:19-20 TTypeVariable "a" -9:22-23 TTypeVariable "b" -11:1-4 TFunction "add" -11:8-11 TTypeConstructor "Int" -11:12-15 TOperator ":+:" -11:16-19 TTypeConstructor "Int" -11:23-26 TTypeConstructor "Int" -11:27-30 TOperator ":-:" -11:31-34 TTypeConstructor "Int" -13:1-4 TFunction "add" -13:6-9 TDataConstructor "Add" -13:10-11 TVariable "x" -13:12-13 TVariable "y" -13:18-19 TVariable "x" -13:21-22 TVariable "y" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-21 HsSyntacticTokenType TComment "-- imported operator"] +[4:1-3 HsSemanticTokenType TFunction "go"] +[4:4-5 HsSemanticTokenType TFunction "f"] +[4:6-7 HsSemanticTokenType TVariable "x"] +[4:8-9 HsSyntacticTokenType TKeyword "="] +[4:10-11 HsSemanticTokenType TFunction "f"] +[4:11-12 HsSemanticTokenType TOperator "$"] +[4:12-13 HsSemanticTokenType TVariable "x"] +[5:1-36 HsSyntacticTokenType TComment "-- operator defined in local module"] +[6:2-6 HsSemanticTokenType TOperator "$$$$"] +[6:8-9 HsSyntacticTokenType TKeyword "="] +[7:1-2 HsSemanticTokenType TVariable "x"] +[7:3-4 HsSyntacticTokenType TKeyword "="] +[7:5-6 HsSyntacticTokenType TNumberLit "1"] +[7:7-11 HsSemanticTokenType TOperator "$$$$"] +[7:12-13 HsSyntacticTokenType TNumberLit "2"] +[8:1-5 HsSyntacticTokenType TKeyword "data"] +[8:6-7 HsSemanticTokenType TTypeVariable "a"] +[8:8-11 HsSemanticTokenType TOperator ":+:"] +[8:12-13 HsSemanticTokenType TTypeVariable "b"] +[8:14-15 HsSyntacticTokenType TKeyword "="] +[8:16-19 HsSemanticTokenType TDataConstructor "Add"] +[8:20-21 HsSemanticTokenType TTypeVariable "a"] +[8:22-23 HsSemanticTokenType TTypeVariable "b"] +[9:1-5 HsSyntacticTokenType TKeyword "type"] +[9:7-10 HsSemanticTokenType TOperator ":-:"] +[9:12-13 HsSemanticTokenType TTypeVariable "a"] +[9:14-15 HsSemanticTokenType TTypeVariable "b"] +[9:16-17 HsSyntacticTokenType TKeyword "="] +[9:19-20 HsSemanticTokenType TTypeVariable "a"] +[9:22-23 HsSemanticTokenType TTypeVariable "b"] +[10:1-38 HsSyntacticTokenType TComment "-- type take precedence over operator"] +[11:1-4 HsSemanticTokenType TFunction "add"] +[11:5-7 HsSyntacticTokenType TKeyword "::"] +[11:8-11 HsSemanticTokenType TTypeConstructor "Int"] +[11:12-15 HsSemanticTokenType TOperator ":+:"] +[11:16-19 HsSemanticTokenType TTypeConstructor "Int"] +[11:23-26 HsSemanticTokenType TTypeConstructor "Int"] +[11:27-30 HsSemanticTokenType TOperator ":-:"] +[11:31-34 HsSemanticTokenType TTypeConstructor "Int"] +[12:1-46 HsSyntacticTokenType TComment "-- class method take precedence over operator"] +[13:1-4 HsSemanticTokenType TFunction "add"] +[13:6-9 HsSemanticTokenType TDataConstructor "Add"] +[13:10-11 HsSemanticTokenType TVariable "x"] +[13:12-13 HsSemanticTokenType TVariable "y"] +[13:15-16 HsSyntacticTokenType TKeyword "="] +[13:17-18 HsSyntacticTokenType TKeyword "("] +[13:18-19 HsSemanticTokenType TVariable "x"] +[13:21-22 HsSemanticTokenType TVariable "y"] +[13:22-23 HsSyntacticTokenType TKeyword ")"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternMatch.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternMatch.expected index 0535662e63..daad3c53ca 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternMatch.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternMatch.expected @@ -1,2 +1,8 @@ -4:1-2 TFunction "g" -4:4-11 TDataConstructor "Nothing" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:22-27 HsSyntacticTokenType TKeyword "where"] +[4:1-2 HsSemanticTokenType TFunction "g"] +[4:3-4 HsSyntacticTokenType TKeyword "("] +[4:4-11 HsSemanticTokenType TDataConstructor "Nothing"] +[4:14-15 HsSyntacticTokenType TKeyword ")"] +[4:16-17 HsSyntacticTokenType TKeyword "="] +[4:18-19 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternSynonym.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternSynonym.expected index 7cdf5260cb..277f79c9e1 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternSynonym.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternSynonym.expected @@ -1 +1,6 @@ -5:9-12 TPatternSynonym "Foo" +[1:1-33 HsSyntacticTokenType TComment "{-# LANGUAGE PatternSynonyms #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:24-29 HsSyntacticTokenType TKeyword "where"] +[5:1-8 HsSyntacticTokenType TKeyword "pattern"] +[5:9-12 HsSemanticTokenType TPatternSynonym "Foo"] +[5:13-14 HsSyntacticTokenType TKeyword "="] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternbind.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternbind.expected index 6c62634487..0a62728b59 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternbind.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TPatternbind.expected @@ -1,7 +1,17 @@ -3:2-3 TVariable "a" -3:5-6 TVariable "b" -5:1-2 TFunction "f" -5:3-4 TFunction "g" -5:5-6 TVariable "y" -5:9-10 TFunction "g" -5:11-12 TVariable "y" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:18-23 HsSyntacticTokenType TKeyword "where"] +[3:1-2 HsSyntacticTokenType TKeyword "("] +[3:2-3 HsSemanticTokenType TVariable "a"] +[3:5-6 HsSemanticTokenType TVariable "b"] +[3:6-7 HsSyntacticTokenType TKeyword ")"] +[3:8-9 HsSyntacticTokenType TKeyword "="] +[3:10-11 HsSyntacticTokenType TKeyword "("] +[3:11-12 HsSyntacticTokenType TNumberLit "1"] +[3:14-15 HsSyntacticTokenType TNumberLit "2"] +[3:15-16 HsSyntacticTokenType TKeyword ")"] +[5:1-2 HsSemanticTokenType TFunction "f"] +[5:3-4 HsSemanticTokenType TFunction "g"] +[5:5-6 HsSemanticTokenType TVariable "y"] +[5:7-8 HsSyntacticTokenType TKeyword "="] +[5:9-10 HsSemanticTokenType TFunction "g"] +[5:11-12 HsSemanticTokenType TVariable "y"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TQualifiedName.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TQualifiedName.expected index 0ca7cd7d5b..035ef7c732 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TQualifiedName.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TQualifiedName.expected @@ -1,12 +1,29 @@ -3:18-27 TModule "Data.List" -6:1-2 TVariable "a" -6:5-13 TModule "Prelude." -6:13-22 TVariable "undefined" -7:1-2 TVariable "b" -7:8-18 TModule "Data.List." -7:18-22 TClassMethod "elem" -8:1-2 TVariable "c" -8:6-14 TModule "Prelude." -8:14-15 TOperator "+" -9:1-2 TVariable "d" -9:6-7 TOperator "+" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:23-28 HsSyntacticTokenType TKeyword "where"] +[3:1-7 HsSyntacticTokenType TKeyword "import"] +[3:8-17 HsSyntacticTokenType TKeyword "qualified"] +[3:18-27 HsSemanticTokenType TModule "Data.List"] +[6:1-2 HsSemanticTokenType TVariable "a"] +[6:3-4 HsSyntacticTokenType TKeyword "="] +[6:5-13 HsSemanticTokenType TModule "Prelude."] +[6:13-22 HsSemanticTokenType TVariable "undefined"] +[7:1-2 HsSemanticTokenType TVariable "b"] +[7:3-4 HsSyntacticTokenType TKeyword "="] +[7:5-6 HsSyntacticTokenType TNumberLit "1"] +[7:8-18 HsSemanticTokenType TModule "Data.List."] +[7:18-22 HsSemanticTokenType TClassMethod "elem"] +[7:24-25 HsSyntacticTokenType TKeyword "["] +[7:25-26 HsSyntacticTokenType TNumberLit "1"] +[7:28-29 HsSyntacticTokenType TNumberLit "2"] +[7:29-30 HsSyntacticTokenType TKeyword "]"] +[8:1-2 HsSemanticTokenType TVariable "c"] +[8:3-4 HsSyntacticTokenType TKeyword "="] +[8:6-14 HsSemanticTokenType TModule "Prelude."] +[8:14-15 HsSemanticTokenType TOperator "+"] +[8:17-18 HsSyntacticTokenType TNumberLit "1"] +[8:19-20 HsSyntacticTokenType TNumberLit "1"] +[9:1-2 HsSemanticTokenType TVariable "d"] +[9:3-4 HsSyntacticTokenType TKeyword "="] +[9:6-7 HsSemanticTokenType TOperator "+"] +[9:9-10 HsSyntacticTokenType TNumberLit "1"] +[9:11-12 HsSyntacticTokenType TNumberLit "1"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecord.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecord.expected index 43b8e4d3b0..e097d8be34 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecord.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecord.expected @@ -1,4 +1,11 @@ -4:6-9 TTypeConstructor "Foo" -4:12-15 TDataConstructor "Foo" -4:18-21 TRecordField "foo" -4:25-28 TTypeConstructor "Int" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:16-21 HsSyntacticTokenType TKeyword "where"] +[4:1-5 HsSyntacticTokenType TKeyword "data"] +[4:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[4:10-11 HsSyntacticTokenType TKeyword "="] +[4:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[4:16-17 HsSyntacticTokenType TKeyword "{"] +[4:18-21 HsSyntacticTokenType TRecordSelector "foo",4:18-21 HsSemanticTokenType TRecordField "foo"] +[4:22-24 HsSyntacticTokenType TKeyword "::"] +[4:25-28 HsSemanticTokenType TTypeConstructor "Int"] +[4:29-30 HsSyntacticTokenType TKeyword "}"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecordDuplicateRecordFields.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecordDuplicateRecordFields.expected index 70fdc63e18..7d116f7825 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecordDuplicateRecordFields.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TRecordDuplicateRecordFields.expected @@ -1,4 +1,13 @@ -5:6-9 TTypeConstructor "Foo" -5:12-15 TDataConstructor "Foo" -5:18-21 TRecordField "boo" -5:26-32 TTypeSynonym "String" +[1:1-44 HsSyntacticTokenType TComment "{-# LANGUAGE DuplicateRecordFields #-}"] +[3:1-7 HsSyntacticTokenType TKeyword "module"] +[3:37-42 HsSyntacticTokenType TKeyword "where"] +[5:1-5 HsSyntacticTokenType TKeyword "data"] +[5:6-9 HsSemanticTokenType TTypeConstructor "Foo"] +[5:10-11 HsSyntacticTokenType TKeyword "="] +[5:12-15 HsSemanticTokenType TDataConstructor "Foo"] +[5:16-17 HsSyntacticTokenType TKeyword "{"] +[5:18-21 HsSyntacticTokenType TRecordSelector "boo",5:18-21 HsSemanticTokenType TRecordField "boo"] +[5:22-24 HsSyntacticTokenType TKeyword "::"] +[5:25-26 HsSyntacticTokenType TKeyword "!"] +[5:26-32 HsSemanticTokenType TTypeSynonym "String"] +[5:33-34 HsSyntacticTokenType TKeyword "}"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TTypefamily.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TTypefamily.expected index 08019bc3f3..4b8efcd07b 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TTypefamily.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TTypefamily.expected @@ -1,8 +1,16 @@ -4:13-16 TTypeFamily "Foo" -4:17-18 TTypeVariable "a" -5:3-6 TTypeFamily "Foo" -5:7-10 TTypeConstructor "Int" -5:13-16 TTypeConstructor "Int" -6:3-6 TTypeFamily "Foo" -6:7-8 TTypeVariable "a" -6:11-17 TTypeSynonym "String" +[1:1-30 HsSyntacticTokenType TComment "{-# LANGUAGE TypeFamilies #-}"] +[2:1-7 HsSyntacticTokenType TKeyword "module"] +[2:20-25 HsSyntacticTokenType TKeyword "where"] +[4:1-5 HsSyntacticTokenType TKeyword "type"] +[4:6-12 HsSyntacticTokenType TKeyword "family"] +[4:13-16 HsSemanticTokenType TTypeFamily "Foo"] +[4:17-18 HsSemanticTokenType TTypeVariable "a"] +[4:19-24 HsSyntacticTokenType TKeyword "where"] +[5:3-6 HsSemanticTokenType TTypeFamily "Foo"] +[5:7-10 HsSemanticTokenType TTypeConstructor "Int"] +[5:11-12 HsSyntacticTokenType TKeyword "="] +[5:13-16 HsSemanticTokenType TTypeConstructor "Int"] +[6:3-6 HsSemanticTokenType TTypeFamily "Foo"] +[6:7-8 HsSemanticTokenType TTypeVariable "a"] +[6:9-10 HsSyntacticTokenType TKeyword "="] +[6:11-17 HsSemanticTokenType TTypeSynonym "String"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TUnicodeSyntax.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TUnicodeSyntax.expected index 0b94b7c045..f06fed9a39 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TUnicodeSyntax.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TUnicodeSyntax.expected @@ -1 +1,5 @@ -3:1-4 TVariable "a\66560b" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:23-28 HsSyntacticTokenType TKeyword "where"] +[3:1-4 HsSemanticTokenType TVariable "a\66560b"] +[3:4-5 HsSyntacticTokenType TKeyword " "] +[3:6-10 HsSyntacticTokenType TStringLit " \"a\66560"] diff --git a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TValBind.expected b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TValBind.expected index ec20b01e56..f0bf77f829 100644 --- a/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TValBind.expected +++ b/plugins/hls-semantic-tokens-plugin/test/testdata/before_9_10/TValBind.expected @@ -1,4 +1,9 @@ -4:1-6 TVariable "hello" -4:10-13 TTypeConstructor "Int" -5:1-6 TVariable "hello" -5:9-15 TClassMethod "length" +[1:1-7 HsSyntacticTokenType TKeyword "module"] +[1:17-22 HsSyntacticTokenType TKeyword "where"] +[4:1-6 HsSemanticTokenType TVariable "hello"] +[4:7-9 HsSyntacticTokenType TKeyword "::"] +[4:10-13 HsSemanticTokenType TTypeConstructor "Int"] +[5:1-6 HsSemanticTokenType TVariable "hello"] +[5:7-8 HsSyntacticTokenType TKeyword "="] +[5:9-15 HsSemanticTokenType TClassMethod "length"] +[5:16-33 HsSyntacticTokenType TStringLit "\"Hello, Haskell!\""] diff --git a/test/testdata/schema/ghc910/default-config.golden.json b/test/testdata/schema/ghc910/default-config.golden.json index 3b4e687ef9..c8d9697451 100644 --- a/test/testdata/schema/ghc910/default-config.golden.json +++ b/test/testdata/schema/ghc910/default-config.golden.json @@ -134,21 +134,27 @@ }, "semanticTokens": { "config": { + "charLitToken": "string", "classMethodToken": "method", "classToken": "class", + "commentToken": "comment", "dataConstructorToken": "enumMember", "functionToken": "function", + "keywordToken": "keyword", "moduleToken": "namespace", + "numberLitToken": "number", "operatorToken": "operator", "patternSynonymToken": "macro", "recordFieldToken": "property", + "recordSelectorToken": "property", + "stringLitToken": "string", "typeConstructorToken": "enum", "typeFamilyToken": "interface", "typeSynonymToken": "type", "typeVariableToken": "typeParameter", "variableToken": "variable" }, - "globalOn": false + "globalOn": true }, "stan": { "globalOn": false diff --git a/test/testdata/schema/ghc910/markdown-reference.md b/test/testdata/schema/ghc910/markdown-reference.md index 668323ce66..3c3fafbe2a 100644 --- a/test/testdata/schema/ghc910/markdown-reference.md +++ b/test/testdata/schema/ghc910/markdown-reference.md @@ -51,6 +51,12 @@ | `recordFieldToken` | LSP semantic token type to use for record fields | `SemanticTokenTypes_Property` |
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator
SemanticTokenTypes_Namespace
SemanticTokenTypes_Type
SemanticTokenTypes_Class
SemanticTokenTypes_Enum
SemanticTokenTypes_Interface
SemanticTokenTypes_Struct
SemanticTokenTypes_TypeParameter
SemanticTokenTypes_Parameter
SemanticTokenTypes_Variable
SemanticTokenTypes_Property
SemanticTokenTypes_EnumMember
SemanticTokenTypes_Event
SemanticTokenTypes_Function
SemanticTokenTypes_Method
SemanticTokenTypes_Macro
SemanticTokenTypes_Keyword
SemanticTokenTypes_Modifier
SemanticTokenTypes_Comment
SemanticTokenTypes_String
SemanticTokenTypes_Number
SemanticTokenTypes_Regexp
SemanticTokenTypes_Operator
SemanticTokenTypes_Decorator