From baefa467a15701036d1e5c953ec03f921c2702ea Mon Sep 17 00:00:00 2001 From: Patrick Date: Sun, 31 Dec 2023 14:32:23 +0800 Subject: [PATCH 01/10] fix typo --- lsp-test/src/Language/LSP/Test.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lsp-test/src/Language/LSP/Test.hs b/lsp-test/src/Language/LSP/Test.hs index ddfdf679..eb06aca3 100644 --- a/lsp-test/src/Language/LSP/Test.hs +++ b/lsp-test/src/Language/LSP/Test.hs @@ -985,7 +985,7 @@ resolveRequestWithListResp method params = do rsp <- request method params pure $ absorbNull $ getResponseResult rsp --- | Pass a param and return the response from `prepareCallHierarchy` +-- | Pass a param and return the response from `semanticTokensFull` getSemanticTokens :: TextDocumentIdentifier -> Session (SemanticTokens |? Null) getSemanticTokens doc = do let params = SemanticTokensParams Nothing Nothing doc From b8f0908880e829f7122666e796078ae7bdd88d26 Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 16:48:27 +0800 Subject: [PATCH 02/10] update Data.Text.Utf16.Rope to Data.Text.Utf16.Rope.Mixed --- lsp/src/Language/LSP/VFS.hs | 92 ++++++++++--------------------------- lsp/test/VspSpec.hs | 6 +-- 2 files changed, 27 insertions(+), 71 deletions(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index ecf09599..f1035b99 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -82,9 +82,10 @@ import Data.Text (Text) import Data.Text qualified as T import Data.Text.IO qualified as T import Data.Text.Prettyprint.Doc hiding (line) -import Data.Text.Rope qualified as URope -import Data.Text.Utf16.Rope (Rope) -import Data.Text.Utf16.Rope qualified as Rope +import Data.Text.Lines as Char ( Position(..) ) +import Data.Text.Utf16.Lines as Utf16 ( Position(..) ) +import Data.Text.Utf16.Rope.Mixed ( Rope ) +import Data.Text.Utf16.Rope.Mixed qualified as Rope import Language.LSP.Protocol.Lens qualified as J import Language.LSP.Protocol.Message qualified as J import Language.LSP.Protocol.Types qualified as J @@ -114,8 +115,8 @@ data VFS = VFS } deriving (Show) -data VfsLog - = SplitInsideCodePoint Rope.Position Rope +data VfsLog = + SplitInsideCodePoint Utf16.Position Rope | URINotFound J.NormalizedUri | Opening J.NormalizedUri | Closing J.NormalizedUri @@ -350,7 +351,7 @@ applyChange :: (Monad m) => LogAction m (WithSeverity VfsLog) -> Rope -> J.TextD applyChange logger str (J.TextDocumentContentChangeEvent (J.InL e)) | J.Range (J.Position sl sc) (J.Position fl fc) <- e .! #range , txt <- e .! #text = - changeChars logger str (Rope.Position (fromIntegral sl) (fromIntegral sc)) (Rope.Position (fromIntegral fl) (fromIntegral fc)) txt + changeChars logger str (Utf16.Position (fromIntegral sl) (fromIntegral sc)) (Utf16.Position (fromIntegral fl) (fromIntegral fc)) txt applyChange _ _ (J.TextDocumentContentChangeEvent (J.InR e)) = pure $ Rope.fromText $ e .! #text @@ -360,11 +361,11 @@ applyChange _ _ (J.TextDocumentContentChangeEvent (J.InR e)) = the given range with the new text. If the given positions lie within a code point then this does nothing (returns the original 'Rope') and logs. -} -changeChars :: (Monad m) => LogAction m (WithSeverity VfsLog) -> Rope -> Rope.Position -> Rope.Position -> Text -> m Rope +changeChars :: (Monad m) => LogAction m (WithSeverity VfsLog) -> Rope -> Utf16.Position -> Utf16.Position -> Text -> m Rope changeChars logger str start finish new = do - case Rope.splitAtPosition finish str of + case Rope.utf16SplitAtPosition finish str of Nothing -> logger <& SplitInsideCodePoint finish str `WithSeverity` Warning >> pure str - Just (before, after) -> case Rope.splitAtPosition start before of + Just (before, after) -> case Rope.utf16SplitAtPosition start before of Nothing -> logger <& SplitInsideCodePoint start before `WithSeverity` Warning >> pure str Just (before', _) -> pure $ mconcat [before', Rope.fromText new, after] @@ -398,58 +399,14 @@ makeFieldsNoPrefix ''CodePointRange {- Note [Converting between code points and code units] This is inherently a somewhat expensive operation, but we take some care to minimize the cost. In particular, we use the good asymptotics of 'Rope' to our advantage: -- We extract the single line that we are interested in in time logarithmic in the number of lines. -- We then split the line at the given position, and check how long the prefix is, which takes -linear time in the length of the (single) line. +- utf16SplitAtPosition is logarithmic in the number of lines and linear in the length of the line +- charSplitAtPosition is logarithmic in the number of lines and linear in the length of the line -We also may need to convert the line back and forth between ropes with different indexing. Again -this is linear time in the length of the line. So the overall process is logarithmic in the number of lines, and linear in the length of the specific line. Which is okay-ish, so long as we don't have very long lines. -} -{- | Extracts a specific line from a 'Rope.Rope'. - Logarithmic in the number of lines. --} -extractLine :: Rope.Rope -> Word -> Maybe Rope.Rope -extractLine rope l = do - -- Check for the line being out of bounds - let lastLine = Rope.posLine $ Rope.lengthAsPosition rope - guard $ l <= lastLine - - let (_, suffix) = Rope.splitAtLine l rope - (prefix, _) = Rope.splitAtLine 1 suffix - pure prefix - -{- | Translate a code-point offset into a code-unit offset. - Linear in the length of the rope. --} -codePointOffsetToCodeUnitOffset :: URope.Rope -> Word -> Maybe Word -codePointOffsetToCodeUnitOffset rope offset = do - -- Check for the position being out of bounds - guard $ offset <= URope.length rope - -- Split at the given position in *code points* - let (prefix, _) = URope.splitAt offset rope - -- Convert the prefix to a rope using *code units* - utf16Prefix = Rope.fromText $ URope.toText prefix - -- Get the length of the prefix in *code units* - pure $ Rope.length utf16Prefix - -{- | Translate a UTF-16 code-unit offset into a code-point offset. - Linear in the length of the rope. --} -codeUnitOffsetToCodePointOffset :: Rope.Rope -> Word -> Maybe Word -codeUnitOffsetToCodePointOffset rope offset = do - -- Check for the position being out of bounds - guard $ offset <= Rope.length rope - -- Split at the given position in *code units* - (prefix, _) <- Rope.splitAt offset rope - -- Convert the prefix to a rope using *code points* - let utfPrefix = URope.fromText $ Rope.toText prefix - -- Get the length of the prefix in *code points* - pure $ URope.length utfPrefix - {- | Given a virtual file, translate a 'CodePointPosition' in that file into a 'J.Position' in that file. Will return 'Nothing' if the requested position is out of bounds of the document. @@ -461,12 +418,11 @@ codePointPositionToPosition :: VirtualFile -> CodePointPosition -> Maybe J.Posit codePointPositionToPosition vFile (CodePointPosition l cpc) = do -- See Note [Converting between code points and code units] let text = _file_text vFile - utf16Line <- extractLine text (fromIntegral l) - -- Convert the line a rope using *code points* - let utfLine = URope.fromText $ Rope.toText utf16Line - - cuc <- codePointOffsetToCodeUnitOffset utfLine (fromIntegral cpc) - pure $ J.Position l (fromIntegral cuc) + let pos = Char.Position (fromIntegral l) (fromIntegral cpc) + let (prefix, _) = Rope.charSplitAtPosition pos text + guard $ pos == Rope.charLengthAsPosition prefix + let Utf16.Position cpl pc = Rope.utf16LengthAsPosition prefix + pure (J.Position (fromIntegral cpl) (fromIntegral pc)) {- | Given a virtual file, translate a 'CodePointRange' in that file into a 'J.Range' in that file. @@ -487,13 +443,13 @@ codePointRangeToRange vFile (CodePointRange b e) = the position. -} positionToCodePointPosition :: VirtualFile -> J.Position -> Maybe CodePointPosition -positionToCodePointPosition vFile (J.Position l cuc) = do - -- See Note [Converting between code points and code units] +positionToCodePointPosition vFile (J.Position cul cuc) = do let text = _file_text vFile - utf16Line <- extractLine text (fromIntegral l) - - cpc <- codeUnitOffsetToCodePointOffset utf16Line (fromIntegral cuc) - pure $ CodePointPosition l (fromIntegral cpc) + let pos = Utf16.Position (fromIntegral cul) (fromIntegral cuc) + (prefix, _) <- Rope.utf16SplitAtPosition pos text + guard $ pos == Rope.utf16LengthAsPosition prefix + let Char.Position cpl cpc = Rope.charLengthAsPosition prefix + pure $ CodePointPosition (fromIntegral cpl) (fromIntegral cpc) {- | Given a virtual file, translate a 'J.Range' in that file into a 'CodePointRange' in that file. @@ -535,7 +491,7 @@ getCompletionPrefix pos@(J.Position l c) (VirtualFile _ _ ropetext) = lastMaybe xs = Just $ last xs let curRope = fst $ Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) ropetext - beforePos <- Rope.toText . fst <$> Rope.splitAt (fromIntegral c) curRope + beforePos <- Rope.toText . fst <$> Rope.utf16SplitAt (fromIntegral c) curRope curWord <- if | T.null beforePos -> Just "" diff --git a/lsp/test/VspSpec.hs b/lsp/test/VspSpec.hs index 335620ec..4eaf06cf 100644 --- a/lsp/test/VspSpec.hs +++ b/lsp/test/VspSpec.hs @@ -6,7 +6,7 @@ module VspSpec where import Data.Row import Data.String import Data.Text qualified as T -import Data.Text.Utf16.Rope qualified as Rope +import Data.Text.Utf16.Rope.Mixed qualified as Rope import Language.LSP.Protocol.Types qualified as J import Language.LSP.VFS @@ -252,7 +252,7 @@ vspSpec = do positionToCodePointPosition vfile (J.Position 1 2) `shouldBe` Nothing positionToCodePointPosition vfile (J.Position 1 3) `shouldBe` Just (CodePointPosition 1 2) positionToCodePointPosition vfile (J.Position 1 4) `shouldBe` Just (CodePointPosition 1 3) - positionToCodePointPosition vfile (J.Position 1 5) `shouldBe` Just (CodePointPosition 1 4) + positionToCodePointPosition vfile (J.Position 1 5) `shouldBe` Nothing -- Greater column than max column positionToCodePointPosition vfile (J.Position 1 6) `shouldBe` Nothing positionToCodePointPosition vfile (J.Position 2 1) `shouldBe` Nothing @@ -272,7 +272,7 @@ vspSpec = do codePointPositionToPosition vfile (CodePointPosition 1 1) `shouldBe` Just (J.Position 1 1) codePointPositionToPosition vfile (CodePointPosition 1 2) `shouldBe` Just (J.Position 1 3) codePointPositionToPosition vfile (CodePointPosition 1 3) `shouldBe` Just (J.Position 1 4) - codePointPositionToPosition vfile (CodePointPosition 1 4) `shouldBe` Just (J.Position 1 5) + codePointPositionToPosition vfile (CodePointPosition 1 4) `shouldBe` Nothing -- Greater column than max column codePointPositionToPosition vfile (CodePointPosition 1 5) `shouldBe` Nothing codePointPositionToPosition vfile (CodePointPosition 2 1) `shouldBe` Nothing From 8ffe6d89de4e9b5264fd2e43388e61cc876dc28d Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 19:20:19 +0800 Subject: [PATCH 03/10] fix omitting newline --- lsp/src/Language/LSP/VFS.hs | 40 ++++++++++++++++++++++++++----------- lsp/test/VspSpec.hs | 4 ++-- 2 files changed, 30 insertions(+), 14 deletions(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index f1035b99..8bf340a4 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -407,6 +407,18 @@ So the overall process is logarithmic in the number of lines, and linear in the line. Which is okay-ish, so long as we don't have very long lines. -} +{- | Extracts a specific line from a 'Rope.Rope'. + Logarithmic in the number of lines. +-} +extractLine :: Rope.Rope -> Word -> Maybe Rope.Rope +extractLine rope l = do + -- Check for the line being out of bounds + let lastLine = Rope.lengthInLines rope + guard $ l <= lastLine + let (_, suffix) = Rope.splitAtLine l rope + (prefix, _) = Rope.splitAtLine 1 suffix + pure prefix + {- | Given a virtual file, translate a 'CodePointPosition' in that file into a 'J.Position' in that file. Will return 'Nothing' if the requested position is out of bounds of the document. @@ -415,14 +427,16 @@ line. Which is okay-ish, so long as we don't have very long lines. the position. -} codePointPositionToPosition :: VirtualFile -> CodePointPosition -> Maybe J.Position -codePointPositionToPosition vFile (CodePointPosition l cpc) = do +codePointPositionToPosition vFile (CodePointPosition l c) = do -- See Note [Converting between code points and code units] let text = _file_text vFile - let pos = Char.Position (fromIntegral l) (fromIntegral cpc) - let (prefix, _) = Rope.charSplitAtPosition pos text - guard $ pos == Rope.charLengthAsPosition prefix - let Utf16.Position cpl pc = Rope.utf16LengthAsPosition prefix - pure (J.Position (fromIntegral cpl) (fromIntegral pc)) + lineRope <- extractLine text $ fromIntegral l + kLine <- case compare c (fromIntegral $ Rope.charLength lineRope) of + LT -> return $ fst $ Rope.charSplitAt (fromIntegral c) lineRope + EQ -> return lineRope + GT -> Nothing + return $ J.Position l (fromIntegral $ Rope.utf16Length kLine) + {- | Given a virtual file, translate a 'CodePointRange' in that file into a 'J.Range' in that file. @@ -443,13 +457,15 @@ codePointRangeToRange vFile (CodePointRange b e) = the position. -} positionToCodePointPosition :: VirtualFile -> J.Position -> Maybe CodePointPosition -positionToCodePointPosition vFile (J.Position cul cuc) = do +positionToCodePointPosition vFile (J.Position l c) = do let text = _file_text vFile - let pos = Utf16.Position (fromIntegral cul) (fromIntegral cuc) - (prefix, _) <- Rope.utf16SplitAtPosition pos text - guard $ pos == Rope.utf16LengthAsPosition prefix - let Char.Position cpl cpc = Rope.charLengthAsPosition prefix - pure $ CodePointPosition (fromIntegral cpl) (fromIntegral cpc) + lineRope <- extractLine text $ fromIntegral l + kLine <- case compare c (fromIntegral $ Rope.utf16Length lineRope) of + LT -> fst <$> Rope.utf16SplitAt (fromIntegral c) lineRope + EQ -> return lineRope + GT -> Nothing + return $ CodePointPosition l (fromIntegral $ Rope.charLength kLine) + {- | Given a virtual file, translate a 'J.Range' in that file into a 'CodePointRange' in that file. diff --git a/lsp/test/VspSpec.hs b/lsp/test/VspSpec.hs index 4eaf06cf..8167553e 100644 --- a/lsp/test/VspSpec.hs +++ b/lsp/test/VspSpec.hs @@ -252,7 +252,7 @@ vspSpec = do positionToCodePointPosition vfile (J.Position 1 2) `shouldBe` Nothing positionToCodePointPosition vfile (J.Position 1 3) `shouldBe` Just (CodePointPosition 1 2) positionToCodePointPosition vfile (J.Position 1 4) `shouldBe` Just (CodePointPosition 1 3) - positionToCodePointPosition vfile (J.Position 1 5) `shouldBe` Nothing + positionToCodePointPosition vfile (J.Position 1 5) `shouldBe` Just (CodePointPosition 1 4) -- Greater column than max column positionToCodePointPosition vfile (J.Position 1 6) `shouldBe` Nothing positionToCodePointPosition vfile (J.Position 2 1) `shouldBe` Nothing @@ -272,7 +272,7 @@ vspSpec = do codePointPositionToPosition vfile (CodePointPosition 1 1) `shouldBe` Just (J.Position 1 1) codePointPositionToPosition vfile (CodePointPosition 1 2) `shouldBe` Just (J.Position 1 3) codePointPositionToPosition vfile (CodePointPosition 1 3) `shouldBe` Just (J.Position 1 4) - codePointPositionToPosition vfile (CodePointPosition 1 4) `shouldBe` Nothing + codePointPositionToPosition vfile (CodePointPosition 1 4) `shouldBe` Just (J.Position 1 5) -- Greater column than max column codePointPositionToPosition vfile (CodePointPosition 1 5) `shouldBe` Nothing codePointPositionToPosition vfile (CodePointPosition 2 1) `shouldBe` Nothing From deab787c4433af8cf2c5fffddacca8c65981ca42 Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 20:17:23 +0800 Subject: [PATCH 04/10] revert extractLine --- lsp/src/Language/LSP/VFS.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 8bf340a4..6db5b941 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -413,7 +413,7 @@ line. Which is okay-ish, so long as we don't have very long lines. extractLine :: Rope.Rope -> Word -> Maybe Rope.Rope extractLine rope l = do -- Check for the line being out of bounds - let lastLine = Rope.lengthInLines rope + let lastLine = Utf16.posLine $ Rope.utf16LengthAsPosition rope guard $ l <= lastLine let (_, suffix) = Rope.splitAtLine l rope (prefix, _) = Rope.splitAtLine 1 suffix From 8e88af9dd10023dca21078f1ca82a9ce8a37bcda Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 20:18:42 +0800 Subject: [PATCH 05/10] update Note [Converting between code points and code units] --- lsp/src/Language/LSP/VFS.hs | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 6db5b941..679ad782 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -399,9 +399,9 @@ makeFieldsNoPrefix ''CodePointRange {- Note [Converting between code points and code units] This is inherently a somewhat expensive operation, but we take some care to minimize the cost. In particular, we use the good asymptotics of 'Rope' to our advantage: -- utf16SplitAtPosition is logarithmic in the number of lines and linear in the length of the line -- charSplitAtPosition is logarithmic in the number of lines and linear in the length of the line - +- We extract the single line that we are interested in in time logarithmic in the number of lines. +- We then split the line at the given position, and check how long the prefix is, which takes +linear time in the length of the (single) line. So the overall process is logarithmic in the number of lines, and linear in the length of the specific line. Which is okay-ish, so long as we don't have very long lines. From 9b12397160ed3711ca46c2e573978b8e6b471255 Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 20:33:53 +0800 Subject: [PATCH 06/10] format --- lsp/src/Language/LSP/VFS.hs | 14 ++++++-------- 1 file changed, 6 insertions(+), 8 deletions(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 679ad782..4ad9de36 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -81,11 +81,11 @@ import Data.Row import Data.Text (Text) import Data.Text qualified as T import Data.Text.IO qualified as T +import Data.Text.Lines as Char (Position (..)) import Data.Text.Prettyprint.Doc hiding (line) -import Data.Text.Lines as Char ( Position(..) ) -import Data.Text.Utf16.Lines as Utf16 ( Position(..) ) -import Data.Text.Utf16.Rope.Mixed ( Rope ) -import Data.Text.Utf16.Rope.Mixed qualified as Rope +import Data.Text.Utf16.Lines as Utf16 (Position (..)) +import Data.Text.Utf16.Rope.Mixed (Rope) +import Data.Text.Utf16.Rope.Mixed qualified as Rope import Language.LSP.Protocol.Lens qualified as J import Language.LSP.Protocol.Message qualified as J import Language.LSP.Protocol.Types qualified as J @@ -115,8 +115,8 @@ data VFS = VFS } deriving (Show) -data VfsLog = - SplitInsideCodePoint Utf16.Position Rope +data VfsLog + = SplitInsideCodePoint Utf16.Position Rope | URINotFound J.NormalizedUri | Opening J.NormalizedUri | Closing J.NormalizedUri @@ -436,7 +436,6 @@ codePointPositionToPosition vFile (CodePointPosition l c) = do EQ -> return lineRope GT -> Nothing return $ J.Position l (fromIntegral $ Rope.utf16Length kLine) - {- | Given a virtual file, translate a 'CodePointRange' in that file into a 'J.Range' in that file. @@ -465,7 +464,6 @@ positionToCodePointPosition vFile (J.Position l c) = do EQ -> return lineRope GT -> Nothing return $ CodePointPosition l (fromIntegral $ Rope.charLength kLine) - {- | Given a virtual file, translate a 'J.Range' in that file into a 'CodePointRange' in that file. From 40fe213e8d3a3de4633aaaa2db39f901317d9b12 Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 20:38:39 +0800 Subject: [PATCH 07/10] add back note --- lsp/src/Language/LSP/VFS.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 4ad9de36..17a46e9e 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -457,6 +457,7 @@ codePointRangeToRange vFile (CodePointRange b e) = -} positionToCodePointPosition :: VirtualFile -> J.Position -> Maybe CodePointPosition positionToCodePointPosition vFile (J.Position l c) = do + -- See Note [Converting between code points and code units] let text = _file_text vFile lineRope <- extractLine text $ fromIntegral l kLine <- case compare c (fromIntegral $ Rope.utf16Length lineRope) of From f7a631463c401b72659e635be5617918482aa8ce Mon Sep 17 00:00:00 2001 From: Patrick Date: Mon, 1 Jan 2024 23:02:00 +0800 Subject: [PATCH 08/10] simplified --- lsp/src/Language/LSP/VFS.hs | 14 ++++---------- 1 file changed, 4 insertions(+), 10 deletions(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 17a46e9e..9ec7bf9f 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -431,11 +431,8 @@ codePointPositionToPosition vFile (CodePointPosition l c) = do -- See Note [Converting between code points and code units] let text = _file_text vFile lineRope <- extractLine text $ fromIntegral l - kLine <- case compare c (fromIntegral $ Rope.charLength lineRope) of - LT -> return $ fst $ Rope.charSplitAt (fromIntegral c) lineRope - EQ -> return lineRope - GT -> Nothing - return $ J.Position l (fromIntegral $ Rope.utf16Length kLine) + guard $ c <= fromIntegral (Rope.charLength lineRope) + return $ J.Position l (fromIntegral $ Rope.utf16Length $ fst $ Rope.charSplitAt (fromIntegral c) lineRope) {- | Given a virtual file, translate a 'CodePointRange' in that file into a 'J.Range' in that file. @@ -460,11 +457,8 @@ positionToCodePointPosition vFile (J.Position l c) = do -- See Note [Converting between code points and code units] let text = _file_text vFile lineRope <- extractLine text $ fromIntegral l - kLine <- case compare c (fromIntegral $ Rope.utf16Length lineRope) of - LT -> fst <$> Rope.utf16SplitAt (fromIntegral c) lineRope - EQ -> return lineRope - GT -> Nothing - return $ CodePointPosition l (fromIntegral $ Rope.charLength kLine) + guard $ c <= fromIntegral (Rope.utf16Length lineRope) + CodePointPosition l . fromIntegral . Rope.charLength . fst <$> Rope.utf16SplitAt (fromIntegral c) lineRope {- | Given a virtual file, translate a 'J.Range' in that file into a 'CodePointRange' in that file. From 374041f272305454a017d97f4ceb8010d2e1f573 Mon Sep 17 00:00:00 2001 From: Patrick Date: Tue, 2 Jan 2024 18:17:12 +0800 Subject: [PATCH 09/10] update comment --- lsp/src/Language/LSP/VFS.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 9ec7bf9f..bd26aa09 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -405,6 +405,12 @@ linear time in the length of the (single) line. So the overall process is logarithmic in the number of lines, and linear in the length of the specific line. Which is okay-ish, so long as we don't have very long lines. + +We are not able to use the `Rope.splitAtPosition` +Because the when column index out of range or when the column indexing at the newline char. +The prefix result would wrap over the line and having the same result (nextLineNum, 0). +We would not be able to distinguish them. When the first case should return `Nothing`, +other should return a `Just (CurrentLineNum, columnNumberConverted)`. -} {- | Extracts a specific line from a 'Rope.Rope'. From ac411ef7564e6d3a92c861ee2d59599e8b7891ae Mon Sep 17 00:00:00 2001 From: Patrick Date: Tue, 2 Jan 2024 18:26:19 +0800 Subject: [PATCH 10/10] fix typo --- lsp/src/Language/LSP/VFS.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index bd26aa09..a26c6be2 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -407,10 +407,10 @@ So the overall process is logarithmic in the number of lines, and linear in the line. Which is okay-ish, so long as we don't have very long lines. We are not able to use the `Rope.splitAtPosition` -Because the when column index out of range or when the column indexing at the newline char. +Because when column index out of range or when the column indexing at the newline char. The prefix result would wrap over the line and having the same result (nextLineNum, 0). We would not be able to distinguish them. When the first case should return `Nothing`, -other should return a `Just (CurrentLineNum, columnNumberConverted)`. +second case should return a `Just (CurrentLineNum, columnNumberConverted)`. -} {- | Extracts a specific line from a 'Rope.Rope'.