nvim-hs-2.3.2.0: Haskell plugin backend for neovim
Copyright(c) Sebastian Witte
LicenseApache-2.0
Maintainerwoozletoff@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Neovim.Plugin.Classes

Description

 
Synopsis

Documentation

data FunctionalityDescription Source #

Functionality specific functional description entries.

All fields which are directly specified in these constructors are not optional, but can partialy be generated via the Template Haskell functions. The last field is a data type that contains all relevant options with sensible defaults, hence def can be used as an argument.

Constructors

Function FunctionName Synchronous

Exported function. Callable via call name(arg1,arg2).

  • Name of the function (must start with an uppercase letter)
  • Option to indicate how neovim should behave when calling this function
Command FunctionName CommandOptions

Exported Command. Callable via :Name arg1 arg2.

  • Name of the command (must start with an uppercase letter)
  • Options to configure neovim's behavior for calling the command
Autocmd Text FunctionName Synchronous AutocmdOptions

Exported autocommand. Will call the given function if the type and filter match.

NB: Since we are registering this on the Haskell side of things, the number of accepted arguments should be 0.

  • Type of the autocmd (e.g. "BufWritePost")
  • Name for the function to call
  • Whether to use rpcrequest or rpcnotify
  • Options for the autocmd (use def here if you don't want to change anything)

Instances

Instances details
Generic FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep FunctionalityDescription :: Type -> Type #

Read FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Eq FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

HasFunctionName FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep FunctionalityDescription Source # 
Instance details

Defined in Neovim.Plugin.Classes

newtype FunctionName Source #

Essentially just a string.

Constructors

F Text 

Instances

Instances details
Generic FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep FunctionName :: Type -> Type #

Read FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: FunctionName -> () #

Eq FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord FunctionName 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 #

type Rep FunctionName Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep FunctionName = D1 ('MetaData "FunctionName" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" 'True) (C1 ('MetaCons "F" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype NeovimEventId Source #

Constructors

NeovimEventId Text 

Instances

Instances details
Generic NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep NeovimEventId :: Type -> Type #

Read NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: NeovimEventId -> () #

Eq NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: NeovimEventId -> Doc ann #

prettyList :: [NeovimEventId] -> Doc ann #

type Rep NeovimEventId Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep NeovimEventId = D1 ('MetaData "NeovimEventId" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" 'True) (C1 ('MetaCons "NeovimEventId" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype SubscriptionId Source #

Constructors

SubscriptionId Int64 

Instances

Instances details
Enum SubscriptionId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Read SubscriptionId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show SubscriptionId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Eq SubscriptionId Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord SubscriptionId Source # 
Instance details

Defined in Neovim.Plugin.Classes

newtype NvimMethod Source #

Constructors

NvimMethod 

Fields

Instances

Instances details
Generic NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep NvimMethod :: Type -> Type #

Read NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: NvimMethod -> () #

Eq NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: NvimMethod -> Doc ann #

prettyList :: [NvimMethod] -> Doc ann #

type Rep NvimMethod Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep NvimMethod = D1 ('MetaData "NvimMethod" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" 'True) (C1 ('MetaCons "NvimMethod" 'PrefixI 'True) (S1 ('MetaSel ('Just "nvimMethodName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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

Instances details
IsString Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Enum 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 #

Read Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: Synchronous -> () #

Eq Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: Synchronous -> Doc ann #

prettyList :: [Synchronous] -> Doc ann #

type Rep Synchronous Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep Synchronous = D1 ('MetaData "Synchronous" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" '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: "\""

CmdNargs String

Command takes a specific amount of arguments

Automatically set via template haskell functions. You really shouldn't use this option yourself unless you have to.

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

CmdComplete String

Verbatim string passed to the -complete= command attribute

Instances

Instances details
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 #

Read CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: CommandOption -> () #

Eq CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord CommandOption Source # 
Instance details

Defined in Neovim.Plugin.Classes

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 CommandOptions Source #

Newtype wrapper for a list of CommandOption. Any properly constructed object of this type is sorted and only contains zero or one object for each possible option.

Instances

Instances details
Generic CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandOptions :: Type -> Type #

Read CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: CommandOptions -> () #

Eq CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandOptions 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 #

type Rep CommandOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep CommandOptions = D1 ('MetaData "CommandOptions" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" 'True) (C1 ('MetaCons "CommandOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCommandOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CommandOption])))

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

Instances details
Generic RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep RangeSpecification :: Type -> Type #

Read RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: RangeSpecification -> () #

Eq RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject RangeSpecification Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty 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.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" '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

Instances details
Generic CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep CommandArguments :: Type -> Type #

Read CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Default CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

NFData CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

rnf :: CommandArguments -> () #

Eq CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep CommandArguments Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep CommandArguments = D1 ('MetaData "CommandArguments" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" 'False) (C1 ('MetaCons "CommandArguments" 'PrefixI 'True) ((S1 ('MetaSel ('Just "bang") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool)) :*: S1 ('MetaSel ('Just "range") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Int, Int)))) :*: (S1 ('MetaSel ('Just "count") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "register") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe String)))))

mkCommandOptions :: [CommandOption] -> CommandOptions Source #

Smart constructor for CommandOptions. This sorts the command options and removes duplicate entries for semantically the same thing. Note that the smallest option stays for whatever ordering is defined. It is best to simply not define the same thing multiple times.

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

Instances details
Generic AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Associated Types

type Rep AutocmdOptions :: Type -> Type #

Read AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Show AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

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 -> () #

Eq AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Ord AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

NvimObject AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Pretty AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

Methods

pretty :: AutocmdOptions -> Doc ann #

prettyList :: [AutocmdOptions] -> Doc ann #

type Rep AutocmdOptions Source # 
Instance details

Defined in Neovim.Plugin.Classes

type Rep AutocmdOptions = D1 ('MetaData "AutocmdOptions" "Neovim.Plugin.Classes" "nvim-hs-2.3.2.0-LwjpNNRb9LEEjbgeMCdSQ3" '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)))))