{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Test.Crypto.Regressions (
tests
) where
import Test.Hspec (Spec, describe, it, shouldBe)
import Cardano.Crypto.DSIGN (rawDeserialiseVerKeyDSIGN)
import Cardano.Crypto.DSIGN.Ed25519 (Ed25519DSIGN)
import qualified Data.ByteString as BS
#ifdef SECP256K1_ENABLED
import Cardano.Crypto.DSIGN.SchnorrSecp256k1 (SchnorrSecp256k1DSIGN)
#endif
tests :: Spec
tests :: Spec
tests = String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Regressions" (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
"DSIGN" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
#ifdef SECP256K1_ENABLED
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Schnorr serialization" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Schnorr verkey deserialization fails on \"m\" literal" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
rawDeserialiseVerKeyDSIGN @SchnorrSecp256k1DSIGN ByteString
"m" Maybe (VerKeyDSIGN SchnorrSecp256k1DSIGN)
-> Maybe (VerKeyDSIGN SchnorrSecp256k1DSIGN) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Maybe (VerKeyDSIGN SchnorrSecp256k1DSIGN)
forall a. Maybe a
Nothing
#endif
String -> Spec -> Spec
forall a. HasCallStack => String -> SpecWith a -> SpecWith a
describe String
"Ed25519 serialization" (Spec -> Spec) -> Spec -> Spec
forall a b. (a -> b) -> a -> b
$ do
String -> Expectation -> SpecWith (Arg Expectation)
forall a.
(HasCallStack, Example a) =>
String -> a -> SpecWith (Arg a)
it String
"Ed25519 sign key deserialization fails on 33 NUL bytes" (Expectation -> SpecWith (Arg Expectation))
-> Expectation -> SpecWith (Arg Expectation)
forall a b. (a -> b) -> a -> b
$ do
forall v. DSIGNAlgorithm v => ByteString -> Maybe (VerKeyDSIGN v)
rawDeserialiseVerKeyDSIGN @Ed25519DSIGN (Int -> Word8 -> ByteString
BS.replicate Int
33 Word8
0) Maybe (VerKeyDSIGN Ed25519DSIGN)
-> Maybe (VerKeyDSIGN Ed25519DSIGN) -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Maybe (VerKeyDSIGN Ed25519DSIGN)
forall a. Maybe a
Nothing