yi-core-0.14.0: Yi editor core library

LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • ScopedTypeVariables
  • OverloadedStrings
  • DeriveDataTypeable
  • TypeSynonymInstances
  • FlexibleInstances
  • ConstrainedClassMethods
  • MultiParamTypeClasses
  • GeneralizedNewtypeDeriving
  • TypeOperators
  • ExplicitNamespaces
  • ExplicitForAll
  • LambdaCase

Yi.MiniBuffer

Contents

Description

Functions working with the minibuffer.

Synopsis

Documentation

spawnMinibufferE :: Text -> KeymapEndo -> EditorM BufferRef Source #

Open a minibuffer window with the given prompt and keymap The third argument is an action to perform after the minibuffer is opened such as move to the first occurence of a searched for string. If you don't need this just supply return ()

withMinibufferFree :: Text -> (Text -> YiM ()) -> YiM () Source #

withMinibufferFree prompt act: Simple version of withMinibufferGen

withMinibuffer :: Text -> (Text -> YiM [Text]) -> (Text -> YiM ()) -> YiM () Source #

withMinibuffer prompt completer act: open a minibuffer with prompt. Once a string s is obtained, run act s. completer can be used to complete functions: it returns a list of possible matches.

withMinibufferGen :: Text -> (Text -> YiM [Text]) -> Text -> (Text -> YiM Text) -> (Text -> YiM ()) -> (Text -> YiM ()) -> YiM () Source #

withMinibufferGen proposal getHint prompt completer onTyping act: open a minibuffer with prompt, and initial content proposal. Once a string s is obtained, run act s. completer can be used to complete inputs by returning an incrementally better match, and getHint can give an immediate feedback to the user on the current input.

on Typing is an extra action which will fire with every user key-press and receives minibuffer contents. Use something like const $ return () if you don't need this.

withMinibufferFin :: Text -> [Text] -> (Text -> YiM ()) -> YiM () Source #

Open a minibuffer, given a finite number of suggestions.

noHint :: a -> YiM [a] Source #

Hint function that does nothing, for use with withMinibufferGen

mkCompleteFn Source #

Arguments

:: (Text -> (Text -> Maybe Text) -> [Text] -> EditorM Text)

List completion, such as completeInList.

-> (Text -> Text -> Maybe Text)

Matcher such as prefixMatch

-> (Text -> YiM [Text])

Function to fetch possibilites for completion.

-> Text

Input to try and complete against

-> YiM Text 

Makes a completion function.

matchingBufferNames :: YiM [Text] Source #

Returns all the buffer names

newtype t ::: doc Source #

Tag a type with a documentation

Constructors

Doc 

Fields

Instances

Eq t => Eq ((:::) t doc) Source # 

Methods

(==) :: (t ::: doc) -> (t ::: doc) -> Bool #

(/=) :: (t ::: doc) -> (t ::: doc) -> Bool #

Num t => Num ((:::) t doc) Source # 

Methods

(+) :: (t ::: doc) -> (t ::: doc) -> t ::: doc #

(-) :: (t ::: doc) -> (t ::: doc) -> t ::: doc #

(*) :: (t ::: doc) -> (t ::: doc) -> t ::: doc #

negate :: (t ::: doc) -> t ::: doc #

abs :: (t ::: doc) -> t ::: doc #

signum :: (t ::: doc) -> t ::: doc #

fromInteger :: Integer -> t ::: doc #

Show x => Show ((:::) x t) Source # 

Methods

showsPrec :: Int -> (x ::: t) -> ShowS #

show :: (x ::: t) -> String #

showList :: [x ::: t] -> ShowS #

IsString t => IsString ((:::) t doc) Source # 

Methods

fromString :: String -> t ::: doc #

commentRegion :: YiM () Source #

Prompts the user for comment syntax to use for the current mode.

promptingForBuffer Source #

Arguments

:: Text

Prompt

-> (BufferRef -> YiM ())

Handler

-> ([BufferRef] -> [BufferRef] -> [BufferRef])

Hint pre-processor. It takes the list of open buffers and a list of all buffers, and should spit out all the buffers to possibly hint, in the wanted order. Note the hinter uses name prefix for filtering regardless of what you do here.

-> YiM () 

Prompts for a buffer name, turns it into a BufferRef and passes it on to the handler function. Uses all known buffers for hinting.

Orphan instances

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

Methods

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