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

Ribosome.Msgpack.Decode

Documentation

class MsgpackDecode a where Source #

Minimal complete definition

Nothing

Instances

Instances details
MsgpackDecode Bool Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Char Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Double Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Float Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Int Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Int64 Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode () Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode ByteString Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode String Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Text Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Object Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode CommandArguments Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

MsgpackDecode Window Source # 
Instance details

Defined in Ribosome.Nvim.Api.Data

MsgpackDecode Tabpage Source # 
Instance details

Defined in Ribosome.Nvim.Api.Data

MsgpackDecode Buffer Source # 
Instance details

Defined in Ribosome.Nvim.Api.Data

MsgpackDecode WindowConfig Source # 
Instance details

Defined in Ribosome.Data.WindowConfig

MsgpackDecode RegisterType Source # 
Instance details

Defined in Ribosome.Data.RegisterType

MsgpackDecode Register Source # 
Instance details

Defined in Ribosome.Data.Register

MsgpackDecode NvimMode Source # 
Instance details

Defined in Ribosome.Api.Mode

MsgpackDecode AtomicStatus Source # 
Instance details

Defined in Ribosome.Api.Atomic

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

Defined in Ribosome.Msgpack.Decode

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

Defined in Ribosome.Msgpack.Decode

(MsgpackDecode a, MsgpackDecode b) => MsgpackDecode (Either a b) Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

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

Defined in Ribosome.Msgpack.Decode

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

Defined in Ribosome.Msgpack.Decode

DecodePath b t => MsgpackDecode (Path b t) Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

class GMsgpackDecode f where Source #

Minimal complete definition

gMsgpackDecode

Instances

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

Defined in Ribosome.Msgpack.Decode

Methods

gMsgpackDecode :: forall (a :: k0). Object -> Either Err ((f :+: g) a) Source #

gMissingKey :: forall (a :: k0). String -> Object -> Either Err ((f :+: g) a) Source #

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

Defined in Ribosome.Msgpack.Decode

Methods

gMsgpackDecode :: forall (a :: k0). Object -> Either Err (D1 c f a) Source #

gMissingKey :: forall (a :: k0). String -> Object -> Either Err (D1 c f a) Source #

MsgpackDecode a => GMsgpackDecode (K1 i a :: k -> Type) Source # 
Instance details

Defined in Ribosome.Msgpack.Decode

Methods

gMsgpackDecode :: forall (a0 :: k0). Object -> Either Err (K1 i a a0) Source #

gMissingKey :: forall (a0 :: k0). String -> Object -> Either Err (K1 i a a0) Source #

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

Defined in Ribosome.Msgpack.Decode

Methods

gMsgpackDecode :: forall (a :: k0). Object -> Either Err (C1 c f a) Source #

gMissingKey :: forall (a :: k0). String -> Object -> Either Err (C1 c f a) Source #

class MsgpackDecodeProd f where Source #

Instances

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

Defined in Ribosome.Msgpack.Decode

Methods

msgpackDecodeRecord :: forall (a :: k0). Map Object Object -> Either Err (S1 s f a) Source #

msgpackDecodeProd :: forall (a :: k0). [Object] -> Either Err ([Object], S1 s f a) Source #

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

Defined in Ribosome.Msgpack.Decode

Methods

msgpackDecodeRecord :: forall (a :: k0). Map Object Object -> Either Err ((f :*: g) a) Source #

msgpackDecodeProd :: forall (a :: k0). [Object] -> Either Err ([Object], (f :*: g) a) Source #

decodePathE :: forall b t. DecodePath b t => Text -> Either Err (Path b t) Source #

fromMsgpack' :: forall a e m. MonadDeepError e DecodeError m => MsgpackDecode a => Object -> m a Source #