yi-core-0.15.0: Yi editor core library

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • TemplateHaskell
  • TemplateHaskellQuotes
  • ScopedTypeVariables
  • BangPatterns
  • OverloadedStrings
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • FlexibleContexts
  • ExistentialQuantification
  • GeneralizedNewtypeDeriving
  • TupleSections
  • RankNTypes
  • ExplicitForAll
  • LambdaCase

Yi.Buffer.Misc

Contents

Description

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

Synopsis

Documentation

data FBuffer Source #

Constructors

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

newtype BufferM a Source #

The BufferM monad writes the updates performed.

Constructors

BufferM 

Instances

Monad BufferM Source # 

Methods

(>>=) :: BufferM a -> (a -> BufferM b) -> BufferM b #

(>>) :: BufferM a -> BufferM b -> BufferM b #

return :: a -> BufferM a #

fail :: String -> BufferM a #

Functor BufferM Source # 

Methods

fmap :: (a -> b) -> BufferM a -> BufferM b #

(<$) :: a -> BufferM b -> BufferM a #

Applicative BufferM Source # 

Methods

pure :: a -> BufferM a #

(<*>) :: BufferM (a -> b) -> BufferM a -> BufferM b #

(*>) :: BufferM a -> BufferM b -> BufferM b #

(<*) :: BufferM a -> BufferM b -> BufferM a #

MonadReader Window BufferM Source # 

Methods

ask :: BufferM Window #

local :: (Window -> Window) -> BufferM a -> BufferM a #

reader :: (Window -> a) -> BufferM a #

MonadState FBuffer BufferM Source # 

Methods

get :: BufferM FBuffer #

put :: FBuffer -> BufferM () #

state :: (FBuffer -> (a, FBuffer)) -> BufferM a #

YiAction (BufferM x) x Source # 

data MarkSet a Source #

Constructors

MarkSet 

Fields

Instances

Functor MarkSet Source # 

Methods

fmap :: (a -> b) -> MarkSet a -> MarkSet b #

(<$) :: a -> MarkSet b -> MarkSet a #

Foldable MarkSet Source # 

Methods

fold :: Monoid m => MarkSet m -> m #

foldMap :: Monoid m => (a -> m) -> MarkSet a -> m #

foldr :: (a -> b -> b) -> b -> MarkSet a -> b #

foldr' :: (a -> b -> b) -> b -> MarkSet a -> b #

foldl :: (b -> a -> b) -> b -> MarkSet a -> b #

foldl' :: (b -> a -> b) -> b -> MarkSet a -> b #

foldr1 :: (a -> a -> a) -> MarkSet a -> a #

foldl1 :: (a -> a -> a) -> MarkSet a -> a #

toList :: MarkSet a -> [a] #

null :: MarkSet a -> Bool #

length :: MarkSet a -> Int #

elem :: Eq a => a -> MarkSet a -> Bool #

maximum :: Ord a => MarkSet a -> a #

minimum :: Ord a => MarkSet a -> a #

sum :: Num a => MarkSet a -> a #

product :: Num a => MarkSet a -> a #

Traversable MarkSet Source # 

Methods

traverse :: Applicative f => (a -> f b) -> MarkSet a -> f (MarkSet b) #

sequenceA :: Applicative f => MarkSet (f a) -> f (MarkSet a) #

mapM :: Monad m => (a -> m b) -> MarkSet a -> m (MarkSet b) #

sequence :: Monad m => MarkSet (m a) -> m (MarkSet a) #

Show a => Show (MarkSet a) Source # 

Methods

showsPrec :: Int -> MarkSet a -> ShowS #

show :: MarkSet a -> String #

showList :: [MarkSet a] -> ShowS #

Binary a => Binary (MarkSet a) Source # 

Methods

put :: MarkSet a -> Put #

get :: Get (MarkSet a) #

putList :: [MarkSet a] -> Put #

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.

screenTopLn :: BufferM Int Source #

Top line of the screen

screenMidLn :: BufferM Int Source #

Middle line of the screen

screenBotLn :: BufferM Int Source #

Bottom line of the screen

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

eolPointB :: Point -> BufferM Point Source #

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

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

Create buffer named nm with contents s

mkOverlay :: YiString -> Region -> StyleName -> YiString -> 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 :: 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 Char Source #

Read the character at the current point

elemsB :: BufferM YiString Source #

Return the contents of the buffer.

undosA :: HasAttributes c => Lens' c URList Source #

getVisibleSelection :: BufferM Bool Source #

Whether the selection is highlighted

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

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

movingToPrefVisCol :: BufferM a -> BufferM a Source #

Moves to a visual column within the current line as shown on the editor (ie, moving within the current width of a single visual line)

preferColA :: HasAttributes c => Lens' c (Maybe Int) Source #

markSavedB :: UTCTime -> BufferM () Source #

Mark the current point in the undo list as a saved state.

retroactivelyAtSavePointB :: BufferM a -> BufferM a Source #

Undo all updates that happened since last save, perform a given action and redo all updates again. Given action must not modify undo history.

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.

savingPositionB :: BufferM a -> BufferM a Source #

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 (Seq UIUpdate) Source #

readOnlyA :: HasAttributes c => Lens' c Bool Source #

insertingA :: HasAttributes c => Lens' c Bool Source #

pointFollowsWindowA :: HasAttributes c => Lens' c (Set WindowRef) Source #

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

modeNameA :: forall syntax. Lens' (Mode syntax) Text Source #

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 #

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 #

modeGotoDeclarationA :: forall syntax. Lens' (Mode syntax) (BufferM ()) Source #

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

data AnyMode Source #

Constructors

AnyMode (Mode syntax) 

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

modeAlwaysApplies :: a -> b -> Bool Source #

Mode applies function that always returns True.

modeNeverApplies :: a -> b -> 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 #

keymapProcessA :: HasAttributes c => Lens' c KeymapProcess Source #

data SearchExp :: * #

Instances

lastActiveWindowA :: HasAttributes c => Lens' c Window Source #

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 :: forall m a. (Default a, YiVariable a, MonadState FBuffer m, Functor m) => m a Source #

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

value <- getBufferDyn

shortIdentString Source #

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 number of path components.

>>> let memBuf = newB (BufferRef 0) (MemBuffer "foo/bar/hello") ""
>>> shortIdentString 2 memBuf
"*foo/bar/hello*"
>>> let fileBuf = newB (BufferRef 0) (FileBuffer "foo/bar/hello") ""
>>> shortIdentString 2 fileBuf
"hello"

identString :: FBuffer -> Text Source #

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

>>> let memBuf = newB (BufferRef 0) (MemBuffer "foo/bar/hello") ""
>>> identString memBuf
"*foo/bar/hello*"
>>> let fileBuf = newB (BufferRef 0) (FileBuffer "foo/bar/hello") ""
>>> identString fileBuf
"foo/bar/hello"

identA :: HasAttributes c => Lens' c BufferId Source #

directoryContentA :: HasAttributes c => Lens' c Bool Source #

lastSyncTimeA :: HasAttributes c => Lens' c UTCTime Source #

destinationOfMoveB :: BufferM a -> BufferM Point Source #

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

betweenB Source #

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 IndentSettings Source #

Gives the IndentSettings for the current buffer.

fontsizeVariationA :: HasAttributes c => Lens' c Int Source #

stickyEolA :: HasAttributes c => Lens' c Bool Source #

queryBuffer :: (forall syntax. BufferImpl syntax -> x) -> BufferM x Source #

Orphan instances

Show FBuffer Source # 
Binary FBuffer Source # 

Methods

put :: FBuffer -> Put #

get :: Get FBuffer #

putList :: [FBuffer] -> Put #

Binary (Mode syntax) Source #

Just stores the mode name.

Methods

put :: Mode syntax -> Put #

get :: Get (Mode syntax) #

putList :: [Mode syntax] -> Put #