module Generators where

import Data.Int (Int64)
import Hedgehog (MonadGen)
import qualified Hedgehog.Gen as Gen
import qualified Hedgehog.Range as Range
import Tahoe.CHK.Types (Parameters (..))

-- | The maximum value an Int64 can represent.
maxInt64 :: Integer
maxInt64 = fromIntegral (maxBound :: Int64)

-- | Generate Parameters values for which all field invariants hold.
genParameters :: MonadGen m => m Parameters
genParameters = do
    paramSegmentSize <- Gen.integral (Range.exponential 1 maxInt64)
    paramTotalShares <- Gen.integral (Range.linear 2 256)
    paramRequiredShares <- Gen.integral (Range.linear 1 (paramTotalShares - 1))
    -- XXX We're going to get rid of "Happy" from this type.  For now it's
    -- easier not to let this value vary and it doesn't hurt anything.
    let paramHappyShares = 1
    pure $ Parameters{paramSegmentSize, paramTotalShares, paramHappyShares, paramRequiredShares}