{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Cardano.Crypto.CBOR (
constantByteString,
getBytes,
tests,
)
where
import Cardano.Crypto (
AbstractHash,
PassPhrase,
ProtocolMagicId (..),
RedeemSignature,
SignTag (SignForTestingOnly),
Signature,
SigningKey (..),
VerificationKey (..),
redeemDeterministicKeyGen,
redeemSign,
serializeCborHash,
sign,
)
import Cardano.Crypto.Wallet (xprv, xpub)
import Cardano.Ledger.Binary (Dropper, EncCBOR, dropBytes, dropList, enforceSize)
import Cardano.Prelude
import Crypto.Hash (Blake2b_224, Blake2b_256, Blake2b_384, Blake2b_512, SHA1)
import qualified Data.ByteArray as ByteArray
import qualified Data.ByteString as BS
import GetDataFileName ((<:<))
import Hedgehog (Gen, Property)
import qualified Hedgehog as H
import Test.Cardano.Crypto.Gen
import Test.Cardano.Ledger.Binary.Vintage.Helpers (SizeTestConfig (..), scfg, sizeTest)
import Test.Cardano.Ledger.Binary.Vintage.Helpers.GoldenRoundTrip (
deprecatedGoldenDecode,
goldenTestCBOR,
roundTripsCBORBuildable,
roundTripsCBORShow,
)
import Test.Cardano.Prelude
roundTripProtocolMagicAeson :: Property
roundTripProtocolMagicAeson :: Property
roundTripProtocolMagicAeson = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen ProtocolMagic
genProtocolMagic forall a (m :: * -> *).
(Eq a, MonadTest m, ToJSON a, FromJSON a, Show a) =>
a -> m ()
roundTripsAesonShow
roundTripRequiresNetworkMagicCBOR :: Property
roundTripRequiresNetworkMagicCBOR :: Property
roundTripRequiresNetworkMagicCBOR =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
100 Gen RequiresNetworkMagic
genRequiresNetworkMagic forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
goldenVerificationKey :: Property
goldenVerificationKey :: Property
goldenVerificationKey = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR VerificationKey
vkey (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/VerificationKey"
where
Right VerificationKey
vkey = XPub -> VerificationKey
VerificationKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either FilePath XPub
xpub (Int -> Int -> ByteString
getBytes Int
0 Int
64)
roundTripVerificationKeyCBOR :: Property
roundTripVerificationKeyCBOR :: Property
roundTripVerificationKeyCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen VerificationKey
genVerificationKey forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripVerificationKeyAeson :: Property
roundTripVerificationKeyAeson :: Property
roundTripVerificationKeyAeson = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen VerificationKey
genVerificationKey forall a (m :: * -> *).
(Eq a, MonadTest m, ToJSON a, FromJSON a, Buildable a) =>
a -> m ()
roundTripsAesonBuildable
roundTripCompactRedeemVerificationKeyCBOR :: Property
roundTripCompactRedeemVerificationKeyCBOR :: Property
roundTripCompactRedeemVerificationKeyCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen CompactRedeemVerificationKey
genCompactRedeemVerificationKey forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Show a, HasCallStack) =>
a -> m ()
roundTripsCBORShow
goldenSigningKey :: Property
goldenSigningKey :: Property
goldenSigningKey = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR SigningKey
skey (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/SigningKey"
where
Right SigningKey
skey = XPrv -> SigningKey
SigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall bin. ByteArrayAccess bin => bin -> Either FilePath XPrv
xprv (Int -> Int -> ByteString
getBytes Int
10 Int
128)
roundTripSigningKeyCBOR :: Property
roundTripSigningKeyCBOR :: Property
roundTripSigningKeyCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen SigningKey
genSigningKey forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenSignature :: Property
goldenSignature :: Property
goldenSignature = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR Signature ()
sig (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/Signature"
where
Right SigningKey
skey = XPrv -> SigningKey
SigningKey forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall bin. ByteArrayAccess bin => bin -> Either FilePath XPrv
xprv (Int -> Int -> ByteString
getBytes Int
10 Int
128)
sig :: Signature ()
sig = forall a.
EncCBOR a =>
ProtocolMagicId -> SignTag -> SigningKey -> a -> Signature a
sign (Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0) SignTag
SignForTestingOnly SigningKey
skey ()
genUnitSignature :: Gen (Signature ())
genUnitSignature :: Gen (Signature ())
genUnitSignature = do
ProtocolMagicId
pm <- Gen ProtocolMagicId
genProtocolMagicId
forall a.
EncCBOR a =>
ProtocolMagicId -> Gen a -> Gen (Signature a)
genSignature ProtocolMagicId
pm (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
roundTripSignatureCBOR :: Property
roundTripSignatureCBOR :: Property
roundTripSignatureCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen (Signature ())
genUnitSignature forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripSignatureAeson :: Property
roundTripSignatureAeson :: Property
roundTripSignatureAeson = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen (Signature ())
genUnitSignature forall a (m :: * -> *).
(Eq a, MonadTest m, ToJSON a, FromJSON a, Buildable a) =>
a -> m ()
roundTripsAesonBuildable
goldenRedeemVerificationKey :: Property
goldenRedeemVerificationKey :: Property
goldenRedeemVerificationKey = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR RedeemVerificationKey
rvk (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/RedeemVerificationKey"
where
Just RedeemVerificationKey
rvk = forall a b. (a, b) -> a
fst forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (RedeemVerificationKey, RedeemSigningKey)
redeemDeterministicKeyGen (Int -> Int -> ByteString
getBytes Int
0 Int
32)
roundTripRedeemVerificationKeyCBOR :: Property
roundTripRedeemVerificationKeyCBOR :: Property
roundTripRedeemVerificationKeyCBOR =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen RedeemVerificationKey
genRedeemVerificationKey forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripRedeemVerificationKeyAeson :: Property
roundTripRedeemVerificationKeyAeson :: Property
roundTripRedeemVerificationKeyAeson =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen RedeemVerificationKey
genRedeemVerificationKey forall a (m :: * -> *).
(Eq a, MonadTest m, ToJSON a, FromJSON a, Buildable a) =>
a -> m ()
roundTripsAesonBuildable
goldenRedeemSigningKey :: Property
goldenRedeemSigningKey :: Property
goldenRedeemSigningKey = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR RedeemSigningKey
rsk (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/RedeemSigningKey"
where
Just RedeemSigningKey
rsk = forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (RedeemVerificationKey, RedeemSigningKey)
redeemDeterministicKeyGen (Int -> Int -> ByteString
getBytes Int
0 Int
32)
roundTripRedeemSigningKeyCBOR :: Property
roundTripRedeemSigningKeyCBOR :: Property
roundTripRedeemSigningKeyCBOR =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen RedeemSigningKey
genRedeemSigningKey forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
goldenRedeemSignature :: Property
goldenRedeemSignature :: Property
goldenRedeemSignature = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR RedeemSignature ()
rsig (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/RedeemSignature"
where
Just RedeemSigningKey
rsk = forall a b. (a, b) -> b
snd forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Maybe (RedeemVerificationKey, RedeemSigningKey)
redeemDeterministicKeyGen (Int -> Int -> ByteString
getBytes Int
0 Int
32)
rsig :: RedeemSignature ()
rsig = forall a.
EncCBOR a =>
ProtocolMagicId
-> SignTag -> RedeemSigningKey -> a -> RedeemSignature a
redeemSign (Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0) SignTag
SignForTestingOnly RedeemSigningKey
rsk ()
genUnitRedeemSignature :: Gen (RedeemSignature ())
genUnitRedeemSignature :: Gen (RedeemSignature ())
genUnitRedeemSignature = do
ProtocolMagicId
pm <- Gen ProtocolMagicId
genProtocolMagicId
forall a.
EncCBOR a =>
ProtocolMagicId -> Gen a -> Gen (RedeemSignature a)
genRedeemSignature ProtocolMagicId
pm (forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
roundTripRedeemSignatureCBOR :: Property
roundTripRedeemSignatureCBOR :: Property
roundTripRedeemSignatureCBOR =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen (RedeemSignature ())
genUnitRedeemSignature forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripRedeemSignatureAeson :: Property
roundTripRedeemSignatureAeson :: Property
roundTripRedeemSignatureAeson =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen (RedeemSignature ())
genUnitRedeemSignature forall a (m :: * -> *).
(Eq a, MonadTest m, ToJSON a, FromJSON a, Buildable a) =>
a -> m ()
roundTripsAesonBuildable
goldenDeprecatedVssPublicKey :: Property
goldenDeprecatedVssPublicKey :: Property
goldenDeprecatedVssPublicKey =
HasCallStack =>
Text -> (forall s. Decoder s ()) -> FilePath -> Property
deprecatedGoldenDecode Text
"VssPublicKey" forall s. Decoder s ()
dropBytes (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/VssPublicKey"
goldenDeprecatedDecShare :: Property
goldenDeprecatedDecShare :: Property
goldenDeprecatedDecShare =
HasCallStack =>
Text -> (forall s. Decoder s ()) -> FilePath -> Property
deprecatedGoldenDecode Text
"DecShare" forall s. Decoder s ()
dropBytes (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/DecShare"
goldenDeprecatedEncShare :: Property
goldenDeprecatedEncShare :: Property
goldenDeprecatedEncShare =
HasCallStack =>
Text -> (forall s. Decoder s ()) -> FilePath -> Property
deprecatedGoldenDecode Text
"EncShare" forall s. Decoder s ()
dropBytes (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/EncShare"
goldenDeprecatedSecret :: Property
goldenDeprecatedSecret :: Property
goldenDeprecatedSecret =
HasCallStack =>
Text -> (forall s. Decoder s ()) -> FilePath -> Property
deprecatedGoldenDecode Text
"Secret" forall s. Decoder s ()
dropBytes (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/Secret"
goldenDeprecatedSecretProof :: Property
goldenDeprecatedSecretProof :: Property
goldenDeprecatedSecretProof =
HasCallStack =>
Text -> (forall s. Decoder s ()) -> FilePath -> Property
deprecatedGoldenDecode
Text
"SecretProof"
forall s. Decoder s ()
dropSecretProof
(FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/SecretProof"
where
dropSecretProof :: Dropper s
dropSecretProof :: forall s. Decoder s ()
dropSecretProof = do
forall s. Text -> Int -> Decoder s ()
enforceSize Text
"SecretProof" Int
4
forall (m :: * -> *) a. Applicative m => Int -> m a -> m ()
replicateM_ Int
3 forall s. Decoder s ()
dropBytes
forall s. Dropper s -> Dropper s
dropList forall s. Decoder s ()
dropBytes
goldenAbstractHash :: Property
goldenAbstractHash :: Property
goldenAbstractHash = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR (forall a. EncCBOR a => a -> Hash a
serializeCborHash ()) (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/AbstractHash"
genUnitAbstractHash :: Gen (AbstractHash Blake2b_256 ())
genUnitAbstractHash :: Gen (AbstractHash Blake2b_256 ())
genUnitAbstractHash = forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
genAbstractHash forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
roundTripAbstractHashCBOR :: Property
roundTripAbstractHashCBOR :: Property
roundTripAbstractHashCBOR =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen (AbstractHash Blake2b_256 ())
genUnitAbstractHash forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
roundTripAbstractHashAeson :: Property
roundTripAbstractHashAeson :: Property
roundTripAbstractHashAeson =
forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen (AbstractHash Blake2b_256 ())
genUnitAbstractHash forall a (m :: * -> *).
(Eq a, MonadTest m, ToJSON a, FromJSON a, Buildable a) =>
a -> m ()
roundTripsAesonBuildable
goldenPassPhrase :: Property
goldenPassPhrase :: Property
goldenPassPhrase = forall a.
(DecCBOR a, EncCBOR a, Eq a, Show a, HasCallStack) =>
a -> FilePath -> Property
goldenTestCBOR PassPhrase
passphrase (FilePath -> Property) -> FilePath -> Property
<:< FilePath
"golden/PassPhrase"
where
passphrase :: PassPhrase
passphrase = forall a. ByteArray a => [Word8] -> a
ByteArray.pack (ByteString -> [Word8]
BS.unpack forall a b. (a -> b) -> a -> b
$ Int -> Int -> ByteString
getBytes Int
3 Int
32) :: PassPhrase
roundTripPassPhraseCBOR :: Property
roundTripPassPhraseCBOR :: Property
roundTripPassPhraseCBOR = forall a.
(Show a, HasCallStack) =>
TestLimit -> Gen a -> (a -> PropertyT IO ()) -> Property
eachOf TestLimit
1000 Gen PassPhrase
genPassPhrase forall a (m :: * -> *).
(DecCBOR a, EncCBOR a, Eq a, MonadTest m, Buildable a,
HasCallStack) =>
a -> m ()
roundTripsCBORBuildable
getBytes :: Int -> Int -> ByteString
getBytes :: Int -> Int -> ByteString
getBytes Int
offset Int
len = Int -> ByteString -> ByteString
BS.take Int
len forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
BS.drop Int
offset ByteString
constantByteString
constantByteString :: ByteString
constantByteString :: ByteString
constantByteString =
ByteString
"Kmyw4lDSE5S4fSH6etNouiXezCyEjKc3tG4ja0kFjO8qzai26ZMPUEJfEy15ox5kJ0uKD\
\bi7i6dLXkuesVZ9JfHgjrctsLFt2NvovXnchsOvX05Y6LohlTNt5mkPFhUoXu1EZSJTIy\
\3fTU53b412r4AEusD7tcdRgH47yTr5hMO63bJnYBbmNperLHfiT1lP0MLQLh1J1DfoYBs\
\auoJOzvtAgvjHo6UFttnK6vZ3Cknpuob6uMS2MkJKmuoQsqsAYcRDWbJ2Rgw4bm2ndTM4\
\zFfuRDKvdrL6sDkuPNPYqxMWlqnXjSbU0eLtceZuKgXLHR8cdvsEvywt4JaZUQhnbq3Vl\
\7nZqcXdoi4XGTCgSGcGp8N0SDVhvkVh0QF1RVpWPnOMyYISJvuaHfo1zXMdq9tEdtJfID"
sizeEstimates :: H.Group
sizeEstimates :: Group
sizeEstimates =
let testPrecise :: forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise :: forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise Gen a
g = forall a. EncCBOR a => SizeTestConfig a -> Property
sizeTest forall a b. (a -> b) -> a -> b
$ forall a. Show a => SizeTestConfig a
scfg {gen :: Gen a
gen = Gen a
g, precise :: Bool
precise = Bool
True}
in GroupName -> [(PropertyName, Property)] -> Group
H.Group
GroupName
"Encoded size bounds for crypto types."
[ (PropertyName
"VerificationKey", forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise Gen VerificationKey
genVerificationKey)
,
( PropertyName
"AbstractHash Blake2b_224 VerificationKey"
, forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise @(AbstractHash Blake2b_224 VerificationKey)
forall a b. (a -> b) -> a -> b
$ forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
genAbstractHash Gen VerificationKey
genVerificationKey
)
,
( PropertyName
"AbstractHash Blake2b_256 VerificationKey"
, forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise @(AbstractHash Blake2b_256 VerificationKey)
forall a b. (a -> b) -> a -> b
$ forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
genAbstractHash Gen VerificationKey
genVerificationKey
)
,
( PropertyName
"AbstractHash Blake2b_384 VerificationKey"
, forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise @(AbstractHash Blake2b_384 VerificationKey)
forall a b. (a -> b) -> a -> b
$ forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
genAbstractHash Gen VerificationKey
genVerificationKey
)
,
( PropertyName
"AbstractHash Blake2b_512 VerificationKey"
, forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise @(AbstractHash Blake2b_512 VerificationKey)
forall a b. (a -> b) -> a -> b
$ forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
genAbstractHash Gen VerificationKey
genVerificationKey
)
,
( PropertyName
"AbstractHash SHA1 VerificationKey"
, forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise @(AbstractHash SHA1 VerificationKey)
forall a b. (a -> b) -> a -> b
$ forall a algo.
(EncCBOR a, HashAlgorithm algo) =>
Gen a -> Gen (AbstractHash algo a)
genAbstractHash Gen VerificationKey
genVerificationKey
)
, (PropertyName
"RedeemVerificationKey", forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise Gen RedeemVerificationKey
genRedeemVerificationKey)
, (PropertyName
"RedeemSigningKey", forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise Gen RedeemSigningKey
genRedeemSigningKey)
,
( PropertyName
"RedeemSignature VerificationKey"
, forall a. (Show a, EncCBOR a) => Gen a -> Property
testPrecise (forall a.
EncCBOR a =>
ProtocolMagicId -> Gen a -> Gen (RedeemSignature a)
genRedeemSignature (Word32 -> ProtocolMagicId
ProtocolMagicId Word32
0) Gen VerificationKey
genVerificationKey)
)
]
tests :: IO Bool
tests :: IO Bool
tests =
forall (t :: * -> *). Foldable t => t Bool -> Bool
and
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence
[ forall (m :: * -> *). MonadIO m => Group -> m Bool
H.checkSequential $$FilePath
[(PropertyName, Property)]
Property
FilePath -> PropertyName
FilePath -> GroupName
GroupName -> [(PropertyName, Property)] -> Group
goldenPassPhrase :: Property
goldenAbstractHash :: Property
goldenDeprecatedSecretProof :: Property
goldenDeprecatedSecret :: Property
goldenDeprecatedEncShare :: Property
goldenDeprecatedDecShare :: Property
goldenDeprecatedVssPublicKey :: Property
goldenRedeemSignature :: Property
goldenRedeemSigningKey :: Property
goldenRedeemVerificationKey :: Property
goldenSignature :: Property
goldenSigningKey :: Property
goldenVerificationKey :: Property
discoverGolden
, forall (m :: * -> *). MonadIO m => Group -> m Bool
H.checkParallel $$FilePath
[(PropertyName, Property)]
Property
FilePath -> PropertyName
FilePath -> GroupName
GroupName -> [(PropertyName, Property)] -> Group
roundTripPassPhraseCBOR :: Property
roundTripAbstractHashAeson :: Property
roundTripAbstractHashCBOR :: Property
roundTripRedeemSignatureAeson :: Property
roundTripRedeemSignatureCBOR :: Property
roundTripRedeemSigningKeyCBOR :: Property
roundTripRedeemVerificationKeyAeson :: Property
roundTripRedeemVerificationKeyCBOR :: Property
roundTripSignatureAeson :: Property
roundTripSignatureCBOR :: Property
roundTripSigningKeyCBOR :: Property
roundTripCompactRedeemVerificationKeyCBOR :: Property
roundTripVerificationKeyAeson :: Property
roundTripVerificationKeyCBOR :: Property
roundTripRequiresNetworkMagicCBOR :: Property
roundTripProtocolMagicAeson :: Property
discoverRoundTrip
, forall (m :: * -> *). MonadIO m => Group -> m Bool
H.checkParallel Group
sizeEstimates
]