{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
module Language.LSP.Protocol.Types.Edit where
import Data.Text (Text)
import Data.Text qualified as T
import Control.Lens hiding (index)
import Language.LSP.Protocol.Internal.Types
import Language.LSP.Protocol.Types.Common
type DocumentChange = TextDocumentEdit |? CreateFile |? RenameFile |? DeleteFile
applyTextEdit :: TextEdit -> Text -> Text
applyTextEdit :: TextEdit -> Text -> Text
applyTextEdit (TextEdit (Range Position
sp Position
ep) Text
newText) Text
oldText =
let (Text
_, Text
afterEnd) = Position -> Text -> (Text, Text)
splitAtPos Position
ep Text
oldText
(Text
beforeStart, Text
_) = Position -> Text -> (Text, Text)
splitAtPos Position
sp Text
oldText
in forall a. Monoid a => [a] -> a
mconcat [Text
beforeStart, Text
newText, Text
afterEnd]
where
splitAtPos :: Position -> Text -> (Text, Text)
splitAtPos :: Position -> Text -> (Text, Text)
splitAtPos (Position UInt
sl UInt
sc) Text
t =
let index :: UInt
index = UInt
sc forall a. Num a => a -> a -> a
+ UInt -> Text -> UInt
startLineIndex UInt
sl Text
t
in Int -> Text -> (Text, Text)
T.splitAt (forall a b. (Integral a, Num b) => a -> b
fromIntegral UInt
index) Text
t
startLineIndex :: UInt -> Text -> UInt
startLineIndex :: UInt -> Text -> UInt
startLineIndex UInt
0 Text
_ = UInt
0
startLineIndex UInt
line Text
t' =
case (Char -> Bool) -> Text -> Maybe Int
T.findIndex (forall a. Eq a => a -> a -> Bool
== Char
'\n') Text
t' of
Just Int
i -> forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i forall a. Num a => a -> a -> a
+ UInt
1 forall a. Num a => a -> a -> a
+ UInt -> Text -> UInt
startLineIndex (UInt
line forall a. Num a => a -> a -> a
- UInt
1) (Int -> Text -> Text
T.drop (Int
i forall a. Num a => a -> a -> a
+ Int
1) Text
t')
Maybe Int
Nothing -> forall a b. (Integral a, Num b) => a -> b
fromIntegral forall a b. (a -> b) -> a -> b
$ Text -> Int
T.length Text
t'
editTextEdit :: TextEdit -> TextEdit -> TextEdit
editTextEdit :: TextEdit -> TextEdit -> TextEdit
editTextEdit (TextEdit Range
origRange Text
origText) TextEdit
innerEdit =
let newText :: Text
newText = TextEdit -> Text -> Text
applyTextEdit TextEdit
innerEdit Text
origText
in Range -> Text -> TextEdit
TextEdit Range
origRange Text
newText
_versionedTextDocumentIdentifier :: Prism' OptionalVersionedTextDocumentIdentifier VersionedTextDocumentIdentifier
_versionedTextDocumentIdentifier :: Prism'
OptionalVersionedTextDocumentIdentifier
VersionedTextDocumentIdentifier
_versionedTextDocumentIdentifier = forall b t s a. (b -> t) -> (s -> Either t a) -> Prism s t a b
prism VersionedTextDocumentIdentifier
-> OptionalVersionedTextDocumentIdentifier
down OptionalVersionedTextDocumentIdentifier
-> Either
OptionalVersionedTextDocumentIdentifier
VersionedTextDocumentIdentifier
up
where
down :: VersionedTextDocumentIdentifier
-> OptionalVersionedTextDocumentIdentifier
down (VersionedTextDocumentIdentifier Uri
uri Int32
v) = Uri -> (Int32 |? Null) -> OptionalVersionedTextDocumentIdentifier
OptionalVersionedTextDocumentIdentifier Uri
uri (forall a b. a -> a |? b
InL Int32
v)
up :: OptionalVersionedTextDocumentIdentifier
-> Either
OptionalVersionedTextDocumentIdentifier
VersionedTextDocumentIdentifier
up (OptionalVersionedTextDocumentIdentifier Uri
uri (InL Int32
v)) = forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ Uri -> Int32 -> VersionedTextDocumentIdentifier
VersionedTextDocumentIdentifier Uri
uri Int32
v
up i :: OptionalVersionedTextDocumentIdentifier
i@(OptionalVersionedTextDocumentIdentifier Uri
_ (InR Null
_)) = forall a b. a -> Either a b
Left OptionalVersionedTextDocumentIdentifier
i