{-# LANGUAGE CPP #-}
module Ouroboros.Network.Testing.Serialise
  ( -- * Class
    Serialise (..)
  , prop_serialise
  , prop_serialise_valid
  , prop_serialise_roundtrip
  ) where

import           Codec.CBOR.FlatTerm
import           Codec.Serialise
import           Test.QuickCheck (Property, counterexample, property, (.&&.),
                     (===))

-- Class properties
--

prop_serialise :: (Serialise a, Eq a, Show a) => a -> Property
prop_serialise :: a -> Property
prop_serialise a
x =     a -> Property
forall a. Serialise a => a -> Property
prop_serialise_valid a
x
                  Property -> Property -> Property
forall prop1 prop2.
(Testable prop1, Testable prop2) =>
prop1 -> prop2 -> Property
.&&. a -> Property
forall a. (Serialise a, Eq a, Show a) => a -> Property
prop_serialise_roundtrip a
x

prop_serialise_valid :: Serialise a => a -> Property
prop_serialise_valid :: a -> Property
prop_serialise_valid a
a =
    let e :: Encoding
e = a -> Encoding
forall a. Serialise a => a -> Encoding
encode a
a
        f :: FlatTerm
f = Encoding -> FlatTerm
toFlatTerm Encoding
e
        s :: [Char]
s = [Char]
"invalid flat term " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ FlatTerm -> [Char]
forall a. Show a => a -> [Char]
show FlatTerm
f [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" from encoding " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Encoding -> [Char]
forall a. Show a => a -> [Char]
show Encoding
e
    in  [Char] -> Bool -> Property
forall prop. Testable prop => [Char] -> prop -> Property
counterexample [Char]
s (Bool -> Property) -> Bool -> Property
forall a b. (a -> b) -> a -> b
$ FlatTerm -> Bool
validFlatTerm FlatTerm
f

-- Written like this so that an Eq DeserialiseFailure is not required.
prop_serialise_roundtrip :: (Serialise a, Eq a, Show a) => a -> Property
prop_serialise_roundtrip :: a -> Property
prop_serialise_roundtrip a
x = case ByteString -> Either DeserialiseFailure a
forall a. Serialise a => ByteString -> Either DeserialiseFailure a
deserialiseOrFail (a -> ByteString
forall a. Serialise a => a -> ByteString
serialise a
x) of
  Right a
y                            -> a
y a -> a -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== a
x
  Left (DeserialiseFailure ByteOffset
_ [Char]
string) -> [Char] -> Property -> Property
forall prop. Testable prop => [Char] -> prop -> Property
counterexample [Char]
string (Bool -> Property
forall prop. Testable prop => prop -> Property
property Bool
False)