yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Buffer.Normal
Description
A normalized API to many buffer operations.
Synopsis
data TextUnit
= Character
| Line
| VLine
| Document
outsideUnit :: TextUnit -> TextUnit
leftBoundaryUnit :: TextUnit -> TextUnit
unitWord :: TextUnit
unitViWord :: TextUnit
unitViWORD :: TextUnit
unitViWordAnyBnd :: TextUnit
unitViWORDAnyBnd :: TextUnit
unitViWordOnLine :: TextUnit
unitViWORDOnLine :: TextUnit
unitDelimited :: Char -> Char -> Bool -> TextUnit
unitSentence :: TextUnit
unitEmacsParagraph :: TextUnit
unitParagraph :: TextUnit
isAnySep :: Char -> Bool
unitSep :: TextUnit
unitSepThisLine :: TextUnit
isWordChar :: Char -> Bool
moveB :: TextUnit -> Direction -> BufferM ()
maybeMoveB :: TextUnit -> Direction -> BufferM ()
transformB :: (String -> String) -> TextUnit -> Direction -> BufferM ()
transposeB :: TextUnit -> Direction -> BufferM ()
regionOfB :: TextUnit -> BufferM Region
regionOfNonEmptyB :: TextUnit -> BufferM Region
regionOfPartB :: TextUnit -> Direction -> BufferM Region
regionOfPartNonEmptyB :: TextUnit -> Direction -> BufferM Region
regionOfPartNonEmptyAtB :: TextUnit -> Direction -> Point -> BufferM Region
readPrevUnitB :: TextUnit -> BufferM String
readUnitB :: TextUnit -> BufferM String
untilB :: BufferM Bool -> BufferM a -> BufferM [a]
doUntilB_ :: BufferM Bool -> BufferM a -> BufferM ()
untilB_ :: BufferM Bool -> BufferM a -> BufferM ()
whileB :: BufferM Bool -> BufferM a -> BufferM [a]
doIfCharB :: (Char -> Bool) -> BufferM a -> BufferM ()
atBoundaryB :: TextUnit -> Direction -> BufferM Bool
numberOfB :: TextUnit -> TextUnit -> BufferM Int
deleteB :: TextUnit -> Direction -> BufferM ()
genMaybeMoveB :: TextUnit -> (Direction, BoundarySide) -> Direction -> BufferM ()
genMoveB :: TextUnit -> (Direction, BoundarySide) -> Direction -> BufferM ()
data BoundarySide
= InsideBound
| OutsideBound
genAtBoundaryB :: TextUnit -> Direction -> BoundarySide -> BufferM Bool
genEnclosingUnit :: TextUnit -> TextUnit
genUnitBoundary :: TextUnit -> Direction -> BufferM Bool
checkPeekB :: Int -> [Char -> Bool] -> Direction -> BufferM Bool
data RegionStyle
= LineWise
| Inclusive
| Exclusive
| Block
mkRegionOfStyleB :: Point -> Point -> RegionStyle -> BufferM Region
unitWiseRegion :: TextUnit -> Region -> BufferM Region
extendRegionToBoundaries :: TextUnit -> BoundarySide -> BoundarySide -> Region -> BufferM Region
regionStyleA :: Accessor FBuffer RegionStyle
Documentation
data TextUnit Source
Designate a given unit of text.
Constructors
Charactera single character
Linea line of text (between newlines)
VLinea vertical line of text (area of text between two characters at the same column number)
Documentthe whole document
show/hide Instances
outsideUnit :: TextUnit -> TextUnitSource
Turns a unit into its negative by inverting the boundaries. For example, outsideUnit unitViWord will be the unit of spaces between words. For units without boundaries (Character, Document, ...), this is the identity function.
leftBoundaryUnit :: TextUnit -> TextUnitSource
Unit that have its left and right boundaries at the left boundary of the argument unit.
unitWord :: TextUnitSource

a word as in use in Emacs (fundamental mode)

delimited on the left and right by given characters, boolean argument tells if whether those are included.

unitViWord :: TextUnitSource
unitViWORD :: TextUnitSource
unitViWordAnyBnd :: TextUnitSource
unitViWORDAnyBnd :: TextUnitSource
unitViWordOnLine :: TextUnitSource
unitViWORDOnLine :: TextUnitSource
unitDelimited :: Char -> Char -> Bool -> TextUnitSource
unitSentence :: TextUnitSource
unitEmacsParagraph :: TextUnitSource
Paragraph to implement emacs-like forward-paragraph/backward-paragraph
unitParagraph :: TextUnitSource
Paragraph that begins and ends in the paragraph, not the empty lines surrounding it.
isAnySep :: Char -> BoolSource
Separator characters (space, tab, unicode separators). Most of the units above attempt to identify words with various punctuation and symbols included or excluded. This set of units is a simple inverse: it is true for whitespace or separators and false for anything that is not (letters, numbers, symbols, punctuation, whatever).
unitSep :: TextUnitSource
unitSep is true for any kind of whitespace/separator
unitSepThisLine :: TextUnitSource
unitSepThisLine is true for any kind of whitespace/separator on this line only
isWordChar :: Char -> BoolSource
moveB :: TextUnit -> Direction -> BufferM ()Source
Move to the next unit boundary
maybeMoveB :: TextUnit -> Direction -> BufferM ()Source
As moveB, unless the point is at a unit boundary
transformB :: (String -> String) -> TextUnit -> Direction -> BufferM ()Source
transposeB :: TextUnit -> Direction -> BufferM ()Source
regionOfB :: TextUnit -> BufferM RegionSource
Region of the whole textunit where the current point is.
regionOfNonEmptyB :: TextUnit -> BufferM RegionSource
Non empty region of the whole textunit where the current point is.
regionOfPartB :: TextUnit -> Direction -> BufferM RegionSource
Region between the point and the next boundary. The region is empty if the point is at the boundary.
regionOfPartNonEmptyB :: TextUnit -> Direction -> BufferM RegionSource
Non empty region between the point and the next boundary, In fact the region can be empty if we are at the end of file.
regionOfPartNonEmptyAtB :: TextUnit -> Direction -> Point -> BufferM RegionSource
Non empty region at given point and the next boundary,
readPrevUnitB :: TextUnit -> BufferM StringSource
readUnitB :: TextUnit -> BufferM StringSource
untilB :: BufferM Bool -> BufferM a -> BufferM [a]Source
Repeat an action until the condition is fulfilled or the cursor stops moving. The Action may be performed zero times.
doUntilB_ :: BufferM Bool -> BufferM a -> BufferM ()Source
untilB_ :: BufferM Bool -> BufferM a -> BufferM ()Source
whileB :: BufferM Bool -> BufferM a -> BufferM [a]Source
doIfCharB :: (Char -> Bool) -> BufferM a -> BufferM ()Source
Do an action if the current buffer character passes the predicate
atBoundaryB :: TextUnit -> Direction -> BufferM BoolSource
numberOfB :: TextUnit -> TextUnit -> BufferM IntSource
deleteB :: TextUnit -> Direction -> BufferM ()Source
Delete between point and next unit boundary, return the deleted region.
genMaybeMoveB :: TextUnit -> (Direction, BoundarySide) -> Direction -> BufferM ()Source
Generic maybe move operation. As genMoveB, but don't move if we are at boundary already.
genMoveB :: TextUnit -> (Direction, BoundarySide) -> Direction -> BufferM ()Source
Generic move operation Warning: moving To the (OutsideBound, Backward) bound of Document is impossible (offset -1!) genMoveB u b d: move in direction d until encountering boundary b or unit u. See genAtBoundaryB for boundary explanation.
data BoundarySide Source
Boundary side
Constructors
InsideBound
OutsideBound
genAtBoundaryB :: TextUnit -> Direction -> BoundarySide -> BufferM BoolSource

genAtBoundaryB u d s returns whether the point is at a given boundary (d,s) . Boundary (d,s) , taking Word as example, means: Word ^^ ^^ 12 34 1: (Backward,OutsideBound) 2: (Backward,InsideBound) 3: (Forward,InsideBound) 4: (Forward,OutsideBound)

rules: genAtBoundaryB u Backward InsideBound = atBoundaryB u Backward genAtBoundaryB u Forward OutsideBound = atBoundaryB u Forward

genEnclosingUnit :: TextUnit -> TextUnitSource
genUnitBoundary :: TextUnit -> Direction -> BufferM BoolSource
checkPeekB :: Int -> [Char -> Bool] -> Direction -> BufferM BoolSource
data RegionStyle Source
Constructors
LineWise
Inclusive
Exclusive
Block
show/hide Instances
mkRegionOfStyleB :: Point -> Point -> RegionStyle -> BufferM RegionSource
unitWiseRegion :: TextUnit -> Region -> BufferM RegionSource
extendRegionToBoundaries :: TextUnit -> BoundarySide -> BoundarySide -> Region -> BufferM RegionSource
Extend the given region to boundaries of the text unit. For instance one can extend the selection to complete lines, or paragraphs.
regionStyleA :: Accessor FBuffer RegionStyleSource
Produced by Haddock version 2.6.1