Skip to content

Commit 28232e6

Browse files
authored
Merge pull request #392 from Bodigrim/master
Support text-2.0
2 parents 15cf002 + 82bc411 commit 28232e6

File tree

4 files changed

+31
-41
lines changed

4 files changed

+31
-41
lines changed

lsp-types/lsp-types.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -88,10 +88,10 @@ library
8888
, mtl
8989
, network-uri
9090
, mod
91-
, rope-utf16-splay >= 0.3.1.0
9291
, scientific
9392
, some
9493
, text
94+
, text-rope
9595
, template-haskell
9696
, temporary
9797
, unordered-containers

lsp-types/src/Language/LSP/VFS.hs

Lines changed: 15 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -52,8 +52,8 @@ import Data.Ord
5252
import qualified Data.HashMap.Strict as HashMap
5353
import qualified Data.Map.Strict as Map
5454
import Data.Maybe
55-
import Data.Rope.UTF16 ( Rope )
56-
import qualified Data.Rope.UTF16 as Rope
55+
import Data.Text.Utf16.Rope ( Rope )
56+
import qualified Data.Text.Utf16.Rope as Rope
5757
import qualified Language.LSP.Types as J
5858
import qualified Language.LSP.Types.Lens as J
5959
import System.FilePath
@@ -136,7 +136,7 @@ applyCreateFile (J.CreateFile uri options _ann) =
136136
updateVFS $ Map.insertWith
137137
(\ new old -> if shouldOverwrite then new else old)
138138
(J.toNormalizedUri uri)
139-
(VirtualFile 0 0 (Rope.fromText ""))
139+
(VirtualFile 0 0 mempty)
140140
where
141141
shouldOverwrite :: Bool
142142
shouldOverwrite = case options of
@@ -260,7 +260,7 @@ persistFileVFS vfs uri =
260260
action = do
261261
exists <- doesFileExist tfn
262262
unless exists $ do
263-
let contents = Rope.toString (_text vf)
263+
let contents = T.unpack (Rope.toText (_text vf))
264264
writeRaw h = do
265265
-- We honour original file line endings
266266
hSetNewlineMode h noNewlineTranslation
@@ -291,26 +291,18 @@ applyChanges = foldl' applyChange
291291
applyChange :: Rope -> J.TextDocumentContentChangeEvent -> Rope
292292
applyChange _ (J.TextDocumentContentChangeEvent Nothing Nothing str)
293293
= Rope.fromText str
294-
applyChange str (J.TextDocumentContentChangeEvent (Just (J.Range (J.Position sl sc) _to)) (Just len) txt)
295-
= changeChars str start (fromIntegral len) txt
296-
where
297-
start = Rope.rowColumnCodeUnits (Rope.RowColumn (fromIntegral sl) (fromIntegral sc)) str
298-
applyChange str (J.TextDocumentContentChangeEvent (Just (J.Range (J.Position sl sc) (J.Position el ec))) Nothing txt)
299-
= changeChars str start len txt
300-
where
301-
start = Rope.rowColumnCodeUnits (Rope.RowColumn (fromIntegral sl) (fromIntegral sc)) str
302-
end = Rope.rowColumnCodeUnits (Rope.RowColumn (fromIntegral el) (fromIntegral ec)) str
303-
len = end - start
294+
applyChange str (J.TextDocumentContentChangeEvent (Just (J.Range (J.Position sl sc) (J.Position fl fc))) _ txt)
295+
= changeChars str (Rope.Position (fromIntegral sl) (fromIntegral sc)) (Rope.Position (fromIntegral fl) (fromIntegral fc)) txt
304296
applyChange str (J.TextDocumentContentChangeEvent Nothing (Just _) _txt)
305297
= str
306298

307299
-- ---------------------------------------------------------------------
308300

309-
changeChars :: Rope -> Int -> Int -> Text -> Rope
310-
changeChars str start len new = mconcat [before, Rope.fromText new, after']
301+
changeChars :: Rope -> Rope.Position -> Rope.Position -> Text -> Rope
302+
changeChars str start finish new = mconcat [before', Rope.fromText new, after]
311303
where
312-
(before, after) = Rope.splitAt start str
313-
after' = Rope.drop len after
304+
(before, after) = fromJust $ Rope.splitAtPosition finish str
305+
(before', _) = fromJust $ Rope.splitAtPosition start before
314306

315307
-- ---------------------------------------------------------------------
316308

@@ -336,14 +328,11 @@ data PosPrefixInfo = PosPrefixInfo
336328
getCompletionPrefix :: (Monad m) => J.Position -> VirtualFile -> m (Maybe PosPrefixInfo)
337329
getCompletionPrefix pos@(J.Position l c) (VirtualFile _ _ ropetext) =
338330
return $ Just $ fromMaybe (PosPrefixInfo "" "" "" pos) $ do -- Maybe monad
339-
let headMaybe [] = Nothing
340-
headMaybe (x:_) = Just x
341-
lastMaybe [] = Nothing
331+
let lastMaybe [] = Nothing
342332
lastMaybe xs = Just $ last xs
343333

344-
curLine <- headMaybe $ T.lines $ Rope.toText
345-
$ fst $ Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) ropetext
346-
let beforePos = T.take (fromIntegral c) curLine
334+
let curRope = fst $ Rope.splitAtLine 1 $ snd $ Rope.splitAtLine (fromIntegral l) ropetext
335+
beforePos <- Rope.toText . fst <$> Rope.splitAt (fromIntegral c) curRope
347336
curWord <-
348337
if | T.null beforePos -> Just ""
349338
| T.last beforePos == ' ' -> Just "" -- don't count abc as the curword in 'abc '
@@ -357,6 +346,8 @@ getCompletionPrefix pos@(J.Position l c) (VirtualFile _ _ ropetext) =
357346
let modParts = dropWhile (not . isUpper . T.head)
358347
$ reverse $ filter (not .T.null) xs
359348
modName = T.intercalate "." modParts
349+
-- curRope is already a single line, but it may include an enclosing '\n'
350+
let curLine = T.dropWhileEnd (== '\n') $ Rope.toText curRope
360351
return $ PosPrefixInfo curLine modName x pos
361352

362353
-- ---------------------------------------------------------------------

lsp/lsp.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -122,9 +122,9 @@ test-suite unit-test
122122
, lens >= 4.15.2
123123
, network-uri
124124
, quickcheck-instances
125-
, rope-utf16-splay >= 0.2
126125
, sorted-list == 0.2.1.*
127126
, text
127+
, text-rope
128128
, unordered-containers
129129
-- For GHCI tests
130130
-- , async

lsp/test/VspSpec.hs

Lines changed: 14 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,8 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
module VspSpec where
33

4-
54
import Data.String
6-
import qualified Data.Rope.UTF16 as Rope
5+
import qualified Data.Text.Utf16.Rope as Rope
76
import Language.LSP.VFS
87
import qualified Language.LSP.Types as J
98
import qualified Data.Text as T
@@ -65,7 +64,7 @@ vspSpec = do
6564
]
6665
new = applyChange (fromString orig)
6766
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 2 1 2 5) (Just 4) ""
68-
lines (Rope.toString new) `shouldBe`
67+
Rope.lines new `shouldBe`
6968
[ "abcdg"
7069
, "module Foo where"
7170
, "-oo"
@@ -82,7 +81,7 @@ vspSpec = do
8281
]
8382
new = applyChange (fromString orig)
8483
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 2 1 2 5) Nothing ""
85-
lines (Rope.toString new) `shouldBe`
84+
Rope.lines new `shouldBe`
8685
[ "abcdg"
8786
, "module Foo where"
8887
, "-oo"
@@ -102,7 +101,7 @@ vspSpec = do
102101
]
103102
new = applyChange (fromString orig)
104103
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 2 0 3 0) (Just 8) ""
105-
lines (Rope.toString new) `shouldBe`
104+
Rope.lines new `shouldBe`
106105
[ "abcdg"
107106
, "module Foo where"
108107
, "foo :: Int"
@@ -119,7 +118,7 @@ vspSpec = do
119118
]
120119
new = applyChange (fromString orig)
121120
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 2 0 3 0) Nothing ""
122-
lines (Rope.toString new) `shouldBe`
121+
Rope.lines new `shouldBe`
123122
[ "abcdg"
124123
, "module Foo where"
125124
, "foo :: Int"
@@ -137,7 +136,7 @@ vspSpec = do
137136
]
138137
new = applyChange (fromString orig)
139138
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 1 0 3 0) (Just 19) ""
140-
lines (Rope.toString new) `shouldBe`
139+
Rope.lines new `shouldBe`
141140
[ "module Foo where"
142141
, "foo = bb"
143142
]
@@ -153,7 +152,7 @@ vspSpec = do
153152
]
154153
new = applyChange (fromString orig)
155154
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 1 0 3 0) Nothing ""
156-
lines (Rope.toString new) `shouldBe`
155+
Rope.lines new `shouldBe`
157156
[ "module Foo where"
158157
, "foo = bb"
159158
]
@@ -170,7 +169,7 @@ vspSpec = do
170169
]
171170
new = applyChange (fromString orig)
172171
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 1 16 1 16) (Just 0) "\n-- fooo"
173-
lines (Rope.toString new) `shouldBe`
172+
Rope.lines new `shouldBe`
174173
[ "abcdg"
175174
, "module Foo where"
176175
, "-- fooo"
@@ -188,7 +187,7 @@ vspSpec = do
188187
]
189188
new = applyChange (fromString orig)
190189
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 1 8 1 8) Nothing "\n-- fooo\nfoo :: Int"
191-
lines (Rope.toString new) `shouldBe`
190+
Rope.lines new `shouldBe`
192191
[ "module Foo where"
193192
, "foo = bb"
194193
, "-- fooo"
@@ -215,7 +214,7 @@ vspSpec = do
215214
-- new = changeChars (fromString orig) (J.Position 7 0) (J.Position 7 8) "baz ="
216215
new = applyChange (fromString orig)
217216
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 7 0 7 8) (Just 8) "baz ="
218-
lines (Rope.toString new) `shouldBe`
217+
Rope.lines new `shouldBe`
219218
[ "module Foo where"
220219
, "-- fooo"
221220
, "foo :: Int"
@@ -243,7 +242,7 @@ vspSpec = do
243242
-- new = changeChars (fromString orig) (J.Position 7 0) (J.Position 7 8) "baz ="
244243
new = applyChange (fromString orig)
245244
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 7 0 7 8) Nothing "baz ="
246-
lines (Rope.toString new) `shouldBe`
245+
Rope.lines new `shouldBe`
247246
[ "module Foo where"
248247
, "-- fooo"
249248
, "foo :: Int"
@@ -262,7 +261,7 @@ vspSpec = do
262261
]
263262
new = applyChange (fromString orig)
264263
$ J.TextDocumentContentChangeEvent (Just $ J.mkRange 1 0 1 3) (Just 3) "𐐀𐐀"
265-
lines (Rope.toString new) `shouldBe`
264+
Rope.lines new `shouldBe`
266265
[ "a𐐀b"
267266
, "𐐀𐐀b"
268267
]
@@ -285,13 +284,13 @@ vspSpec = do
285284
]
286285
(left,right) = Rope.splitAtLine 4 (fromString orig)
287286

288-
lines (Rope.toString left) `shouldBe`
287+
Rope.lines left `shouldBe`
289288
[ "module Foo where"
290289
, "-- fooo"
291290
, "foo :: Int"
292291
, "foo = bb"
293292
]
294-
lines (Rope.toString right) `shouldBe`
293+
Rope.lines right `shouldBe`
295294
[ ""
296295
, "bb = 5"
297296
, ""

0 commit comments

Comments
 (0)