Safe Haskell | None |
---|
The Buffer
module defines monadic editing operations over one-dimensional
buffers, maintaining a current point.
- 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 {}
- 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
- lineCountB :: 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
- 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' :: Rope -> BufferM ()
- insertN :: String -> BufferM ()
- insertNAt' :: Rope -> Point -> BufferM ()
- insertNAt :: String -> Point -> BufferM ()
- insertB :: Char -> BufferM ()
- deleteN :: Int -> BufferM ()
- nelemsB :: Int -> Point -> BufferM String
- nelemsB' :: Int -> Point -> BufferM Rope
- 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
- setMarkHereB :: BufferM Mark
- setNamedMarkHereB :: String -> BufferM ()
- 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 ()
- savingPrefCol :: BufferM a -> BufferM a
- forgetPreferCol :: BufferM ()
- movingToPrefCol :: BufferM a -> BufferM a
- getPrefCol :: BufferM (Maybe Int)
- 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 ()
- modeModeLine :: [String] -> BufferM String
- modeNameA :: forall syntax. T (Mode syntax) String
- modeAppliesA :: forall syntax. T (Mode syntax) (FilePath -> String -> Bool)
- modeHLA :: forall syntax. T (Mode syntax) (ExtHL syntax)
- modePrettifyA :: forall syntax. T (Mode syntax) (syntax -> BufferM ())
- modeKeymapA :: forall syntax. T (Mode syntax) (KeymapSet -> KeymapSet)
- modeIndentA :: forall syntax. T (Mode syntax) (syntax -> IndentBehaviour -> BufferM ())
- modeAdjustBlockA :: forall syntax. T (Mode syntax) (syntax -> Int -> BufferM ())
- modeFollowA :: forall syntax. T (Mode syntax) (syntax -> Action)
- modeIndentSettingsA :: forall syntax. T (Mode syntax) IndentSettings
- modeToggleCommentSelectionA :: forall syntax. T (Mode syntax) (BufferM ())
- modeGetStrokesA :: forall syntax. T (Mode syntax) (syntax -> Point -> Point -> Point -> [Stroke])
- modeGetAnnotationsA :: forall syntax. T (Mode syntax) (syntax -> Point -> [Span String])
- modePrintTreeA :: forall syntax. T (Mode syntax) (syntax -> BufferM ())
- modeOnLoadA :: forall syntax. T (Mode syntax) (BufferM ())
- modeModeLineA :: forall syntax. T (Mode syntax) ([String] -> BufferM String)
- data AnyMode = forall syntax . AnyMode (Mode syntax)
- data IndentBehaviour
- 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 :: YiVariable 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
- replaceCharB :: Char -> BufferM ()
- replaceCharWithBelowB :: BufferM ()
- replaceCharWithAboveB :: BufferM ()
- insertCharWithBelowB :: BufferM ()
- insertCharWithAboveB :: BufferM ()
- pointAfterCursorB :: Point -> BufferM Point
- destinationOfMoveB :: BufferM a -> BufferM Point
- withEveryLineB :: BufferM () -> BufferM ()
- startUpdateTransactionB :: BufferM ()
- commitUpdateTransactionB :: BufferM ()
Documentation
The BufferM monad writes the updates performed.
Monad BufferM | |
Functor BufferM | |
Typeable1 BufferM | |
Applicative BufferM | |
MonadReader Window BufferM | |
MonadState FBuffer BufferM | |
MonadWriter [Update] BufferM | |
YiAction (BufferM x) x | |
MkSnippetCmd (SnippetCmd a) a |
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.
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.
Current column. Note that this is different from offset or number of chars from sol. (This takes into account tabs, unicode chars, etc.)
lineCountB :: BufferM IntSource
pointOfLineColB :: Int -> Int -> BufferM PointSource
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.
MarkValue | |
|
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.
moveN :: Int -> BufferM ()Source
Move point by the given number of characters. A negative offset moves backwards a positive one forward.
insertNAt' :: Rope -> Point -> BufferM ()Source
insertNAt :: String -> Point -> BufferM ()Source
Insert the list at specified point, extending size of buffer
deleteNAt :: Direction -> Int -> Point -> BufferM ()Source
deleteNAt n p
deletes n
characters forwards from position p
setNamedMarkHereB :: String -> BufferM ()Source
setMarkPointB :: Mark -> Point -> BufferM ()Source
Set the given mark's point.
deleteMarkB :: Mark -> BufferM ()Source
setVisibleSelection :: Bool -> BufferM ()Source
Highlight the selection
isUnchangedBuffer :: FBuffer -> BoolSource
setAnyMode :: AnyMode -> BufferM ()Source
Set the mode
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
savingPrefCol :: BufferM a -> BufferM aSource
forgetPreferCol :: BufferM ()Source
movingToPrefCol :: BufferM a -> BufferM aSource
getPrefCol :: BufferM (Maybe Int)Source
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
highlightSelectionA :: Accessor FBuffer BoolSource
rectangleSelectionA :: 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.
clearSyntax :: FBuffer -> FBufferSource
udpate the syntax information (clear the dirty flag)
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.
Mode | |
|
modeAppliesA :: forall syntax. T (Mode syntax) (FilePath -> String -> Bool)Source
modePrettifyA :: forall syntax. T (Mode syntax) (syntax -> BufferM ())Source
modeIndentA :: forall syntax. T (Mode syntax) (syntax -> IndentBehaviour -> BufferM ())Source
modeAdjustBlockA :: forall syntax. T (Mode syntax) (syntax -> Int -> BufferM ())Source
modeFollowA :: forall syntax. T (Mode syntax) (syntax -> Action)Source
modeIndentSettingsA :: forall syntax. T (Mode syntax) IndentSettingsSource
modeToggleCommentSelectionA :: forall syntax. T (Mode syntax) (BufferM ())Source
modeGetStrokesA :: forall syntax. T (Mode syntax) (syntax -> Point -> Point -> Point -> [Stroke])Source
modePrintTreeA :: forall syntax. T (Mode syntax) (syntax -> BufferM ())Source
modeOnLoadA :: forall syntax. T (Mode syntax) (BufferM ())Source
data IndentBehaviour Source
Used to specify the behaviour of the automatic indent command.
IncreaseCycle | Increase the indentation to the next higher indentation hint. If we are currently at the highest level of indentation then cycle back to the lowest. |
DecreaseCycle | Decrease the indentation to the next smaller indentation hint. If we are currently at the smallest level then cycle back to the largest |
IncreaseOnly | Increase the indentation to the next higher hint if no such hint exists do nothing. |
DecreaseOnly | Decrease the indentation to the next smaller indentation hint, if no such hint exists do nothing. |
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.
IndentSettings | |
|
modeAlwaysApplies :: FilePath -> String -> BoolSource
Mode applies function that always returns True.
modeNeverApplies :: FilePath -> String -> BoolSource
Mode applies function that always returns False.
withSyntaxB :: (forall syntax. Mode syntax -> syntax -> a) -> BufferM aSource
withSyntaxB' :: (forall syntax. Mode syntax -> syntax -> BufferM a) -> BufferM aSource
getMarkPointB :: Mark -> BufferM PointSource
lastActiveWindowA :: Accessor FBuffer WindowSource
Use in readonly!
bufferDynamicValueA :: YiVariable 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
type BufferId = Either String FilePathSource
maybe a filename associated with this buffer. Filename is canonicalized.
lastSyncTimeA :: Accessor FBuffer UTCTimeSource
replaceCharB :: Char -> BufferM ()Source
destinationOfMoveB :: BufferM a -> BufferM PointSource
What would be the point after doing the given action? The argument must not modify the buffer.
withEveryLineB :: BufferM () -> BufferM ()Source