rasa-0.1.9: A modular text editor

Safe HaskellNone
LanguageHaskell2010

Rasa.Internal.Range

Synopsis

Documentation

type Coord = Coord' Int Int Source #

A type alias to Coord' which specializes the types to integers.

data Coord' a b Source #

(Coord Row Column) represents a char in a block of text. (zero indexed) e.g. Coord 0 0 is the first character in the text, Coord 2 1 is the second character of the third row

Constructors

Coord 

Fields

Instances

Bifunctor Coord' Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Coord' a c -> Coord' b d #

first :: (a -> b) -> Coord' a c -> Coord' b c #

second :: (b -> c) -> Coord' a b -> Coord' a c #

Biapplicative Coord' Source # 

Methods

bipure :: a -> b -> Coord' a b #

(<<*>>) :: Coord' (a -> b) (c -> d) -> Coord' a c -> Coord' b d #

(*>>) :: Coord' a b -> Coord' c d -> Coord' c d #

(<<*) :: Coord' a b -> Coord' c d -> Coord' a b #

(Eq b, Eq a) => Eq (Coord' a b) Source # 

Methods

(==) :: Coord' a b -> Coord' a b -> Bool #

(/=) :: Coord' a b -> Coord' a b -> Bool #

(Num a, Num b) => Num (Coord' a b) Source # 

Methods

(+) :: Coord' a b -> Coord' a b -> Coord' a b #

(-) :: Coord' a b -> Coord' a b -> Coord' a b #

(*) :: Coord' a b -> Coord' a b -> Coord' a b #

negate :: Coord' a b -> Coord' a b #

abs :: Coord' a b -> Coord' a b #

signum :: Coord' a b -> Coord' a b #

fromInteger :: Integer -> Coord' a b #

(Ord a, Ord b) => Ord (Coord' a b) Source # 

Methods

compare :: Coord' a b -> Coord' a b -> Ordering #

(<) :: Coord' a b -> Coord' a b -> Bool #

(<=) :: Coord' a b -> Coord' a b -> Bool #

(>) :: Coord' a b -> Coord' a b -> Bool #

(>=) :: Coord' a b -> Coord' a b -> Bool #

max :: Coord' a b -> Coord' a b -> Coord' a b #

min :: Coord' a b -> Coord' a b -> Coord' a b #

(Show b, Show a) => Show (Coord' a b) Source # 

Methods

showsPrec :: Int -> Coord' a b -> ShowS #

show :: Coord' a b -> String #

showList :: [Coord' a b] -> ShowS #

overRow :: (Int -> Int) -> Coord -> Coord Source #

Applies a function over the row of a Coord

overCol :: (Int -> Int) -> Coord -> Coord Source #

Applies a function over the column of a Coord

overBoth :: Bifunctor f => (a -> b) -> f a a -> f b b Source #

Applies a function over both functors in any Bifunctor.

coordRow :: forall a b a. Lens (Coord' a b) (Coord' a b) a a Source #

coordCol :: forall a b b. Lens (Coord' a b) (Coord' a b) b b Source #

newtype Offset Source #

An Offset represents an exact position in a file as a number of characters from the start.

Constructors

Offset Int 

Instances

asCoord :: YiString -> Iso' Offset Coord Source #

Given the text you're operating over, creates an iso from an Offset to a Coord.

clampCoord :: YiString -> Coord -> Coord Source #

This will restrict a given Coord to a valid one which lies within the given text.

clampRange :: YiString -> CrdRange -> CrdRange Source #

This will restrict a given Range to a valid one which lies within the given text.

data Range a b Source #

This represents a range between two coordinates (Coord)

Constructors

Range 

Fields

Instances

Bifunctor Range Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Range a c -> Range b d #

first :: (a -> b) -> Range a c -> Range b c #

second :: (b -> c) -> Range a b -> Range a c #

Bitraversable Range Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Range a b -> f (Range c d) #

Bifoldable Range Source # 

Methods

bifold :: Monoid m => Range m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Range a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Range a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Range a b -> c #

(Eq b, Eq a) => Eq (Range a b) Source # 

Methods

(==) :: Range a b -> Range a b -> Bool #

(/=) :: Range a b -> Range a b -> Bool #

(Ord a, Ord b) => Ord (Range a b) Source # 

Methods

compare :: Range a b -> Range a b -> Ordering #

(<) :: Range a b -> Range a b -> Bool #

(<=) :: Range a b -> Range a b -> Bool #

(>) :: Range a b -> Range a b -> Bool #

(>=) :: Range a b -> Range a b -> Bool #

max :: Range a b -> Range a b -> Range a b #

min :: Range a b -> Range a b -> Range a b #

(Show b, Show a) => Show (Range a b) Source # 

Methods

showsPrec :: Int -> Range a b -> ShowS #

show :: Range a b -> String #

showList :: [Range a b] -> ShowS #

type CrdRange = Range Coord Coord Source #

A type alias to Range' which specializes the types to Coords.

range :: CrdRange -> Lens' YiString YiString Source #

A lens over text which is encompassed by a Range

rStart :: forall a b a. Lens (Range a b) (Range a b) a a Source #

rEnd :: forall a b b. Lens (Range a b) (Range a b) b b Source #

sizeOf :: YiString -> Coord Source #

Returns the number of rows and columns that a chunk of text spans as a Coord

sizeOfR :: CrdRange -> Coord Source #

Returns the number of rows and columns that a Range spans as a Coord

moveRange :: Coord -> CrdRange -> CrdRange Source #

Moves a Range by a given Coord It may be unintuitive, but for (Coord row col) a given range will be moved down by row and to the right by col.

moveRangeByN :: Int -> CrdRange -> CrdRange Source #

Moves a range forward by the given amount

moveCursorByN :: Int -> Coord -> Coord Source #

Moves a Coord forward by the given amount of columns

moveCursor :: Coord -> Coord -> Coord Source #

Adds the rows and columns of the given two Coords.

data Span a b Source #

A span which maps a piece of Monoidal data over a range.

Constructors

Span a b 

Instances

Bifunctor Span Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Span a c -> Span b d #

first :: (a -> b) -> Span a c -> Span b c #

second :: (b -> c) -> Span a b -> Span a c #

Functor (Span a) Source # 

Methods

fmap :: (a -> b) -> Span a a -> Span a b #

(<$) :: a -> Span a b -> Span a a #

(Eq b, Eq a) => Eq (Span a b) Source # 

Methods

(==) :: Span a b -> Span a b -> Bool #

(/=) :: Span a b -> Span a b -> Bool #

(Show b, Show a) => Show (Span a b) Source # 

Methods

showsPrec :: Int -> Span a b -> ShowS #

show :: Span a b -> String #

showList :: [Span a b] -> ShowS #

combineSpans :: forall a. Monoid a => [Span CrdRange a] -> [(Coord, a)] Source #

Combines a list of spans containing some monoidal data into a list of offsets with with the data that applies from each Offset forwards.

clamp :: Int -> Int -> Int -> Int Source #

clamp min max val restricts val to be within min and max (inclusive)

beforeC :: Coord -> Lens' YiString YiString Source #

A lens over text before a given Coord

afterC :: Coord -> Lens' YiString YiString Source #

A lens over text after a given Coord