yi-core-0.19.2: Yi editor core library
LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • RankNTypes
  • ExplicitForAll

Yi.Config.Simple

Description

A simplified configuration interface for Yi.

This module provides a simple configuration API, allowing users to start with an initial configuration and imperatively (monadically) modify it. Some common actions (keybindings, selecting modes, choosing the frontend) have been given special commands (globalBindKeys, setFrontendPreferences, addMode, and so on).

A simple configuration might look like the following:

import Yi.Config.Simple
import Yi.Boot
import qualified Yi.Mode.Haskell as Haskell
-- note: don't import Yi, or else there will be name clashes

main = configMain defaultEmacsConfig $ do
  fontSize %= Just 10
  modeBindKeys Haskell.cleverMode (metaCh 'q' ?>>! reload)
  globalBindKeys (metaCh 'r' ?>>! reload)

A lot of the fields here are specified with the Field type. To write a field, use (%=). To read, use get. For modification, use (modify). For example, the functions foo and bar are equivalent:

foo = modify layoutManagers reverse
bar = do
 lms <- get layoutManagers
 layoutManagers %= reverse lms
Synopsis

The main interface

data ConfigM a Source #

The configuration monad. Run it with configMain.

Instances

Instances details
Monad ConfigM Source # 
Instance details

Defined in Yi.Config.Simple.Types

Methods

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

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

return :: a -> ConfigM a #

Functor ConfigM Source # 
Instance details

Defined in Yi.Config.Simple.Types

Methods

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

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

Applicative ConfigM Source # 
Instance details

Defined in Yi.Config.Simple.Types

Methods

pure :: a -> ConfigM a #

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

liftA2 :: (a -> b -> c) -> ConfigM a -> ConfigM b -> ConfigM c #

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

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

MonadState Config ConfigM Source # 
Instance details

Defined in Yi.Config.Simple.Types

Methods

get :: ConfigM Config #

put :: Config -> ConfigM () #

state :: (Config -> (a, Config)) -> ConfigM a #

MonadBase IO ConfigM Source # 
Instance details

Defined in Yi.Config.Simple.Types

Methods

liftBase :: IO α -> ConfigM α #

type Field a = Lens' Config a Source #

Fields that can be modified with all lens machinery.

Modes, commands, and keybindings

globalBindKeys :: Keymap -> ConfigM () Source #

Adds the given key bindings to the `global keymap'. The bindings will override existing bindings in the case of a clash.

modeBindKeys :: Mode syntax -> Keymap -> ConfigM () Source #

modeBindKeys mode keys adds the keybindings in keys to all modes with the same name as mode.

As with modifyMode, a mode by the given name must already be registered, or the function will have no effect, and issue a command-line warning.

modeBindKeysByName :: Text -> Keymap -> ConfigM () Source #

modeBindKeysByName name keys adds the keybindings in keys to all modes with name name (if it is registered). Consider using modeBindKeys instead.

addMode :: Mode syntax -> ConfigM () Source #

Register the given mode. It will be preferred over any modes already defined.

modifyMode :: Mode syntax -> (forall syntax'. Mode syntax' -> Mode syntax') -> ConfigM () Source #

modifyMode mode f modifies all modes with the same name as mode, using the function f.

Note that the mode argument is only used by its modeName. In particular, a mode by the given name must already be registered, or this function will have no effect, and issue a command-line warning.

modifyMode mode f = modifyModeByName (modeName mode) f

modifyModeByName :: Text -> (forall syntax. Mode syntax -> Mode syntax) -> ConfigM () Source #

modifyModeByName name f modifies the mode with name name using the function f. Consider using modifyMode instead.

Evaluation of commands

publishedActionsEvaluator :: Evaluator Source #

Evaluator based on a fixed list of published actions. Has a few differences from ghciEvaluator:

  • expressions can't be evaluated
  • all suggested actions are actually valued
  • (related to the above) doesn't contain junk actions from Prelude
  • doesn't require GHCi backend, so uses less memory

publishAction :: (YiAction a x, Show x) => String -> a -> ConfigM () Source #

Publish the given action, by the given name. This will overwrite any existing actions by the same name.

publishedActions :: Field (HashMap String Action) Source #

Accessor for the published actions. Consider using publishAction.

Appearance

fontName :: Field (Maybe String) Source #

Just the font name, or Nothing for default.

fontSize :: Field (Maybe Int) Source #

Just the font size, or Nothing for default.

scrollWheelAmount :: Field Int Source #

Amount to move the buffer when using the scroll wheel.

scrollStyle :: Field (Maybe ScrollStyle) Source #

Just the scroll style, or Nothing for default.

cursorStyle :: Field CursorStyle Source #

See CursorStyle for documentation.

data CursorStyle Source #

When should we use a "fat" cursor (i.e. 2 pixels wide, rather than 1)? Fat cursors have only been implemented for the Pango frontend.

data Side Source #

Constructors

LeftSide 
RightSide 

scrollBarSide :: Field Side Source #

Which side to display the scroll bar on.

autoHideScrollBar :: Field Bool Source #

Should the scroll bar autohide?

autoHideTabBar :: Field Bool Source #

Should the tab bar autohide?

lineWrap :: Field Bool Source #

Should lines be wrapped?

windowFill :: Field Char Source #

The character with which to fill empty window space. Usually '~' for vi-like editors, ' ' for everything else.

theme :: Field Theme Source #

UI colour theme.

lineNumbers :: Field Bool Source #

Line numbers.

Layout

layoutManagers :: Field [AnyLayoutManager] Source #

List of registered layout managers. When cycling through layouts, this list will be consulted.

Debugging

debug :: Field Bool Source #

Produce a .yi.dbg file with debugging information?

Startup hooks

runOnStartup :: Action -> ConfigM () Source #

Run when the editor is started (this is run after all actions which have already been registered)

runAfterStartup :: Action -> ConfigM () Source #

Run after the startup actions have completed, or on reload (this is run after all actions which have already been registered)

Advanced

These fields are here for completeness -- that is, to expose all the functionality of the Yi.Config module. However, most users probably need not use these fields, typically because they provide advanced functinality, or because a simpler interface for the common case is available above.

startActions :: Field [Action] Source #

Actions to run when the editor is started. Consider using runOnStartup or runManyOnStartup instead.

initialActions :: Field [Action] Source #

Actions to run after startup or reload. Consider using runAfterStartup or runManyAfterStartup instead.

defaultKm :: Field KeymapSet Source #

Default keymap to use.

modes :: Field [AnyMode] Source #

List of modes by order of preference. Consider using addMode, modeBindKeys, or modifyMode instead.

regionStyle :: Field RegionStyle Source #

Set to Exclusive for an emacs-like behaviour. Consider starting with defaultEmacsConfig, defaultVimConfig, or defaultCuaConfig to instead.

killringAccumulate :: Field Bool Source #

Set to True for an emacs-like behaviour, where all deleted text is accumulated in a killring. Consider starting with defaultEmacsConfig, defaultVimConfig, or defaultCuaConfig instead.

Module exports

data SearchExp #

Instances

Instances details
Binary SearchExp 
Instance details

Defined in Yi.Regex

includedRegion :: Region -> Region -> Bool #

Returns if a region (1st arg) is included in another (2nd arg)

nearRegion :: Point -> Region -> Bool #

True if the given point is inside the given region or at the end of it.

inRegion :: Point -> Region -> Bool #

True if the given point is inside the given region.

emptyRegion :: Region #

The empty region

mkRegion :: Point -> Point -> Region #

Construct a region from its bounds, emacs style: the right bound is excluded

unionRegion :: Region -> Region -> Region #

Take the union of two regions (including what is between them)

intersectRegion :: Region -> Region -> Region #

Take the intersection of two regions

data Region #

The region data type. The region is semi open: it includes the start but not the end bound. This allows simpler region-manipulation algorithms. Invariant : regionStart r <= regionEnd r

Instances

Instances details
Show Region 
Instance details

Defined in Yi.Region

Generic Region 
Instance details

Defined in Yi.Region

Associated Types

type Rep Region :: Type -> Type #

Methods

from :: Region -> Rep Region x #

to :: Rep Region x -> Region #

Binary Region 
Instance details

Defined in Yi.Region

Methods

put :: Region -> Put #

get :: Get Region #

putList :: [Region] -> Put #

type Rep Region 
Instance details

Defined in Yi.Region

type Rep Region = D1 ('MetaData "Region" "Yi.Region" "yi-language-0.19.0-IdyJrIEoDq11Qjn5TopPkH" 'False) (C1 ('MetaCons "Region" 'PrefixI 'True) (S1 ('MetaSel ('Just "regionDirection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Direction) :*: (S1 ('MetaSel ('Just "regionStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Point) :*: S1 ('MetaSel ('Just "regionEnd") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Point))))

directionElim :: Direction -> a -> a -> a #

direction is in the same style of maybe or either functions, It takes one argument per direction (backward, then forward) and a direction to select the output.

mayReverse :: Direction -> [a] -> [a] #

reverse if Backward

data Direction #

Direction of movement inside a buffer

Constructors

Backward 
Forward 

Instances

Instances details
Bounded Direction 
Instance details

Defined in Yi.Buffer.Basic

Enum Direction 
Instance details

Defined in Yi.Buffer.Basic

Eq Direction 
Instance details

Defined in Yi.Buffer.Basic

Ord Direction 
Instance details

Defined in Yi.Buffer.Basic

Show Direction 
Instance details

Defined in Yi.Buffer.Basic

Generic Direction 
Instance details

Defined in Yi.Buffer.Basic

Associated Types

type Rep Direction :: Type -> Type #

Binary Direction 
Instance details

Defined in Yi.Buffer.Basic

type Rep Direction 
Instance details

Defined in Yi.Buffer.Basic

type Rep Direction = D1 ('MetaData "Direction" "Yi.Buffer.Basic" "yi-language-0.19.0-IdyJrIEoDq11Qjn5TopPkH" 'False) (C1 ('MetaCons "Backward" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Forward" 'PrefixI 'False) (U1 :: Type -> Type))

newtype Mark #

A mark in a buffer

Constructors

Mark 

Fields

Instances

Instances details
Eq Mark 
Instance details

Defined in Yi.Buffer.Basic

Methods

(==) :: Mark -> Mark -> Bool #

(/=) :: Mark -> Mark -> Bool #

Ord Mark 
Instance details

Defined in Yi.Buffer.Basic

Methods

compare :: Mark -> Mark -> Ordering #

(<) :: Mark -> Mark -> Bool #

(<=) :: Mark -> Mark -> Bool #

(>) :: Mark -> Mark -> Bool #

(>=) :: Mark -> Mark -> Bool #

max :: Mark -> Mark -> Mark #

min :: Mark -> Mark -> Mark #

Show Mark 
Instance details

Defined in Yi.Buffer.Basic

Methods

showsPrec :: Int -> Mark -> ShowS #

show :: Mark -> String #

showList :: [Mark] -> ShowS #

Binary Mark 
Instance details

Defined in Yi.Buffer.Basic

Methods

put :: Mark -> Put #

get :: Get Mark #

putList :: [Mark] -> Put #

newtype BufferRef #

Reference to a buffer.

Constructors

BufferRef Int 

newtype Point #

A point in a buffer

Constructors

Point 

Fields

Instances

Instances details
Bounded Point 
Instance details

Defined in Yi.Buffer.Basic

Enum Point 
Instance details

Defined in Yi.Buffer.Basic

Eq Point 
Instance details

Defined in Yi.Buffer.Basic

Methods

(==) :: Point -> Point -> Bool #

(/=) :: Point -> Point -> Bool #

Integral Point 
Instance details

Defined in Yi.Buffer.Basic

Num Point 
Instance details

Defined in Yi.Buffer.Basic

Ord Point 
Instance details

Defined in Yi.Buffer.Basic

Methods

compare :: Point -> Point -> Ordering #

(<) :: Point -> Point -> Bool #

(<=) :: Point -> Point -> Bool #

(>) :: Point -> Point -> Bool #

(>=) :: Point -> Point -> Bool #

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Real Point 
Instance details

Defined in Yi.Buffer.Basic

Methods

toRational :: Point -> Rational #

Show Point 
Instance details

Defined in Yi.Buffer.Basic

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Ix Point 
Instance details

Defined in Yi.Buffer.Basic

Binary Point 
Instance details

Defined in Yi.Buffer.Basic

Methods

put :: Point -> Put #

get :: Get Point #

putList :: [Point] -> Put #

SemiNum Point Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

(+~) :: Point -> Size -> Point #

(-~) :: Point -> Size -> Point #

(~-) :: Point -> Point -> Size #

newtype Size #

Size of a buffer region

Constructors

Size 

Fields

Instances

Instances details
Enum Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

succ :: Size -> Size #

pred :: Size -> Size #

toEnum :: Int -> Size #

fromEnum :: Size -> Int #

enumFrom :: Size -> [Size] #

enumFromThen :: Size -> Size -> [Size] #

enumFromTo :: Size -> Size -> [Size] #

enumFromThenTo :: Size -> Size -> Size -> [Size] #

Eq Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Integral Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

quot :: Size -> Size -> Size #

rem :: Size -> Size -> Size #

div :: Size -> Size -> Size #

mod :: Size -> Size -> Size #

quotRem :: Size -> Size -> (Size, Size) #

divMod :: Size -> Size -> (Size, Size) #

toInteger :: Size -> Integer #

Num Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Real Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

toRational :: Size -> Rational #

Show Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

Binary Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

put :: Size -> Put #

get :: Get Size #

putList :: [Size] -> Put #

SemiNum Point Size 
Instance details

Defined in Yi.Buffer.Basic

Methods

(+~) :: Point -> Size -> Point #

(-~) :: Point -> Size -> Point #

(~-) :: Point -> Point -> Size #

newtype WindowRef #

Window references

Constructors

WindowRef 

Fields

Instances

Instances details
Enum WindowRef 
Instance details

Defined in Yi.Buffer.Basic

Eq WindowRef 
Instance details

Defined in Yi.Buffer.Basic

Ord WindowRef 
Instance details

Defined in Yi.Buffer.Basic

Show WindowRef 
Instance details

Defined in Yi.Buffer.Basic

Binary WindowRef 
Instance details

Defined in Yi.Buffer.Basic

Default WindowRef 
Instance details

Defined in Yi.Buffer.Basic

Methods

def :: WindowRef #

data MarkValue Source #

Constructors

MarkValue 

Instances

Instances details
Eq MarkValue Source # 
Instance details

Defined in Yi.Buffer.Implementation

Ord MarkValue Source # 
Instance details

Defined in Yi.Buffer.Implementation

Show MarkValue Source # 
Instance details

Defined in Yi.Buffer.Implementation

Generic MarkValue Source # 
Instance details

Defined in Yi.Buffer.Implementation

Associated Types

type Rep MarkValue :: Type -> Type #

Binary MarkValue Source # 
Instance details

Defined in Yi.Buffer.Implementation

type Rep MarkValue Source # 
Instance details

Defined in Yi.Buffer.Implementation

type Rep MarkValue = D1 ('MetaData "MarkValue" "Yi.Buffer.Implementation" "yi-core-0.19.2-E39Ao5fNBKQEmSrSHU3CM4" 'False) (C1 ('MetaCons "MarkValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "markPoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Point) :*: S1 ('MetaSel ('Just "markGravity") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Direction)))

data UIUpdate Source #

Instances

Instances details
Generic UIUpdate Source # 
Instance details

Defined in Yi.Buffer.Implementation

Associated Types

type Rep UIUpdate :: Type -> Type #

Methods

from :: UIUpdate -> Rep UIUpdate x #

to :: Rep UIUpdate x -> UIUpdate #

Binary UIUpdate Source # 
Instance details

Defined in Yi.Buffer.Implementation

Methods

put :: UIUpdate -> Put #

get :: Get UIUpdate #

putList :: [UIUpdate] -> Put #

type Rep UIUpdate Source # 
Instance details

Defined in Yi.Buffer.Implementation

type Rep UIUpdate = D1 ('MetaData "UIUpdate" "Yi.Buffer.Implementation" "yi-core-0.19.2-E39Ao5fNBKQEmSrSHU3CM4" 'False) (C1 ('MetaCons "TextUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Update)) :+: C1 ('MetaCons "StyleUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Point) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Size)))

data Update Source #

Mutation actions (also used the undo or redo list)

For the undoredo, we use the partial checkpoint/ (Berlage, pg16) strategy to store just the components of the state that change.

Note that the update direction is only a hint for moving the cursor (mainly for undo purposes); the insertions and deletions are always applied Forward.

Note that keeping the text does not cost much: we keep the updates in the undo list; if it's a Delete it means we have just inserted the text in the buffer, so the update shares the data with the buffer. If it's an Insert we have to keep the data any way.

Instances

Instances details
Show Update Source # 
Instance details

Defined in Yi.Buffer.Implementation

Generic Update Source # 
Instance details

Defined in Yi.Buffer.Implementation

Associated Types

type Rep Update :: Type -> Type #

Methods

from :: Update -> Rep Update x #

to :: Rep Update x -> Update #

Binary Update Source # 
Instance details

Defined in Yi.Buffer.Implementation

Methods

put :: Update -> Put #

get :: Get Update #

putList :: [Update] -> Put #

type Rep Update Source # 
Instance details

Defined in Yi.Buffer.Implementation

type Rep Update = D1 ('MetaData "Update" "Yi.Buffer.Implementation" "yi-core-0.19.2-E39Ao5fNBKQEmSrSHU3CM4" 'False) (C1 ('MetaCons "Insert" 'PrefixI 'True) (S1 ('MetaSel ('Just "updatePoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Point) :*: (S1 ('MetaSel ('Just "updateDirection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Direction) :*: S1 ('MetaSel ('Just "_insertUpdateString") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 YiString))) :+: C1 ('MetaCons "Delete" 'PrefixI 'True) (S1 ('MetaSel ('Just "updatePoint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Point) :*: (S1 ('MetaSel ('Just "updateDirection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Direction) :*: S1 ('MetaSel ('Just "_deleteUpdateString") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 YiString))))

data Overlay Source #

Instances

Instances details
Eq Overlay Source # 
Instance details

Defined in Yi.Buffer.Implementation

Methods

(==) :: Overlay -> Overlay -> Bool #

(/=) :: Overlay -> Overlay -> Bool #

Ord Overlay Source # 
Instance details

Defined in Yi.Buffer.Implementation

Show Overlay Source # 
Instance details

Defined in Yi.Buffer.Implementation

mkOverlay :: YiString -> Region -> StyleName -> YiString -> Overlay Source #

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

data URList Source #

A URList consists of an undo and a redo list.

Instances

Instances details
Show URList Source # 
Instance details

Defined in Yi.Buffer.Undo

Generic URList Source # 
Instance details

Defined in Yi.Buffer.Undo

Associated Types

type Rep URList :: Type -> Type #

Methods

from :: URList -> Rep URList x #

to :: Rep URList x -> URList #

Binary URList Source # 
Instance details

Defined in Yi.Buffer.Undo

Methods

put :: URList -> Put #

get :: Get URList #

putList :: [URList] -> Put #

type Rep URList Source # 
Instance details

Defined in Yi.Buffer.Undo

type Rep URList = D1 ('MetaData "URList" "Yi.Buffer.Undo" "yi-core-0.19.2-E39Ao5fNBKQEmSrSHU3CM4" 'False) (C1 ('MetaCons "URList" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Seq Change)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Seq Change))))

data Change Source #

Instances

Instances details
Show Change Source # 
Instance details

Defined in Yi.Buffer.Undo

Generic Change Source # 
Instance details

Defined in Yi.Buffer.Undo

Associated Types

type Rep Change :: Type -> Type #

Methods

from :: Change -> Rep Change x #

to :: Rep Change x -> Change #

Binary Change Source # 
Instance details

Defined in Yi.Buffer.Undo

Methods

put :: Change -> Put #

get :: Get Change #

putList :: [Change] -> Put #

type Rep Change Source # 
Instance details

Defined in Yi.Buffer.Undo

type Rep Change = D1 ('MetaData "Change" "Yi.Buffer.Undo" "yi-core-0.19.2-E39Ao5fNBKQEmSrSHU3CM4" 'False) (C1 ('MetaCons "SavedFilePoint" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "InteractivePoint" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AtomicChange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Update))))

emptyU :: URList Source #

A new empty URList. Notice we must have a saved file point as this is when we assume we are opening the file so it is currently the same as the one on disk

addChangeU :: Change -> URList -> URList Source #

Add an action to the undo list. According to the restricted, linear undo model, if we add a command whilst the redo list is not empty, we will lose our redoable changes.

setSavedFilePointU :: URList -> URList Source #

Add a saved file point so that we can tell that the buffer has not been modified since the previous saved file point. Notice that we must be sure to remove the previous saved file points since they are now worthless.

undoU :: Mark -> URList -> BufferImpl syntax -> (BufferImpl syntax, (URList, Seq Update)) Source #

This undoes one interaction step.

redoU :: Mark -> URList -> BufferImpl syntax -> (BufferImpl syntax, (URList, Seq Update)) Source #

This redoes one iteraction step.

isAtSavedFilePointU :: URList -> Bool Source #

undoIsAtSavedFilePoint. True if the undo list is at a SavedFilePoint indicating that the buffer has not been modified since we last saved the file. Note: that an empty undo list does NOT mean that the buffer is not modified since the last save. Because we may have saved the file and then undone actions done before the save.

data RegionStyle Source #

Instances

Instances details
Eq RegionStyle Source # 
Instance details

Defined in Yi.Types

Show RegionStyle Source # 
Instance details

Defined in Yi.Types

Binary RegionStyle Source # 
Instance details

Defined in Yi.Types

Default RegionStyle Source # 
Instance details

Defined in Yi.Types

Methods

def :: RegionStyle #

YiVariable RegionStyle Source # 
Instance details

Defined in Yi.Types

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

Instances details
Eq IndentBehaviour Source # 
Instance details

Defined in Yi.Types

Show IndentBehaviour Source # 
Instance details

Defined in Yi.Types

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

Instances

Instances details
Binary (Mode syntax) Source #

Just stores the mode name.

Instance details

Defined in Yi.Buffer.Misc

Methods

put :: Mode syntax -> Put #

get :: Get (Mode syntax) #

putList :: [Mode syntax] -> Put #

data AnyMode Source #

Constructors

forall syntax. AnyMode (Mode syntax) 

data BufferId Source #

Instances

Instances details
Eq BufferId Source # 
Instance details

Defined in Yi.Types

Ord BufferId Source # 
Instance details

Defined in Yi.Types

Show BufferId Source # 
Instance details

Defined in Yi.Types

Binary BufferId Source # 
Instance details

Defined in Yi.Types

Methods

put :: BufferId -> Put #

get :: Get BufferId #

putList :: [BufferId] -> Put #

data MarkSet a Source #

Constructors

MarkSet 

Fields

Instances

Instances details
Functor MarkSet Source # 
Instance details

Defined in Yi.Types

Methods

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

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

Foldable MarkSet Source # 
Instance details

Defined in Yi.Types

Methods

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

foldMap :: Monoid m => (a -> m) -> MarkSet a -> 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 # 
Instance details

Defined in Yi.Types

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 # 
Instance details

Defined in Yi.Types

Methods

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

show :: MarkSet a -> String #

showList :: [MarkSet a] -> ShowS #

Binary a => Binary (MarkSet a) Source # 
Instance details

Defined in Yi.Types

Methods

put :: MarkSet a -> Put #

get :: Get (MarkSet a) #

putList :: [MarkSet a] -> Put #

data FBuffer Source #

Constructors

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

Instances

Instances details
Eq FBuffer Source # 
Instance details

Defined in Yi.Types

Methods

(==) :: FBuffer -> FBuffer -> Bool #

(/=) :: FBuffer -> FBuffer -> Bool #

Show FBuffer Source # 
Instance details

Defined in Yi.Buffer.Misc

Binary FBuffer Source # 
Instance details

Defined in Yi.Buffer.Misc

Methods

put :: FBuffer -> Put #

get :: Get FBuffer #

putList :: [FBuffer] -> Put #

MonadState FBuffer BufferM Source # 
Instance details

Defined in Yi.Types

Methods

get :: BufferM FBuffer #

put :: FBuffer -> BufferM () #

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

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

Instances

Instances details
Eq IndentSettings Source # 
Instance details

Defined in Yi.Types

Show IndentSettings Source # 
Instance details

Defined in Yi.Types

newtype BufferM a Source #

The BufferM monad writes the updates performed.

Constructors

BufferM 

Instances

Instances details
Monad BufferM Source # 
Instance details

Defined in Yi.Types

Methods

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

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

return :: a -> BufferM a #

Functor BufferM Source # 
Instance details

Defined in Yi.Types

Methods

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

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

MonadFail BufferM Source # 
Instance details

Defined in Yi.Types

Methods

fail :: String -> BufferM a #

Applicative BufferM Source # 
Instance details

Defined in Yi.Types

Methods

pure :: a -> BufferM a #

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

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

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

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

MonadReader Window BufferM Source # 
Instance details

Defined in Yi.Types

Methods

ask :: BufferM Window #

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

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

MonadState FBuffer BufferM Source # 
Instance details

Defined in Yi.Types

Methods

get :: BufferM FBuffer #

put :: FBuffer -> BufferM () #

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

YiAction (BufferM x) x Source # 
Instance details

Defined in Yi.Keymap

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

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

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

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

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

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

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

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

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

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

pendingUpdatesA :: HasAttributes c => Lens' c (Seq UIUpdate) Source #

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

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

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"

clearSyntax :: FBuffer -> FBuffer Source #

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

increaseFontSize :: Int -> BufferM () Source #

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

decreaseFontSize :: Int -> BufferM () Source #

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

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

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

addOverlayB :: Overlay -> BufferM () Source #

Adds an "overlay" to the buffer

delOverlayB :: Overlay -> BufferM () Source #

Remove an existing "overlay"

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.

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.

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

Mode applies function that always returns True.

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

Mode applies function that always returns False.

newB :: BufferRef -> BufferId -> YiString -> FBuffer Source #

Create buffer named nm with contents s

sizeB :: BufferM Point Source #

Point of eof

pointB :: BufferM Point Source #

Extract the current point

moveTo :: Point -> BufferM () Source #

Move point in buffer to the given index

revertPendingUpdatesB :: BufferM () Source #

Revert all the pending updates; don't touch the 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.

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

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

insertN :: YiString -> BufferM () Source #

Insert the YiString at current point, extending size of 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.

deleteNAt :: Direction -> Int -> Point -> BufferM () Source #

deleteNAt n p deletes n characters forwards from position p

curLn :: BufferM Int Source #

Return the current line number

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

markLines :: BufferM (MarkSet Int) Source #

Return line numbers of marks

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)

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

setAnyMode :: AnyMode -> BufferM () Source #

Set the mode

setMode :: Mode syntax -> BufferM () Source #

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

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

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

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

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

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

setVisibleSelection :: Bool -> BufferM () Source #

Highlight the selection

getVisibleSelection :: BufferM Bool Source #

Whether the selection is highlighted

moveN :: Int -> BufferM () Source #

Move point by the given number of characters. A negative offset moves backwards a positive one forward.

leftB :: BufferM () Source #

Move point -1

leftN :: Int -> BufferM () Source #

Move cursor -n

rightB :: BufferM () Source #

Move cursor +1

rightN :: Int -> BufferM () Source #

Move cursor +n

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.

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)

lineUp :: BufferM () Source #

Move point up one line

lineDown :: BufferM () Source #

Move point down one line

elemsB :: BufferM YiString Source #

Return the contents of 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.

readB :: BufferM Char Source #

Read the character at the current point

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

deleteN :: Int -> BufferM () Source #

Delete n characters forward from the current point

indentSettingsB :: BufferM IndentSettings Source #

Gives the IndentSettings for the current buffer.

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

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.

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.

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

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

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.

destinationOfMoveB :: BufferM a -> BufferM Point Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

deleteRegionB :: Region -> BufferM () Source #

Delete an arbitrary part of the buffer

replaceRegionB :: Region -> YiString -> BufferM () Source #

Replace a region with a given rope.

mapRegionB :: Region -> (Char -> Char) -> BufferM () Source #

Map the given function over the characters in the region.

swapRegionsB :: Region -> Region -> BufferM () Source #

Swap the content of two Regions

modifyRegionB Source #

Arguments

:: (YiString -> YiString)

The string modification function

-> Region

The region to modify

-> BufferM () 

Modifies the given region according to the given string transformation function

inclusiveRegionB :: Region -> BufferM Region Source #

Extend the right bound of a region to include it.

blockifyRegion :: Region -> BufferM [Region] Source #

See a region as a block/rectangular region, since regions are represented by two point, this returns a list of small regions form this block region.

joinLinesB :: Region -> BufferM () Source #

Joins lines in the region with a single space, skipping any empty lines.

concatLinesB :: Region -> BufferM () Source #

Concatenates lines in the region preserving the trailing newline if any.

linesOfRegionB :: Region -> BufferM [Region] Source #

Gets the lines of a region (as a region), preserving newlines. Thus the resulting list of regions is a partition of the original region.

The direction of the region is preserved and all smaller regions will retain that direction.

Note that regions should never be empty, so it would be odd for this to return an empty list...

data BoundarySide Source #

Boundary side

Constructors

InsideBound 
OutsideBound 

Instances

Instances details
Eq BoundarySide Source # 
Instance details

Defined in Yi.Buffer.TextUnit

data TextUnit Source #

Designate a given "unit" of text.

Constructors

Character

a single character

Line

a line of text (between newlines)

VLine

a "vertical" line of text (area of text between two characters at the same column number)

Document

the whole document

GenUnit 

outsideUnit :: TextUnit -> TextUnit Source #

Turns a unit into its "negative" by inverting the boundaries. For example, outsideUnit unitViWord will be the unit of spaces between words. For units without boundaries (Character, Document, ...), this is the identity function.

unitWord :: TextUnit Source #

a word as in use in Emacs (fundamental mode)

unitDelimited :: Char -> Char -> Bool -> TextUnit Source #

delimited on the left and right by given characters, boolean argument tells if whether those are included.

isAnySep :: Char -> Bool Source #

Separator characters (space, tab, unicode separators). Most of the units above attempt to identify "words" with various punctuation and symbols included or excluded. This set of units is a simple inverse: it is true for "whitespace" or "separators" and false for anything that is not (letters, numbers, symbols, punctuation, whatever).

unitSep :: TextUnit Source #

unitSep is true for any kind of whitespace/separator

unitSepThisLine :: TextUnit Source #

unitSepThisLine is true for any kind of whitespace/separator on this line only

unitEmacsParagraph :: TextUnit Source #

Paragraph to implement emacs-like forward-paragraph/backward-paragraph

unitParagraph :: TextUnit Source #

Paragraph that begins and ends in the paragraph, not the empty lines surrounding it.

leftBoundaryUnit :: TextUnit -> TextUnit Source #

Unit that have its left and right boundaries at the left boundary of the argument unit.

genAtBoundaryB :: TextUnit -> Direction -> BoundarySide -> BufferM Bool Source #

genAtBoundaryB u d s returns whether the point is at a given boundary (d,s) . Boundary (d,s) , taking Word as example, means: Word ^^ ^^ 12 34 1: (Backward,OutsideBound) 2: (Backward,InsideBound) 3: (Forward,InsideBound) 4: (Forward,OutsideBound)

rules: genAtBoundaryB u Backward InsideBound = atBoundaryB u Backward genAtBoundaryB u Forward OutsideBound = atBoundaryB u Forward

untilB :: BufferM Bool -> BufferM a -> BufferM [a] Source #

Repeat an action until the condition is fulfilled or the cursor stops moving. The Action may be performed zero times.

doIfCharB :: (Char -> Bool) -> BufferM a -> BufferM () Source #

Do an action if the current buffer character passes the predicate

genMoveB :: TextUnit -> (Direction, BoundarySide) -> Direction -> BufferM () Source #

Generic move operation Warning: moving To the (OutsideBound, Backward) bound of Document is impossible (offset -1!) genMoveB u b d: move in direction d until encountering boundary b or unit u. See genAtBoundaryB for boundary explanation.

genMaybeMoveB :: TextUnit -> (Direction, BoundarySide) -> Direction -> BufferM () Source #

Generic maybe move operation. As genMoveB, but don't move if we are at boundary already.

moveB :: TextUnit -> Direction -> BufferM () Source #

Move to the next unit boundary

maybeMoveB :: TextUnit -> Direction -> BufferM () Source #

As moveB, unless the point is at a unit boundary

transformB :: (YiString -> YiString) -> TextUnit -> Direction -> BufferM () Source #

Transforms the region given by TextUnit in the Direction with user-supplied function.

deleteB :: TextUnit -> Direction -> BufferM () Source #

Delete between point and next unit boundary, return the deleted region.

regionOfB :: TextUnit -> BufferM Region Source #

Region of the whole textunit where the current point is.

regionOfNonEmptyB :: TextUnit -> BufferM Region Source #

Non empty region of the whole textunit where the current point is.

regionOfPartB :: TextUnit -> Direction -> BufferM Region Source #

Region between the point and the next boundary. The region is empty if the point is at the boundary.

regionOfPartNonEmptyB :: TextUnit -> Direction -> BufferM Region Source #

Non empty region between the point and the next boundary, In fact the region can be empty if we are at the end of file.

regionOfPartNonEmptyAtB :: TextUnit -> Direction -> Point -> BufferM Region Source #

Non empty region at given point and the next boundary,

extendRegionToBoundaries :: TextUnit -> BoundarySide -> BoundarySide -> Region -> BufferM Region Source #

Extend the given region to boundaries of the text unit. For instance one can extend the selection to complete lines, or paragraphs.

moveToMTB :: BufferM () Source #

Move point between the middle, top and bottom of the screen If the point stays at the middle, it'll be gone to the top else if the point stays at the top, it'll be gone to the bottom else it'll be gone to the middle

moveToSol :: BufferM () Source #

Move point to start of line

moveToEol :: BufferM () Source #

Move point to end of line

topB :: BufferM () Source #

Move cursor to origin

botB :: BufferM () Source #

Move cursor to end of buffer

leftOnEol :: BufferM () Source #

Move left if on eol, but not on blank line

moveXorSol :: Int -> BufferM () Source #

Move x chars back, or to the sol, whichever is less

moveXorEol :: Int -> BufferM () Source #

Move x chars forward, or to the eol, whichever is less

nextWordB :: BufferM () Source #

Move to first char of next word forwards

prevWordB :: BufferM () Source #

Move to first char of next word backwards

nextCInc :: Char -> BufferM () Source #

Move to the next occurence of c

nextCExc :: Char -> BufferM () Source #

Move to the character before the next occurence of c

prevCInc :: Char -> BufferM () Source #

Move to the previous occurence of c

prevCExc :: Char -> BufferM () Source #

Move to the character after the previous occurence of c

firstNonSpaceB :: BufferM () Source #

Move to first non-space character in this line

lastNonSpaceB :: BufferM () Source #

Move to the last non-space character in this line

moveNonspaceOrSol :: BufferM () Source #

Go to the first non space character in the line; if already there, then go to the beginning of the line.

isCurrentLineEmptyB :: BufferM Bool Source #

True if current line consists of just a newline (no whitespace)

isCurrentLineAllWhiteSpaceB :: BufferM Bool Source #

Note: Returns False if line doesn't have any characters besides a newline

nextNParagraphs :: Int -> BufferM () Source #

Move down next n paragraphs

prevNParagraphs :: Int -> BufferM () Source #

Move up prev n paragraphs

selectNParagraphs :: Int -> BufferM () Source #

Select next n paragraphs

atSol :: BufferM Bool Source #

Return true if the current point is the start of a line

atEol :: BufferM Bool Source #

Return true if the current point is the end of a line

atSof :: BufferM Bool Source #

True if point at start of file

atEof :: BufferM Bool Source #

True if point at end of file

atLastLine :: BufferM Bool Source #

True if point at the last line

getLineAndCol :: BufferM (Int, Int) Source #

Get the current line and column number

readLnB :: BufferM YiString Source #

Read the line the point is on

readCurrentWordB :: BufferM YiString Source #

Reads in word at point.

readPrevWordB :: BufferM YiString Source #

Reads in word before point.

bdeleteB :: BufferM () Source #

Delete one character backward

killWordB :: BufferM () Source #

Delete forward whitespace or non-whitespace depending on the character under point.

bkillWordB :: BufferM () Source #

Delete backward whitespace or non-whitespace depending on the character before point.

bdeleteLineB :: BufferM () Source #

Delete backward to the sof or the new line character

deleteHorizontalSpaceB :: Maybe Int -> BufferM () Source #

emacs' delete-horizontal-space with the optional argument.

uppercaseWordB :: BufferM () Source #

capitalise the word under the cursor

lowercaseWordB :: BufferM () Source #

lowerise word under the cursor

capitaliseWordB :: BufferM () Source #

capitalise the first letter of this word

deleteToEol :: BufferM () Source #

Delete to the end of line, excluding it.

swapB :: BufferM () Source #

Transpose two characters, (the Emacs C-t action)

deleteTrailingSpaceB :: BufferM () Source #

Delete trailing whitespace from all lines. Uses savingPositionB to get back to where it was.

setSelectionMarkPointB :: Point -> BufferM () Source #

Marks

Set the current buffer selection mark

getSelectionMarkPointB :: BufferM Point Source #

Get the current buffer selection mark

exchangePointAndMarkB :: BufferM () Source #

Exchange point & mark.

bufInfoB :: BufferM BufferFileInfo Source #

File info, size in chars, line no, col num, char num, percent

upScreenB :: BufferM () Source #

Scroll up 1 screen

downScreenB :: BufferM () Source #

Scroll down 1 screen

scrollScreensB :: Int -> BufferM () Source #

Scroll by n screens (negative for up)

vimScrollB :: Int -> BufferM () Source #

Same as scrollB, but also moves the cursor

vimScrollByB :: (Int -> Int) -> Int -> BufferM () Source #

Same as scrollByB, but also moves the cursor

scrollToCursorB :: BufferM () Source #

Move to middle line in screen

scrollCursorToTopB :: BufferM () Source #

Move cursor to the top of the screen

scrollCursorToBottomB :: BufferM () Source #

Move cursor to the bottom of the screen

scrollB :: Int -> BufferM () Source #

Scroll by n lines.

snapInsB :: BufferM () Source #

Move the point to inside the viewable region

snapScreenB :: Maybe ScrollStyle -> BufferM Bool Source #

Move the visible region to include the point

downFromTosB :: Int -> BufferM () Source #

Move to n lines down from top of screen

upFromBosB :: Int -> BufferM () Source #

Move to n lines up from the bottom of the screen

middleB :: BufferM () Source #

Move to middle line in screen

getRawestSelectRegionB :: BufferM Region Source #

Return the region between point and mark

getSelectRegionB :: BufferM Region Source #

Get the current region boundaries. Extended to the current selection unit.

setSelectRegionB :: Region -> BufferM () Source #

Select the given region: set the selection mark at the regionStart and the current point at the regionEnd.

lineStreamB :: Direction -> BufferM [YiString] Source #

Get a (lazy) stream of lines in the buffer, starting at the next line in the given direction.

getNextLineB :: Direction -> BufferM YiString Source #

The same as getMaybeNextLineB but avoids the use of the Maybe type in the return by returning the empty string if there is no next line.

getNextNonBlankLineB :: Direction -> BufferM YiString Source #

Returns the closest line to the current line which is non-blank, in the given direction. Returns the empty string if there is no such line (for example if we are on the top line already).

linePrefixSelectionB Source #

Arguments

:: YiString

The string that starts a line comment

-> BufferM () 

Prefix each line in the selection using the given string.

unLineCommentSelectionB Source #

Arguments

:: YiString

The string which begins a line comment

-> YiString

A potentially shorter string that begins a comment

-> BufferM () 

Uncomments the selection using the given line comment starting string. This only works for the comments which begin at the start of the line.

toggleCommentB :: YiString -> BufferM () Source #

Just like toggleCommentSelectionB but automatically inserts a whitespace suffix to the inserted comment string. In fact:

replaceBufferContent :: YiString -> BufferM () Source #

Replace the contents of the buffer with some string

sortLines :: BufferM () Source #

Sort the lines of the region.

revertB :: YiString -> UTCTime -> BufferM () Source #

Helper function: revert the buffer contents to its on-disk version

incrementNextNumberByB :: Int -> BufferM () Source #

Increase (or decrease if negative) next number on line by n.

isNumberB :: BufferM Bool Source #

Is character under cursor a number.

test3CharB :: BufferM Bool Source #

Used by isNumber to test if current character under cursor is a number.

testHexB :: BufferM Bool Source #

Characters [a..f] are part of a hex number only if preceded by 0x. Test if the current occurence of [a..f] is part of a hex number.

lineMoveVisRel :: Int -> BufferM () Source #

Move point down by n lines If line extends past width of window, count moving a single line as moving width points to the right.

markWord :: BufferM () Source #

Implements the same logic that emacs' `mark-word` does. Checks the mark point and moves it forth (or backward) for one word.

tabB :: BufferM String Source #

Return either a t or the number of spaces specified by tabSize in the IndentSettings. Note that if you actually want to insert a tab character (for example when editing makefiles) then you should use: insertB 't'.

autoIndentB :: IndentBehaviour -> BufferM () Source #

A specialisation of autoIndentHelperB. This is the most basic and the user is encouraged to specialise autoIndentHelperB on their own.

cycleIndentsB :: IndentBehaviour -> [Int] -> BufferM () Source #

Cycles through the indentation hints. It does this without requiring to set/get any state. We just look at the current indentation of the current line and moving to the largest indent that is

indentOfB :: YiString -> BufferM Int Source #

Returns the indentation of a given string. Note that this depends on the current indentation settings.

indentToB :: Int -> BufferM () Source #

Indents the current line to the given indentation level. In addition moves the point according to where it was on the line originally. If we were somewhere within the indentation (ie at the start of the line or on an empty line) then we want to just go to the end of the (new) indentation. However if we are currently pointing somewhere within the text of the line then we wish to remain pointing to the same character.

modifyIndentB :: (Int -> Int) -> BufferM () Source #

Modifies current line indent measured in visible spaces. Respects indent settings. Calling this with value (+ 4) will turn "t" into "tt" if shiftwidth is 4 and into "t " if shiftwidth is 8 If current line is empty nothing happens.

indentAsPreviousB :: BufferM () Source #

Indent as much as the previous line

indentAsNextB :: BufferM () Source #

Indent as much as the next line

newlineAndIndentB :: BufferM () Source #

Insert a newline at point and indent the new line as the previous one.

shiftIndentOfRegionB :: Int -> Region -> BufferM () Source #

Increases the indentation on the region by the given amount of shiftWidth

indentOfCurrentPosB :: BufferM Int Source #

Return the number of spaces at the beginning of the line, up to the point.

module Yi.Core

module Yi.Dired

module Yi.Editor

module Yi.File

data Config Source #

Configuration record. All Yi hooks can be set here.

Instances

Instances details
MonadReader Config EditorM Source # 
Instance details

Defined in Yi.Types

Methods

ask :: EditorM Config #

local :: (Config -> Config) -> EditorM a -> EditorM a #

reader :: (Config -> a) -> EditorM a #

MonadState Config ConfigM Source # 
Instance details

Defined in Yi.Config.Simple.Types

Methods

get :: ConfigM Config #

put :: Config -> ConfigM () #

state :: (Config -> (a, Config)) -> ConfigM a #

data CursorStyle Source #

When should we use a "fat" cursor (i.e. 2 pixels wide, rather than 1)? Fat cursors have only been implemented for the Pango frontend.

module Yi.Keymap

module Yi.Layout

module Yi.Search

module Yi.Style

module Yi.Misc