symbiote-0.0.5: Data serialization, communication, and operation verification implementation

Copyright(c) 2019 Athan Clark
LicenseBSD-3-Style
Maintainerathan.clark@gmail.com
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Test.Serialization.Symbiote

Contents

Description

As an example, say you have some data type TypeA, and some encoding / decoding instance with Aeson for that data type. Now, you've also got a few functions that work with that data type - f :: TypeA -> TypeA and g :: TypeA -> TypeA -> TypeA, and you've also taken the time to write a proper Arbitrary instance for TypeA.

Your first order of business in making TypeA a symbiote, is to first demonstrate what operations are supported by it:


instance SymbioteOperation TypeA TypeA where
  data Operation TypeA
    = F
    | G TypeA
  perform op x = case op of
    F -> f x
    G y -> g y x

You're also going to need to make sure your new data-family has appropriate serialization instances, as well:

instance ToJSON (Operation TypeA) where
  toJSON op = case op of
    F -> toJSON "f"
    G x -> "g" .: x

instance FromJSON (Operation TypeA) where
  parseJSON json = getF <|> getG
    where
      getF = do
        s <- parseJSON json
        if s == "f"
          then pure F
          else typeMismatch "Operation TypeA" json
      getG = do
        o <- parseJSON json
        G <$> o .: "g"

Next, let's make TypeA an instance of Symbiote:

instance Symbiote TypeA TypeA Value where
  encode = Aeson.toJSON
  decode = Aeson.parseMaybe Aeson.parseJSON
  encodeOut _ = Aeson.toJSON
  decodeOut _ = Aeson.parseMaybe Aeson.parseJSON
  encodeOp = Aeson.toJSON
  decodeOp = Aeson.parseMaybe Aeson.parseJSON

this instance above actually works for any type that implements ToJSON and FromJSON - there's an orphan definition in Test.Serialization.Symbiote.Aeson.

Next, you're going to need to actually use this, by registering the type in a test suite:

myFancyTestSuite :: SymbioteT Value IO ()
myFancyTestSuite = register "TypeA" 100 (Proxy :: Proxy TypeA)

Lastly, you're going to need to actually run the test suite by attaching it to a network. The best way to do that, is decide whether this peer will be the first or second peer to start the protocol, then use the respective firstPeer and secondPeer functions - they take as arguments functions that define "how to send" and "how to receive" messages, and likewise how to report status.

Synopsis

Suite Building

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.

Methods

perform :: Operation a -> a -> o Source #

Apply the Operation to a, to get an o.

Instances
(Fractional a, Eq a) => SymbioteOperation (AbidesField a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesField a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesEuclideanRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesEuclideanRing a) :: Type Source #

(Fractional a, Eq a) => SymbioteOperation (AbidesDivisionRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesDivisionRing a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesCommutativeRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesCommutativeRing a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesRing a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesRing a) :: Type Source #

(Num a, Eq a) => SymbioteOperation (AbidesSemiring a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesSemiring a) :: Type Source #

(Enum a, Ord a) => SymbioteOperation (AbidesEnum a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesEnum a) :: Type Source #

Ord a => SymbioteOperation (AbidesOrd a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesOrd a) :: Type Source #

Eq a => SymbioteOperation (AbidesEq a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesEq a) :: Type Source #

(Monoid a, Eq a) => SymbioteOperation (AbidesMonoid a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesMonoid a) :: Type Source #

(Semigroup a, Eq a) => SymbioteOperation (AbidesSemigroup a) Bool Source # 
Instance details

Defined in Test.Serialization.Symbiote.Abides

Associated Types

data Operation (AbidesSemigroup a) :: Type Source #

class SymbioteOperation a o => Symbiote a o s | a -> o where Source #

A serialization format for a particular type, and serialized data type.

Methods

encode :: a -> s Source #

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

encodeOp :: Operation a -> s Source #

decodeOp :: s -> Maybe (Operation a) Source #

Instances
(Serialize a, Serialize o, Serialize (Operation a), SymbioteOperation a o) => Symbiote a o ByteString Source # 
Instance details

Defined in Test.Serialization.Symbiote.Cereal.Lazy

(Serialize a, Serialize o, Serialize (Operation a), SymbioteOperation a o) => Symbiote a o ByteString Source # 
Instance details

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 # 
Instance details

Defined in Test.Serialization.Symbiote.Aeson

SymbioteOperation a o => Symbiote a o (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

data SimpleSerialization a o Source #

The most trivial serialization medium for any a and o. There's no need to implement transmission protocol specific instances for this type, like ToJSON or Serialize, because it is intended to operate locally (on the same program), and over Eq.

Constructors

SimpleValue a

A value a encodes as just that value

SimpleOutput o

An output o encodes as just that output

SimpleOperation (Operation a)

An operation Operation encodes as just that operation

Instances
SymbioteOperation a o => Symbiote a o (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

(Eq a, Eq o, Eq (Operation a)) => Eq (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

(Show a, Show o, Show (Operation a)) => Show (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Generic (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Associated Types

type Rep (SimpleSerialization a o) :: Type -> Type #

type Rep (SimpleSerialization a o) Source # 
Instance details

Defined in Test.Serialization.Symbiote

type Rep (SimpleSerialization a o) = D1 (MetaData "SimpleSerialization" "Test.Serialization.Symbiote" "symbiote-0.0.5-CizdGLSttkNC7czGnIyxfU" False) (C1 (MetaCons "SimpleValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: (C1 (MetaCons "SimpleOutput" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 o)) :+: C1 (MetaCons "SimpleOperation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Operation a)))))

data Topic Source #

Unique name of a type, for a suite of tests. Ref - Topic.

Instances
Eq Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

(==) :: Topic -> Topic -> Bool #

(/=) :: Topic -> Topic -> Bool #

Ord Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

compare :: Topic -> Topic -> Ordering #

(<) :: Topic -> Topic -> Bool #

(<=) :: Topic -> Topic -> Bool #

(>) :: Topic -> Topic -> Bool #

(>=) :: Topic -> Topic -> Bool #

max :: Topic -> Topic -> Topic #

min :: Topic -> Topic -> Topic #

Show Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

showsPrec :: Int -> Topic -> ShowS #

show :: Topic -> String #

showList :: [Topic] -> ShowS #

IsString Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

fromString :: String -> Topic #

Arbitrary Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

arbitrary :: Gen Topic #

shrink :: Topic -> [Topic] #

ToJSON Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

ToJSONKey Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

FromJSON Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

FromJSONKey Topic Source # 
Instance details

Defined in Test.Serialization.Symbiote.Core

Serialize Topic Source #

Serialized as a String32 in the symbiotic-data standard.

Instance details

Defined in Test.Serialization.Symbiote.Core

Methods

put :: Putter Topic #

get :: Get Topic #

type SymbioteT s m = ReaderT Bool (StateT (Map Topic (ExistsSymbiote s)) m) Source #

Builder for the total set of topics supported by this peer.

register Source #

Arguments

:: Arbitrary a 
=> Arbitrary (Operation a) 
=> Symbiote a o s 
=> Eq o 
=> MonadIO m 
=> Topic

Topic name as a Text

-> Int32

Max size

-> Proxy a

Reference to the datatype

-> SymbioteT s m () 

Register a topic in the test suite builder.

Protocol Messages

data First s Source #

Messages sent by the first peer - polymorphic in the serialization medium. Ref - First

Constructors

AvailableTopics (Map Topic Int32)

"Here are the topics I support."

BadStartSubset

"I got your subset of topics, but they don't match to mine."

FirstGenerating

"It's my turn to generate, so here's a generating message."

FirstOperating

"It's my turn to operate, so here's my operating message."

Instances
Eq s => Eq (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: First s -> First s -> Bool #

(/=) :: First s -> First s -> Bool #

Show s => Show (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

showsPrec :: Int -> First s -> ShowS #

show :: First s -> String #

showList :: [First s] -> ShowS #

Generic (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Associated Types

type Rep (First s) :: Type -> Type #

Methods

from :: First s -> Rep (First s) x #

to :: Rep (First s) x -> First s #

Arbitrary s => Arbitrary (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

arbitrary :: Gen (First s) #

shrink :: First s -> [First s] #

ToJSON s => ToJSON (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

FromJSON s => FromJSON (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Serialize (First ByteString) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Serialize (First ByteString) Source # 
Instance details

Defined in Test.Serialization.Symbiote

type Rep (First s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

type Rep (First s) = D1 (MetaData "First" "Test.Serialization.Symbiote" "symbiote-0.0.5-CizdGLSttkNC7czGnIyxfU" False) ((C1 (MetaCons "AvailableTopics" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Topic Int32))) :+: C1 (MetaCons "BadStartSubset" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "FirstGenerating" PrefixI True) (S1 (MetaSel (Just "firstGeneratingTopic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Topic) :*: S1 (MetaSel (Just "firstGenerating") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Generating s))) :+: C1 (MetaCons "FirstOperating" PrefixI True) (S1 (MetaSel (Just "firstOperatingTopic") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Topic) :*: S1 (MetaSel (Just "firstOperating") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Operating s)))))

data Second s Source #

Messages sent by the second peer - polymorphic in the serialization medium. Ref - Second

Constructors

BadTopics (Map Topic Int32)

"Although my topics should be at least a subset of your topics available, the following of mine do not have the same max size as yours."

Start (Set Topic)

"All systems nominal, you may fire (the following subset of topics) when ready."

SecondOperating

"It's my turn to operate, so here's my operating message."

SecondGenerating

"It's my turn to generate, so here's my generating message."

Instances
Eq s => Eq (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Second s -> Second s -> Bool #

(/=) :: Second s -> Second s -> Bool #

Show s => Show (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

showsPrec :: Int -> Second s -> ShowS #

show :: Second s -> String #

showList :: [Second s] -> ShowS #

Generic (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Associated Types

type Rep (Second s) :: Type -> Type #

Methods

from :: Second s -> Rep (Second s) x #

to :: Rep (Second s) x -> Second s #

Arbitrary s => Arbitrary (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

arbitrary :: Gen (Second s) #

shrink :: Second s -> [Second s] #

ToJSON s => ToJSON (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

FromJSON s => FromJSON (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Serialize (Second ByteString) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Serialize (Second ByteString) Source # 
Instance details

Defined in Test.Serialization.Symbiote

type Rep (Second s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

data Generating s Source #

Messages sent by a peer during their generating phase - polymorphic in the serialization medium. Ref - Generating

Constructors

Generated

"I've generated a value and operation, here you go."

Fields

BadResult s

"You sent the wrong value!"

YourTurn

"It's your turn to generate, I just finished and we're both O.K."

ImFinished

"I just finished all generation, and my topic state's size is equal to the maxSize."

GeneratingNoParseOperated s

"I could not deserialize the output value sent by you, and I have to tell you about it."

Instances
Eq s => Eq (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Generating s -> Generating s -> Bool #

(/=) :: Generating s -> Generating s -> Bool #

Show s => Show (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Generic (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Associated Types

type Rep (Generating s) :: Type -> Type #

Methods

from :: Generating s -> Rep (Generating s) x #

to :: Rep (Generating s) x -> Generating s #

Arbitrary s => Arbitrary (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

ToJSON s => ToJSON (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

FromJSON s => FromJSON (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Serialize (Generating ByteString) Source #

For supporting 32bit limitation on length prefix

Instance details

Defined in Test.Serialization.Symbiote

Serialize (Generating ByteString) Source #

For supporting 32bit limitation on length prefix

Instance details

Defined in Test.Serialization.Symbiote

type Rep (Generating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

type Rep (Generating s) = D1 (MetaData "Generating" "Test.Serialization.Symbiote" "symbiote-0.0.5-CizdGLSttkNC7czGnIyxfU" False) ((C1 (MetaCons "Generated" PrefixI True) (S1 (MetaSel (Just "genValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s) :*: S1 (MetaSel (Just "genOperation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)) :+: C1 (MetaCons "BadResult" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s))) :+: (C1 (MetaCons "YourTurn" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "ImFinished" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "GeneratingNoParseOperated" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)))))

data Operating s Source #

Messages sent by a peer during their operating phase - polymorphic in the serialization medium. Ref - Operating

Constructors

Operated s

"I've performed the operation on the value, and here's the output result."

OperatingNoParseValue s

"I couldn't deserialize the input value sent by you, and I have to tell you about it."

OperatingNoParseOperation s

"I couldn't deserialize the operation sent by you, and I have to tell you about it."

Instances
Eq s => Eq (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Operating s -> Operating s -> Bool #

(/=) :: Operating s -> Operating s -> Bool #

Show s => Show (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Generic (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Associated Types

type Rep (Operating s) :: Type -> Type #

Methods

from :: Operating s -> Rep (Operating s) x #

to :: Rep (Operating s) x -> Operating s #

Arbitrary s => Arbitrary (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

arbitrary :: Gen (Operating s) #

shrink :: Operating s -> [Operating s] #

ToJSON s => ToJSON (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

FromJSON s => FromJSON (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Serialize (Operating ByteString) Source #

For supporting 32bit limitation on length prefix

Instance details

Defined in Test.Serialization.Symbiote

Serialize (Operating ByteString) Source #

For supporting 32bit limitation on length prefix

Instance details

Defined in Test.Serialization.Symbiote

type Rep (Operating s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

type Rep (Operating s) = D1 (MetaData "Operating" "Test.Serialization.Symbiote" "symbiote-0.0.5-CizdGLSttkNC7czGnIyxfU" False) (C1 (MetaCons "Operated" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)) :+: (C1 (MetaCons "OperatingNoParseValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s)) :+: C1 (MetaCons "OperatingNoParseOperation" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 s))))

Result Handling

data Failure them s Source #

Exception data type

Constructors

BadTopicsFailure

Topic sets do not match between peers

BadStartSubsetFailure (Set Topic)

The first peer doesn't have the subset topics identified by second

OutOfSyncFirst (First s)

The first peer is out of sync and not sending the correct message

OutOfSyncSecond (Second s)

The second peer is out of sync and not sending the correct message

TopicNonexistent Topic

Topic does not exist

WrongTopic

Got the wrong topic

CantParseOperated Topic s 
CantParseGeneratedValue Topic s 
CantParseGeneratedOperation Topic s 
CantParseLocalValue Topic s 
CantParseLocalOperation Topic s 
BadOperating Topic (Operating s)

Incorrect operating message received

BadGenerating Topic (Generating s)

Incorrect generating message received

BadThem Topic (them s)

Incorrect peer message (First and Second agnostic)

SafeFailure

Failed because the output of the operation applied to the value does not match between the peers.

Instances
(Eq s, Eq (them s)) => Eq (Failure them s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

(==) :: Failure them s -> Failure them s -> Bool #

(/=) :: Failure them s -> Failure them s -> Bool #

(Show s, Show (them s)) => Show (Failure them s) Source # 
Instance details

Defined in Test.Serialization.Symbiote

Methods

showsPrec :: Int -> Failure them s -> ShowS #

show :: Failure them s -> String #

showList :: [Failure them s] -> ShowS #

defaultFailure :: Show (them s) => Show s => Failure them s -> IO () Source #

nullProgress :: Applicative m => Topic -> Float -> m () Source #

Do nothing

Test Execution

simpleTest :: MonadBaseControl IO m stM => MonadIO m => Show s => SymbioteT s m () -> m () Source #

Prints to stdout and uses a local channel for a sanity-check - doesn't serialize.

simpleTest' Source #

Arguments

:: MonadBaseControl IO m stM 
=> MonadIO m 
=> Show s 
=> (Topic -> m ())

report topic success

-> (Failure Second s -> m ())

report topic failure from first (sees second)

-> (Failure First s -> m ())

report topic failure from second (sees first)

-> (Topic -> Float -> m ())

report topic progress

-> SymbioteT s m () 
-> m () 

firstPeer Source #

Arguments

:: MonadIO m 
=> Show s 
=> (First s -> m ())

Encode and send first messages

-> m (Second s)

Receive and decode second messages

-> (Topic -> m ())

Report when Successful

-> (Failure Second s -> m ())

Report when Failed

-> (Topic -> Float -> m ())

Report on Progress

-> SymbioteT s m () 
-> m () 

Run the test suite as the first peer - see Test.Serialization.Symbiote.WebSocket and Test.Serialization.Symbiote.ZeroMQ for end-user implementations.

secondPeer Source #

Arguments

:: MonadIO m 
=> Show s 
=> (Second s -> m ())

Encode and send second messages

-> m (First s)

Receive and decode first messages

-> (Topic -> m ())

Report when Successful

-> (Failure First s -> m ())

Report when Failed

-> (Topic -> Float -> m ())

Report on Progress

-> SymbioteT s m () 
-> m () 

Run the test suite as the second peer - see Test.Serialization.Symbiote.WebSocket and Test.Serialization.Symbiote.ZeroMQ for end-user implementations.