text-region-0.3.1.0: Marking text regions

Safe HaskellNone
LanguageHaskell2010

Data.Text.Region.Types

Synopsis

Documentation

pointRegion :: Iso' Point Region Source #

As empty region

type Size = Point Source #

Distance between Points is measured in lines and columns. And it is defined, that distance between point at l:c and point (l + 1):0 is one line no matter c is because we need to go to new line to reach destination point Columns are taken into account only if points are on the same line

(.-.) :: Point -> Point -> Point Source #

pt .-. base is distance from base to pt Distance can't be less then zero lines and columns

(.+.) :: Point -> Point -> Point Source #

Opposite to .-.

(pt .-. base) .+. base = pt

newtype Map Source #

Main idea is that there are only two basic actions, that changes regions: inserting and cutting When something is cutted out or inserted in, Region positions must be updated All editings can be represented as many cuts and inserts, so we can combine them to get function which maps source regions to regions on updated data Because insert is dual to cut (and therefore composes something like iso), we can also get function to map regions back Combining this functions while edit, we get function, that maps regions from source data to edited one To get back function, we must also combine opposite actions, or we can represent actions as Iso Same idea goes for modifying contents, represent each action as isomorphism and combine them together This works if we don't use overlapped regions

Constructors

Map 

Instances

Semigroup Map Source # 

Methods

(<>) :: Map -> Map -> Map #

sconcat :: NonEmpty Map -> Map #

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

Monoid Map Source # 

Methods

mempty :: Map #

mappend :: Map -> Map -> Map #

mconcat :: [Map] -> Map #

Group Map Source # 

Methods

invert :: Map -> Map #

pow :: Integral x => Map -> x -> Map #

type Contents a = [a] Source #

Contents is list of lines, list must have at least one (maybe empty) line

emptyContents :: Monoid a => Contents a Source #

Empty contents are contents with one empty line

splitCts :: Editable a => Point -> Contents a -> (Contents a, Contents a) Source #

Split Contents at some Point

splitted :: Editable a => Point -> Iso' (Contents a) (Contents a, Contents a) Source #

Get splitted Contents at some Point

class Monoid a => Editable a where Source #

Something editable, string types implements this

Minimal complete definition

splitContents, contentsLength, splitLines, joinLines

Methods

splitContents :: Int -> a -> (a, a) Source #

Split editable at some position

contentsLength :: a -> Int Source #

splitLines :: a -> [a] Source #

joinLines :: [a] -> a Source #

contents :: (Editable a, Editable b) => Iso a b (Contents a) (Contents b) Source #

Get Contents for some Editable, splitting lines

by :: Editable a => a -> Contents a Source #

measure :: Editable s => Contents s -> Size Source #

Contents Size

data Replace s Source #

Serializable edit action

Constructors

Replace 

Fields

replaceWith :: forall s s. Lens (Replace s) (Replace s) (Contents s) (Contents s) Source #

newtype Edit s Source #

Edit is several replace actions, applied simultaneously, must not overlap

Constructors

Edit 

Fields

Instances

Editable s => EditAction Edit s Source # 
Eq s => Eq (Edit s) Source # 

Methods

(==) :: Edit s -> Edit s -> Bool #

(/=) :: Edit s -> Edit s -> Bool #

(ToJSON s, Editable s) => Show (Edit s) Source # 

Methods

showsPrec :: Int -> Edit s -> ShowS #

show :: Edit s -> String #

showList :: [Edit s] -> ShowS #

Semigroup (Edit s) Source # 

Methods

(<>) :: Edit s -> Edit s -> Edit s #

sconcat :: NonEmpty (Edit s) -> Edit s #

stimes :: Integral b => b -> Edit s -> Edit s #

Monoid (Edit s) Source # 

Methods

mempty :: Edit s #

mappend :: Edit s -> Edit s -> Edit s #

mconcat :: [Edit s] -> Edit s #

(Editable s, ToJSON s) => ToJSON (Edit s) Source # 
(Editable s, FromJSON s) => FromJSON (Edit s) Source # 
Regioned (Edit s) Source # 

replaces :: forall s s. Iso (Edit s) (Edit s) [Replace s] [Replace s] Source #

module Data.Group