yi-0.6.2.3: The Haskell-Scriptable EditorSource codeContentsIndex
Yi.Keymap
Synopsis
data Action
= forall a . Show a => YiA (YiM a)
| forall a . Show a => EditorA (EditorM a)
| forall a . Show a => BufferA (BufferM a)
| TaggedA String Action
emptyAction :: Action
type Interact ev a = I ev Action a
type KeymapM a = Interact Event a
type Keymap = KeymapM ()
type KeymapEndo = Keymap -> Keymap
type KeymapProcess = P Event Action
data Yi = Yi {
yiUi :: UI
input :: Event -> IO ()
output :: [Action] -> IO ()
yiConfig :: Config
yiVar :: MVar YiVar
}
data YiVar = YiVar {
yiEditor :: !Editor
threads :: ![ThreadId]
yiSubprocessIdSupply :: !SubprocessId
yiSubprocesses :: !(Map SubprocessId SubprocessInfo)
}
newtype YiM a = YiM {
runYiM :: ReaderT Yi IO a
}
write :: (MonadInteract m Action ev, YiAction a x, Show x) => a -> m ()
withUI :: (UI -> IO a) -> YiM a
unsafeWithEditor :: Config -> MVar YiVar -> EditorM a -> IO a
withGivenBuffer :: BufferRef -> BufferM a -> YiM a
withBuffer :: BufferM a -> YiM a
readEditor :: (Editor -> a) -> YiM a
catchDynE :: Typeable exception => YiM a -> (exception -> YiM a) -> YiM a
catchJustE :: (Exception -> Maybe b) -> YiM a -> (b -> YiM a) -> YiM a
handleJustE :: (Exception -> Maybe b) -> (b -> YiM a) -> YiM a -> YiM a
shutdown :: YiM ()
class YiAction a x | a -> x where
makeAction :: Show x => a -> Action
data KeymapSet = KeymapSet {
topKeymap :: Keymap
startInsertKeymap :: Keymap
insertKeymap :: Keymap
startTopKeymap :: Keymap
}
startTopKeymapA :: T KeymapSet Keymap
insertKeymapA :: T KeymapSet Keymap
startInsertKeymapA :: T KeymapSet Keymap
topKeymapA :: T KeymapSet Keymap
extractTopKeymap :: KeymapSet -> Keymap
modelessKeymapSet :: Keymap -> KeymapSet
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)
TaggedA String Action
show/hide Instances
emptyAction :: ActionSource
type Interact ev a = I ev Action aSource
type KeymapM a = Interact Event aSource
type Keymap = KeymapM ()Source
type KeymapEndo = Keymap -> KeymapSource
type KeymapProcess = P Event ActionSource
data Yi Source
Constructors
Yi
yiUi :: UI
input :: Event -> IO ()input stream
output :: [Action] -> IO ()output stream
yiConfig :: Config
yiVar :: MVar YiVarThe only mutable state in the program
show/hide Instances
data YiVar Source
Constructors
YiVar
yiEditor :: !Editor
threads :: ![ThreadId]all our threads
yiSubprocessIdSupply :: !SubprocessId
yiSubprocesses :: !(Map SubprocessId SubprocessInfo)
newtype YiM a Source
The type of user-bindable functions
Constructors
YiM
runYiM :: ReaderT Yi IO a
show/hide Instances
write :: (MonadInteract m Action ev, YiAction a x, Show x) => a -> m ()Source
write a returns a keymap that just outputs the action a.
withUI :: (UI -> IO a) -> YiM aSource
unsafeWithEditor :: Config -> MVar YiVar -> EditorM a -> IO aSource
withGivenBuffer :: BufferRef -> BufferM a -> YiM aSource
withBuffer :: BufferM a -> YiM aSource
readEditor :: (Editor -> a) -> YiM aSource
catchDynE :: Typeable exception => YiM a -> (exception -> YiM a) -> YiM aSource
catchJustESource
:: Exception -> Maybe bPredicate to select exceptions
-> YiM aComputation to run
-> b -> YiM aHandler
-> YiM a
handleJustE :: (Exception -> Maybe b) -> (b -> YiM a) -> YiM a -> YiM aSource
shutdown :: YiM ()Source
Shut down all of our threads. Should free buffers etc.
class YiAction a x | a -> x whereSource
Methods
makeAction :: Show x => a -> ActionSource
show/hide Instances
YiAction Action ()
YiAction (IO x) x
YiAction (BufferM x) x
YiAction (EditorM x) x
YiAction (YiM x) x
(YiAction a x, Promptable r) => YiAction (r -> a) x
data KeymapSet Source
Constructors
KeymapSet
topKeymap :: KeymapContent of the top-level loop.
startInsertKeymap :: KeymapStartup when entering insert mode
insertKeymap :: KeymapFor insertion-only modes
startTopKeymap :: KeymapStartup bit, to execute only once at the beginning.
startTopKeymapA :: T KeymapSet KeymapSource
insertKeymapA :: T KeymapSet KeymapSource
startInsertKeymapA :: T KeymapSet KeymapSource
topKeymapA :: T KeymapSet KeymapSource
extractTopKeymap :: KeymapSet -> KeymapSource
modelessKeymapSet :: Keymap -> KeymapSetSource
Produced by Haddock version 2.6.1