Question

What would be the best way to do this? unsafePerformIO? Template Haskell? Something else? I have never used either of those so I don't know many of the details of using them.

Note that the program will be compiled every time it is run, so it doesn't matter if I generate the string at compile time or run time. I also need to use this string in tons of places throughout the code so I can't really do it the 'proper' way and have it be an IO action, that would require far too much other code to be put into the IO monad.

Était-ce utile?

La solution 3

Using unsafeperformIO in this particular case seems to be fine as the documentation says :

For this to be safe, the IO computation should be free of side effects and independent of its environment.

We are not worried about the order of newStdGen.

import System.Random
import System.IO.Unsafe

randomStr :: String
randomStr = take 10 $ randomRs ('a','z') $ unsafePerformIO newStdGen

main = do
     putStrLn randomStr
     putStrLn randomStr

Autres conseils

I wouldn't recommend using unsafePerformIO. I guess The Haskell Report doesn't state that a constant function is memoized so it can happen that

randStringUnsafe :: String
randStringUnsafe = unsafePerformIO $ liftM (take 10 . randomRs ('a','z')) newStdGen

will give you different results for different calls! With GHC it's most likely going to be memoized, but without guarantees. For example, what if the compiler inlines the function? (GHC is probably smart enough not to do it, but again, no guarantees ...). And for example

randNumUnsafe :: (Random a, Num a) => [a]
randNumUnsafe = unsafePerformIO $ liftM (take 10 . randomRs (0, 9)) newStdGen

will definitely give you different results each time it's called.


I'd rather go with Template Haskell. It's perhaps a bit more complicated, but safe. In one module we define

{-# LANGUAGE TemplateHaskell #-}
module RandomTH where
import Control.Monad
import System.Random
import Language.Haskell.TH

-- A standard function generating random strings.
randString :: IO String
randString = liftM (take 10 . randomRs ('a','z')) newStdGen

-- .. lifted to Q
randStringQ :: Q String
randStringQ = runIO randString

-- .. lifted to an Q Exp
randStringExp :: Q Exp
randStringExp = randStringQ >>= litE . stringL

-- | Declares a constant `String` function with a given name
-- that returns a random string generated on compile time.
randStringD :: String -> DecsQ
randStringD fname = liftM (: []) $
    funD (mkName fname) [clause [] (normalB randStringExp) []]

(Perhaps randStringD could be written in a more readable way - if you have an idea, please edit it or comment.)

Then, in another module we can use it to declare a constant function with a given name:

{-# LANGUAGE TemplateHaskell #-}

$(randStringD "randStr")

main = do
    putStrLn randStr
    putStrLn randStr

It might be easier to answer this question if we knew more about the surrounding context, but the approach I would take would be to pass in the string everywhere it was necessary, and create it once in main. Thus:

import Control.Monad
import System.Random

-- Some arbitrary functions

f :: String -> Int -> Int -> Int
f rstr x y = length rstr * x * y

-- This one doesn't depend on the random string
g :: Int -> Int
g x = x*x

h :: String -> String -> Int
h rstr str = sum . map fromEnum $ zipWith min rstr str

main :: IO ()
main = do
  rstr <- randomString
  putStr "The result is: "
  print $ f rstr (g 17) (h rstr "other string")

randomString :: IO String
randomString = flip replicateM (randomRIO (' ','~')) =<< randomRIO (1,32)

This is probably what I would do.

On the other hand, if you have a lot of these functions, you might potentially find it bulky to pass rstr into all of them. To abstract this, you can use the Reader monad; values of type Reader r a—or more generally, values of type MonadReader r m => m a—are able to ask for a value of type r, which is passed in once, at the top level. That would give you:

{-# LANGUAGE FlexibleContexts #-}

import Control.Applicative
import Control.Monad.Reader
import System.Random

f :: MonadReader String m => Int -> Int -> m Int
f x y = do
  rstr <- ask
  return $ length rstr * x * y

g :: Int -> Int
g x = x*x

h :: MonadReader String m => String -> m Int
h str = do
  rstr <- ask
  return . sum . map fromEnum $ zipWith min rstr str

main :: IO ()
main = do
  rstr <- randomString
  putStr "The result is: "
  print $ runReader (f (g 17) =<< h "other string") rstr

randomString :: IO String
randomString = flip replicateM (randomRIO (' ','~')) =<< randomRIO (1,32)

(Actually, since (r ->) is an instance of MonadReader r, the functions above can be viewed as having type f :: Int -> Int -> String -> Int, etc., and you can leave out the call to runReader (and remove FlexibleContexts)—the monadic computation you've built will just be of type String -> Int. But I probably wouldn't bother.)

Yet another approach, which is probably an unnecessary use of language extensions (I certainly prefer the two approaches above), would be to use an implicit parameter, which is a variable that gets passed around dynamically and reflected in the type (sort of like the MonadReader String m constraint). That would look like so:

{-# LANGUAGE ImplicitParams #-}

import Control.Monad
import System.Random

f :: (?rstr :: String) => Int -> Int -> Int
f x y = length ?rstr * x * y

g :: Int -> Int
g x = x*x

h :: (?rstr :: String) => String -> Int
h str = sum . map fromEnum $ zipWith min ?rstr str

main :: IO ()
main = do
  rstr <- randomString
  let ?rstr = rstr
  putStr "The result is: "
  print $ f (g 17) (h "other string")

randomString :: IO String
randomString = flip replicateM (randomRIO (' ','~')) =<< randomRIO (1,32)

Now. I must admit that you can do these sorts of things at the top level. There's a standard hack which allows using unsafePerformIO to get top-level IORefs, for instance; and Template Haskell would allow you to run an IO action once, at compile time, and embed the result. But I would avoid both of those approaches. Why? Well, fundamentally, there's some debate over whether "pure" means "determined exactly by the syntax/doesn't change over any run of the program" (an interpretation I would favor), or it means "doesn't change over this run of the program." As one example of the problems this caused: the Hashable package, at one point, switched from a fixed salt to a random salt. This caused an uproar on Reddit, and introduced bugs into previously-working code. The package backpedalled, and now allows users to opt-in to this behavior through an environment variable, defaulting to between-runs purity.

That said, here's how to use the two approaches that you mentioned, unsafePerformIO and Template Haskell, to get top-level random data—along with why, separate from the concerns about between-runs purity, I wouldn't use these techniques. (These are the only two techniques for doing this that I can think of.)

  1. The unsafePerformIO hack, as it's called, is very fragile; it relies on certain optimizations not being performed, and is generally not a well-liked approach. Doing it this way would look like so:

    import Control.Monad
    import System.Random
    import System.IO.Unsafe
    
    unsafeConstantRandomString :: String
    unsafeConstantRandomString = unsafePerformIO $
      flip replicateM (randomRIO (' ','~')) =<< randomRIO (1,32)
    {-# NOINLINE unsafeConstantRandomString #-}
    

    Seriously, though, see how much the word unsafe is used in the above code? That's because using unsafePerformIO will bite you unless you really know what you're doing, and possibly even then. Even when unsafePerformIO doesn't bite you directly, no less than the authors of GHC would say that it's probably not worth using for this (see the section titled "Crime Doesn't Pay"). Don't do this.

  2. Using Template Haskell for this is like using a nuclear warhead to kill a gnat. An ugly nuclear warhead, to boot. That approach would look like the following:

    {-# LANGUAGE TemplateHaskell #-}
    
    import Control.Monad
    import System.Random
    import Language.Haskell.TH
    
    thConstantRandomString :: String
    thConstantRandomString = $(fmap (LitE . StringL) . runIO $
      flip replicateM (randomRIO (' ','~')) =<< randomRIO (1,32))
    

    Note also that in the Template Haskell version, you can't abstract the random-string-creation functionality into a separate value randomString :: IO String in the same module, or you'll run afoul of the stage restriction. It is safe, though, unlike the unsafePerformIO hack; at least, safe modulo the concerns about between-run purity mentioned above.

Generating a random number in IO does not imply that downstream functions must use IO.

Here's an example pure function that depends on a value of type A:

f :: A -> B

... and here is an IO action that generates an A:

io :: IO A

I don't have to modify f to use IO. Instead, I use fmap:

fmap f io :: IO B

This is exactly the sort of problem that functors are supposed to solve: lifting morphisms over wrapped values so that the morphisms do not need to be modified.

import System.Random

main = do
   gen <- newStdGen
   let str = take 10 $ randomRs ('a','z') gen 

   putStrLn str

   putStrLn $ (reverse . (take 3)) str

This generates a string ten characters long with only lowercase letters. This code is in the IO monad but str is pure it can be passed to pure functions. You can't get something random without the IO Monad. You could do an unsafePerformIO but I don't really see why. You can pass the str value around if you always want the same one. If you look at the last line of my code you can see i have a pure function that operates on the string but since i want to see it i call putStrLn which returns an empty IO action.

EDIT: Or this may be the place for the Reader Monad

For strings, numbers, and others:

import System.Random ( newStdGen, randomRs, randomRIO )

main :: IO ()
main = do
    s <- randomString 8 ""
    putStrLn s
randomString :: Integer -> String -> IO String
randomString 0 str = return str
randomString size str = do
    g <- newStdGen
    t <- randomRIO ( 0, 2 )
    let s = take 1 $ randomRs ( range t ) g
    randomString ( size - 1 ) ( str ++ s )
    
    where
        range :: Integer -> ( Char, Char )
        range i
            | i == 0 = ('0', '9')
            | i == 1 = ('A', 'Z')
            | otherwise = ('a', 'z')
Licencié sous: CC-BY-SA avec attribution
Non affilié à StackOverflow
scroll top