yi-core-0.14.0: Yi editor core library

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • RankNTypes
  • ExplicitForAll

Yi.Config.Simple

Contents

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

Monad ConfigM Source # 

Methods

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

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

return :: a -> ConfigM a #

fail :: String -> ConfigM a #

Functor ConfigM Source # 

Methods

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

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

Applicative ConfigM Source # 

Methods

pure :: a -> ConfigM a #

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

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

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

MonadState Config ConfigM Source # 

Methods

get :: ConfigM Config #

put :: Config -> ConfigM () #

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

MonadBase IO ConfigM Source # 

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.

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

module Yi.Buffer

module Yi.Core

module Yi.Dired

module Yi.Editor

module Yi.File

module Yi.Config

module Yi.Keymap

module Yi.Layout

module Yi.Search

module Yi.Style

module Yi.Misc