> An exact criterion would require a formal semantics for Haskell, which
> we don't have.  But informally, if a function which is implemented using
> unsafePerformIO is pure - that is, its result depends only on the values
> of its arguments and possibly its free variables - then that is a "safe"
> use of unsafePerformIO.

I'm not sure I completely understand you here.  Obviously, these free 
variables must also include mutable variables, as mkFastString employs these, 
and the side-effects can be seen from within the module itself.  

> > "unsafePerformIO" is used in the implementation of
> > mkFastString, so how is it's side effects "safe".
>
> It is safe because the side effects aren't visible outside the
> implementation of mkFastString.

My intuition says that none of the side-effects in my implementation are 
visible from the abstract level of the module.  However, the use of 
unsafePerformIO certainly modifies the behaviour of the module.  For example, 
the following definitions at the beginning of a GHCi session on the attached 
code lead to the subsequent behaviour:


foo1 <- return (unsafePerformIO (mkAtom "foo"))
foo2 <- return (unsafePerformIO (mkAtom "foo"))
bar  <- return (unsafePerformIO (mkAtom "bar"))
safefoo1 <- mkAtom "foo"
safefoo2 <- mkAtom "foo"
safebar  <- mkAtom "bar"
list <- return [safefoo1, safefoo2, safebar, foo1, foo2, bar]


Atom> [x == y| x <- list, y <- list]
[True ,True ,False,False,False,False,
 True ,True ,False,False,False,False,
 False,False,True ,False,False,False,
 False,False,False,True ,False,False,
 False,False,False,False,True ,False,
 False,False,False,False,False,True  ]

As can be seen from above, the only times that (==) returns true, aside from 
reflexive cases, is when  (safefoo1 == safefoo2) and (safefoo2 == safefoo1).  

I've also played with the order of atom creation, and it doesn't appear to 
have any effect on the truth table.

best,
leon
module Atom
    (   Atom()
    ,   mkAtom
    ) where

import IOExts
import FiniteMap

newtype Atom = MkAtom String

instance Eq Atom where
    (==) = unsafePtrEq

instance Ord Atom where
    (MkAtom x) <= (MkAtom x')      = x <= x'
    (MkAtom x) <  (MkAtom x')      = x <  x'
    (MkAtom x) >= (MkAtom x')      = x >= x'
    (MkAtom x) >  (MkAtom x')      = x >  x'
    compare (MkAtom x) (MkAtom x') = compare x x'

instance Show Atom where
    show (MkAtom x) = x


atomTable :: IORef (FiniteMap String Atom)
atomTable = unsafePerformIO (newIORef emptyFM)

mkAtom str
    = do
      fm <- readIORef atomTable
      case lookupFM fm str of
       Just x  -> return x
       Nothing -> let
                    atom = MkAtom str
                   in do
                      writeIORef atomTable (addToFM fm str atom)
                      return atom










Reply via email to