@@ -52,8 +52,8 @@ import Data.Ord
5252import qualified Data.HashMap.Strict as HashMap
5353import qualified Data.Map.Strict as Map
5454import 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
5757import qualified Language.LSP.Types as J
5858import qualified Language.LSP.Types.Lens as J
5959import 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
291291applyChange :: Rope -> J. TextDocumentContentChangeEvent -> Rope
292292applyChange _ (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
304296applyChange 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
336328getCompletionPrefix :: (Monad m ) => J. Position -> VirtualFile -> m (Maybe PosPrefixInfo )
337329getCompletionPrefix 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-- ---------------------------------------------------------------------
0 commit comments