fix offsetMap computation to include cursor character

This commit is contained in:
pdlla 2021-07-02 10:52:22 -07:00
parent 53abc346e8
commit 15e4329217
2 changed files with 10 additions and 2 deletions

View File

@ -12,7 +12,7 @@ module Data.Text.Zipper where
import Prelude
import Control.Exception (assert)
import Control.Monad.State (evalState, forM, get, put, join)
import Control.Monad.State (evalState, forM, get, put)
import Data.Char (isSpace)
import Data.Map (Map)
import Data.Maybe (fromMaybe)
@ -418,10 +418,13 @@ displayLinesWithAlignment alignment width tag cursorTag (TextZipper lb b a la) =
linesBefore = map (wrapWithOffsetAndAlignment alignment width 0) $ reverse lb
linesAfter :: [[WrappedLine]] -- The wrapped lines after the cursor line
linesAfter = map (wrapWithOffsetAndAlignment alignment width 0) la
-- simulate trailing cursor character when computing OffsetMap
afterWithCursor = if T.null a then " " else a
offsets :: OffsetMapWithAlignment
offsets = offsetMapWithAlignmentInternal $ mconcat
[ linesBefore
, [wrapWithOffsetAndAlignment alignment width 0 $ b <> a]
, [wrapWithOffsetAndAlignment alignment width 0 $ b <> afterWithCursor]
, linesAfter
]
flattenLines = concatMap (fmap _wrappedLines_text)

View File

@ -88,6 +88,11 @@ spec =
_displayLines_cursorPos dl4 `shouldBe` (5,0)
_displayLines_cursorPos dl5 `shouldBe` (4,0)
_displayLines_cursorPos dl6 `shouldBe` (4,0)
it "displayLines - offsetMap" $ do
let
dl0 = displayLinesWithAlignment TextAlignment_Left 5 () () (end $ fromText "aoeku")
_displayLines_cursorPos dl0 `shouldBe` (0,1)
Map.size (_displayLines_offsetMap dl0) `shouldBe` 2 -- cursor character is on second line
it "displayLinesWithAlignment - spans" $ do
let
someText = top $ fromText "0123456789abcdefgh"