[Haskell-cafe] more on the "Beautiful Concurrency" function "withdraw" application ...

Dean Herington heringtonlacey at mindspring.com
Mon Dec 24 01:44:16 EST 2007


At 12:19 AM -0600 12/24/07, Galchin Vasili wrote:
>module Main where
>import Control.Concurrent.STM
>import Control.Concurrent
>import System.Random
>
>type Account = TVar Int
>
>transfer :: Account -> Account -> Int -> IO ()
>transfer from to amount
>       = atomically (do {deposit to amount;
>                         withdraw from amount})
>
>deposit :: Account -> Int -> STM ()
>deposit acc amount = withdraw acc (- amount)
>
>withdraw :: Account -> Int -> STM ()
>withdraw acc amount
>    = do { bal <- readTVar acc;
>           writeTVar acc (bal - amount) }
>
>
>
>When I try
>
>withdraw (TVar 10) ..
>
>I get "Not in scope: data constructor 'TVar'.  OK .. "Tvar" is a 
>class and not a Haskell data type ... so now what?

You first need to create an account:

>  acct <- newTVar 100

Then you can withdraw from it:

>  atomically (withdraw acct 10)

Dean


More information about the Haskell-Cafe mailing list