yi-0.8.1: The Haskell-Scriptable Editor

Safe HaskellNone
LanguageHaskell2010

Yi.Buffer.Misc

Description

The Buffer module defines monadic editing operations over one-dimensional buffers, maintaining a current point.

Synopsis

Documentation

data FBuffer Source

Constructors

forall syntax . FBuffer !(Mode syntax) !(BufferImpl syntax) !Attributes 

newtype BufferM a Source

The BufferM monad writes the updates performed.

Constructors

BufferM 

data MarkSet a Source

Constructors

MarkSet 

Fields

fromMark :: !a
 
insMark :: !a
 
selMark :: !a
 

Instances

Functor MarkSet 
Foldable MarkSet 
Traversable MarkSet 
Binary a_1628300227 => Binary (MarkSet a_1628300227) 

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 -> a Source

Execute a BufferM value on a given buffer, using a dummy window. The new state of the buffer is discarded.

curLn :: BufferM Int Source

Return the current line number

curCol :: BufferM Int Source

Current column. Note that this is different from offset or number of chars from sol. (This takes into account tabs, unicode chars, etc.)

sizeB :: BufferM Point Source

Point of eof

pointB :: BufferM Point Source

Extract the current point

solPointB :: Point -> BufferM Point Source

Returns start of line point for a given point p

markLines :: BufferM (MarkSet Int) Source

Return line numbers of marks

moveTo :: Point -> BufferM () Source

Move point in buffer to the given index

lineMoveRel :: Int -> BufferM Int Source

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 -> FBuffer Source

Create buffer named nm with contents s

data OvlLayer Source

Constructors

UserLayer 
HintLayer 

Instances

mkOverlay :: OvlLayer -> Region -> StyleName -> Overlay Source

Create an "overlay" for the style sty between points s and e

gotoLn :: Int -> BufferM Int Source

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 Int Source

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' :: Rope -> BufferM () Source

insertN :: String -> BufferM () Source

Insert the list at current point, extending size of buffer

insertNAt' :: Rope -> Point -> BufferM () Source

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 String Source

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 Char Source

Read the character at the current point

elemsB :: BufferM String Source

Return the contents of the buffer as a list

setMarkPointB :: Mark -> Point -> BufferM () Source

Set the given mark's point.

setVisibleSelection :: Bool -> BufferM () Source

Highlight the selection

setAnyMode :: AnyMode -> BufferM () Source

Set the mode

setMode :: Mode syntax -> BufferM () Source

setMode0 :: forall syntax. Mode syntax -> FBuffer -> FBuffer Source

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 Char Source

Read the character at the given index This is an unsafe operation: character NUL is returned when out of bounds

getModeLine :: [String] -> BufferM String Source

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 -> String Source

Given a point, and the file size, gives us a percent string

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"

savingExcursionB :: BufferM a -> BufferM a Source

perform a BufferM a, and return to the current point. (by using a mark)

savingPointB :: BufferM a -> BufferM a Source

perform an BufferM a, and return to the current point

revertPendingUpdatesB :: BufferM () Source

Revert all the pending updates; don't touch the point.

clearSyntax :: FBuffer -> FBuffer Source

update the syntax information (clear the dirty "flag")

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 

Fields

modeName :: String

so this can be serialized, debugged.

modeApplies :: FilePath -> String -> Bool

What type of files does this mode apply to?

modeHL :: ExtHL syntax

Syntax highlighter

modePrettify :: syntax -> BufferM ()

Prettify current "paragraph"

modeKeymap :: KeymapSet -> KeymapSet

Buffer-local keymap modification

modeIndent :: syntax -> IndentBehaviour -> BufferM ()

emacs-style auto-indent line

modeAdjustBlock :: syntax -> Int -> BufferM ()

adjust the indentation after modification

modeFollow :: syntax -> Action

Follow a "link" in the file. (eg. go to location of error message)

modeIndentSettings :: IndentSettings
 
modeToggleCommentSelection :: YiM ()
 
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

modeModeLine :: [String] -> BufferM String

buffer-local modeline formatting method

Instances

Binary (Mode syntax) 

modeNameA :: forall syntax. Lens' (Mode syntax) String Source

modeAppliesA :: forall syntax. Lens' (Mode syntax) (FilePath -> String -> Bool) Source

modeHLA :: forall syntax. Lens' (Mode syntax) (ExtHL syntax) Source

modePrettifyA :: forall syntax. Lens' (Mode syntax) (syntax -> BufferM ()) Source

modeKeymapA :: forall syntax. Lens' (Mode syntax) (KeymapSet -> KeymapSet) Source

modeIndentA :: forall syntax. Lens' (Mode syntax) (syntax -> IndentBehaviour -> BufferM ()) Source

modeAdjustBlockA :: forall syntax. Lens' (Mode syntax) (syntax -> Int -> BufferM ()) Source

modeFollowA :: forall syntax. Lens' (Mode syntax) (syntax -> Action) Source

modeToggleCommentSelectionA :: forall syntax. Lens' (Mode syntax) (YiM ()) Source

modeGetStrokesA :: forall syntax. Lens' (Mode syntax) (syntax -> Point -> Point -> Point -> [Stroke]) Source

modeGetAnnotationsA :: forall syntax. Lens' (Mode syntax) (syntax -> Point -> [Span String]) Source

modePrintTreeA :: forall syntax. Lens' (Mode syntax) (syntax -> BufferM ()) Source

modeOnLoadA :: forall syntax. Lens' (Mode syntax) (BufferM ()) Source

modeModeLineA :: forall syntax. Lens' (Mode syntax) ([String] -> BufferM String) Source

data AnyMode Source

Constructors

forall syntax . AnyMode (Mode syntax) 

Instances

data IndentBehaviour Source

Used to specify the behaviour of the automatic indent command.

Constructors

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.

Constructors

IndentSettings 

Fields

expandTabs :: Bool

Insert spaces instead of tabs as possible

tabSize :: Int

Size of a Tab

shiftWidth :: Int

Indent by so many columns

modeAlwaysApplies :: FilePath -> String -> Bool Source

Mode applies function that always returns True.

modeNeverApplies :: FilePath -> String -> Bool Source

Mode applies function that always returns False.

withModeB :: (forall syntax. Mode syntax -> BufferM a) -> BufferM a Source

withMode0 :: (forall syntax. Mode syntax -> a) -> FBuffer -> a Source

onMode :: (forall syntax. Mode syntax -> Mode syntax) -> AnyMode -> AnyMode Source

withSyntaxB :: (forall syntax. Mode syntax -> syntax -> a) -> BufferM a Source

withSyntaxB' :: (forall syntax. Mode syntax -> syntax -> BufferM a) -> BufferM a Source

pointAt :: forall a. BufferM a -> BufferM Point Source

bufferDynamicValueA :: YiVariable a => Lens' FBuffer a Source

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

assign bufferDynamicValueA updatedvalue
value <- use bufferDynamicValueA

type BufferId = Either String FilePath Source

maybe a filename associated with this buffer. Filename is canonicalized.

destinationOfMoveB :: BufferM a -> BufferM Point Source

What would be the point after doing the given action? The argument must not modify the buffer.