
Dan Doel wrote:
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.
Well that wouldn't be my main complaint :-) Thanks for taking the time to do this Dan. I think the safety requirement has been met, but I think it fails on the improved API. The main complaint would be what I see as loss of modularity, in that somehow what should be a small irrelevant detail of the implementation of some obscure module somewhere has propogated it's way all the way upto main. This is something it seems to have in common with all other attempts I've seen to solve the "global variable" problem without actually using a..you know what :-) It doesn't matter whether it's explicit state handle args, withWhateverDo wrappers, novel monads or what. They all have this effect. To me this seems completely at odds with what I thought was generally accepted wisdom of how to write good maintainable, modular software. Namely hiding as much implemention detail possible and keeping APIs as simple and stable as they can be. I don't know if I'm alone in that view nowadays. I'm also not sure I understand why so many people seem to feel that stateful effects must be "accounted for" somehow in the args and/or types of the effecting function. Like if I had.. getThing :: IO Thing ..as an FFI binding, nobody would give it a moments thought. They'd see it from it's type that it had some mysterious world state dependent/effecting behaviour, but would be quite happy to just accept that the didn't really need to worry about all that magic... instead they'd accept that it "just works". Why then, if I want to implement precisely the same thing in Haskell (using a "global variable") does it suddenly become so important for this stateful magic to be accounted for? Like the presence of that "global variable" must be made so very painfully apparent in main (and everywhere else on the dependency path too I guess). In short, I just don't get it :-) Purists aren't going to like it, but I think folk *will* be using "real" global variables in I/O libs for the forseeable future. Seems a shame that they'll have to do this with unsafePerformIO hack though :-( Regards -- Adrian Hey