nvim-hs-0.0.5: Haskell plugin backend for neovim

Copyright(c) Sebastian Witte
LicenseApache-2.0
Maintainerwoozletoff@gmail.com
Stabilityexperimental
PortabilityGHC (due to Template Haskell)
Safe HaskellNone
LanguageHaskell2010

Neovim

Contents

Description

This module should contain all the things you need to write neovim plugins in your favorite language! :-)

The documentation in this module should provide every information you need to start writing plugins.

Synopsis

Installation

tl;dr

Make sure that neovim's executable (nvim) is on your $PATH during the cabal commands!

nvim-hs is a normal haskell program and a normal haskell library. You can install it in various flavors. These steps describe a more laborous approach that is suited for developing plugins or nvim-hs itself.

The following steps will install `nvim-hs` from git (example assumes you clone to $HOME/git/nvim-hs) using a sandbox:

$ mkdir -p ~/git ; cd ~/git
$ git clone https://github.com/neovimhaskell/nvim-hs
$ cd nvim-hs
$ cabal sandbox init
$ cabal install

Or in one line for copy-pasting:

mkdir -p ~/git ; cd ~/git ; git clone https://github.com/neovimhaskell/nvim-hs && cd nvim-hs && cabal sandbox init && cabal install

Copy the script nvim-hs-devel.sh to a location you like, make it executable and follow the brief instructions in the comments.

$ cp nvim-hs-devel.sh ~/bin/
$ chmod +x ~/bin/nvim-hs-devel.sh

Assuming you have copied the script to $HOME/bin/nvim-hs-devel.sh, put this in your neovim config file (typically ~/.nvimrc or ~/.nvim/nvimrc):

if has('nvim') " This way you can also put it in your vim config file
    call rpcrequest(rpcstart(expand('$HOME/.bin/nvim-hs-devel.sh')), "PingNvimhs")
endif

Explained

If you want to use or write plugins written in haskell for nvim-hs, you first have to make sure that neovim is installed and that it is available on your $PATH during the compilation of nvim-hs. Neovim emits information about its remotely callable API if you call it with the `--api-info` command line argument. This output is used to generate the API functions you need to create useful plugins. Also, some internal functionality requires some of these functions.

The instructions to install nvim-hs should be self-explanatory. In any case, I (saep) recommend using a sandbox for now since I the version constraints of the dependencies are quire lax and there are still changes on the way. Also, there is no official neovim release yet, so you may have to reinstall nvim-hs a few times because the generated API could change or something similar. A sandboxed environment can be saefly deleted and it requires you only to copy and edit a small shell script!

Using a sandbox requires you to install all the libraries you want or have to use in your plugins to be installed inside the sandbox! Some Vim plugins (e.g. ghc-mod) may show weird errors inside neovim for your configuration file because the sandbox is not inside your configuration folder. For nvim-hs you don't need to worry about that, though, because it has a builtin plugin which puts all compile-errors in the quickfix list automatically after you save your configuration file, so you don't need another plugin to detect compile time errors here. But we will discuss this later in more detail. The executable script mentioned in the tl;dr installation instructions sets up the build environment for nvim-hs to use the sandbox.

The Vim-script snippet is a bit conservative and may have a negative impact on your startup time. You can remove the rpcrequest() wrapping and call the function PingNvimhs at a later time when you need nvim-hs to be initialized. Use your own judgement! In any case, the snippet can be put anywhere in your neovim configuration. You may wonder why we have to explicitly call PingNvimhs with the function rpcrequest here. The short answer is: The internals for registering functions from a remote host require this. The longer answer is as follows: Registering functions from a remote host does not define a function directly. It instead installs a hook via an autocmd that defines the function. This way, only functions that are actually used are registered and this probably was implemented this way for performance reasons. Buf, if we try to call a function from a remote host too early, the hooks may not yet be in place and we receive error messages. Since we do not generate any Vim-script files which contain those hooks, nvim-hs must be started and initialized and create those hooks. So the best way to make sure that nvim-hs is initialized is to try to call some functionon on the msgpack-rpc channel that nvim-hs listens on. The function must not even exist, but not throwing an error message is probably nicer, so nvim-hs provides a function "PingNvimhs" which takes no arguments and returns "Pong".

Using nvim-hs essentially means to use a static binary that incorporates all plugins. It is generated using the Dyre library and the binary itself is found in $XDG_CACHE_DIR/nvim (usually ~/.cache/nvim). The Dyre library makes it feel more like a scripting language, because the binary is automatically created and executed without having to restart neovim. You can also use the functions from the Neovim.Debug module if you want to develop your plugins in a REPL environment. This is probably a bit more difficult to use, so I won't go into detail here.

Tutorial

tl;dr

If you are proficient with Haskell, it may be sufficient to point you at some of the important data structures and functions. So, I will do it here. If you need more assistance, please skip to the next section and follow the links for functions or data types you do no understand how to use. If you think that the documentation is lacking, please create an issue on github (or even better, a pull request with a fix ;-)). The code sections that describe new functionality are followed by the source code documentation of the used functions (and possibly a few more).

Create a file called nvim.hs in $XDG_CONFIG_HOME/nvim (usually ~/.config/nvim with the following content:

import Neovim

main = neovim defaultConfig

Adjust the fields in defaultConfig according to the the parameters in NeovimConfig. Depending on how you define the parameters, you may have to add some language extensions which GHC should point you to.

data Neovim r st a Source

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 
MonadThrow (Neovim r st) Source 
MonadCatch (Neovim r st) Source 
MonadMask (Neovim r st) Source 
MonadIO (Neovim r st) Source 
MonadResource (Neovim r st) Source 

type Neovim' = Neovim () () Source

Convenience alias for Neovim () ().

neovim :: NeovimConfig -> IO () Source

This is essentially the main function for nvim-hs, at least if you want to use Config.Dyre for the configuration.

data NeovimConfig Source

This data type contins information about the configuration of neovim. See the fields' documentation for what you possibly want to change. Also, the tutorial in the Neovim module should get you started.

Constructors

Config 

Fields

plugins :: [Neovim (StartupConfig NeovimConfig) () NeovimPlugin]

The list of plugins. The IO type inside the list allows the plugin author to run some arbitrary startup code before creating a value of type NeovimPlugin.

logOptions :: Maybe (FilePath, Priority)

Set the general logging options.

errorMessage :: Maybe String

Internally used field. Changing this has no effect.

Used by Dyre for storing compilation errors.

defaultConfig :: NeovimConfig Source

Default configuration options for nvim-hs. If you want to keep the default plugins enabled, you can define you rconfig like this:

main = neovim defaultConfig
         { plugins = myPlugins ++ plugins defaultConfig
         }

data StartupConfig cfg Source

This data type contains internal fields of nvim-hs that may be useful for plugin authors. It is available via ask inside the plugin startup code.

Constructors

StartupConfig 

Fields

dyreParams :: Maybe (Params cfg)

The configuration options for Config.Dyre. This is always set if nvim-hs has been started via Config.Dyre. Be sure to set up the ghcEnvironmentVariables correctly if you issue a recompilation via the Config.Dyre API.

ghcEnvironmentVariables :: [(String, Maybe String)]

The GHC environment variables with which nvim-hs has been started. This are mainly of significance if you want to use the same environment for compilation or a REPL that nvim-hs runs on.

These variables have to be used if you want to invoke functionality of Config.Dyre targeting nvim-hs.

def :: Default a => a

The default value for this type.

Using existing plugins

nvim-hs is all about importing and creating plugins. This is done following a concise API. Let's start by making a given plugin available inside our plugin provider. Assuming that we have installed a cabal package that exports an examplePlugin from the module TestPlugin.ExamplePlugin. A minimal configuration would then look like this:

import TestPlugin.ExamplePlugin (examplePlugin)

main = neovim def
        { plugins = [ examplePlugin ] ++ plugins defaultConfig
        }

That's all you have to do! Multiple plugins are simply imported and put in a list.

If the plugin is not packaged, you can also put the source files of the plugin inside $XDG_CONFIG_HOME/nvim/lib (usually ~/.config/nvim/lib). Assuming the same module name and plugin name, you can use the same configuration file. The source for the plugin must be located at $XDG_CONFIG_HOME/nvim/lib/TestPlugin/ExamplePlugin.hs and all source files it depends on must follow the same structure. This is the standard way how Haskell modules are defined in cabal projects. Having all plugins as source files can increase the compilation times, so plugins should be put in a cabal project once they are mature enough. This also makes them easy to share!

Creating a plugin

Creating plugins isn't difficult either. You just have to follow and survive the the compile time errors of seemingly valid code. This may sound scary, but it is not so bad. We will cover most pitfalls in the following paragraphs and if there isn't a solution for your error, you can always ask any friendly Haskeller in #haskell on irc.freenode.net!

Enough scary stuff said for now, let's write a plugin! Due to a stage restriction in GHC when using Template Haskell, we must define our functions in a different module than $XDG_CONFIG_HOME/nvim/nvim.hs. This is a bit unfortunate, but it will save you a lot of boring boilerplate and it will present you with helpful error messages if your plugin's functions do not work together with neovim.

So, let's write a plugin that calculates the nth Fibonacci number. Don't we all love those!

File ~/.config/nvim/lib/Fibonacci/Plugin.hs

module Fibonacci.Plugin (fibonacci) where

import Neovim

-- | Neovim is not really good with big numbers, so we return a String here.
fibonacci :: Int -> Neovim' String
fibonacci n = return . show $ fibs !! n
  where
    fibs :: [Integer]
    fibs = 0:1:scanl1 (+) fibs

File ~/.config/nvim/lib/Fibonacci.hs:

{-# LANGUAGE TemplateHaskell #-}
module Fibonacci (plugin) where

import Neovim
import Fibonacci.Plugin (fibonacci)

plugin :: Neovim (StartupConfig NeovimConfig) () NeovimPlugin
plugin = wrapPlugin Plugin
    { exports         = [ $(function' 'fibonacci) Sync ]
    , statefulExports = []
    }

File ~/.config/nvim/nvim.hs:

import Neovim

import qualified Fibonacci as Fibonacci

main :: IO ()
main = neovim defaultConfig
    { plugins = plugins defaultConfig ++ [ Fibonacci.plugin ]
    }

Let's analyze how it works. The module Fibonacci.Plugin simply defines a function that takes the nth element of the infinite list of Fibonacci numbers. Even though the definition is very concise and asthetically pleasing, the important part is the type signature for fibonacci. Similarly how main :: IO () works in normal Haskell programs, Neovim' is the environment we need for plugins. Internally, it stores a few things that are needed to communicate with neovim, but that shouldn't bother you too much. Simply remember that every plugin function must have a function signature whose last element is of type Neovim r st something. The result of fibonacci is String because neovim cannot handle big numbers so well. :-) You can use any argument or result type as long as it is an instance of NvimObject.

The second part of of the puzzle, which is the definition of plugin in ~/.config/nvim/lib/Fibonaccin.hs, shows what a plugin is. It is essentially two lists of stateless and stateful functionality. A functionality can currently be one of three things: a function, a command and an autocmd in the context of vim terminology. In the end, all of those functionalities map to a function at the side of nvim-hs. If you really want to know what the distinction between those, you have to consult the :help pages of neovim (e.g. :help :function, :help :command and :help :autocmd). What's relevant from the side of nvim-hs is the distinction between stateful and stateless. A stateless function can be called at any time and it does not share any of its internals with other functions. A stateful function on the other hand can share a well-defined amount of state with other functions and in the next section I will show you a simple example for that. Anyhow, if you take a look at the type alias for Neovim, you notice the two type variables r and st. These can be accessed with different semantics each. A value of type r can only be read. It is more or less a static value you can query with ask or asks if you are inside a Neovim environment. The value st can be changed and those changes will be available to other functions which run in the same environment. You can get the current value with get, you can replace an existing value with put and you can also apply a function to the current state with modify. Notice how Neovim' is just a specialization of Neovim with its r and st set to ().

Now to the magical part: $(function' 'fibonacci). This is a so called Template Haskell splice and this is why you need {-# LANGUAGE TemplateHaskell #-} at the top of your Haskell file. This splice simply generates Haskell code that, in this case, still needs a value of type Synchronous which indicates whether calling the function will make neovim wait for its result or not. Internally, the expression $(function' 'fibonacci) Sync creates a value that contains all the necessary information to properly register the function with neovim. Note the prime symbol before the function name! This would have probably caused you some trouble if I haven't mentioned it here! Template Haskell simply requires you to put that in front of function names that are passed in a splice.

If you compile this (which should happen automatically if you have put those files at the appropriate places), you can restart nvim-hs with the command :RestartNvimhs which is available as long as you do not remove the default plugins from you rconfig. Afterwards, you can calculate the 2000th Fibonacci number like as if it were a normal vim-script function:

:echo Fibonacci(2000)

You can also directly insert the result inside any text file opened with neovim by using the evaluation register by pressing the following key sequence in insert mode:

<C-r>=Fibonacci(2000)

data NeovimPlugin Source

Plugin values are wraped inside this data type via wrapPlugin so that we can put plugins in an ordinary list.

Constructors

forall r st . NeovimPlugin (Plugin r st) 

data Plugin r st Source

This data type contains meta information for the plugin manager.

Constructors

Plugin 

Fields

exports :: [ExportedFunctionality () ()]
 
statefulExports :: [(r, st, [ExportedFunctionality r st])]
 

class NvimObject o where Source

Conversion from Object files to Haskell types and back with respect to neovim's interpretation.

Minimal complete definition

toObject

Methods

toObject :: o -> Object Source

fromObjectUnsafe :: Object -> o Source

fromObject :: NvimObject o => Object -> Either String o Source

Instances

NvimObject Bool Source 
NvimObject Char Source 
NvimObject Double Source 
NvimObject Int Source 
NvimObject Int8 Source 
NvimObject Int16 Source 
NvimObject Int32 Source 
NvimObject Int64 Source 
NvimObject Integer Source 
NvimObject Word Source 
NvimObject Word8 Source 
NvimObject Word16 Source 
NvimObject Word32 Source 
NvimObject Word64 Source 
NvimObject () Source 
NvimObject ByteString Source 
NvimObject Text Source 
NvimObject Object Source 
NvimObject AutocmdOptions Source 
NvimObject CommandArguments Source 
NvimObject RangeSpecification Source 
NvimObject CommandOptions Source 
NvimObject Synchronous Source 
NvimObject Message Source 
NvimObject Window Source 
NvimObject Tabpage Source 
NvimObject Buffer Source 
NvimObject NeovimExceptionGen Source 
NvimObject QuickfixAction Source 
NvimObject QuickfixErrorType Source 
NvimObject [Char] Source 
NvimObject o => NvimObject [o] Source 
NvimObject o => NvimObject (Maybe o) Source 
(Monoid strType, NvimObject strType) => NvimObject (QuickfixListItem strType) Source 
(NvimObject l, NvimObject r) => NvimObject (Either l r) Source

Right-biased instance for toObject.

(NvimObject o1, NvimObject o2) => NvimObject (o1, o2) Source 
(Ord key, NvimObject key, NvimObject val) => NvimObject (Map key val) Source 
(NvimObject o1, NvimObject o2, NvimObject o3) => NvimObject (o1, o2, o3) Source 
(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4) => NvimObject (o1, o2, o3, o4) Source 
(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5) => NvimObject (o1, o2, o3, o4, o5) Source 
(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6) => NvimObject (o1, o2, o3, o4, o5, o6) Source 
(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6, NvimObject o7) => NvimObject (o1, o2, o3, o4, o5, o6, o7) Source 
(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6, NvimObject o7, NvimObject o8) => NvimObject (o1, o2, o3, o4, o5, o6, o7, o8) Source 
(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5, NvimObject o6, NvimObject o7, NvimObject o8, NvimObject o9) => NvimObject (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source 

type Dictionary = Map ByteString Object Source

A generic vim dictionary is a simply a map from strings to objects. This type alias is sometimes useful as a type annotation especially if the OverloadedStrings extension is enabled.

wrapPlugin :: Monad m => Plugin r st -> m NeovimPlugin Source

Wrap a Plugin in some nice blankets, so that we can put them in a simple list.

function :: String -> Name -> Q Exp Source

Define an exported function by providing a cutom name and referencing the function you want to export.

Note that the name must start with an upper case letter.

Example: $(function "MyExportedFunction" 'myDefinedFunction) Sync

function' :: Name -> Q Exp Source

Define an exported function. This function works exactly like function, but it generates the exported name automatically by converting the first letter to upper case.

command :: String -> Name -> Q Exp Source

Similarly to function, this function is used to export a command with a custom name.

Note that commands must start with an upper case letter.

Due to limitations on the side of (neo)vim, commands can only have one of the following five signatures, where you can replace String with ByteString or Text if you wish:

Example: $(command "RememberThePrime" 'someFunction) [CmdBang]

Note that the list of command options (i.e. the last argument) removes duplicate options by means of some internally convienient sorting. You should simply not defined the same option twice.

command' :: Name -> Q Exp Source

Define an exported command. This function works exactly like command, but it generates the command name by converting the first letter to upper case.

autocmd :: Name -> Q Exp Source

This function generates an export for autocmd. Since this is a static registration, arguments are not allowed here. You can, of course, define a fully applied function and pass it as an argument. If you have to add autocmds dynamically, it can be done with addAutocmd.

Example:

someFunction :: a -> b -> c -> d -> Neovim r st res
someFunction = ...

theFunction :: Neovim r st res
theFunction = someFunction 1 2 3 4

$(autocmd 'theFunction) def

def is of type AutocmdOptions.

Note that you have to define theFunction in a different module due to the use of Template Haskell.

data Synchronous Source

This option detemines how neovim should behave when calling some functionality on a remote host.

Constructors

Async

Call the functionality entirely for its side effects and do not wait for it to finish. Calling a functionality with this flag set is completely asynchronous and nothing is really expected to happen. This is why a call like this is called notification on the neovim side of things.

Sync

Call the function and wait for its result. This is only synchronous on the neovim side. This means that the GUI will (probably) not allow any user input until a reult is received.

data CommandOption Source

Options for commands.

Some command can also be described by using the OverloadedString extensions. This means that you can write a literal String inside your source file in place for a CommandOption value. See the documentation for each value on how these strings should look like (Both versions are compile time checked.)

Constructors

CmdSync Synchronous

Stringliteral "sync" or "async"

CmdRegister

Register passed to the command.

Stringliteral: "\""

CmdRange RangeSpecification

Determines how neovim passes the range.

Stringliterals: "%" for WholeFile, "," for line and ",123" for 123 lines.

CmdCount Word

Command handles a count. The argument defines the default count.

Stringliteral: string of numbers (e.g. "132")

CmdBang

Command handles a bang

Stringliteral: "!"

data RangeSpecification Source

Specification of a range that acommand can operate on.

Constructors

CurrentLine

The line the cursor is at when the command is invoked.

WholeFile

Let the command operate on every line of the file.

RangeCount Int

Let the command operate on each line in the given range.

data CommandArguments Source

You can use this type as the first argument for a function which is intended to be exported as a command. It holds information about the special attributes a command can take.

Constructors

CommandArguments 

Fields

bang :: Maybe Bool

Nothing means that the function was not defined to handle a bang, otherwise it means that the bang was passed (Just True) or that it was not passed when called (Just False).

range :: Maybe (Int, Int)

Range passed from neovim. Only set if CmdRange was used in the export declaration of the command.

Example:

  • Just (1,12)
count :: Maybe Int

Count passed by neovim. Only set if CmdCount was used in the export declaration of the command.

register :: Maybe String

Register that the command can/should/must use.

data AutocmdOptions Source

Options that can be used to register an autocmd. See :h :autocmd or any referenced neovim help-page from the fields of this data type.

Constructors

AutocmdOptions 

Fields

acmdPattern :: String

Pattern to match on. (default: "*")

acmdNested :: Bool

Nested autocmd. (default: False)

See :h autocmd-nested

acmdGroup :: Maybe String

Group in which the autocmd should be registered.

addAutocmd Source

Arguments

:: ByteString

The event to register to (e.g. BufWritePost)

-> AutocmdOptions 
-> Neovim r st ()

Fully applied function to register

-> Neovim r st (Maybe (Either (Neovim anyR anySt ()) ReleaseKey))

A ReleaseKey if the registration worked

Register an autocmd in the current context. This means that, if you are currently in a stateful plugin, the function will be called in the current thread and has access to the configuration and state of this thread. If you need that information, but do not want to block the other functions in this thread, you have to manually fork a thread and make the state you need available there. If you don't care abou the state (or your function has been appield to all the necessary state (e.g. a TVar to share the rusult), then you can also call addAutocmd' which will register a stateless function that only interacts with other threads by means of concurrency abstractions.

Note that the function you pass must be fully applied.

Note beside: This function is equivalent to addAutocmd' if called from a stateless plugin thread.

addAutocmd' :: ByteString -> AutocmdOptions -> Neovim' () -> Neovim r st (Maybe ReleaseKey) Source

Add a stateless autocmd.

See addAutocmd for more details.

ask :: MonadReader r m => m r

Retrieves the monad environment.

asks

Arguments

:: forall (m :: * -> *). MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

put :: MonadState s m => s -> m ()

Replace the state inside the monad.

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.

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.

Creating a stateful plugin

Calling remote functions

Now that we are a little bit comfortable with the interface provided by nvim-hs, we can start to write a more complicated plugin. Let's create a random number generator!

File ~/.config/nvim/lib/Random/Plugin.hs:

module Random.Plugin (nextRandom, setNextRandom) where

import Neovim

-- | Neovim isn't so good with big numbers here either.
nextRandom :: Neovim r [Int16] Int16
nextRandom = do
    r <- gets head -- get the head of the infinite random number list
    modify tail    -- set the list to its tail
    return r

setNextRandom :: Int -> Neovim r [Int16] ()
setNextRandom n = modify (n:) -- cons to the front of the infinite list

File ~/.config/nvim/lib/Random.hs:

{-# LANGUAGE TemplateHaskell #-}
module Random (plugin) where

import Neovim
import Random.Plugin (nextRandom, setNextRandom)
import System.Random (newStdGen, randoms)

plugin :: Neovim (StartupConfig NeovimConfig) () NeovimPlugin
plugin = do
    g <- liftIO newStdGen         -- initialize with a random seed
    let randomNumbers = randoms g -- an infinite list of random numbers
    wrapPlugin Plugin
        { exports         = []
        , statefulExports =
            [ ((), randomNumbers,
                [ $(function' 'nextRandom) Sync
                , $(function "SetNextRandom" 'setNextRandom) Async
                ])
            ]
        }

File ~/.config/nvim/nvim.hs:

import Neovim

import qualified Fibonacci as Fibonacci
import qualified Random    as Random

main :: IO ()
main = neovim defaultConfig
    { plugins = plugins defaultConfig ++ [ Fibonacci.plugin, Random.plugin ]
    }

That wasn't too hard, was it? The definition is very similar to the previous example, we just were able to mutate our state and share that with other functions. The only slightly tedious thing was to define the statefulExports field because it is a list of triples which has a list of exported functionalities as its third argument. Another noteworthy detail, in case you are not familiar with it, is the use of liftIO in front of newStdGen. You have to do this, because newStdGen has type IO StdGen but the actions inside the startup code are of type Neovim (StartupConfig NeovimConfig) () something. liftIO lifts an IO function so that it can be run inside the Neovim context (or more generally, any monad that implements the MonadIO type class).

After you have saved these files (and removed any typos :-)), you can restart nvim-hs with :RestartNvimhs and insert random numbers in your text files!

<C-r>=NextRandom()

You can also cheat and pretend you know the next number:

:call SetNextRandom(42)

wait :: Neovim r st (STM result) -> Neovim r st result Source

Wait for the result of the STM action.

This action possibly blocks as it is an alias for ioSTM -> ioSTM >>= liftIO . atomically.

wait' :: Neovim r st (STM result) -> Neovim r st () Source

Variant of wait that discards the result.

waitErr Source

Arguments

:: Show e 
=> String

Prefix error message with this.

-> Neovim r st (STM (Either e result))

Function call to neovim

-> Neovim r st result 

Wait for the result of the STM action and call err . (loc++) . show if the action returned an error.

waitErr' :: Show e => String -> Neovim r st (STM (Either e result)) -> Neovim r st () Source

waitErr that discards the result.

err :: String -> Neovim r st a Source

throw . ErrorMessage

Generated functions for neovim interaction

Unsorted exports

liftIO :: MonadIO m => forall a. IO a -> m a

withCustomEnvironment :: (MonadMask io, MonadIO io) => [(String, Maybe String)] -> io a -> io a Source

Execute the given action with a changed set of environment variables and restore the original state of the environment afterwards.

whenM :: Monad m => m Bool -> m () -> m () Source

when with a monadic predicate.

unlessM :: Monad m => m Bool -> m () -> m () Source

unless with a monadic predicate.

data Priority :: *

Priorities are used to define how important a log message is. Users can filter log messages based on priorities.

These have their roots on the traditional syslog system. The standard definitions are given below, but you are free to interpret them however you like. They are listed here in ascending importance order.

Constructors

DEBUG

Debug messages

INFO

Information

NOTICE

Normal runtime conditions

WARNING

General Warnings

ERROR

General Errors

CRITICAL

Severe situations

ALERT

Take immediate action

EMERGENCY

System is unusable

Instances

Bounded Priority 
Enum Priority 
Eq Priority 
Ord Priority 
Read Priority 
Show Priority