| Copyright | (c) Sebastian Witte | 
|---|---|
| License | Apache-2.0 | 
| Maintainer | woozletoff@gmail.com | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Neovim.Context
Description
- newUniqueFunctionName :: Neovim r st FunctionName
- data Neovim r st a
- type Neovim' = Neovim () ()
- data NeovimException
- type FunctionMap = Map FunctionName FunctionMapEntry
- type FunctionMapEntry = (FunctionalityDescription, FunctionType)
- mkFunctionMap :: [FunctionMapEntry] -> FunctionMap
- runNeovim :: NFData a => Config r st -> st -> Neovim r st a -> IO (Either Doc (a, st))
- forkNeovim :: NFData a => ir -> ist -> Neovim ir ist a -> Neovim r st ThreadId
- err :: Pretty err => err -> Neovim r st a
- errOnInvalidResult :: NvimObject o => Neovim r st (Either NeovimException Object) -> Neovim r st o
- restart :: Neovim r st ()
- quit :: Neovim r st ()
- 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 ()
- throwError :: MonadError e m => forall a. e -> m a
- module Control.Monad.IO.Class
Documentation
newUniqueFunctionName :: Neovim r st 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.
 Stateless functions use '()' for the static configuration and the mutable
 state and there is another type alias for that case: Neovim'.
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
| MonadBase IO (Neovim r st) Source # | |
| MonadReader r (Neovim r st) Source # | User facing instance declaration for the reader state. | 
| MonadState st (Neovim r st) Source # | |
| Monad (Neovim r st) Source # | |
| Functor (Neovim r st) Source # | |
| Applicative (Neovim r st) Source # | |
| MonadIO (Neovim r st) Source # | |
| MonadThrow (Neovim r st) Source # | |
| MonadCatch (Neovim r st) Source # | |
| MonadMask (Neovim r st) Source # | |
| MonadResource (Neovim r st) Source # | |
data NeovimException Source #
Exceptions specific to nvim-hs.
Constructors
| ErrorMessage Doc | Simply error message that is passed to neovim. It should currently only contain one line of text. | 
| ErrorResult Object | Error that can be returned by a remote API call. A call of  | 
type FunctionMap = Map FunctionName 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 r st -> st -> Neovim r st a -> IO (Either Doc (a, st)) Source #
Initialize a Neovim context by supplying an InternalEnvironment.
forkNeovim :: NFData a => ir -> ist -> Neovim ir ist a -> Neovim r st ThreadId Source #
Fork a neovim thread with the given custom config value and a custom
 state. The result of the thread is discarded and only the ThreadId is
 returend immediately.
 FIXME This function is pretty much unused and mayhave undesired effects,
       namely that you cannot register autocmds in the forked thread.
errOnInvalidResult :: NvimObject o => Neovim r st (Either NeovimException Object) -> Neovim r st o Source #
ask :: MonadReader r m => m r #
Retrieves the monad environment.
Arguments
| :: 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.
throwError :: MonadError e m => forall a. e -> m a #
Is used within a monadic computation to begin exception processing.
module Control.Monad.IO.Class