hsdev-0.3.3.1: Haskell development library

Safe HaskellNone
LanguageHaskell98

HsDev.Tools.AutoFix

Contents

Synopsis

Documentation

class Monoid m => Group m where #

A Group is a Monoid plus a function, invert, such that:

a <> invert a == mempty
invert a <> a == mempty

Minimal complete definition

invert

Methods

invert :: m -> m #

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

pow a n == a <> a <> ... <> a
 (n lots of a)

If n is negative, the result is inverted.

Instances
Group () 
Instance details

Defined in Data.Group

Methods

invert :: () -> () #

pow :: Integral x => () -> x -> () #

Group Map 
Instance details

Defined in Data.Text.Region.Types

Methods

invert :: Map -> Map #

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

Group Point 
Instance details

Defined in Data.Text.Region.Types

Methods

invert :: Point -> Point #

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

Group a => Group (Dual a) 
Instance details

Defined in Data.Group

Methods

invert :: Dual a -> Dual a #

pow :: Integral x => Dual a -> x -> Dual a #

Num a => Group (Sum a) 
Instance details

Defined in Data.Group

Methods

invert :: Sum a -> Sum a #

pow :: Integral x => Sum a -> x -> Sum a #

Fractional a => Group (Product a) 
Instance details

Defined in Data.Group

Methods

invert :: Product a -> Product a #

pow :: Integral x => Product a -> x -> Product a #

Group b => Group (a -> b) 
Instance details

Defined in Data.Group

Methods

invert :: (a -> b) -> a -> b #

pow :: Integral x => (a -> b) -> x -> a -> b #

(Group a, Group b) => Group (a, b) 
Instance details

Defined in Data.Group

Methods

invert :: (a, b) -> (a, b) #

pow :: Integral x => (a, b) -> x -> (a, b) #

(Group a, Group b, Group c) => Group (a, b, c) 
Instance details

Defined in Data.Group

Methods

invert :: (a, b, c) -> (a, b, c) #

pow :: Integral x => (a, b, c) -> x -> (a, b, c) #

(Group a, Group b, Group c, Group d) => Group (a, b, c, d) 
Instance details

Defined in Data.Group

Methods

invert :: (a, b, c, d) -> (a, b, c, d) #

pow :: Integral x => (a, b, c, d) -> x -> (a, b, c, d) #

(Group a, Group b, Group c, Group d, Group e) => Group (a, b, c, d, e) 
Instance details

Defined in Data.Group

Methods

invert :: (a, b, c, d, e) -> (a, b, c, d, e) #

pow :: Integral x => (a, b, c, d, e) -> x -> (a, b, c, d, e) #

class Group g => Abelian g #

An Abelian group is a Group that follows the rule:

a <> b == b <> a
Instances
Abelian () 
Instance details

Defined in Data.Group

Abelian a => Abelian (Dual a) 
Instance details

Defined in Data.Group

Num a => Abelian (Sum a) 
Instance details

Defined in Data.Group

Fractional a => Abelian (Product a) 
Instance details

Defined in Data.Group

Abelian b => Abelian (a -> b) 
Instance details

Defined in Data.Group

(Abelian a, Abelian b) => Abelian (a, b) 
Instance details

Defined in Data.Group

(Abelian a, Abelian b, Abelian c) => Abelian (a, b, c) 
Instance details

Defined in Data.Group

(Abelian a, Abelian b, Abelian c, Abelian d) => Abelian (a, b, c, d) 
Instance details

Defined in Data.Group

(Abelian a, Abelian b, Abelian c, Abelian d, Abelian e) => Abelian (a, b, c, d, e) 
Instance details

Defined in Data.Group

undo :: Editable s => Edit s -> s -> Edit s #

Get undo

apply :: Editable s => Edit s -> s -> s #

overwrite :: EditAction e s => Point -> s -> e s #

Overwrites Contents at some Point

paste :: EditAction e s => Point -> s -> e s #

Pastes Contents at some Point

cut :: EditAction e s => Region -> e s #

Cuts region

replace :: EditAction e s => Region -> s -> e s #

Replace region with data

insertRegion :: Region -> Region -> Region #

Update second region position as if it was data inserted at first region (region sets insertion point and data size) Region tries not to extend if data inserted at region bound except when region is empty This allows define replace as cut and insert in special case when we replace region itself

cutRegion :: Region -> Region -> Region #

Update second Region position as if it was data cutted at first Region

insertMap :: Region -> Map #

Opposite to cutMap

cutMap :: Region -> Map #

Cut Region mapping

overlaps :: Region -> Region -> Bool #

Does regions overlaps

atRegion :: Editable s => Region -> Lens' (Contents s) (Contents s) #

Get contents at Region

expandLines :: Region -> Region #

Expand Region to contain full lines

regionSize :: Point -> Size -> Region #

Make Region by start position and Size

line :: Int -> Region #

n'th line region, starts at the beginning of line and ends on the next line

linesSize :: Int -> Size #

Distance of n lines

till :: Point -> Point -> Region #

Region from one Point to another

regionLength :: Lens' Region Size #

Regions length

lineStart :: Int -> Point #

Point at the beginning of line

start :: Point #

Point at the beginning

pt :: Int -> Int -> Point #

Make Point from line and column

class Editable s => EditAction (e :: Type -> Type) s where #

Methods

replaceAction :: Region -> Contents s -> e s #

Make replace action over Region and Contents

actionMap :: e s -> Map #

Make Map from action

perform :: e s -> Contents s -> Contents s #

Perform action, modifying Contents

inversed :: e s -> Contents s -> e s #

Get action undo

Instances
Editable s => EditAction Edit s 
Instance details

Defined in Data.Text.Region

Methods

replaceAction :: Region -> Contents s -> Edit s #

actionMap :: Edit s -> Map #

perform :: Edit s -> Contents s -> Contents s #

inversed :: Edit s -> Contents s -> Edit s #

Editable s => EditAction Replace s 
Instance details

Defined in Data.Text.Region

replaces :: Iso (Edit s1) (Edit s2) [Replace s1] [Replace s2] #

class Regioned a where #

Instances
Regioned Region 
Instance details

Defined in Data.Text.Region.Types

Regioned Point 
Instance details

Defined in Data.Text.Region.Types

Regioned Refact Source # 
Instance details

Defined in HsDev.Tools.Refact

Regioned (Edit s) 
Instance details

Defined in Data.Text.Region.Types

Regioned (Replace s) 
Instance details

Defined in Data.Text.Region.Types

Regioned a => Regioned (Note a) Source # 
Instance details

Defined in HsDev.Tools.AutoFix

newtype Edit s #

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

Constructors

Edit 

Fields

Instances
Editable s => EditAction Edit s 
Instance details

Defined in Data.Text.Region

Methods

replaceAction :: Region -> Contents s -> Edit s #

actionMap :: Edit s -> Map #

perform :: Edit s -> Contents s -> Contents s #

inversed :: Edit s -> Contents s -> Edit s #

Eq s => Eq (Edit s) 
Instance details

Defined in Data.Text.Region.Types

Methods

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

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

(Editable s, ToJSON s) => Show (Edit s) 
Instance details

Defined in Data.Text.Region.Types

Methods

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

show :: Edit s -> String #

showList :: [Edit s] -> ShowS #

Semigroup (Edit s) 
Instance details

Defined in Data.Text.Region.Types

Methods

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

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

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

Monoid (Edit s) 
Instance details

Defined in Data.Text.Region.Types

Methods

mempty :: Edit s #

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

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

(Editable s, ToJSON s) => ToJSON (Edit s) 
Instance details

Defined in Data.Text.Region.Types

(Editable s, FromJSON s) => FromJSON (Edit s) 
Instance details

Defined in Data.Text.Region.Types

Regioned (Edit s) 
Instance details

Defined in Data.Text.Region.Types

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

Contents Size

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

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

Get Contents for some Editable, splitting lines

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

Get splitted Contents at some Point

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

Split Contents at some Point

emptyContents :: Monoid a => Contents a #

Empty contents are contents with one empty line

newtype Map #

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 
Instance details

Defined in Data.Text.Region.Types

Methods

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

sconcat :: NonEmpty Map -> Map #

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

Monoid Map 
Instance details

Defined in Data.Text.Region.Types

Methods

mempty :: Map #

mappend :: Map -> Map -> Map #

mconcat :: [Map] -> Map #

Group Map 
Instance details

Defined in Data.Text.Region.Types

Methods

invert :: Map -> Map #

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

type Contents a = [a] #

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

class Monoid a => Editable a where #

Something editable, string types implements this

Methods

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

Split editable at some position

contentsLength :: a -> Int #

splitLines :: a -> [a] #

joinLines :: [a] -> a #

Instances
Editable String 
Instance details

Defined in Data.Text.Region.Types

Editable Text 
Instance details

Defined in Data.Text.Region.Types

data Replace s #

Serializable edit action

Constructors

Replace 

Fields

Instances
Editable s => EditAction Replace s 
Instance details

Defined in Data.Text.Region

Eq s => Eq (Replace s) 
Instance details

Defined in Data.Text.Region.Types

Methods

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

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

(Editable s, ToJSON s) => Show (Replace s) 
Instance details

Defined in Data.Text.Region.Types

Methods

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

show :: Replace s -> String #

showList :: [Replace s] -> ShowS #

(Editable s, ToJSON s) => ToJSON (Replace s) 
Instance details

Defined in Data.Text.Region.Types

(Editable s, FromJSON s) => FromJSON (Replace s) 
Instance details

Defined in Data.Text.Region.Types

Regioned (Replace s) 
Instance details

Defined in Data.Text.Region.Types

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

Opposite to .-.

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

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

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

pointRegion :: Iso' Point Region #

As empty region

type Size = Point #

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

data Point #

Point at text: zero-based line and column

Constructors

Point 
Instances
Eq Point 
Instance details

Defined in Data.Text.Region.Types

Methods

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

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

Ord Point 
Instance details

Defined in Data.Text.Region.Types

Methods

compare :: Point -> Point -> Ordering #

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

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

(>) :: Point -> Point -> Bool #

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

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Read Point 
Instance details

Defined in Data.Text.Region.Types

Show Point 
Instance details

Defined in Data.Text.Region.Types

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Semigroup Point 
Instance details

Defined in Data.Text.Region.Types

Methods

(<>) :: Point -> Point -> Point #

sconcat :: NonEmpty Point -> Point #

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

Monoid Point 
Instance details

Defined in Data.Text.Region.Types

Methods

mempty :: Point #

mappend :: Point -> Point -> Point #

mconcat :: [Point] -> Point #

ToJSON Point 
Instance details

Defined in Data.Text.Region.Types

FromJSON Point 
Instance details

Defined in Data.Text.Region.Types

Group Point 
Instance details

Defined in Data.Text.Region.Types

Methods

invert :: Point -> Point #

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

Regioned Point 
Instance details

Defined in Data.Text.Region.Types

Orphan instances

Regioned a => Regioned (Note a) Source # 
Instance details