Hi,

Sorry to bring up this thread from so long ago.

On Wed, Mar 01, 2006 at 11:53:42AM +0000, Simon Marlow wrote:
> Ashley Yakeley wrote:
> >Simon Marlow wrote:
> >>Simon & I have discussed doing some form of thread-local state, which 
> >>covers many uses of implicit 
> >>parameters and is much preferable IMO. Thread-local state doesn't change 
> >>your types, and it 
> >>doesn't require passing any extra parameters at runtime.  It works 
> >>perfectly well for the OS 
> >>example you give, for example.
> >Interesting. What would that look like in code?
> 
> No concrete plans yet.  There have been proposals for thread-local variables 
> in the past on this 
> list and haskell-cafe, and other languages have similar features (eg. 
> Scheme's support for dynamic 
> scoping).  Doing something along these lines is likely to be quite 
> straightforward to implement, 
> won't require any changes to the type system, and gives you a useful form of 
> implicit parameters 
> without any of the drawbacks.
> 
> The main difference from implicit parameters would be that thread-local 
> variables would be 
> restricted to the IO monad.

I think support for thread-local variables is something which is
urgently needed. It's very frustrating that using concurrency in
Haskell is so easy and nice, yet when it comes to IORefs there is no
way to get thread-local behavior. Furthermore, that one can make
certain things thread-local (e.g. with withArgs, withProgName) makes
the solution seem close at hand (although I can appreciate that it may
not be). Yet isn't it just a matter of making a Map with existentially
quantified values part of the state of each thread, just as the
program name and arguments are also part of that state?

----------------------------------------------------------------
import qualified Data.Map as M 
import Data.Maybe 
import Data.Unique
import Data.IORef 
import Data.Typeable 
 
-- only these 2 must be implemented:
withParams :: ParamsMap -> IO () -> IO () 
getParams :: IO ParamsMap 
--

type ParamsMap = M.Map Unique Value

data Value = forall a . (Typeable a) => V a 
 
type IOParam a = IORef (Unique, a) 
 
newIOParam :: Typeable a => a -> IO (IOParam a) 
newIOParam def = do 
    k <- newUnique 
    newIORef (k,def) 
 
withIOParam :: Typeable a => IOParam a -> a -> IO () -> IO () 
withIOParam p value act = do 
    (k,def) <- readIORef p 
    m <- getParams 
    withParams (M.insert k (V value) m) act 
 
getIOParam :: Typeable a => IOParam a -> IO a 
getIOParam p = do 
    (k,def) <- readIORef p 
    m <- getParams 
    return $ fromMaybe def (M.lookup k m >>= (\ (V x) -> cast x)) 
----------------------------------------------------------------

Frederik

P.S. I sent a message about this a while back, when I was trying to
implement my own version using ThreadId (not really a good approach).

-- 
http://ofb.net/~frederik/
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to