Jordan/pow cache management (#888)

* PoW wrapper for verification & mining

why:
  It eases data management of per-Epoch lookup tables. Also some unit
  tests show limits of usefulness on non-specialised machines for
  mining besides developing tests.

details:
  For PoW verification, this patch provides a pretty wrapper hiding the
  details of the ethash/Hashimoto lookup cache management.

  For mining on my development system without special hardware, the
  underlying ethash functions are prohibitively slow. It takes
   * ~20 minutes to prepare the full ethash/Hashimoto lookup dataset
   * a second to run ~25k nonce tests (in the mining loop)

  The mining part might be of some use for generating test data for
  the tx-pool, though.

* Using PowRef as replacement for EpochHashCache + hashimotoLight()

* Fix typo (CI failed)

why:
  was below log level when testing locally

* fix canonical naming
This commit is contained in:
Jordan Hrycaj 2021-12-10 08:49:57 +00:00 committed by GitHub
parent 10a3946194
commit 55f7a4425f
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
11 changed files with 875 additions and 171 deletions

View File

@ -13,10 +13,10 @@ import
../../db/db_chain,
../../genesis,
../../utils,
../../utils/pow,
../../chain_config,
../clique,
../validate,
../validate/epoch_hash_cache,
chronicles,
eth/[common, trie/db],
stew/endians2,
@ -53,8 +53,8 @@ type
## First block to when `extraValidation` will be applied (only
## effective if `extraValidation` is true.)
cacheByEpoch: EpochHashCache ##\
## Objects cache to speed up hash lookup in validation functions.
pow: PowRef ##\
## Wrapper around `hashimotoLight()` and lookup cache
poa: Clique ##\
## For non-PoA networks (when `db.config.poaEngine` is `false`),
@ -144,9 +144,9 @@ proc initChain(c: Chain; db: BaseChainDB; poa: Clique; extraValidation: bool)
# this descriptor is ignored.
c.poa = db.newClique
# Always initialise the epoch cache even though it migh no be used
# Always initialise the PoW epoch cache even though it migh no be used
# unless `extraValidation` is set `true`.
c.cacheByEpoch.initEpochHashCache
c.pow = PowRef.new
# ------------------------------------------------------------------------------
# Public constructors
@ -204,9 +204,9 @@ proc clique*(c: Chain): var Clique {.inline.} =
## Getter
c.poa
proc cacheByEpoch*(c: Chain): var EpochHashCache {.inline.} =
proc pow*(c: Chain): PowRef {.inline.} =
## Getter
c.cacheByEpoch
c.pow
proc db*(c: Chain): auto {.inline.} =
## Getter

View File

@ -88,7 +88,7 @@ proc persistBlocksImpl(c: Chain; headers: openarray[BlockHeader];
header,
body,
checkSealOK = false, # TODO: how to checkseal from here
c.cacheByEpoch)
c.pow)
if res.isErr:
debug "block validation error",
msg = res.error

View File

@ -19,7 +19,7 @@ import
../vm_types,
../forks,
./dao,
./validate/epoch_hash_cache,
../utils/pow,
./gaslimit,
chronicles,
eth/[common, rlp, trie/trie_defs],
@ -32,119 +32,55 @@ from stew/byteutils
import nil
export
epoch_hash_cache.EpochHashCache,
epoch_hash_cache.initEpochHashCache,
pow.PowRef,
pow.new,
results
const
daoForkBlockExtraData =
byteutils.hexToByteArray[13](DAOForkBlockExtra).toSeq
type
MiningHeader = object
parentHash : Hash256
ommersHash : Hash256
coinbase : EthAddress
stateRoot : Hash256
txRoot : Hash256
receiptRoot : Hash256
bloom : common.BloomFilter
difficulty : DifficultyInt
blockNumber : BlockNumber
gasLimit : GasInt
gasUsed : GasInt
timestamp : EthTime
extraData : Blob
Hash512 = MDigest[512]
{.push raises: [Defect,CatchableError].}
# ------------------------------------------------------------------------------
# Private Helpers
# ------------------------------------------------------------------------------
func toMiningHeader(header: BlockHeader): MiningHeader =
result.parentHash = header.parentHash
result.ommersHash = header.ommersHash
result.coinbase = header.coinbase
result.stateRoot = header.stateRoot
result.txRoot = header.txRoot
result.receiptRoot = header.receiptRoot
result.bloom = header.bloom
result.difficulty = header.difficulty
result.blockNumber = header.blockNumber
result.gasLimit = header.gasLimit
result.gasUsed = header.gasUsed
result.timestamp = header.timestamp
result.extraData = header.extraData
func hash(header: MiningHeader): Hash256 =
keccakHash(rlp.encode(header))
func isGenesis(header: BlockHeader): bool =
header.blockNumber == 0.u256 and
header.parentHash == GENESIS_PARENT_HASH
# ------------------------------------------------------------------------------
# Private cache management functions
# ------------------------------------------------------------------------------
func cacheHash(x: EpochHashDigest): Hash256 =
var ctx: keccak256
ctx.init()
for a in x:
ctx.update(a.data[0].unsafeAddr, uint(a.data.len))
ctx.finish result.data
ctx.clear()
# ------------------------------------------------------------------------------
# Pivate validator functions
# ------------------------------------------------------------------------------
proc checkPOW(blockNumber: Uint256; miningHash, mixHash: Hash256;
nonce: BlockNonce; difficulty: DifficultyInt;
hashCache: var EpochHashCache): Result[void,string] =
let
blockNumber = blockNumber.truncate(uint64)
cache = hashCache.getEpochHash(blockNumber)
size = getDataSize(blockNumber)
miningOutput = hashimotoLight(
size, cache, miningHash, uint64.fromBytesBE(nonce))
proc validateSeal(pow: PoWRef; header: BlockHeader): Result[void,string] =
let (expMixDigest,miningValue) = pow.getPowDigest(header)
if miningOutput.mixDigest != mixHash:
if expMixDigest != header.mixDigest:
let
miningHash = header.getPowSpecs.miningHash
(size, cachedHash) = pow.getPowCacheLookup(header.blockNumber)
debug "mixHash mismatch",
actual = miningOutput.mixDigest,
expected = mixHash,
blockNumber = blockNumber,
actual = header.mixDigest,
expected = expMixDigest,
blockNumber = header.blockNumber,
miningHash = miningHash,
nonce = nonce.toHex,
difficulty = difficulty,
nonce = header.nonce.toHex,
difficulty = header.difficulty,
size = size,
cachedHash = cacheHash(cache)
cachedHash = cachedHash
return err("mixHash mismatch")
let value = Uint256.fromBytesBE(miningOutput.value.data)
if value > Uint256.high div difficulty:
let value = Uint256.fromBytesBE(miningValue.data)
if value > Uint256.high div header.difficulty:
return err("mining difficulty error")
result = ok()
proc validateSeal(hashCache: var EpochHashCache;
header: BlockHeader): Result[void,string] =
let miningHeader = header.toMiningHeader
let miningHash = miningHeader.hash
checkPOW(header.blockNumber, miningHash,
header.mixDigest, header.nonce, header.difficulty, hashCache)
ok()
proc validateHeader(db: BaseChainDB; header, parentHeader: BlockHeader;
numTransactions: int; checkSealOK: bool;
hashCache: var EpochHashCache): Result[void,string] =
pow: PowRef): Result[void,string] =
template inDAOExtraRange(blockNumber: BlockNumber): bool =
# EIP-799
@ -178,7 +114,7 @@ proc validateHeader(db: BaseChainDB; header, parentHeader: BlockHeader;
return err("provided header difficulty is too low")
if checkSealOK:
return hashCache.validateSeal(header)
return pow.validateSeal(header)
result = ok()
@ -202,7 +138,7 @@ func validateUncle(currBlock, uncle, uncleParent: BlockHeader):
proc validateUncles(chainDB: BaseChainDB; header: BlockHeader;
uncles: seq[BlockHeader]; checkSealOK: bool;
hashCache: var EpochHashCache): Result[void,string] =
pow: PowRef): Result[void,string] =
let hasUncles = uncles.len > 0
let shouldHaveUncles = header.ommersHash != EMPTY_UNCLE_HASH
@ -258,7 +194,7 @@ proc validateUncles(chainDB: BaseChainDB; header: BlockHeader;
# Now perform VM level validation of the uncle
if checkSealOK:
result = hashCache.validateSeal(uncle)
result = pow.validateSeal(uncle)
if result.isErr:
return
@ -351,7 +287,7 @@ proc validateTransaction*(vmState: BaseVMState, tx: Transaction,
proc validateHeaderAndKinship*(chainDB: BaseChainDB; header: BlockHeader;
uncles: seq[BlockHeader]; numTransactions: int; checkSealOK: bool;
hashCache: var EpochHashCache): Result[void,string] =
pow: PowRef): Result[void,string] =
if header.isGenesis:
if header.extraData.len > 32:
return err("BlockHeader.extraData larger than 32 bytes")
@ -359,7 +295,7 @@ proc validateHeaderAndKinship*(chainDB: BaseChainDB; header: BlockHeader;
let parent = chainDB.getBlockHeader(header.parentHash)
result = chainDB.validateHeader(
header, parent, numTransactions, checkSealOK, hashCache)
header, parent, numTransactions, checkSealOK, pow)
if result.isErr:
return
@ -369,22 +305,22 @@ proc validateHeaderAndKinship*(chainDB: BaseChainDB; header: BlockHeader;
if not chainDB.exists(header.stateRoot):
return err("`state_root` was not found in the db.")
result = chainDB.validateUncles(header, uncles, checkSealOK, hashCache)
result = chainDB.validateUncles(header, uncles, checkSealOK, pow)
if result.isOk:
result = chainDB.validateGasLimitOrBaseFee(header, parent)
proc validateHeaderAndKinship*(chainDB: BaseChainDB;
header: BlockHeader; body: BlockBody; checkSealOK: bool;
hashCache: var EpochHashCache): Result[void,string] =
pow: PowRef): Result[void,string] =
chainDB.validateHeaderAndKinship(
header, body.uncles, body.transactions.len, checkSealOK, hashCache)
header, body.uncles, body.transactions.len, checkSealOK, pow)
proc validateHeaderAndKinship*(chainDB: BaseChainDB; ethBlock: EthBlock;
checkSealOK: bool; hashCache: var EpochHashCache): Result[void,string] =
checkSealOK: bool; pow: PowRef): Result[void,string] =
chainDB.validateHeaderAndKinship(
ethBlock.header, ethBlock.uncles, ethBlock.txs.len, checkSealOK, hashCache)
ethBlock.header, ethBlock.uncles, ethBlock.txs.len, checkSealOK, pow)
# ------------------------------------------------------------------------------
# End

View File

@ -1,66 +0,0 @@
# Nimbus
# Copyright (c) 2018 Status Research & Development GmbH
# Licensed under either of
# * Apache License, version 2.0, ([LICENSE-APACHE](LICENSE-APACHE) or
# http://www.apache.org/licenses/LICENSE-2.0)
# * MIT license ([LICENSE-MIT](LICENSE-MIT) or
# http://opensource.org/licenses/MIT)
# at your option. This file may not be copied, modified, or distributed except
# according to those terms.
## Hash Cache
## ==========
##
## provide LRU hash, indexed by epoch
import
../../utils/lru_cache,
ethash,
nimcrypto,
tables
type
BlockEpoch = distinct uint64
EpochHashDigest* = seq[MDigest[512]]
EpochHashCache* = LruCache[uint64,BlockEpoch,EpochHashDigest,void]
{.push raises: [Defect,CatchableError].}
# ------------------------------------------------------------------------------
# Private cache management functions
# ------------------------------------------------------------------------------
# needed for table key to work
proc `==`(a,b: BlockEpoch): bool {.borrow.}
# ------------------------------------------------------------------------------
# Public functions
# ------------------------------------------------------------------------------
proc initEpochHashCache*(cache: var EpochHashCache; cacheMaxItems = 10) =
## Initialise a new cache indexed by block epoch
template bnToEpoch(num: uint64): BlockEpoch =
BlockEpoch(blockNumber div EPOCH_LENGTH)
var toKey: LruKey[uint64,BlockEpoch] =
proc(blockNumber: uint64): BlockEpoch =
blockNumber.bnToEpoch
var toValue: LruValue[uint64,EpochHashDigest,void] =
proc(blockNumber: uint64): Result[EpochHashDigest,void] =
let top = blockNumber.bnToEpoch.uint64 * EPOCH_LENGTH
ok( mkcache( getCacheSize(top), getSeedhash(top)))
cache.initCache(toKey, toValue, cacheMaxItems)
proc getEpochHash*(cache: var EpochHashCache;
blockNumber: uint64): auto {.inline.} =
## Return hash list, indexed by epoch of argument `blockNumber`
cache.getItem(blockNumber).value
# ------------------------------------------------------------------------------
# End
# ------------------------------------------------------------------------------

352
nimbus/utils/pow.nim Normal file
View File

@ -0,0 +1,352 @@
# Nimbus
# Copyright (c) 2018 Status Research & Development GmbH
# Licensed under either of
# * Apache License, version 2.0, ([LICENSE-APACHE](LICENSE-APACHE) or
# http://www.apache.org/licenses/LICENSE-2.0)
# * MIT license ([LICENSE-MIT](LICENSE-MIT) or
# http://opensource.org/licenses/MIT)
# at your option. This file may not be copied, modified, or distributed except
# according to those terms.
## Block PoW Support (Verifying & Mining)
## ======================================
##
import
std/[options, strutils],
../utils,
./pow/[pow_cache, pow_dataset],
bearssl,
eth/[common, keys, p2p, rlp],
ethash,
nimcrypto,
stint
{.push raises: [Defect].}
type
PowDigest = tuple ##\
## Return value from the `hashimotoLight()` function
mixDigest: Hash256
value: Hash256
PowSpecs* = object ##\
## Relevant block header parts for PoW mining & verifying. This object
## might be more useful for testing and debugging than for production.
blockNumber*: BlockNumber
miningHash*: Hash256
nonce*: BlockNonce
mixDigest*: Hash256
difficulty*: DifficultyInt
PowHeader = object ##\
## Stolen from `p2p/validate.MiningHeader`
parentHash : Hash256
ommersHash : Hash256
coinbase : EthAddress
stateRoot : Hash256
txRoot : Hash256
receiptRoot : Hash256
bloom : common.BloomFilter
difficulty : DifficultyInt
blockNumber : BlockNumber
gasLimit : GasInt
gasUsed : GasInt
timestamp : EthTime
extraData : Blob
PowRef* = ref object of RootObj ##\
## PoW context descriptor
lightByEpoch: PowCacheRef ## PoW cache indexed by epoch
fullByEpoch: PowDatasetRef ## Ditto for dataset
nonceAttempts: uint64 ## Unsuccessful tests in last mining process
# You should only create one instance of the RNG per application / library
# Ref is used so that it can be shared between components
rng: ref BrHmacDrbgContext
# ------------------------------------------------------------------------------
# Private functions: RLP support
# ------------------------------------------------------------------------------
proc append(w: var RlpWriter; specs: PowSpecs) =
## RLP support
w.startList(5)
w.append(HashOrNum(isHash: false, number: specs.blockNumber))
w.append(HashOrNum(isHash: true, hash: specs.miningHash))
w.append(specs.nonce.toUint)
w.append(HashOrNum(isHash: true, hash: specs.mixDigest))
w.append(specs.difficulty)
proc read(rlp: var Rlp; Q: type PowSpecs): Q
{.raises: [Defect,RlpError].} =
## RLP support
rlp.tryEnterList()
result.blockNumber = rlp.read(HashOrNum).number
result.miningHash = rlp.read(HashOrNum).hash
result.nonce = rlp.read(uint64).toBlockNonce
result.mixDigest = rlp.read(HashOrNum).hash
result.difficulty = rlp.read(DifficultyInt)
proc rlpTextEncode(specs: PowSpecs): string =
"specs #" & $specs.blockNumber & " " & rlp.encode(specs).toHex
proc decodeRlpText(data: string): PowSpecs
{.raises: [Defect,CatchableError].} =
if 180 < data.len and data[0 .. 6] == "specs #":
let hexData = data.split
if hexData.len == 3:
var rlpData = hexData[2].rlpFromHex
result = rlpData.read(PowSpecs)
# ------------------------------------------------------------------------------
# Private functions
# ------------------------------------------------------------------------------
proc miningHash(header: BlockHeader): Hash256 =
## Calculate hash from mining relevant fields of the argument `header`
let miningHeader = PowHeader(
parentHash: header.parentHash,
ommersHash: header.ommersHash,
coinbase: header.coinbase,
stateRoot: header.stateRoot,
txRoot: header.txRoot,
receiptRoot: header.receiptRoot,
bloom: header.bloom,
difficulty: header.difficulty,
blockNumber: header.blockNumber,
gasLimit: header.gasLimit,
gasUsed: header.gasUsed,
timestamp: header.timestamp,
extraData: header.extraData)
rlp.encode(miningHeader).keccakHash
# ---------------
proc tryNonceFull(nonce: uint64;
ds: PowDatasetItemRef; hash: Hash256): Uint256 =
let
rc = hashimotoFull(ds.size, ds.data, hash, nonce)
value = readUintBE[256](rc.value.data)
# echo ">>> nonce=", nonce.toHex, " value=", value.toHex
return value
proc mineFull(tm: PowRef; blockNumber: BlockNumber; powHeaderDigest: Hash256,
difficulty: DifficultyInt; startNonce: BlockNonce): uint64
{.gcsafe,raises: [Defect,CatchableError].} =
## Returns a valid nonce. This function was inspired by the function
## python function `mine()` from
## `ethash <https://eth.wiki/en/concepts/ethash/ethash>`_.
result = startNonce.toUint
if difficulty.isZero:
# Ooops???
return
let
ds = tm.fullByEpoch.get(blockNumber)
valueMax = Uint256.high div difficulty
while valueMax < result.tryNonceFull(ds, powHeaderDigest):
result.inc # rely on uint overflow mod 2^64
# Book keeping, debugging support
tm.nonceAttempts = if result <= startNonce.toUint:
startNonce.toUint - result
else:
(uint64.high - startNonce.toUint) + result
# ---------------
proc init(tm: PowRef;
rng: Option[ref BrHmacDrbgContext];
light: Option[PowCacheRef];
full: Option[PowDatasetRef]) =
## Constructor
if rng.isSome:
tm.rng = rng.get
else:
tm.rng = newRng()
if light.isSome:
tm.lightByEpoch = light.get
else:
tm.lightByEpoch = PowCacheRef.new
if full.isSome:
tm.fullByEpoch = full.get
else:
tm.fullByEpoch = PowDatasetRef.new(cache = tm.lightByEpoch)
# ------------------------------------------------------------------------------
# Public functions, Constructor
# ------------------------------------------------------------------------------
proc new*(T: type PowRef;
rng: ref BrHmacDrbgContext;
cache: PowCacheRef;
dataset: PowDatasetRef): T =
## Constructor
new result
result.init(
some(rng), some(cache), some(dataset))
proc new*(T: type PowRef; cache: PowCacheRef; dataset: PowDatasetRef): T =
## Constructor
new result
result.init(
none(ref BrHmacDrbgContext), some(cache), some(dataset))
proc new*(T: type PowRef; rng: ref BrHmacDrbgContext): T =
## Constructor
new result
result.init(
some(rng), none(PowCacheRef), none(PowDatasetRef))
proc new*(T: type PowRef): T =
## Constructor
new result
result.init(
none(ref BrHmacDrbgContext), none(PowCacheRef), none(PowDatasetRef))
# ------------------------------------------------------------------------------
# Public functions
# ------------------------------------------------------------------------------
proc getPowSpecs*(header: BlockHeader): PowSpecs =
## Extracts relevant parts from the `header` argument that are needed
## for mining or pow verification. This function might be more useful for
## testing and debugging than for production.
PowSpecs(
blockNumber: header.blockNumber,
miningHash: header.miningHash,
nonce: header.nonce,
mixDigest: header.mixDigest,
difficulty: header.difficulty)
proc getPowCacheLookup*(tm: PowRef;
blockNumber: BlockNumber): (uint64,Hash256)
{.gcsafe,raises: [Defect,CatchableError].} =
## Returns the pair `(size,digest)` derived from the lookup cache for the
## `hashimotoLight()` function for the given block number. The `size` is the
## full size of the dataset (the cache represents) as passed on to the
## `hashimotoLight()` function. The `digest` is a hash derived from the
## cache that would be passed on to `hashimotoLight()`.
##
## This function is intended for error reporting and might also be useful
## for testing and debugging.
let ds = tm.lightByEpoch.get(blockNumber)
result[0] = ds.size
var ctx: keccak256
ctx.init()
for a in ds.data:
ctx.update(a.data[0].unsafeAddr, uint(a.data.len))
ctx.finish result[1].data
ctx.clear()
# ------------------------
proc getPowDigest*(tm: PowRef; blockNumber: BlockNumber;
powHeaderDigest: Hash256; nonce: BlockNonce): PowDigest
{.gcsafe,raises: [Defect,CatchableError].} =
## Calculate the expected value of `header.mixDigest` using the
## `hashimotoLight()` library method.
let
ds = tm.lightByEpoch.get(blockNumber)
u64Nonce = uint64.fromBytesBE(nonce)
hashimotoLight(ds.size, ds.data, powHeaderDigest, u64Nonce)
proc getPowDigest*(tm: PowRef; header: BlockHeader): PowDigest
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getPowDigest()`
tm.getPowDigest(header.blockNumber, header.miningHash, header.nonce)
proc getPowDigest*(tm: PowRef; specs: PowSpecs): PowDigest
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getPowDigest()`
tm.getPowDigest(specs.blockNumber, specs.miningHash, specs.nonce)
# ------------------
proc getNonce*(tm: PowRef; number: BlockNumber; powHeaderDigest: Hash256;
difficulty: DifficultyInt; startNonce: BlockNonce): BlockNonce
{.gcsafe,raises: [Defect,CatchableError].} =
## Mining function that calculates the value of a `nonce` satisfying the
## difficulty challenge. This is the most basic function of the
## `getNonce()` series with explicit argument `startNonce`. If this is
## a valid `nonce` already, the function stops and returns that value.
## Otherwise it derives other nonces from the `startNonce` start and
## continues trying.
##
## The function depends on a mining dataset which can be generated with
## `generatePowDataset()` before that function is invoked.
##
## This mining logic was inspired by the Python function `mine()` from
## `ethash <https://eth.wiki/en/concepts/ethash/ethash>`_.
tm.mineFull(number, powHeaderDigest, difficulty, startNonce).toBytesBE
proc getNonce*(tm: PowRef; number: BlockNumber; powHeaderDigest: Hash256;
difficulty: DifficultyInt): BlockNonce
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getNonce()`
var startNonce: array[8,byte]
tm.rng[].brHmacDrbgGenerate(startNonce)
tm.getNonce(number, powHeaderDigest, difficulty, startNonce)
proc getNonce*(tm: PowRef; header: BlockHeader): BlockNonce
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getNonce()`
tm.getNonce(header.blockNumber, header.miningHash, header.difficulty)
proc getNonce*(tm: PowRef; specs: PowSpecs): BlockNonce
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getNonce()`
tm.getNonce(specs.blockNumber, specs.miningHash, specs.difficulty)
proc nGetNonce*(tm: PowRef): uint64 =
## Number of unsucchessful internal tests in the last invocation
## of `getNonce()`.
tm.nonceAttempts
# ------------------
proc generatePowDataset*(tm: PowRef; number: BlockNumber)
{.gcsafe,raises: [Defect,CatchableError].} =
## Prepare dataset for the `getNonce()` mining function. This dataset
## changes with the epoch of the argument `number` so it is applicable for
## the full epoch. If not generated explicitely, it will be done so by the
## next invocation of `getNonce()`.
##
## This is a slow process which produces a huge data table. So expect this
## function to hang on for a while and do not mind if the OS starts swapping.
## A list of the data sizes indexed by epoch is available at the end of
## the `ethash <https://eth.wiki/en/concepts/ethash/ethash>`_ Python
## reference implementation.
discard tm.fullByEpoch.get(number)
# ------------------------------------------------------------------------------
# Public functions, debugging & testing
# ------------------------------------------------------------------------------
proc dumpPowSpecs*(specs: PowSpecs): string =
## Text representation of `PowSpecs` argument object
specs.rlpTextEncode
proc dumpPowSpecs*(header: BlockHeader): string =
## Variant of `dumpPowSpecs()`
header.getPowSpecs.dumpPowSpecs
proc undumpPowSpecs*(data: string): PowSpecs
{.raises: [Defect,CatchableError].} =
## Recover `PowSpecs` object from text representation
data.decodeRlpText
# ------------------------------------------------------------------------------
# End
# ------------------------------------------------------------------------------

View File

@ -0,0 +1,122 @@
# Nimbus
# Copyright (c) 2018 Status Research & Development GmbH
# Licensed under either of
# * Apache License, version 2.0, ([LICENSE-APACHE](LICENSE-APACHE) or
# http://www.apache.org/licenses/LICENSE-2.0)
# * MIT license ([LICENSE-MIT](LICENSE-MIT) or
# http://opensource.org/licenses/MIT)
# at your option. This file may not be copied, modified, or distributed except
# according to those terms.
## LRU Cache for Epoch Indexed Hashimoto Cache
## ============================================
##
## This module uses the eth-block number (mapped to epoch) to hold and re-use
## the cache needed for running the `hasimotoLight()` proof-of-work function.
import
eth/common,
ethash,
nimcrypto,
stew/keyed_queue
{.push raises: [Defect].}
type
PowCacheItemRef* = ref object
size*: uint64
data*: seq[MDigest[512]]
PowCacheStats* = tuple
maxItems: int
size: int
PowCache* = object
cacheMax: int
cache: KeyedQueue[uint64,PowCacheItemRef]
PowCacheRef* = ref PowCache
const
nItemsMax = 10
nItemsInit = 2
# ------------------------------------------------------------------------------
# Private helpers
# ------------------------------------------------------------------------------
proc toKey(bn: BlockNumber): uint64 =
bn.truncate(uint64) div EPOCH_LENGTH
# ------------------------------------------------------------------------------
# Public functions, constructor
# ------------------------------------------------------------------------------
proc init*(pc: var PowCache; maxItems = nItemsMax) =
## Constructor for PoW cache
pc.cacheMax = maxItems
pc.cache.init(nItemsInit)
proc init*(T: type PowCache; maxItems = nItemsMax): T =
## Constructor variant
result.init(maxItems)
proc new*(T: type PowCacheRef; maxItems = nItemsMax): T =
## Constructor variant
new result
result[].init(maxItems)
# ------------------------------------------------------------------------------
# Public functions, constructor
# ------------------------------------------------------------------------------
proc get*(pc: var PowCache; bn: BlockNumber): PowCacheItemRef
{.gcsafe,raises: [Defect,CatchableError].} =
## Return a cache derived from argument `blockNumber` ready to be used
## for the `hashimotoLight()` method.
let
key = bn.toKey
rc = pc.cache.lruFetch(key)
if rc.isOK:
return rc.value
let
# note that `getDataSize()` and `getCacheSize()` depend on
# `key * EPOCH_LENGTH` rather than the original block number.
top = key * EPOCH_LENGTH
pair = PowCacheItemRef(
size: top.getDataSize,
data: top.getCacheSize.mkcache(top.getSeedhash))
pc.cache.lruAppend(key, pair, pc.cacheMax)
proc get*(pcr: PowCacheRef; bn: BlockNumber): PowCacheItemRef
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getCache()`
pcr[].get(bn)
proc hasItem*(pc: var PowCache; bn: BlockNumber): bool
{.gcsafe,raises: [Defect,CatchableError].} =
## Returns true if there is a cache entry for argument `bn`.
pc.cache.hasKey(bn.toKey)
proc hasItem*(pcr: PowCacheRef; bn: BlockNumber): bool
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `hasItem()`
pcr[].hasItem(bn)
# -------------------------
proc stats*(pc: var PowCache): PowCacheStats =
## Return current cache sizes
result = (maxItems: pc.cacheMax, size: pc.cache.len)
proc stats*(pcr: PowCacheRef): PowCacheStats =
## Variant of `stats()`
pcr[].stats
# ------------------------------------------------------------------------------
# End
# ------------------------------------------------------------------------------

View File

@ -0,0 +1,155 @@
# Nimbus
# Copyright (c) 2018 Status Research & Development GmbH
# Licensed under either of
# * Apache License, version 2.0, ([LICENSE-APACHE](LICENSE-APACHE) or
# http://www.apache.org/licenses/LICENSE-2.0)
# * MIT license ([LICENSE-MIT](LICENSE-MIT) or
# http://opensource.org/licenses/MIT)
# at your option. This file may not be copied, modified, or distributed except
# according to those terms.
## LRU Cache for Epoch Indexed Hashimoto Dataset
## =============================================
##
## This module uses the eth-block number (mapped to epoch) to hold and re-use
## the dataset needed for running the `hasimotoFull()` proof-of-work function.
import
std/[options],
./pow_cache,
eth/common,
ethash,
nimcrypto,
stew/keyed_queue
{.push raises: [Defect].}
type
PowDatasetItemRef* = ref object
size*: uint64
data*: seq[MDigest[512]]
PowDatasetStats* = tuple
maxItems: int
size: int
PowDataset* = object
datasetMax: int
dataset: KeyedQueue[uint64,PowDatasetItemRef]
cache: PowCacheRef
PowDatasetRef* = ref PowDataset
const
nItemsMax = 2
nItemsInit = 2
# ------------------------------------------------------------------------------
# Private helpers
# ------------------------------------------------------------------------------
proc toKey(bn: BlockNumber): uint64 =
bn.truncate(uint64) div EPOCH_LENGTH
proc init(pd: var PowDataset;
maxItems: Option[int]; cache: Option[PowCacheRef]) =
## Constructor for LRU cache
pd.dataset.init(nItemsInit)
if maxItems.isSome:
pd.datasetMax = maxItems.get
else:
pd.datasetMax = nItemsMax
if cache.isSome:
pd.cache = cache.get
else:
pd.cache = PowCacheRef.new(nItemsInit)
# ------------------------------------------------------------------------------
# Public functions, constructor
# ------------------------------------------------------------------------------
proc init*(pd: var PowDataset; maxItems = nItemsMax; cache: PowCacheRef) =
## Constructor for PoW dataset
pd.init(some(maxItems), some(cache))
proc init*(pd: var PowDataset; maxItems = nItemsMax) =
## Constructor variant
pd.init(some(maxItems), none(PowCacheRef))
proc init*(T: type PowDataset; maxItems = nItemsMax; cache: PowCacheRef): T =
## Constructor variant
result.init(some(maxItems), some(cache))
proc init*(T: type PowDataset; maxItems = nItemsMax): T =
## Constructor variant
result.init(some(maxItems), none(PowCacheRef))
proc new*(T: type PowDatasetRef; maxItems = nItemsMax; cache: PowCacheRef): T =
## Constructor variant
new result
result[].init(some(maxItems), some(cache))
proc new*(T: type PowDatasetRef; maxItems = nItemsMax): T =
## Constructor for PoW dataset reference
new result
result[].init(some(maxItems), none(PowCacheRef))
# ------------------------------------------------------------------------------
# Public functions, constructor
# ------------------------------------------------------------------------------
proc get*(pd: var PowDataset; bn: BlockNumber): PowDatasetItemRef
{.gcsafe,raises: [Defect,CatchableError].} =
## Return a cache derived from argument `blockNumber` ready to be used
## for the `hashimotoLight()` method.
let
key = bn.toKey
rc = pd.dataset.lruFetch(key)
if rc.isOK:
return rc.value
let
# note that `getDataSize()` and `getCacheSize()` depend on
# `key * EPOCH_LENGTH` rather than the original block number.
top = key * EPOCH_LENGTH
cache = pd.cache.get(bn)
pair = PowDatasetItemRef(
size: cache.size,
data: cache.size.calcDataset(cache.data))
pd.dataset.lruAppend(key, pair, pd.datasetMax)
proc get*(pdr: PowDatasetRef; bn: BlockNumber): PowDatasetItemRef
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `getCache()`
pdr[].get(bn)
proc hasItem*(pd: var PowDataset; bn: BlockNumber): bool
{.gcsafe,raises: [Defect,CatchableError].} =
##Returns true if there is a cache entry for argument `bn`.
pd.dataset.hasKey(bn.toKey)
proc hasItem*(pdr: PowDatasetRef; bn: BlockNumber): bool
{.gcsafe,raises: [Defect,CatchableError].} =
## Variant of `hasItem()`
pdr[].hasItem(bn)
# -------------------------
proc stats*(pd: var PowDataset): PowDatasetStats =
## Return current cache sizes
result = (maxItems: pd.datasetMax, size: pd.dataset.len)
proc stats*(pd: PowDatasetRef): PowDatasetStats =
## Variant of `stats()`
pd[].stats
# ------------------------------------------------------------------------------
# End
# ------------------------------------------------------------------------------

View File

@ -38,4 +38,5 @@ cliBuilder:
./test_graphql,
./test_lru_cache,
./test_clique,
./test_pow,
./test_configuration

View File

@ -40,8 +40,7 @@ type
debugData : JsonNode
network : string
var cacheByEpoch: EpochHashCache
cacheByEpoch.initEpochHashCache
var pow = PowRef.new
proc testFixture(node: JsonNode, testStatusIMPL: var TestStatus, debugMode = false, trace = false)
@ -260,7 +259,7 @@ proc importBlock(tester: var Tester, chainDB: BaseChainDB,
if validation:
let rc = chainDB.validateHeaderAndKinship(
result.header, body, checkSeal, cacheByEpoch)
result.header, body, checkSeal, pow)
if rc.isErr:
raise newException(
ValidationError, "validateHeaderAndKinship: " & rc.error)
@ -310,7 +309,7 @@ proc runTester(tester: var Tester, chainDB: BaseChainDB, testStatusIMPL: var Tes
# manually validating
check chainDB.validateHeaderAndKinship(
preminedBlock, checkSeal, cacheByEpoch).isOk
preminedBlock, checkSeal, pow).isOk
except:
debugEcho "FATAL ERROR(WE HAVE BUG): ", getCurrentExceptionMsg()

205
tests/test_pow.nim Normal file
View File

@ -0,0 +1,205 @@
# Nimbus
# Copyright (c) 2018-2019 Status Research & Development GmbH
# Licensed under either of
# * Apache License, version 2.0, ([LICENSE-APACHE](LICENSE-APACHE) or
# http://www.apache.org/licenses/LICENSE-2.0)
# * MIT license ([LICENSE-MIT](LICENSE-MIT) or
# http://opensource.org/licenses/MIT)
# at your option. This file may not be copied, modified, or distributed except
# according to those terms.
import
std/[os, sequtils, strformat, strutils, times],
./test_clique/gunzip,
../nimbus/utils/[pow, pow/pow_cache, pow/pow_dataset],
eth/[common],
unittest2
const
baseDir = [".", "tests", ".." / "tests", $DirSep] # path containg repo
repoDir = ["test_pow", "status"] # alternative repos
specsDump = "mainspecs2k.txt.gz"
# ------------------------------------------------------------------------------
# Helpers
# ------------------------------------------------------------------------------
proc ppMs*(elapsed: Duration): string =
result = $elapsed.inMilliSeconds
let ns = elapsed.inNanoSeconds mod 1_000_000
if ns != 0:
# to rounded deca milli seconds
let dm = (ns + 5_000i64) div 10_000i64
result &= &".{dm:02}"
result &= "ms"
proc ppSecs*(elapsed: Duration): string =
result = $elapsed.inSeconds
let ns = elapsed.inNanoseconds mod 1_000_000_000
if ns != 0:
# to rounded decs seconds
let ds = (ns + 5_000_000i64) div 10_000_000i64
result &= &".{ds:02}"
result &= "s"
proc toKMG*[T](s: T): string =
proc subst(s: var string; tag, new: string): bool =
if tag.len < s.len and s[s.len - tag.len ..< s.len] == tag:
s = s[0 ..< s.len - tag.len] & new
return true
result = $s
for w in [("000", "K"),("000K","M"),("000M","G"),("000G","T"),
("000T","P"),("000P","E"),("000E","Z"),("000Z","Y")]:
if not result.subst(w[0],w[1]):
return
template showElapsed*(noisy: bool; info: string; code: untyped) =
let start = getTime()
code
if noisy:
let elpd {.inject.} = getTime() - start
if 0 < elpd.inSeconds:
echo "*** ", info, &": {elpd.ppSecs:>4}"
else:
echo "*** ", info, &": {elpd.ppMs:>4}"
proc say*(noisy = false; pfx = "***"; args: varargs[string, `$`]) =
if noisy:
if args.len == 0:
echo "*** ", pfx
elif 0 < pfx.len and pfx[^1] != ' ':
echo pfx, " ", args.toSeq.join
else:
echo pfx, args.toSeq.join
proc pp*(a: BlockNonce): string =
a.mapIt(it.toHex(2)).join.toLowerAscii
proc pp*(a: Hash256): string =
a.data.mapIt(it.toHex(2)).join[24 .. 31].toLowerAscii
proc findFilePath(file: string): string =
result = "?unknown?" / file
for dir in baseDir:
for repo in repoDir:
let path = dir / repo / file
if path.fileExists:
return path
# ------------------------------------------------------------------------------
# Test Runners
# ------------------------------------------------------------------------------
proc runPowTests(noisy = true; file = specsDump;
nVerify = int.high; nFakeMiner = 0, nRealMiner = 0) =
let
filePath = file.findFilePath
fileInfo = file.splitFile.name.split(".")[0]
powCache = PowCacheRef.new # so we can inspect the LRU caches
powDataset = PowDatasetRef.new(cache = powCache)
pow = PowRef.new(powCache, powDataset)
var
specsList: seq[PowSpecs]
suite &"PoW: Header test specs from {fileInfo} capture":
block:
test "Loading from capture":
for (lno,line) in gunzipLines(filePath):
let specs = line.undumpPowSpecs
if 0 < specs.blockNumber:
specsList.add specs
check line == specs.dumpPowSpecs
noisy.say "***", " block range #",
specsList[0].blockNumber, " .. #", specsList[^1].blockNumber
# Adjust number of tests
let
startVerify = max(0, specsList.len - nVerify)
startFakeMiner = max(0, specsList.len - nFakeMiner)
startRealMiner = max(0, specsList.len - nRealMiner)
nDoVerify = specsList.len - startVerify
nDoFakeMiner = specsList.len - startFakeMiner
nDoRealMiner = specsList.len - startRealMiner
backStep = 1u64 shl 11
block:
test &"Running single getPowDigest() to fill the cache":
if nVerify <= 0:
skip()
else:
noisy.showElapsed(&"first getPowDigest() instance"):
let p = specsList[startVerify]
check pow.getPowDigest(p).mixDigest == p.mixDigest
test &"Running getPowDigest() on {nDoVerify} specs records":
if nVerify <= 0:
skip()
else:
noisy.showElapsed(&"all {nDoVerify} getPowDigest() instances"):
for n in startVerify ..< specsList.len:
let p = specsList[n]
check pow.getPowDigest(p).mixDigest == p.mixDigest
test &"Generate PoW mining dataset (slow proocess)":
if nDoFakeMiner <= 0 and nRealMiner <= 0:
skip()
else:
noisy.showElapsed "generate PoW dataset":
pow.generatePowDataset(specsList[startFakeMiner].blockNumber)
test &"Running getNonce() on {nDoFakeMiner} instances with start" &
&" nonce {backStep} before result":
if nDoFakeMiner <= 0:
skip()
else:
noisy.showElapsed &"all {nDoFakeMiner} getNonce() instances":
for n in startFakeMiner ..< specsList.len:
let
p = specsList[n]
nonce = toBytesBE(uint64.fromBytesBE(p.nonce) - backStep)
check pow.getNonce(
p.blockNumber, p.miningHash, p.difficulty, nonce) == p.nonce
test &"Running getNonce() mining function" &
&" on {nDoRealMiner} specs records":
if nRealMiner <= 0:
skip()
else:
for n in startRealMiner ..< specsList.len:
let p = specsList[n]
noisy.say "***", " #", p.blockNumber, " needs ", p.nonce.pp
noisy.showElapsed("getNonce()"):
let nonce = pow.getNonce(p)
noisy.say "***", " got ", nonce.pp,
" after ", pow.nGetNonce, " attempts"
if nonce != p.nonce:
var q = p
q.nonce = nonce
check pow.getPowDigest(q).mixDigest == p.mixDigest
# ------------------------------------------------------------------------------
# Main function(s)
# ------------------------------------------------------------------------------
proc powMain*(noisy = defined(debug)) =
noisy.runPowTests(nVerify = 100)
when isMainModule:
# Note:
# 0 < nFakeMiner: allow ~20 minuntes for building lookup table
# 0 < nRealMiner: takes days/months/years ...
true.runPowTests(nVerify = 200, nFakeMiner = 200, nRealMiner = 5)
# ------------------------------------------------------------------------------
# End
# ------------------------------------------------------------------------------

Binary file not shown.