[Haskell-cafe] Suggestions for simulating Object ID
Thomas Schilling
nominolo at googlemail.com
Wed Jul 1 17:09:07 EDT 2009
This is implemented in Data.Supply
(http://hackage.haskell.org/package/value-supply). The difference is:
Data.Unique is *globally* unique, while Data.Supply is only locally
unique. I ran into problems with this when writing tests.
2009/6/30 Ryan Ingram <ryani.spam at gmail.com>:
> On Tue, Jun 30, 2009 at 9:16 AM, Felipe Lessa<felipe.lessa at gmail.com> wrote:
>> On Tue, Jun 30, 2009 at 07:57:07PM +0530, Hemanth Kapila wrote:
>>> Can't we come up with something like this staying within the
>>> limits of purity?
>>
>> No, because that would break referential transparency :(. I.e.,
>> it would be possible to distinguish things that should be
>> "equal", such as '3' from '1+2'.
>
> This isn't entirely true; you can do something like this:
>
>> newtype Unique = U Integer deriving (Eq)
>> newtype UniqueM a = UniqueM (State Integer a) deriving Monad
>> runUniqueM (UniqueM a) = evalState a 0
>
>> newUnique = UniqueM $ do
>> u <- get
>> put $! (u+1)
>> return (U u)
>
> Also, if you are willing to go inside of IO/ST for some bits of your
> code, you can use some tricks with unsafeInterleaveIO/ST to create
> data structures with unique ids that only get created if they are
> used; this allows creating infinite data structures and still keeping
> object ID. The returned data structure is still pure if the "U"
> constructor is hidden; all we can do is compare uniques for equality.
> You can relax this slightly by adding an Ord derivation; this
> technically allows you to observe creation order for the uniques which
> is wrong, but it's quite useful to be able to use Uniques as map keys.
>
>> data Tree a = Tree a (Tree a) (Tree a)
>> infTree :: IO (Tree Unique)
>> infTree = do
>> r <- newIORef 0
>> mkTree r
>> mkTree :: IORef Integer -> IO (Tree Unique)
>> mkTree r = unsafeInterleaveIO $ do
>> v <- readIORef r
>> writeIORef r $! (v+1)
>> l <- mkTree r
>> r <- mkTree r
>> return (Tree (U v) l r)
>
> I believe GHC uses this technique internally.
>
> -- ryan
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
--
Push the envelope. Watch it bend.
More information about the Haskell-Cafe
mailing list