{- |
Module      : Haskoin.Test.Block
Copyright   : No rights reserved
License     : MIT
Maintainer  : jprupp@protonmail.ch
Stability   : experimental
Portability : POSIX
-}
module Haskoin.Util.Arbitrary.Block where

import qualified Data.HashMap.Strict as HashMap
import Haskoin.Block
import Haskoin.Data
import Haskoin.Util.Arbitrary.Crypto
import Haskoin.Util.Arbitrary.Network
import Haskoin.Util.Arbitrary.Transaction
import Haskoin.Util.Arbitrary.Util
import Test.QuickCheck

-- | Block full or arbitrary transactions.
arbitraryBlock :: Network -> Gen Block
arbitraryBlock :: Network -> Gen Block
arbitraryBlock Network
net = do
    BlockHeader
h <- Gen BlockHeader
arbitraryBlockHeader
    Int
c <- forall a. Random a => (a, a) -> Gen a
choose (Int
0, Int
10)
    [Tx]
txs <- forall a. Int -> Gen a -> Gen [a]
vectorOf Int
c (Network -> Gen Tx
arbitraryTx Network
net)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ BlockHeader -> [Tx] -> Block
Block BlockHeader
h [Tx]
txs

-- | Block header with random hash.
arbitraryBlockHeader :: Gen BlockHeader
arbitraryBlockHeader :: Gen BlockHeader
arbitraryBlockHeader =
    Word32
-> BlockHash
-> Hash256
-> Word32
-> Word32
-> Word32
-> BlockHeader
BlockHeader forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen BlockHash
arbitraryBlockHash
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen Hash256
arbitraryHash256
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Arbitrary a => Gen a
arbitrary

-- | Arbitrary block hash.
arbitraryBlockHash :: Gen BlockHash
arbitraryBlockHash :: Gen BlockHash
arbitraryBlockHash = Hash256 -> BlockHash
BlockHash forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen Hash256
arbitraryHash256

-- | Arbitrary 'GetBlocks' object with at least one block hash.
arbitraryGetBlocks :: Gen GetBlocks
arbitraryGetBlocks :: Gen GetBlocks
arbitraryGetBlocks =
    Word32 -> BlockLocator -> BlockHash -> GetBlocks
GetBlocks forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Gen a -> Gen [a]
listOf1 Gen BlockHash
arbitraryBlockHash
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen BlockHash
arbitraryBlockHash

-- | Arbitrary 'GetHeaders' object with at least one block header.
arbitraryGetHeaders :: Gen GetHeaders
arbitraryGetHeaders :: Gen GetHeaders
arbitraryGetHeaders =
    Word32 -> BlockLocator -> BlockHash -> GetHeaders
GetHeaders forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Gen a -> Gen [a]
listOf1 Gen BlockHash
arbitraryBlockHash
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen BlockHash
arbitraryBlockHash

-- | Arbitrary 'Headers' object with at least one block header.
arbitraryHeaders :: Gen Headers
arbitraryHeaders :: Gen Headers
arbitraryHeaders =
    [BlockHeaderCount] -> Headers
Headers forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Gen a -> Gen [a]
listOf1 ((,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen BlockHeader
arbitraryBlockHeader forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen VarInt
arbitraryVarInt)

-- | Arbitrary 'MerkleBlock' with at least one hash.
arbitraryMerkleBlock :: Gen MerkleBlock
arbitraryMerkleBlock :: Gen MerkleBlock
arbitraryMerkleBlock = do
    BlockHeader
bh <- Gen BlockHeader
arbitraryBlockHeader
    Word32
ntx <- forall a. Arbitrary a => Gen a
arbitrary
    [Hash256]
hashes <- forall a. Gen a -> Gen [a]
listOf1 Gen Hash256
arbitraryHash256
    Int
c <- forall a. Random a => (a, a) -> Gen a
choose (Int
1, Int
10)
    [Bool]
flags <- forall a. Int -> Gen a -> Gen [a]
vectorOf (Int
c forall a. Num a => a -> a -> a
* Int
8) forall a. Arbitrary a => Gen a
arbitrary
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ BlockHeader -> Word32 -> [Hash256] -> [Bool] -> MerkleBlock
MerkleBlock BlockHeader
bh Word32
ntx [Hash256]
hashes [Bool]
flags

-- | Arbitrary 'BlockNode'
arbitraryBlockNode :: Gen BlockNode
arbitraryBlockNode :: Gen BlockNode
arbitraryBlockNode =
    forall a. [Gen a] -> Gen a
oneof
        [ BlockHeader -> Word32 -> BlockWork -> BlockHash -> BlockNode
BlockNode
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen BlockHeader
arbitraryBlockHeader
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Random a => (a, a) -> Gen a
choose (Word32
0, forall a. Bounded a => a
maxBound)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. Integral a => Gen a
arbitrarySizedNatural
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen BlockHash
arbitraryBlockHash
        ]

-- | Arbitrary 'HeaderMemory'
arbitraryHeaderMemory :: Gen HeaderMemory
arbitraryHeaderMemory :: Gen HeaderMemory
arbitraryHeaderMemory = do
    [(ShortBlockHash, ShortByteString)]
ls <- forall a. Gen a -> Gen [a]
listOf forall a b. (a -> b) -> a -> b
$ (,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Arbitrary a => Gen a
arbitrary forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Gen ShortByteString
arbitraryBSS
    BlockMap -> BlockNode -> HeaderMemory
HeaderMemory (forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HashMap.fromList [(ShortBlockHash, ShortByteString)]
ls) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Gen BlockNode
arbitraryBlockNode