Skip to content

Instantly share code, notes, and snippets.

@thalesmg
Created October 9, 2022 15:39
Show Gist options
  • Save thalesmg/36cf95ea91a7c05b921a64913427423a to your computer and use it in GitHub Desktop.
Save thalesmg/36cf95ea91a7c05b921a64913427423a to your computer and use it in GitHub Desktop.
Generate random bit masks for corrupting packets with probability
{-# LANGUAGE ScopedTypeVariables #-}
-- https://stackoverflow.com/questions/2075912/generate-a-random-binary-number-with-a-variable-proportion-of-1-bits
import Control.Monad (replicateM)
import Data.Bits
import Data.Foldable (foldl')
import Data.Word (Word8)
import Numeric.Natural (Natural)
import System.Random (Random, randomIO)
generate :: forall a p. (Bits a, Random a, Ord p, Fractional p) => p -> IO a
generate prob = res
where
tol :: (Fractional p) => p
tol = 0.001
gas :: Natural
gas = 10
plan :: (Fractional p, Bits a) => p -> Natural -> [a -> a -> a]
plan p g
| g == 0 = []
| p > 0.5 + tol = (.|.) : plan (2 * p - 1) (g - 1)
| p < 0.5 - tol = (.&.) : plan (2 * p) (g - 1)
| otherwise = []
res :: IO a
res = do
let ops = plan prob gas
nOps = length ops
x0 <- randomIO
xs <- replicateM nOps randomIO
pure $ foldr (\(x, op) acc -> op x acc) x0 (zip xs ops)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment