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

Neovim.Context

Description

 
Synopsis

Documentation

newUniqueFunctionName :: Neovim env FunctionName Source #

Create a new unique function name. To prevent possible name clashes, digits are stripped from the given suffix.

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

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

MonadFail (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

fail :: String -> Neovim env a #

MonadIO (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

liftIO :: IO a -> 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 #

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 #

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 #

MonadThrow (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

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

MonadUnliftIO (Neovim env) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

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

Monoid a => Monoid (Neovim env a) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

mempty :: Neovim env a #

mappend :: Neovim env a -> Neovim env a -> Neovim env a #

mconcat :: [Neovim env a] -> Neovim env a #

Semigroup a => Semigroup (Neovim env a) Source # 
Instance details

Defined in Neovim.Context.Internal

Methods

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

sconcat :: NonEmpty (Neovim env a) -> Neovim env a #

stimes :: Integral b => b -> Neovim env a -> Neovim env a #

data NeovimException Source #

Exceptions specific to nvim-hs.

Constructors

ErrorMessage (Doc AnsiStyle)

Simple error message that is passed to neovim. It should currently only contain one line of text.

ErrorResult (Doc AnsiStyle) Object

Error that can be returned by a remote API call. The Doc argument is the name of the remote function that threw this exception.

type FunctionMap = Map NvimMethod FunctionMapEntry Source #

A function map is a map containing the names of functions as keys and some context dependent value which contains all the necessary information to execute that function in the intended way.

This type is only used internally and handles two distinct cases. One case is a direct function call, wich is simply a function that accepts a list of Object values and returns a result in the Neovim context. The second case is calling a function that has a persistent state. This is mediated to a thread that reads from a TQueue. (NB: persistent currently means, that state is stored for as long as the plugin provider is running and not restarted.)

type FunctionMapEntry = (FunctionalityDescription, FunctionType) Source #

Type of the values stored in the function map.

mkFunctionMap :: [FunctionMapEntry] -> FunctionMap Source #

Create a new function map from the given list of FunctionMapEntry values.

runNeovim :: NFData a => Config env -> Neovim env a -> IO (Either (Doc AnsiStyle) a) Source #

Initialize a Neovim context by supplying an InternalEnvironment.

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

throw specialized to a Pretty value.

restart :: Neovim env () Source #

Initiate a restart of the plugin provider.

quit :: Neovim env () Source #

Initiate the termination of the plugin provider.

subscribe :: Text -> ([Object] -> Neovim env ()) -> Neovim env Subscription Source #

Subscribe to an event. When the event is received, the given callback function is run. It is usually necessary to call the appropriate API function in order for neovim to send the notifications to nvim-hs. The returned subscription can be used to unsubscribe.

unsubscribe :: Subscription -> Neovim env () Source #

Remove the subscription that has been returned by subscribe.

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.

get :: MonadState s m => m s #

Return the state from the internals of the monad.

gets :: MonadState s m => (s -> a) -> m a #

Gets specific component of the state, using a projection function supplied.

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

Replace the state inside the monad.

modify :: MonadState s m => (s -> s) -> m () #

Monadic state transformer.

Maps an old state to a new state inside a state monad. The old state is thrown away.

     Main> :t modify ((+1) :: Int -> Int)
     modify (...) :: (MonadState Int a) => a ()

This says that modify (+1) acts over any Monad that is a member of the MonadState class, with an Int state.

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

Instances details
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 Prettyprinter.Internal

Methods

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

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

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 Prettyprinter.Internal

Methods

fromString :: String -> Doc ann #

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

Defined in Prettyprinter.Internal

Methods

mempty :: Doc ann #

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

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

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

Defined in Prettyprinter.Internal

Methods

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

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

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

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

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

Methods

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

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

Show (Doc ann)

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

Instance details

Defined in Prettyprinter.Internal

Methods

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

show :: Doc ann -> String #

showList :: [Doc ann] -> ShowS #

type Rep (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

type Rep (Doc ann) = D1 ('MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-Fnq1Vt2JMTY81kvR0W9kdP" '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

Instances details
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 Prettyprinter.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 Prettyprinter.Render.Terminal.Internal

Show AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Eq AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

Ord AnsiStyle 
Instance details

Defined in Prettyprinter.Render.Terminal.Internal

throwError :: MonadError e m => e -> m a #

Is used within a monadic computation to begin exception processing.