-- |Special command parameter that activates the bang modifier.
module Ribosome.Host.Data.Bang where

import Data.MessagePack (Object (ObjectBool))
import Exon (exon)

import Ribosome.Host.Class.Msgpack.Decode (pattern Msgpack, MsgpackDecode (fromMsgpack))
import Ribosome.Host.Class.Msgpack.Error (decodeError)

-- |When this type is used as a parameter of a command handler function, the command is declared with the @-bang@
-- option, and when invoked, the argument passed to the handler is v'Bang' if the user specified the @!@ and 'NoBang'
-- otherwise.
data Bang =
  -- |Bang was used.
  Bang
  |
  -- |Bang was not used.
  NoBang
  deriving stock (Bang -> Bang -> Bool
(Bang -> Bang -> Bool) -> (Bang -> Bang -> Bool) -> Eq Bang
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Bang -> Bang -> Bool
$c/= :: Bang -> Bang -> Bool
== :: Bang -> Bang -> Bool
$c== :: Bang -> Bang -> Bool
Eq, Int -> Bang -> ShowS
[Bang] -> ShowS
Bang -> String
(Int -> Bang -> ShowS)
-> (Bang -> String) -> ([Bang] -> ShowS) -> Show Bang
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Bang] -> ShowS
$cshowList :: [Bang] -> ShowS
show :: Bang -> String
$cshow :: Bang -> String
showsPrec :: Int -> Bang -> ShowS
$cshowsPrec :: Int -> Bang -> ShowS
Show)

instance MsgpackDecode Bang where
  fromMsgpack :: Object -> Either DecodeError Bang
fromMsgpack = \case
    ObjectBool Bool
True ->
      Bang -> Either DecodeError Bang
forall a b. b -> Either a b
Right Bang
Bang
    ObjectBool Bool
False ->
      Bang -> Either DecodeError Bang
forall a b. b -> Either a b
Right Bang
NoBang
    Msgpack (Int
1 :: Int) ->
      Bang -> Either DecodeError Bang
forall a b. b -> Either a b
Right Bang
Bang
    Msgpack (Int
0 :: Int) ->
      Bang -> Either DecodeError Bang
forall a b. b -> Either a b
Right Bang
NoBang
    Object
o ->
      Text -> Either DecodeError Bang
forall a. Typeable a => Text -> Either DecodeError a
decodeError [exon|Bang arg must be boolean: #{show o}|]