Copyright | (c) 2019 Athan Clark |
---|---|
License | BSD-3-Style |
Maintainer | athan.clark@gmail.com |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Test.Serialization.Symbiote.Core
Description
This module defines the machinery of any topic's state machine:
- agnostic for whatever type or operation you're testing
- doesn't try to define the stuff that orchestrates multiple topics operating together
- doesn't specify how the protocol actually looks with respect to the messages sent between the peers
Synopsis
- class SymbioteOperation a o | a -> o where
- class SymbioteOperation a o => Symbiote a o s | a -> o where
- newtype Topic = Topic Text
- data SymbioteProtocol a s
- = MeGenerated {
- meGenValue :: a
- meGenOperation :: Operation a
- meGenReceived :: Maybe s
- | ThemGenerating { }
- | NotStarted
- | Finished
- = MeGenerated {
- data SymbioteGeneration a s = SymbioteGeneration {
- size :: Int32
- protocol :: SymbioteProtocol a s
- newGeneration :: SymbioteGeneration a s
- data SymbioteState a o s = SymbioteState {
- generate :: Gen a
- generateOp :: Gen (Operation a)
- equal :: o -> o -> Bool
- maxSize :: Int32
- generation :: TVar (SymbioteGeneration a s)
- encode' :: a -> s
- encodeOut' :: o -> s
- encodeOp' :: Operation a -> s
- decode' :: s -> Maybe a
- decodeOut' :: s -> Maybe o
- decodeOp' :: s -> Maybe (Operation a)
- perform' :: Operation a -> a -> o
- data ExistsSymbiote s = (Arbitrary a, Arbitrary (Operation a), Symbiote a o s, Eq o) => ExistsSymbiote (SymbioteState a o s)
- type SymbioteT s m = ReaderT Bool (StateT (Map Topic (ExistsSymbiote s)) m)
- runSymbioteT :: Monad m => SymbioteT s m () -> Bool -> m (Map Topic (ExistsSymbiote s))
- data GenerateSymbiote s
- = DoneGenerating
- | GeneratedSymbiote {
- generatedValue :: s
- generatedOperation :: s
- generateSymbiote :: forall s m. MonadIO m => ExistsSymbiote s -> m (GenerateSymbiote s)
- getProgress :: MonadIO m => ExistsSymbiote s -> m Float
Documentation
class SymbioteOperation a o | a -> o where Source #
A type-level relation between a type and appropriate, testable operations on that type.
Associated Types
data Operation a :: * Source #
An enumerated type of operations on a
that result in o
.
Instances
class SymbioteOperation a o => Symbiote a o s | a -> o where Source #
A serialization format for a particular type, and serialized data type.
Methods
decode :: s -> Maybe a Source #
encodeOut :: Proxy a -> o -> s Source #
Needs a reference to a
because the fundep is only one direction (i.e. only one output defined per input, but could be used elsewhere)
decodeOut :: Proxy a -> s -> Maybe o Source #
Needs a reference to a
because the fundep is only one direction
Instances
(Serialize a, Serialize o, Serialize (Operation a), SymbioteOperation a o) => Symbiote a o ByteString Source # | |
Defined in Test.Serialization.Symbiote.Cereal.Lazy | |
(Serialize a, Serialize o, Serialize (Operation a), SymbioteOperation a o) => Symbiote a o ByteString Source # | |
Defined in Test.Serialization.Symbiote.Cereal | |
(ToJSON a, FromJSON a, ToJSON o, FromJSON o, ToJSON (Operation a), FromJSON (Operation a), SymbioteOperation a o) => Symbiote a o Value Source # | |
SymbioteOperation a o => Symbiote a o (SimpleSerialization a o) Source # | |
Defined in Test.Serialization.Symbiote Methods encode :: a -> SimpleSerialization a o Source # decode :: SimpleSerialization a o -> Maybe a Source # encodeOut :: Proxy a -> o -> SimpleSerialization a o Source # decodeOut :: Proxy a -> SimpleSerialization a o -> Maybe o Source # encodeOp :: Operation a -> SimpleSerialization a o Source # decodeOp :: SimpleSerialization a o -> Maybe (Operation a) Source # |
Unique name of a type, for a suite of tests. Ref - Topic.
Instances
Eq Topic Source # | |
Ord Topic Source # | |
Show Topic Source # | |
IsString Topic Source # | |
Defined in Test.Serialization.Symbiote.Core Methods fromString :: String -> Topic # | |
Arbitrary Topic Source # | |
ToJSON Topic Source # | |
Defined in Test.Serialization.Symbiote.Core | |
ToJSONKey Topic Source # | |
Defined in Test.Serialization.Symbiote.Core | |
FromJSON Topic Source # | |
FromJSONKey Topic Source # | |
Defined in Test.Serialization.Symbiote.Core | |
Serialize Topic Source # | Serialized as a |
data SymbioteProtocol a s Source #
The state-machine representation for a particular topic, identical for each peer. As the protocol progresses and messages are passed, and values are generated, this value will change over time, and is unique for each topic.
Constructors
MeGenerated | "I'm generating a value" |
Fields
| |
ThemGenerating | "They're generating a value" |
NotStarted | The topic's generation / operation exchange hasn't started for either peer |
Finished | The topic's generation / operation exchange has completed, and is currently being processed on another topic, or the whole suite is finished for all topics. |
data SymbioteGeneration a s Source #
Protocol state, with amended "current generation value" information
Constructors
SymbioteGeneration | |
Fields
|
newGeneration :: SymbioteGeneration a s Source #
The initial state for any topic's state machine.
data SymbioteState a o s Source #
Internal existential state of a registered topic, with fields explicitly storing a type's normally typeclass-specified facilities.
Constructors
SymbioteState | |
Fields
|
data ExistsSymbiote s Source #
A custom existential quantifier, which places additional typeclass constraints on the a
and o
variables of SymbioteState
, leaving only s
as the globally visible type variable - the "serialization" medium.
Constructors
(Arbitrary a, Arbitrary (Operation a), Symbiote a o s, Eq o) => ExistsSymbiote (SymbioteState a o s) |
type SymbioteT s m = ReaderT Bool (StateT (Map Topic (ExistsSymbiote s)) m) Source #
Builder for the total set of topics supported by this peer.
Arguments
:: Monad m | |
=> SymbioteT s m () | |
-> Bool | Is this the first peer to initiate the protocol? |
-> m (Map Topic (ExistsSymbiote s)) |
Get the set of topics from the builder.
data GenerateSymbiote s Source #
Used internally - attempt generating a value and operation for a specific topic, by using the mechanics defined in the protocol's stored state and existential typeclass facilities.
Constructors
DoneGenerating | Can't generate any more values, and "is finished" |
GeneratedSymbiote | Generated a value and operation, as serialized values |
Fields
|
generateSymbiote :: forall s m. MonadIO m => ExistsSymbiote s -> m (GenerateSymbiote s) Source #
Given an existentially stored topic state, attempt to generate a value and operation for that topic's type.
getProgress :: MonadIO m => ExistsSymbiote s -> m Float Source #