[Haskell-cafe] I love purity, but it's killing me.
Matthew Naylor
mfn-haskell-cafe at cs.york.ac.uk
Sun Feb 10 13:52:37 EST 2008
Hi Tom,
> So is the general strategy with observable sharing to use
> unsafePerformIO with Data.Unique to label expressions at
> construction?
something like that, yes. Basically, you just need:
{-# NOINLINE ref #-}
ref x = unsafePerformIO (newIORef x)
and you can write expressions like
ref False == ref False
and
let x = ref False in x == x
However, while referential equality is enough for sharing detection, I
*suspect* it's simpler to use the fact that refs are IORefs and you
can read and write them (in the IO monad). So a very simple Lava
might look like
module Lava (Bit,Netlist,low,high,nand2,netlist) where
import Data.IORef
import System.IO.Unsafe
{-# NOINLINE ref #-}
ref x = unsafePerformIO (newIORef x)
type Ref = IORef (Maybe Int)
data Bit = Gate String Ref [Bit]
type Netlist = [(String, Int, [Int])]
-- gate, output, inputs
low = Gate "low" (ref Nothing) []
high = Gate "high" (ref Nothing) []
nand2 (a, b) = Gate "nand2" (ref Nothing) [a, b]
netlist :: Bit -> IO Netlist
netlist x = do i <- newIORef (0 :: Int) ; f i x
where
f i (Gate str r xs) =
do val <- readIORef r
num <- readIORef i
case val of
Nothing -> do writeIORef r (Just num)
writeIORef i (num+1)
rest <- mapM (f i) xs
let is = map ((\(g,o,is) -> o) . head) rest
return ((str,num,is):concat rest)
Just j -> return [("indirection",j,[])] -- explicit sharing!
Indirections can be filtered out at the end, they don't actually give
the netlist any information.
> Of course, now that you have me reading up on Yhc.Core, option #5 is
> looking considerably more fun.
Yeah, I think Yhc.Core is pretty nifty too. Thank Neil!
Matt.
More information about the Haskell-Cafe
mailing list