{-# LANGUAGE LambdaCase, ScopedTypeVariables #-} {- Example of using PBKDF2 to seed the Multiply with Carry (MWC) random number generator with a string. Copyright 2015 Ken Takusagawa This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} module Main(main) where { import qualified System.Random.MWC as MWC; import Data.ByteString (ByteString); import qualified Data.Binary as Binary; import Data.Binary(Binary); import Data.Binary.Get(runGet); import qualified Data.Binary.Get as Binary.Get; import Crypto.PBKDF.ByteString(sha512PBKDF2); import Data.Text.Encoding(encodeUtf8); import qualified Data.Text as Text; import qualified Data.ByteString.Lazy as Lazy; import qualified Data.Vector as Vector; import Data.Word; main :: IO (); main = do { gen <- MWC.initialize $ Vector.fromList $ runGet getManyUntilEmpty $ Lazy.fromStrict $ sha512PBKDF2 (string2bs mypassphrase) (string2bs salt) (fromIntegral iterations_pbkdf2) (fromIntegral keylength_bytes); sequence_ $ repeat $ (MWC.uniform gen :: IO Word8) >>= print; }; string2bs :: String -> ByteString; string2bs = encodeUtf8 . Text.pack; -- world's most famous password mypassphrase :: String; mypassphrase = "ACollectionOfDiplomaticHistorySince_1966_ToThe_PresentDay#"; salt::String; salt = "mysalt98754321"; -- magic number for mwc mwc_statesize :: Integer; mwc_statesize = 258; keylength_bytes :: Integer; keylength_bytes = mwc_statesize * 4; -- MWC is not a cryptographically secure generator, so it would be -- pointless to harden against brute-force key-recovery attacks by -- having a high number of iterations. iterations_pbkdf2 :: Integer; iterations_pbkdf2 = 1; -- A seemingly useful function for Binary.Get but unfortunately of -- limited use, because it does not parse lazily, i.e. does not return -- a lazy list; it must consume the entire input before returning the -- first item. getManyUntilEmpty :: forall a. Binary a => Binary.Get [a]; getManyUntilEmpty = Binary.Get.isEmpty >>= \case { True -> return []; False -> do { x <- Binary.get; rest :: [a] <- getManyUntilEmpty; return $ x:rest; }}; } -- end