Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Point = Point {
- _pointLine :: Int
- _pointColumn :: Int
- pointLine :: Lens' Point Int
- pointColumn :: Lens' Point Int
- pointRegion :: Iso' Point Region
- type Size = Point
- (.-.) :: Point -> Point -> Point
- (.+.) :: Point -> Point -> Point
- data Region = Region {
- _regionFrom :: Point
- _regionTo :: Point
- regionFrom :: Lens' Region Point
- regionTo :: Lens' Region Point
- newtype Map = Map {}
- type Contents a = [a]
- emptyContents :: Monoid a => Contents a
- concatCts :: Monoid a => Contents a -> Contents a -> Contents a
- splitCts :: Editable a => Point -> Contents a -> (Contents a, Contents a)
- splitted :: Editable a => Point -> Iso' (Contents a) (Contents a, Contents a)
- class Monoid a => Editable a where
- contents :: (Editable a, Editable b) => Iso a b (Contents a) (Contents b)
- by :: Editable a => a -> Contents a
- measure :: Editable s => Contents s -> Size
- data Replace s = Replace {
- _replaceRegion :: Region
- _replaceWith :: Contents s
- replaceRegion :: forall s. Lens' (Replace s) Region
- replaceWith :: forall s s. Lens (Replace s) (Replace s) (Contents s) (Contents s)
- newtype Edit s = Edit {}
- replaces :: forall s s. Iso (Edit s) (Edit s) [Replace s] [Replace s]
- class Regioned a where
- module Data.Group
Documentation
Point at text: zero-based line and column
Point | |
|
Distance between Point
s 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
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
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
class Monoid a => Editable a where Source #
Something editable, string types implements this
splitContents :: Int -> a -> (a, a) Source #
Split editable at some position
contentsLength :: a -> Int Source #
splitLines :: a -> [a] Source #
Serializable edit action
Replace | |
|
Edit is several replace actions, applied simultaneously, must not overlap
Editable s => EditAction Edit s Source # | |
Eq s => Eq (Edit s) Source # | |
(ToJSON s, Editable s) => Show (Edit s) Source # | |
Semigroup (Edit s) Source # | |
Monoid (Edit s) Source # | |
(Editable s, ToJSON s) => ToJSON (Edit s) Source # | |
(Editable s, FromJSON s) => FromJSON (Edit s) Source # | |
Regioned (Edit s) Source # | |
module Data.Group