I've attached the script that I had trouble with. It tries to replicate one directory structure in another directory, while replacing filenames and file contents with random data. When compiled with -O1 or -O2 resulting file and directory names are composed only of a's and b's, but file contents seem properly randomized.
ghc-7.6.2, vector-0.10.0.1, primitive-0.5.0.1, mwc-random-0.12.0.1, Gentoo Linux i686 3.8.2-pf. On Tue, 09 Jul 2013 22:43:36 +0400 Aleksey Khudyakov <alexey.sklad...@gmail.com> wrote: > On 09.07.2013 22:10, kudah wrote: > > Same here, I used mwc-random to generate random strings. It works in > > ghci and when compiled with -O0, but with -O1 and -O2 I've been > > getting exclusively a's and b's. > > > It looks like MWC generates only 0 and 1 for some reason. I've tried > to write simple test but everything works fine. Could you post test > case and compiler/libraries/OS versions you use? > > _______________________________________________ > Haskell-Cafe mailing list > Haskell-Cafe@haskell.org > http://www.haskell.org/mailman/listinfo/haskell-cafe
{-# LANGUAGE OverloadedStrings #-} {-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-imports #-} module Main where import Shelly import Filesystem.Path.CurrentOS (splitDirectories, encodeString, decodeString) import qualified Filesystem as F import qualified Data.Text as T import qualified Data.ByteString as B import Control.Monad.IO.Class import System.Random.MWC import Control.Monad.Primitive import Control.Monad import Control.Applicative import Prelude hiding (FilePath) import Data.String import System.Environment rands :: (PrimMonad m, Variate a) => Gen (PrimState m) -> Int -> m [a] rands gen i = replicateM i (uniform gen) randRs :: (PrimMonad m, Variate a) => Gen (PrimState m) -> Int -> (a, a) -> m [a] randRs gen i z = replicateM i (uniformR z gen) lastElemLength :: FilePath -> Int lastElemLength fd = case splitDirectories fd of [] -> error $ "Empty filepath " ++ show fd g -> T.length $ toTextIgnore $ last g randName :: Gen (PrimState IO) -> Int -> IO FilePath randName gen l = decodeString . map toEnum <$> randRs gen l (fromEnum 'a', fromEnum 'z') main :: IO () main = do g <- getArgs case g of [inDir, outDir] -> withSystemRandom . asGenIO $ \gen -> do shellyNoDir $ do escaping False $ do -- verbosely $ do out <- absPath (decodeString outDir) in' <- absPath (decodeString inDir) descent gen out in' _ -> putStrLn "Specify input directory and output directory" descent :: Gen (PrimState IO) -> FilePath -> FilePath -> Sh () descent gen outDir fd = do isDir <- test_d fd if isDir then do n <- liftIO $ randName gen $ lastElemLength fd let newDir = outDir </> n mkdir_p newDir chdir fd $ do filesOrDirs <- ls "." mapM_ (descent gen newDir) filesOrDirs else do file <- absPath fd liftIO $ do size <- F.getSize file newFname <- randName gen $ lastElemLength file bs <- B.pack <$> rands gen (fromInteger size) B.writeFile (encodeString $ outDir </> newFname) bs
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe