{-# LANGUAGE DeriveAnyClass #-}
module Hercules.API.Agent.Socket.Frame where
import Control.Applicative
import Data.Void (Void)
import Hercules.API.Prelude
data Frame o a
=
Msg {n :: Integer, p :: a}
|
Oob {o :: o}
|
Ack {n :: Integer}
|
Exception {message :: Text}
deriving (Generic, Show, Eq, ToJSON, FromJSON)
mapOob :: (a -> b) -> Frame a c -> Frame b c
mapOob f (Oob a) = Oob (f a)
mapOob _ (Msg a b) = Msg a b
mapOob _ (Ack a) = Ack a
mapOob _ (Exception e) = Exception e
removeOob :: Alternative f => Frame o a -> f (Frame Void a)
removeOob (Msg a b) = pure $ Msg a b
removeOob (Ack a) = pure $ Ack a
removeOob (Oob {}) = empty
removeOob (Exception e) = pure $ Exception e