nvim-hs-2.1.0.4: Haskell plugin backend for neovim

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

Neovim.Plugin.IPC.Classes

Description

 
Synopsis

Documentation

data SomeMessage Source #

Taken from xmonad and based on ideas in /An Extensible Dynamically-Typed Hierarchy of Exceptions/, Simon Marlow, 2006.

User-extensible messages must be put into a value of this type, so that it can be sent to other plugins.

Constructors

Message msg => SomeMessage msg 

class (NFData message, Typeable message) => Message message where Source #

This class allows type safe casting of SomeMessage to an actual message. The cast is successful if the type you're expecting matches the type in the SomeMessage wrapper. This way, you can subscribe to an arbitrary message type withouth having to pattern match on the constructors. This also allows plugin authors to create their own message types without having to change the core code of nvim-hs.

Minimal complete definition

Nothing

Methods

fromMessage :: SomeMessage -> Maybe message Source #

Try to convert a given message to a value of the message type we are interested in. Will evaluate to Nothing for any other type.

data FunctionCall Source #

Haskell representation of supported Remote Procedure Call messages.

Constructors

FunctionCall FunctionName [Object] (TMVar (Either Object Object)) UTCTime

Method name, parameters, callback, timestamp

data Request Source #

A request is a data type containing the method to call, its arguments and an identifier used to map the result to the function that has been called.

Constructors

Request 

Fields

Instances
Eq Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

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

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

Ord Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Show Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Generic Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Associated Types

type Rep Request :: Type -> Type #

Methods

from :: Request -> Rep Request x #

to :: Rep Request x -> Request #

NFData Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

rnf :: Request -> () #

Pretty Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: Request -> Doc ann #

prettyList :: [Request] -> Doc ann #

Message Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

type Rep Request Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

type Rep Request = D1 (MetaData "Request" "Neovim.Plugin.IPC.Classes" "nvim-hs-2.1.0.4-LZS7wAistQIJp35oFvAkCz" False) (C1 (MetaCons "Request" PrefixI True) (S1 (MetaSel (Just "reqMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FunctionName) :*: (S1 (MetaSel (Just "reqId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int64) :*: S1 (MetaSel (Just "reqArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Object]))))

data Notification Source #

A notification is similar to a Request. It essentially does the same thing, but the function is only called for its side effects. This type of message is sent by neovim if the caller there does not care about the result of the computation.

Constructors

Notification 

Fields

Instances
Eq Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Ord Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Show Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Generic Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Associated Types

type Rep Notification :: Type -> Type #

NFData Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

rnf :: Notification -> () #

Pretty Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

Methods

pretty :: Notification -> Doc ann #

prettyList :: [Notification] -> Doc ann #

Message Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

type Rep Notification Source # 
Instance details

Defined in Neovim.Plugin.IPC.Classes

type Rep Notification = D1 (MetaData "Notification" "Neovim.Plugin.IPC.Classes" "nvim-hs-2.1.0.4-LZS7wAistQIJp35oFvAkCz" False) (C1 (MetaCons "Notification" PrefixI True) (S1 (MetaSel (Just "notMethod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FunctionName) :*: S1 (MetaSel (Just "notArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Object])))

writeMessage :: (MonadIO m, Message message) => TQueue SomeMessage -> message -> m () Source #

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances
Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
Instance details

Defined in Data.Time.Format

ParseTime UTCTime 
Instance details

Defined in Data.Time.Format.Parse

getCurrentTime :: IO UTCTime #

Get the current UTCTime from the system clock.

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

Uniform Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformM :: StatefulGen g m => g -> m Int64 #

UniformRange Int64 
Instance details

Defined in System.Random.Internal

Methods

uniformRM :: StatefulGen g m => (Int64, Int64) -> g -> m Int64 #

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