nvim-hs-2.1.0.2: 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

Installation instructions are in the README.md file that comes with the source of this package. It is also on the repositories front page.

Tutorial

Motivation

An nvim-hs plugin is just a collection of haskell functions that can be called from neovim.

As a user of plugins, you basically have two choices. You can start every plugin in a separate process and use normal vim plugin management strategies such as vim-plug or pathogen. Alternatively, you can create a haskell project and depend on the plugins you want to use and plumb them together. This plumbing is equivalent to writing a plugin.

Since you are reading haddock documentation, you probably want the latter, so just keep reading. :-)

The easiest way to start is to use the stack template as described in the README.md of this package. If you initialize it in your neovim configuration directory (~.convignvim on linux-based systems), it should automatically be compiled and run with two simple example plugins

You have to define a haskell project that depends on this package and contains an executable secion with a main file that looks like this:

import TestPlugin.ExamplePlugin (examplePlugin)

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

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 main file would then look like this:

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

data Neovim env a Source #

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.

Instance details

Defined in Neovim.Context.Internal

Methods

ask :: Neovim env env #

local :: (env -> env) -> Neovim env a -> Neovim env a #

reader :: (env -> a) -> Neovim env a #

Monad (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

(>>=) :: Neovim env a -> (a -> Neovim env b) -> Neovim env b #

(>>) :: Neovim env a -> Neovim env b -> Neovim env b #

return :: a -> Neovim env a #

fail :: String -> Neovim env a #

Functor (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

fmap :: (a -> b) -> Neovim env a -> Neovim env b #

(<$) :: a -> Neovim env b -> Neovim env a #

MonadFail (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

fail :: String -> Neovim env a #

Applicative (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

pure :: a -> Neovim env a #

(<*>) :: Neovim env (a -> b) -> Neovim env a -> Neovim env b #

liftA2 :: (a -> b -> c) -> Neovim env a -> Neovim env b -> Neovim env c #

(*>) :: Neovim env a -> Neovim env b -> Neovim env b #

(<*) :: Neovim env a -> Neovim env b -> Neovim env a #

MonadIO (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

liftIO :: IO a -> Neovim env a #

MonadUnliftIO (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

askUnliftIO :: Neovim env (UnliftIO (Neovim env)) #

withRunInIO :: ((forall a. Neovim env a -> IO a) -> IO b) -> Neovim env b #

MonadResource (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

liftResourceT :: ResourceT IO a -> Neovim env a #

MonadThrow (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

throwM :: Exception e => e -> Neovim env a #

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 contains 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

defaultConfig :: NeovimConfig Source #

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

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

def :: Default a => a #

The default value for this type.

Creating a plugin

Creating plugins isn't difficult either. You just have to follow and survive 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 (i.e. code generation), we must define our functions in a different module than $XDG_CONFIG_HOME/nvim/nvim.hs. (I'm assuming here, that you use $XDG_CONFIG_HOME/nvim/ as the base directory for historical reasons and because it might be an appropriate place.) 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 env 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 () NeovimPlugin
plugin = wrapPlugin Plugin
    { environment = ()
    , exports     = [ $(function' 'fibonacci) Sync ]
    }

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 env 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/Fibonacci.hs, shows what a plugin is. It is essentially an empty environment and a list of functions, commands or autocommands in the context of vim terminology. In the end, all of those things map to a function at the side of nvim-hs. If you really want to know what the distinction between those is, 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 environment. The environment is a data type that is avaiable to all exported functions of your plugin. This example does not make use of anything of that environment, so we used '()', also known as unit, as our environment. The definition of fibonacci uses a type variable env as it does not access the environment and can handle any environment. If you want to access the environment, you can call ask or asks if you are inside a Neovim environment. An example that shows you how to use it can be found in a later chapter.

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 and restart the plugin, 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)

The haddock documentation will now list all the things we have used up until now. Afterwards, there is a plugin with state which uses the environment.

data NeovimPlugin Source #

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

Constructors

NeovimPlugin (Plugin env) 

data Plugin env Source #

This data type contains meta information for the plugin manager.

Constructors

Plugin 

Fields

class NFData o => NvimObject o where Source #

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

The NFData constraint has been added to allow forcing results of function evaluations in order to catch exceptions from pure code. This adds more stability to the plugin provider and seems to be a cleaner approach.

Minimal complete definition

toObject, (fromObject | fromObjectUnsafe)

Instances
NvimObject Bool Source # 
Instance details

Defined in Neovim.Classes

NvimObject Double Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int8 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int16 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int32 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Int64 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Integer Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word8 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word16 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word32 Source # 
Instance details

Defined in Neovim.Classes

NvimObject Word64 Source # 
Instance details

Defined in Neovim.Classes

NvimObject () Source # 
Instance details

Defined in Neovim.Classes

NvimObject ByteString Source # 
Instance details

Defined in Neovim.Classes

NvimObject Text Source # 
Instance details

Defined in Neovim.Classes

NvimObject Object Source # 
Instance details

Defined in Neovim.Classes

NvimObject AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject Message Source # 
Instance details

Defined in Neovim.RPC.Classes

NvimObject Window Source # 
Instance details

Defined in Neovim.API.Text

NvimObject Tabpage Source # 
Instance details

Defined in Neovim.API.Text

NvimObject Buffer Source # 
Instance details

Defined in Neovim.API.Text

NvimObject NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.Text

NvimObject Window Source # 
Instance details

Defined in Neovim.API.String

NvimObject Tabpage Source # 
Instance details

Defined in Neovim.API.String

NvimObject Buffer Source # 
Instance details

Defined in Neovim.API.String

NvimObject NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.String

NvimObject QuickfixAction Source # 
Instance details

Defined in Neovim.Quickfix

NvimObject QuickfixErrorType Source # 
Instance details

Defined in Neovim.Quickfix

NvimObject Window Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject Tabpage Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject Buffer Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject NeovimExceptionGen Source # 
Instance details

Defined in Neovim.API.ByteString

NvimObject [Char] Source # 
Instance details

Defined in Neovim.Classes

NvimObject o => NvimObject [o] Source # 
Instance details

Defined in Neovim.Classes

NvimObject o => NvimObject (Maybe o) Source # 
Instance details

Defined in Neovim.Classes

NvimObject o => NvimObject (Vector o) Source # 
Instance details

Defined in Neovim.Classes

(Monoid strType, NvimObject strType) => NvimObject (QuickfixListItem strType) Source # 
Instance details

Defined in Neovim.Quickfix

(NvimObject l, NvimObject r) => NvimObject (Either l r) Source #

Right-biased instance for toObject.

Instance details

Defined in Neovim.Classes

(NvimObject o1, NvimObject o2) => NvimObject (o1, o2) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2) Source #

(Ord key, NvimObject key, NvimObject val) => NvimObject (Map key val) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: Map key val -> Object Source #

fromObjectUnsafe :: Object -> Map key val Source #

fromObject :: Object -> Either (Doc AnsiStyle) (Map key val) Source #

fromObject' :: MonadIO io => Object -> io (Map key val) Source #

(NvimObject o1, NvimObject o2, NvimObject o3) => NvimObject (o1, o2, o3) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4) => NvimObject (o1, o2, o3, o4) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4) Source #

(NvimObject o1, NvimObject o2, NvimObject o3, NvimObject o4, NvimObject o5) => NvimObject (o1, o2, o3, o4, o5) Source # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5) Source #

fromObject' :: MonadIO io => Object -> io (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 # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6) Source #

fromObject' :: MonadIO io => Object -> io (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 # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6, o7) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6, o7) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6, o7) Source #

fromObject' :: MonadIO io => Object -> io (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 # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6, o7, o8) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6, o7, o8) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6, o7, o8) Source #

fromObject' :: MonadIO io => Object -> io (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 # 
Instance details

Defined in Neovim.Classes

Methods

toObject :: (o1, o2, o3, o4, o5, o6, o7, o8, o9) -> Object Source #

fromObjectUnsafe :: Object -> (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source #

fromObject :: Object -> Either (Doc AnsiStyle) (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source #

fromObject' :: MonadIO io => Object -> io (o1, o2, o3, o4, o5, o6, o7, o8, o9) Source #

(+:) :: NvimObject o => o -> [Object] -> [Object] infixr 5 Source #

Convenient operator to create a list of Object from normal values. values +: of :+ different :+ types :+ can +: be +: combined +: this +: way +: []

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.

data Object #

Constructors

ObjectNil 
ObjectUInt Word64

Unsigned integers from the MsgPack protocol: uint 8, uint 16, uint 32, uint 64

ObjectInt Int64

Signed integers and fixnums from the MsgPack protocol: positive fixnum, negative fixnum, int 8, int 16, int 32, int 64

ObjectBool Bool 
ObjectFloat Float 
ObjectDouble Double 
ObjectString ByteString 
ObjectBinary ByteString 
ObjectArray [Object] 
ObjectMap (Map Object Object) 
ObjectExt !Int8 ByteString 
Instances
Eq Object 
Instance details

Defined in Data.MessagePack

Methods

(==) :: Object -> Object -> Bool #

(/=) :: Object -> Object -> Bool #

Ord Object 
Instance details

Defined in Data.MessagePack

Show Object 
Instance details

Defined in Data.MessagePack

Generic Object 
Instance details

Defined in Data.MessagePack

Associated Types

type Rep Object :: Type -> Type #

Methods

from :: Object -> Rep Object x #

to :: Rep Object x -> Object #

Serialize Object 
Instance details

Defined in Data.MessagePack

NFData Object 
Instance details

Defined in Data.MessagePack

Methods

rnf :: Object -> () #

NvimObject Object Source # 
Instance details

Defined in Neovim.Classes

type Rep Object 
Instance details

Defined in Data.MessagePack

type Rep Object = D1 (MetaData "Object" "Data.MessagePack" "messagepack-0.5.4-3mZR78HZbYJGLFBOHkTSON" False) (((C1 (MetaCons "ObjectNil" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "ObjectUInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word64))) :+: (C1 (MetaCons "ObjectInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int64)) :+: (C1 (MetaCons "ObjectBool" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) :+: C1 (MetaCons "ObjectFloat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Float))))) :+: ((C1 (MetaCons "ObjectDouble" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Double)) :+: (C1 (MetaCons "ObjectString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)) :+: C1 (MetaCons "ObjectBinary" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))) :+: (C1 (MetaCons "ObjectArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Object])) :+: (C1 (MetaCons "ObjectMap" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Object Object))) :+: C1 (MetaCons "ObjectExt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int8) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))))))

wrapPlugin :: Applicative m => Plugin env -> 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 custom 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 convenient sorting. You should simply not define 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.

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.

Instances
Enum Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Eq Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Read Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

IsString Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Generic Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep Synchronous :: Type -> Type #

NFData Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: Synchronous -> () #

Pretty Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: Synchronous -> Doc ann #

prettyList :: [Synchronous] -> Doc ann #

NvimObject Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep Synchronous = D1 (MetaData "Synchronous" "Neovim.Plugin.Classes" "nvim-hs-2.1.0.2-47XZonBAGjb6QzC4PmrUFP" False) (C1 (MetaCons "Async" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Sync" PrefixI False) (U1 :: Type -> Type))

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: "!"

Instances
Eq CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Read CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

IsString CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Generic CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandOption :: Type -> Type #

NFData CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: CommandOption -> () #

Pretty CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: CommandOption -> Doc ann #

prettyList :: [CommandOption] -> Doc ann #

type Rep CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

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.

Instances
Eq RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Read RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Generic RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep RangeSpecification :: Type -> Type #

NFData RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: RangeSpecification -> () #

Pretty RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep RangeSpecification = D1 (MetaData "RangeSpecification" "Neovim.Plugin.Classes" "nvim-hs-2.1.0.2-47XZonBAGjb6QzC4PmrUFP" False) (C1 (MetaCons "CurrentLine" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "WholeFile" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RangeCount" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))

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.

Instances
Eq CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Read CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Generic CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandArguments :: Type -> Type #

Default CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: CommandArguments -> () #

Pretty CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

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

Instances
Eq AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Read AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Generic AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep AutocmdOptions :: Type -> Type #

Default AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

def :: AutocmdOptions #

NFData AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: AutocmdOptions -> () #

Pretty AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: AutocmdOptions -> Doc ann #

prettyList :: [AutocmdOptions] -> Doc ann #

NvimObject AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep AutocmdOptions = D1 (MetaData "AutocmdOptions" "Neovim.Plugin.Classes" "nvim-hs-2.1.0.2-47XZonBAGjb6QzC4PmrUFP" False) (C1 (MetaCons "AutocmdOptions" PrefixI True) (S1 (MetaSel (Just "acmdPattern") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: (S1 (MetaSel (Just "acmdNested") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "acmdGroup") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe String)))))

addAutocmd Source #

Arguments

:: ByteString

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

-> Synchronous 
-> AutocmdOptions 
-> Neovim env ()

Fully applied function to register

-> Neovim env (Maybe (Either (Neovim anyEnv ()) 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. .

Note that the function you pass must be fully applied.

ask :: MonadReader r m => m r #

Retrieves the monad environment.

asks #

Arguments

:: MonadReader r m 
=> (r -> a)

The selector function to apply to the environment.

-> m a 

Retrieves a function of the current environment.

Creating a stateful plugin

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

import System.Random (newStdGen, randoms)
import UnliftIO.STM  (TVar, atomically, readTVar, modifyTVar, newTVarIO)

-- You may want to define a type alias for your plugin, so that if you change
-- your environment, you don't have to change all type signatures.
--
-- If I were to write a real plugin, I would probably also create a data type
-- instead of directly using a TVar here.
--
type MyNeovim a = Neovim (TVar [Int16]) a

-- This function will create an initial environment for our random number
-- generator. Note that the return type is the type of our environment.
randomNumbers :: Neovim startupEnv (TVar [Int16])
randomNumbers = do
    g <- liftIO newStdGen -- Create a new seed for a pseudo random number generator
    newTVarIO (randoms g) -- Put an infinite list of random numbers into a TVar

-- | Get the next random number and update the state of the list.
nextRandom :: MyNeovim Int16
nextRandom = do
    tVarWithRandomNumbers <- ask
    atomically $ do
        -- pick the head of our list of random numbers
        r <- head $ readTVar tVarWithRandomNumbers

        -- Since we do not want to return the same number all over the place
        -- remove the head of our list of random numbers
        modifyTVar tVarWithRandomNumbers tail

        return r


-- | You probably don't want this in a random number generator, but this shows
-- hoy you can edit the state of a stateful plugin.
setNextRandom :: Int16 -> MyNeovim ()
setNextRandom n = do
    tVarWithRandomNumbers <- ask

    -- cons n to the front of the infinite list
    atomically $ modifyTVar tVarWithRandomNumbers (n:)

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
    env <- randomNumbers
    wrapPlugin Plugin
        { environment = env
        , exports         =
          [ $(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. 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 () 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)

Calling remote functions

Calling remote functions is only possible inside a Neovim context. There are a few patterns of return values for the available functions. Let's start with getting some abstract Buffer object, test whether it is valid and then try to rename it.

inspectBuffer :: Neovim env ()
inspectBuffer = do
    cb <- vim_get_current_buffer
    isValid <- buffer_is_valid cb
    when isValid $ do
        let newName = "magic"
        cbName <- wait' $ buffer_set_name cb newName
        case () of
            _ | cbName == newName -> return ()
            _ -> err $ "Renaming the current buffer failed!"

You may have noticed the wait' function in there. Some functions have a return type with STM in it. This means that the function call is asynchronous. We can wait (or wait') for the result at the point at which we actually need it. In this short example, we put the wait' directly in front of the remote function call because we want to inspect the result immediately, though. The other functions either returned a result directly or they returned Either Object something whose result we inspected ourselves. The err function directly terminates the current thread and sends the given error message to neovim which the user immediately notices.

That's pretty much all there is to it.

wait :: Neovim env (STM result) -> Neovim env 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 env (STM result) -> Neovim env () Source #

Variant of wait that discards the result.

err :: Doc AnsiStyle -> Neovim env a Source #

throw specialized to a Pretty value.

data NeovimException Source #

Exceptions specific to nvim-hs.

Constructors

ErrorMessage (Doc AnsiStyle)

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 fromObject on this value could be converted to a value of NeovimExceptionGen.

Unsorted exports

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

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.

docToObject :: Doc AnsiStyle -> Object Source #

Convert a Doc-ument to a messagepack Object. This is more a convenience method to transport error message from and to neovim. It generally does not hold that 'docToObject . docFromObject' = id.

data Doc ann #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann.

More specifically, a value of type Doc 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.

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
Functor Doc

Alter the document’s annotations.

This instance makes Doc more flexible (because it can be used in Functor-polymorphic values), but fmap is much less readable compared to using reAnnotate in code that only works for Doc anyway. Consider using the latter when the type does not matter.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

fmap :: (a -> b) -> Doc a -> Doc b #

(<$) :: a -> Doc b -> Doc a #

Show (Doc ann)

(show doc) prettyprints document doc with defaultLayoutOptions, ignoring all annotations.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

showsPrec :: Int -> Doc ann -> ShowS #

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

IsString (Doc ann)
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Doc instance, and uses the same newline to line conversion.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

fromString :: String -> Doc ann #

Generic (Doc ann) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type #

Methods

from :: Doc ann -> Rep (Doc ann) x #

to :: Rep (Doc ann) x -> Doc ann #

Semigroup (Doc ann)
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

(<>) :: Doc ann -> Doc ann -> Doc ann #

sconcat :: NonEmpty (Doc ann) -> Doc ann #

stimes :: Integral b => b -> Doc ann -> Doc ann #

Monoid (Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

mempty :: Doc ann #

mappend :: Doc ann -> Doc ann -> Doc ann #

mconcat :: [Doc ann] -> Doc ann #

type Rep (Doc ann) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

type Rep (Doc ann) = D1 (MetaData "Doc" "Data.Text.Prettyprint.Doc.Internal" "prettyprinter-1.3.0-6qg3eRt5h66FauUzehlm4q" False) (((C1 (MetaCons "Fail" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Empty" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Char" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Char)))) :+: (C1 (MetaCons "Text" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: (C1 (MetaCons "Line" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "FlatAlt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 (MetaCons "Cat" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) :+: (C1 (MetaCons "Nest" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))) :+: C1 (MetaCons "Union" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 (MetaCons "Column" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 (MetaCons "WithPageWidth" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (PageWidth -> Doc ann)))) :+: (C1 (MetaCons "Nesting" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 (MetaCons "Annotated" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ann) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Doc ann)))))))

data AnsiStyle #

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
Eq AnsiStyle 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Terminal.Internal

Ord AnsiStyle 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Terminal.Internal

Show AnsiStyle 
Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Terminal.Internal

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:

color Red <> color Green

is red because the first color wins, and not bold because (or if) that’s the terminal’s default.

Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Terminal.Internal

Monoid AnsiStyle

mempty does nothing, which is equivalent to inheriting the style of the surrounding doc, or the terminal’s default if no style has been set yet.

Instance details

Defined in Data.Text.Prettyprint.Doc.Render.Terminal.Internal

class Pretty a where #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

prettyList :: [a] -> Doc ann #

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]
Instances
Pretty Bool
>>> pretty True
True
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char

Instead of (pretty '\n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Int8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Int16 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty Word 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty Word8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty ()
>>> pretty ()
()

The argument is not used,

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text

(lazy Doc instance, identical to the strict version)

Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: NvimMethod -> Doc ann #

prettyList :: [NvimMethod] -> Doc ann #

Pretty AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: AutocmdOptions -> Doc ann #

prettyList :: [AutocmdOptions] -> Doc ann #

Pretty CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: CommandOptions -> Doc ann #

prettyList :: [CommandOptions] -> Doc ann #

Pretty CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: CommandOption -> Doc ann #

prettyList :: [CommandOption] -> Doc ann #

Pretty Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: Synchronous -> Doc ann #

prettyList :: [Synchronous] -> Doc ann #

Pretty FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: FunctionName -> Doc ann #

prettyList :: [FunctionName] -> Doc ann #

Pretty Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: Notification -> Doc ann #

prettyList :: [Notification] -> Doc ann #

Pretty Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: Request -> Doc ann #

prettyList :: [Request] -> Doc ann #

Pretty FunctionCall Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: FunctionCall -> Doc ann #

prettyList :: [FunctionCall] -> Doc ann #

Pretty FunctionType Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

pretty :: FunctionType -> Doc ann #

prettyList :: [FunctionType] -> Doc ann #

Pretty Message Source # 
Instance details

Defined in Neovim.RPC.Classes

Methods

pretty :: Message -> Doc ann #

prettyList :: [Message] -> Doc ann #

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

putDoc :: Doc AnsiStyle -> IO () #

(putDoc doc) prettyprints document doc to standard output using defaultLayoutOptions.

>>> putDoc ("hello" <+> "world")
hello world
putDoc = hPutDoc stdout

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 
Instance details

Defined in System.Log

Enum Priority 
Instance details

Defined in System.Log

Eq Priority 
Instance details

Defined in System.Log

Ord Priority 
Instance details

Defined in System.Log

Read Priority 
Instance details

Defined in System.Log

Show Priority 
Instance details

Defined in System.Log

void :: Functor f => f a -> f () #

void value discards or ignores the result of evaluation, such as the return value of an IO action.

Examples

Expand

Replace the contents of a Maybe Int with unit:

>>> void Nothing
Nothing
>>> void (Just 3)
Just ()

Replace the contents of an Either Int Int with unit, resulting in an Either Int '()':

>>> void (Left 8675309)
Left 8675309
>>> void (Right 8675309)
Right ()

Replace every element of a list with unit:

>>> void [1,2,3]
[(),(),()]

Replace the second element of a pair with unit:

>>> void (1,2)
(1,())

Discard the result of an IO action:

>>> mapM print [1,2]
1
2
[(),()]
>>> void $ mapM print [1,2]
1
2

data Int8 #

8-bit signed integer type

Instances
Bounded Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

succ :: Int8 -> Int8 #

pred :: Int8 -> Int8 #

toEnum :: Int -> Int8 #

fromEnum :: Int8 -> Int #

enumFrom :: Int8 -> [Int8] #

enumFromThen :: Int8 -> Int8 -> [Int8] #

enumFromTo :: Int8 -> Int8 -> [Int8] #

enumFromThenTo :: Int8 -> Int8 -> Int8 -> [Int8] #

Eq Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int8 -> Int8 -> Bool #

(/=) :: Int8 -> Int8 -> Bool #

Integral Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

quot :: Int8 -> Int8 -> Int8 #

rem :: Int8 -> Int8 -> Int8 #

div :: Int8 -> Int8 -> Int8 #

mod :: Int8 -> Int8 -> Int8 #

quotRem :: Int8 -> Int8 -> (Int8, Int8) #

divMod :: Int8 -> Int8 -> (Int8, Int8) #

toInteger :: Int8 -> Integer #

Data Int8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int8 -> c Int8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int8 #

toConstr :: Int8 -> Constr #

dataTypeOf :: Int8 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int8) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int8) #

gmapT :: (forall b. Data b => b -> b) -> Int8 -> Int8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int8 -> m Int8 #

Num Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(+) :: Int8 -> Int8 -> Int8 #

(-) :: Int8 -> Int8 -> Int8 #

(*) :: Int8 -> Int8 -> Int8 #

negate :: Int8 -> Int8 #

abs :: Int8 -> Int8 #

signum :: Int8 -> Int8 #

fromInteger :: Integer -> Int8 #

Ord Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int8 -> Int8 -> Ordering #

(<) :: Int8 -> Int8 -> Bool #

(<=) :: Int8 -> Int8 -> Bool #

(>) :: Int8 -> Int8 -> Bool #

(>=) :: Int8 -> Int8 -> Bool #

max :: Int8 -> Int8 -> Int8 #

min :: Int8 -> Int8 -> Int8 #

Read Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int8 -> Rational #

Show Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int8 -> ShowS #

show :: Int8 -> String #

showList :: [Int8] -> ShowS #

Ix Int8

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

range :: (Int8, Int8) -> [Int8] #

index :: (Int8, Int8) -> Int8 -> Int #

unsafeIndex :: (Int8, Int8) -> Int8 -> Int

inRange :: (Int8, Int8) -> Int8 -> Bool #

rangeSize :: (Int8, Int8) -> Int #

unsafeRangeSize :: (Int8, Int8) -> Int

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

Hashable Int8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int8 -> Int #

hash :: Int8 -> Int #

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Bits Int8

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int8

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Serialize Int8 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int8 #

get :: Get Int8 #

Default Int8 
Instance details

Defined in Data.Default.Class

Methods

def :: Int8 #

NFData Int8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int8 -> () #

Pretty Int8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Unbox Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Int8 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int8 = MV_Int8 (MVector s Int8)

data Int16 #

16-bit signed integer type

Instances
Bounded Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int16 -> Int16 -> Bool #

(/=) :: Int16 -> Int16 -> Bool #

Integral Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int16

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int16 -> c Int16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int16 #

toConstr :: Int16 -> Constr #

dataTypeOf :: Int16 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int16) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int16) #

gmapT :: (forall b. Data b => b -> b) -> Int16 -> Int16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int16 -> m Int16 #

Num Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int16 -> Int16 -> Ordering #

(<) :: Int16 -> Int16 -> Bool #

(<=) :: Int16 -> Int16 -> Bool #

(>) :: Int16 -> Int16 -> Bool #

(>=) :: Int16 -> Int16 -> Bool #

max :: Int16 -> Int16 -> Int16 #

min :: Int16 -> Int16 -> Int16 #

Read Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int16 -> Rational #

Show Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int16 -> ShowS #

show :: Int16 -> String #

showList :: [Int16] -> ShowS #

Ix Int16

Since: base-2.1

Instance details

Defined in GHC.Int

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

Hashable Int16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int16 -> Int #

hash :: Int16 -> Int #

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Bits Int16

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int16

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Serialize Int16 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int16 #

get :: Get Int16 #

Default Int16 
Instance details

Defined in Data.Default.Class

Methods

def :: Int16 #

NFData Int16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int16 -> () #

Pretty Int16 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Unbox Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Int16 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int32 #

32-bit signed integer type

Instances
Bounded Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int32 -> Int32 -> Bool #

(/=) :: Int32 -> Int32 -> Bool #

Integral Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int32 -> c Int32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int32 #

toConstr :: Int32 -> Constr #

dataTypeOf :: Int32 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int32) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int32) #

gmapT :: (forall b. Data b => b -> b) -> Int32 -> Int32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int32 -> m Int32 #

Num Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int32 -> Int32 -> Ordering #

(<) :: Int32 -> Int32 -> Bool #

(<=) :: Int32 -> Int32 -> Bool #

(>) :: Int32 -> Int32 -> Bool #

(>=) :: Int32 -> Int32 -> Bool #

max :: Int32 -> Int32 -> Int32 #

min :: Int32 -> Int32 -> Int32 #

Read Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int32 -> Rational #

Show Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int32 -> ShowS #

show :: Int32 -> String #

showList :: [Int32] -> ShowS #

Ix Int32

Since: base-2.1

Instance details

Defined in GHC.Int

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

Hashable Int32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int32 -> Int #

hash :: Int32 -> Int #

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Bits Int32

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int32

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Serialize Int32 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int32 #

get :: Get Int32 #

Default Int32 
Instance details

Defined in Data.Default.Class

Methods

def :: Int32 #

NFData Int32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int32 -> () #

Pretty Int32 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Unbox Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Int32 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int32 
Instance details

Defined in Data.Vector.Unboxed.Base

data Int64 #

64-bit signed integer type

Instances
Bounded Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Enum Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Eq Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

(==) :: Int64 -> Int64 -> Bool #

(/=) :: Int64 -> Int64 -> Bool #

Integral Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Data Int64

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int64 -> c Int64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int64 #

toConstr :: Int64 -> Constr #

dataTypeOf :: Int64 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int64) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int64) #

gmapT :: (forall b. Data b => b -> b) -> Int64 -> Int64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int64 -> m Int64 #

Num Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Ord Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

compare :: Int64 -> Int64 -> Ordering #

(<) :: Int64 -> Int64 -> Bool #

(<=) :: Int64 -> Int64 -> Bool #

(>) :: Int64 -> Int64 -> Bool #

(>=) :: Int64 -> Int64 -> Bool #

max :: Int64 -> Int64 -> Int64 #

min :: Int64 -> Int64 -> Int64 #

Read Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Real Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

toRational :: Int64 -> Rational #

Show Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Methods

showsPrec :: Int -> Int64 -> ShowS #

show :: Int64 -> String #

showList :: [Int64] -> ShowS #

Ix Int64

Since: base-2.1

Instance details

Defined in GHC.Int

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

Hashable Int64 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Int64 -> Int #

hash :: Int64 -> Int #

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Bits Int64

Since: base-2.1

Instance details

Defined in GHC.Int

FiniteBits Int64

Since: base-4.6.0.0

Instance details

Defined in GHC.Int

Serialize Int64 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Int64 #

get :: Get Int64 #

Default Int64 
Instance details

Defined in Data.Default.Class

Methods

def :: Int64 #

NFData Int64 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Int64 -> () #

Pretty Int64 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Unbox Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Int64 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Int64 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word #

A Word is an unsigned integral type, with the same size as Int.

Instances
Bounded Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Enum Word

Since: base-2.1

Instance details

Defined in GHC.Enum

Methods

succ :: Word -> Word #

pred :: Word -> Word #

toEnum :: Int -> Word #

fromEnum :: Word -> Int #

enumFrom :: Word -> [Word] #

enumFromThen :: Word -> Word -> [Word] #

enumFromTo :: Word -> Word -> [Word] #

enumFromThenTo :: Word -> Word -> Word -> [Word] #

Eq Word 
Instance details

Defined in GHC.Classes

Methods

(==) :: Word -> Word -> Bool #

(/=) :: Word -> Word -> Bool #

Integral Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

quot :: Word -> Word -> Word #

rem :: Word -> Word -> Word #

div :: Word -> Word -> Word #

mod :: Word -> Word -> Word #

quotRem :: Word -> Word -> (Word, Word) #

divMod :: Word -> Word -> (Word, Word) #

toInteger :: Word -> Integer #

Data Word

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word -> c Word #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word #

toConstr :: Word -> Constr #

dataTypeOf :: Word -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word) #

gmapT :: (forall b. Data b => b -> b) -> Word -> Word #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word -> m Word #

Num Word

Since: base-2.1

Instance details

Defined in GHC.Num

Methods

(+) :: Word -> Word -> Word #

(-) :: Word -> Word -> Word #

(*) :: Word -> Word -> Word #

negate :: Word -> Word #

abs :: Word -> Word #

signum :: Word -> Word #

fromInteger :: Integer -> Word #

Ord Word 
Instance details

Defined in GHC.Classes

Methods

compare :: Word -> Word -> Ordering #

(<) :: Word -> Word -> Bool #

(<=) :: Word -> Word -> Bool #

(>) :: Word -> Word -> Bool #

(>=) :: Word -> Word -> Bool #

max :: Word -> Word -> Word #

min :: Word -> Word -> Word #

Read Word

Since: base-4.5.0.0

Instance details

Defined in GHC.Read

Real Word

Since: base-2.1

Instance details

Defined in GHC.Real

Methods

toRational :: Word -> Rational #

Show Word

Since: base-2.1

Instance details

Defined in GHC.Show

Methods

showsPrec :: Int -> Word -> ShowS #

show :: Word -> String #

showList :: [Word] -> ShowS #

Ix Word

Since: base-4.6.0.0

Instance details

Defined in GHC.Arr

Methods

range :: (Word, Word) -> [Word] #

index :: (Word, Word) -> Word -> Int #

unsafeIndex :: (Word, Word) -> Word -> Int

inRange :: (Word, Word) -> Word -> Bool #

rangeSize :: (Word, Word) -> Int #

unsafeRangeSize :: (Word, Word) -> Int

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word -> Q Exp #

Hashable Word 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word -> Int #

hash :: Word -> Int #

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Serialize Word 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Word #

get :: Get Word #

Default Word 
Instance details

Defined in Data.Default.Class

Methods

def :: Word #

NFData Word 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word -> () #

Pretty Word 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Prim Word 
Instance details

Defined in Data.Primitive.Types

Unbox Word 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Word Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

Generic1 (URec Word :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec Word) :: k -> Type #

Methods

from1 :: URec Word a -> Rep1 (URec Word) a #

to1 :: Rep1 (URec Word) a -> URec Word a #

Functor (URec Word :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec Word a -> URec Word b #

(<$) :: a -> URec Word b -> URec Word a #

Foldable (URec Word :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => URec Word m -> m #

foldMap :: Monoid m => (a -> m) -> URec Word a -> m #

foldr :: (a -> b -> b) -> b -> URec Word a -> b #

foldr' :: (a -> b -> b) -> b -> URec Word a -> b #

foldl :: (b -> a -> b) -> b -> URec Word a -> b #

foldl' :: (b -> a -> b) -> b -> URec Word a -> b #

foldr1 :: (a -> a -> a) -> URec Word a -> a #

foldl1 :: (a -> a -> a) -> URec Word a -> a #

toList :: URec Word a -> [a] #

null :: URec Word a -> Bool #

length :: URec Word a -> Int #

elem :: Eq a => a -> URec Word a -> Bool #

maximum :: Ord a => URec Word a -> a #

minimum :: Ord a => URec Word a -> a #

sum :: Num a => URec Word a -> a #

product :: Num a => URec Word a -> a #

Traversable (URec Word :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> URec Word a -> f (URec Word b) #

sequenceA :: Applicative f => URec Word (f a) -> f (URec Word a) #

mapM :: Monad m => (a -> m b) -> URec Word a -> m (URec Word b) #

sequence :: Monad m => URec Word (m a) -> m (URec Word a) #

Eq (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec Word p -> URec Word p -> Bool #

(/=) :: URec Word p -> URec Word p -> Bool #

Ord (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec Word p -> URec Word p -> Ordering #

(<) :: URec Word p -> URec Word p -> Bool #

(<=) :: URec Word p -> URec Word p -> Bool #

(>) :: URec Word p -> URec Word p -> Bool #

(>=) :: URec Word p -> URec Word p -> Bool #

max :: URec Word p -> URec Word p -> URec Word p #

min :: URec Word p -> URec Word p -> URec Word p #

Show (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

showsPrec :: Int -> URec Word p -> ShowS #

show :: URec Word p -> String #

showList :: [URec Word p] -> ShowS #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: Type -> Type #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

newtype Vector Word 
Instance details

Defined in Data.Vector.Unboxed.Base

data URec Word (p :: k)

Used for marking occurrences of Word#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec Word (p :: k) = UWord {}
newtype MVector s Word 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype MVector s Word = MV_Word (MVector s Word)
type Rep1 (URec Word :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec Word :: k -> Type) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UWord :: k -> Type)))
type Rep (URec Word p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec Word p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UWord" PrefixI True) (S1 (MetaSel (Just "uWord#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UWord :: Type -> Type)))

data Word8 #

8-bit unsigned integer type

Instances
Bounded Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word8 -> Word8 -> Bool #

(/=) :: Word8 -> Word8 -> Bool #

Integral Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word8

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word8 -> c Word8 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word8 #

toConstr :: Word8 -> Constr #

dataTypeOf :: Word8 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word8) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word8) #

gmapT :: (forall b. Data b => b -> b) -> Word8 -> Word8 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word8 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word8 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word8 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word8 -> m Word8 #

Num Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

compare :: Word8 -> Word8 -> Ordering #

(<) :: Word8 -> Word8 -> Bool #

(<=) :: Word8 -> Word8 -> Bool #

(>) :: Word8 -> Word8 -> Bool #

(>=) :: Word8 -> Word8 -> Bool #

max :: Word8 -> Word8 -> Word8 #

min :: Word8 -> Word8 -> Word8 #

Read Word8

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

toRational :: Word8 -> Rational #

Show Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

showsPrec :: Int -> Word8 -> ShowS #

show :: Word8 -> String #

showList :: [Word8] -> ShowS #

Ix Word8

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

Hashable Word8 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word8 -> Int #

hash :: Word8 -> Int #

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Bits Word8

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word8

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Serialize Word8 
Instance details

Defined in Data.Serialize

Methods

put :: Putter Word8 #

get :: Get Word8 #

Default Word8 
Instance details

Defined in Data.Default.Class

Methods

def :: Word8 #

NFData Word8 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word8 -> () #

Pretty Word8 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Prim Word8 
Instance details

Defined in Data.Primitive.Types

ByteSource Word8 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) :: ByteSink Word8 g -> Word8 -> g

Unbox Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Word8 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word8 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word8 g = Takes1Byte g
newtype MVector s Word8 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word16 #

16-bit unsigned integer type

Instances
Bounded Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word16 -> Word16 -> Bool #

(/=) :: Word16 -> Word16 -> Bool #

Integral Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word16

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word16 -> c Word16 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word16 #

toConstr :: Word16 -> Constr #

dataTypeOf :: Word16 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word16) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word16) #

gmapT :: (forall b. Data b => b -> b) -> Word16 -> Word16 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word16 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word16 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word16 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word16 -> m Word16 #

Num Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word16

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word16

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

Hashable Word16 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word16 -> Int #

hash :: Word16 -> Int #

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word16

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word16

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Serialize Word16 
Instance details

Defined in Data.Serialize

Default Word16 
Instance details

Defined in Data.Default.Class

Methods

def :: Word16 #

NFData Word16 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word16 -> () #

Pretty Word16 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Prim Word16 
Instance details

Defined in Data.Primitive.Types

ByteSource Word16 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) :: ByteSink Word16 g -> Word16 -> g

Unbox Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Word16 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word16 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word16 g = Takes2Bytes g
newtype MVector s Word16 
Instance details

Defined in Data.Vector.Unboxed.Base

data Word32 #

32-bit unsigned integer type

Instances
Bounded Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Enum Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Eq Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Methods

(==) :: Word32 -> Word32 -> Bool #

(/=) :: Word32 -> Word32 -> Bool #

Integral Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Data Word32

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word32 -> c Word32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word32 #

toConstr :: Word32 -> Constr #

dataTypeOf :: Word32 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Word32) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word32) #

gmapT :: (forall b. Data b => b -> b) -> Word32 -> Word32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word32 -> m Word32 #

Num Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ord Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Read Word32

Since: base-2.1

Instance details

Defined in GHC.Read

Real Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Show Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Ix Word32

Since: base-2.1

Instance details

Defined in GHC.Word

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

Hashable Word32 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Word32 -> Int #

hash :: Word32 -> Int #

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Bits Word32

Since: base-2.1

Instance details

Defined in GHC.Word

FiniteBits Word32

Since: base-4.6.0.0

Instance details

Defined in GHC.Word

Serialize Word32 
Instance details

Defined in Data.Serialize

Default Word32 
Instance details

Defined in Data.Default.Class

Methods

def :: Word32 #

NFData Word32 
Instance details

Defined in Control.DeepSeq

Methods

rnf :: Word32 -> () #

Pretty Word32 
Instance details

Defined in Data.Text.Prettyprint.Doc.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Prim Word32 
Instance details

Defined in Data.Primitive.Types

ByteSource Word32 
Instance details

Defined in Data.UUID.Types.Internal.Builder

Methods

(/-/) :: ByteSink Word32 g -> Word32 -> g

Unbox Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

NvimObject Word32 Source # 
Instance details

Defined in Neovim.Classes

Vector Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

MVector MVector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

newtype Vector Word32 
Instance details

Defined in Data.Vector.Unboxed.Base

type ByteSink Word32 g 
Instance details

Defined in Data.UUID.Types.Internal.Builder

type ByteSink Word32 g = Takes4Bytes g
newtype MVector s Word32 
Instance details

Defined in Data.Vector.Unboxed.Base