{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.Text.Zipper where
import Data.Char (isSpace)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Maybe (fromMaybe)
import Data.String
import Control.Monad.State (evalState, forM, get, put)
import Data.Text (Text)
import qualified Data.Text as T
import Data.Text.ICU.Char
import Data.Text.Internal (Text(..), text)
import Data.Text.Internal.Fusion (stream)
import Data.Text.Internal.Fusion.Types (Stream(..), Step(..))
import Data.Text.Unsafe
data TextZipper = TextZipper
{ TextZipper -> [Text]
_textZipper_linesBefore :: [Text]
, TextZipper -> Text
_textZipper_before :: Text
, TextZipper -> Text
_textZipper_after :: Text
, TextZipper -> [Text]
_textZipper_linesAfter :: [Text]
}
deriving (Int -> TextZipper -> ShowS
[TextZipper] -> ShowS
TextZipper -> String
(Int -> TextZipper -> ShowS)
-> (TextZipper -> String)
-> ([TextZipper] -> ShowS)
-> Show TextZipper
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TextZipper] -> ShowS
$cshowList :: [TextZipper] -> ShowS
show :: TextZipper -> String
$cshow :: TextZipper -> String
showsPrec :: Int -> TextZipper -> ShowS
$cshowsPrec :: Int -> TextZipper -> ShowS
Show)
instance IsString TextZipper where
fromString :: String -> TextZipper
fromString = Text -> TextZipper
fromText (Text -> TextZipper) -> (String -> Text) -> String -> TextZipper
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
T.pack
mapZipper :: (Char -> Char) -> TextZipper -> TextZipper
mapZipper :: (Char -> Char) -> TextZipper -> TextZipper
mapZipper f :: Char -> Char
f (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = TextZipper :: [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper
{ _textZipper_linesBefore :: [Text]
_textZipper_linesBefore = (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char -> Char) -> Text -> Text
T.map Char -> Char
f) [Text]
lb
, _textZipper_before :: Text
_textZipper_before = (Char -> Char) -> Text -> Text
T.map Char -> Char
f Text
b
, _textZipper_after :: Text
_textZipper_after = (Char -> Char) -> Text -> Text
T.map Char -> Char
f Text
a
, _textZipper_linesAfter :: [Text]
_textZipper_linesAfter = (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Char -> Char) -> Text -> Text
T.map Char -> Char
f) [Text]
la
}
left :: TextZipper -> TextZipper
left :: TextZipper -> TextZipper
left = Int -> TextZipper -> TextZipper
leftN 1
leftN :: Int -> TextZipper -> TextZipper
leftN :: Int -> TextZipper -> TextZipper
leftN n :: Int
n z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) =
if Text -> Int
T.length Text
b Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n
then
let n' :: Int
n' = Text -> Int
T.length Text
b Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n
in [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb (Int -> Text -> Text
T.take Int
n' Text
b) (Int -> Text -> Text
T.drop Int
n' Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) [Text]
la
else case [Text]
lb of
[] -> TextZipper -> TextZipper
home TextZipper
z
(l :: Text
l:ls :: [Text]
ls) -> Int -> TextZipper -> TextZipper
leftN (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
b Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
ls Text
l "" ((Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
la)
right :: TextZipper -> TextZipper
right :: TextZipper -> TextZipper
right = Int -> TextZipper -> TextZipper
rightN 1
rightN :: Int -> TextZipper -> TextZipper
rightN :: Int -> TextZipper -> TextZipper
rightN n :: Int
n z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) =
if Text -> Int
T.length Text
a Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
n
then [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb (Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.take Int
n Text
a) (Int -> Text -> Text
T.drop Int
n Text
a) [Text]
la
else case [Text]
la of
[] -> TextZipper -> TextZipper
end TextZipper
z
(l :: Text
l:ls :: [Text]
ls) -> Int -> TextZipper -> TextZipper
rightN (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Text -> Int
T.length Text
a Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper ((Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
lb) "" Text
l [Text]
ls
up :: TextZipper -> TextZipper
up :: TextZipper -> TextZipper
up z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = case [Text]
lb of
[] -> TextZipper
z
(l :: Text
l:ls :: [Text]
ls) ->
let (b' :: Text
b', a' :: Text
a') = Int -> Text -> (Text, Text)
T.splitAt (Text -> Int
T.length Text
b) Text
l
in [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
ls Text
b' Text
a' ((Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
la)
down :: TextZipper -> TextZipper
down :: TextZipper -> TextZipper
down z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = case [Text]
la of
[] -> TextZipper
z
(l :: Text
l:ls :: [Text]
ls) ->
let (b' :: Text
b', a' :: Text
a') = Int -> Text -> (Text, Text)
T.splitAt (Text -> Int
T.length Text
b) Text
l
in [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper ((Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: [Text]
lb) Text
b' Text
a' [Text]
ls
pageUp :: Int -> TextZipper -> TextZipper
pageUp :: Int -> TextZipper -> TextZipper
pageUp pageSize :: Int
pageSize z :: TextZipper
z = if Int
pageSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 0
then TextZipper
z
else Int -> TextZipper -> TextZipper
pageUp (Int
pageSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ TextZipper -> TextZipper
up TextZipper
z
pageDown :: Int -> TextZipper -> TextZipper
pageDown :: Int -> TextZipper -> TextZipper
pageDown pageSize :: Int
pageSize z :: TextZipper
z = if Int
pageSize Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 0
then TextZipper
z
else Int -> TextZipper -> TextZipper
pageDown (Int
pageSize Int -> Int -> Int
forall a. Num a => a -> a -> a
- 1) (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ TextZipper -> TextZipper
down TextZipper
z
home :: TextZipper -> TextZipper
home :: TextZipper -> TextZipper
home (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb "" (Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) [Text]
la
end :: TextZipper -> TextZipper
end :: TextZipper -> TextZipper
end (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb (Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) "" [Text]
la
top :: TextZipper -> TextZipper
top :: TextZipper -> TextZipper
top (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = case [Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
lb of
[] -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [] "" (Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a) [Text]
la
(start :: Text
start:rest :: [Text]
rest) -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [] "" Text
start ([Text]
rest [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a] [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
la)
insertChar :: Char -> TextZipper -> TextZipper
insertChar :: Char -> TextZipper -> TextZipper
insertChar i :: Char
i = Text -> TextZipper -> TextZipper
insert (Char -> Text
T.singleton Char
i)
insert :: Text -> TextZipper -> TextZipper
insert :: Text -> TextZipper -> TextZipper
insert i :: Text
i z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = case (Char -> Bool) -> Text -> [Text]
T.split (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
=='\n') Text
i of
[] -> TextZipper
z
(start :: Text
start:rest :: [Text]
rest) -> case [Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
rest of
[] -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb (Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
start) Text
a [Text]
la
(l :: Text
l:ls :: [Text]
ls) -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper ([Text]
ls [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
start] [Text] -> [Text] -> [Text]
forall a. Semigroup a => a -> a -> a
<> [Text]
lb) Text
l Text
a [Text]
la
deleteLeft :: TextZipper-> TextZipper
deleteLeft :: TextZipper -> TextZipper
deleteLeft z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = case Text -> Maybe (Text, Char)
T.unsnoc Text
b of
Nothing -> case [Text]
lb of
[] -> TextZipper
z
(l :: Text
l:ls :: [Text]
ls) -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
ls Text
l Text
a [Text]
la
Just (b' :: Text
b', _) -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb Text
b' Text
a [Text]
la
deleteRight :: TextZipper -> TextZipper
deleteRight :: TextZipper -> TextZipper
deleteRight z :: TextZipper
z@(TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = case Text -> Maybe (Char, Text)
T.uncons Text
a of
Nothing -> case [Text]
la of
[] -> TextZipper
z
(l :: Text
l:ls :: [Text]
ls) -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb Text
b Text
l [Text]
ls
Just (_, a' :: Text
a') -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb Text
b Text
a' [Text]
la
deleteLeftWord :: TextZipper -> TextZipper
deleteLeftWord :: TextZipper -> TextZipper
deleteLeftWord (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) =
let b' :: Text
b' = (Char -> Bool) -> Text -> Text
T.dropWhileEnd Char -> Bool
isSpace Text
b
in if Text -> Bool
T.null Text
b'
then case [Text]
lb of
[] -> [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [] Text
b' Text
a [Text]
la
(l :: Text
l:ls :: [Text]
ls) -> TextZipper -> TextZipper
deleteLeftWord (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
ls Text
l Text
a [Text]
la
else [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [Text]
lb ((Char -> Bool) -> Text -> Text
T.dropWhileEnd (Bool -> Bool
not (Bool -> Bool) -> (Char -> Bool) -> Char -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Bool
isSpace) Text
b') Text
a [Text]
la
tab :: Int -> TextZipper -> TextZipper
tab :: Int -> TextZipper -> TextZipper
tab n :: Int
n z :: TextZipper
z@(TextZipper _ b :: Text
b _ _) =
Text -> TextZipper -> TextZipper
insert (Int -> Text -> Text
T.replicate (Int -> Int
forall a. Enum a => a -> Int
fromEnum (Int -> Int) -> Int -> Int
forall a b. (a -> b) -> a -> b
$ Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Text -> Int
T.length Text
b Int -> Int -> Int
forall a. Integral a => a -> a -> a
`mod` Int -> Int -> Int
forall a. Ord a => a -> a -> a
max 1 Int
n)) " ") TextZipper
z
value :: TextZipper -> Text
value :: TextZipper -> Text
value (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) = Text -> [Text] -> Text
T.intercalate "\n" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [Text]
forall a. Monoid a => [a] -> a
mconcat [ [Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
lb
, [Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a]
, [Text]
la
]
empty :: TextZipper
empty :: TextZipper
empty = [Text] -> Text -> Text -> [Text] -> TextZipper
TextZipper [] "" "" []
fromText :: Text -> TextZipper
fromText :: Text -> TextZipper
fromText = (Text -> TextZipper -> TextZipper)
-> TextZipper -> Text -> TextZipper
forall a b c. (a -> b -> c) -> b -> a -> c
flip Text -> TextZipper -> TextZipper
insert TextZipper
empty
data Span tag = Span tag Text
deriving (Int -> Span tag -> ShowS
[Span tag] -> ShowS
Span tag -> String
(Int -> Span tag -> ShowS)
-> (Span tag -> String) -> ([Span tag] -> ShowS) -> Show (Span tag)
forall tag. Show tag => Int -> Span tag -> ShowS
forall tag. Show tag => [Span tag] -> ShowS
forall tag. Show tag => Span tag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Span tag] -> ShowS
$cshowList :: forall tag. Show tag => [Span tag] -> ShowS
show :: Span tag -> String
$cshow :: forall tag. Show tag => Span tag -> String
showsPrec :: Int -> Span tag -> ShowS
$cshowsPrec :: forall tag. Show tag => Int -> Span tag -> ShowS
Show)
data DisplayLines tag = DisplayLines
{ DisplayLines tag -> [[Span tag]]
_displayLines_spans :: [[Span tag]]
, DisplayLines tag -> Map Int Int
_displayLines_offsetMap :: Map Int Int
, DisplayLines tag -> Int
_displayLines_cursorY :: Int
}
deriving (Int -> DisplayLines tag -> ShowS
[DisplayLines tag] -> ShowS
DisplayLines tag -> String
(Int -> DisplayLines tag -> ShowS)
-> (DisplayLines tag -> String)
-> ([DisplayLines tag] -> ShowS)
-> Show (DisplayLines tag)
forall tag. Show tag => Int -> DisplayLines tag -> ShowS
forall tag. Show tag => [DisplayLines tag] -> ShowS
forall tag. Show tag => DisplayLines tag -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DisplayLines tag] -> ShowS
$cshowList :: forall tag. Show tag => [DisplayLines tag] -> ShowS
show :: DisplayLines tag -> String
$cshow :: forall tag. Show tag => DisplayLines tag -> String
showsPrec :: Int -> DisplayLines tag -> ShowS
$cshowsPrec :: forall tag. Show tag => Int -> DisplayLines tag -> ShowS
Show)
displayLines
:: Int
-> tag
-> tag
-> TextZipper
-> DisplayLines tag
displayLines :: Int -> tag -> tag -> TextZipper -> DisplayLines tag
displayLines width :: Int
width tag :: tag
tag cursorTag :: tag
cursorTag (TextZipper lb :: [Text]
lb b :: Text
b a :: Text
a la :: [Text]
la) =
let linesBefore :: [[Text]]
linesBefore :: [[Text]]
linesBefore = (Text -> [Text]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Text -> [Text]
wrapWithOffset Int
width 0) ([Text] -> [[Text]]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> a -> b
$ [Text] -> [Text]
forall a. [a] -> [a]
reverse [Text]
lb
linesAfter :: [[Text]]
linesAfter :: [[Text]]
linesAfter = (Text -> [Text]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Text -> [Text]
wrapWithOffset Int
width 0) [Text]
la
offsets :: Map Int Int
offsets :: Map Int Int
offsets = [[Text]] -> Map Int Int
offsetMap ([[Text]] -> Map Int Int) -> [[Text]] -> Map Int Int
forall a b. (a -> b) -> a -> b
$ [[[Text]]] -> [[Text]]
forall a. Monoid a => [a] -> a
mconcat
[ [[Text]]
linesBefore
, [Int -> Int -> Text -> [Text]
wrapWithOffset Int
width 0 (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text
b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
a]
, [[Text]]
linesAfter
]
spansBefore :: [[Span tag]]
spansBefore = (Text -> [Span tag]) -> [Text] -> [[Span tag]]
forall a b. (a -> b) -> [a] -> [b]
map ((Span tag -> [Span tag] -> [Span tag]
forall a. a -> [a] -> [a]
:[]) (Span tag -> [Span tag])
-> (Text -> Span tag) -> Text -> [Span tag]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. tag -> Text -> Span tag
forall tag. tag -> Text -> Span tag
Span tag
tag) ([Text] -> [[Span tag]]) -> [Text] -> [[Span tag]]
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Text]]
linesBefore
spansAfter :: [[Span tag]]
spansAfter = (Text -> [Span tag]) -> [Text] -> [[Span tag]]
forall a b. (a -> b) -> [a] -> [b]
map ((Span tag -> [Span tag] -> [Span tag]
forall a. a -> [a] -> [a]
:[]) (Span tag -> [Span tag])
-> (Text -> Span tag) -> Text -> [Span tag]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. tag -> Text -> Span tag
forall tag. tag -> Text -> Span tag
Span tag
tag) ([Text] -> [[Span tag]]) -> [Text] -> [[Span tag]]
forall a b. (a -> b) -> a -> b
$ [[Text]] -> [Text]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[Text]]
linesAfter
(spansCurrentBefore :: [[Span tag]]
spansCurrentBefore, spansCurLineBefore :: [Span tag]
spansCurLineBefore) = ([[Span tag]], [Span tag])
-> Maybe ([[Span tag]], [Span tag]) -> ([[Span tag]], [Span tag])
forall a. a -> Maybe a -> a
fromMaybe ([], []) (Maybe ([[Span tag]], [Span tag]) -> ([[Span tag]], [Span tag]))
-> Maybe ([[Span tag]], [Span tag]) -> ([[Span tag]], [Span tag])
forall a b. (a -> b) -> a -> b
$
[[Span tag]] -> Maybe ([[Span tag]], [Span tag])
forall a. [a] -> Maybe ([a], a)
initLast ([[Span tag]] -> Maybe ([[Span tag]], [Span tag]))
-> [[Span tag]] -> Maybe ([[Span tag]], [Span tag])
forall a b. (a -> b) -> a -> b
$ (Text -> [Span tag]) -> [Text] -> [[Span tag]]
forall a b. (a -> b) -> [a] -> [b]
map ((Span tag -> [Span tag] -> [Span tag]
forall a. a -> [a] -> [a]
:[]) (Span tag -> [Span tag])
-> (Text -> Span tag) -> Text -> [Span tag]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. tag -> Text -> Span tag
forall tag. tag -> Text -> Span tag
Span tag
tag) (Int -> Int -> Text -> [Text]
wrapWithOffset Int
width 0 Text
b)
curLineOffset :: Int
curLineOffset = [Span tag] -> Int
forall tag. [Span tag] -> Int
spansWidth [Span tag]
spansCurLineBefore
cursorAfterEOL :: Bool
cursorAfterEOL = Int
curLineOffset Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
width
cursorCharWidth :: Int
cursorCharWidth = case Text -> Maybe (Char, Text)
T.uncons Text
a of
Nothing -> 1
Just (c :: Char
c, _) -> Char -> Int
charWidth Char
c
(spansCurLineAfter :: [Span tag]
spansCurLineAfter, spansCurrentAfter :: [[Span tag]]
spansCurrentAfter) = ([Span tag], [[Span tag]])
-> Maybe ([Span tag], [[Span tag]]) -> ([Span tag], [[Span tag]])
forall a. a -> Maybe a -> a
fromMaybe ([], []) (Maybe ([Span tag], [[Span tag]]) -> ([Span tag], [[Span tag]]))
-> Maybe ([Span tag], [[Span tag]]) -> ([Span tag], [[Span tag]])
forall a b. (a -> b) -> a -> b
$
[[Span tag]] -> Maybe ([Span tag], [[Span tag]])
forall a. [a] -> Maybe (a, [a])
headTail ([[Span tag]] -> Maybe ([Span tag], [[Span tag]]))
-> [[Span tag]] -> Maybe ([Span tag], [[Span tag]])
forall a b. (a -> b) -> a -> b
$ case Text -> Maybe (Char, Text)
T.uncons Text
a of
Nothing -> [[tag -> Text -> Span tag
forall tag. tag -> Text -> Span tag
Span tag
cursorTag " "]]
Just (c :: Char
c, rest :: Text
rest) ->
let o :: Int
o = if Bool
cursorAfterEOL then Int
cursorCharWidth else Int
curLineOffset Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
cursorCharWidth
cursor :: Span tag
cursor = tag -> Text -> Span tag
forall tag. tag -> Text -> Span tag
Span tag
cursorTag (Char -> Text
T.singleton Char
c)
in case (Text -> [Span tag]) -> [Text] -> [[Span tag]]
forall a b. (a -> b) -> [a] -> [b]
map ((Span tag -> [Span tag] -> [Span tag]
forall a. a -> [a] -> [a]
:[]) (Span tag -> [Span tag])
-> (Text -> Span tag) -> Text -> [Span tag]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. tag -> Text -> Span tag
forall tag. tag -> Text -> Span tag
Span tag
tag) (Int -> Int -> Text -> [Text]
wrapWithOffset Int
width Int
o Text
rest) of
[] -> [[Span tag
cursor]]
(l :: [Span tag]
l:ls :: [[Span tag]]
ls) -> (Span tag
cursor Span tag -> [Span tag] -> [Span tag]
forall a. a -> [a] -> [a]
: [Span tag]
l) [Span tag] -> [[Span tag]] -> [[Span tag]]
forall a. a -> [a] -> [a]
: [[Span tag]]
ls
in DisplayLines :: forall tag. [[Span tag]] -> Map Int Int -> Int -> DisplayLines tag
DisplayLines
{ _displayLines_spans :: [[Span tag]]
_displayLines_spans = [[[Span tag]]] -> [[Span tag]]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [[Span tag]]
spansBefore
, [[Span tag]]
spansCurrentBefore
, if Bool
cursorAfterEOL
then [ [Span tag]
spansCurLineBefore, [Span tag]
spansCurLineAfter ]
else [ [Span tag]
spansCurLineBefore [Span tag] -> [Span tag] -> [Span tag]
forall a. Semigroup a => a -> a -> a
<> [Span tag]
spansCurLineAfter ]
, [[Span tag]]
spansCurrentAfter
, [[Span tag]]
spansAfter
]
, _displayLines_offsetMap :: Map Int Int
_displayLines_offsetMap = Map Int Int
offsets
, _displayLines_cursorY :: Int
_displayLines_cursorY = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum
[ [[Span tag]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Span tag]]
spansBefore
, [[Span tag]] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [[Span tag]]
spansCurrentBefore
, if Bool
cursorAfterEOL then Int
cursorCharWidth else 0
]
}
where
initLast :: [a] -> Maybe ([a], a)
initLast :: [a] -> Maybe ([a], a)
initLast = \case
[] -> Maybe ([a], a)
forall a. Maybe a
Nothing
(x :: a
x:xs :: [a]
xs) -> case [a] -> Maybe ([a], a)
forall a. [a] -> Maybe ([a], a)
initLast [a]
xs of
Nothing -> ([a], a) -> Maybe ([a], a)
forall a. a -> Maybe a
Just ([], a
x)
Just (ys :: [a]
ys, y :: a
y) -> ([a], a) -> Maybe ([a], a)
forall a. a -> Maybe a
Just (a
xa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
ys, a
y)
headTail :: [a] -> Maybe (a, [a])
headTail :: [a] -> Maybe (a, [a])
headTail = \case
[] -> Maybe (a, [a])
forall a. Maybe a
Nothing
x :: a
x:xs :: [a]
xs -> (a, [a]) -> Maybe (a, [a])
forall a. a -> Maybe a
Just (a
x, [a]
xs)
wrapWithOffset
:: Int
-> Int
-> Text
-> [Text]
wrapWithOffset :: Int -> Int -> Text -> [Text]
wrapWithOffset maxWidth :: Int
maxWidth _ _ | Int
maxWidth Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 0 = []
wrapWithOffset maxWidth :: Int
maxWidth n :: Int
n xs :: Text
xs =
let (firstLine :: Text
firstLine, rest :: Text
rest) = Int -> Text -> (Text, Text)
splitAtWidth (Int
maxWidth Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) Text
xs
in Text
firstLine Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: ((Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Int -> Text -> Text
takeWidth Int
maxWidth) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Bool) -> [Text] -> [Text]
forall a. (a -> Bool) -> [a] -> [a]
takeWhile (Bool -> Bool
not (Bool -> Bool) -> (Text -> Bool) -> Text -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Bool
T.null) ([Text] -> [Text]) -> (Text -> [Text]) -> Text -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Text -> Text) -> Text -> [Text]
forall a. (a -> a) -> a -> [a]
iterate (Int -> Text -> Text
dropWidth Int
maxWidth) (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ Text
rest)
splitAtWidth :: Int -> Text -> (Text, Text)
splitAtWidth :: Int -> Text -> (Text, Text)
splitAtWidth n :: Int
n t :: Text
t@(Text arr :: Array
arr off :: Int
off len :: Int
len)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= 0 = (Text
T.empty, Text
t)
| Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Text -> Int
textWidth Text
t = (Text
t, Text
T.empty)
| Bool
otherwise = let k :: Int
k = Int -> Text -> Int
iterNWidth Int
n Text
t
in (Array -> Int -> Int -> Text
text Array
arr Int
off Int
k, Array -> Int -> Int -> Text
text Array
arr (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
k) (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
k))
where
iterNWidth :: Int -> Text -> Int
iterNWidth :: Int -> Text -> Int
iterNWidth n' :: Int
n' t' :: Text
t'@(Text _ _ len' :: Int
len') = Int -> Int -> Int
loop 0 0
where loop :: Int -> Int -> Int
loop !Int
i !Int
cnt
| Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len' Bool -> Bool -> Bool
|| Int
cnt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
n' = Int
i
| Bool
otherwise = Int -> Int -> Int
loop (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
d) (Int
cnt Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
w)
where Iter c :: Char
c d :: Int
d = Text -> Int -> Iter
iter Text
t' Int
i
w :: Int
w = Char -> Int
charWidth Char
c
takeWidth :: Int -> Text -> Text
takeWidth :: Int -> Text -> Text
takeWidth n :: Int
n = (Text, Text) -> Text
forall a b. (a, b) -> a
fst ((Text, Text) -> Text) -> (Text -> (Text, Text)) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> (Text, Text)
splitAtWidth Int
n
dropWidth :: Int -> Text -> Text
dropWidth :: Int -> Text -> Text
dropWidth n :: Int
n = (Text, Text) -> Text
forall a b. (a, b) -> b
snd ((Text, Text) -> Text) -> (Text -> (Text, Text)) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Text -> (Text, Text)
splitAtWidth Int
n
charWidth :: Char -> Int
charWidth :: Char -> Int
charWidth c :: Char
c = case EastAsianWidth_ -> Char -> EastAsianWidth
forall p v. Property p v => p -> Char -> v
property EastAsianWidth_
EastAsianWidth Char
c of
EAFull -> 2
EAWide -> 2
_ -> 1
offsetMap
:: [[Text]]
-> Map Int Int
offsetMap :: [[Text]] -> Map Int Int
offsetMap ts :: [[Text]]
ts = State (Int, Int) (Map Int Int) -> (Int, Int) -> Map Int Int
forall s a. State s a -> s -> a
evalState ([[Text]] -> State (Int, Int) (Map Int Int)
forall k (f :: * -> *) (f :: * -> *) (f :: * -> *).
(Ord k, Traversable f, Traversable f, MonadState (k, Int) f,
Num k) =>
f (f Text) -> f (Map k Int)
offsetMap' [[Text]]
ts) (0, 0)
where
offsetMap' :: f (f Text) -> f (Map k Int)
offsetMap' xs :: f (f Text)
xs = (f (Map k Int) -> Map k Int) -> f (f (Map k Int)) -> f (Map k Int)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap f (Map k Int) -> Map k Int
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
Map.unions (f (f (Map k Int)) -> f (Map k Int))
-> f (f (Map k Int)) -> f (Map k Int)
forall a b. (a -> b) -> a -> b
$ f (f Text) -> (f Text -> f (Map k Int)) -> f (f (Map k Int))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM f (f Text)
xs ((f Text -> f (Map k Int)) -> f (f (Map k Int)))
-> (f Text -> f (Map k Int)) -> f (f (Map k Int))
forall a b. (a -> b) -> a -> b
$ \x :: f Text
x -> do
f (Map k Int)
maps <- f Text -> (Text -> f (Map k Int)) -> f (f (Map k Int))
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM f Text
x ((Text -> f (Map k Int)) -> f (f (Map k Int)))
-> (Text -> f (Map k Int)) -> f (f (Map k Int))
forall a b. (a -> b) -> a -> b
$ \line :: Text
line -> do
let l :: Int
l = Text -> Int
T.length Text
line
(dl :: k
dl, o :: Int
o) <- f (k, Int)
forall s (m :: * -> *). MonadState s m => m s
get
(k, Int) -> f ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (k
dl k -> k -> k
forall a. Num a => a -> a -> a
+ 1, Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l)
Map k Int -> f (Map k Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map k Int -> f (Map k Int)) -> Map k Int -> f (Map k Int)
forall a b. (a -> b) -> a -> b
$ k -> Int -> Map k Int
forall k a. k -> a -> Map k a
Map.singleton k
dl Int
o
(dl :: k
dl, o :: Int
o) <- f (k, Int)
forall s (m :: * -> *). MonadState s m => m s
get
(k, Int) -> f ()
forall s (m :: * -> *). MonadState s m => s -> m ()
put (k
dl, Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1)
Map k Int -> f (Map k Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map k Int -> f (Map k Int)) -> Map k Int -> f (Map k Int)
forall a b. (a -> b) -> a -> b
$ k -> Int -> Map k Int -> Map k Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert k
dl (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ 1) (Map k Int -> Map k Int) -> Map k Int -> Map k Int
forall a b. (a -> b) -> a -> b
$ f (Map k Int) -> Map k Int
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
Map.unions f (Map k Int)
maps
goToDisplayLinePosition :: Int -> Int -> DisplayLines tag -> TextZipper -> TextZipper
goToDisplayLinePosition :: Int -> Int -> DisplayLines tag -> TextZipper -> TextZipper
goToDisplayLinePosition x :: Int
x y :: Int
y dl :: DisplayLines tag
dl tz :: TextZipper
tz =
let offset :: Maybe Int
offset = Int -> Map Int Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Int
y (Map Int Int -> Maybe Int) -> Map Int Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$ DisplayLines tag -> Map Int Int
forall tag. DisplayLines tag -> Map Int Int
_displayLines_offsetMap DisplayLines tag
dl
in case Maybe Int
offset of
Nothing -> TextZipper
tz
Just o :: Int
o ->
let displayLineLength :: Int
displayLineLength = case Int -> [[Span tag]] -> [[Span tag]]
forall a. Int -> [a] -> [a]
drop Int
y ([[Span tag]] -> [[Span tag]]) -> [[Span tag]] -> [[Span tag]]
forall a b. (a -> b) -> a -> b
$ DisplayLines tag -> [[Span tag]]
forall tag. DisplayLines tag -> [[Span tag]]
_displayLines_spans DisplayLines tag
dl of
[] -> Int
x
(s :: [Span tag]
s:_) -> [Span tag] -> Int
forall tag. [Span tag] -> Int
spansWidth [Span tag]
s
in Int -> TextZipper -> TextZipper
rightN (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
displayLineLength Int
x) (TextZipper -> TextZipper) -> TextZipper -> TextZipper
forall a b. (a -> b) -> a -> b
$ TextZipper -> TextZipper
top TextZipper
tz
spansWidth :: [Span tag] -> Int
spansWidth :: [Span tag] -> Int
spansWidth = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> ([Span tag] -> [Int]) -> [Span tag] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Span tag -> Int) -> [Span tag] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\(Span _ t :: Text
t) -> Text -> Int
textWidth Text
t)
spansLength :: [Span tag] -> Int
spansLength :: [Span tag] -> Int
spansLength = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ([Int] -> Int) -> ([Span tag] -> [Int]) -> [Span tag] -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Span tag -> Int) -> [Span tag] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (\(Span _ t :: Text
t) -> Text -> Int
T.length Text
t)
textWidth :: Text -> Int
textWidth :: Text -> Int
textWidth t :: Text
t = Stream Char -> Int
widthI (Text -> Stream Char
stream Text
t)
widthI :: Stream Char -> Int
widthI :: Stream Char -> Int
widthI (Stream next :: s -> Step s Char
next s0 :: s
s0 _len :: Size
_len) = Int -> s -> Int
loop_length 0 s
s0
where
loop_length :: Int -> s -> Int
loop_length !Int
z s :: s
s = case s -> Step s Char
next s
s of
Done -> Int
z
Skip s' :: s
s' -> Int -> s -> Int
loop_length Int
z s
s'
Yield c :: Char
c s' :: s
s' -> Int -> s -> Int
loop_length (Int
z Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Char -> Int
charWidth Char
c) s
s'
{-# INLINE[0] widthI #-}