Skip to content

Commit

Permalink
Merge #4386
Browse files Browse the repository at this point in the history
4386: Introduces property checking the size of Header's VRF Certs for different Eras r=abailly-iohk a=abailly-iohk

# Description

This PR does 2 things:
* An attempt at minimising the "attack surface" of consensus' dependencies on cardano-ledger crypto stuff related to Praos/TPraos, 
* Introduction of Property to check dispatching of crypto depending on era actually produces the right results.

## Hide Ledger's `PraosCrypto`

The idea is to remove direct dependencies from consensus package to cardano-ledger's `TPraos.API` module. There is a duplication of the `PraosCrypto` typeclass between the two components which does seem unnecessary as ultimately, these crypto primitives should end up in the consensus where they are used and relevant. 

I would have loved to be able to remove the ledger's `PraosCrypto` altogether but of course this is not possible as we use quite a few functions from the ledger that depend on it. So the tiny first step consists in hiding the dependency on `Ledger.PraosCrypto` behind the `Ouroboros.Consensus.Praos.Crypto.PraosCrypto` typeclass (reexported by `Praos` and `TPraos` modules). This simplifies some constraints down the road.

The hypothesis this work is based on is that if we manage to locate all dependencies from consensus to ledger for KES and VRF stuff, then introducing a new `Crypto` typeclass and primitives will have a minimal impact over the codebase and could be done independently of the refactoring in the cardano-ledger.

## Add Property to check "dispatching" of VRF per Era

The goal of #4150 is to ensure different eras can have different crypto implementations for things such as VRF proofs generation and verification, and KES signing. While #4151 provided solutions to this problem, this PR tries to make the problem manifest through a property that, given an arbitrary header from different eras, verifies the correct crypto is used. This is done simply by verifying the sizes of the VRF certificates which are different between plain Praos and Batch compatible VRF. 
 


Co-authored-by: Arnaud Bailly <arnaud.bailly@iohk.io>
Co-authored-by: Arnaud Bailly <79840582+abailly-iohk@users.noreply.github.com>
Co-authored-by: Joris Dral <joris@well-typed.com>
  • Loading branch information
4 people authored Mar 10, 2023
2 parents f5f8679 + b42c81d commit f82b50f
Show file tree
Hide file tree
Showing 18 changed files with 264 additions and 90 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -83,6 +83,7 @@ test-suite test
main-is: Main.hs
other-modules:
Test.Consensus.Cardano.ByronCompatibility
Test.Consensus.Cardano.Crypto
Test.Consensus.Cardano.Golden
Test.Consensus.Cardano.Serialisation
Test.ThreadNet.AllegraMary
Expand All @@ -93,6 +94,7 @@ test-suite test
build-depends: base >=4.14 && <4.17
, bytestring
, cardano-crypto-class
, cardano-crypto-praos
, cardano-slotting
, cborg
, containers
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,7 @@ import Ouroboros.Consensus.HeaderValidation
import Ouroboros.Consensus.Node.NetworkProtocolVersion
import Ouroboros.Consensus.Node.Serialisation (Some (..))
import Ouroboros.Consensus.Protocol.Praos.Translate ()
import Ouroboros.Consensus.Protocol.TPraos (TPraos)
import Ouroboros.Consensus.Protocol.TPraos (PraosCrypto, TPraos)
import Ouroboros.Consensus.Shelley.Ledger.Block ()
import Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol ()
import Ouroboros.Consensus.TypeFamilyWrappers
Expand All @@ -53,28 +53,41 @@ import Ouroboros.Consensus.Shelley.Ledger
import Ouroboros.Consensus.Cardano.Block
import Ouroboros.Consensus.Cardano.Node (CardanoHardForkConstraints)

import Cardano.Ledger.Crypto (Crypto (..))

import Test.Cardano.Ledger.Conway.Serialisation.Generators ()
import Test.Consensus.Byron.Generators
import Test.Consensus.Cardano.MockCrypto
import Test.Consensus.Protocol.Serialisation.Generators ()
import Test.Consensus.Shelley.Generators
import Test.Consensus.Shelley.Generators (SomeResult (..))
import Test.Consensus.Shelley.MockCrypto (CanMock)
import Test.Util.Orphans.Arbitrary ()
import Test.Util.Serialisation.Roundtrip (Coherent (..),
WithVersion (..))

import qualified Cardano.Crypto.DSIGN as DSIGN
import Cardano.Crypto.Hash.Blake2b (Blake2b_224, Blake2b_256)
import qualified Cardano.Crypto.KES as KES
import Cardano.Crypto.Util (SignableRepresentation)
import qualified Cardano.Crypto.VRF as VRF
import qualified Cardano.Ledger.BaseTypes as SL

{-------------------------------------------------------------------------------
Disk
-------------------------------------------------------------------------------}

instance Arbitrary (CardanoBlock MockCryptoCompatByron) where
instance ( DSIGN.Signable (DSIGN c) ~ SignableRepresentation
, KES.Signable (KES c) ~ SignableRepresentation
, VRF.Signable (VRF c) SL.Seed
, PraosCrypto c
) => Arbitrary (CardanoBlock c) where
arbitrary =
oneof $ catMaybes $ hcollapse generators
where
generators ::
NP
(K (Maybe (Gen (CardanoBlock MockCryptoCompatByron))))
(CardanoEras MockCryptoCompatByron)
(K (Maybe (Gen (CardanoBlock c))))
(CardanoEras c)
generators =
mk BlockByron
:* mk BlockShelley
Expand All @@ -87,18 +100,22 @@ instance Arbitrary (CardanoBlock MockCryptoCompatByron) where

mk ::
forall a x. Arbitrary a
=> (a -> CardanoBlock MockCryptoCompatByron)
-> K (Maybe (Gen (CardanoBlock MockCryptoCompatByron))) x
=> (a -> CardanoBlock c)
-> K (Maybe (Gen (CardanoBlock c))) x
mk f = K $ Just $ f <$> arbitrary

instance Arbitrary (Coherent (CardanoBlock MockCryptoCompatByron)) where
instance ( DSIGN.Signable (DSIGN c) ~ SignableRepresentation
, KES.Signable (KES c) ~ SignableRepresentation
, VRF.Signable (VRF c) SL.Seed
, PraosCrypto c
) => Arbitrary (Coherent (CardanoBlock c)) where
arbitrary =
fmap Coherent $ oneof $ catMaybes $ hcollapse generators
where
generators ::
NP
(K (Maybe (Gen (CardanoBlock MockCryptoCompatByron))))
(CardanoEras MockCryptoCompatByron)
(K (Maybe (Gen (CardanoBlock c))))
(CardanoEras c)
generators =
mk BlockByron
:* mk BlockShelley
Expand All @@ -111,12 +128,41 @@ instance Arbitrary (Coherent (CardanoBlock MockCryptoCompatByron)) where

mk ::
forall a x. Arbitrary (Coherent a)
=> (a -> CardanoBlock MockCryptoCompatByron)
-> K (Maybe (Gen (CardanoBlock MockCryptoCompatByron))) x
=> (a -> CardanoBlock c)
-> K (Maybe (Gen (CardanoBlock c))) x
mk f = K $ Just $ f . getCoherent <$> arbitrary

instance Arbitrary (CardanoHeader MockCryptoCompatByron) where
arbitrary = getHeader <$> arbitrary
instance ( DSIGN.Signable (DSIGN c) ~ SignableRepresentation
, KES.Signable (KES c) ~ SignableRepresentation
, VRF.Signable (VRF c) SL.Seed
, HASH c ~ Blake2b_256
, ADDRHASH c ~ Blake2b_224
, DSIGN c ~ DSIGN.Ed25519DSIGN
, PraosCrypto c
) => Arbitrary (CardanoHeader c) where
arbitrary =
oneof $ catMaybes $ hcollapse generators
where
generators ::
NP
(K (Maybe (Gen (CardanoHeader c))))
(CardanoEras c)
generators =
mk HeaderByron
:* mk HeaderShelley
:* mk HeaderAllegra
:* mk HeaderMary
:* mk HeaderAlonzo
:* mk HeaderBabbage
:* mk HeaderConway
:* Nil

mk ::
forall a x. Arbitrary a
=> (a -> CardanoHeader c)
-> K (Maybe (Gen (CardanoHeader c))) x
mk f = K $ Just $ f <$> arbitrary


instance (CanMock (TPraos c) (ShelleyEra c), CardanoHardForkConstraints c)
=> Arbitrary (OneEraHash (CardanoEras c)) where
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ import Cardano.Crypto.KES (MockKES)
import Cardano.Crypto.VRF (MockVRF)

import Cardano.Ledger.Crypto (Crypto (..))
import qualified Cardano.Protocol.TPraos.API as Protocol

import qualified Ouroboros.Consensus.Protocol.Praos as Praos
import qualified Ouroboros.Consensus.Protocol.TPraos as TPraos

-- | A replacement for 'Test.Consensus.Shelley.MockCrypto' that is compatible
Expand Down Expand Up @@ -41,6 +41,6 @@ instance Crypto MockCryptoCompatByron where
type KES MockCryptoCompatByron = MockKES 10
type VRF MockCryptoCompatByron = MockVRF

instance TPraos.PraosCrypto MockCryptoCompatByron
instance Protocol.PraosCrypto MockCryptoCompatByron

instance Praos.PraosCrypto MockCryptoCompatByron
instance TPraos.PraosCrypto MockCryptoCompatByron
2 changes: 2 additions & 0 deletions ouroboros-consensus-cardano-test/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ import Cardano.Crypto.Libsodium (sodiumInit)
import Test.Tasty

import qualified Test.Consensus.Cardano.ByronCompatibility (tests)
import qualified Test.Consensus.Cardano.Crypto (tests)
import qualified Test.Consensus.Cardano.Golden (tests)
import qualified Test.Consensus.Cardano.Serialisation (tests)
import qualified Test.ThreadNet.AllegraMary (tests)
Expand All @@ -30,6 +31,7 @@ tests =
[ Test.Consensus.Cardano.ByronCompatibility.tests
, Test.Consensus.Cardano.Golden.tests
, Test.Consensus.Cardano.Serialisation.tests
, Test.Consensus.Cardano.Crypto.tests
, Test.ThreadNet.AllegraMary.tests
, Test.ThreadNet.Cardano.tests
, Test.ThreadNet.MaryAlonzo.tests
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,98 @@
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

-- | Tests consensus-specific crypto operations in relationship with blocks/headers.
module Test.Consensus.Cardano.Crypto (tests) where

import Cardano.Crypto.VRF (sizeCertVRF)
import Cardano.Crypto.VRF.Praos (certSizeVRF)
import Data.Function ((&))
import Ouroboros.Consensus.Cardano.Block (CardanoHeader,
StandardCrypto, pattern HeaderAllegra,
pattern HeaderAlonzo, pattern HeaderBabbage,
pattern HeaderByron, pattern HeaderConway,
pattern HeaderMary, pattern HeaderShelley)
import Ouroboros.Consensus.Shelley.Ledger.Block (Header (..))
import Ouroboros.Consensus.Shelley.Protocol.Abstract
(pTieBreakVRFValue)
import Ouroboros.Consensus.Shelley.Protocol.Praos ()
import Test.Consensus.Cardano.Generators ()
import Test.QuickCheck (Property, label, property, (===))
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.QuickCheck (testProperty)

tests :: TestTree
tests =
testGroup "Cardano Crypto" [
testProperty "era-dependent VRF" prop_VRFCryptoDependsOnBlockEra
]

-- | Check that Babbage and Conway blocks use different VRF crypto.
--
-- This test is based on the following steps:
--
-- 1. generate (forge?) babbage or conway headers
-- - those should contain different VRF proofs (because they are supposed to
-- use different algorithms)
-- - the VRF proof should be invalid for the other era
-- 2. call some header validation functions that's calling VRF certificate check
-- 3. assert that different VRF function is called for each era
-- - the header should be valid
--
-- * why not mock everything? because it does not check that we are
-- implementing things correctly for Conway we would like to test
-- the dispatchign induced by this type, to make clear Conway relies
-- on different crypto primitives
--
-- What needs to change is this type:
--
-- @@
-- type CardanoShelleyEras c =
-- '[ ShelleyBlock (TPraos c) (ShelleyEra c)
-- , ShelleyBlock (TPraos c) (AllegraEra c)
-- , ShelleyBlock (TPraos c) (MaryEra c)
-- , ShelleyBlock (TPraos c) (AlonzoEra c)
-- , ShelleyBlock (Praos c) (BabbageEra c)
-- , ShelleyBlock (Praos c) (ConwayEra c)
-- ]
-- @@
--
-- is it enough to test a single specialised crypto function? yes,
-- because that's a start, but also because using the high level
-- HFBlock even with a single function would be evidence we are doing
-- the dispatching right => we don't test the actual crypto functions,
-- only the "dispatching" logic that requires different instances for
-- different eras.
--
prop_VRFCryptoDependsOnBlockEra :: CardanoHeader StandardCrypto -> Property
prop_VRFCryptoDependsOnBlockEra = \case
HeaderShelley ShelleyHeader {shelleyHeaderRaw} ->
certVRFHasPraosSize shelleyHeaderRaw & label "Shelley"
HeaderAllegra ShelleyHeader {shelleyHeaderRaw} ->
certVRFHasPraosSize shelleyHeaderRaw & label "Allegra"
HeaderMary ShelleyHeader {shelleyHeaderRaw} ->
certVRFHasPraosSize shelleyHeaderRaw & label "Mary"
HeaderAlonzo ShelleyHeader {shelleyHeaderRaw} ->
certVRFHasPraosSize shelleyHeaderRaw & label "Alonzo"
HeaderBabbage ShelleyHeader {shelleyHeaderRaw} ->
certVRFHasPraosSize shelleyHeaderRaw & label "Babbage"
HeaderConway ShelleyHeader {shelleyHeaderRaw} ->
-- TODO: this is were we need to change to check we use in the Conway case
-- Cardano.Crypto.VRF.PraosBatchCompat.certSizevrf
certVRFHasPraosSize shelleyHeaderRaw & label "Conway"
HeaderByron _ -> property True & label "Byron"

where
certVRFHasPraosSize hdrRaw = sizeCertVRF (pTieBreakVRFValue hdrRaw) === fromIntegral certSizeVRF
Original file line number Diff line number Diff line change
Expand Up @@ -47,6 +47,7 @@ library
, cardano-data
, cardano-ledger-byron
, cardano-ledger-core
, cardano-ledger-mary
, cardano-ledger-shelley
, cardano-prelude
, cardano-protocol-tpraos
Expand Down
Loading

0 comments on commit f82b50f

Please sign in to comment.