yi-0.11.0: The Haskell-Scriptable Editor

Portabilityportable
Stabilityexperimental
Maintaineryi-devel@googlegroups.com
Safe HaskellNone

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 

Instances

Eq FBuffer 
Show FBuffer 
Typeable FBuffer 
Binary FBuffer 
MonadState FBuffer BufferM 

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 => Binary (MarkSet 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.

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.)

sizeB :: BufferM PointSource

Point of eof

pointB :: BufferM PointSource

Extract the current point

solPointB :: Point -> BufferM PointSource

Returns start of line point for a given point p

eolPointB :: Point -> BufferM PointSource

Returns end of line for given point.

markLines :: BufferM (MarkSet Int)Source

Return line numbers of marks

moveTo :: Point -> BufferM ()Source

Move point in buffer to the given index

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 -> YiString -> FBufferSource

Create buffer named nm with contents s

data MarkValue Source

Constructors

MarkValue 

Instances

Eq MarkValue 
Ord MarkValue 
Show MarkValue 
Typeable MarkValue 
Binary MarkValue 

data Overlay Source

Instances

Eq Overlay 
Ord Overlay 

data OvlLayer Source

Constructors

UserLayer 
HintLayer 

Instances

Eq OvlLayer 
Ord OvlLayer 

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

Insert the YiString at current point, extending size of buffer

insertNAt :: YiString -> Point -> BufferM ()Source

Insert given YiString at specified point, extending size of the buffer.

insertB :: Char -> BufferM ()Source

Insert the char at current point, extending size of buffer

Implementation note: This just insertBs a singleton. This seems sub-optimal because we should be able to do much better without spewing chunks of size 1 everywhere. This approach is necessary however so an Update can be recorded. A possible improvement for space would be to have ‘yi-rope’ package optimise for appends with length 1.

deleteN :: Int -> BufferM ()Source

Delete n characters forward from the current point

writeB :: Char -> BufferM ()Source

Write an element into the buffer at the current point.

writeN :: YiString -> 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 YiStringSource

Return the contents of the buffer.

undosA :: HasAttributes c => Lens' c URListSource

getMarkB :: Maybe String -> BufferM MarkSource

mayGetMarkB :: String -> BufferM (Maybe Mark)Source

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 -> 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 :: [Text] -> BufferM TextSource

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 -> TextSource

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

preferColA :: HasAttributes c => Lens' c (Maybe Int)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

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.

savingPositionB :: BufferM a -> BufferM aSource

Perform an BufferM a, and return to the current line and column number. The difference between this and savingPointB is that here we attempt to return to the specific line and column number, rather than a specific number of characters from the beginning of the buffer.

In case the column is further away than EOL, the point is left at EOL: moveToLineColB is used internally.

pendingUpdatesA :: HasAttributes c => Lens' c [UIUpdate]Source

readOnlyA :: HasAttributes c => Lens' c BoolSource

insertingA :: HasAttributes c => Lens' c BoolSource

pointFollowsWindowA :: HasAttributes c => Lens' c (WindowRef -> Bool)Source

revertPendingUpdatesB :: BufferM ()Source

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

clearSyntax :: FBuffer -> FBufferSource

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 :: Text

so this can be serialized, debugged.

modeApplies :: FilePath -> YiString -> 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 :: Maybe (BufferM ())
 
modeGetStrokes :: syntax -> Point -> Point -> Point -> [Stroke]

Strokes that should be applied when displaying a syntax element should this be an Action instead?

modeOnLoad :: BufferM ()

An action that is to be executed when this mode is set

modeModeLine :: [Text] -> BufferM Text

buffer-local modeline formatting method

modeGotoDeclaration :: BufferM ()

go to the point where the variable is declared

Instances

Binary (Mode syntax)

Just stores the mode name.

modeNameA :: forall syntax. Lens' (Mode syntax) TextSource

modeAppliesA :: forall syntax. Lens' (Mode syntax) (FilePath -> YiString -> 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) (Maybe (BufferM ()))Source

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

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

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

data AnyMode Source

Constructors

forall syntax . AnyMode (Mode syntax) 

Instances

Typeable AnyMode 

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.

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 

Fields

expandTabs :: Bool

Insert spaces instead of tabs as possible

tabSize :: Int

Size of a Tab

shiftWidth :: Int

Indent by so many columns

Instances

modeAlwaysApplies :: a -> b -> BoolSource

Mode applies function that always returns True.

modeNeverApplies :: a -> b -> BoolSource

Mode applies function that always returns False.

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 :: HasAttributes c => Lens' c KeymapProcessSource

data SearchExp

Instances

Binary SearchExp 

lastActiveWindowA :: HasAttributes c => Lens' c WindowSource

putBufferDyn :: (YiVariable a, MonadState FBuffer m, Functor m) => a -> m ()Source

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

 putBufferDyn updatedvalue

getBufferDyn :: (YiVariable a, MonadState FBuffer m, Functor m) => m aSource

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

 value <- getBufferDyn

shortIdentStringSource

Arguments

:: Int

Number of characters to drop from FileBuffer names

-> FBuffer

Buffer to work with

-> Text 

Gets a short identifier of a buffer. If we're given a MemBuffer then just wraps the buffer name like so: *name*. If we're given a FileBuffer, it drops the the number of characters specified.

>>> shortIdentString 3 (MemBuffer "hello")
"*hello*"
>>> shortIdentString 3 (FileBuffer "hello")
"lo"

identString :: FBuffer -> TextSource

Gets the buffer's identifier string, emphasising the MemBuffer:

>>> identString (MemBuffer "hello")
"*hello*"
>>> identString (FileBuffer "hello")
"hello"

identA :: HasAttributes c => Lens' c BufferIdSource

directoryContentA :: HasAttributes c => Lens' c BoolSource

data BufferId Source

Constructors

MemBuffer Text 
FileBuffer FilePath 

Instances

Eq BufferId 
Show BufferId 
Binary BufferId 

file :: FBuffer -> Maybe FilePathSource

lastSyncTimeA :: HasAttributes c => Lens' c UTCTimeSource

destinationOfMoveB :: BufferM a -> BufferM PointSource

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

betweenBSource

Arguments

:: Point

Point to start at

-> Point

Point to stop at

-> BufferM YiString 

Returns the contents of the buffer between the two points.

If the startPoint >= endPoint, empty string is returned. If the points are out of bounds, as much of the content as possible is taken: you're not guaranteed to get endPoint - startPoint characters.

decreaseFontSize :: Int -> BufferM ()Source

Decreases the font size in the buffer by specified number. What this number actually means depends on the front-end.

increaseFontSize :: Int -> BufferM ()Source

Increases the font size in the buffer by specified number. What this number actually means depends on the front-end.

indentSettingsB :: BufferM IndentSettingsSource

Gives the IndentSettings for the current buffer.

fontsizeVariationA :: HasAttributes c => Lens' c IntSource

encodingConverterNameA :: HasAttributes c => Lens' c (Maybe ConverterName)Source