Last active
February 11, 2021 06:58
-
-
Save adamwespiser/e0d8b593f953a0a4ffd746e8516ee621 to your computer and use it in GitHub Desktop.
Random Integers from Cryptonite
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{- stack --resolver lts-16.8 --install-ghc exec ghci --package "random cryptonite text memory"-} | |
{- ghcid -c "stack RandomExample.hs" -} | |
{-# Language OverloadedStrings, PackageImports, ScopedTypeVariables, TypeApplications #-} | |
module RandomExample where | |
import Prelude | |
import qualified GHC.List as Fold | |
import "cryptonite" Crypto.Random (MonadRandom, drgNew, withDRG, getRandomBytes) | |
import qualified Data.ByteString as BS hiding (foldl1') | |
import Data.Bits | |
main :: IO () | |
main = do | |
drg <- drgNew | |
-- use the ChaCha Deterministic Random Generator pulled from system entropy | |
-- every draw, update the DRG. This should be "CSPNG": https://en.wikipedia.org/wiki/Cryptographically_secure_pseudorandom_number_generator | |
-- more info on why System.Random won't work: https://alexey.kuleshevi.ch/blog/2019/12/21/random-benchmarks/ | |
-- More broadly, one of the "die hard" tests, the birthday spacing problem, is applicable. | |
-- Die Hard Tests: https://en.wikipedia.org/wiki/Diehard_tests | |
print . fmap fst . take 3 . iterate getNext . withDRG drg $ randomR (0,2048) | |
where | |
getNext (a,gen) = withDRG gen $ randomR (0,2048) | |
-- Function not available in cryptonite, so we'll get the entropy from cryptonite, | |
-- and use the same conversion to integer. | |
-- https://hackage.haskell.org/package/crypto-rng-0.1.2.0/docs/src/Crypto.RNG.html#local-6989586621679059821 | |
randomR :: (MonadRandom m, Integral a) => (a, a) -> m a | |
randomR (minb', maxb') = do | |
bs <- getRandomBytes byteLen | |
return $ fromIntegral $ | |
minb + Fold.foldl1' (\r a -> shiftL r 8 .|. a) (map toInteger (BS.unpack bs)) `mod` range | |
where | |
minb, maxb, range :: Integer | |
minb = fromIntegral minb' | |
maxb = fromIntegral maxb' | |
range = maxb - minb + 1 | |
byteLen = ceiling $ logBase 2 (fromIntegral range) / (8 :: Double) |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment