Difference between revisions of "Thread-local storage"

From HaskellWiki
Jump to navigation Jump to search
Line 7: Line 7:
 
However, if many people are going to use thread-local storage then it would be best to have a standard implementation, for library compatibility.
 
However, if many people are going to use thread-local storage then it would be best to have a standard implementation, for library compatibility.
   
Robert Dockins has put forward a proposal[http://article.gmane.org/gmane.comp.lang.haskell.cafe/11010].
+
Robert Dockins has put forward a proposal[http://article.gmane.org/gmane.comp.lang.haskell.cafe/11010] which deals specially with initialization issues.
   
 
Frederik Eaton posted an example API to the Haskell mailing list [http://www.haskell.org/pipermail/haskell/2006-July/018300.html]. It depends on two new functions 'withParams' and 'getParams'.
 
Frederik Eaton posted an example API to the Haskell mailing list [http://www.haskell.org/pipermail/haskell/2006-July/018300.html]. It depends on two new functions 'withParams' and 'getParams'.
Line 107: Line 107:
 
freshly-initialised set. Sometimes you want one, sometimes the other,
 
freshly-initialised set. Sometimes you want one, sometimes the other,
 
alas.
 
alas.
  +
</pre>
  +
  +
Frederik's response is:
  +
  +
<pre>
  +
The main difference between my and your proposals, as I see it, is
  +
that your proposal is based on "keys" which can be used for other
  +
things.
  +
  +
I think that leads to an interface which is less natural. In my
  +
proposal, the IOParam type is quite similar to an IORef - it has a
  +
user-specified initial state, and the internal implementation is
  +
hidden from the user - yours differs in both of these aspects.
 
</pre>
 
</pre>

Revision as of 12:50, 8 August 2006

No facility for thread-local storage exists yet in any Haskell compiler.

If we override 'fork', then we can implement a thread-local storage facility using 'ThreadId'. The following implementation uses one variable per type:

http://www.cs.helsinki.fi/u/ekarttun/haskell/TLS/TLSVar.hs

However, if many people are going to use thread-local storage then it would be best to have a standard implementation, for library compatibility.

Robert Dockins has put forward a proposal[1] which deals specially with initialization issues.

Frederik Eaton posted an example API to the Haskell mailing list [2]. It depends on two new functions 'withParams' and 'getParams'.

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))

Einar Karttunen expressed concern that extensive use of thread-local storage might cause problems with libraries that run actions in thread pools. He suggested that it would be better to define monads which contain all of the contextual state [3]. Frederik Eaton pointed out that in many reasonable designs, an approach which carries state in custom monads requires code which is quadratic in the number of layers of context [4]. Einar Karttunen also suggested a function which would solve the thread pool problem:

-- | Tie all TLS references in the IO action to the current
-- environment rather than the environment it will actually
-- be executed.
tieToCurrentTLS :: IO a -> IO (IO a)

Simon Marlow and Simon Peyton-Jones have both expressed that they support some form of thread-local storage.[5][6]

Simon Peyton-Jones gave another proposal:

* The thoughts that Simon and were considering about thread-local state
are quite close to Robert's proposal.  For myself, I am somewhat
persuaded that some form of implicitly-passed state in the IO monad
(without explicit parameters) is useful.   Examples I often think of are
        - Allocating unique identifiers
        - Making random numbers
        - Where stdin and stdout should go
In all of these cases, a form of dynamic binding is just what we want:
send stdout to the current thread's stdout, use the current thread's
random number seed, etc.

* There's no need to connect it to *state*.  The key top-level thing you
need is to allocate what Adrian Hey calls a "thing with identity".
http://www.haskell.org/hawiki/GlobalMutableState.
I'll call it a key.  For example, rather than a 'threadlocal'
declaration, one might just have:

        newkey foo :: Key Int

where 'newkey' the keyword; this declares a new key with type (Key Int),
distinct from all other keys.

Now you can imagine that the IO monad could provide operations
        withBinding :: Key a -> a -> IO b -> IO b
        lookupBinding :: Key a -> IO a

very much like the dynamic-binding primitives that have popped up on
this thread.

* If you want *state*, you can have a (Key (IORef Int)).  Now you look
up the binding to get an IORef (or MVar, whatever you like) and you can
mutate that at will.  So this separates a thread-local *environment*
from thread-local *state*.

* Keys may be useful for purposes other than withBinding and
thread-local state.  One would also want to dynamically create new keys:
        newKey :: IO (Key a)

* I agree with Robert that a key issue is initialisation.  Maybe it
should be possible to associate an initialiser with a key.  I have not
thought this out.

*  A key issue is this: when forking a thread, does the new thread
inherit the current thread's bindings, or does it get a
freshly-initialised set.  Sometimes you want one, sometimes the other,
alas.

Frederik's response is:

The main difference between my and your proposals, as I see it, is 
that your proposal is based on "keys" which can be used for other 
things. 
 
I think that leads to an interface which is less natural. In my 
proposal, the IOParam type is quite similar to an IORef - it has a 
user-specified initial state, and the internal implementation is 
hidden from the user - yours differs in both of these aspects.