
So we all know the age-old rule of thumb, that unsafeXXX is simply evil and anybody that uses it should be shot (except when it's ok). I understand that unsafeXXX allows impurity, which defiles our ability to reason logically about haskell programs like we would like to. My question is, to what extent is this true? Suppose we had a module, UnsafeRandoms, which had a function that would allow you to generate a different random number every time you call it. The semantics are relatively well-defined, impurity is safely sectioned off in its own impure module, which is clearly labeled as such. How much damage does this do? Can we push the lines elsewhere? Is sectioning unsafeXXX into Unsafe modules a useful idiom that we can use for other things as well?

On Thu, 2009-02-05 at 16:11 -0500, Andrew Wagner wrote:
So we all know the age-old rule of thumb, that unsafeXXX is simply evil and anybody that uses it should be shot (except when it's ok).
I understand that unsafeXXX allows impurity, which defiles our ability to reason logically about haskell programs like we would like to.
Not just that! Parametric polymorphism is unsound in combination with mutable values; but unsafePerformIO turns on exactly that combination. unsafeCoerce :: alpha -> beta unsafeCoerce x = unsafePerformIO $ do let r = unsafePerformIO $ newIORef undefined r `writeIORef` x readIORef r
My question is, to what extent is this true?
unsafePerformIO is a true function --- in the absence of any fancy compiler trickery --- on a small subset of its domain. Outside of that subset, I would regard use of unsafePerformIO simply as a bug --- violation of an unchecked precondition. Period.
Suppose we had a module, UnsafeRandoms, which had a function that would allow you to generate a different random number every time you call it.
unsafePerformIO does not allow you to guarantee this! If I defined myRandomNumber = unsafePerformIO $ randomNumber then the compiler is permitted to call randomNumber (at most) *once*, and use that number throughout the program.
The semantics are relatively well-defined,
Leaving aside the issue above, I would think complete randomness was nearly the worst possible case, semantically. (The *worst* worst possible case would be non-statistical non-determinism --- which is what you actually get here).
impurity is safely sectioned off in its own impure module, which is clearly labeled as such. How much damage does this do?
Well, it forces me to chase your libraries import lists to decide whether I want to trust your code, for one thing. Haskell is all about making it easier to audit code, not harder.
Can we push the lines elsewhere?
I'd rather not.
Is sectioning unsafeXXX into Unsafe modules a useful idiom that we can use for other things as well?
I'd rather not write other unsafe functions at all. Sectioning off things that need to be unsafe into pure solutions --- like, say, monads --- is a much better idea. (Go read the global variables thread from last year). jcc

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Andrew Wagner wrote: | I understand that unsafeXXX allows impurity, which defiles our ability | to reason logically about haskell programs like we would like to. My | question is, to what extent is this true? My opinion is that unsafeXXX is acceptable only when its use is preserved behind an abstraction that is referentially transparent and type safe. Others may be able to help refine this statement. | Suppose we had a module, UnsafeRandoms, which had a function that would | allow you to generate a different random number every time you call it. | The semantics are relatively well-defined, impurity is safely sectioned | off in its own impure module, which is clearly labeled as such. How much | damage does this do? This does not preserve referential transparency, so by my criteria above this is an unacceptable use of an unsafe function. One reason it's a bad idea is that it removes determinism, which may be very important for testability. - - Jake -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iEYEARECAAYFAkmLW/MACgkQye5hVyvIUKniOACfQGPLiY65+eiMfsv7BlbYLI++ Bd0An1N5wp6TDkJzhmdw831/Gj45Bv9S =TnQg -----END PGP SIGNATURE-----

I do have asked myself the question whether a "really random generating"
function could be regarded as "pure" somehow (actually would a true random
function still be a mathematical function?)
E.g. the function would return a true (not pseudo) random number,
practically unpredictable (e.g. hardware assisted, using some physical
phenomenon, e.g. using atmospheric noise or something). So you surely won't
get referential transparency but since the function is really random, this
would be correct behavior?
Of course you could just put this random generator in the IO monad, but
certain algorithms- like Monte Carlo - intuitively don't seem to operate in
a IO monad to me.
Okay, just some thoughts from someone who knows absolutely nothing about
category theory or advanced computer science, so don't shoot me ;-)
On Thu, Feb 5, 2009 at 10:36 PM, Jake McArthur
-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
Andrew Wagner wrote: | I understand that unsafeXXX allows impurity, which defiles our ability | to reason logically about haskell programs like we would like to. My | question is, to what extent is this true?
My opinion is that unsafeXXX is acceptable only when its use is preserved behind an abstraction that is referentially transparent and type safe. Others may be able to help refine this statement.
| Suppose we had a module, UnsafeRandoms, which had a function that would | allow you to generate a different random number every time you call it. | The semantics are relatively well-defined, impurity is safely sectioned | off in its own impure module, which is clearly labeled as such. How much | damage does this do?
This does not preserve referential transparency, so by my criteria above this is an unacceptable use of an unsafe function. One reason it's a bad idea is that it removes determinism, which may be very important for testability.
- - Jake -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
iEYEARECAAYFAkmLW/MACgkQye5hVyvIUKniOACfQGPLiY65+eiMfsv7BlbYLI++ Bd0An1N5wp6TDkJzhmdw831/Gj45Bv9S =TnQg -----END PGP SIGNATURE-----
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

2009/2/5 Peter Verswyvelen
Of course you could just put this random generator in the IO monad, but certain algorithms- like Monte Carlo - intuitively don't seem to operate in a IO monad to me.
For PRNGs, only State is needed, not IO. But you might find the `randoms' function useful: it returns in infinite list of pseudo-random values. --Max

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 Peter Verswyvelen wrote: | I do have asked myself the question whether a "really random generating" | function could be regarded as "pure" somehow (actually would a true | random function still be a mathematical function?) | | E.g. the function would return a true (not pseudo) random number, | practically unpredictable (e.g. hardware assisted, using some physical | phenomenon, e.g. using atmospheric noise or something). So you surely | won't get referential transparency but since the function is really | random, this would be correct behavior? An informal definition of a function might be something like a black box that takes and input and produces an output, and for each possible input, the output must be the same. Taking this to be a function, there is really no such thing as a random function, and if there was, it wouldn't even need to be a function. (What would the input to it be?) If you wanted to mathematically represent a random number, it would, in most cases I can think of, best be represented as a free variable. In a program, such a free variable could be filled in by the runtime. Conveniently, (and by no coincidence) this is something the IO monad can provide for us! :) | Of course you could just put this random generator in the IO monad, but | certain algorithms- like Monte Carlo - intuitively don't seem to operate | in a IO monad to me. Why not? A Random monad might be more appropriate in this case anyway. Such a monad is a State monad that hold a random seed. Every time a random number is needed, the seed is passed to a deterministic psuedo-random number generator, and a new seed is put as the next state. If a truly random number is ever needed, either IO or unsafeInterleaveIO will be needed. The use of unsafeInterleaveIO would be a (rightly) controversial choice though. - - Jake -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org iEYEARECAAYFAkmLaK4ACgkQye5hVyvIUKk88QCfRksu7z80QmzgjUvmiyrzDDjl QnsAn1R5DHz2tJpWP3yb0+U+loyBdyCX =RIX9 -----END PGP SIGNATURE-----

Well, one could say that a truly random number function takes as input time
and some constant unique identifier (serial number) of the TRND device and
gives you the random value measured at that time by this device. Of course
this would mean the random value is not really random, since "the potential
creator of the universe" would have known the value already, but to all
humble beings living in the bubble, it would be Truly Random :)
Then the question is, is time a function? If so, is it discrete?
Okay, this is not Haskell anymore, this would become philosophy, and since a
good and smart friend of mine told me that nobody really knows what time is,
this is off topic. Sorry! :)
On Thu, Feb 5, 2009 at 11:31 PM, Jake McArthur
-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1
Peter Verswyvelen wrote: | I do have asked myself the question whether a "really random generating" | function could be regarded as "pure" somehow (actually would a true | random function still be a mathematical function?) | | E.g. the function would return a true (not pseudo) random number, | practically unpredictable (e.g. hardware assisted, using some physical | phenomenon, e.g. using atmospheric noise or something). So you surely | won't get referential transparency but since the function is really | random, this would be correct behavior?
An informal definition of a function might be something like a black box that takes and input and produces an output, and for each possible input, the output must be the same. Taking this to be a function, there is really no such thing as a random function, and if there was, it wouldn't even need to be a function. (What would the input to it be?)
If you wanted to mathematically represent a random number, it would, in most cases I can think of, best be represented as a free variable. In a program, such a free variable could be filled in by the runtime. Conveniently, (and by no coincidence) this is something the IO monad can provide for us! :)
| Of course you could just put this random generator in the IO monad, but | certain algorithms- like Monte Carlo - intuitively don't seem to operate | in a IO monad to me.
Why not?
A Random monad might be more appropriate in this case anyway. Such a monad is a State monad that hold a random seed. Every time a random number is needed, the seed is passed to a deterministic psuedo-random number generator, and a new seed is put as the next state.
If a truly random number is ever needed, either IO or unsafeInterleaveIO will be needed. The use of unsafeInterleaveIO would be a (rightly) controversial choice though.
- - Jake -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.9 (GNU/Linux) Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org
iEYEARECAAYFAkmLaK4ACgkQye5hVyvIUKk88QCfRksu7z80QmzgjUvmiyrzDDjl QnsAn1R5DHz2tJpWP3yb0+U+loyBdyCX =RIX9 -----END PGP SIGNATURE-----

Peter Verswyvelen
I do have asked myself the question whether a "really random generating" function could be regarded as "pure" somehow (actually would a true random function still be a mathematical function?)
Wasn't there some agreement some time ago on this list that the universe itself is pure and computers are just simulating impurity by being, essentially, state monads on steroids? -- (c) this sig last receiving data processing entity. Inspect headers for copyright history. All rights reserved. Copying, hiring, renting, performance and/or quoting of this signature prohibited.

Hi,
My opinion is that unsafeXXX is acceptable only when its use is preserved behind an abstraction that is referentially transparent and type safe. Others may be able to help refine this statement.
I would agree with this. The problem is that impurity spreads easily. For example, suppose we have this truly random number generator, 'random'. As soon as we have this, then *almost every* function is potentially impure: f :: Integer -> Integer f x = random + x g :: [Integer] g = repeat random etc. etc. The compiler has no way of tracking impurity other than through the type system which is, of course, exactly what monads do. To echo the sentiment above, the only safe way to use unsafePerformIO is to hide it behind a function that *is* guaranteed to be pure (i.e., returns the same values for the same arguments, can be inlined, etc.). And even then, I would recommend against it. Let me give a *practical* reason why. For a long time, I would never even have considered unsafePerformIO, but I recently had an application that needed unique global identifiers in lots of places, and I was reluctant to pass state around everywhere; *but* I could hide it in a few functions, which were themselves pure. It looked something like: -- Replace (some) name by a number quote :: Integer -> Term -> Term -- Replace a number by (that) name unquote :: Name -> Term -> Term -- Typical usage foo t == let l = getUnsafeUniqueGlobalIdentifier () in unquote l . do some stuff . quote l Since "unquote l . quote l" is an identity operation, 'foo' itself is pure -- provided that nothing in 'do some stuff' relies on the exact identity of the identifier. --- A rule which I broke at some point, got some very strange behaviour, and took me ages to debug. This was mostly due to laziness, which made the point of execution of the unsafe operation to be very difficult to predict. For example, every call to getUnsafeUniqueGlobalIdentifier (it wasn't actually called that, don't worry :-) yielded a number one higher than the previous. However, in a list of terms [t1, t2, .., tn] all of which include some unique idnetifier, it is *not* the generation of the list that determines whether the identifiers in these terms are incrementing, but the *evaluation* of the list -- when are the terms forced to normal form. I was called 'sort' on this list, and sort depended on the values of these identifiers -- but since sort evaluated the terms in the list to normal form in a hard to predict order, the order of the list was anything but sorted! --- Moreover, you need all sorts of compiler options or nasty hacks (the unit argument to getUnsafeUniqueGlobalIdentifier above is no mistake) to avoid the compiler optimizing your code in ways that you did not expect. In the end, I ended up rewriting the entire application to avoid the use of this global unique identifiers, because it was simply too difficult to get right. I felt I was writing C code again and was chasing bugs due to dangling pointers and the wrong memory being used. Not a time I want to return to! Moral of the story: unless you really really need to and really really know what you are doing -- do not use unsafePerformIO. Uncontrolled side effects and lazines will cause extremely hard to track behaviour in your program, and things are almost guaranteed to go wrong. Edsko

On 5 Feb 2009, at 22:11, Andrew Wagner wrote:
So we all know the age-old rule of thumb, that unsafeXXX is simply evil and anybody that uses it should be shot (except when it's ok).
I understand that unsafeXXX allows impurity, which defiles our ability to reason logically about haskell programs like we would like to. My question is, to what extent is this true?
Suppose we had a module, UnsafeRandoms, which had a function that would allow you to generate a different random number every time you call it. The semantics are relatively well-defined, impurity is safely sectioned off in its own impure module, which is clearly labeled as such. How much damage does this do?
The problem here is composability – you have no idea how far your non referentially transparent code has spread, because you can compose functions together willy nilly, meaning your random numbers can get pushed through all sorts of things, and cause odd behaviors (e.g. if a constant happens to get evaluated twice rather than once, and return different values each time).
Can we push the lines elsewhere? Is sectioning unsafeXXX into Unsafe modules a useful idiom that we can use for other things as well?
Well not useful modules, but useful types instead. The point of IO for example is to deliberately construct an environment in which you can't get one of your unsafe values out into the referentially transparent world – the IO type denotes the line on which one side contains unsafe values, and the other side does not. There are however some instances where unsafe functions *are* safe, Conal's unamb function for example, always returns the same value (as long as its precondition is met), even though it contains IO based code to race the values. There are also some instances where unsafe functions are safe purely through force of will. For example: type ResourcePath = FilePath loadImageResource :: ResourcePath -> Image loadImageResource = unsafePerformIO . loadImage =<< readFile This is safe iff you treat the resource as a part of your program, just like your program's code, if it changes, the world falls down, but as long as it's still there and still the same, you're entirely safe. Bob

On Thu, Feb 5, 2009 at 3:11 PM, Andrew Wagner
So we all know the age-old rule of thumb, that unsafeXXX is simply evil and anybody that uses it should be shot (except when it's ok). I understand that unsafeXXX allows impurity, which defiles our ability to reason logically about haskell programs like we would like to. My question is, to what extent is this true?
Tangential to all of this - sometimes my unsafeXXX functions are pure, but partial. So I'll have: foo :: a -> b -> Maybe c and unsafeFoo :: a -> b -> c -Antoine

On Fri, Feb 6, 2009 at 1:00 PM, Antoine Latter
Tangential to all of this - sometimes my unsafeXXX functions are pure, but partial. So I'll have:
foo :: a -> b -> Maybe c
and
unsafeFoo :: a -> b -> c
I use the "unsafe" prefix in the same way. For me it means 'assume that preconditions hold'. If the preconditions do not hold and you evaluate an unsafe function anyway I would expect an error, as opposed to an exception. I have done that in my (tiny) roman numerals package. -- simplified toRoman :: Int -> Either String Int unsafeToRoman :: Int -> String The first function is very clear about the fact that something can go wrong. If you provide it with a value of (-3) it will (hopefully) produce something like 'Left "no negative numbers allowed"'. The second function hides this fact and will result in a (uncatchable) runtime error. It is still a pure function, but preventing errors is now the responsibility of whoever evaluates it.

"Roel" == Roel van Dijk
writes:
Roel> On Fri, Feb 6, 2009 at 1:00 PM, Antoine Latter

Do you document the preconditions? Yes. The 'safe' variants of those functions have all preconditions listed in the accompanying (haddock) comments. The 'unsafe' variants simply state that they promote exceptions to errors.
It seems to me that this is more useful than naming a function unsafeXXX. Well, I do both :-) They are called unsafeXXX and they state why they are unsafe.
I was using comments to document the contracts on my functions, but I have just found about about ESC/Haskell, so I am now using the contract notation of that (not yet released) tool.
See http://www.cl.cam.ac.uk/~nx200/ That is interesting. I like formal proofs and preconditions better than informal ones.

Excerpts from Andrew Wagner's message of Thu Feb 05 15:11:17 -0600 2009:
My question is, to what extent is this true?
You can completely destroy the soundness of the type system: import Data.IORef import System.IO.Unsafe import Control.Monad cast :: a -> b cast x = f where f = unsafePerformIO $ do writeIORef r [x] b <- liftM head $ readIORef r return b Austin

Excerpts from Austin Seipp's message of Sun Feb 08 01:45:45 -0600 2009:
... code ...
Austin
*smacks head* import Data.IORef import System.IO.Unsafe import Control.Monad cast :: a -> b cast x = f where f = unsafePerformIO $ do writeIORef r [x] b <- liftM head $ readIORef r return b r = unsafePerformIO $ newIORef []
participants (12)
-
Achim Schneider
-
Andrew Wagner
-
Antoine Latter
-
Austin Seipp
-
Colin Paul Adams
-
Edsko de Vries
-
Jake McArthur
-
Jonathan Cast
-
Max Rabkin
-
Peter Verswyvelen
-
Roel van Dijk
-
Thomas Davie