@@ -292,12 +292,12 @@ data SemanticTokens = SemanticTokens {
292292 _resultId :: Maybe Text ,
293293
294294 -- | The actual tokens.
295- _xdata :: List Word32
295+ _xdata :: List UInt
296296} deriving (Show , Read , Eq )
297297deriveJSON lspOptions ''SemanticTokens
298298
299299data SemanticTokensPartialResult = SemanticTokensPartialResult {
300- _xdata :: List Word32
300+ _xdata :: List UInt
301301}
302302deriveJSON lspOptions ''SemanticTokensPartialResult
303303
@@ -311,11 +311,11 @@ deriveJSON lspOptions ''SemanticTokensDeltaParams
311311
312312data SemanticTokensEdit = SemanticTokensEdit {
313313 -- | The start offset of the edit.
314- _start :: Word32 ,
314+ _start :: UInt ,
315315 -- | The count of elements to remove.
316- _deleteCount :: Word32 ,
316+ _deleteCount :: UInt ,
317317 -- | The elements to insert.
318- _xdata :: Maybe (List Word32 )
318+ _xdata :: Maybe (List UInt )
319319} deriving (Show , Read , Eq )
320320deriveJSON lspOptions ''SemanticTokensEdit
321321
@@ -359,9 +359,9 @@ deriveJSON lspOptions ''SemanticTokensWorkspaceClientCapabilities
359359-- | A single 'semantic token' as described in the LSP specification, using absolute positions.
360360-- This is the kind of token that is usually easiest for editors to produce.
361361data SemanticTokenAbsolute = SemanticTokenAbsolute {
362- line :: Word32 ,
363- startChar :: Word32 ,
364- length :: Word32 ,
362+ line :: UInt ,
363+ startChar :: UInt ,
364+ length :: UInt ,
365365 tokenType :: SemanticTokenTypes ,
366366 tokenModifiers :: [SemanticTokenModifiers ]
367367} deriving (Show , Read , Eq , Ord )
@@ -370,9 +370,9 @@ data SemanticTokenAbsolute = SemanticTokenAbsolute {
370370
371371-- | A single 'semantic token' as described in the LSP specification, using relative positions.
372372data SemanticTokenRelative = SemanticTokenRelative {
373- deltaLine :: Word32 ,
374- deltaStartChar :: Word32 ,
375- length :: Word32 ,
373+ deltaLine :: UInt ,
374+ deltaStartChar :: UInt ,
375+ length :: UInt ,
376376 tokenType :: SemanticTokenTypes ,
377377 tokenModifiers :: [SemanticTokenModifiers ]
378378} deriving (Show , Read , Eq , Ord )
@@ -385,7 +385,7 @@ relativizeTokens :: [SemanticTokenAbsolute] -> [SemanticTokenRelative]
385385relativizeTokens xs = DList. toList $ go 0 0 xs mempty
386386 where
387387 -- Pass an accumulator to make this tail-recursive
388- go :: Word32 -> Word32 -> [SemanticTokenAbsolute ] -> DList. DList SemanticTokenRelative -> DList. DList SemanticTokenRelative
388+ go :: UInt -> UInt -> [SemanticTokenAbsolute ] -> DList. DList SemanticTokenRelative -> DList. DList SemanticTokenRelative
389389 go _ _ [] acc = acc
390390 go lastLine lastChar (SemanticTokenAbsolute l c len ty mods: ts) acc =
391391 let
@@ -400,7 +400,7 @@ absolutizeTokens :: [SemanticTokenRelative] -> [SemanticTokenAbsolute]
400400absolutizeTokens xs = DList. toList $ go 0 0 xs mempty
401401 where
402402 -- Pass an accumulator to make this tail-recursive
403- go :: Word32 -> Word32 -> [SemanticTokenRelative ] -> DList. DList SemanticTokenAbsolute -> DList. DList SemanticTokenAbsolute
403+ go :: UInt -> UInt -> [SemanticTokenRelative ] -> DList. DList SemanticTokenAbsolute -> DList. DList SemanticTokenAbsolute
404404 go _ _ [] acc = acc
405405 go lastLine lastChar (SemanticTokenRelative dl dc len ty mods: ts) acc =
406406 let
@@ -410,18 +410,18 @@ absolutizeTokens xs = DList.toList $ go 0 0 xs mempty
410410 in go l c ts (DList. snoc acc (SemanticTokenAbsolute l c len ty mods))
411411
412412-- | Encode a series of relatively-positioned semantic tokens into an integer array following the given legend.
413- encodeTokens :: SemanticTokensLegend -> [SemanticTokenRelative ] -> Either Text [Word32 ]
413+ encodeTokens :: SemanticTokensLegend -> [SemanticTokenRelative ] -> Either Text [UInt ]
414414encodeTokens SemanticTokensLegend {_tokenTypes= List tts,_tokenModifiers= List tms} sts =
415415 DList. toList . DList. concat <$> traverse encodeToken sts
416416 where
417417 -- Note that there's no "fast" version of these (e.g. backed by an IntMap or similar)
418418 -- in general, due to the possibility of unknown token types which are only identified by strings.
419- tyMap :: Map. Map SemanticTokenTypes Word32
419+ tyMap :: Map. Map SemanticTokenTypes UInt
420420 tyMap = Map. fromList $ zip tts [0 .. ]
421421 modMap :: Map. Map SemanticTokenModifiers Int
422422 modMap = Map. fromList $ zip tms [0 .. ]
423423
424- lookupTy :: SemanticTokenTypes -> Either Text Word32
424+ lookupTy :: SemanticTokenTypes -> Either Text UInt
425425 lookupTy ty = case Map. lookup ty tyMap of
426426 Just tycode -> pure tycode
427427 Nothing -> throwError $ " Semantic token type " <> fromString (show ty) <> " did not appear in the legend"
@@ -431,17 +431,17 @@ encodeTokens SemanticTokensLegend{_tokenTypes=List tts,_tokenModifiers=List tms}
431431 Nothing -> throwError $ " Semantic token modifier " <> fromString (show modifier) <> " did not appear in the legend"
432432
433433 -- Use a DList here for better efficiency when concatenating all these together
434- encodeToken :: SemanticTokenRelative -> Either Text (DList. DList Word32 )
434+ encodeToken :: SemanticTokenRelative -> Either Text (DList. DList UInt )
435435 encodeToken (SemanticTokenRelative dl dc len ty mods) = do
436436 tycode <- lookupTy ty
437437 modcodes <- traverse lookupMod mods
438- let combinedModcode :: Word32 = foldl' Bits. setBit Bits. zeroBits modcodes
438+ let combinedModcode :: Int = foldl' Bits. setBit Bits. zeroBits modcodes
439439
440- pure [dl, dc, len, tycode, combinedModcode ]
440+ pure [dl, dc, len, tycode, fromIntegral combinedModcode ]
441441
442442-- This is basically 'SemanticTokensEdit', but slightly easier to work with.
443443-- | An edit to a buffer of items.
444- data Edit a = Edit { editStart :: Word32 , editDeleteCount :: Word32 , editInsertions :: [a ] }
444+ data Edit a = Edit { editStart :: UInt , editDeleteCount :: UInt , editInsertions :: [a ] }
445445 deriving (Read , Show , Eq , Ord )
446446
447447-- | Compute a list of edits that will turn the first list into the second list.
@@ -455,7 +455,7 @@ computeEdits l r = DList.toList $ go 0 Nothing (Diff.getGroupedDiff l r) mempty
455455 dump the 'Edit' into the accumulator.
456456 We need the index, because 'Edit's need to say where they start.
457457 -}
458- go :: Word32 -> Maybe (Edit a ) -> [Diff. Diff [a ]] -> DList. DList (Edit a ) -> DList. DList (Edit a )
458+ go :: UInt -> Maybe (Edit a ) -> [Diff. Diff [a ]] -> DList. DList (Edit a ) -> DList. DList (Edit a )
459459 -- No more diffs: append the current edit if there is one and return
460460 go _ e [] acc = acc <> DList. fromList (maybeToList e)
461461
0 commit comments