{-# OPTIONS_GHC -Wno-name-shadowing #-}
module Data.Text.Rope.Zipper
( RopeZipper (..)
, Position (..)
, null
, cursor
, moveCursor
, setCursor
, lines
, lengthInLines
, toRope
, toText
, fromParts
, fromRope
, fromText
, splitFirstLine
, splitLastLine
, insertRope
, insertText
, insertChar
, deleteBefore
, deleteAfter
, moveForward
, moveBackward
, moveUp
, moveDown
, moveToLineStart
, moveToLineEnd
, moveToFirstLine
, moveToLastLine
)
where
import Data.Ord (clamp)
import Data.String (IsString (fromString))
import Data.Text (Text)
import Data.Text qualified as Strict
import Data.Text.Lazy qualified as Lazy
import Data.Text.Lazy.Zipper (TextZipper (TextZipper))
import Data.Text.Lazy.Zipper qualified as TextZipper
import Data.Text.Rope (Position (..), Rope)
import Data.Text.Rope qualified as Rope
import GHC.Generics (Generic)
import GHC.Records qualified as GHC
import Prelude hiding (lines, null)
import Util
data RopeZipper = RopeZipper
{ RopeZipper -> Rope
linesBefore :: !Rope
, RopeZipper -> TextZipper
currentLine :: !TextZipper
, RopeZipper -> Rope
linesAfter :: !Rope
, RopeZipper -> Word
stickyCol :: !TextZipper.Position
}
deriving stock ((forall x. RopeZipper -> Rep RopeZipper x)
-> (forall x. Rep RopeZipper x -> RopeZipper) -> Generic RopeZipper
forall x. Rep RopeZipper x -> RopeZipper
forall x. RopeZipper -> Rep RopeZipper x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RopeZipper -> Rep RopeZipper x
from :: forall x. RopeZipper -> Rep RopeZipper x
$cto :: forall x. Rep RopeZipper x -> RopeZipper
to :: forall x. Rep RopeZipper x -> RopeZipper
Generic, RopeZipper -> RopeZipper -> Bool
(RopeZipper -> RopeZipper -> Bool)
-> (RopeZipper -> RopeZipper -> Bool) -> Eq RopeZipper
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RopeZipper -> RopeZipper -> Bool
== :: RopeZipper -> RopeZipper -> Bool
$c/= :: RopeZipper -> RopeZipper -> Bool
/= :: RopeZipper -> RopeZipper -> Bool
Eq, Int -> RopeZipper -> ShowS
[RopeZipper] -> ShowS
RopeZipper -> String
(Int -> RopeZipper -> ShowS)
-> (RopeZipper -> String)
-> ([RopeZipper] -> ShowS)
-> Show RopeZipper
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RopeZipper -> ShowS
showsPrec :: Int -> RopeZipper -> ShowS
$cshow :: RopeZipper -> String
show :: RopeZipper -> String
$cshowList :: [RopeZipper] -> ShowS
showList :: [RopeZipper] -> ShowS
Show)
instance Monoid RopeZipper where
mempty :: RopeZipper
mempty :: RopeZipper
mempty =
RopeZipper
{ $sel:linesBefore:RopeZipper :: Rope
linesBefore = Rope
forall a. Monoid a => a
mempty
, $sel:currentLine:RopeZipper :: TextZipper
currentLine = TextZipper
forall a. Monoid a => a
mempty
, $sel:linesAfter:RopeZipper :: Rope
linesAfter = Rope
forall a. Monoid a => a
mempty
, $sel:stickyCol:RopeZipper :: Word
stickyCol = Word
0
}
instance Semigroup RopeZipper where
(<>) :: RopeZipper -> RopeZipper -> RopeZipper
RopeZipper
a <> :: RopeZipper -> RopeZipper -> RopeZipper
<> RopeZipper
b | Bool -> Bool
not (Rope -> Bool
Rope.null RopeZipper
a.linesAfter) = RopeZipper
a{linesAfter = a.linesAfter <> toRope b}
RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: RopeZipper -> Rope
$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
$sel:linesAfter:RopeZipper :: RopeZipper -> Rope
$sel:stickyCol:RopeZipper :: RopeZipper -> Word
linesBefore :: Rope
currentLine :: TextZipper
linesAfter :: Rope
stickyCol :: Word
..} <> RopeZipper
b =
let
(Text
firstLine, Rope
linesAfter) = Rope -> (Text, Rope)
splitFirstLine (Rope -> (Text, Rope)) -> Rope -> (Text, Rope)
forall a b. (a -> b) -> a -> b
$ RopeZipper -> Rope
toRope RopeZipper
b
in
RopeZipper
{ $sel:currentLine:RopeZipper :: TextZipper
currentLine = TextZipper
currentLine TextZipper -> TextZipper -> TextZipper
forall a. Semigroup a => a -> a -> a
<> Text -> TextZipper
TextZipper.fromText Text
firstLine
, Word
Rope
$sel:linesBefore:RopeZipper :: Rope
$sel:linesAfter:RopeZipper :: Rope
$sel:stickyCol:RopeZipper :: Word
linesBefore :: Rope
stickyCol :: Word
linesAfter :: Rope
..
}
null :: RopeZipper -> Bool
null :: RopeZipper -> Bool
null RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: RopeZipper -> Rope
$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
$sel:linesAfter:RopeZipper :: RopeZipper -> Rope
$sel:stickyCol:RopeZipper :: RopeZipper -> Word
linesBefore :: Rope
currentLine :: TextZipper
linesAfter :: Rope
stickyCol :: Word
..} = Rope -> Bool
Rope.null Rope
linesBefore Bool -> Bool -> Bool
&& TextZipper -> Bool
TextZipper.null TextZipper
currentLine Bool -> Bool -> Bool
&& Rope -> Bool
Rope.null Rope
linesAfter
cursor :: RopeZipper -> Position
cursor :: RopeZipper -> Position
cursor RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: RopeZipper -> Rope
$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
$sel:linesAfter:RopeZipper :: RopeZipper -> Rope
$sel:stickyCol:RopeZipper :: RopeZipper -> Word
linesBefore :: Rope
currentLine :: TextZipper
linesAfter :: Rope
stickyCol :: Word
..} =
Position
{ posLine :: Word
posLine = (Rope -> Position
Rope.lengthAsPosition Rope
linesBefore).posLine
, posColumn :: Word
posColumn = TextZipper
currentLine.cursor
}
instance GHC.HasField "cursor" RopeZipper Position where
getField :: RopeZipper -> Position
getField = RopeZipper -> Position
cursor
moveCursor :: (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor :: (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor Position -> Position
f RopeZipper
r
| (Word
newY Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
> Word
oldY)
Bool -> Bool -> Bool
&& (TextZipper -> Bool
TextZipper.hasTrailingNewline RopeZipper
r.currentLine Bool -> Bool -> Bool
|| Bool -> Bool
not (Rope -> Bool
Rope.null RopeZipper
r.linesAfter)) =
let (Rope
before, TextZipper
currentLine, Rope
linesAfter) = Word -> Rope -> (Rope, TextZipper, Rope)
splitAtLine (Word
absDy Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1) RopeZipper
r.linesAfter
in RopeZipper
{ $sel:linesBefore:RopeZipper :: Rope
linesBefore = RopeZipper
r.linesBefore Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Rope
currentLineAsRope Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Rope
before
, $sel:stickyCol:RopeZipper :: Word
stickyCol = (Word -> Word) -> Word
withStickyCol ((Word -> Word) -> Word) -> (Word -> Word) -> Word
forall a b. (a -> b) -> a -> b
$ Word -> Word -> Word
forall a. Ord a => a -> a -> a
min TextZipper
currentLine.cursor
, Rope
TextZipper
$sel:currentLine:RopeZipper :: TextZipper
$sel:linesAfter:RopeZipper :: Rope
currentLine :: TextZipper
linesAfter :: Rope
..
}
| Word
newY Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
oldY Bool -> Bool -> Bool
&& Word
newY Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
0 =
let ( (Text -> Word -> TextZipper) -> Word -> Text -> TextZipper
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> Word -> TextZipper
TextZipper.fromTextAt (if Word
absDx Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
0 then Word
newX else RopeZipper
r.stickyCol) ->
TextZipper -> TextZipper
moveBackFromNewline -> TextZipper
currentLine
, Rope
linesAfter
) = Rope -> (Text, Rope)
splitFirstLine (Rope -> (Text, Rope)) -> Rope -> (Text, Rope)
forall a b. (a -> b) -> a -> b
$ RopeZipper
r.linesBefore Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Rope
currentLineAsRope Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> RopeZipper
r.linesAfter
in RopeZipper
{ $sel:linesBefore:RopeZipper :: Rope
linesBefore = Rope
forall a. Monoid a => a
mempty
, TextZipper
$sel:currentLine:RopeZipper :: TextZipper
currentLine :: TextZipper
currentLine
, $sel:stickyCol:RopeZipper :: Word
stickyCol = (Word -> Word) -> Word
withStickyCol ((Word -> Word) -> Word) -> (Word -> Word) -> Word
forall a b. (a -> b) -> a -> b
$ Word -> Word -> Word
forall a. Ord a => a -> a -> a
min TextZipper
currentLine.cursor
, Rope
$sel:linesAfter:RopeZipper :: Rope
linesAfter :: Rope
..
}
| Word
newY Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
oldY Bool -> Bool -> Bool
&& Bool -> Bool
not (Rope -> Bool
Rope.null RopeZipper
r.linesBefore) =
let (Rope
linesBefore, TextZipper
currentLine, Rope
after) =
Word -> Rope -> (Rope, TextZipper, Rope)
splitAtLine
((Rope -> Position
Rope.lengthAsPosition RopeZipper
r.linesBefore).posLine Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
absDy)
RopeZipper
r.linesBefore
in RopeZipper
{ $sel:linesAfter:RopeZipper :: Rope
linesAfter = Rope
after Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Rope
currentLineAsRope Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> RopeZipper
r.linesAfter
, $sel:stickyCol:RopeZipper :: Word
stickyCol = (Word -> Word) -> Word
withStickyCol ((Word -> Word) -> Word) -> (Word -> Word) -> Word
forall a b. (a -> b) -> a -> b
$ Word -> Word -> Word
forall a. Ord a => a -> a -> a
min TextZipper
currentLine.cursor
, Rope
TextZipper
$sel:linesBefore:RopeZipper :: Rope
$sel:currentLine:RopeZipper :: TextZipper
linesBefore :: Rope
currentLine :: TextZipper
..
}
| Bool
otherwise =
let currentLine :: TextZipper
currentLine = TextZipper -> TextZipper
moveBackFromNewline (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ Word -> TextZipper -> TextZipper
TextZipper.setCursor Word
newX RopeZipper
r.currentLine
in RopeZipper
r
{ currentLine
, stickyCol =
if absDx > 0 && absDy == 0 && r.currentLine.cursor /= currentLine.cursor
then currentLine.cursor
else r.stickyCol
}
where
Position{posLine :: Position -> Word
posLine = Word
oldY, posColumn :: Position -> Word
posColumn = Word
oldX} = RopeZipper
r.cursor
Position{posLine :: Position -> Word
posLine = Word
newY, posColumn :: Position -> Word
posColumn = Word
newX} = Position -> Position
f RopeZipper
r.cursor
absDy :: Word
absDy = Word -> Word -> Word
forall a. (Num a, Ord a) => a -> a -> a
absDelta Word
newY Word
oldY
absDx :: Word
absDx = Word -> Word -> Word
forall a. (Num a, Ord a) => a -> a -> a
absDelta Word
newX Word
oldX
withStickyCol :: (Word -> Word) -> Word
withStickyCol Word -> Word
f = if Word
absDx Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
0 then RopeZipper
r.stickyCol else Word -> Word
f Word
newX
currentLineAsRope :: Rope
currentLineAsRope = Text -> Rope
Rope.fromText (Text -> Rope) -> (TextZipper -> Text) -> TextZipper -> Rope
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Lazy.toStrict (Text -> Text) -> (TextZipper -> Text) -> TextZipper -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextZipper -> Text
TextZipper.toText (TextZipper -> Rope) -> TextZipper -> Rope
forall a b. (a -> b) -> a -> b
$ RopeZipper
r.currentLine
splitAtLine :: Word -> Rope -> (Rope, TextZipper, Rope)
splitAtLine :: Word -> Rope -> (Rope, TextZipper, Rope)
splitAtLine Word
n Rope
rope =
let (Rope
before, Rope
after) = Word -> Rope -> (Rope, Rope)
Rope.splitAtLine ((Word, Word) -> Word -> Word
forall a. Ord a => (a, a) -> a -> a
clamp (Word
0, (Rope -> Position
Rope.lengthAsPosition Rope
rope).posLine) Word
n) Rope
rope
(Text
current, Rope
after') = Rope -> (Text, Rope)
splitFirstLine Rope
after
stickyCol :: Word
stickyCol = if Word
absDx Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
/= Word
0 then Word
newX else RopeZipper
r.stickyCol
in (Rope
before, TextZipper -> TextZipper
moveBackFromNewline (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ Text -> Word -> TextZipper
TextZipper.fromTextAt Text
current Word
stickyCol, Rope
after')
setCursor :: Position -> RopeZipper -> RopeZipper
setCursor :: Position -> RopeZipper -> RopeZipper
setCursor Position
c = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor (Position -> Position -> Position
forall a b. a -> b -> a
const Position
c)
lines :: RopeZipper -> [Text]
lines :: RopeZipper -> [Text]
lines = Rope -> [Text]
Rope.lines (Rope -> [Text]) -> (RopeZipper -> Rope) -> RopeZipper -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RopeZipper -> Rope
toRope
lengthInLines :: RopeZipper -> Word
lengthInLines :: RopeZipper -> Word
lengthInLines r :: RopeZipper
r@RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: RopeZipper -> Rope
$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
$sel:linesAfter:RopeZipper :: RopeZipper -> Rope
$sel:stickyCol:RopeZipper :: RopeZipper -> Word
linesBefore :: Rope
currentLine :: TextZipper
linesAfter :: Rope
stickyCol :: Word
..} = Word
before Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
current Word -> Word -> Word
forall a. Num a => a -> a -> a
+ Word
after
where
before :: Word
before = Position -> Word
posLine (Position -> Word)
-> (RopeZipper -> Position) -> RopeZipper -> Word
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RopeZipper -> Position
cursor (RopeZipper -> Word) -> RopeZipper -> Word
forall a b. (a -> b) -> a -> b
$ RopeZipper
r
current :: Word
current = if TextZipper -> Bool
TextZipper.null TextZipper
currentLine then Word
0 else Word
1
after :: Word
after = Rope -> Word
Rope.lengthInLines Rope
linesAfter
toRope :: RopeZipper -> Rope
toRope :: RopeZipper -> Rope
toRope RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: RopeZipper -> Rope
$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
$sel:linesAfter:RopeZipper :: RopeZipper -> Rope
$sel:stickyCol:RopeZipper :: RopeZipper -> Word
linesBefore :: Rope
currentLine :: TextZipper
linesAfter :: Rope
stickyCol :: Word
..} =
[Rope] -> Rope
forall a. Monoid a => [a] -> a
mconcat
[ Rope
linesBefore
, Text -> Rope
Rope.fromText (Text -> Rope) -> Text -> Rope
forall a b. (a -> b) -> a -> b
$ Text -> Text
Lazy.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ TextZipper -> Text
TextZipper.toText TextZipper
currentLine
, Rope
linesAfter
]
toText :: RopeZipper -> Text
toText :: RopeZipper -> Text
toText = Rope -> Text
Rope.toText (Rope -> Text) -> (RopeZipper -> Rope) -> RopeZipper -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RopeZipper -> Rope
toRope
fromParts :: Rope -> Rope -> RopeZipper
fromParts :: Rope -> Rope -> RopeZipper
fromParts Rope
r1 Rope
r2 = RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: Rope
$sel:currentLine:RopeZipper :: TextZipper
$sel:linesAfter:RopeZipper :: Rope
$sel:stickyCol:RopeZipper :: Word
linesBefore :: Rope
linesAfter :: Rope
currentLine :: TextZipper
stickyCol :: Word
..}
where
(Rope
linesBefore, Text
beforeCursor) = Rope -> (Rope, Text)
splitLastLine Rope
r1
(Text
afterCursor, Rope
linesAfter) = Rope -> (Text, Rope)
splitFirstLine Rope
r2
currentLine :: TextZipper
currentLine = Text -> Text -> TextZipper
TextZipper.fromParts Text
beforeCursor Text
afterCursor
stickyCol :: Word
stickyCol = TextZipper
currentLine.cursor
fromRope :: Rope -> RopeZipper
fromRope :: Rope -> RopeZipper
fromRope = (Rope -> Rope -> RopeZipper) -> Rope -> Rope -> RopeZipper
forall a b c. (a -> b -> c) -> b -> a -> c
flip Rope -> Rope -> RopeZipper
fromParts Rope
forall a. Monoid a => a
mempty
fromText :: Text -> RopeZipper
fromText :: Text -> RopeZipper
fromText = Rope -> RopeZipper
fromRope (Rope -> RopeZipper) -> (Text -> Rope) -> Text -> RopeZipper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Rope
Rope.fromText
instance IsString RopeZipper where
fromString :: String -> RopeZipper
fromString = Text -> RopeZipper
fromText (Text -> RopeZipper) -> (String -> Text) -> String -> RopeZipper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString
splitFirstLine :: Rope -> (Lazy.Text, Rope)
splitFirstLine :: Rope -> (Text, Rope)
splitFirstLine Rope
r = (Text -> Text
Lazy.fromStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Rope -> Text
Rope.toText Rope
firstLine, Rope
linesAfter)
where
(Rope
firstLine, Rope
linesAfter) = Word -> Rope -> (Rope, Rope)
Rope.splitAtLine Word
1 Rope
r
splitLastLine :: Rope -> (Rope, Lazy.Text)
splitLastLine :: Rope -> (Rope, Text)
splitLastLine Rope
r = (Rope
linesBefore, Text -> Text
Lazy.fromStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Rope -> Text
Rope.toText Rope
lastLine)
where
(Rope
linesBefore, Rope
lastLine) = Word -> Rope -> (Rope, Rope)
Rope.splitAtLine (Rope -> Position
Rope.lengthAsPosition Rope
r).posLine Rope
r
split2ndLastLine :: Rope -> (Rope, Lazy.Text)
split2ndLastLine :: Rope -> (Rope, Text)
split2ndLastLine Rope
r
| Word
numLines Word -> Word -> Bool
forall a. Ord a => a -> a -> Bool
< Word
1 = (Rope
"", Text -> Text
Lazy.fromStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Rope -> Text
Rope.toText Rope
r)
| Bool
otherwise = (Rope
linesBefore, Text -> Text
Lazy.fromStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Rope -> Text
Rope.toText Rope
lastLine)
where
numLines :: Word
numLines = (Rope -> Position
Rope.lengthAsPosition Rope
r).posLine
(Rope
linesBefore, Rope
lastLine) = Word -> Rope -> (Rope, Rope)
Rope.splitAtLine (Word
numLines Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1) Rope
r
insertRope :: Rope -> RopeZipper -> RopeZipper
insertRope :: Rope -> RopeZipper -> RopeZipper
insertRope rope :: Rope
rope@(Rope -> Position
Rope.lengthAsPosition -> Rope.Position{posLine :: Position -> Word
posLine = Word
0}) RopeZipper
r =
RopeZipper
r{currentLine, stickyCol = currentLine.cursor}
where
currentLine :: TextZipper
currentLine = Text -> TextZipper -> TextZipper
TextZipper.insert (Text -> Text
Lazy.fromStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Rope -> Text
Rope.toText Rope
rope) RopeZipper
r.currentLine
insertRope (Rope -> RopeZipper
fromRope -> RopeZipper
t) RopeZipper
r =
RopeZipper
r{linesBefore, currentLine, stickyCol = currentLine.cursor}
where
linesBefore :: Rope
linesBefore =
RopeZipper
r.linesBefore
Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> Text -> Rope
Rope.fromText (Text -> Text
Lazy.toStrict RopeZipper
r.currentLine.beforeCursor)
Rope -> Rope -> Rope
forall a. Semigroup a => a -> a -> a
<> RopeZipper
t.linesBefore
currentLine :: TextZipper
currentLine = RopeZipper
t.currentLine TextZipper -> TextZipper -> TextZipper
forall a. Semigroup a => a -> a -> a
<> Text -> TextZipper
TextZipper.fromText RopeZipper
r.currentLine.afterCursor
insertText :: Text -> RopeZipper -> RopeZipper
insertText :: Text -> RopeZipper -> RopeZipper
insertText = Rope -> RopeZipper -> RopeZipper
insertRope (Rope -> RopeZipper -> RopeZipper)
-> (Text -> Rope) -> Text -> RopeZipper -> RopeZipper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Rope
Rope.fromText
insertChar :: Char -> RopeZipper -> RopeZipper
insertChar :: Char -> RopeZipper -> RopeZipper
insertChar = Text -> RopeZipper -> RopeZipper
insertText (Text -> RopeZipper -> RopeZipper)
-> (Char -> Text) -> Char -> RopeZipper -> RopeZipper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Text
Strict.singleton
deleteBefore :: RopeZipper -> RopeZipper
deleteBefore :: RopeZipper -> RopeZipper
deleteBefore r :: RopeZipper
r@RopeZipper{$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
currentLine = TextZipper{$sel:beforeCursor:TextZipper :: TextZipper -> Text
beforeCursor = Text -> Bool
Lazy.null -> Bool
False}} =
RopeZipper
r{currentLine, stickyCol = currentLine.cursor}
where
currentLine :: TextZipper
currentLine = TextZipper -> TextZipper
TextZipper.deleteBefore RopeZipper
r.currentLine
deleteBefore RopeZipper
r = RopeZipper{$sel:linesAfter:RopeZipper :: Rope
linesAfter = RopeZipper
r.linesAfter, Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: Rope
$sel:currentLine:RopeZipper :: TextZipper
$sel:stickyCol:RopeZipper :: Word
linesBefore :: Rope
currentLine :: TextZipper
stickyCol :: Word
..}
where
(Rope
linesBefore, Text -> Text
TextZipper.removeTrailingNewline -> Text
beforeCursor) = Rope -> (Rope, Text)
split2ndLastLine RopeZipper
r.linesBefore
currentLine :: TextZipper
currentLine = Text -> Text -> TextZipper
TextZipper.fromParts Text
beforeCursor RopeZipper
r.currentLine.afterCursor
stickyCol :: Word
stickyCol = TextZipper
currentLine.cursor
deleteAfter :: RopeZipper -> RopeZipper
deleteAfter :: RopeZipper -> RopeZipper
deleteAfter r :: RopeZipper
r@RopeZipper{$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
currentLine = TextZipper{$sel:afterCursor:TextZipper :: TextZipper -> Text
afterCursor = Text
"\n"}} = RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: Rope
$sel:currentLine:RopeZipper :: TextZipper
$sel:linesAfter:RopeZipper :: Rope
$sel:stickyCol:RopeZipper :: Word
linesBefore :: Rope
linesAfter :: Rope
currentLine :: TextZipper
stickyCol :: Word
..}
where
linesBefore :: Rope
linesBefore = RopeZipper
r.linesBefore
(Text
afterCursor, Rope
linesAfter) = Rope -> (Text, Rope)
splitFirstLine RopeZipper
r.linesAfter
currentLine :: TextZipper
currentLine = Text -> Text -> TextZipper
TextZipper.fromParts RopeZipper
r.currentLine.beforeCursor Text
afterCursor
stickyCol :: Word
stickyCol = TextZipper
currentLine.cursor
deleteAfter RopeZipper{Word
Rope
TextZipper
$sel:linesBefore:RopeZipper :: RopeZipper -> Rope
$sel:currentLine:RopeZipper :: RopeZipper -> TextZipper
$sel:linesAfter:RopeZipper :: RopeZipper -> Rope
$sel:stickyCol:RopeZipper :: RopeZipper -> Word
linesBefore :: Rope
currentLine :: TextZipper
linesAfter :: Rope
stickyCol :: Word
..} = RopeZipper{$sel:currentLine:RopeZipper :: TextZipper
currentLine = TextZipper -> TextZipper
TextZipper.deleteAfter TextZipper
currentLine, Word
Rope
$sel:linesBefore:RopeZipper :: Rope
$sel:linesAfter:RopeZipper :: Rope
$sel:stickyCol:RopeZipper :: Word
linesBefore :: Rope
linesAfter :: Rope
stickyCol :: Word
..}
moveBackward :: RopeZipper -> RopeZipper
moveBackward :: RopeZipper -> RopeZipper
moveBackward = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posColumn = boundedPred c.posColumn}
moveForward :: RopeZipper -> RopeZipper
moveForward :: RopeZipper -> RopeZipper
moveForward = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posColumn = boundedSucc c.posColumn}
moveUp :: RopeZipper -> RopeZipper
moveUp :: RopeZipper -> RopeZipper
moveUp = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posLine = boundedPred c.posLine}
moveDown :: RopeZipper -> RopeZipper
moveDown :: RopeZipper -> RopeZipper
moveDown = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posLine = boundedSucc c.posLine}
moveToLineStart :: RopeZipper -> RopeZipper
moveToLineStart :: RopeZipper -> RopeZipper
moveToLineStart = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posColumn = minBound}
moveToLineEnd :: RopeZipper -> RopeZipper
moveToLineEnd :: RopeZipper -> RopeZipper
moveToLineEnd = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posColumn = maxBound}
moveToFirstLine :: RopeZipper -> RopeZipper
moveToFirstLine :: RopeZipper -> RopeZipper
moveToFirstLine = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posLine = minBound}
moveToLastLine :: RopeZipper -> RopeZipper
moveToLastLine :: RopeZipper -> RopeZipper
moveToLastLine = (Position -> Position) -> RopeZipper -> RopeZipper
moveCursor ((Position -> Position) -> RopeZipper -> RopeZipper)
-> (Position -> Position) -> RopeZipper -> RopeZipper
forall a b. (a -> b) -> a -> b
$ \Position
c -> Position
c{posLine = maxBound}
moveBackFromNewline :: TextZipper -> TextZipper
moveBackFromNewline :: TextZipper -> TextZipper
moveBackFromNewline TextZipper
t
| TextZipper -> Bool
TextZipper.hasTrailingNewline TextZipper
t Bool -> Bool -> Bool
&& Text -> Bool
Lazy.null TextZipper
t.afterCursor =
TextZipper -> TextZipper
TextZipper.moveBackward TextZipper
t
| Bool
otherwise = TextZipper
t