-- |RPC message execution
module Ribosome.Host.Data.Execution where

import Ribosome.Host.Class.Msgpack.Decode (MsgpackDecode (fromMsgpack))
import Ribosome.Host.Class.Msgpack.Encode (MsgpackEncode (toMsgpack))

-- |This type indicates the execution style that Neovim should be instructed to use for RPC messages – synchronous
-- requests that block Neovim until a result is returned and asynchronous notifications.
--
-- 
data Execution =
  -- |RPC Request
  Sync
  |
  -- |RPC Notification
  Async
  deriving stock (Execution -> Execution -> Bool
(Execution -> Execution -> Bool)
-> (Execution -> Execution -> Bool) -> Eq Execution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Execution -> Execution -> Bool
$c/= :: Execution -> Execution -> Bool
== :: Execution -> Execution -> Bool
$c== :: Execution -> Execution -> Bool
Eq, Int -> Execution -> ShowS
[Execution] -> ShowS
Execution -> String
(Int -> Execution -> ShowS)
-> (Execution -> String)
-> ([Execution] -> ShowS)
-> Show Execution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Execution] -> ShowS
$cshowList :: [Execution] -> ShowS
show :: Execution -> String
$cshow :: Execution -> String
showsPrec :: Int -> Execution -> ShowS
$cshowsPrec :: Int -> Execution -> ShowS
Show, Int -> Execution
Execution -> Int
Execution -> [Execution]
Execution -> Execution
Execution -> Execution -> [Execution]
Execution -> Execution -> Execution -> [Execution]
(Execution -> Execution)
-> (Execution -> Execution)
-> (Int -> Execution)
-> (Execution -> Int)
-> (Execution -> [Execution])
-> (Execution -> Execution -> [Execution])
-> (Execution -> Execution -> [Execution])
-> (Execution -> Execution -> Execution -> [Execution])
-> Enum Execution
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Execution -> Execution -> Execution -> [Execution]
$cenumFromThenTo :: Execution -> Execution -> Execution -> [Execution]
enumFromTo :: Execution -> Execution -> [Execution]
$cenumFromTo :: Execution -> Execution -> [Execution]
enumFromThen :: Execution -> Execution -> [Execution]
$cenumFromThen :: Execution -> Execution -> [Execution]
enumFrom :: Execution -> [Execution]
$cenumFrom :: Execution -> [Execution]
fromEnum :: Execution -> Int
$cfromEnum :: Execution -> Int
toEnum :: Int -> Execution
$ctoEnum :: Int -> Execution
pred :: Execution -> Execution
$cpred :: Execution -> Execution
succ :: Execution -> Execution
$csucc :: Execution -> Execution
Enum, Execution
Execution -> Execution -> Bounded Execution
forall a. a -> a -> Bounded a
maxBound :: Execution
$cmaxBound :: Execution
minBound :: Execution
$cminBound :: Execution
Bounded)

instance MsgpackEncode Execution where
  toMsgpack :: Execution -> Object
toMsgpack Execution
exec =
    Bool -> Object
forall a. MsgpackEncode a => a -> Object
toMsgpack (Execution
exec Execution -> Execution -> Bool
forall a. Eq a => a -> a -> Bool
== Execution
Sync)

instance MsgpackDecode Execution where
  fromMsgpack :: Object -> Either DecodeError Execution
fromMsgpack Object
o =
    Object -> Either DecodeError Bool
forall a. MsgpackDecode a => Object -> Either DecodeError a
fromMsgpack Object
o Either DecodeError Bool
-> (Bool -> Execution) -> Either DecodeError Execution
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
      Bool
True -> Execution
Sync
      Bool
False -> Execution
Async