Safe Haskell | None |
---|
The top level editor state, and operations on it.
- type Status = ([String], StyleName)
- type Statuses = DelayList Status
- data Editor = Editor {
- bufferStack :: ![BufferRef]
- buffers :: !(Map BufferRef FBuffer)
- refSupply :: !Int
- tabs_ :: !(PointedList Tab)
- dynamic :: !DynamicValues
- statusLines :: !Statuses
- maxStatusHeight :: !Int
- killring :: !Killring
- currentRegex :: !(Maybe SearchExp)
- searchDirection :: !Direction
- pendingEvents :: ![Event]
- onCloseActions :: !(Map BufferRef (EditorM ()))
- newtype EditorM a = EditorM {
- fromEditorM :: RWS Config () Editor a
- class (Monad m, MonadState Editor m) => MonadEditor m where
- askCfg :: m Config
- withEditor :: EditorM a -> m a
- liftEditor :: MonadEditor m => EditorM a -> m a
- emptyEditor :: Editor
- runEditor :: Config -> EditorM a -> Editor -> (Editor, a)
- onCloseActionsA :: T Editor (Map BufferRef (EditorM ()))
- pendingEventsA :: T Editor [Event]
- searchDirectionA :: T Editor Direction
- currentRegexA :: T Editor (Maybe SearchExp)
- killringA :: T Editor Killring
- maxStatusHeightA :: T Editor Int
- statusLinesA :: T Editor Statuses
- dynamicA :: T Editor DynamicValues
- tabs_A :: T Editor (PointedList Tab)
- refSupplyA :: T Editor Int
- buffersA :: T Editor (Map BufferRef FBuffer)
- bufferStackA :: T Editor [BufferRef]
- windows :: Editor -> PointedList Window
- windowsA :: Accessor Editor (PointedList Window)
- tabsA :: Accessor Editor (PointedList Tab)
- currentTabA :: Accessor Editor Tab
- askConfigVariableA :: (YiConfigVariable b, MonadEditor m) => m b
- dynA :: YiVariable a => Accessor Editor a
- newRef :: EditorM Int
- newBufRef :: EditorM BufferRef
- stringToNewBuffer :: BufferId -> Rope -> EditorM BufferRef
- insertBuffer :: FBuffer -> EditorM ()
- forceFold1 :: Foldable t => t a -> t a
- forceFoldTabs :: Foldable t => t Tab -> t Tab
- deleteBuffer :: BufferRef -> EditorM ()
- bufferSet :: Editor -> [FBuffer]
- commonNamePrefix :: Editor -> [String]
- getBufferStack :: EditorM [FBuffer]
- findBuffer :: BufferRef -> EditorM (Maybe FBuffer)
- findBufferWith :: BufferRef -> Editor -> FBuffer
- findBufferWithName :: String -> Editor -> [BufferRef]
- getBufferWithName :: String -> EditorM BufferRef
- openAllBuffersE :: EditorM ()
- shiftBuffer :: Int -> EditorM ()
- withGivenBuffer0 :: BufferRef -> BufferM a -> EditorM a
- withGivenBufferAndWindow0 :: Window -> BufferRef -> BufferM a -> EditorM a
- withBuffer0 :: BufferM a -> EditorM a
- currentWindowA :: Accessor Editor Window
- currentBuffer :: Editor -> BufferRef
- printMsg :: String -> EditorM ()
- printMsgs :: [String] -> EditorM ()
- printStatus :: Status -> EditorM ()
- setStatus :: Status -> EditorM ()
- clrStatus :: EditorM ()
- statusLine :: Editor -> [String]
- statusLineInfo :: Editor -> Status
- setTmpStatus :: Int -> Status -> EditorM ()
- setRegE :: String -> EditorM ()
- getRegE :: EditorM String
- getDynamic :: YiVariable a => EditorM a
- setDynamic :: YiVariable a => a -> EditorM ()
- nextBufW :: EditorM ()
- prevBufW :: EditorM ()
- newBufferE :: BufferId -> Rope -> EditorM BufferRef
- newTempBufferE :: EditorM BufferRef
- data TempBufferNameHint = TempBufferNameHint {
- tmp_name_base :: String
- tmp_name_index :: Int
- alternateBufferE :: Int -> EditorM ()
- newZeroSizeWindow :: Bool -> BufferRef -> WindowRef -> Window
- newWindowE :: Bool -> BufferRef -> EditorM Window
- switchToBufferE :: BufferRef -> EditorM ()
- switchToBufferOtherWindowE :: BufferRef -> EditorM ()
- switchToBufferWithNameE :: String -> EditorM ()
- closeBufferE :: String -> EditorM ()
- getBufferWithNameOrCurrent :: String -> EditorM BufferRef
- closeBufferAndWindowE :: EditorM ()
- nextWinE :: EditorM ()
- prevWinE :: EditorM ()
- swapWinWithFirstE :: EditorM ()
- pushWinToFirstE :: EditorM ()
- moveWinNextE :: EditorM ()
- moveWinPrevE :: EditorM ()
- fixCurrentBufferA_ :: Accessor Editor Editor
- fixCurrentWindow :: EditorM ()
- withWindowE :: Window -> BufferM a -> EditorM a
- findWindowWith :: WindowRef -> Editor -> Window
- windowsOnBufferE :: BufferRef -> EditorM [Window]
- focusWindowE :: WindowRef -> EditorM ()
- splitE :: EditorM ()
- layoutManagersNextE :: EditorM ()
- layoutManagersPreviousE :: EditorM ()
- withLMStack :: (PointedList AnyLayoutManager -> PointedList AnyLayoutManager) -> EditorM ()
- layoutManagerNextVariantE :: EditorM ()
- layoutManagerPreviousVariantE :: EditorM ()
- enlargeWinE :: EditorM ()
- shrinkWinE :: EditorM ()
- setDividerPosE :: DividerRef -> DividerPosition -> EditorM ()
- newTabE :: EditorM ()
- nextTabE :: EditorM ()
- previousTabE :: EditorM ()
- moveTab :: Maybe Int -> EditorM ()
- deleteTabE :: EditorM ()
- tryCloseE :: EditorM ()
- closeOtherE :: EditorM ()
- shiftOtherWindow :: MonadEditor m => m ()
- withOtherWindow :: MonadEditor m => m a -> m a
- acceptedInputs :: EditorM [String]
- onCloseBufferE :: BufferRef -> EditorM () -> EditorM ()
- addJumpHereE :: EditorM ()
- jumpBackE :: EditorM ()
- jumpForwardE :: EditorM ()
- modifyJumpListE :: (JumpList -> JumpList) -> EditorM ()
Documentation
The Editor state
Editor | |
|
EditorM | |
|
class (Monad m, MonadState Editor m) => MonadEditor m whereSource
liftEditor :: MonadEditor m => EditorM a -> m aSource
The initial state
pendingEventsA :: T Editor [Event]Source
maxStatusHeightA :: T Editor IntSource
refSupplyA :: T Editor IntSource
windows :: Editor -> PointedList WindowSource
askConfigVariableA :: (YiConfigVariable b, MonadEditor m) => m bSource
dynA :: YiVariable a => Accessor Editor aSource
:: 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.
insertBuffer :: FBuffer -> EditorM ()Source
forceFold1 :: Foldable t => t a -> t aSource
forceFoldTabs :: Foldable t => t Tab -> t TabSource
deleteBuffer :: BufferRef -> EditorM ()Source
Delete a buffer (and release resources associated with it).
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
printStatus :: Status -> EditorM ()Source
setStatus :: Status -> EditorM ()Source
Set the background status line
statusLine :: Editor -> [String]Source
statusLineInfo :: Editor -> StatusSource
setTmpStatus :: Int -> Status -> EditorM ()Source
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
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?
data TempBufferNameHint Source
Specifies the hint for the next temp buffer's name.
TempBufferNameHint | |
|
alternateBufferE :: Int -> EditorM ()Source
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.
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.
withWindowE :: Window -> BufferM a -> EditorM aSource
findWindowWith :: WindowRef -> Editor -> WindowSource
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.
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
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.
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.
addJumpHereE :: EditorM ()Source
jumpForwardE :: EditorM ()Source
modifyJumpListE :: (JumpList -> JumpList) -> EditorM ()Source