text-region-0.1.0.0: Provides functions to update text region positions according to text edit actions

Safe HaskellNone
LanguageHaskell2010

Data.Text.Region.Types

Synopsis

Documentation

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

Constructors

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

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

_replaceRegion :: Region

Region to replace

_replaceWith :: Contents s

Contents to replace with

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

newtype Chain e s Source

Chain of edit actions

Constructors

Chain 

Fields

_chain :: [e s]
 

Instances

EditAction e s => EditAction (Chain e) s Source 
Eq (e s) => Eq (Chain e s) Source 
Show (e s) => Show (Chain e s) Source 
ToJSON (e s) => ToJSON (Chain e s) Source 
FromJSON (e s) => FromJSON (Chain e s) Source 
Monoid (Chain e s) Source 
ApplyMap (e s) => ApplyMap (Chain e s) Source 

chain :: forall e s e s. Iso (Chain e s) (Chain e s) [e s] [e s] Source

data ActionIso e Source

Some action with its inverse

Constructors

ActionIso 

Fields

_action :: e
 
_actionBack :: e
 

action :: forall e. Lens' (ActionIso e) e Source

actionBack :: forall e. Lens' (ActionIso e) e Source

data ActionStack e Source

Stack of undo/redo actions

Constructors

ActionStack 

Fields

_undoStack :: [ActionIso e]
 
_redoStack :: [ActionIso e]
 

data EditState s r Source

Edit state

Constructors

EditState 

Fields

_history :: ActionStack (Edit s)

Edit history is stack of edit actions

_edited :: Contents s

Currently edited data

_regions :: r

Some region-based state, that will be updated on each edit

editState :: Editable s => s -> r -> EditState s r Source

Make edit state for contents

history :: forall s r. Lens' (EditState s r) (ActionStack (Edit s)) Source

edited :: forall s r. Lens' (EditState s r) (Contents s) Source

regions :: forall s r r. Lens (EditState s r) (EditState s r) r r Source

newtype EditM s r a Source

Constructors

EditM 

Fields

runEditM :: State (EditState s r) a
 

module Data.Group