Skip to content

Commit

Permalink
[WIP] block authentication
Browse files Browse the repository at this point in the history
  • Loading branch information
larskuhtz committed Apr 20, 2023
1 parent c39ad55 commit 24c100a
Show file tree
Hide file tree
Showing 3 changed files with 42 additions and 1 deletion.
2 changes: 2 additions & 0 deletions chainweb.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -118,6 +118,7 @@ library
c-sources: c/shathree.c
exposed-modules:
Chainweb.Backup
, Chainweb.BlockAuthentication
, Chainweb.BlockCreationTime
, Chainweb.BlockHash
, Chainweb.BlockHeader
Expand Down Expand Up @@ -352,6 +353,7 @@ library
, filepath >= 1.4
, ghc-compact >= 0.1
, hashable >= 1.3
, hashes >= 0.2.3
, heaps >= 0.3
, hourglass >=0.2
, http-client >= 0.5
Expand Down
11 changes: 11 additions & 0 deletions src/Chainweb/BlockHeader.hs
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,8 @@ module Chainweb.BlockHeader
, blockFlags
, _blockPow
, blockPow
, _blockAuth
, blockAuth
, _blockAdjacentChainIds
, blockAdjacentChainIds
, encodeBlockHeader
Expand Down Expand Up @@ -129,6 +131,7 @@ import GHC.Generics (Generic)

-- Internal imports

import Chainweb.BlockAuthentication
import Chainweb.BlockCreationTime
import Chainweb.BlockHash
import Chainweb.BlockHeight
Expand Down Expand Up @@ -824,6 +827,14 @@ blockPow :: Getter BlockHeader PowHash
blockPow = to _blockPow
{-# INLINE blockPow #-}

_blockAuth :: BlockAuthenticationKey -> BlockHeader -> BlockAuthenticationHash
_blockAuth k h = blockAuthenticationHash k
$ runPutS $ encodeBlockHeaderWithoutHash h

blockAuth :: BlockAuthenticationKey -> Getter BlockHeader BlockAuthenticationHash
blockAuth k = to (_blockAuth k)
{-# INLINE blockAuth #-}

-- | The number of microseconds between the creation time of two `BlockHeader`s.
--
timeBetween :: BlockCreationTime -> BlockCreationTime -> Micros
Expand Down
30 changes: 29 additions & 1 deletion src/Chainweb/BlockHeader/Validation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}

-- |
-- Module: Chainweb.BlockHeader.Validation
Expand Down Expand Up @@ -73,6 +74,7 @@ module Chainweb.BlockHeader.Validation

-- * Intrinsic BlockHeader Properties
, prop_block_pow
, prop_block_auth
, prop_block_hash
, prop_block_genesis_parent
, prop_block_genesis_target
Expand Down Expand Up @@ -108,6 +110,7 @@ import System.IO.Unsafe

-- internal modules

import Chainweb.BlockAuthentication
import Chainweb.BlockCreationTime
import Chainweb.BlockHash
import Chainweb.BlockHeader
Expand Down Expand Up @@ -305,6 +308,7 @@ instance Show ValidationFailure where
AdjacentParentChainMismatch -> "An adjacent parent hash references a block on the wrong chain"
IncorrectHash -> "The hash of the block header does not match the one given"
IncorrectPow -> "The POW hash does not match the POW target of the block"
IncorrectAuth -> "The block authentication hash of the header does not match the the nonce of the header"
IncorrectEpoch -> "The epoch start time of the block is incorrect"
IncorrectHeight -> "The given height is not one more than the parent height"
IncorrectWeight -> "The given weight is not the sum of the difficulty target and the parent's weight"
Expand Down Expand Up @@ -342,6 +346,10 @@ data ValidationFailureType
| IncorrectPow
-- ^ The POW hash of the header does not match the POW target of the
-- block.
| IncorrectAuth
-- ^ [Only applicable for networks that support it and if the BLOCK_AUTHENTICATION_KEY
-- environment variable is set] The block authentication hash of the header does not match
-- the the nonce of the header.
| IncorrectHeight
-- ^ The given height is not one more than the parent height.
| IncorrectWeight
Expand Down Expand Up @@ -396,6 +404,7 @@ definiteValidationFailures =
, ChainMismatch
, IncorrectHash
, IncorrectPow
, IncorrectAuth
, IncorrectHeight
, IncorrectWeight
, IncorrectTarget
Expand Down Expand Up @@ -627,6 +636,7 @@ validateIntrinsic
-- ^ A list of ways in which the block header isn't valid
validateIntrinsic t b = concat
[ [ IncorrectHash | not (prop_block_hash b) ]
, [ IncorrectAuth | not (prop_block_auth b) ]
, [ IncorrectPow | not (prop_block_pow b) ]
, [ IncorrectGenesisParent | not (prop_block_genesis_parent b)]
, [ IncorrectGenesisTarget | not (prop_block_genesis_target b)]
Expand Down Expand Up @@ -675,6 +685,24 @@ validateInductiveWebStep s = concat
-- Intrinsic BlockHeader properties
-- -------------------------------------------------------------------------- --

blockAuthenticationKey :: Maybe BlockAuthenticationKey
blockAuthenticationKey = fmap (unsafeFromText . T.pack)
$ unsafeDupablePerformIO
$ lookupEnv "BLOCK_AUTHENTICATION_KEY"
{-# NOINLINE blockAuthenticationKey #-}

prop_block_auth :: BlockHeader -> Bool
prop_block_auth b
-- Genesis block headers are not mined. So there's not need for Auth
| isGenesisBlockHeader b = True

-- Mainnet: no support for block authentication
| _blockChainwebVersion b == Mainnet01 = True

| otherwise = case blockAuthenticationKey of
Just k -> blockAuthenticationHashAsWord64 (_blockAuth k b) == encodeNonceToWord64 (_blockNonce b)
Nothing -> True

powDisabled :: Bool
powDisabled = case unsafeDupablePerformIO $ lookupEnv "DISABLE_POW_VALIDATION" of
Nothing -> False
Expand All @@ -683,8 +711,8 @@ powDisabled = case unsafeDupablePerformIO $ lookupEnv "DISABLE_POW_VALIDATION" o

prop_block_pow :: BlockHeader -> Bool
prop_block_pow b
-- Genesis block headers are not mined. So there's not need for POW
| isGenesisBlockHeader b = True
-- Genesis block headers are not mined. So there's not need for POW
| _blockChainwebVersion b == Development && powDisabled = True
| otherwise = checkTarget (_blockTarget b) (_blockPow b)

Expand Down

0 comments on commit 24c100a

Please sign in to comment.