[test] add random number generation tests
This commit is contained in:
parent
ca2ec5a03d
commit
a4baf9383b
@ -3,6 +3,7 @@ module Number (tests) where
|
||||
import Imports
|
||||
|
||||
import Crypto.Number.Basic
|
||||
import Crypto.Number.Generate
|
||||
import Data.Bits
|
||||
|
||||
tests = testGroup "number"
|
||||
@ -13,4 +14,17 @@ tests = testGroup "number"
|
||||
]
|
||||
, testProperty "num-bits2" $ \(Positive i) ->
|
||||
not (i `testBit` numBits i) && (i `testBit` (numBits i - 1))
|
||||
, testProperty "generate-param" $ \testDRG (Positive bits) ->
|
||||
let r = withTestDRG testDRG $ generateParams bits (Just SetHighest) False
|
||||
in r >= 0 && numBits r == bits && testBit r (bits-1)
|
||||
, testProperty "generate-param2" $ \testDRG (Positive m1bits) ->
|
||||
let bits = m1bits + 1 -- make sure minimum is 2
|
||||
r = withTestDRG testDRG $ generateParams bits (Just SetTwoHighest) False
|
||||
in r >= 0 && numBits r == bits && testBit r (bits-1) && testBit r (bits-2)
|
||||
, testProperty "generate-param-odd" $ \testDRG (Positive bits) ->
|
||||
let r = withTestDRG testDRG $ generateParams bits Nothing True
|
||||
in r >= 0 && odd r
|
||||
, testProperty "generate-range" $ \testDRG (Positive range) ->
|
||||
let r = withTestDRG testDRG $ generateMax range
|
||||
in 0 <= r && r < range
|
||||
]
|
||||
|
||||
@ -3,6 +3,7 @@ module Main where
|
||||
|
||||
import Imports
|
||||
|
||||
import qualified Number
|
||||
import qualified Hash
|
||||
import qualified Poly1305
|
||||
import qualified Salsa
|
||||
@ -24,7 +25,8 @@ import qualified KAT_TripleDES
|
||||
import qualified KAT_AFIS
|
||||
|
||||
tests = testGroup "cryptonite"
|
||||
[ Hash.tests
|
||||
[ Number.tests
|
||||
, Hash.tests
|
||||
, testGroup "MAC"
|
||||
[ Poly1305.tests
|
||||
, KAT_HMAC.tests
|
||||
|
||||
@ -2,12 +2,22 @@ module Utils where
|
||||
|
||||
import Control.Monad (replicateM)
|
||||
import Data.Char
|
||||
import Data.Word
|
||||
import Data.ByteString (ByteString)
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Lazy as L
|
||||
import Crypto.Random
|
||||
|
||||
import Test.Tasty.QuickCheck
|
||||
|
||||
newtype TestDRG = TestDRG (Word64, Word64, Word64, Word64, Word64)
|
||||
deriving (Show,Eq)
|
||||
|
||||
instance Arbitrary TestDRG where
|
||||
arbitrary = TestDRG `fmap` arbitrary
|
||||
|
||||
withTestDRG (TestDRG l) f = fst $ withDRG (drgNewTest l) f
|
||||
|
||||
newtype ChunkingLen = ChunkingLen [Int]
|
||||
deriving (Show,Eq)
|
||||
|
||||
|
||||
Loading…
Reference in New Issue
Block a user