{-# OPTIONS_GHC -fno-warn-orphans #-} {- Copyright 2016 Joey Hess - - Licensed under the GNU AGPL version 3 or higher. -} module ByteStrings where import qualified Data.ByteString as B import qualified Raaz import Control.Monad import Data.Word allByteStringsOfLength :: Int -> [B.ByteString] allByteStringsOfLength = go [] where go ws n | n == 0 = return (B.pack ws) | otherwise = do w <- [0..255] go (w:ws) (n-1) -- | Contains every possible byte strings, with shorter ones first. allByteStrings :: [B.ByteString] allByteStrings = concatMap allByteStringsOfLength [1..] chunkByteString :: Int -> B.ByteString -> [B.ByteString] chunkByteString n = go [] where go cs b | B.length b <= n = reverse (b:cs) | otherwise = let (h, t) = B.splitAt n b in go (h:cs) t instance Raaz.Random Word8 randomByteStringOfLength :: Int -> Raaz.SystemPRG -> IO B.ByteString randomByteStringOfLength n prg = B.pack <$> replicateM n randbyte where randbyte = Raaz.random prg :: IO Word8