nvim-hs-0.2.5: Haskell plugin backend for neovim

Copyright(c) Sebastian Witte
LicenseApache-2.0
Maintainerwoozletoff@gmail.com
Stabilityexperimental
PortabilityGHC
Safe HaskellNone
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 ByteString FunctionName 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
  • Options for the autocmd (use def here if you don't want to change anything)

Instances

Eq FunctionalityDescription Source # 
Ord FunctionalityDescription Source # 
Read FunctionalityDescription Source # 
Show FunctionalityDescription Source # 
Generic FunctionalityDescription Source # 
Pretty FunctionalityDescription Source # 
NFData FunctionalityDescription Source # 
HasFunctionName FunctionalityDescription Source # 
type Rep FunctionalityDescription Source # 

newtype FunctionName Source #

Essentially just a string.

Constructors

F ByteString 

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 # 
Eq Synchronous Source # 
Ord Synchronous Source # 
Read Synchronous Source # 
Show Synchronous Source # 
IsString Synchronous Source # 
Generic Synchronous Source # 

Associated Types

type Rep Synchronous :: * -> * #

Pretty Synchronous Source # 
NFData Synchronous Source # 

Methods

rnf :: Synchronous -> () #

NvimObject Synchronous Source # 
type Rep Synchronous Source # 
type Rep Synchronous = D1 * (MetaData "Synchronous" "Neovim.Plugin.Classes" "nvim-hs-0.2.5-Jju5PaldQ6jL5dqBGEr7IX" False) ((:+:) * (C1 * (MetaCons "Async" PrefixI False) (U1 *)) (C1 * (MetaCons "Sync" PrefixI False) (U1 *)))

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

Instances

Eq CommandOption Source # 
Ord CommandOption Source # 
Read CommandOption Source # 
Show CommandOption Source # 
IsString CommandOption Source # 
Generic CommandOption Source # 

Associated Types

type Rep CommandOption :: * -> * #

Pretty CommandOption Source # 
NFData CommandOption Source # 

Methods

rnf :: CommandOption -> () #

type Rep CommandOption Source # 

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

Eq CommandOptions Source # 
Ord CommandOptions Source # 
Read CommandOptions Source # 
Show CommandOptions Source # 
Generic CommandOptions Source # 

Associated Types

type Rep CommandOptions :: * -> * #

Pretty CommandOptions Source # 
NFData CommandOptions Source # 

Methods

rnf :: CommandOptions -> () #

NvimObject CommandOptions Source # 
type Rep CommandOptions Source # 
type Rep CommandOptions = D1 * (MetaData "CommandOptions" "Neovim.Plugin.Classes" "nvim-hs-0.2.5-Jju5PaldQ6jL5dqBGEr7IX" True) (C1 * (MetaCons "CommandOptions" PrefixI True) (S1 * (MetaSel (Just Symbol "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

Eq RangeSpecification Source # 
Ord RangeSpecification Source # 
Read RangeSpecification Source # 
Show RangeSpecification Source # 
Generic RangeSpecification Source # 
Pretty RangeSpecification Source # 
NFData RangeSpecification Source # 

Methods

rnf :: RangeSpecification -> () #

NvimObject RangeSpecification Source # 
type Rep RangeSpecification Source # 
type Rep RangeSpecification = D1 * (MetaData "RangeSpecification" "Neovim.Plugin.Classes" "nvim-hs-0.2.5-Jju5PaldQ6jL5dqBGEr7IX" False) ((:+:) * (C1 * (MetaCons "CurrentLine" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "WholeFile" PrefixI False) (U1 *)) (C1 * (MetaCons "RangeCount" PrefixI False) (S1 * (MetaSel (Nothing 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 # 
Ord CommandArguments Source # 
Read CommandArguments Source # 
Show CommandArguments Source # 
Generic CommandArguments Source # 
Pretty CommandArguments Source # 
Default CommandArguments Source # 
NFData CommandArguments Source # 

Methods

rnf :: CommandArguments -> () #

NvimObject CommandArguments Source # 
type Rep CommandArguments Source # 

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

Eq AutocmdOptions Source # 
Ord AutocmdOptions Source # 
Read AutocmdOptions Source # 
Show AutocmdOptions Source # 
Generic AutocmdOptions Source # 

Associated Types

type Rep AutocmdOptions :: * -> * #

Pretty AutocmdOptions Source # 
Default AutocmdOptions Source # 

Methods

def :: AutocmdOptions #

NFData AutocmdOptions Source # 

Methods

rnf :: AutocmdOptions -> () #

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

class HasFunctionName a where Source #

Conveniennce class to extract a name from some value.

Minimal complete definition

name

Methods

name :: a -> FunctionName Source #