yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Buffer.Misc
Description
The Buffer module defines monadic editing operations over one-dimensional buffers, maintaining a current point.
Synopsis
data FBuffer = forall syntax . FBuffer !(Mode syntax) !(BufferImpl syntax) !Attributes
newtype BufferM a = BufferM {
fromBufferM :: RWS Window [Update] FBuffer a
}
type WinMarks = MarkSet Mark
data MarkSet a = MarkSet {
fromMark :: !a
insMark :: !a
selMark :: !a
}
bkey :: FBuffer -> BufferRef
getMarks :: Window -> BufferM (Maybe WinMarks)
runBuffer :: Window -> FBuffer -> BufferM a -> (a, FBuffer)
runBufferFull :: Window -> FBuffer -> BufferM a -> (a, [Update], FBuffer)
runBufferDummyWindow :: FBuffer -> BufferM a -> a
curLn :: BufferM Int
curCol :: BufferM Int
colOf :: Point -> BufferM Int
lineOf :: Point -> BufferM Int
sizeB :: BufferM Point
pointB :: BufferM Point
pointOfLineColB :: Int -> Int -> BufferM Point
solPointB :: BufferM Point
markLines :: BufferM (MarkSet Int)
moveTo :: Point -> BufferM ()
moveToColB :: Int -> BufferM ()
moveToLineColB :: Int -> Int -> BufferM ()
lineMoveRel :: Int -> BufferM Int
lineUp :: BufferM ()
lineDown :: BufferM ()
newB :: BufferRef -> BufferId -> Rope -> FBuffer
data MarkValue = MarkValue {
markPoint :: !Point
markGravity :: !Direction
}
data Overlay
data OvlLayer
= UserLayer
| HintLayer
mkOverlay :: OvlLayer -> Region -> StyleName -> Overlay
gotoLn :: Int -> BufferM Int
gotoLnFrom :: Int -> BufferM Int
leftB :: BufferM ()
rightB :: BufferM ()
moveN :: Int -> BufferM ()
leftN :: Int -> BufferM ()
rightN :: Int -> BufferM ()
insertN :: String -> BufferM ()
insertNAt :: String -> Point -> BufferM ()
insertB :: Char -> BufferM ()
deleteN :: Int -> BufferM ()
nelemsB :: Int -> Point -> BufferM String
writeB :: Char -> BufferM ()
writeN :: String -> BufferM ()
newlineB :: BufferM ()
deleteNAt :: Direction -> Int -> Point -> BufferM ()
readB :: BufferM Char
elemsB :: BufferM String
undosA :: Accessor FBuffer URList
undoB :: BufferM ()
redoB :: BufferM ()
getMarkB :: Maybe String -> BufferM Mark
mayGetMarkB :: String -> BufferM (Maybe Mark)
getMarkValueB :: Mark -> BufferM MarkValue
setMarkPointB :: Mark -> Point -> BufferM ()
modifyMarkB :: Mark -> (MarkValue -> MarkValue) -> BufferM ()
newMarkB :: MarkValue -> BufferM Mark
deleteMarkB :: Mark -> BufferM ()
setVisibleSelection :: Bool -> BufferM ()
isUnchangedBuffer :: FBuffer -> Bool
setAnyMode :: AnyMode -> BufferM ()
setMode :: Mode syntax -> BufferM ()
setMode0 :: forall syntax. Mode syntax -> FBuffer -> FBuffer
modifyMode :: (forall syntax. Mode syntax -> Mode syntax) -> BufferM ()
regexRegionB :: SearchExp -> Region -> BufferM [Region]
regexB :: Direction -> SearchExp -> BufferM [Region]
readAtB :: Point -> BufferM Char
getModeLine :: [String] -> BufferM String
getPercent :: Point -> Point -> String
setInserting :: Bool -> BufferM ()
forgetPreferCol :: BufferM ()
movingToPrefCol :: BufferM a -> BufferM a
setPrefCol :: Maybe Int -> BufferM ()
markSavedB :: UTCTime -> BufferM ()
addOverlayB :: Overlay -> BufferM ()
delOverlayB :: Overlay -> BufferM ()
delOverlayLayerB :: OvlLayer -> BufferM ()
savingExcursionB :: BufferM a -> BufferM a
savingPointB :: BufferM a -> BufferM a
pendingUpdatesA :: Accessor FBuffer [UIUpdate]
highlightSelectionA :: Accessor FBuffer Bool
rectangleSelectionA :: Accessor FBuffer Bool
readOnlyA :: Accessor FBuffer Bool
insertingA :: Accessor FBuffer Bool
pointFollowsWindowA :: Accessor FBuffer (WindowRef -> Bool)
revertPendingUpdatesB :: BufferM ()
askWindow :: (Window -> a) -> BufferM a
clearSyntax :: FBuffer -> FBuffer
focusSyntax :: Map WindowRef Region -> FBuffer -> FBuffer
data Mode syntax = Mode {
modeName :: String
modeApplies :: FilePath -> String -> Bool
modeHL :: ExtHL syntax
modePrettify :: syntax -> BufferM ()
modeKeymap :: KeymapSet -> KeymapSet
modeIndent :: syntax -> IndentBehaviour -> BufferM ()
modeAdjustBlock :: syntax -> Int -> BufferM ()
modeFollow :: syntax -> Action
modeIndentSettings :: IndentSettings
modeToggleCommentSelection :: BufferM ()
modeGetStrokes :: syntax -> Point -> Point -> Point -> [Stroke]
modeGetAnnotations :: syntax -> Point -> [Span String]
modePrintTree :: syntax -> BufferM ()
modeOnLoad :: BufferM ()
}
data AnyMode = forall syntax . AnyMode (Mode syntax)
data IndentBehaviour
= IncreaseCycle
| DecreaseCycle
| IncreaseOnly
| DecreaseOnly
data IndentSettings = IndentSettings {
expandTabs :: Bool
tabSize :: Int
shiftWidth :: Int
}
modeAlwaysApplies :: FilePath -> String -> Bool
modeNeverApplies :: FilePath -> String -> Bool
emptyMode :: Mode syntax
withModeB :: (forall syntax. Mode syntax -> BufferM a) -> BufferM a
withMode0 :: (forall syntax. Mode syntax -> a) -> FBuffer -> a
onMode :: (forall syntax. Mode syntax -> Mode syntax) -> AnyMode -> AnyMode
withSyntaxB :: (forall syntax. Mode syntax -> syntax -> a) -> BufferM a
withSyntaxB' :: (forall syntax. Mode syntax -> syntax -> BufferM a) -> BufferM a
keymapProcessA :: Accessor FBuffer KeymapProcess
strokesRangesB :: Maybe SearchExp -> Region -> BufferM [[Stroke]]
streamB :: Direction -> Point -> BufferM Rope
indexedStreamB :: Direction -> Point -> BufferM [(Point, Char)]
getMarkPointB :: Mark -> BufferM Point
askMarks :: BufferM WinMarks
pointAt :: forall a. BufferM a -> BufferM Point
data SearchExp
lastActiveWindowA :: Accessor FBuffer Window
bufferDynamicValueA :: Initializable a => Accessor FBuffer a
shortIdentString :: [a] -> FBuffer -> [Char]
identString :: FBuffer -> [Char]
miniIdentString :: FBuffer -> [Char]
identA :: Accessor FBuffer BufferId
type BufferId = Either String FilePath
file :: FBuffer -> Maybe FilePath
lastSyncTimeA :: Accessor FBuffer UTCTime
Documentation
data FBuffer Source
Constructors
forall syntax . FBuffer !(Mode syntax) !(BufferImpl syntax) !Attributes
show/hide Instances
newtype BufferM a Source
The BufferM monad writes the updates performed.
Constructors
BufferM
fromBufferM :: RWS Window [Update] FBuffer a
show/hide Instances
type WinMarks = MarkSet MarkSource
data MarkSet a Source
Constructors
MarkSet
fromMark :: !a
insMark :: !a
selMark :: !a
show/hide Instances
bkey :: FBuffer -> BufferRefSource
getMarks :: Window -> BufferM (Maybe WinMarks)Source
runBuffer :: Window -> FBuffer -> BufferM a -> (a, FBuffer)Source
Execute a BufferM value on a given buffer and window. The new state of the buffer is returned alongside the result of the computation.
runBufferFull :: Window -> FBuffer -> BufferM a -> (a, [Update], FBuffer)Source
runBufferDummyWindow :: FBuffer -> BufferM a -> aSource
Execute a BufferM value on a given buffer, using a dummy window. The new state of the buffer is discarded.
curLn :: BufferM IntSource
Return the current line number
curCol :: BufferM IntSource
Current column. Note that this is different from offset or number of chars from sol. (This takes into account tabs, unicode chars, etc.)
colOf :: Point -> BufferM IntSource
lineOf :: Point -> BufferM IntSource
sizeB :: BufferM PointSource
Point of eof
pointB :: BufferM PointSource
Extract the current point
pointOfLineColB :: Int -> Int -> BufferM PointSource
solPointB :: BufferM PointSource
markLines :: BufferM (MarkSet Int)Source
Return line numbers of marks
moveTo :: Point -> BufferM ()Source
Move point in buffer to the given index
moveToColB :: Int -> BufferM ()Source
moveToLineColB :: Int -> Int -> BufferM ()Source
lineMoveRel :: Int -> BufferM IntSource
Move point down by n lines. n can be negative. Returns the actual difference in lines which we moved which may be negative if the requested line difference is negative.
lineUp :: BufferM ()Source
Move point up one line
lineDown :: BufferM ()Source
Move point down one line
newB :: BufferRef -> BufferId -> Rope -> FBufferSource
Create buffer named nm with contents s
data MarkValue Source
Constructors
MarkValue
markPoint :: !Point
markGravity :: !Direction
show/hide Instances
data Overlay Source
show/hide Instances
data OvlLayer Source
Constructors
UserLayer
HintLayer
show/hide Instances
mkOverlay :: OvlLayer -> Region -> StyleName -> OverlaySource
Create an overlay for the style sty between points s and e
gotoLn :: Int -> BufferM IntSource
Go to line number n. n is indexed from 1. Returns the actual line we went to (which may be not be the requested line, if it was out of range)
gotoLnFrom :: Int -> BufferM IntSource
Go to line indexed from current point Returns the actual moved difference which of course may be negative if the requested difference was negative.
leftB :: BufferM ()Source
Move point -1
rightB :: BufferM ()Source
Move cursor +1
moveN :: Int -> BufferM ()Source
Move point by the given number of characters. A negative offset moves backwards a positive one forward.
leftN :: Int -> BufferM ()Source
Move cursor -n
rightN :: Int -> BufferM ()Source
Move cursor +n
insertN :: String -> BufferM ()Source
Insert the list at current point, extending size of buffer
insertNAt :: String -> Point -> BufferM ()Source
Insert the list at specified point, extending size of buffer
insertB :: Char -> BufferM ()Source
Insert the char at current point, extending size of buffer
deleteN :: Int -> BufferM ()Source
Delete n characters forward from the current point
nelemsB :: Int -> Point -> BufferM StringSource
Return n elems starting at i of the buffer as a list
writeB :: Char -> BufferM ()Source
Write an element into the buffer at the current point.
writeN :: String -> BufferM ()Source
Write the list into the buffer at current point.
newlineB :: BufferM ()Source
Insert newline at current point.
deleteNAt :: Direction -> Int -> Point -> BufferM ()Source
deleteNAt n p deletes n characters forwards from position p
readB :: BufferM CharSource
Read the character at the current point
elemsB :: BufferM StringSource
Return the contents of the buffer as a list
undosA :: Accessor FBuffer URListSource
undoB :: BufferM ()Source
redoB :: BufferM ()Source
getMarkB :: Maybe String -> BufferM MarkSource
mayGetMarkB :: String -> BufferM (Maybe Mark)Source
getMarkValueB :: Mark -> BufferM MarkValueSource
setMarkPointB :: Mark -> Point -> BufferM ()Source
Set the given mark's point.
modifyMarkB :: Mark -> (MarkValue -> MarkValue) -> BufferM ()Source
newMarkB :: MarkValue -> BufferM MarkSource
deleteMarkB :: Mark -> BufferM ()Source
setVisibleSelection :: Bool -> BufferM ()Source
Highlight the selection
isUnchangedBuffer :: FBuffer -> BoolSource
setAnyMode :: AnyMode -> BufferM ()Source
Set the mode
setMode :: Mode syntax -> BufferM ()Source
setMode0 :: forall syntax. Mode syntax -> FBuffer -> FBufferSource
modifyMode :: (forall syntax. Mode syntax -> Mode syntax) -> BufferM ()Source
Modify the mode
regexRegionB :: SearchExp -> Region -> BufferM [Region]Source
Return indices of strings in buffer matched by regex in the given region.
regexB :: Direction -> SearchExp -> BufferM [Region]Source
Return indices of next string in buffer matched by regex in the given direction
readAtB :: Point -> BufferM CharSource
Read the character at the given index This is an unsafe operation: character NUL is returned when out of bounds
getModeLine :: [String] -> BufferM StringSource

Given a buffer, and some information update the modeline

N.B. the contents of modelines should be specified by user, and not hardcoded.

getPercent :: Point -> Point -> StringSource
Given a point, and the file size, gives us a percent string
setInserting :: Bool -> BufferM ()Source
forgetPreferCol :: BufferM ()Source
movingToPrefCol :: BufferM a -> BufferM aSource
setPrefCol :: Maybe Int -> BufferM ()Source
markSavedB :: UTCTime -> BufferM ()Source
Mark the current point in the undo list as a saved state.
addOverlayB :: Overlay -> BufferM ()Source
Adds an overlay to the buffer
delOverlayB :: Overlay -> BufferM ()Source
Remove an existing overlay
delOverlayLayerB :: OvlLayer -> BufferM ()Source
savingExcursionB :: BufferM a -> BufferM aSource
perform a BufferM a, and return to the current point. (by using a mark)
savingPointB :: BufferM a -> BufferM aSource
perform an BufferM a, and return to the current point
pendingUpdatesA :: Accessor FBuffer [UIUpdate]Source
highlightSelectionA :: Accessor FBuffer BoolSource
rectangleSelectionA :: Accessor FBuffer BoolSource
readOnlyA :: Accessor FBuffer BoolSource
insertingA :: Accessor FBuffer BoolSource
pointFollowsWindowA :: Accessor FBuffer (WindowRef -> Bool)Source
revertPendingUpdatesB :: BufferM ()Source
Revert all the pending updates; don't touch the point.
askWindow :: (Window -> a) -> BufferM aSource
clearSyntax :: FBuffer -> FBufferSource
udpate the syntax information (clear the dirty flag)
focusSyntax :: Map WindowRef Region -> FBuffer -> FBufferSource
data Mode syntax Source
A Mode customizes the Yi interface for editing a particular data format. It specifies when the mode should be used and controls file-specific syntax highlighting and command input, among other things.
Constructors
Mode
modeName :: Stringso this can be serialized, debugged.
modeApplies :: FilePath -> String -> BoolWhat type of files does this mode apply to?
modeHL :: ExtHL syntaxSyntax highlighter
modePrettify :: syntax -> BufferM ()Prettify current "paragraph"
modeKeymap :: KeymapSet -> KeymapSetBuffer-local keymap modification
modeIndent :: syntax -> IndentBehaviour -> BufferM ()emacs-style auto-indent line
modeAdjustBlock :: syntax -> Int -> BufferM ()adjust the indentation after modification
modeFollow :: syntax -> ActionFollow a "link" in the file. (eg. go to location of error message)
modeIndentSettings :: IndentSettings
modeToggleCommentSelection :: BufferM ()
modeGetStrokes :: syntax -> Point -> Point -> Point -> [Stroke]Strokes that should be applied when displaying a syntax element
modeGetAnnotations :: syntax -> Point -> [Span String]
modePrintTree :: syntax -> BufferM ()
modeOnLoad :: BufferM ()An action that is to be executed when this mode is set
show/hide Instances
Binary (Mode syntax)
data AnyMode Source
Constructors
forall syntax . AnyMode (Mode syntax)
show/hide Instances
data IndentBehaviour Source
Used to specify the behaviour of the automatic indent command.
Constructors
IncreaseCycleIncrease the indentation to the next higher indentation hint. If we are currently at the highest level of indentation then cycle back to the lowest.
DecreaseCycleDecrease the indentation to the next smaller indentation hint. If we are currently at the smallest level then cycle back to the largest
IncreaseOnlyIncrease the indentation to the next higher hint if no such hint exists do nothing.
DecreaseOnlyDecrease the indentation to the next smaller indentation hint, if no such hint exists do nothing.
show/hide Instances
data IndentSettings Source
Currently duplicates some of Vim's indent settings. Allowing a buffer to - specify settings that are more dynamic, perhaps via closures, could be - useful.
Constructors
IndentSettings
expandTabs :: BoolInsert spaces instead of tabs as possible
tabSize :: IntSize of a Tab
shiftWidth :: IntIndent by so many columns
show/hide Instances
modeAlwaysApplies :: FilePath -> String -> BoolSource
Mode applies function that always returns True.
modeNeverApplies :: FilePath -> String -> BoolSource
Mode applies function that always returns False.
emptyMode :: Mode syntaxSource
withModeB :: (forall syntax. Mode syntax -> BufferM a) -> BufferM aSource
withMode0 :: (forall syntax. Mode syntax -> a) -> FBuffer -> aSource
onMode :: (forall syntax. Mode syntax -> Mode syntax) -> AnyMode -> AnyModeSource
withSyntaxB :: (forall syntax. Mode syntax -> syntax -> a) -> BufferM aSource
withSyntaxB' :: (forall syntax. Mode syntax -> syntax -> BufferM a) -> BufferM aSource
keymapProcessA :: Accessor FBuffer KeymapProcessSource
strokesRangesB :: Maybe SearchExp -> Region -> BufferM [[Stroke]]Source
streamB :: Direction -> Point -> BufferM RopeSource
indexedStreamB :: Direction -> Point -> BufferM [(Point, Char)]Source
getMarkPointB :: Mark -> BufferM PointSource
askMarks :: BufferM WinMarksSource
pointAt :: forall a. BufferM a -> BufferM PointSource
data SearchExp Source
lastActiveWindowA :: Accessor FBuffer WindowSource
Use in readonly!
bufferDynamicValueA :: Initializable a => Accessor FBuffer aSource

Access to a value into the extensible state, keyed by its type. This allows you to save or retrieve inside a BufferM monad, ie:

 putA bufferDynamicValueA updatedvalue
 value <- getA bufferDynamicValueA
shortIdentString :: [a] -> FBuffer -> [Char]Source
identString :: FBuffer -> [Char]Source
miniIdentString :: FBuffer -> [Char]Source
identA :: Accessor FBuffer BufferIdSource
type BufferId = Either String FilePathSource
maybe a filename associated with this buffer. Filename is canonicalized.
file :: FBuffer -> Maybe FilePathSource
lastSyncTimeA :: Accessor FBuffer UTCTimeSource
Produced by Haddock version 2.6.1