{-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} module Protocol.Base.Internal.Data ( -- * Re-exports of basic data types ByteString , Int8 , Int16 , Int32 , Int64 , Word8 , Word16 , Word32 , Word64 , Word128(..) -- * Re-exports of time-based data types , Tick , TickDelta -- * Re-exports of strict containers , IntMap , Map , Seq , Set -- * Re-exports of serialisation type classes , Binary , Generic , Serialise -- * Definitions for message-passing , Want(..) , Give(..) ) where -- external import qualified Data.Strict as Z import Codec.Serialise (Serialise) import Data.Binary (Binary) import Data.ByteString (ByteString) import Data.Int import Data.Schedule (Tick, TickDelta) import Data.Strict.Containers.Lens () import Data.Strict.Containers.Serialise () import Data.Strict.IntMap (IntMap) import Data.Strict.Map (Map) import Data.Strict.Sequence (Seq) import Data.Strict.Set (Set) import Data.WideWord import Data.Word import GHC.Generics (Generic) {- | Message from a data consumer (such as the recipient of a write-command, or the sender of a read-command), indicating that they want a bounded number of units, or if 'Nothing' then as many units as the producer cares to give. This allows for proper flow control between the producer and consumer. The effect is cumulative, so sending e.g. @'Want' (Just 4)@ twice means that you want (and have space to store) 8 units. -} data Want = Want !(Z.Maybe Int) deriving (Show, Read, Generic, Binary, Serialise, Eq, Ord) {- | Message from a data producer (such as the sender of a write-command, or the recipient of a read-command), passing the given data, and indicating how many units remain to be consumed in the future. 'Nothing' means EOF. This allows for proper flow control between the producer and consumer. -} data Give = Give !(Z.Maybe ByteString) !Int deriving (Show, Read, Generic, Binary, Serialise, Eq, Ord)