yi-core-0.19.2: Yi editor core library
LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • TemplateHaskell
  • TemplateHaskellQuotes
  • StandaloneDeriving
  • DeriveDataTypeable
  • TypeSynonymInstances
  • FlexibleContexts
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • FunctionalDependencies
  • ExistentialQuantification
  • GeneralizedNewtypeDeriving
  • RankNTypes
  • ExplicitForAll

Yi.Keymap

Contents

Description

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) 

Instances

Instances details
Eq Action Source # 
Instance details

Defined in Yi.Types

Methods

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

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

Show Action Source # 
Instance details

Defined in Yi.Types

YiAction Action () Source # 
Instance details

Defined in Yi.Keymap

type Interact ev a = I ev Action a Source #

data KeymapSet Source #

Constructors

KeymapSet 

Fields

newtype YiM a Source #

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

Constructors

YiM 

Fields

Instances

Instances details
Monad YiM Source # 
Instance details

Defined in Yi.Types

Methods

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

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

return :: a -> YiM a #

Functor YiM Source # 
Instance details

Defined in Yi.Types

Methods

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

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

MonadFail YiM Source # 
Instance details

Defined in Yi.Types

Methods

fail :: String -> YiM a #

Applicative YiM Source # 
Instance details

Defined in Yi.Types

Methods

pure :: a -> YiM a #

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

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

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

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

MonadEditor YiM Source # 
Instance details

Defined in Yi.Types

MonadReader Yi YiM Source # 
Instance details

Defined in Yi.Types

Methods

ask :: YiM Yi #

local :: (Yi -> Yi) -> YiM a -> YiM a #

reader :: (Yi -> a) -> YiM a #

MonadState Editor YiM Source # 
Instance details

Defined in Yi.Types

Methods

get :: YiM Editor #

put :: Editor -> YiM () #

state :: (Editor -> (a, Editor)) -> YiM a #

MonadBase IO YiM Source # 
Instance details

Defined in Yi.Types

Methods

liftBase :: IO α -> YiM α #

HookType (YiM a) Source # 
Instance details

Defined in Yi.Hooks

Methods

runHookImpl :: YiConfigVariable var => (var -> YiM a) -> YiM a

YiAction (YiM x) x Source # 
Instance details

Defined in Yi.Keymap

Methods

makeAction :: YiM x -> Action Source #

withUI :: (UI Editor -> IO a) -> YiM a Source #

readEditor :: MonadEditor m => (Editor -> a) -> m a Source #

catchDynE :: Exception exception => YiM a -> (exception -> YiM a) -> YiM a Source #

catchJustE Source #

Arguments

:: Exception e 
=> (e -> Maybe b)

Predicate to select exceptions

-> YiM a

Computation to run

-> (b -> YiM a)

Handler

-> YiM a 

handleJustE :: Exception e => (e -> Maybe b) -> (b -> YiM a) -> YiM a -> YiM a Source #

class YiAction a x | a -> x where Source #

Methods

makeAction :: Show x => a -> Action Source #

Instances

Instances details
YiAction Action () Source # 
Instance details

Defined in Yi.Keymap

YiAction (IO x) x Source # 
Instance details

Defined in Yi.Keymap

Methods

makeAction :: IO x -> Action Source #

YiAction (EditorM x) x Source # 
Instance details

Defined in Yi.Keymap

YiAction (BufferM x) x Source # 
Instance details

Defined in Yi.Keymap

YiAction (YiM x) x Source # 
Instance details

Defined in Yi.Keymap

Methods

makeAction :: YiM x -> Action Source #

(YiAction a x, Promptable r) => YiAction (r -> a) x Source # 
Instance details

Defined in Yi.MiniBuffer

Methods

makeAction :: (r -> a) -> Action Source #

data Yi Source #

Constructors

Yi 

Fields

Instances

Instances details
MonadReader Yi YiM Source # 
Instance details

Defined in Yi.Types

Methods

ask :: YiM Yi #

local :: (Yi -> Yi) -> YiM a -> YiM a #

reader :: (Yi -> a) -> YiM a #

data IsRefreshNeeded Source #

Instances

Instances details
Eq IsRefreshNeeded Source # 
Instance details

Defined in Yi.Types

Show IsRefreshNeeded Source # 
Instance details

Defined in Yi.Types

write :: (MonadInteract m Action ev, YiAction a x, Show x) => a -> m () Source #

write a returns a keymap that just outputs the action a.

withModeY :: (forall syntax. Mode syntax -> YiM ()) -> YiM () Source #

withModeY f runs f on the current buffer's mode. As this runs in the YiM monad, we're able to do more than with just withModeB such as prompt the user for something before running the action.

Lenses