-- |Special command parameter that enables command chaining.
module Ribosome.Host.Data.Bar where

import Ribosome.Host.Class.Msgpack.Decode (MsgpackDecode (fromMsgpack))

-- |When this type is used as a parameter of a command handler function, the command is declared with the @-bar@ option,
-- allowing other commands to be chained after it with @|@.
--
-- This has no effect on the execution.
data Bar =
  Bar
  deriving stock (Bar -> Bar -> Bool
(Bar -> Bar -> Bool) -> (Bar -> Bar -> Bool) -> Eq Bar
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bar -> Bar -> Bool
$c/= :: Bar -> Bar -> Bool
== :: Bar -> Bar -> Bool
$c== :: Bar -> Bar -> Bool
Eq, Int -> Bar -> ShowS
[Bar] -> ShowS
Bar -> String
(Int -> Bar -> ShowS)
-> (Bar -> String) -> ([Bar] -> ShowS) -> Show Bar
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bar] -> ShowS
$cshowList :: [Bar] -> ShowS
show :: Bar -> String
$cshow :: Bar -> String
showsPrec :: Int -> Bar -> ShowS
$cshowsPrec :: Int -> Bar -> ShowS
Show)

instance MsgpackDecode Bar where
  fromMsgpack :: Object -> Either DecodeError Bar
fromMsgpack Object
_ =
    Bar -> Either DecodeError Bar
forall a b. b -> Either a b
Right Bar
Bar