{- 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@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@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe