{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_HADDOCK hide #-}
module Core.Text.Breaking
( breakRope
, breakWords
, breakLines
, breakPieces
, intoPieces
, intoChunks
, isNewline
) where
import Core.Text.Rope
import Data.Char (isSpace)
import Data.List (uncons)
import qualified Data.Text.Short as S (ShortText, break, empty, null, uncons)
breakWords :: Rope -> [Rope]
breakWords :: Rope -> [Rope]
breakWords = forall a. (a -> Bool) -> [a] -> [a]
filter (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rope -> Bool
nullRope) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> Rope -> [Rope]
breakPieces Char -> Bool
isSpace
breakLines :: Rope -> [Rope]
breakLines :: Rope -> [Rope]
breakLines Rope
text =
let result :: [Rope]
result = (Char -> Bool) -> Rope -> [Rope]
breakPieces Char -> Bool
isNewline Rope
text
n :: Int
n = forall (t :: * -> *) a. Foldable t => t a -> Int
length [Rope]
result forall a. Num a => a -> a -> a
- Int
1
([Rope]
fore, [Rope]
aft) = forall a. Int -> [a] -> ([a], [a])
splitAt Int
n [Rope]
result
in case [Rope]
result of
[] -> []
[Rope
p] -> [Rope
p]
[Rope]
_ ->
if [Rope]
aft forall a. Eq a => a -> a -> Bool
== [Rope
""]
then [Rope]
fore
else [Rope]
result
isNewline :: Char -> Bool
isNewline :: Char -> Bool
isNewline Char
c = Char
c forall a. Eq a => a -> a -> Bool
== Char
'\n'
{-# INLINEABLE isNewline #-}
breakPieces :: (Char -> Bool) -> Rope -> [Rope]
breakPieces :: (Char -> Bool) -> Rope -> [Rope]
breakPieces Char -> Bool
predicate Rope
text =
let x :: FingerTree Width ShortText
x = Rope -> FingerTree Width ShortText
unRope Rope
text
(Maybe ShortText
final, [Rope]
result) = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ((Char -> Bool)
-> ShortText
-> (Maybe ShortText, [Rope])
-> (Maybe ShortText, [Rope])
intoPieces Char -> Bool
predicate) (forall a. Maybe a
Nothing, []) FingerTree Width ShortText
x
in case Maybe ShortText
final of
Maybe ShortText
Nothing -> [Rope]
result
Just ShortText
piece -> forall α. Textual α => α -> Rope
intoRope ShortText
piece forall a. a -> [a] -> [a]
: [Rope]
result
intoPieces :: (Char -> Bool) -> S.ShortText -> (Maybe S.ShortText, [Rope]) -> (Maybe S.ShortText, [Rope])
intoPieces :: (Char -> Bool)
-> ShortText
-> (Maybe ShortText, [Rope])
-> (Maybe ShortText, [Rope])
intoPieces Char -> Bool
predicate ShortText
piece (Maybe ShortText
stream, [Rope]
list) =
let piece' :: ShortText
piece' = case Maybe ShortText
stream of
Maybe ShortText
Nothing -> ShortText
piece
Just ShortText
previous -> ShortText
piece forall a. Semigroup a => a -> a -> a
<> ShortText
previous
pieces :: [Rope]
pieces = (Char -> Bool) -> ShortText -> [Rope]
intoChunks Char -> Bool
predicate ShortText
piece'
in case forall a. [a] -> Maybe (a, [a])
uncons [Rope]
pieces of
Maybe (Rope, [Rope])
Nothing -> (forall a. Maybe a
Nothing, [Rope]
list)
Just (Rope
text, [Rope]
remainder) -> (forall a. a -> Maybe a
Just (forall α. Textual α => Rope -> α
fromRope Rope
text), [Rope]
remainder forall a. [a] -> [a] -> [a]
++ [Rope]
list)
intoChunks :: (Char -> Bool) -> S.ShortText -> [Rope]
intoChunks :: (Char -> Bool) -> ShortText -> [Rope]
intoChunks Char -> Bool
_ ShortText
piece | ShortText -> Bool
S.null ShortText
piece = []
intoChunks Char -> Bool
predicate ShortText
piece =
let (ShortText
chunk, ShortText
remainder) = (Char -> Bool) -> ShortText -> (ShortText, ShortText)
S.break Char -> Bool
predicate ShortText
piece
(Bool
trailing, ShortText
remainder') = case ShortText -> Maybe (Char, ShortText)
S.uncons ShortText
remainder of
Maybe (Char, ShortText)
Nothing -> (Bool
False, ShortText
S.empty)
Just (Char
c, ShortText
remaining) ->
if ShortText -> Bool
S.null ShortText
remaining
then (Char -> Bool
predicate Char
c, ShortText
S.empty)
else (Bool
False, ShortText
remaining)
in if Bool
trailing
then forall α. Textual α => α -> Rope
intoRope ShortText
chunk forall a. a -> [a] -> [a]
: Rope
emptyRope forall a. a -> [a] -> [a]
: []
else forall α. Textual α => α -> Rope
intoRope ShortText
chunk forall a. a -> [a] -> [a]
: (Char -> Bool) -> ShortText -> [Rope]
intoChunks Char -> Bool
predicate ShortText
remainder'
breakRope :: (Char -> Bool) -> Rope -> (Rope, Rope)
breakRope :: (Char -> Bool) -> Rope -> (Rope, Rope)
breakRope Char -> Bool
predicate Rope
text =
let possibleIndex :: Maybe Int
possibleIndex = (Char -> Bool) -> Rope -> Maybe Int
findIndexRope Char -> Bool
predicate Rope
text
in case Maybe Int
possibleIndex of
Maybe Int
Nothing -> (Rope
text, Rope
emptyRope)
Just Int
i -> Int -> Rope -> (Rope, Rope)
splitRope Int
i Rope
text