yi-0.7.1: The Haskell-Scriptable Editor

Safe HaskellNone

Yi.Editor

Description

The top level editor state, and operations on it.

Synopsis

Documentation

type Statuses = DelayList StatusSource

data Editor Source

The Editor state

Constructors

Editor 

Fields

bufferStack :: ![BufferRef]

Stack of all the buffers. Invariant: never empty Invariant: first buffer is the current one.

buffers :: !(Map BufferRef FBuffer)
 
refSupply :: !Int

Supply for buffer, window and tab ids.

tabs_ :: !(PointedList Tab)

current tab contains the visible windows pointed list.

dynamic :: !DynamicValues

dynamic components

statusLines :: !Statuses
 
maxStatusHeight :: !Int
 
killring :: !Killring
 
currentRegex :: !(Maybe SearchExp)

currently highlighted regex (also most recent regex for use in vim bindings)

searchDirection :: !Direction
 
pendingEvents :: ![Event]

Processed events that didn't yield any action yet.

onCloseActions :: !(Map BufferRef (EditorM ()))

Actions to be run when the buffer is closed; should be scrapped.

emptyEditor :: EditorSource

The initial state

dynA :: YiVariable a => Accessor Editor aSource

stringToNewBufferSource

Arguments

:: BufferId

The buffer indentifier

-> Rope

The contents with which to populate the buffer

-> EditorM BufferRef 

Create and fill a new buffer, using contents of string. | Does not focus the window, or make it the current window. | Call newWindowE or switchToBufferE to take care of that.

forceFold1 :: Foldable t => t a -> t aSource

deleteBuffer :: BufferRef -> EditorM ()Source

Delete a buffer (and release resources associated with it).

bufferSet :: Editor -> [FBuffer]Source

Return the buffers we have, in no particular order

commonNamePrefix :: Editor -> [String]Source

Return a prefix that can be removed from all buffer paths while keeping them unique.

findBufferWith :: BufferRef -> Editor -> FBufferSource

Find buffer with this key

findBufferWithName :: String -> Editor -> [BufferRef]Source

Find buffer with this name

getBufferWithName :: String -> EditorM BufferRefSource

Find buffer with given name. Fail if not found.

openAllBuffersE :: EditorM ()Source

Make all buffers visible by splitting the current window list. FIXME: rename to displayAllBuffersE; make sure buffers are not open twice.

shiftBuffer :: Int -> EditorM ()Source

Rotate the buffer stack by the given amount.

withGivenBuffer0 :: BufferRef -> BufferM a -> EditorM aSource

Perform action with any given buffer, using the last window that was used for that buffer.

withGivenBufferAndWindow0 :: Window -> BufferRef -> BufferM a -> EditorM aSource

Perform action with any given buffer

withBuffer0 :: BufferM a -> EditorM aSource

Perform action with current window's buffer

currentBuffer :: Editor -> BufferRefSource

Return the current buffer

printMsg :: String -> EditorM ()Source

Display a transient message

setStatus :: Status -> EditorM ()Source

Set the background status line

clrStatus :: EditorM ()Source

Clear the status line

setRegE :: String -> EditorM ()Source

Put string into yank register

getRegE :: EditorM StringSource

Return the contents of the yank register

getDynamic :: YiVariable a => EditorM aSource

Dynamically-extensible state components.

These hooks are used by keymaps to store values that result from Actions (i.e. that restult from IO), as opposed to the pure values they generate themselves, and can be stored internally.

The dynamic field is a type-indexed map.

Retrieve a value from the extensible state

setDynamic :: YiVariable a => a -> EditorM ()Source

Insert a value into the extensible state, keyed by its type

nextBufW :: EditorM ()Source

Attach the next buffer in the buffer stack to the current window.

prevBufW :: EditorM ()Source

Attach the previous buffer in the stack list to the current window.

newBufferESource

Arguments

:: BufferId

buffer name

-> Rope

buffer contents

-> EditorM BufferRef 

Like fnewE, create a new buffer filled with the String s, Switch the current window to this buffer. Doesn't associate any file with the buffer (unlike fnewE) and so is good for popup internal buffers (like scratch)

newTempBufferE :: EditorM BufferRefSource

Creates an in-memory buffer with a unique name.

A hint for the buffer naming scheme can be specified in the dynamic variable TempBufferNameHint The new buffer always has a buffer ID that did not exist before newTempBufferE. TODO: this probably a lot more complicated than it should be: why not count from zero every time?

newZeroSizeWindow :: Bool -> BufferRef -> WindowRef -> WindowSource

Create a new zero size window on a given buffer

newWindowE :: Bool -> BufferRef -> EditorM WindowSource

Create a new window onto the given buffer.

switchToBufferE :: BufferRef -> EditorM ()Source

Attach the specified buffer to the current window

switchToBufferOtherWindowE :: BufferRef -> EditorM ()Source

Attach the specified buffer to some other window than the current one

switchToBufferWithNameE :: String -> EditorM ()Source

Switch to the buffer specified as parameter. If the buffer name is empty, switch to the next buffer.

closeBufferE :: String -> EditorM ()Source

Close a buffer. Note: close the current buffer if the empty string is given

closeBufferAndWindowE :: EditorM ()Source

Close current buffer and window, unless it's the last one.

nextWinE :: EditorM ()Source

Rotate focus to the next window

prevWinE :: EditorM ()Source

Rotate focus to the previous window

swapWinWithFirstE :: EditorM ()Source

Swaps the focused window with the first window. Useful for layouts such as HPairOneStack, for which the first window is the largest.

pushWinToFirstE :: EditorM ()Source

Moves the focused window to the first window, and moves all other windows down the stack.

moveWinNextE :: EditorM ()Source

Swap focused window with the next one

moveWinPrevE :: EditorM ()Source

Swap focused window with the previous one

fixCurrentBufferA_ :: Accessor Editor EditorSource

A fake accessor that fixes the current buffer after a change of the current window. Enforces invariant that top of buffer stack is the buffer of the current window.

fixCurrentWindow :: EditorM ()Source

Counterpart of fixCurrentBufferA_: fix the current window to point to the right buffer.

windowsOnBufferE :: BufferRef -> EditorM [Window]Source

Return the windows that are currently open on the buffer whose key is given

focusWindowE :: WindowRef -> EditorM ()Source

bring the editor focus the window with the given key.

Fails if no window with the given key is found.

splitE :: EditorM ()Source

Split the current window, opening a second window onto current buffer. TODO: unfold newWindowE here?

layoutManagersNextE :: EditorM ()Source

Cycle to the next layout manager, or the first one if the current one is nonstandard.

layoutManagersPreviousE :: EditorM ()Source

Cycle to the previous layout manager, or the first one if the current one is nonstandard.

withLMStack :: (PointedList AnyLayoutManager -> PointedList AnyLayoutManager) -> EditorM ()Source

Helper function for layoutManagersNext and layoutManagersPrevious

layoutManagerNextVariantE :: EditorM ()Source

Next variant of the current layout manager, as given by nextVariant

layoutManagerPreviousVariantE :: EditorM ()Source

Previous variant of the current layout manager, as given by previousVariant

enlargeWinE :: EditorM ()Source

Enlarge the current window

shrinkWinE :: EditorM ()Source

Shrink the current window

setDividerPosE :: DividerRef -> DividerPosition -> EditorM ()Source

Sets the given divider position on the current tab

newTabE :: EditorM ()Source

Creates a new tab containing a window that views the current buffer.

nextTabE :: EditorM ()Source

Moves to the next tab in the round robin set of tabs

previousTabE :: EditorM ()Source

Moves to the previous tab in the round robin set of tabs

moveTab :: Maybe Int -> EditorM ()Source

Moves the focused tab to the given index, or to the end if the index is not specified.

deleteTabE :: EditorM ()Source

Deletes the current tab. If there is only one tab open then error out. When the last tab is focused, move focus to the left, otherwise move focus to the right.

tryCloseE :: EditorM ()Source

Close the current window. If there is only one tab open and the tab contains only one window then do nothing.

closeOtherE :: EditorM ()Source

Make the current window the only window on the screen

shiftOtherWindow :: MonadEditor m => m ()Source

Switch focus to some other window. If none is available, create one.

withOtherWindow :: MonadEditor m => m a -> m aSource

Execute the argument in the context of an other window. Create one if necessary. The current window is re-focused after the argument has completed.

onCloseBufferE :: BufferRef -> EditorM () -> EditorM ()Source

Defines an action to be executed when the current buffer is closed.

Used by the minibuffer to assure the focus is restored to the buffer that spawned the minibuffer.

todo: These actions are not restored on reload.

todo: These actions should probably be very careful at what they do. TODO: All in all, this is a very ugly way to achieve the purpose. The nice way to proceed is to somehow attach the miniwindow to the window that has spawned it.