[Haskell-cafe] Re: [Haskell] Top Level <-
Dan Doel
dan.doel at gmail.com
Thu Aug 28 13:17:29 EDT 2008
On Thursday 28 August 2008 12:26:27 pm Adrian Hey wrote:
> As I've pointed out several times already you can find simple examples
> in the standard haskell libs. So far nobody has accepted my challenge to
> re-implement any of these "competantly" (I.E. avoiding the use of global
> variables).
>
> Why don't you try it with Data.Unique and find out :-)
Here's a first pass:
-- snip --
{-# LANGUAGE Rank2Types, GeneralizedNewtypeDeriving #-}
module Unique where
import Control.Monad.Reader
import Control.Monad.Trans
import Control.Concurrent.MVar
-- Give Uniques a phantom region parameter, so that you can't accidentally
-- compare Uniques from two different uniqueness sources.
newtype Unique r = Unique Integer deriving Eq
newtype U r a = U { unU :: ReaderT (MVar Integer) IO a }
deriving (Functor, Monad, MonadIO)
-- Higher rank type for region consistency
runU :: (forall r. U r a) -> IO a
runU m = newMVar 0 >>= runReaderT (unU m)
newUnique :: U r (Unique r)
newUnique = U (do source <- ask
val <- lift $ takeMVar source
let next = val + 1
lift $ putMVar source next
return $ Unique next)
-- hashUnique omitted
-- snip --
It's possible that multiple unique sources can exist in a program with this
implementation, but because of the region parameter, the fact that a Unique
may not be "globally" unique shouldn't be a problem. If your whole program
needs arbitrary access to unique values, then I suppose something like:
main = runU realMain
realMain :: U r ()
realMain = ...
is in order.
Insert standard complaints about this implementation requiring liftIO all over
the place if you actually want to do other I/O stuff inside the U monad.
You could also make a version that extracts to STM, or even a pure version if
you don't need unique values across multiple threads.
-- Dan
More information about the Haskell-Cafe
mailing list