Copyright | (c) Sebastian Witte |
---|---|
License | Apache-2.0 |
Maintainer | woozletoff@gmail.com |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newUniqueFunctionName :: Neovim env FunctionName
- data Neovim env a
- data NeovimException
- exceptionToDoc :: NeovimException -> Doc AnsiStyle
- type FunctionMap = Map NvimMethod FunctionMapEntry
- type FunctionMapEntry = (FunctionalityDescription, FunctionType)
- mkFunctionMap :: [FunctionMapEntry] -> FunctionMap
- runNeovim :: NFData a => Config env -> Neovim env a -> IO (Either (Doc AnsiStyle) a)
- err :: Doc AnsiStyle -> Neovim env a
- errOnInvalidResult :: NvimObject o => Neovim env (Either NeovimException Object) -> Neovim env o
- restart :: Neovim env ()
- quit :: Neovim env ()
- subscribe :: Text -> ([Object] -> Neovim env ()) -> Neovim env Subscription
- unsubscribe :: Subscription -> Neovim env ()
- ask :: MonadReader r m => m r
- asks :: MonadReader r m => (r -> a) -> m a
- get :: MonadState s m => m s
- gets :: MonadState s m => (s -> a) -> m a
- put :: MonadState s m => s -> m ()
- modify :: MonadState s m => (s -> s) -> m ()
- data Doc ann
- data AnsiStyle
- docToText :: Doc AnsiStyle -> Text
- throwError :: MonadError e m => e -> m a
- module Control.Monad.IO.Class
Documentation
newUniqueFunctionName :: Neovim env FunctionName Source #
Create a new unique function name. To prevent possible name clashes, digits are stripped from the given suffix.
This is the environment in which all plugins are initially started.
Functions have to run in this transformer stack to communicate with neovim.
If parts of your own functions dont need to communicate with neovim, it is
good practice to factor them out. This allows you to write tests and spot
errors easier. Essentially, you should treat this similar to IO
in general
haskell programs.
Instances
MonadReader env (Neovim env) Source # | User facing instance declaration for the reader state. |
MonadFail (Neovim env) Source # | |
Defined in Neovim.Context.Internal | |
MonadIO (Neovim env) Source # | |
Defined in Neovim.Context.Internal | |
Applicative (Neovim env) Source # | |
Defined in Neovim.Context.Internal | |
Functor (Neovim env) Source # | |
Monad (Neovim env) Source # | |
MonadThrow (Neovim env) Source # | |
Defined in Neovim.Context.Internal | |
MonadUnliftIO (Neovim env) Source # | |
Defined in Neovim.Context.Internal | |
Monoid a => Monoid (Neovim env a) Source # | |
Semigroup a => Semigroup (Neovim env a) Source # | |
data NeovimException Source #
Exceptions specific to nvim-hs.
ErrorMessage (Doc AnsiStyle) | Simple error message that is passed to neovim. It should currently only contain one line of text. |
ErrorResult (Doc AnsiStyle) Object | Error that can be returned by a remote API call. The |
Instances
IsString NeovimException Source # | |
Defined in Neovim.Exceptions fromString :: String -> NeovimException # | |
Exception NeovimException Source # | |
Defined in Neovim.Exceptions | |
Show NeovimException Source # | |
Defined in Neovim.Exceptions showsPrec :: Int -> NeovimException -> ShowS # show :: NeovimException -> String # showList :: [NeovimException] -> ShowS # |
type FunctionMap = Map NvimMethod FunctionMapEntry Source #
A function map is a map containing the names of functions as keys and some context dependent value which contains all the necessary information to execute that function in the intended way.
This type is only used internally and handles two distinct cases. One case
is a direct function call, wich is simply a function that accepts a list of
Object
values and returns a result in the Neovim
context. The second
case is calling a function that has a persistent state. This is mediated to
a thread that reads from a TQueue
. (NB: persistent currently means, that
state is stored for as long as the plugin provider is running and not
restarted.)
type FunctionMapEntry = (FunctionalityDescription, FunctionType) Source #
Type of the values stored in the function map.
mkFunctionMap :: [FunctionMapEntry] -> FunctionMap Source #
Create a new function map from the given list of FunctionMapEntry
values.
runNeovim :: NFData a => Config env -> Neovim env a -> IO (Either (Doc AnsiStyle) a) Source #
Initialize a Neovim
context by supplying an InternalEnvironment
.
errOnInvalidResult :: NvimObject o => Neovim env (Either NeovimException Object) -> Neovim env o Source #
subscribe :: Text -> ([Object] -> Neovim env ()) -> Neovim env Subscription Source #
Subscribe to an event. When the event is received, the given callback function
is run. It is usually necessary to call the appropriate API function in order for
neovim to send the notifications to nvim-hs. The returned subscription can be
used to unsubscribe
.
unsubscribe :: Subscription -> Neovim env () Source #
Remove the subscription that has been returned by subscribe
.
ask :: MonadReader r m => m r #
Retrieves the monad environment.
:: MonadReader r m | |
=> (r -> a) | The selector function to apply to the environment. |
-> m a |
Retrieves a function of the current environment.
get :: MonadState s m => m s #
Return the state from the internals of the monad.
gets :: MonadState s m => (s -> a) -> m a #
Gets specific component of the state, using a projection function supplied.
put :: MonadState s m => s -> m () #
Replace the state inside the monad.
modify :: MonadState s m => (s -> s) -> m () #
Monadic state transformer.
Maps an old state to a new state inside a state monad. The old state is thrown away.
Main> :t modify ((+1) :: Int -> Int) modify (...) :: (MonadState Int a) => a ()
This says that modify (+1)
acts over any
Monad that is a member of the MonadState
class,
with an Int
state.
The abstract data type
represents pretty documents that have
been annotated with data of type Doc
annann
.
More specifically, a value of type
represents a non-empty set of
possible layouts of a document. The layout functions select one of these
possibilities, taking into account things like the width of the output
document.Doc
The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as
- color information (e.g. when rendering to the terminal)
- mouseover text (e.g. when rendering to rich HTML)
- whether to show something or not (to allow simple or detailed versions)
The simplest way to display a Doc
is via the Show
class.
>>>
putStrLn (show (vsep ["hello", "world"]))
hello world
Instances
Render the annotated document in a certain style. Styles not set in the annotation will use the style of the surrounding document, or the terminal’s default if none has been set yet.
style =color
Green
<>
bold
styledDoc =annotate
style "hello world"
Instances
Monoid AnsiStyle |
|
Semigroup AnsiStyle | Keep the first decision for each of foreground color, background color, boldness, italication, and underlining. If a certain style is not set, the terminal’s default will be used. Example:
is red because the first color wins, and not bold because (or if) that’s the terminal’s default. |
Show AnsiStyle | |
Eq AnsiStyle | |
Ord AnsiStyle | |
Defined in Prettyprinter.Render.Terminal.Internal |
throwError :: MonadError e m => e -> m a #
Is used within a monadic computation to begin exception processing.
module Control.Monad.IO.Class