ribosome-0.4.0.0: api extensions for nvim-hs
Safe HaskellNone
LanguageHaskell2010

Ribosome.Msgpack.Encode

Documentation

class MsgpackEncode a where Source #

Minimal complete definition

Nothing

Methods

toMsgpack :: a -> Object Source #

default toMsgpack :: (Generic a, GMsgpackEncode (Rep a)) => a -> Object Source #

Instances

Instances details
MsgpackEncode Bool Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode Double Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode Float Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode Int Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: Int -> Object Source #

MsgpackEncode Int64 Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode () Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: () -> Object Source #

MsgpackEncode ByteString Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode String Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode Text Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode Object Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

MsgpackEncode FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatAnchor Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatRelative Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode Window Source # 
Instance details

Defined in Ribosome.Nvim.Api.Data

MsgpackEncode Tabpage Source # 
Instance details

Defined in Ribosome.Nvim.Api.Data

MsgpackEncode Buffer Source # 
Instance details

Defined in Ribosome.Nvim.Api.Data

MsgpackEncode WindowConfig Source # 
Instance details

Defined in Ribosome.Data.WindowConfig

MsgpackEncode RegisterType Source # 
Instance details

Defined in Ribosome.Data.RegisterType

MsgpackEncode Register Source # 
Instance details

Defined in Ribosome.Data.Register

MsgpackEncode a => MsgpackEncode [a] Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: [a] -> Object Source #

MsgpackEncode a => MsgpackEncode (Maybe a) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: Maybe a -> Object Source #

MsgpackEncode a => MsgpackEncode (NonEmpty a) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

(MsgpackEncode a, MsgpackEncode b) => MsgpackEncode (a, b) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: (a, b) -> Object Source #

(MsgpackEncode k, MsgpackEncode v) => MsgpackEncode (Map k v) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: Map k v -> Object Source #

MsgpackEncode (Path b t) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

toMsgpack :: Path b t -> Object Source #

class GMsgpackEncode f where Source #

Methods

gMsgpackEncode :: f a -> Object Source #

Instances

Instances details
(GMsgpackEncode f, GMsgpackEncode g) => GMsgpackEncode (f :+: g :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

gMsgpackEncode :: forall (a :: k0). (f :+: g) a -> Object Source #

GMsgpackEncode f => GMsgpackEncode (D1 c f :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

gMsgpackEncode :: forall (a :: k0). D1 c f a -> Object Source #

MsgpackEncode a => GMsgpackEncode (K1 i a :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

gMsgpackEncode :: forall (a0 :: k0). K1 i a a0 -> Object Source #

(Constructor c, MsgpackEncodeProd f) => GMsgpackEncode (C1 c f :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

gMsgpackEncode :: forall (a :: k0). C1 c f a -> Object Source #

class MsgpackEncodeProd f where Source #

Instances

Instances details
(Selector s, GMsgpackEncode f) => MsgpackEncodeProd (S1 s f :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

msgpackEncodeRecord :: forall (a :: k0). S1 s f a -> [(String, Object)] Source #

msgpackEncodeProd :: forall (a :: k0). S1 s f a -> [Object] Source #

(MsgpackEncodeProd f, MsgpackEncodeProd g) => MsgpackEncodeProd (f :*: g :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Encode

Methods

msgpackEncodeRecord :: forall (a :: k0). (f :*: g) a -> [(String, Object)] Source #

msgpackEncodeProd :: forall (a :: k0). (f :*: g) a -> [Object] Source #

Orphan instances

IsString Object Source # 
Instance details

Methods

fromString :: String -> Object #