Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread ajb
G'day all.

Quoting John Meacham <[EMAIL PROTECTED]>:

> would it be possible to provide an Ord instance for (IORef a)?

It would, although then someone else would just want a hashable instance.
Sounds to me like it might be worth coming up with a general IORef (and
STRef) wrapper.

Until then, this is what I use.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread ajb
G'day all.

Quoting [EMAIL PROTECTED]:

> Until then, this is what I use.

Second time lucky.

Cheers,
Andrew Bromage-
-- |
-- Module  :  Data.IOStableRef
-- Copyright   :  (c) Andrew Bromage 2002
-- License :  BSD-style (see the file libraries/base/LICENSE)
-- 
-- Maintainer  :  [EMAIL PROTECTED]
-- Stability   :  experimental
-- Portability :  portable
--
-- Mutable references in the IO monad, with stable orderings.
--
-

module Data.IOStableRef
  ( 
	IOStableRef,		-- abstract, instance of: Eq, Ord, Typeable
	newIOStableRef,		-- :: a -> IO (IOStableRef a)
readIOStableRef,	-- :: IOStableRef a -> IO a
writeIOStableRef,	-- :: IOStableRef a -> a -> IO ()
	modifyIOStableRef,	-- :: IOStableRef a -> (a -> a) -> IO ()
	hashIOStableRef,	-- :: IOStableRef a -> Int
	) where

import Prelude
import Data.IORef
import Data.Unique

data IOStableRef a
  = IOStableRef !Unique !(IORef a)


instance Eq (IOStableRef a) where
  IOStableRef u1 _ == IOStableRef u2 _  = u1 == u2

instance Ord (IOStableRef a) where
  IOStableRef u1 _ <  IOStableRef u2 _  = u1 <  u2
  IOStableRef u1 _ <= IOStableRef u2 _  = u1 <= u2
  IOStableRef u1 _ >  IOStableRef u2 _  = u1 >  u2
  IOStableRef u1 _ >= IOStableRef u2 _  = u1 >= u2
  compare (IOStableRef u1 _) (IOStableRef u2 _) = compare u1 u2

hashIOStableRef :: IOStableRef a -> Int
hashIOStableRef (IOStableRef u _)
  = hashUnique u

newIOStableRef :: a -> IO (IOStableRef a)
newIOStableRef x
  = newUnique >>= \u -> newIORef x >>= \r -> return (IOStableRef u r)

readIOStableRef :: IOStableRef a -> IO a
readIOStableRef (IOStableRef _ r)
  = readIORef r

writeIOStableRef :: IOStableRef a -> a -> IO ()
writeIOStableRef (IOStableRef _ r)
  = writeIORef r

modifyIOStableRef :: IOStableRef a -> (a -> a) -> IO ()
modifyIOStableRef (IOStableRef _ r) f
  = modifyIORef r f

#include "Dynamic.h"
INSTANCE_TYPEABLE1(IOStableRef,ioStableRefTc,"IOStableRef")
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Graham Klyne
If I have a polymorphic algebraic type (T a) with several type 
constructors, only one of which actually references the type parameter, is 
there any way to express type conversion for the type-parameter-independent 
constructors without actually mentioning all the constructors?

Here's a simple example based on Either:
[[
data A = A String deriving (Show, Eq)
data B = B String deriving (Show, Eq)
f :: (a->b) -> Either String a -> Either String b
f g (Right a) = (Right $ g a)
f g (Left  s) = (Left s)
-- f g (s) = (s) -- doesn't work
a2b (A s) = (B s)
t1 = f a2b (Left "x")
t2 = f a2b (Right (A "y"))
]]
The second case for 'f' throws a type error when the constructor 'Left' is 
omitted, because the type of 's' is fixed to be Either String A when the 
required result (in this case, because of a2b) is Either String B.

#g

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread Simon Peyton-Jones
| From: John Meacham
| would it be possible to provide an Ord instance for (IORef a)? For
| things like loop detection, one may need to make many IORef
comparasions
| and being able to use an efficient set would be a really big win.
| 
| Since IORefs are created in the IO monad, the actual order can be
| arbitrary without breaking referential transparency (as long as it
| doesn't change over the lifetime of the IORef.)

I think that'd be entirely reasonable.  Two runs of the same program
might give observably different behaviour wrt Ord, but that's ok because
the refs are allocates in the monad, as you say.

There is an efficiency cost though.  Each IORef would need to have an
extra field, to record its allocation ID.  (Address is not enough -- the
garbage collector can mangle them.)   

My own view is that this is fine -- IORefs shouldn't be in your inner
loop, so an extra word in each is no big deal.   Unless there are views
to the contrary, I'd be happy to see this in GHC.

Simon
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread Tom Pledger
John Meacham wrote:
would it be possible to provide an Ord instance for (IORef a)? For
things like loop detection, one may need to make many IORef comparasions
and being able to use an efficient set would be a really big win.
Since IORefs are created in the IO monad, the actual order can be
arbitrary without breaking referential transparency (as long as it
doesn't change over the lifetime of the IORef.)
   John
Someone posted an 'inside out' solution to this a while ago, but I'm 
having trouble finding it in the mail archives.

It was along these lines:
   type CollectionOfIoRef = Int
   newtype IoRef a = IoRef (IORef (a, Array CollectionOfIoRef Bool))
You use this wrapper, IoRef, instead of IORef. To insert a reference 
into a collection, you add the *collection* to the IoRef's hidden set.

Regards,
Tom
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread Simon Marlow
On 22 June 2004 10:38, Simon Peyton-Jones wrote:

>> From: John Meacham
>> would it be possible to provide an Ord instance for (IORef a)? For
>> things like loop detection, one may need to make many IORef
>> comparasions and being able to use an efficient set would be a
>> really big win. 
>> 
>> Since IORefs are created in the IO monad, the actual order can be
>> arbitrary without breaking referential transparency (as long as it
>> doesn't change over the lifetime of the IORef.)
> 
> I think that'd be entirely reasonable.  Two runs of the same program
> might give observably different behaviour wrt Ord, but that's ok
> because the refs are allocates in the monad, as you say.
> 
> There is an efficiency cost though.  Each IORef would need to have an
> extra field, to record its allocation ID.  (Address is not enough --
> the garbage collector can mangle them.)
> 
> My own view is that this is fine -- IORefs shouldn't be in your inner
> loop, so an extra word in each is no big deal.   Unless there are
> views to the contrary, I'd be happy to see this in GHC.

I'm torn.  If it were free, it would be a no-brainer.  But I know of
several cases where IORefs are performance-critical (or at least
performance-important).  We should implement & measure.

Cheers,
Simon
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread MR K P SCHUPKE
>If I have a polymorphic algebraic type (T a) with several type

data MyType a = A a | B String | C Int

So how do you expect to get the contents of B and C outm 
when they are differenf Types - surely you mean:

data MyType a = A a | B MyStrings


Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Tomasz Zielonka
On Mon, Jun 21, 2004 at 06:03:21PM +0100, Graham Klyne wrote:
> If I have a polymorphic algebraic type (T a) with several type 
> constructors, only one of which actually references the type parameter, is 
> there any way to express type conversion for the type-parameter-independent 
> constructors without actually mentioning all the constructors?

One way to do this would be to use record update syntax, but you would
have to have the same field in all type-parameter-independent
constructors.

  data E a b
  = L1 { r :: a }
  | L2 { r :: a }
  | L3 { r :: a }
  | L4 { r :: a }
  | R b
  deriving Show

  f g (R a) = R (g a)
  f _ other = other { r = r other }

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread MR K P SCHUPKE
>data E a b
>  = L1 { r :: a }
> | L2 { r :: a }
>  | L3 { r :: a }
>  | L4 { r :: a }
>  | R b
>  deriving Show


How is this different from:

data E a b = L1 a | L2 a | R b

f g (R a) = R (g a)
f _ other = other

Isn't this more or less what was in the original...

The problem is the type:

f :: (a->b) -> Either String a -> Either String b

this line: f _ other = other

says: Either String a == Either String b -- which it doesn't


Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Adrian Hey
I think this was the topic of my very first post to Haskell
mailing list, many years ago..

 http://www.dcs.gla.ac.uk/mail-www/haskell/msg00452.html

I think the answer is no. Apparently this is feature
(I still think it's a bug though:-)

Regards
--
Adrian Hey

On Monday 21 Jun 2004 6:03 pm, Graham Klyne wrote:
> If I have a polymorphic algebraic type (T a) with several type
> constructors, only one of which actually references the type parameter, is
> there any way to express type conversion for the type-parameter-independent
> constructors without actually mentioning all the constructors?
>
> Here's a simple example based on Either:
>
> [[
> data A = A String deriving (Show, Eq)
> data B = B String deriving (Show, Eq)
>
> f :: (a->b) -> Either String a -> Either String b
> f g (Right a) = (Right $ g a)
> f g (Left  s) = (Left s)
> -- f g (s) = (s) -- doesn't work
>
> a2b (A s) = (B s)
>
> t1 = f a2b (Left "x")
> t2 = f a2b (Right (A "y"))
> ]]
>
> The second case for 'f' throws a type error when the constructor 'Left' is
> omitted, because the type of 's' is fixed to be Either String A when the
> required result (in this case, because of a2b) is Either String B.
>
> #g
>
>
> 
> Graham Klyne
> For email:
> http://www.ninebynine.org/#Contact
>
> ___
> Haskell-Cafe mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread MR K P SCHUPKE
>(I still think it's a bug though:-)

It is definitely not a bug... you cannot assert that the types:

Either String a
Either String b

are both equal ant not equal at the same time. You either mean:

f :: (a->a) -> Either String a -> Either String a

Or you mean

f :: (a->b) -> Either String a -> Either String b

actually the second form a and b can be the same but they cannot
be unified inside the closure.


One way of doing this is to group all the string types on one side:

so instead of:

data A a = A a | B String | C String | D String

you do:

data A a = A a | B Strings
data Strings = S1 String | S2 String | S3 String

you can then write:

 f :: (a->b) -> A a -> A b
 f g (A a) = (A $ g a)
 f g (B a) = (B a)

and use (S1 . B), (S2 . B), (S3 . B) to access each string.

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Tomasz Zielonka
On Tue, Jun 22, 2004 at 01:29:02PM +0100, MR K P SCHUPKE wrote:
> >data E a b
> >  = L1 { r :: a }
> > | L2 { r :: a }
> >  | L3 { r :: a }
> >  | L4 { r :: a }
> >  | R b
> >  deriving Show
> 
> How is this different from:
> 
> data E a b = L1 a | L2 a | R b
> 
> f g (R a) = R (g a)
> f _ other = other

> Isn't this more or less what was in the original...
 
Nope. My f has type
 (b -> b1) -> E a b -> E a b1

> The problem is the type:
> 
> f :: (a->b) -> Either String a -> Either String b
> 
> this line: f _ other = other
> 
> says: Either String a == Either String b -- which it doesn't

Record update avoids this because of the way it is translated.
Basically, the result of record update is a reconstructed record, but
constructors not containing updated fields are not built/copied, so they
don't constrain the resulting type. See Haskell 98 Report for details.

Anyway, I doubt the OP can benefit from it.

> Keean.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread Fergus Henderson
On 22-Jun-2004, Simon Peyton-Jones <[EMAIL PROTECTED]> wrote:
> My own view is that this is fine -- IORefs shouldn't be in your inner
> loop, so an extra word in each is no big deal.

I find that attitude rather extraordinary and I do not agree.

For some applications, IORefs may well be a major contributor to
memory usage, and increasing the amount of space that they take up may
significantly decrease locality and hence performance.

-- 
Fergus J. Henderson |  "I have always known that the pursuit
Galois Connections, Inc.|  of excellence is a lethal habit"
Phone: +1 503 626 6616  | -- the last words of T. S. Garp.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread Jan-Willem Maessen - Sun Labs East
Simon Peyton-Jones wrote:
...
There is an efficiency cost though.  Each IORef would need to have an
extra field, to record its allocation ID.  (Address is not enough -- the
garbage collector can mangle them.)   

My own view is that this is fine -- IORefs shouldn't be in your inner
loop, so an extra word in each is no big deal.   Unless there are views
to the contrary, I'd be happy to see this in GHC.
It's worth noting at this point that the Java world has developed a 
nice, big bag of tricks for language implementors to use to solve 
exactly this problem.  Somehow, they make it work even for the stuff 
which *is* in the inner loop. :-)

-Jan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Tomasz Zielonka
On Tue, Jun 22, 2004 at 02:52:21PM +0200, Tomasz Zielonka wrote:
> 
> Record update avoids this because of the way it is translated.
> Basically, the result of record update is a reconstructed record, but
> constructors not containing updated fields are not built/copied, so they
> don't constrain the resulting type. See Haskell 98 Report for details.

Sorry, I confused some facts. It suffices that result of labeled record
update is a newly constructed record (or bottom).

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] how to get started: a text application

2004-06-22 Thread Max Ischenko
Hi all,
I'm going to try to implement a version of Markdown tool[1] in Haskell. 
The application is rather simple: take a text file with some (simple) 
mark-up embedded in it and turn it into another text file, this time 
with XHTML markup.

I need some guidelines on how to get started. I'll have to struggle with 
both the language itself (as I am a newcomer) plus with libraries that I 
may need.

If I to do this in some convenient language, like Python, I'd use a 
lexer to parse the input, a state machine to build some internal 
representation and some serializer to write this into XHTML.

Which approaches could you suggest for that kind of application in 
Haskell? I'd especially glad to hear about some "idiomatic" or "native" 
ways to solve the problem.

I've made a quick search and found tools like Parsec, HaXML, Happy and 
WASH/HTML. Not sure which ones I'll need.

[1] - http://daringfireball.net/projects/markdown/
TIA,
max.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Adrian Hey
On Tuesday 22 Jun 2004 1:50 pm, MR K P SCHUPKE wrote:
> >(I still think it's a bug though:-)
>
> It is definitely not a bug... you cannot assert that the types:
>
> Either String a
> Either String b
>
> are both equal ant not equal at the same time.

I wasn't.

> You either mean:
>
> f :: (a->a) -> Either String a -> Either String a
>
> Or you mean
>
> f :: (a->b) -> Either String a -> Either String b

My gripe with the current Haskell (and every other statically typed
FPL I've used) treatment of this is that if you view a type as an
abstract description of a set of values then it seems that these
sets are not permitted to intersect. I.E In any given context the
same value can only be a element of one and only one set, even
if the value is partially known as a result of pattern matching.

I don't know if this is the correct interpretation in a type
theoretical sense (I'm not a type theorist), but I would say
that this is the most intuitive interpretation from Joe programmers
perspective, and so should be allowed unless there are persuasive
technical arguments why this is impossible. There might well be, but
I was left quite unconvinced that this is the case last time I mentioned
this, and my opinion hasn't changed since.

It's especially strange I think, because Haskell doesn't seem to apply
the same rules to values which are partially (or completely) known as a
result of pattern matching as it does to values which are partially
(or completely) known as a result of let binding.

for example..

 let e=[] in e:e

is perfectly legal, whereas..

 f :: [Int] -> [Bool]
 f (i:is) = even i : f is
 f [EMAIL PROTECTED]   = e

will give a type error, despite the fact that e's value is known
to be [] in each case.

Regards
--
Adrian Hey
 














  






___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread MR K P SCHUPKE
>to be [] in each case.

ahh but in this example:

 f :: [Int] -> [Bool]
 f (i:is) = even i : f is
 f [EMAIL PROTECTED]   = e

e is an empty list of Ints not an empty list of Bools!

you mean:

f :: [Int] -> [Bool]
 f (i:is) = even i : f is
 f _ = []


Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Adrian Hey
On Tuesday 22 Jun 2004 6:20 pm, MR K P SCHUPKE wrote:
> ahh but in this example:
>
>  f :: [Int] -> [Bool]
>  f (i:is) = even i : f is
>  f [EMAIL PROTECTED]   = e
>
> e is an empty list of Ints not an empty list of Bools!

If the difference is significant (I don't believe it is)
then consistency demands that this expression should
give a type error..

 let e=[] in (length e : e, null e : e)

It doesn't, so clearly e can be both an empty list of
Ints and an empty list of Bools :-)

Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Duncan Coutts
On Tue, 2004-06-22 at 20:52, Adrian Hey wrote:
> On Tuesday 22 Jun 2004 6:20 pm, MR K P SCHUPKE wrote:
> > ahh but in this example:
> >
> >  f :: [Int] -> [Bool]
> >  f (i:is) = even i : f is
> >  f [EMAIL PROTECTED]   = e
> >
> > e is an empty list of Ints not an empty list of Bools!
> 
> If the difference is significant (I don't believe it is)
> then consistency demands that this expression should
> give a type error..
> 
>  let e=[] in (length e : e, null e : e)
> 
> It doesn't, so clearly e can be both an empty list of
> Ints and an empty list of Bools :-)

I think the point is that [] (or e in your example) has type
forall a.[a]
where as in the original example e was bound to an argument with the
type [Int], so e could not be used where something of type [Bool] was
required. On the other hand
[] :: forall a.[a]
could be used in either context.

Duncan

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] How to use QSem?

2004-06-22 Thread S. Alexander Jacobson
The GHC documentation on QSem is very sparse.  I
would like to give a thread exclusive access to a
resource.

My *guess* based on the documentation is that I
can create an exclusive lock using:

   logSem <- newQSem 1

And then any thread that wants to lock the
resource uses:

   withLogSem x = do waitQSem logSem; y <- x; signalQSem logSem; return y

as follows:

   withLogSem $ rotate curLogPos

Am I misunderstanding QSem?

-Alex-



_
S. Alexander Jacobson  mailto:[EMAIL PROTECTED]
tel:917-770-6565   http://alexjacobson.com
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Polymorphic algebraic type constructors

2004-06-22 Thread Adrian Hey
On Tuesday 22 Jun 2004 9:09 pm, Duncan Coutts wrote:

> I think the point is that [] (or e in your example) has type
> forall a.[a]
> where as in the original example e was bound to an argument with the
> type [Int], so e could not be used where something of type [Bool] was
> required. On the other hand
> [] :: forall a.[a]
> could be used in either context.

Whilst I understand perfectly well why this inconsistency arises, I don't
agree that this is the point :-) I think the point is this inconsistency
should not arise. I think that function definitions of form..

 f v@ = 

should be type checked as if they had been written..

 f  = let v =  -- assuming  is syntactically correct expr
   in 

Same applies to case expressions to.

Of course one would need to be careful if  contained '_'.

However, cases like this..

 f (i:is) = even i : f is
 f e  = e

are a bit more ambiguous. Although we all know e must be [], that
isn't immediately obvious. So I guess the answer depends on whether
type checking should be done before or after pattern match compilation.

Regards
--
Adrian Hey

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread ajb
G'day all.

Quoting Fergus Henderson <[EMAIL PROTECTED]>:

> I find that attitude rather extraordinary and I do not agree.

Me too.  I've written more than one Haskell program where hash consing
is part of an "inner loop".  For this applciation the data structures
weren't that big, but I can easily think of a few applications for which
it would be.

Cheers,
Andrew Bromage
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ord (IORef a)?

2004-06-22 Thread John Meacham
On Tue, Jun 22, 2004 at 11:54:17AM +0100, Simon Marlow wrote:
> I'm torn.  If it were free, it would be a no-brainer.  But I know of
> several cases where IORefs are performance-critical (or at least
> performance-important).  We should implement & measure.

Yeah, i forgot about the GC moving things around. actually, if the GC
could be coaxed to move things around, but never change the relative
order of IORefs (like a compacting collector), then the address could
still be used for Ord and Eq.

how is Eq implemented such that the GC doesn't move one side after you
read the address of the other?

Actually, the problem is exasperated by the fact we still havn't come up
with a good standard class to encapsulate references and the monads they
work in. If this were solved, then it would be much easier to use a
wrapper which includes an identity and would be a good addition to the
libraries. 
John

-- 
John Meacham - ârepetae.netâjohnâ 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe