{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Test.Crypto.VRF (
tests,
)
where
import Cardano.Crypto.Util
import Cardano.Crypto.VRF
import Cardano.Crypto.VRF.Praos
import qualified Cardano.Crypto.VRF.Praos as Ver03
import Cardano.Crypto.VRF.PraosBatchCompat
import qualified Cardano.Crypto.VRF.PraosBatchCompat as Ver13
import qualified Data.ByteString as BS
import qualified Data.Char as Char
import Data.Proxy (Proxy (..))
import Data.Word (Word64, Word8)
import GHC.Stack (HasCallStack)
import qualified Text.ParserCombinators.ReadP as Parse
import qualified Text.Read as Read
import Paths_cardano_crypto_tests (getDataFileName)
import Test.Crypto.Util
import Test.HUnit (assertBool, assertFailure, (@?=))
import Test.Hspec (Expectation, Spec, describe, it)
import Test.Hspec.QuickCheck (prop)
import Test.QuickCheck (
Arbitrary (..),
Gen,
NonNegative (..),
Property,
counterexample,
vectorOf,
(===),
(==>),
)
tests :: Spec
tests :: Spec
tests =
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Crypto.VRF" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
Proxy MockVRF -> String -> Spec
forall (proxy :: * -> *) v.
(VRFAlgorithm v, ToCBOR (VerKeyVRF v), FromCBOR (VerKeyVRF v),
ToCBOR (SignKeyVRF v), FromCBOR (SignKeyVRF v), ToCBOR (CertVRF v),
FromCBOR (CertVRF v), Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
proxy v -> String -> Spec
testVRFAlgorithm (Proxy MockVRF
forall {k} (t :: k). Proxy t
Proxy :: Proxy MockVRF) String
"MockVRF"
Proxy SimpleVRF -> String -> Spec
forall (proxy :: * -> *) v.
(VRFAlgorithm v, ToCBOR (VerKeyVRF v), FromCBOR (VerKeyVRF v),
ToCBOR (SignKeyVRF v), FromCBOR (SignKeyVRF v), ToCBOR (CertVRF v),
FromCBOR (CertVRF v), Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
proxy v -> String -> Spec
testVRFAlgorithm (Proxy SimpleVRF
forall {k} (t :: k). Proxy t
Proxy :: Proxy SimpleVRF) String
"SimpleVRF"
Proxy PraosVRF -> String -> Spec
forall (proxy :: * -> *) v.
(VRFAlgorithm v, ToCBOR (VerKeyVRF v), FromCBOR (VerKeyVRF v),
ToCBOR (SignKeyVRF v), FromCBOR (SignKeyVRF v), ToCBOR (CertVRF v),
FromCBOR (CertVRF v), Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
proxy v -> String -> Spec
testVRFAlgorithm (Proxy PraosVRF
forall {k} (t :: k). Proxy t
Proxy :: Proxy PraosVRF) String
"PraosVRF"
Proxy PraosBatchCompatVRF -> String -> Spec
forall (proxy :: * -> *) v.
(VRFAlgorithm v, ToCBOR (VerKeyVRF v), FromCBOR (VerKeyVRF v),
ToCBOR (SignKeyVRF v), FromCBOR (SignKeyVRF v), ToCBOR (CertVRF v),
FromCBOR (CertVRF v), Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
proxy v -> String -> Spec
testVRFAlgorithm (Proxy PraosBatchCompatVRF
forall {k} (t :: k). Proxy t
Proxy :: Proxy PraosBatchCompatVRF) String
"PraosBatchCompatVRF"
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"OutputVRF" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> ([Word8] -> Bool) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"bytesToNatural" [Word8] -> Bool
prop_bytesToNatural
String -> (NonNegative Int -> Word64 -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"naturalToBytes" NonNegative Int -> Word64 -> Property
prop_naturalToBytes
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"ConvertingTypes" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF PraosVRF -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"pubKeyToBatchCompat" VerKeyVRF PraosVRF -> Property
prop_pubKeyToBatchComopat
String -> (SignKeyVRF PraosVRF -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"signKeyToBatchCompat" SignKeyVRF PraosVRF -> Property
prop_signKeyToBatchCompat
String -> (OutputVRF PraosVRF -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"outputToBatchCompat" OutputVRF PraosVRF -> Property
prop_outputToBatchComat
String -> (SizedSeed 32 -> Message -> Bool) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"compatibleVerKeyConversion" SizedSeed 32 -> Message -> Bool
prop_verKeyValidConversion
String -> (SizedSeed 32 -> Bool) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"compatibleSignKeyConversion" SizedSeed 32 -> Bool
prop_signKeyValidConversion
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"test vectors for Praos" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_generated_1" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_generated_1"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_generated_2" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_generated_2"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_generated_3" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_generated_3"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_generated_4" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_generated_4"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_standard_10" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_standard_10"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_standard_11" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_standard_11"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver03_standard_12" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer03TestVector String
"vrf_ver03_standard_12"
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"test vectors for PraosBatchCompat" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_generated_1" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_generated_1"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_generated_2" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_generated_2"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_generated_3" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_generated_3"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_generated_4" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_generated_4"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_standard_10" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_standard_10"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_standard_11" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_standard_11"
String -> Expectation -> SpecM (Arg Expectation) ()
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"generated golden test vector: vrf_ver13_standard_12" (Expectation -> SpecM (Arg Expectation) ())
-> Expectation -> SpecM (Arg Expectation) ()
forall a b. (a -> b) -> a -> b
$
String -> Expectation
checkVer13TestVector String
"vrf_ver13_standard_12"
bytesEq :: HasCallStack => (a -> BS.ByteString) -> Maybe a -> a -> Expectation
bytesEq :: forall a.
HasCallStack =>
(a -> ByteString) -> Maybe a -> a -> Expectation
bytesEq a -> ByteString
outputToBytes Maybe a
suppliedM a
expected = case Maybe a
suppliedM of
Just a
supplied ->
a -> ByteString
outputToBytes a
supplied ByteString -> ByteString -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= a -> ByteString
outputToBytes a
expected
Maybe a
Nothing ->
HasCallStack => String -> Bool -> Expectation
String -> Bool -> Expectation
assertBool (String
"suppliedM in byteEq gave Nothing") Bool
False
checkVer03TestVector :: FilePath -> Expectation
checkVer03TestVector :: String -> Expectation
checkVer03TestVector String
file = do
String
filename <- String -> IO String
getDataFileName (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ String
"test_vectors/" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
file
String
str <- String -> IO String
readFile String
filename
let testVectorE :: Maybe VRFTestVector
testVectorE = forall a. Read a => String -> Maybe a
Read.readMaybe @VRFTestVector String
str
VRFTestVector {String
ByteString
testVectorName :: String
testVectorVersion :: String
testVectorCipherSuite :: String
testVectorSigningKey :: ByteString
testVectorVerifyingKey :: ByteString
testVectorMessage :: ByteString
testVectorProof :: ByteString
testVectorHash :: ByteString
testVectorName :: VRFTestVector -> String
testVectorVersion :: VRFTestVector -> String
testVectorCipherSuite :: VRFTestVector -> String
testVectorSigningKey :: VRFTestVector -> ByteString
testVectorVerifyingKey :: VRFTestVector -> ByteString
testVectorMessage :: VRFTestVector -> ByteString
testVectorProof :: VRFTestVector -> ByteString
testVectorHash :: VRFTestVector -> ByteString
..} <-
IO VRFTestVector
-> (VRFTestVector -> IO VRFTestVector)
-> Maybe VRFTestVector
-> IO VRFTestVector
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(String -> IO VRFTestVector
forall a. HasCallStack => String -> IO a
assertFailure (String -> IO VRFTestVector) -> String -> IO VRFTestVector
forall a b. (a -> b) -> a -> b
$ String
"parsing test vector: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
file String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" not successful")
VRFTestVector -> IO VRFTestVector
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Maybe VRFTestVector
testVectorE
SignKey
signKey <- ByteString -> IO SignKey
forall (m :: * -> *). MonadFail m => ByteString -> m SignKey
Ver03.skFromBytes ByteString
testVectorSigningKey
VerKey
verKey <- ByteString -> IO VerKey
forall (m :: * -> *). MonadFail m => ByteString -> m VerKey
Ver03.vkFromBytes ByteString
testVectorVerifyingKey
String
testVectorName String -> String -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= Proxy PraosVRF -> String
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy PraosVRF -> String
algorithmNameVRF (Proxy PraosVRF
forall {k} (t :: k). Proxy t
Proxy :: Proxy PraosVRF)
String
testVectorVersion String -> String -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= String
"ietfdraft03"
String
testVectorCipherSuite String -> String -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= String
"ECVRF-ED25519-SHA512-Elligator2"
Proof
proof' <- ByteString -> IO Proof
forall (m :: * -> *). MonadFail m => ByteString -> m Proof
Ver03.proofFromBytes ByteString
testVectorProof
Output
hash' <- ByteString -> IO Output
forall (m :: * -> *). MonadFail m => ByteString -> m Output
Ver03.outputFromBytes ByteString
testVectorHash
SignKey -> ByteString -> Maybe Proof
Ver03.prove SignKey
signKey ByteString
testVectorMessage Maybe Proof -> Maybe Proof -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= Proof -> Maybe Proof
forall a. a -> Maybe a
Just Proof
proof'
SignKey -> VerKey
Ver03.skToVerKey SignKey
signKey VerKey -> VerKey -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= VerKey
verKey
(Output -> ByteString) -> Maybe Output -> Output -> Expectation
forall a.
HasCallStack =>
(a -> ByteString) -> Maybe a -> a -> Expectation
bytesEq Output -> ByteString
Ver03.outputBytes (Proof -> Maybe Output
Ver03.outputFromProof Proof
proof') Output
hash'
(Output -> ByteString) -> Maybe Output -> Output -> Expectation
forall a.
HasCallStack =>
(a -> ByteString) -> Maybe a -> a -> Expectation
bytesEq Output -> ByteString
Ver03.outputBytes (VerKey -> Proof -> ByteString -> Maybe Output
Ver03.verify VerKey
verKey Proof
proof' ByteString
testVectorMessage) Output
hash'
checkVer13TestVector :: FilePath -> Expectation
checkVer13TestVector :: String -> Expectation
checkVer13TestVector String
file = do
String
filename <- String -> IO String
getDataFileName (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ String
"test_vectors/" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
file
String
str <- String -> IO String
readFile String
filename
let testVectorE :: Maybe VRFTestVector
testVectorE = forall a. Read a => String -> Maybe a
Read.readMaybe @VRFTestVector String
str
VRFTestVector {String
ByteString
testVectorName :: VRFTestVector -> String
testVectorVersion :: VRFTestVector -> String
testVectorCipherSuite :: VRFTestVector -> String
testVectorSigningKey :: VRFTestVector -> ByteString
testVectorVerifyingKey :: VRFTestVector -> ByteString
testVectorMessage :: VRFTestVector -> ByteString
testVectorProof :: VRFTestVector -> ByteString
testVectorHash :: VRFTestVector -> ByteString
testVectorName :: String
testVectorVersion :: String
testVectorCipherSuite :: String
testVectorSigningKey :: ByteString
testVectorVerifyingKey :: ByteString
testVectorMessage :: ByteString
testVectorProof :: ByteString
testVectorHash :: ByteString
..} <-
IO VRFTestVector
-> (VRFTestVector -> IO VRFTestVector)
-> Maybe VRFTestVector
-> IO VRFTestVector
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
(String -> IO VRFTestVector
forall a. HasCallStack => String -> IO a
assertFailure (String -> IO VRFTestVector) -> String -> IO VRFTestVector
forall a b. (a -> b) -> a -> b
$ String
"parsing test vector: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
file String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" not successful")
VRFTestVector -> IO VRFTestVector
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Maybe VRFTestVector
testVectorE
let signKey :: SignKey
signKey = ByteString -> SignKey
Ver13.skFromBytes ByteString
testVectorSigningKey
let verKey :: VerKey
verKey = ByteString -> VerKey
Ver13.vkFromBytes ByteString
testVectorVerifyingKey
String
testVectorName String -> String -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= Proxy PraosBatchCompatVRF -> String
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> String
forall (proxy :: * -> *). proxy PraosBatchCompatVRF -> String
algorithmNameVRF (Proxy PraosBatchCompatVRF
forall {k} (t :: k). Proxy t
Proxy :: Proxy PraosBatchCompatVRF)
String
testVectorVersion String -> String -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= String
"ietfdraft13"
String
testVectorCipherSuite String -> String -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= String
"ECVRF-ED25519-SHA512-Elligator2"
let proof' :: Proof
proof' = ByteString -> Proof
Ver13.proofFromBytes ByteString
testVectorProof
Output
hash' <- ByteString -> IO Output
forall (m :: * -> *). MonadFail m => ByteString -> m Output
Ver13.outputFromBytes ByteString
testVectorHash
SignKey -> ByteString -> Maybe Proof
Ver13.prove SignKey
signKey ByteString
testVectorMessage Maybe Proof -> Maybe Proof -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= Proof -> Maybe Proof
forall a. a -> Maybe a
Just Proof
proof'
SignKey -> VerKey
Ver13.skToVerKey SignKey
signKey VerKey -> VerKey -> Expectation
forall a. (HasCallStack, Eq a, Show a) => a -> a -> Expectation
@?= VerKey
verKey
(Output -> ByteString) -> Maybe Output -> Output -> Expectation
forall a.
HasCallStack =>
(a -> ByteString) -> Maybe a -> a -> Expectation
bytesEq Output -> ByteString
Ver13.outputBytes (Proof -> Maybe Output
Ver13.outputFromProof Proof
proof') Output
hash'
(Output -> ByteString) -> Maybe Output -> Output -> Expectation
forall a.
HasCallStack =>
(a -> ByteString) -> Maybe a -> a -> Expectation
bytesEq Output -> ByteString
Ver13.outputBytes (VerKey -> Proof -> ByteString -> Maybe Output
Ver13.verify VerKey
verKey Proof
proof' ByteString
testVectorMessage) Output
hash'
data VRFTestVector = VRFTestVector
{ VRFTestVector -> String
testVectorName :: String
, VRFTestVector -> String
testVectorVersion :: String
, VRFTestVector -> String
testVectorCipherSuite :: String
, VRFTestVector -> ByteString
testVectorSigningKey :: BS.ByteString
, VRFTestVector -> ByteString
testVectorVerifyingKey :: BS.ByteString
, VRFTestVector -> ByteString
testVectorMessage :: BS.ByteString
, VRFTestVector -> ByteString
testVectorProof :: BS.ByteString
, VRFTestVector -> ByteString
testVectorHash :: BS.ByteString
}
data HexStringWithLength = HexStringWithLength
{ HexStringWithLength -> String
hswlPayload :: String
, HexStringWithLength -> Int
hswExpectedLength :: Int
}
deriving (Int -> HexStringWithLength -> String -> String
[HexStringWithLength] -> String -> String
HexStringWithLength -> String
(Int -> HexStringWithLength -> String -> String)
-> (HexStringWithLength -> String)
-> ([HexStringWithLength] -> String -> String)
-> Show HexStringWithLength
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> HexStringWithLength -> String -> String
showsPrec :: Int -> HexStringWithLength -> String -> String
$cshow :: HexStringWithLength -> String
show :: HexStringWithLength -> String
$cshowList :: [HexStringWithLength] -> String -> String
showList :: [HexStringWithLength] -> String -> String
Show, HexStringWithLength -> HexStringWithLength -> Bool
(HexStringWithLength -> HexStringWithLength -> Bool)
-> (HexStringWithLength -> HexStringWithLength -> Bool)
-> Eq HexStringWithLength
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HexStringWithLength -> HexStringWithLength -> Bool
== :: HexStringWithLength -> HexStringWithLength -> Bool
$c/= :: HexStringWithLength -> HexStringWithLength -> Bool
/= :: HexStringWithLength -> HexStringWithLength -> Bool
Eq)
parserHex :: Maybe Int -> Parse.ReadP BS.ByteString
parserHex :: Maybe Int -> ReadP ByteString
parserHex Maybe Int
lenM = do
String
str <- ReadP String
parseString
if String
str String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"empty"
then
ByteString -> ReadP ByteString
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
BS.empty
else case Maybe Int
lenM of
Just Int
len -> String -> Int -> ReadP ByteString
forall {f :: * -> *}.
Applicative f =>
String -> Int -> f ByteString
handleDecode String
str Int
len
Maybe Int
Nothing -> String -> Int -> ReadP ByteString
forall {f :: * -> *}.
Applicative f =>
String -> Int -> f ByteString
handleDecode String
str (String -> Int
forall a. [a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length String
str Int -> Int -> Int
forall a. Integral a => a -> a -> a
`div` Int
2)
where
handleDecode :: String -> Int -> f ByteString
handleDecode String
str Int
size = case String -> Int -> Either String ByteString
decodeHexString String
str Int
size of
Right ByteString
bs -> ByteString -> f ByteString
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ByteString
bs
Left String
err -> String -> f ByteString
forall a. HasCallStack => String -> a
error String
err
parseKey :: String -> Parse.ReadP String
parseKey :: String -> ReadP String
parseKey String
key = do
String
key' <- String -> ReadP String
Parse.string String
key
ReadP ()
Parse.skipSpaces
String
_ <- String -> ReadP String
Parse.string String
":"
ReadP ()
Parse.skipSpaces
String -> ReadP String
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure String
key'
parseEOL :: Parse.ReadP ()
parseEOL :: ReadP ()
parseEOL =
[ReadP ()] -> ReadP ()
forall a. [ReadP a] -> ReadP a
Parse.choice
[ Char -> ReadP Char
Parse.char Char
'\n' ReadP Char -> ReadP () -> ReadP ()
forall a b. ReadP a -> ReadP b -> ReadP b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> ReadP ()
forall a. a -> ReadP a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
, ReadP ()
Parse.eof
]
parseContent :: String -> Parse.ReadP a -> Parse.ReadP a
parseContent :: forall a. String -> ReadP a -> ReadP a
parseContent String
key ReadP a
parser =
ReadP String -> ReadP () -> ReadP a -> ReadP a
forall open close a.
ReadP open -> ReadP close -> ReadP a -> ReadP a
Parse.between (String -> ReadP String
parseKey String
key) ReadP ()
parseEOL ReadP a
parser
parseString :: Parse.ReadP String
parseString :: ReadP String
parseString = (Char -> Bool) -> ReadP String
Parse.munch1 (\Char
c -> Char -> Bool
Char.isAlphaNum Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
parserVRFTestVector :: Parse.ReadP VRFTestVector
parserVRFTestVector :: ReadP VRFTestVector
parserVRFTestVector = do
String
testVectorName <- String -> ReadP String -> ReadP String
forall a. String -> ReadP a -> ReadP a
parseContent String
"vrf" ReadP String
parseString
String
testVectorVersion <- String -> ReadP String -> ReadP String
forall a. String -> ReadP a -> ReadP a
parseContent String
"ver" ReadP String
parseString
String
testVectorCipherSuite <- String -> ReadP String -> ReadP String
forall a. String -> ReadP a -> ReadP a
parseContent String
"ciphersuite" ReadP String
parseString
ByteString
sk <- String -> ReadP ByteString -> ReadP ByteString
forall a. String -> ReadP a -> ReadP a
parseContent String
"sk" (ReadP ByteString -> ReadP ByteString)
-> ReadP ByteString -> ReadP ByteString
forall a b. (a -> b) -> a -> b
$ Maybe Int -> ReadP ByteString
parserHex (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
32)
ByteString
testVectorVerifyingKey <- String -> ReadP ByteString -> ReadP ByteString
forall a. String -> ReadP a -> ReadP a
parseContent String
"pk" (ReadP ByteString -> ReadP ByteString)
-> ReadP ByteString -> ReadP ByteString
forall a b. (a -> b) -> a -> b
$ Maybe Int -> ReadP ByteString
parserHex (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
32)
let testVectorSigningKey :: ByteString
testVectorSigningKey = ByteString
sk ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
testVectorVerifyingKey
ByteString
testVectorMessage <- String -> ReadP ByteString -> ReadP ByteString
forall a. String -> ReadP a -> ReadP a
parseContent String
"alpha" (Maybe Int -> ReadP ByteString
parserHex Maybe Int
forall a. Maybe a
Nothing)
ByteString
testVectorProof <-
if String
testVectorName String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"PraosVRF"
then
String -> ReadP ByteString -> ReadP ByteString
forall a. String -> ReadP a -> ReadP a
parseContent String
"pi" (Maybe Int -> ReadP ByteString
parserHex (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
80))
else
String -> ReadP ByteString -> ReadP ByteString
forall a. String -> ReadP a -> ReadP a
parseContent String
"pi" (Maybe Int -> ReadP ByteString
parserHex (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
128))
ByteString
testVectorHash <- String -> ReadP ByteString -> ReadP ByteString
forall a. String -> ReadP a -> ReadP a
parseContent String
"beta" (Maybe Int -> ReadP ByteString
parserHex (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
64))
VRFTestVector -> ReadP VRFTestVector
forall a. a -> ReadP a
forall (f :: * -> *) a. Applicative f => a -> f a
pure VRFTestVector {String
ByteString
testVectorName :: String
testVectorVersion :: String
testVectorCipherSuite :: String
testVectorSigningKey :: ByteString
testVectorVerifyingKey :: ByteString
testVectorMessage :: ByteString
testVectorProof :: ByteString
testVectorHash :: ByteString
testVectorName :: String
testVectorVersion :: String
testVectorCipherSuite :: String
testVectorVerifyingKey :: ByteString
testVectorSigningKey :: ByteString
testVectorMessage :: ByteString
testVectorProof :: ByteString
testVectorHash :: ByteString
..}
instance Read VRFTestVector where
readsPrec :: Int -> ReadS VRFTestVector
readsPrec Int
_ = ReadP VRFTestVector -> ReadS VRFTestVector
forall a. ReadP a -> ReadS a
Parse.readP_to_S ReadP VRFTestVector
parserVRFTestVector
testVRFAlgorithm ::
forall proxy v.
( VRFAlgorithm v
, ToCBOR (VerKeyVRF v)
, FromCBOR (VerKeyVRF v)
, ToCBOR (SignKeyVRF v)
, FromCBOR (SignKeyVRF v)
, ToCBOR (CertVRF v)
, FromCBOR (CertVRF v)
, Eq (SignKeyVRF v)
, ContextVRF v ~ ()
, Signable v ~ SignableRepresentation
) =>
proxy v ->
String ->
Spec
testVRFAlgorithm :: forall (proxy :: * -> *) v.
(VRFAlgorithm v, ToCBOR (VerKeyVRF v), FromCBOR (VerKeyVRF v),
ToCBOR (SignKeyVRF v), FromCBOR (SignKeyVRF v), ToCBOR (CertVRF v),
FromCBOR (CertVRF v), Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
proxy v -> String -> Spec
testVRFAlgorithm proxy v
_ String
n =
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
n (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"serialisation" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"raw" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a.
(Eq a, Show a) =>
(a -> ByteString) -> (ByteString -> Maybe a) -> a -> Property
prop_raw_serialise @(VerKeyVRF v)
VerKeyVRF v -> ByteString
forall v. VRFAlgorithm v => VerKeyVRF v -> ByteString
rawSerialiseVerKeyVRF
ByteString -> Maybe (VerKeyVRF v)
forall v. VRFAlgorithm v => ByteString -> Maybe (VerKeyVRF v)
rawDeserialiseVerKeyVRF
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a.
(Eq a, Show a) =>
(a -> ByteString) -> (ByteString -> Maybe a) -> a -> Property
prop_raw_serialise @(SignKeyVRF v)
SignKeyVRF v -> ByteString
forall v. VRFAlgorithm v => SignKeyVRF v -> ByteString
rawSerialiseSignKeyVRF
ByteString -> Maybe (SignKeyVRF v)
forall v. VRFAlgorithm v => ByteString -> Maybe (SignKeyVRF v)
rawDeserialiseSignKeyVRF
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Cert" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a.
(Eq a, Show a) =>
(a -> ByteString) -> (ByteString -> Maybe a) -> a -> Property
prop_raw_serialise @(CertVRF v)
CertVRF v -> ByteString
forall v. VRFAlgorithm v => CertVRF v -> ByteString
rawSerialiseCertVRF
ByteString -> Maybe (CertVRF v)
forall v. VRFAlgorithm v => ByteString -> Maybe (CertVRF v)
rawDeserialiseCertVRF
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"size" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a. (a -> ByteString) -> Word -> a -> Property
prop_size_serialise @(VerKeyVRF v)
VerKeyVRF v -> ByteString
forall v. VRFAlgorithm v => VerKeyVRF v -> ByteString
rawSerialiseVerKeyVRF
(Proxy v -> Word
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> Word
forall (proxy :: * -> *). proxy v -> Word
sizeVerKeyVRF (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @v))
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a. (a -> ByteString) -> Word -> a -> Property
prop_size_serialise @(SignKeyVRF v)
SignKeyVRF v -> ByteString
forall v. VRFAlgorithm v => SignKeyVRF v -> ByteString
rawSerialiseSignKeyVRF
(Proxy v -> Word
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> Word
forall (proxy :: * -> *). proxy v -> Word
sizeSignKeyVRF (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @v))
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Cert" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a. (a -> ByteString) -> Word -> a -> Property
prop_size_serialise @(CertVRF v)
CertVRF v -> ByteString
forall v. VRFAlgorithm v => CertVRF v -> ByteString
rawSerialiseCertVRF
(Proxy v -> Word
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> Word
forall (proxy :: * -> *). proxy v -> Word
sizeCertVRF (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @v))
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"direct CBOR" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a.
(Eq a, Show a) =>
(a -> Encoding) -> (forall s. Decoder s a) -> a -> Property
prop_cbor_with @(VerKeyVRF v)
VerKeyVRF v -> Encoding
forall v. VRFAlgorithm v => VerKeyVRF v -> Encoding
encodeVerKeyVRF
Decoder s (VerKeyVRF v)
forall s. Decoder s (VerKeyVRF v)
forall v s. VRFAlgorithm v => Decoder s (VerKeyVRF v)
decodeVerKeyVRF
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a.
(Eq a, Show a) =>
(a -> Encoding) -> (forall s. Decoder s a) -> a -> Property
prop_cbor_with @(SignKeyVRF v)
SignKeyVRF v -> Encoding
forall v. VRFAlgorithm v => SignKeyVRF v -> Encoding
encodeSignKeyVRF
Decoder s (SignKeyVRF v)
forall s. Decoder s (SignKeyVRF v)
forall v s. VRFAlgorithm v => Decoder s (SignKeyVRF v)
decodeSignKeyVRF
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Cert" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a.
(Eq a, Show a) =>
(a -> Encoding) -> (forall s. Decoder s a) -> a -> Property
prop_cbor_with @(CertVRF v)
CertVRF v -> Encoding
forall v. VRFAlgorithm v => CertVRF v -> Encoding
encodeCertVRF
Decoder s (CertVRF v)
forall s. Decoder s (CertVRF v)
forall v s. VRFAlgorithm v => Decoder s (CertVRF v)
decodeCertVRF
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"To/FromCBOR class" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. (ToCBOR a, FromCBOR a, Eq a, Show a) => a -> Property
prop_cbor @(VerKeyVRF v)
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. (ToCBOR a, FromCBOR a, Eq a, Show a) => a -> Property
prop_cbor @(SignKeyVRF v)
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Cert" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. (ToCBOR a, FromCBOR a, Eq a, Show a) => a -> Property
prop_cbor @(CertVRF v)
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"ToCBOR size" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. ToCBOR a => a -> Property
prop_cbor_size @(VerKeyVRF v)
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. ToCBOR a => a -> Property
prop_cbor_size @(SignKeyVRF v)
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Sig" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. ToCBOR a => a -> Property
prop_cbor_size @(CertVRF v)
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"direct matches class" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a. ToCBOR a => (a -> Encoding) -> a -> Property
prop_cbor_direct_vs_class @(VerKeyVRF v)
VerKeyVRF v -> Encoding
forall v. VRFAlgorithm v => VerKeyVRF v -> Encoding
encodeVerKeyVRF
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a. ToCBOR a => (a -> Encoding) -> a -> Property
prop_cbor_direct_vs_class @(SignKeyVRF v)
SignKeyVRF v -> Encoding
forall v. VRFAlgorithm v => SignKeyVRF v -> Encoding
encodeSignKeyVRF
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Cert" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$
forall a. ToCBOR a => (a -> Encoding) -> a -> Property
prop_cbor_direct_vs_class @(CertVRF v)
CertVRF v -> Encoding
forall v. VRFAlgorithm v => CertVRF v -> Encoding
encodeCertVRF
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"verify" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Message -> SignKeyVRF v -> Bool) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"verify positive" ((Message -> SignKeyVRF v -> Bool) -> Spec)
-> (Message -> SignKeyVRF v -> Bool) -> Spec
forall a b. (a -> b) -> a -> b
$ forall v.
(VRFAlgorithm v, ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> Bool
prop_vrf_verify_pos @v
String
-> (Message -> SignKeyVRF v -> SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"verify negative" ((Message -> SignKeyVRF v -> SignKeyVRF v -> Property) -> Spec)
-> (Message -> SignKeyVRF v -> SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall v.
(VRFAlgorithm v, Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> SignKeyVRF v -> Property
prop_vrf_verify_neg @v
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"output" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (Message -> SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"sizeOutputVRF" ((Message -> SignKeyVRF v -> Property) -> Spec)
-> (Message -> SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall v.
(VRFAlgorithm v, ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> Property
prop_vrf_output_size @v
String -> (Message -> SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"mkTestOutputVRF" ((Message -> SignKeyVRF v -> Property) -> Spec)
-> (Message -> SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall v.
(VRFAlgorithm v, ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> Property
prop_vrf_output_natural @v
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"NoThunks" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> (VerKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"VerKey" ((VerKeyVRF v -> Property) -> Spec)
-> (VerKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. NoThunks a => a -> Property
prop_no_thunks @(VerKeyVRF v)
String -> (SignKeyVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"SignKey" ((SignKeyVRF v -> Property) -> Spec)
-> (SignKeyVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. NoThunks a => a -> Property
prop_no_thunks @(SignKeyVRF v)
String -> (CertVRF v -> Property) -> Spec
forall prop.
(HasCallStack, Testable prop) =>
String -> prop -> Spec
prop String
"Cert" ((CertVRF v -> Property) -> Spec)
-> (CertVRF v -> Property) -> Spec
forall a b. (a -> b) -> a -> b
$ forall a. NoThunks a => a -> Property
prop_no_thunks @(CertVRF v)
prop_vrf_verify_pos ::
forall v.
( VRFAlgorithm v
, ContextVRF v ~ ()
, Signable v ~ SignableRepresentation
) =>
Message ->
SignKeyVRF v ->
Bool
prop_vrf_verify_pos :: forall v.
(VRFAlgorithm v, ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> Bool
prop_vrf_verify_pos Message
a SignKeyVRF v
sk =
let (OutputVRF v
y, CertVRF v
c) = ContextVRF v -> Message -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
evalVRF () Message
a SignKeyVRF v
sk
vk :: VerKeyVRF v
vk = SignKeyVRF v -> VerKeyVRF v
forall v. VRFAlgorithm v => SignKeyVRF v -> VerKeyVRF v
deriveVerKeyVRF SignKeyVRF v
sk
in ContextVRF v
-> VerKeyVRF v -> Message -> CertVRF v -> Maybe (OutputVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v
-> VerKeyVRF v -> a -> CertVRF v -> Maybe (OutputVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v
-> VerKeyVRF v -> a -> CertVRF v -> Maybe (OutputVRF v)
verifyVRF () VerKeyVRF v
vk Message
a CertVRF v
c Maybe (OutputVRF v) -> Maybe (OutputVRF v) -> Bool
forall a. Eq a => a -> a -> Bool
== OutputVRF v -> Maybe (OutputVRF v)
forall a. a -> Maybe a
Just OutputVRF v
y
prop_vrf_verify_neg ::
forall v.
( VRFAlgorithm v
, Eq (SignKeyVRF v)
, ContextVRF v ~ ()
, Signable v ~ SignableRepresentation
) =>
Message ->
SignKeyVRF v ->
SignKeyVRF v ->
Property
prop_vrf_verify_neg :: forall v.
(VRFAlgorithm v, Eq (SignKeyVRF v), ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> SignKeyVRF v -> Property
prop_vrf_verify_neg Message
a SignKeyVRF v
sk SignKeyVRF v
sk' =
SignKeyVRF v
sk
SignKeyVRF v -> SignKeyVRF v -> Bool
forall a. Eq a => a -> a -> Bool
/= SignKeyVRF v
sk'
Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==> let (OutputVRF v
_y, CertVRF v
c) = ContextVRF v -> Message -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
evalVRF () Message
a SignKeyVRF v
sk'
vk :: VerKeyVRF v
vk = SignKeyVRF v -> VerKeyVRF v
forall v. VRFAlgorithm v => SignKeyVRF v -> VerKeyVRF v
deriveVerKeyVRF SignKeyVRF v
sk
in ContextVRF v
-> VerKeyVRF v -> Message -> CertVRF v -> Maybe (OutputVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v
-> VerKeyVRF v -> a -> CertVRF v -> Maybe (OutputVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v
-> VerKeyVRF v -> a -> CertVRF v -> Maybe (OutputVRF v)
verifyVRF () VerKeyVRF v
vk Message
a CertVRF v
c Maybe (OutputVRF v) -> Maybe (OutputVRF v) -> Bool
forall a. Eq a => a -> a -> Bool
== Maybe (OutputVRF v)
forall a. Maybe a
Nothing
prop_vrf_output_size ::
forall v.
( VRFAlgorithm v
, ContextVRF v ~ ()
, Signable v ~ SignableRepresentation
) =>
Message ->
SignKeyVRF v ->
Property
prop_vrf_output_size :: forall v.
(VRFAlgorithm v, ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> Property
prop_vrf_output_size Message
a SignKeyVRF v
sk =
let (OutputVRF v
out, CertVRF v
_c) = ContextVRF v -> Message -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
evalVRF () Message
a SignKeyVRF v
sk
in ByteString -> Int
BS.length (OutputVRF v -> ByteString
forall v. OutputVRF v -> ByteString
getOutputVRFBytes OutputVRF v
out)
Int -> Int -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> Word
forall (proxy :: * -> *). proxy v -> Word
sizeOutputVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v))
prop_vrf_output_natural ::
forall v.
( VRFAlgorithm v
, ContextVRF v ~ ()
, Signable v ~ SignableRepresentation
) =>
Message ->
SignKeyVRF v ->
Property
prop_vrf_output_natural :: forall v.
(VRFAlgorithm v, ContextVRF v ~ (),
Signable v ~ SignableRepresentation) =>
Message -> SignKeyVRF v -> Property
prop_vrf_output_natural Message
a SignKeyVRF v
sk =
let (OutputVRF v
out, CertVRF v
_c) = ContextVRF v -> Message -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
evalVRF () Message
a SignKeyVRF v
sk
n :: Natural
n = OutputVRF v -> Natural
forall v. OutputVRF v -> Natural
getOutputVRFNatural OutputVRF v
out
in String -> Property -> Property
forall prop. Testable prop => String -> prop -> Property
counterexample (Natural -> String
forall a. Show a => a -> String
show Natural
n) (Property -> Property) -> Property -> Property
forall a b. (a -> b) -> a -> b
$
Natural -> OutputVRF v
forall v. VRFAlgorithm v => Natural -> OutputVRF v
mkTestOutputVRF Natural
n OutputVRF v -> OutputVRF v -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== OutputVRF v
out
prop_bytesToNatural :: [Word8] -> Bool
prop_bytesToNatural :: [Word8] -> Bool
prop_bytesToNatural [Word8]
ws =
Int -> Natural -> ByteString
naturalToBytes (ByteString -> Int
BS.length ByteString
bs) (ByteString -> Natural
bytesToNatural ByteString
bs) ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== ByteString
bs
where
bs :: ByteString
bs = [Word8] -> ByteString
BS.pack [Word8]
ws
prop_naturalToBytes :: NonNegative Int -> Word64 -> Property
prop_naturalToBytes :: NonNegative Int -> Word64 -> Property
prop_naturalToBytes (NonNegative Int
sz) Word64
n =
Int
sz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
8 Bool -> Bool -> Property
forall prop. Testable prop => Bool -> prop -> Property
==>
ByteString -> Natural
bytesToNatural (Int -> Natural -> ByteString
naturalToBytes Int
sz (Word64 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
n)) Natural -> Natural -> Bool
forall a. Eq a => a -> a -> Bool
== Word64 -> Natural
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word64
n
prop_pubKeyToBatchComopat :: VerKeyVRF PraosVRF -> Property
prop_pubKeyToBatchComopat :: VerKeyVRF PraosVRF -> Property
prop_pubKeyToBatchComopat VerKeyVRF PraosVRF
vk =
VerKeyVRF PraosBatchCompatVRF -> ByteString
forall v. VRFAlgorithm v => VerKeyVRF v -> ByteString
rawSerialiseVerKeyVRF (VerKeyVRF PraosVRF -> VerKeyVRF PraosBatchCompatVRF
vkToBatchCompat VerKeyVRF PraosVRF
vk) ByteString -> ByteString -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== VerKeyVRF PraosVRF -> ByteString
forall v. VRFAlgorithm v => VerKeyVRF v -> ByteString
rawSerialiseVerKeyVRF VerKeyVRF PraosVRF
vk
prop_signKeyToBatchCompat :: SignKeyVRF PraosVRF -> Property
prop_signKeyToBatchCompat :: SignKeyVRF PraosVRF -> Property
prop_signKeyToBatchCompat SignKeyVRF PraosVRF
sk =
SignKeyVRF PraosBatchCompatVRF -> ByteString
forall v. VRFAlgorithm v => SignKeyVRF v -> ByteString
rawSerialiseSignKeyVRF (SignKeyVRF PraosVRF -> SignKeyVRF PraosBatchCompatVRF
skToBatchCompat SignKeyVRF PraosVRF
sk) ByteString -> ByteString -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== SignKeyVRF PraosVRF -> ByteString
forall v. VRFAlgorithm v => SignKeyVRF v -> ByteString
rawSerialiseSignKeyVRF SignKeyVRF PraosVRF
sk
prop_outputToBatchComat :: OutputVRF PraosVRF -> Property
prop_outputToBatchComat :: OutputVRF PraosVRF -> Property
prop_outputToBatchComat OutputVRF PraosVRF
output =
OutputVRF PraosBatchCompatVRF -> ByteString
forall v. OutputVRF v -> ByteString
getOutputVRFBytes (OutputVRF PraosVRF -> OutputVRF PraosBatchCompatVRF
outputToBatchCompat OutputVRF PraosVRF
output) ByteString -> ByteString -> Property
forall a. (Eq a, Show a) => a -> a -> Property
=== OutputVRF PraosVRF -> ByteString
forall v. OutputVRF v -> ByteString
getOutputVRFBytes OutputVRF PraosVRF
output
prop_verKeyValidConversion :: SizedSeed 32 -> Message -> Bool
prop_verKeyValidConversion :: SizedSeed 32 -> Message -> Bool
prop_verKeyValidConversion SizedSeed 32
sharedBytes Message
msg =
let
vkPraos :: VerKeyVRF PraosVRF
vkPraos = SignKeyVRF PraosVRF -> VerKeyVRF PraosVRF
forall v. VRFAlgorithm v => SignKeyVRF v -> VerKeyVRF v
deriveVerKeyVRF (SignKeyVRF PraosVRF -> VerKeyVRF PraosVRF)
-> (SizedSeed 32 -> SignKeyVRF PraosVRF)
-> SizedSeed 32
-> VerKeyVRF PraosVRF
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Seed -> SignKeyVRF PraosVRF
forall v. VRFAlgorithm v => Seed -> SignKeyVRF v
genKeyVRF (Seed -> SignKeyVRF PraosVRF)
-> (SizedSeed 32 -> Seed) -> SizedSeed 32 -> SignKeyVRF PraosVRF
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedSeed 32 -> Seed
forall (n :: Natural). SizedSeed n -> Seed
unSizedSeed (SizedSeed 32 -> VerKeyVRF PraosVRF)
-> SizedSeed 32 -> VerKeyVRF PraosVRF
forall a b. (a -> b) -> a -> b
$ SizedSeed 32
sharedBytes
skBatchCompat :: SignKeyVRF PraosBatchCompatVRF
skBatchCompat = Seed -> SignKeyVRF PraosBatchCompatVRF
forall v. VRFAlgorithm v => Seed -> SignKeyVRF v
genKeyVRF (Seed -> SignKeyVRF PraosBatchCompatVRF)
-> (SizedSeed 32 -> Seed)
-> SizedSeed 32
-> SignKeyVRF PraosBatchCompatVRF
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedSeed 32 -> Seed
forall (n :: Natural). SizedSeed n -> Seed
unSizedSeed (SizedSeed 32 -> SignKeyVRF PraosBatchCompatVRF)
-> SizedSeed 32 -> SignKeyVRF PraosBatchCompatVRF
forall a b. (a -> b) -> a -> b
$ SizedSeed 32
sharedBytes
vkBatchCompat :: VerKeyVRF PraosBatchCompatVRF
vkBatchCompat = VerKeyVRF PraosVRF -> VerKeyVRF PraosBatchCompatVRF
vkToBatchCompat VerKeyVRF PraosVRF
vkPraos
(OutputVRF PraosBatchCompatVRF
y, CertVRF PraosBatchCompatVRF
c) = ContextVRF PraosBatchCompatVRF
-> Message
-> SignKeyVRF PraosBatchCompatVRF
-> (OutputVRF PraosBatchCompatVRF, CertVRF PraosBatchCompatVRF)
forall a.
(HasCallStack, Signable PraosBatchCompatVRF a) =>
ContextVRF PraosBatchCompatVRF
-> a
-> SignKeyVRF PraosBatchCompatVRF
-> (OutputVRF PraosBatchCompatVRF, CertVRF PraosBatchCompatVRF)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
evalVRF () Message
msg SignKeyVRF PraosBatchCompatVRF
skBatchCompat
in
ContextVRF PraosBatchCompatVRF
-> VerKeyVRF PraosBatchCompatVRF
-> Message
-> CertVRF PraosBatchCompatVRF
-> Maybe (OutputVRF PraosBatchCompatVRF)
forall a.
(HasCallStack, Signable PraosBatchCompatVRF a) =>
ContextVRF PraosBatchCompatVRF
-> VerKeyVRF PraosBatchCompatVRF
-> a
-> CertVRF PraosBatchCompatVRF
-> Maybe (OutputVRF PraosBatchCompatVRF)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v
-> VerKeyVRF v -> a -> CertVRF v -> Maybe (OutputVRF v)
verifyVRF () VerKeyVRF PraosBatchCompatVRF
vkBatchCompat Message
msg CertVRF PraosBatchCompatVRF
c Maybe (OutputVRF PraosBatchCompatVRF)
-> Maybe (OutputVRF PraosBatchCompatVRF) -> Bool
forall a. Eq a => a -> a -> Bool
== OutputVRF PraosBatchCompatVRF
-> Maybe (OutputVRF PraosBatchCompatVRF)
forall a. a -> Maybe a
Just OutputVRF PraosBatchCompatVRF
y
prop_signKeyValidConversion :: SizedSeed 32 -> Bool
prop_signKeyValidConversion :: SizedSeed 32 -> Bool
prop_signKeyValidConversion SizedSeed 32
sharedBytes =
let
skPraos :: SignKeyVRF PraosVRF
skPraos = Seed -> SignKeyVRF PraosVRF
forall v. VRFAlgorithm v => Seed -> SignKeyVRF v
genKeyVRF (Seed -> SignKeyVRF PraosVRF)
-> (SizedSeed 32 -> Seed) -> SizedSeed 32 -> SignKeyVRF PraosVRF
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedSeed 32 -> Seed
forall (n :: Natural). SizedSeed n -> Seed
unSizedSeed (SizedSeed 32 -> SignKeyVRF PraosVRF)
-> SizedSeed 32 -> SignKeyVRF PraosVRF
forall a b. (a -> b) -> a -> b
$ SizedSeed 32
sharedBytes
skBatchCompat :: SignKeyVRF PraosBatchCompatVRF
skBatchCompat = Seed -> SignKeyVRF PraosBatchCompatVRF
forall v. VRFAlgorithm v => Seed -> SignKeyVRF v
genKeyVRF (Seed -> SignKeyVRF PraosBatchCompatVRF)
-> (SizedSeed 32 -> Seed)
-> SizedSeed 32
-> SignKeyVRF PraosBatchCompatVRF
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SizedSeed 32 -> Seed
forall (n :: Natural). SizedSeed n -> Seed
unSizedSeed (SizedSeed 32 -> SignKeyVRF PraosBatchCompatVRF)
-> SizedSeed 32 -> SignKeyVRF PraosBatchCompatVRF
forall a b. (a -> b) -> a -> b
$ SizedSeed 32
sharedBytes
in
SignKeyVRF PraosBatchCompatVRF
skBatchCompat SignKeyVRF PraosBatchCompatVRF
-> SignKeyVRF PraosBatchCompatVRF -> Bool
forall a. Eq a => a -> a -> Bool
== SignKeyVRF PraosVRF -> SignKeyVRF PraosBatchCompatVRF
skToBatchCompat SignKeyVRF PraosVRF
skPraos
instance VRFAlgorithm v => Arbitrary (VerKeyVRF v) where
arbitrary :: Gen (VerKeyVRF v)
arbitrary = SignKeyVRF v -> VerKeyVRF v
forall v. VRFAlgorithm v => SignKeyVRF v -> VerKeyVRF v
deriveVerKeyVRF (SignKeyVRF v -> VerKeyVRF v)
-> Gen (SignKeyVRF v) -> Gen (VerKeyVRF v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen (SignKeyVRF v)
forall a. Arbitrary a => Gen a
arbitrary
shrink :: VerKeyVRF v -> [VerKeyVRF v]
shrink = [VerKeyVRF v] -> VerKeyVRF v -> [VerKeyVRF v]
forall a b. a -> b -> a
const []
instance VRFAlgorithm v => Arbitrary (SignKeyVRF v) where
arbitrary :: Gen (SignKeyVRF v)
arbitrary = Seed -> SignKeyVRF v
forall v. VRFAlgorithm v => Seed -> SignKeyVRF v
genKeyVRF (Seed -> SignKeyVRF v) -> Gen Seed -> Gen (SignKeyVRF v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Word -> Gen Seed
arbitrarySeedOfSize Word
seedSize
where
seedSize :: Word
seedSize = Proxy v -> Word
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> Word
forall (proxy :: * -> *). proxy v -> Word
seedSizeVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v)
shrink :: SignKeyVRF v -> [SignKeyVRF v]
shrink = [SignKeyVRF v] -> SignKeyVRF v -> [SignKeyVRF v]
forall a b. a -> b -> a
const []
instance
( VRFAlgorithm v
, ContextVRF v ~ ()
, Signable v ~ SignableRepresentation
) =>
Arbitrary (CertVRF v)
where
arbitrary :: Gen (CertVRF v)
arbitrary = do
Message
a <- Gen Message
forall a. Arbitrary a => Gen a
arbitrary :: Gen Message
SignKeyVRF v
sk <- Gen (SignKeyVRF v)
forall a. Arbitrary a => Gen a
arbitrary
CertVRF v -> Gen (CertVRF v)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (CertVRF v -> Gen (CertVRF v)) -> CertVRF v -> Gen (CertVRF v)
forall a b. (a -> b) -> a -> b
$ (OutputVRF v, CertVRF v) -> CertVRF v
forall a b. (a, b) -> b
snd ((OutputVRF v, CertVRF v) -> CertVRF v)
-> (OutputVRF v, CertVRF v) -> CertVRF v
forall a b. (a -> b) -> a -> b
$ ContextVRF v -> Message -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall a.
(HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
forall v a.
(VRFAlgorithm v, HasCallStack, Signable v a) =>
ContextVRF v -> a -> SignKeyVRF v -> (OutputVRF v, CertVRF v)
evalVRF () Message
a SignKeyVRF v
sk
shrink :: CertVRF v -> [CertVRF v]
shrink = [CertVRF v] -> CertVRF v -> [CertVRF v]
forall a b. a -> b -> a
const []
instance VRFAlgorithm v => Arbitrary (OutputVRF v) where
arbitrary :: Gen (OutputVRF v)
arbitrary = do
ByteString
bytes <- [Word8] -> ByteString
BS.pack ([Word8] -> ByteString) -> Gen [Word8] -> Gen ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> Gen Word8 -> Gen [Word8]
forall a. Int -> Gen a -> Gen [a]
vectorOf (Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Proxy v -> Word
forall v (proxy :: * -> *). VRFAlgorithm v => proxy v -> Word
forall (proxy :: * -> *). proxy v -> Word
sizeOutputVRF (Proxy v
forall {k} (t :: k). Proxy t
Proxy :: Proxy v))) Gen Word8
forall a. Arbitrary a => Gen a
arbitrary
OutputVRF v -> Gen (OutputVRF v)
forall a. a -> Gen a
forall (m :: * -> *) a. Monad m => a -> m a
return (OutputVRF v -> Gen (OutputVRF v))
-> OutputVRF v -> Gen (OutputVRF v)
forall a b. (a -> b) -> a -> b
$ ByteString -> OutputVRF v
forall v. ByteString -> OutputVRF v
OutputVRF ByteString
bytes