[Haskell-cafe] Hiding side effects in a data structure

Simon Peyton-Jones simonpj at microsoft.com
Fri Oct 19 11:09:47 EDT 2007


Good idea.  GHC uses it
        http://darcs.haskell.org/ghc/compiler/basicTypes/UniqSupply.lhs

Lennart Augustsson and friends invented it
@techreport{Augustsson92a,
   author = {L Augustsson and M Rittri and D Synek},
   title = {Splitting infinite sets of unique names by hidden state changes},
   type = {Report 67, Programming Methodology Group, Chalmers University},
   month = may,
   year = {1992},
   keywords = {name supply, monad plumbing, gensym, unique names}
}

Simon

| -----Original Message-----
| From: haskell-cafe-bounces at haskell.org [mailto:haskell-cafe-
| bounces at haskell.org] On Behalf Of C Rodrigues
| Sent: 19 October 2007 15:16
| To: haskell-cafe at haskell.org
| Subject: [Haskell-cafe] Hiding side effects in a data structure
|
|
| While thinking about how to generate unique integer IDs on demand without
| using a state variable, I came up with an interesting design pattern.  It's a
| way of doing side-effecting computation outside IO.  Referential transparency
| is preserved by making the side effects spatial rather than temporal: by
| hiding side effects behind lazy thunks in a data structure, they can be
| disguised as the output of a single, apparently nondeterministic IO function
| used to data structure.  This lets pure code use nondeterministic computation
| without the monadic plumbing required to maintain state.
|
| The getContents function works this way, but I came up with a more
| interesting example.  The code below is a source of unique integer IDs that
| is modeled after the RandomGen class.  It uses unsafeInterleaveIO under the
| hood, preserving referential transparency but not determinism.
|
| It seems to work.  However, I'm not entirely sure how safe my use of
| unsafeInterleaveIO is.  In particular, could the two branches of the tree get
| CSE'd?  I'm also curious what people think about the general design pattern.
|
| module Unique where
|
| import Control.Monad(liftM)
| import Data.IORef
| import System.IO.Unsafe
|
| -- The goal is to produce an infinite tree of integers where each node in the
| -- tree has a unique value.
| type Unique = Int
| data Supply = Supply Unique Supply Supply
|
| -- The tree can be used in a stateful manner as a source of unique integers.
| getUnique :: Supply -> (Unique, Supply)
| getUnique (Supply u s1 _) = (u, s1)
|
| -- The tree can also be split into independent sources of unique integers.
| split :: Supply -> (Supply, Supply)
| split (Supply _ s1 s2) = (s1, s2)
|
| -- The catch is, the tree will probably be visited very sparsely, with most
| of
| -- it being skipped.  Assigning every node its own integer is very bad,
| because
| -- that will waste most of the 2^32 available integers very quickly.  In
| fact,
| -- it can get used up in just 32 calls to getUnique.
| --
| -- Instead, we'll create a tree where integers magically appear only in
| places
| -- where they are actually used.
|
| -- First, we need an IO-bound supply of integers.
| newtype IOSupply = IOSupply (IORef Unique)
|
| newIOSupply :: IO IOSupply
| newIOSupply = liftM IOSupply $ newIORef 0
|
| getUniqueIO :: IOSupply -> IO Unique
| getUniqueIO (IOSupply s) = do
|     u <- readIORef s
|     writeIORef s $ u+1
|     return u
|
| -- Now we'll use the IO-bound supply to create a tree having the desired
| -- properties.
| {-# NOINLINE getPureSupply #-}
| getPureSupply :: IOSupply -> IO Supply
| getPureSupply s = do
|     s1 <- unsafeInterleaveIO $ getPureSupply s
|     s2 <- unsafeInterleaveIO $ getPureSupply s
|     n  <- unsafeInterleaveIO $ getUniqueIO s
|     return $ Supply n s1 s2
|
| _________________________________________________________________
| Climb to the top of the charts!  Play Star Shuffle:  the word scramble
| challenge with star power.
| http://club.live.com/star_shuffle.aspx?icid=starshuffle_wlmailtextlink_oct___
| ____________________________________________
| Haskell-Cafe mailing list
| Haskell-Cafe at haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe


More information about the Haskell-Cafe mailing list