Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Einar Karttunen
On 31.07 03:18, Frederik Eaton wrote:
 I don't think it's necessarily such a big deal. Presumably the library
 with the worker threads will have to be invoked somewhere. One should
 just make sure that it is invoked in the appropriate environment, for
 instance with the database connection already properly initialized.
 
 (*) One might even want to change the environment a little within each
 thread, for instance so that errors get logged to a thread-specific
 log file.

So we have the following:
1) the library is initialized and spawns worker thread Tw
2) application initializes the database connection and it
   is associated with the current thread Tc and all the children
   it will have (unless changed)
3) the application calls the library in Tc passing an IO action
   to it. The IO action refers to the TLS thinking it is in
   Tc where it is valid.
4) the library runs the callback code in Tw where the TLS state is
   invalid. This is even worse than a global variable in this case.

Of course one can argue that the application should first initialize
the database handle. But if the app uses worker threads (spawned
before library initialization) then things will break if a library
uses TLS and callbacks and they end up running in threads created
before the library initialization.

- Einar Karttunen

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Einar Karttunen
On 31.07 14:03, Thomas Conway wrote:
 This is why I believe transaction-local variables are a more useful concept.
 You are garanteed that there is only one thread accessing them, and
 they behave just like ordinary TVars except that each transaction has
 its own copy.

This seems like it could be useful. E.g. marking graph nodes while
traversing them.

 The argument to newLVar is an initial value that is used at the start
 of each transaction.  Note that this means that the value in an LVar
 does not persist between transaction. I agree that this limits their
 use, but simplifies them immensely, and doesn't stand in the way their
 being useful for solving a bunch of problems.

I think that them reverting to the initial value is more useful
than persisting behavior.

- Einar Karttunen
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-31 Thread Frederik Eaton
On Mon, Jul 31, 2006 at 03:09:59PM +0300, Einar Karttunen wrote:
 On 31.07 03:18, Frederik Eaton wrote:
  I don't think it's necessarily such a big deal. Presumably the library
  with the worker threads will have to be invoked somewhere. One should
  just make sure that it is invoked in the appropriate environment, for
  instance with the database connection already properly initialized.
  
  (*) One might even want to change the environment a little within each
  thread, for instance so that errors get logged to a thread-specific
  log file.
 
 So we have the following:
 1) the library is initialized and spawns worker thread Tw
 2) application initializes the database connection and it
is associated with the current thread Tc and all the children
it will have (unless changed)
 3) the application calls the library in Tc passing an IO action
to it. The IO action refers to the TLS thinking it is in
Tc where it is valid.
 4) the library runs the callback code in Tw where the TLS state is
invalid. This is even worse than a global variable in this case.

If you have threads, and you have something which needs to be
different among different threads, then it is hard for me to see how
thread-local variables could be worse than global variables in any
case at all.

 Of course one can argue that the application should first initialize
 the database handle. But if the app uses worker threads (spawned
 before library initialization) then things will break if a library
 uses TLS and callbacks and they end up running in threads created
 before the library initialization.

OK, sure. In certain situations you have to keep track of whether a
function to which you pass an action might be sending it off to be run
in a different thread. We've been over this. Perhaps users should be
warned in the documentation - and in the documentation for exceptions
as well. I really don't see that as a problem that would sneak up on
people, since if you're passing an action to a function, rather than
executing it yourself, then in most cases it should be clear to
programmers that the action will run in a different context if not a
different thread altogether. And if you want to force the context to
be the same, you wrap the action in something restoring that context,
just like you would have to do with your state transformer monad
stack.

Another way to write buggy code is to have it so bloated with extra
syntax - e.g. with monad conversions, or extra function parameters, as
you propose - that it becomes impossible to read and understand.

Frederik

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


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Einar Karttunen
On 29.07 13:25, Frederik Eaton wrote:
 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?

Are thread local variables really a good idea in Haskell?

If variables are thread local how would this combinator work:

withTimeOut :: Int - IO a - IO a
withTimeOut tout op = mdo
  mv - newEmptyMVar
  wt - forkIO $ do try op = tryPutMVar mv  killThread kt
  kt - forkIO $ do threadDelay tout
e - tryPutMVar mv $ Left $ DynException $ toDyn 
TimeOutException
if e then killThread wt else return ()
  either throw return = takeMVar mv


Would it change the semantics of the action as it is run in a
different thread (this is a must if there are potentially blocking FFI
calls). Now if the action changes the thread local state then
it behaves differently. Do we really want that?

Usually one can just add a monad that wraps IO/STM and provides the
variables one needs. This has the good side of making scoping
explicit.

- Einar Karttunen
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Frederik Eaton
On Sun, Jul 30, 2006 at 12:35:42PM +0300, Einar Karttunen wrote:
 On 29.07 13:25, Frederik Eaton wrote:
  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?
 
 Are thread local variables really a good idea in Haskell?

Yes.

 If variables are thread local how would this combinator work:

Do read the code I posted. Please note I'm not suggesting that *all*
variables be thread local, I was proposing a special data-type for
that.

 withTimeOut :: Int - IO a - IO a
 withTimeOut tout op = mdo
   mv - newEmptyMVar
   wt - forkIO $ do try op = tryPutMVar mv  killThread kt
   kt - forkIO $ do threadDelay tout
 e - tryPutMVar mv $ Left $ DynException $ toDyn 
 TimeOutException
 if e then killThread wt else return ()
   either throw return = takeMVar mv
 
 
 Would it change the semantics of the action as it is run in a
 different thread (this is a must if there are potentially blocking FFI
 calls).

No, because the thread in which it runs inherits any thread-local
state from its parent.

 Now if the action changes the thread local state then
 it behaves differently. Do we really want that?

I'm not sure what you're suggesting. The API I proposed actually
doesn't let users discover when their actions are running in
sub-threads. (Can you write an example using that API?) However, even
if it did, I don't see a problem. Do you think that we should get rid
of 'myThreadId', for instance? I don't.

 Usually one can just add a monad that wraps IO/STM and provides the
 variables one needs. This has the good side of making scoping
 explicit.

That's easier said than done. Sometimes I take that route. But
sometimes I don't want 5 different monads wrapping each other, each
with its own 'lift' and 'catch' functions, making error messages
indecipherable and code difficult to read and debug. Do you propose
creating a special monad for file operations? For network operations? 
No? Then I don't see why I should have to make a special monad for
database operations. Or, if the answer was yes, then fine: obfuscate
your own code, but please don't ask me to do the same. Let's support
both ways of doing things, and we can be different.

Frederik

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


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Einar Karttunen
On 30.07 11:49, Frederik Eaton wrote:
 No, because the thread in which it runs inherits any thread-local
 state from its parent.


So we have different threads modifying the thread-local state?
If it is a copy then updates are not propagated.

What about a design with 10 worker threads taking requests
from a Chan (IO ()) and running them (this occurs in real code).
To get things right they should use the TLS-context relevant
to each IO () rather than the thread.
 
  Now if the action changes the thread local state then
  it behaves differently. Do we really want that?
 
 I'm not sure what you're suggesting. The API I proposed actually
 doesn't let users discover when their actions are running in
 sub-threads. (Can you write an example using that API?) However, even
 if it did, I don't see a problem. Do you think that we should get rid
 of 'myThreadId', for instance? I don't.

I do consider using myThreadId bad form for most purposes.
It is nice to have for debugging output - and occasionally
for sending other threads a handle for asynchronous exceptions,
but this can lead to problems when changing threading patterns.

Usually nice code does not care in which thread it is run.

 
  Usually one can just add a monad that wraps IO/STM and provides the
  variables one needs. This has the good side of making scoping
  explicit.
 
 That's easier said than done. Sometimes I take that route. But
 sometimes I don't want 5 different monads wrapping each other, each
 with its own 'lift' and 'catch' functions, making error messages
 indecipherable and code difficult to read and debug. Do you propose
 creating a special monad for file operations? For network operations? 
 No? Then I don't see why I should have to make a special monad for
 database operations. Or, if the answer was yes, then fine: obfuscate
 your own code, but please don't ask me to do the same. Let's support
 both ways of doing things, and we can be different.

Usually I just define one custom monad for the application which
wraps the stack of monad transformers. Thus changing the monad stack
does not affect the application code. A quite clean and efficient
solution.

My main objection to the TLS is that it looks like normal IO,
but changing the thread that evaluates it can break things in ways
that are hard to debug. E.g. we have an application that uses
TLS and passes an IO action to a library that happens to use
a pool of worker threads that invisible to the application. 
Or the same with the role of the application and library reversed.

Offering it up as a separate library should be ok as it would
be very easy to spot and take extra care not to cause problems.

- Einar Karttunen
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Frederik Eaton
On Mon, Jul 31, 2006 at 03:54:29AM +0300, Einar Karttunen wrote:
 On 30.07 11:49, Frederik Eaton wrote:
  No, because the thread in which it runs inherits any thread-local
  state from its parent.
 
 So we have different threads modifying the thread-local state?
 If it is a copy then updates are not propagated.

As I said, please read my code. There are no updates.

 What about a design with 10 worker threads taking requests
 from a Chan (IO ()) and running them (this occurs in real code).
 To get things right they should use the TLS-context relevant
 to each IO () rather than the thread.

I could see how either behavior might be desirable, see below. (*)

 (snip)
 Usually I just define one custom monad for the application which
 wraps the stack of monad transformers. Thus changing the monad stack
 does not affect the application code. A quite clean and efficient
 solution.

That does sound like a clean approach. However, I think that my
approach would be cleaner; and in any case I think that both
approaches should be available to the programmer.

 My main objection to the TLS is that it looks like normal IO,
 but changing the thread that evaluates it can break things in ways
 that are hard to debug. E.g. we have an application that uses
 TLS and passes an IO action to a library that happens to use
 a pool of worker threads that invisible to the application. 
 Or the same with the role of the application and library reversed.

I don't think it's necessarily such a big deal. Presumably the library
with the worker threads will have to be invoked somewhere. One should
just make sure that it is invoked in the appropriate environment, for
instance with the database connection already properly initialized.

(*) One might even want to change the environment a little within each
thread, for instance so that errors get logged to a thread-specific
log file.

 Offering it up as a separate library should be ok as it would
 be very easy to spot and take extra care not to cause problems.

That's good to hear.

Regards,

Frederik

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


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-30 Thread Thomas Conway

Hi All,

On 7/31/06, Einar Karttunen ekarttun@cs.helsinki.fi wrote:

My main objection to the TLS is that it looks like normal IO,
but changing the thread that evaluates it can break things in ways
that are hard to debug. E.g. we have an application that uses
TLS and passes an IO action to a library that happens to use
a pool of worker threads that invisible to the application.


This is why I believe transaction-local variables are a more useful concept.
You are garanteed that there is only one thread accessing them, and
they behave just like ordinary TVars except that each transaction has
its own copy.

I think you'd need an API like

   type LVar a -- local var
   newLVar :: a - STM (LVar a)
   readLVar :: LVar a - STM a
   writeLVar:: LVar a - a - STM ()

The argument to newLVar is an initial value that is used at the start
of each transaction.  Note that this means that the value in an LVar
does not persist between transaction. I agree that this limits their
use, but simplifies them immensely, and doesn't stand in the way their
being useful for solving a bunch of problems.

cheers,
Tom
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-29 Thread Frederik Eaton
Hi,

Sorry to bring up this thread from so long ago.

On Wed, Mar 01, 2006 at 11:53:42AM +, 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


Re: [Haskell] thread-local variables (was: Re: Implicit Parameters)

2006-07-29 Thread Thomas Conway

I would also note that some form of transaction-local variable would
also be really handy for STM usage.

Tom
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell