RE: unsafePtrCompare, anybody?

2001-09-19 Thread Simon Marlow

 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]

These uses of unsafePerformIO really *are* unsafe though :-)

Your implementation of mkAtom seems to be similar the the StableName
library, in that it has the property that if

mkAtom e == mkAtom e', then e == e'

but the reverse isn't necessarily true (it may or may not be true).
Which is why mkAtom has to be in the IO monad: it has observable
non-determinism.

FastString works differently: it guarantees that both

mkFastString s == mkFastString s'  =   s == s'
s == s'  =  mkFastString s == mkFastString s'

hold.  So it is safe for mkFastString to be a pure non-I/O function,
because it doesn't have any observable non-deterministic behaviour.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: unsafePtrCompare, anybody?

2001-09-18 Thread Simon Marlow


 One's intuition would suggest that you could be safely 
 implement mkAtom 
 without wrapping it in a IO monad.   After all, at least at a 
 abstract level, 
 an atom table is referentially transparent.  The library 
 documentation says 
 that lack of side effects and environmental independance is 
 sufficent to 
 order for uses of unsafePerformIO to be safe.  Is there a 
 exact (or at least 
 better) criterion for safety?   

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.

 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.

HTH,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: unsafePtrCompare, anybody?

2001-09-18 Thread Alastair David Reid


Leon Smith [EMAIL PROTECTED] writes:
 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.

Here's a simple test you can apply:

  Can you rewrite your module in pure Haskell so that it has the
  same observed behaviour but (probably) different operational
  behaviour (e.g. space and time usage)?

If the answer is yes, then you preserve referential transparency, type
safety and other desirable properties (on the assumption that pure
Haskell has these properties).

If the answer is no, you've probably broken one or more important
properties.  (There may still be hope but you might have to get very
devious (cf. non-determinism in Rittri et al.'s UniqueSupply, Hughes
and O'Donnell's non-determism monad and exception handling).)

-- 
Alastair Reid[EMAIL PROTECTED]http://www.cs.utah.edu/~reid/

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



RE: unsafePtrCompare, anybody?

2001-09-17 Thread Simon Marlow

 I'm writing an atom table for a compiler/interpreter, and it 
 would be really 
 nice to use unsafePtrLT to implement tree-based finite maps.  
 
 For clarification, my atom table consists  of these three functions: 
 
 mkAtom :: String - IO Atom
 show  :: Atom - String
 (==)  :: Atom - Atom - Bool
 
 such that   
   mkAtom s = (return . show) == return s
 and
   mkAtom . show == return
 and 
   atom == atom'  =  show atom == show atom' 
 
 mkAtom looks up each string in a table stored in an global 
 variable, and 
 returns the atom stored in the table if it is there.  
 Otherwise, it makes the 
 string into an atom, inserts the atom into the table, and 
 returns this new 
 atom.
 
 The point of all of this is that now string equality, when 
 strings are made 
 into atoms, is just pointer equality, which is available as 
 IOExts.unsafePtrEq.

You might want to check out GHC's FastString module, which does
essentially this.  We use an explicit hash table, and each FastString
has a unique Id for fast comparison.

To solve your immediate problem, you could also take a look at the
StableName library, which lets you map any old Haskell value on to an
Int so you can build finite maps etc. (we use StableNames to build memo
tables).  There's a small garbage collector overhead for this, though.

 Of course, the misuses of unsafePtrEq aren't nearly as 
 heinous as those of 
 unsafePtrCompare.   On the other hand, it might be next to 
 impossible to 
 effectively use unsafePtrCompare in cases that it isn't 
 completely safe to 
 use, whereas there are plently of situations where 
 unsafePtrEq is semi-safe 
 to use.

I can't think of a way to use unsafePtrCompare safely :-)  The relative
ordering of objects isn't guaranteed to be stable under GC.

Cheers,
Simon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: unsafePtrCompare, anybody?

2001-09-17 Thread Carl R. Witty

Leon Smith [EMAIL PROTECTED] writes:

 However, in this situation, pointer comparison is simply an arbitrary total 
 order on the set of all atoms, which is all we need to implement finite maps 
 based on search trees.  And of course, pointer comparisons are a much cheaper 
 operation that actual string comparison.

You could just add an extra Int sequence number to your Atoms, and
compare using that.

Carl Witty

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: unsafePtrCompare, anybody?

2001-09-17 Thread Leon Smith

 I can't think of a way to use unsafePtrCompare safely :-)  The relative
 ordering of objects isn't guaranteed to be stable under GC.

 Cheers,
   Simon

Doh,  that would throw a monkey wrench into things, wouldn't it?   I know of 
compacting GC algorithms, but I didn't consider that GHC might be using one.  
At least I am now more enlightened on the inner workings of the magic beast...

I've considered many of the other implementation options, but as it isn't 
essential to the working of the compiler,  it hasn't been a priority yet.  It 
simply struck me that this would be a particularly quick and easy way to 
implement reasonably good atom tables, only requiring a newtype declaration 
and a few very simple function definitions.   

Thanks to Simon for saving me from reinventing the wheel.   The libraries 
mentioned here should prove to be quite useful.  

One's intuition would suggest that you could be safely implement mkAtom 
without wrapping it in a IO monad.   After all, at least at a abstract level, 
an atom table is referentially transparent.  The library documentation says 
that lack of side effects and environmental independance is sufficent to 
order for uses of unsafePerformIO to be safe.  Is there a exact (or at least 
better) criterion for safety?   

unsafePerformIO is used in the implementation of mkFastString, so how is 
it's side effects safe.   I experimented with unsafePerformIO with my Atom 
table, but I could not get tthe code to work properly.

best,
leon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



unsafePtrCompare, anybody?

2001-09-15 Thread Leon Smith

I'm writing an atom table for a compiler/interpreter, and it would be really 
nice to use unsafePtrLT to implement tree-based finite maps.  

For clarification, my atom table consists  of these three functions: 

mkAtom :: String - IO Atom
show  :: Atom - String
(==)  :: Atom - Atom - Bool

such that   
mkAtom s = (return . show) == return s
and
mkAtom . show == return
and 
atom == atom'  =  show atom == show atom' 

mkAtom looks up each string in a table stored in an global variable, and 
returns the atom stored in the table if it is there.  Otherwise, it makes the 
string into an atom, inserts the atom into the table, and returns this new 
atom.

The point of all of this is that now string equality, when strings are made 
into atoms, is just pointer equality, which is available as 
IOExts.unsafePtrEq.

However, in this situation, pointer comparison is simply an arbitrary total 
order on the set of all atoms, which is all we need to implement finite maps 
based on search trees.  And of course, pointer comparisons are a much cheaper 
operation that actual string comparison.

Of course, the misuses of unsafePtrEq aren't nearly as heinous as those of 
unsafePtrCompare.   On the other hand, it might be next to impossible to 
effectively use unsafePtrCompare in cases that it isn't completely safe to 
use, whereas there are plently of situations where unsafePtrEq is semi-safe 
to use.

best,
leon

___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users