rope-utf16-splay-0.3.1.0: Ropes optimised for updating using UTF-16 code units and row/column pairs.

Safe HaskellNone
LanguageHaskell2010

Data.Rope.UTF16.Internal

Contents

Synopsis

Documentation

data Chunk Source #

Constructors

Chunk 
Instances
Show Chunk Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

showsPrec :: Int -> Chunk -> ShowS #

show :: Chunk -> String #

showList :: [Chunk] -> ShowS #

Semigroup Chunk Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

(<>) :: Chunk -> Chunk -> Chunk #

sconcat :: NonEmpty Chunk -> Chunk #

stimes :: Integral b => b -> Chunk -> Chunk #

Measured Position Chunk Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

newtype Rope Source #

A SplayTree of Text values optimised for being indexed by and modified at UTF-16 code units and row/column (RowColumn) positions. Internal invariant: No empty Chunks in the SplayTree

Constructors

Rope 
Instances
Eq Rope Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

(==) :: Rope -> Rope -> Bool #

(/=) :: Rope -> Rope -> Bool #

Ord Rope Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

compare :: Rope -> Rope -> Ordering #

(<) :: Rope -> Rope -> Bool #

(<=) :: Rope -> Rope -> Bool #

(>) :: Rope -> Rope -> Bool #

(>=) :: Rope -> Rope -> Bool #

max :: Rope -> Rope -> Rope #

min :: Rope -> Rope -> Rope #

Show Rope Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

showsPrec :: Int -> Rope -> ShowS #

show :: Rope -> String #

showList :: [Rope] -> ShowS #

IsString Rope Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

fromString :: String -> Rope #

Semigroup Rope Source #

Append joins adjacent chunks if that can be done while staying below chunkLength.

Instance details

Defined in Data.Rope.UTF16.Internal

Methods

(<>) :: Rope -> Rope -> Rope #

sconcat :: NonEmpty Rope -> Rope #

stimes :: Integral b => b -> Rope -> Rope #

Monoid Rope Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

Methods

mempty :: Rope #

mappend :: Rope -> Rope -> Rope #

mconcat :: [Rope] -> Rope #

Measured Position Rope Source # 
Instance details

Defined in Data.Rope.UTF16.Internal

chunkLength :: Int Source #

The maximum length, in code units, of a chunk

Queries

null :: Rope -> Bool Source #

Is the rope empty?

Since: 0.2.0.0

length :: Rope -> Int Source #

Length in code units (not characters)

rows :: Rope -> Int Source #

The number of newlines in the rope

Since: 0.3.0.0

columns :: Rope -> Int Source #

The number of code units (not characters) since the last newline or the start of the rope

Since: 0.3.0.0

Conversions

Transformations

map :: (Char -> Char) -> Rope -> Rope Source #

Map over the characters of a rope

Since: 0.3.0.0

intercalate :: Rope -> [Rope] -> Rope Source #

Concatenate the interspersion of a rope between the elements of a list of ropes

Since: 0.3.0.0

Chunking

toChunks :: Rope -> [Text] Source #

The raw Text data that the Rope is built from

unconsChunk :: Rope -> Maybe (Text, Rope) Source #

Get the first chunk and the rest of the Rope if non-empty

unsnocChunk :: Rope -> Maybe (Rope, Text) Source #

Get the last chunk and the rest of the Rope if non-empty

UTF-16 code unit indexing

splitAt :: Int -> Rope -> (Rope, Rope) Source #

Split the rope at the nth code unit (not character)

take :: Int -> Rope -> Rope Source #

Take the first n code units (not characters)

drop :: Int -> Rope -> Rope Source #

Drop the first n code units (not characters)

rowColumnCodeUnits :: RowColumn -> Rope -> Int Source #

Get the code unit index in the rope that corresponds to a RowColumn position

Since: 0.2.0.0

Lines

splitAtLine :: Int -> Rope -> (Rope, Rope) Source #

Split the rope immediately after the i:th newline

Since: 0.3.1.0

Breaking by predicate

span :: (Char -> Bool) -> Rope -> (Rope, Rope) Source #

span f r = (takeWhile f r, dropWhile f r)

break :: (Char -> Bool) -> Rope -> (Rope, Rope) Source #

break f = span (not . f)

takeWhile :: (Char -> Bool) -> Rope -> Rope Source #

takeWhile f = fst . span f

dropWhile :: (Char -> Bool) -> Rope -> Rope Source #

dropWhile f = snd . span f

Folds

foldl :: (a -> Char -> a) -> a -> Rope -> a Source #

Fold left

Since: 0.3.0.0

foldl' :: (a -> Char -> a) -> a -> Rope -> a Source #

A strict version of foldl

Since: 0.3.0.0

foldr :: (Char -> a -> a) -> a -> Rope -> a Source #

Fold right

Since: 0.3.0.0

Special folds

any :: (Char -> Bool) -> Rope -> Bool Source #

Do any characters in the rope satisfy the predicate?

Since: 0.3.0.0

all :: (Char -> Bool) -> Rope -> Bool Source #

Do all characters in the rope satisfy the predicate?

Since: 0.3.0.0