Using tiny (atomic) mutables between multiple threads

Hello, Haskell Cafe! I used an MVar to signalize to many threads, when it's time to finish their business (I called it a LoopBreaker). Recently I realized, that it might be too expensive (to use MVar) for cases when threads are many and all of them read my LoopBreaker intensively. This assumption appeared in a case, where I widely (in many threads) used my stopableThreadDelay, which checks LoopBreaker every d = 100 milliseconds. So I decided that I don't really need all the great features, that MVar provides, and that a simpler memory usage concept might be applied here. In a most (machinely) reduced view, all I need is a mutable byte. It would be thread safe, since reading and writing are atomic operations. I then wrote a simple experimental module (my first experience with Ptr in Haskell): ----------------- import Control.Monad import Foreign.Marshal.Utils import Foreign.Ptr import Foreign.Storable newtype MyVar a = MyVar { mvPtr :: Ptr a } newMyVar :: Storable a => a -> IO (MyVar a) newMyVar val = MyVar `liftM` new val readMyVar :: Storable a => (MyVar a) -> IO a readMyVar val = peek $ mvPtr val writeMyVar :: Storable a => (MyVar a) -> a -> IO () writeMyVar var val = poke (mvPtr var) val ----------------- Now, please, help me to answer few questions about all it: 1. Might readMVar really be computationally expensive under heavy load, (with all it's wonderful blocking features)? How much (approximately) more expensive, comparing to a assembler's "mov"? 2. Are the above readMyVar and writeMyVar really atomic? Or are they atomic only if I apply them to <MyVar Word8> type? 3. Are the above readMyVar and writeMyVar safe against asynchronous exceptions? Or again, only if I use <MyVar Word8> type? Belka -- View this message in context: http://www.nabble.com/Using-tiny-%28atomic%29-mutables-between-multiple-thre... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

Hello Belka, Sunday, September 13, 2009, 10:45:35 AM, you wrote: i suggest you to use IORef Bool instead - as it was said once by SimonM, it's safe to use in m/t environment, of course without all fancy features of MVar locking if you need to be as fast as possible, IOUArray (1,1) may be used - this avoids boxing (array of one element is equivalent to IOURef type lacking in std libs)
Hello, Haskell Cafe!
I used an MVar to signalize to many threads, when it's time to finish their business (I called it a LoopBreaker). Recently I realized, that it might be too expensive (to use MVar) for cases when threads are many and all of them read my LoopBreaker intensively. This assumption appeared in a case, where I widely (in many threads) used my stopableThreadDelay, which checks LoopBreaker every d = 100 milliseconds.
So I decided that I don't really need all the great features, that MVar provides, and that a simpler memory usage concept might be applied here. In a most (machinely) reduced view, all I need is a mutable byte. It would be thread safe, since reading and writing are atomic operations. I then wrote a simple experimental module (my first experience with Ptr in Haskell): ----------------- import Control.Monad import Foreign.Marshal.Utils import Foreign.Ptr import Foreign.Storable
newtype MyVar a = MyVar { mvPtr :: Ptr a }
newMyVar :: Storable a => a -> IO (MyVar a) newMyVar val = MyVar `liftM` new val
readMyVar :: Storable a => (MyVar a) -> IO a readMyVar val = peek $ mvPtr val
writeMyVar :: Storable a => (MyVar a) -> a -> IO () writeMyVar var val = poke (mvPtr var) val -----------------
Now, please, help me to answer few questions about all it: 1. Might readMVar really be computationally expensive under heavy load, (with all it's wonderful blocking features)? How much (approximately) more expensive, comparing to a assembler's "mov"? 2. Are the above readMyVar and writeMyVar really atomic? Or are they atomic only if I apply them to <MyVar Word8> type? 3. Are the above readMyVar and writeMyVar safe against asynchronous exceptions? Or again, only if I use <MyVar Word8> type?
Belka
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
i suggest you to use IORef Bool instead - as it was said once by SimonM, it's safe to use in m/t environment, of course without all fancy features of MVar locking
Is it also safe for other types such as Int? And is this documented somewhere? If not it would be helpful to add this to the Haskell Wiki.

Do I have this right? "Remembering" Memoization! For some applications, a lot of state does not to be saved, since "initialization" functions can be called early, and these functions will "remember" - (memoize) their results when called again, because of lazy evaluation? -- Regards, Casey

On 14/09/2009, at 9:28 AM, Casey Hawthorne wrote:
Do I have this right? "Remembering" Memoization!
For some applications, a lot of state does not to be saved, since "initialization" functions can be called early, and these functions will "remember" - (memoize) their results when called again, because of lazy evaluation?
You don't get memoisation for free. If you define a variable once in a where block, it's true that you'll evaluate it at most once, but if you repeatedly call a function "foo" that then calls "bar 12" each time, "bar 12" will be evaluated once per "foo" call. Cheers Mark

I agree with what you meant, but not quite with what you said. To be pedantic:
import Debug.Trace
foo :: Int foo = trace "Foo" (bar 12)
bar :: Int -> Int bar x = trace "Bar" x
main :: IO () main = foo `seq` foo `seq` return ()
main prints "Foo\nBar\n" showing that the bar is only evaluated once, because foo is already evaluated, even though it is referenced twice. So attempting to evaluate foo again just returns the same result.
baz :: Int -> Int baz x = trace "Baz" (bar x)
correct :: IO () correct = baz 10 `seq` baz 11 `seq` return ()
Though, as you said, call, you probably meant foo was a function, and correct prints "Baz\nBar\nBaz\nBar\n" like you had indicated. But pedantically even the function:
quux :: Int -> Int quux x = trace "Quux" (bar 12) optmain :: IO () optmain = quux 10 `seq` quux 11 `seq` return ()
might print only once if GHC at the optimization level selected recognizes
that quux doesn't depend on its argument and rewrote your code with more
sharing.
-Edward Kmett
On Sun, Sep 13, 2009 at 7:45 PM, Mark Wotton
On 14/09/2009, at 9:28 AM, Casey Hawthorne wrote:
Do I have this right? "Remembering" Memoization!
For some applications, a lot of state does not to be saved, since "initialization" functions can be called early, and these functions will "remember" - (memoize) their results when called again, because of lazy evaluation?
You don't get memoisation for free. If you define a variable once in a where block, it's true that you'll evaluate it at most once, but if you repeatedly call a function "foo" that then calls "bar 12" each time, "bar 12" will be evaluated once per "foo" call.
Cheers Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

But pedantically even the function:
quux :: Int -> Int quux x = trace "Quux" (bar 12)
optmain :: IO () optmain = quux 10 `seq` quux 11 `seq` return ()
might print only once if GHC at the optimization level selected recognizes that quux doesn't depend on its argument and rewrote your code with more sharing.
Well to be specific, it depends on how you define "function", quux :: Int -> Int quux = trace "Quux" bar will print "Quux" once under the naive semantics.

The other morning, someone was telling me they had converted most of their VB financial/stock market code to F#. Whereas VB only used one core, the F# code used all four cores. In one software developers meeting, someone was saying that since database work is mostly all state, he didn't see the advantage of a functional programming language. It seems that, if you are doing at least moderately heavy computations, F# buys you a lot of speed on multiple cores. ------------------------------------------ It now occurs to me that he was using an older version of VB, before .NET or for earlier versions of .NET. So maybe the use of multiple cores is now supported by .NET more so than the progamming languages on top of it. -- Regards, Casey

caseyh:
The other morning, someone was telling me they had converted most of their VB financial/stock market code to F#. Whereas VB only used one core, the F# code used all four cores.
In one software developers meeting, someone was saying that since database work is mostly all state, he didn't see the advantage of a functional programming language.
State /= Imperative Programming :-) -- Don

The other morning, someone was telling me they had converted most of their VB financial/stock market code to F#. Whereas VB only used one core, the F# code used all four cores. In one software developers meeting, someone was saying that since database work is mostly all state, he didn't see the advantage of a functional programming language. It seems that, if you are doing at least moderately heavy computations, F# buys you a lot of speed on multiple cores. ------------------------------------------ It now occurs to me that he was using an older version of VB, before .NET or for earlier versions of .NET. So maybe the use of multiple cores is now supported by .NET more so than the progamming languages on top of it. -- Regards, Casey

In one software developers meeting, someone was saying that since database work is mostly all state, he didn't see the advantage of a functional programming language.
Sigh. I'm still waiting for someone to point out how exactly functional languages do a lesser job here. If this was in relation to F#, it makes even less sense, as F# allows you to use the same libraries you would from other .NET languages. The only real argument I've seen is that functional languages don't have all the same pretty designers that, say, VB, has.
So maybe the use of multiple cores is now supported by .NET more so than the progamming languages on top of it.
F# does make it a bit easier as having immutability by default can be helpful. More importantly, VB doesn't support anonymous methods -- only lambda expressions. That can hinder writing clear async or parallel code. Limited type inference can also be annoying at times, especially with heavily generic code. F# doesn't have these problems. .NET 4 will have a nicer multithreading library (http://en.wikipedia.org/wiki/Parallel_Extensions), but F# has some async/parallel support already built-in. I imagine this will let a lot more people to write parallel code without too much pain, even in VB/C#. However, for a lot of async code, F#'s support for monads ("workflows") makes such code many orders of magnitude easier. I don't see any libraries solving this for less capable languages. -Michael -----Original Message----- From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe-bounces@haskell.org] On Behalf Of Casey Hawthorne Sent: Sunday, September 13, 2009 5:32 PM To: haskell-cafe@haskell.org Subject: [Haskell-cafe] Haskell#? F#? The other morning, someone was telling me they had converted most of their VB financial/stock market code to F#. Whereas VB only used one core, the F# code used all four cores. In one software developers meeting, someone was saying that since database work is mostly all state, he didn't see the advantage of a functional programming language. It seems that, if you are doing at least moderately heavy computations, F# buys you a lot of speed on multiple cores. ------------------------------------------ It now occurs to me that he was using an older version of VB, before .NET or for earlier versions of .NET. So maybe the use of multiple cores is now supported by .NET more so than the progamming languages on top of it. -- Regards, Casey _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Felix, Monday, September 14, 2009, 2:39:17 AM, you wrote:
i suggest you to use IORef Bool instead - as it was said once by SimonM, it's safe to use in m/t environment, of course without all fancy features of MVar locking
Is it also safe for other types such as Int? And is this documented somewhere? If not it would be helpful to add this to the Haskell Wiki.
afair, it is safe in one-writer-many-readers setup. probably it isn't documented, otherwise Simon hasn't been asked :) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Belka, Sunday, September 13, 2009, 10:45:35 AM, you wrote:
I used an MVar to signalize to many threads, when it's time to finish their business (I called it a LoopBreaker).
btw, may be you can change the architecture? in particular, where these threads getting their jobs? if they read them from channels (or you may change your code and split it to job producer and job executor communicating via channel), then you may just push EOF job to each queue when party is over -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Thank you, Bulat, for both your suggestions!
1. Since Haskell uses 1 byte for Bool (I confidently guess) and it's safe,
it would also be safe to use <IORef Word8>. Moreover, I found
http://hackage.haskell.org/packages/archive/ArrayRef/0.1.3.1/doc/html/Data-R...
your module and http://www.haskell.org/haskellwiki/Library/ArrayRef the
corresponding article in HaskellWiki , so I plan to use <IOURef Word8>. I
wonder, however, what's the difference between

Hello Belka, Monday, September 14, 2009, 8:05:26 AM, you wrote:
http://www.haskell.org/haskellwiki/Library/ArrayRef the corresponding article in HaskellWiki , so I plan to use <IOURef Word8>. I
if it's compatible with your ghc version :D i don't support this library but other people may keep it up-to-dtae
wonder, however, what's the difference between
and <IORef Word8> (or <IOURef Word8>)?
read http://haskell.org/haskellwiki/Modern_array_libraries , especially "welcome to machine" part. it doesn't describe everything but at least a good starting point
2. As for architecture, I'm not sure that understood the whole suggestion, but got inspired for new ideas for sure! :) My thread's iterations mostly are to acquire resource from load-balancers' chans, and then to react on outer world state changes - networking and DB. I put all the blocking operations to be stoppable by LoopBreaker. There's no real need in job production/execution separation (in most cases) for now
it's just a way to stop executor threads when you are done. cheap threads make it possible to use threading as one more control structure. you can capture this pattern in function and stop worrying about program speed/complexity -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

On 13/09/2009 07:45, Belka wrote:
Hello, Haskell Cafe!
I used an MVar to signalize to many threads, when it's time to finish their business (I called it a LoopBreaker). Recently I realized, that it might be too expensive (to use MVar) for cases when threads are many and all of them read my LoopBreaker intensively. This assumption appeared in a case, where I widely (in many threads) used my stopableThreadDelay, which checks LoopBreaker every d = 100 milliseconds.
So I decided that I don't really need all the great features, that MVar provides, and that a simpler memory usage concept might be applied here. In a most (machinely) reduced view, all I need is a mutable byte. It would be thread safe, since reading and writing are atomic operations. I then wrote a simple experimental module (my first experience with Ptr in Haskell): ----------------- import Control.Monad import Foreign.Marshal.Utils import Foreign.Ptr import Foreign.Storable
newtype MyVar a = MyVar { mvPtr :: Ptr a }
newMyVar :: Storable a => a -> IO (MyVar a) newMyVar val = MyVar `liftM` new val
readMyVar :: Storable a => (MyVar a) -> IO a readMyVar val = peek $ mvPtr val
writeMyVar :: Storable a => (MyVar a) -> a -> IO () writeMyVar var val = poke (mvPtr var) val -----------------
Now, please, help me to answer few questions about all it: 1. Might readMVar really be computationally expensive under heavy load, (with all it's wonderful blocking features)? How much (approximately) more expensive, comparing to a assembler's "mov"?
Probably 10-100 times more expensive than a mov, depending on the cache state.
2. Are the above readMyVar and writeMyVar really atomic? Or are they atomic only if I apply them to<MyVar Word8> type?
It depends what you mean by atomic. If you mean is readMyVar atomic with respect to writeMyVar, then it depends on which type you're instantiating MyVar with, and what machine you're running on. e.g. a MyVar Word32 will probably be atomic, but MyVar Word64 might only be atomic on a 64-bit platform. You'd also have to check your machine's architecture manuals to be sure. MyVar Word8 is atomic on some platforms but not others. The upshot is that it's not a good idea to rely on atomicity here. I'd recommend using IORef and atomicModifyIORef when you need atomicity.
3. Are the above readMyVar and writeMyVar safe against asynchronous exceptions? Or again, only if I use<MyVar Word8> type?
It depends what you mean by "safe", but probably you're worried about atomicity again. It's pretty unusual to want just a mutable variable for communication between threads, normally you need *some* kind of synchronisation. What's your application? Cheers, Simon

Hello Simon, Wednesday, September 16, 2009, 7:05:04 PM, you wrote:
1. Might readMVar really be computationally expensive under heavy load, (with all it's wonderful blocking features)? How much (approximately) more expensive, comparing to a assembler's "mov"?
Probably 10-100 times more expensive than a mov, depending on the cache state.
many years ago, with ghc 6.6 and duron-1000, i had million or two of withMVar per second. anyway, this sort of things is easier to test herself -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com
participants (11)
-
Belka
-
Bulat Ziganshin
-
Casey Hawthorne
-
Derek Elkins
-
Don Stewart
-
Edward Kmett
-
Felix Martini
-
Khudyakov Alexey
-
Mark Wotton
-
Michael Giagnocavo
-
Simon Marlow