yi-0.10.1: The Haskell-Scriptable Editor

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • TemplateHaskell
  • ScopedTypeVariables
  • StandaloneDeriving
  • DeriveDataTypeable
  • DeriveFunctor
  • DeriveTraversable
  • DeriveFoldable
  • FlexibleContexts
  • MultiParamTypeClasses
  • FunctionalDependencies
  • ExistentialQuantification
  • GeneralizedNewtypeDeriving
  • ExplicitForAll
  • NondecreasingIndentation
  • LambdaCase

Yi.Types

Description

This module is the host of the most prevalent types throughout Yi. It is unfortunately a necessary evil to avoid use of bootfiles.

You're encouraged to import from more idiomatic modules which will re-export these where appropriate.

Synopsis

Documentation

data Action Source

Constructors

forall a . Show a => YiA (YiM a) 
forall a . Show a => EditorA (EditorM a) 
forall a . Show a => BufferA (BufferM a) 

class (Default a, Binary a, Typeable a) => YiVariable a Source

Instances

type Interact ev a = I ev Action a Source

data Yi Source

Constructors

Yi 

Fields

yiUi :: UI Editor
 
yiInput :: [Event] -> IO ()

input stream

yiOutput :: IsRefreshNeeded -> [Action] -> IO ()

output stream

yiConfig :: Config
 
yiVar :: MVar YiVar

The only mutable state in the program

Instances

newtype YiM a Source

The type of user-bindable functions TODO: doc how these are actually user-bindable are they?

Constructors

YiM 

Fields

runYiM :: ReaderT Yi IO a
 

data KeymapSet Source

Constructors

KeymapSet 

Fields

topKeymap :: Keymap

Content of the top-level loop.

insertKeymap :: Keymap

For insertion-only modes

newtype BufferM a Source

The BufferM monad writes the updates performed.

Constructors

BufferM 

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

expandTabs :: Bool

Insert spaces instead of tabs as possible

tabSize :: Int

Size of a Tab

shiftWidth :: Int

Indent by so many columns

data FBuffer Source

Constructors

forall syntax . FBuffer 

Fields

bmode :: !(Mode syntax)
 
rawbuf :: !(BufferImpl syntax)
 
attributes :: !Attributes
 

data MarkSet a Source

Constructors

MarkSet 

Fields

fromMark :: !a
 
insMark :: !a
 
selMark :: !a
 

data Attributes Source

Constructors

Attributes 

Fields

ident :: !BufferId
 
bkey__ :: !BufferRef

immutable unique key

undos :: !URList

undo/redo list

bufferDynamic :: !DynamicState

dynamic components

preferCol :: !(Maybe Int)

prefered column to arrive at when we do a lineDown / lineUp

pendingUpdates :: ![UIUpdate]

updates that haven't been synched in the UI yet

selectionStyle :: !SelectionStyle
 
keymapProcess :: !KeymapProcess
 
winMarks :: !(Map WindowRef WinMarks)
 
lastActiveWindow :: !Window
 
lastSyncTime :: !UTCTime

time of the last synchronization with disk

readOnly :: !Bool

read-only flag

inserting :: !Bool

the keymap is ready for insertion into this buffer

directoryContent :: !Bool

does buffer contain directory contents

pointFollowsWindow :: !(WindowRef -> Bool)
 
updateTransactionInFlight :: !Bool
 
updateTransactionAccum :: ![Update]
 
fontsizeVariation :: !Int

How many points (frontend-specific) to change the font by in this buffer

data AnyMode Source

Constructors

forall syntax . AnyMode (Mode syntax) 

Instances

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

modeName :: Text

so this can be serialized, debugged.

modeApplies :: FilePath -> YiString -> Bool

What type of files does this mode apply to?

modeHL :: ExtHL syntax

Syntax highlighter

modePrettify :: syntax -> BufferM ()

Prettify current "paragraph"

modeKeymap :: KeymapSet -> KeymapSet

Buffer-local keymap modification

modeIndent :: syntax -> IndentBehaviour -> BufferM ()

emacs-style auto-indent line

modeAdjustBlock :: syntax -> Int -> BufferM ()

adjust the indentation after modification

modeFollow :: syntax -> Action

Follow a "link" in the file. (eg. go to location of error message)

modeIndentSettings :: IndentSettings
 
modeToggleCommentSelection :: Maybe (BufferM ())
 
modeGetStrokes :: syntax -> Point -> Point -> Point -> [Stroke]

Strokes that should be applied when displaying a syntax element should this be an Action instead?

modeOnLoad :: BufferM ()

An action that is to be executed when this mode is set

modeModeLine :: [Text] -> BufferM Text

buffer-local modeline formatting method

modeGotoDeclaration :: BufferM ()

go to the point where the variable is declared

Instances

Binary (Mode syntax)

Just stores the mode name.

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.

type Statuses = DelayList Status Source

data Editor Source

The Editor state

Constructors

Editor 

Fields

bufferStack :: !(NonEmpty BufferRef)

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

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

Supply for buffer, window and tab ids.

tabs_ :: !(PointedList Tab)

current tab contains the visible windows pointed list.

dynamic :: !DynamicState

dynamic components

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

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

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

Processed events that didn't yield any action yet.

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

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

class (Monad m, MonadState Editor m) => MonadEditor m where Source

Minimal complete definition

askCfg

data UIConfig Source

Constructors

UIConfig 

Fields

configVty :: Config
 
configFontName :: Maybe String

Font name, for the UI that support it.

configFontSize :: Maybe Int

Font size, for the UI that support it.

configScrollStyle :: Maybe ScrollStyle

Style of scroll

configScrollWheelAmount :: Int

Amount to move the buffer when using the scroll wheel

configLeftSideScrollBar :: Bool

Should the scrollbar be shown on the left side?

configAutoHideScrollBar :: Bool

Hide scrollbar automatically if text fits on one page.

configAutoHideTabBar :: Bool

Hide the tabbar automatically if only one tab is present

configLineWrap :: Bool

Wrap lines at the edge of the window if too long to display.

configCursorStyle :: CursorStyle
 
configWindowFill :: Char

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

configTheme :: Theme

UI colours

type UIBoot = Config -> ([Event] -> IO ()) -> ([Action] -> IO ()) -> Editor -> IO (UI Editor) Source

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 Config Source

Configuration record. All Yi hooks can be set here.

Constructors

Config 

Fields

startFrontEnd :: UIBoot

UI to use.

configUI :: UIConfig

UI-specific configuration.

startActions :: [Action]

Actions to run when the editor is started.

initialActions :: [Action]

Actions to run after startup (after startActions) or reload.

defaultKm :: KeymapSet

Default keymap to use.

configInputPreprocess :: P Event Event
 
modeTable :: [AnyMode]

List modes by order of preference.

debugMode :: Bool

Produce a .yi.dbg file with a lot of debug information.

configRegionStyle :: RegionStyle

Set to Exclusive for an emacs-like behaviour.

configKillringAccumulate :: Bool

Set to True for an emacs-like behaviour, where all deleted text is accumulated in a killring.

configCheckExternalChangesObsessively :: Bool
 
bufferUpdateHandler :: [[Update] -> BufferM ()]
 
layoutManagers :: [AnyLayoutManager]

List of layout managers for cycleLayoutManagersNext

configVars :: DynamicState

Custom configuration, containing the YiConfigVariables. Configure with configVariableA.