Skip to content

Commit

Permalink
Switch to rope-utf16-splay for ropes
Browse files Browse the repository at this point in the history
* This makes the licensing story simpler because rope-utf16-splay is
BSD3 licensed. (haskell#16)
* LSP uses UTF-16 code point based indexing, while the Yi rope library
indexes by characters. This means that haskell-lsp would previously not
correctly count characters that are encoded as two code points in
UTF-16. The rope-utf16-splay library uses code point indexing, which
fixes this issue.
* From my benchmarks, this new library, which uses splay trees
internally, can be about twice as fast as finger tree based ones (like
the Yi one) for use cases that are similar to what haskell-lsp might be
doing (many consecutive modifications).
  • Loading branch information
ollef committed Feb 10, 2018
1 parent c22371a commit c7d904d
Show file tree
Hide file tree
Showing 5 changed files with 55 additions and 107 deletions.
4 changes: 2 additions & 2 deletions example/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import qualified Language.Haskell.LSP.Utility as U
import Language.Haskell.LSP.VFS
import System.Exit
import qualified System.Log.Logger as L
import qualified Yi.Rope as Yi
import qualified Data.Rope.UTF16 as Rope
import Control.Lens


Expand Down Expand Up @@ -192,7 +192,7 @@ reactor lf inp = do
mdoc <- liftIO $ Core.getVirtualFileFunc lf doc
case mdoc of
Just (VirtualFile _version str) -> do
liftIO $ U.logs $ "reactor:processing NotDidChangeTextDocument: vf got:" ++ (show $ Yi.toString str)
liftIO $ U.logs $ "reactor:processing NotDidChangeTextDocument: vf got:" ++ (show $ Rope.toString str)
Nothing -> do
liftIO $ U.logs $ "reactor:processing NotDidChangeTextDocument: vf returned Nothing"

Expand Down
6 changes: 3 additions & 3 deletions haskell-lsp.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -47,12 +47,12 @@ library
, lens >= 4.15.2
, mtl
, parsec
, rope-utf16-splay >= 0.1
, sorted-list == 0.2.0.*
, stm
, text
, time
, unordered-containers
, yi-rope
hs-source-dirs: src
default-language: Haskell2010

Expand All @@ -74,13 +74,13 @@ executable lsp-hello
, lens >= 4.15.2
, mtl
, parsec
, rope-utf16-splay >= 0.1
, stm
, text
, time
, transformers
, unordered-containers
, vector
, yi-rope
-- the package library. Comment this out if you want repl changes to propagate
, haskell-lsp

Expand All @@ -102,11 +102,11 @@ test-suite haskell-lsp-test
-- , hspec-jenkins
, lens >= 4.15.2
, sorted-list == 0.2.0.*
, yi-rope
, haskell-lsp
-- , data-default
-- , bytestring
-- , hslogger
, rope-utf16-splay >= 0.1
, text
-- , unordered-containers
ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall
Expand Down
98 changes: 21 additions & 77 deletions src/Language/Haskell/LSP/VFS.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,18 +19,17 @@ module Language.Haskell.LSP.VFS
-- * for tests
, applyChange
, sortChanges
, deleteChars , addChars
, changeChars
, yiSplitAt
) where

import Data.Text ( Text )
import Data.List
import Data.Monoid
import qualified Data.Map as Map
import Data.Rope.UTF16 ( Rope )
import qualified Data.Rope.UTF16 as Rope
import qualified Language.Haskell.LSP.TH.DataTypesJSON as J
import Language.Haskell.LSP.Utility
import qualified Yi.Rope as Yi

-- ---------------------------------------------------------------------
{-# ANN module ("hlint: ignore Eta reduce" :: String) #-}
Expand All @@ -40,7 +39,7 @@ import qualified Yi.Rope as Yi
data VirtualFile =
VirtualFile {
_version :: Int
, _text :: Yi.YiString
, _text :: Rope
} deriving (Show)

type VFS = Map.Map J.Uri VirtualFile
Expand All @@ -51,7 +50,7 @@ openVFS :: VFS -> J.DidOpenTextDocumentNotification -> IO VFS
openVFS vfs (J.NotificationMessage _ _ params) = do
let J.DidOpenTextDocumentParams
(J.TextDocumentItem uri _ version text) = params
return $ Map.insert uri (VirtualFile version (Yi.fromText text)) vfs
return $ Map.insert uri (VirtualFile version (Rope.fromText text)) vfs

-- ---------------------------------------------------------------------

Expand Down Expand Up @@ -87,92 +86,37 @@ data TextDocumentContentChangeEvent =
-}

-- | Apply the list of changes, in descending order of range. Assuming no overlaps.
applyChanges :: Yi.YiString -> [J.TextDocumentContentChangeEvent] -> Yi.YiString
applyChanges :: Rope -> [J.TextDocumentContentChangeEvent] -> Rope
applyChanges str changes' = r
where
changes = sortChanges changes'
r = foldl' applyChange str changes

-- ---------------------------------------------------------------------

applyChange :: Yi.YiString -> J.TextDocumentContentChangeEvent -> Yi.YiString
applyChange :: Rope -> J.TextDocumentContentChangeEvent -> Rope
applyChange _ (J.TextDocumentContentChangeEvent Nothing Nothing str)
= Yi.fromText str
applyChange str (J.TextDocumentContentChangeEvent (Just (J.Range fm _to)) (Just len) txt) =
if txt == ""
then -- delete len chars from fm
deleteChars str fm len
else -- add or change, based on length
if len == 0
then addChars str fm txt
-- Note: changeChars comes from applyEdit, emacs will split it into a
-- delete and an add
else changeChars str fm len txt
applyChange str (J.TextDocumentContentChangeEvent (Just r@(J.Range (J.Position sl sc) (J.Position el ec))) Nothing txt)
= applyChange str (J.TextDocumentContentChangeEvent (Just r) (Just len) txt)
where len = Yi.length region
(beforeEnd, afterEnd) = Yi.splitAtLine el str
lastLine = Yi.take ec afterEnd
lastLine' | sl == el = Yi.drop sc lastLine
| otherwise = lastLine
(_beforeStart, afterStartBeforeEnd) = Yi.splitAtLine sl beforeEnd
region = Yi.drop sc afterStartBeforeEnd <> lastLine'
applyChange str (J.TextDocumentContentChangeEvent Nothing (Just _) _txt)
= str

-- ---------------------------------------------------------------------

deleteChars :: Yi.YiString -> J.Position -> Int -> Yi.YiString
deleteChars str (J.Position l c) len = str'
where
(before,after) = Yi.splitAtLine l str
-- after contains the area we care about, starting with the selected line.
-- Due to LSP zero-based coordinates
beforeOnLine = Yi.take c after
after' = Yi.drop (c + len) after
str' = Yi.append before (Yi.append beforeOnLine after')

-- ---------------------------------------------------------------------

addChars :: Yi.YiString -> J.Position -> Text -> Yi.YiString
addChars str (J.Position l c) new = str'
= Rope.fromText str
applyChange str (J.TextDocumentContentChangeEvent (Just (J.Range (J.Position sl sc) _to)) (Just len) txt)
= changeChars str start len txt
where
(before,after) = Yi.splitAtLine l str
-- after contains the area we care about, starting with the selected line.
-- Due to LSP zero-based coordinates
beforeOnLine = Yi.take c after
after' = Yi.drop c after
str' = Yi.concat [before, beforeOnLine, (Yi.fromText new), after']

-- ---------------------------------------------------------------------

changeChars :: Yi.YiString -> J.Position -> Int -> Text -> Yi.YiString
changeChars str (J.Position ls cs) len new = str'
start = Rope.rowColumnCodePoints (Rope.RowColumn sl sc) str
applyChange str (J.TextDocumentContentChangeEvent (Just (J.Range (J.Position sl sc) (J.Position el ec))) Nothing txt)
= changeChars str start len txt
where
(before,after) = yiSplitAt ls cs str
after' = Yi.drop len after

str' = Yi.concat [before, (Yi.fromText new), after']

-- changeChars :: Yi.YiString -> J.Position -> J.Position -> String -> Yi.YiString
-- changeChars str (J.Position ls cs) (J.Position le ce) new = str'
-- where
-- (before,_after) = yiSplitAt ls cs str
-- (_before,after) = yiSplitAt le ce str

-- str' = Yi.concat [before, (Yi.fromString new), after]
-- -- str' = Yi.concat [before]
-- -- str' = Yi.concat [_before]
start = Rope.rowColumnCodePoints (Rope.RowColumn sl sc) str
end = Rope.rowColumnCodePoints (Rope.RowColumn el ec) str
len = end - start
applyChange str (J.TextDocumentContentChangeEvent Nothing (Just _) _txt)
= str

-- ---------------------------------------------------------------------

yiSplitAt :: Int -> Int -> Yi.YiString -> (Yi.YiString, Yi.YiString)
yiSplitAt l c str = (before,after)
changeChars :: Rope -> Int -> Int -> Text -> Rope
changeChars str start len new = mconcat [before, Rope.fromText new, after']
where
(b,a) = Yi.splitAtLine l str
before = Yi.concat [b,Yi.take c a]
after = Yi.drop c a

(before, after) = Rope.splitAt start str
after' = Rope.drop len after

-- ---------------------------------------------------------------------

Expand Down
1 change: 1 addition & 0 deletions stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,7 @@ resolver: lts-10.1 # GHC 8.2.2 version

packages:
- '.'
extra-deps: [rope-utf16-splay-0.1.0.0]
flags: {}
extra-package-dbs: []
nix:
Expand Down
53 changes: 28 additions & 25 deletions test/VspSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,10 @@
module VspSpec where


import Data.String
import qualified Data.Rope.UTF16 as Rope
import Language.Haskell.LSP.VFS
import qualified Language.Haskell.LSP.TH.DataTypesJSON as J
import qualified Yi.Rope as Yi

import Test.Hspec

Expand Down Expand Up @@ -56,9 +57,9 @@ vspSpec = do
, "-- fooo"
, "foo :: Int"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 2 1 2 5) (Just 4) ""
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "abcdg"
, "module Foo where"
, "-oo"
Expand All @@ -73,9 +74,9 @@ vspSpec = do
, "-- fooo"
, "foo :: Int"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 2 1 2 5) Nothing ""
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "abcdg"
, "module Foo where"
, "-oo"
Expand All @@ -93,9 +94,9 @@ vspSpec = do
, "-- fooo"
, "foo :: Int"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 2 0 3 0) (Just 8) ""
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "abcdg"
, "module Foo where"
, "foo :: Int"
Expand All @@ -110,9 +111,9 @@ vspSpec = do
, "-- fooo"
, "foo :: Int"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 2 0 3 0) Nothing ""
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "abcdg"
, "module Foo where"
, "foo :: Int"
Expand All @@ -128,9 +129,9 @@ vspSpec = do
, "foo :: Int"
, "foo = bb"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 1 0 3 0) (Just 19) ""
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "module Foo where"
, "foo = bb"
]
Expand All @@ -144,9 +145,9 @@ vspSpec = do
, "foo :: Int"
, "foo = bb"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 1 0 3 0) Nothing ""
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "module Foo where"
, "foo = bb"
]
Expand All @@ -161,8 +162,9 @@ vspSpec = do
, "module Foo where"
, "foo :: Int"
]
new = addChars (Yi.fromString orig) (J.Position 1 16) "\n-- fooo"
lines (Yi.toString new) `shouldBe`
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 1 16 1 16) (Just 0) "\n-- fooo"
lines (Rope.toString new) `shouldBe`
[ "abcdg"
, "module Foo where"
, "-- fooo"
Expand All @@ -178,8 +180,9 @@ vspSpec = do
[ "module Foo where"
, "foo = bb"
]
new = addChars (Yi.fromString orig) (J.Position 1 8) "\n-- fooo\nfoo :: Int"
lines (Yi.toString new) `shouldBe`
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 1 8 1 8) Nothing "\n-- fooo\nfoo :: Int"
lines (Rope.toString new) `shouldBe`
[ "module Foo where"
, "foo = bb"
, "-- fooo"
Expand All @@ -203,10 +206,10 @@ vspSpec = do
, "baz = do"
, " putStrLn \"hello world\""
]
-- new = changeChars (Yi.fromString orig) (J.Position 7 0) (J.Position 7 8) "baz ="
new = applyChange (Yi.fromString orig)
-- new = changeChars (fromString orig) (J.Position 7 0) (J.Position 7 8) "baz ="
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 7 0 7 8) (Just 8) "baz ="
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "module Foo where"
, "-- fooo"
, "foo :: Int"
Expand All @@ -231,10 +234,10 @@ vspSpec = do
, "baz = do"
, " putStrLn \"hello world\""
]
-- new = changeChars (Yi.fromString orig) (J.Position 7 0) (J.Position 7 8) "baz ="
new = applyChange (Yi.fromString orig)
-- new = changeChars (fromString orig) (J.Position 7 0) (J.Position 7 8) "baz ="
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 7 0 7 8) Nothing "baz ="
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "module Foo where"
, "-- fooo"
, "foo :: Int"
Expand All @@ -251,9 +254,9 @@ vspSpec = do
[ "a𐐀b"
, "a𐐀b"
]
new = applyChange (Yi.fromString orig)
new = applyChange (fromString orig)
$ J.TextDocumentContentChangeEvent (mkRange 1 0 1 3) (Just 3) "𐐀𐐀"
lines (Yi.toString new) `shouldBe`
lines (Rope.toString new) `shouldBe`
[ "a𐐀b"
, "𐐀𐐀b"
]

0 comments on commit c7d904d

Please sign in to comment.