[Haskell-cafe] Peyton Jones' "Beautiful Concurrency" .. i.e. Software Transactional Memory ...

Ryan Ingram ryani.spam at gmail.com
Mon Dec 24 15:58:48 EST 2007


{- compile with ghc --make stm.hs -}
module Main where
import Control.Concurrent.STM

type Account = TVar Int

withdraw :: Account -> Int -> STM ()
withdraw acc amount = do
    bal <- readTVar acc
    writeTVar acc (bal - amount)

main = do
    account <- atomically $ newTVar 100
    atomically $ withdraw account 50
    value <- atomically $ readTVar account
    print value


On 12/23/07, Galchin Vasili <vigalchin at gmail.com> wrote:
>
> Hello,
>
>      My brain is a "out to lunch". I have read the paper "Beautiful
> Concurrency" (as well as a bunch of "gaming" papers regarding multi cores).
> I am playing with the "Account" example in the paper. In the paper, the
> alias "type Account = TVar Int" is used.  I want to actually apply the
> function "withdraw" to an example "Account" parameter. I keep getting a type
> check error. Can someone give me a concrete example of
>
> > withdraw ......
>
> ??
>
> Kind regards, Vasya
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20071224/7795f376/attachment.htm


More information about the Haskell-Cafe mailing list