|
module Main where |
|
|
|
import Control.Concurrent (threadDelay, forkIO) |
|
import Control.Concurrent.STM.TVar |
|
import Control.Monad (replicateM, forM_, forM) |
|
import Control.Monad.STM |
|
import Data.IntMap hiding (map) |
|
import Data.Pool |
|
import Database.HDBC (disconnect) |
|
import Database.HDBC.PostgreSQL (connectPostgreSQL, Connection) |
|
|
|
main :: IO () |
|
main = do |
|
let numPool = 100 |
|
let numMkConnPerPool = 10 |
|
let sizePerPool = 10 |
|
tvar <- mk numPool |
|
pools <- forM [1..numPool] $ \poolId -> createPool |
|
(create tvar poolId) |
|
destroy |
|
1 -- num of stripes |
|
0.5 -- idle time |
|
sizePerPool -- pool size |
|
forM_ pools $ \pool -> forM_ [1..numMkConnPerPool] $ \n -> forkIO $ |
|
withResource pool $ \(_conn, poolId, connId) -> do |
|
putStrLn $ "using connection: " ++ show (poolId, connId, n) |
|
threadDelay $ 1 * 1000 -- * 1000 |
|
putStrLn $ "done: " ++ show (poolId, connId, n) |
|
threadDelay $ 2 * 1000 * 1000 |
|
putStrLn "*** done" |
|
|
|
create :: TVar (IntMap Int) -> Int -> IO (Connection, Int, Int) |
|
-- create :: TVar (IntMap Int) -> Int -> IO (Int, Int, Int) |
|
create tvar poolId = do |
|
connId <- inc tvar poolId |
|
putStrLn $ "*** create: " ++ show (poolId, connId) |
|
conn <- connectPostgreSQL "postgres:///resource-pool-error" |
|
-- conn <- return 0 |
|
return (conn, poolId, connId) |
|
|
|
destroy :: (Connection, Int, Int) -> IO () |
|
-- destroy :: (Int, Int, Int) -> IO () |
|
destroy (conn, poolId, connId) = do |
|
putStrLn $ "*** destroy: " ++ show (poolId, connId) |
|
disconnect conn |
|
-- return () |
|
|
|
mk :: Int -> IO (TVar (IntMap Int)) |
|
mk size = newTVarIO (fromList $ map (\p -> (p, 1)) [1..size]) |
|
|
|
inc :: TVar (IntMap Int) -> Int -> IO Int |
|
inc tvar poolId = do |
|
(Just n) <- atomically $ stateTVar tvar $ updateLookupWithKey (\_ n -> Just (n + 1)) poolId |
|
return n |
単純に disconnect を並列に呼んだらだめ。
https://github.com/hdbc/hdbc-postgresql/blob/master/hdbc-postgresql-helper.c#L31-L35
おそらく reaper の処理と purgeLocalPool が並列に呼ばれている?
(もともとのこのコードは threaded をつけ忘れていて気づかなかった。GC のスレッドは別なのでたまに起きていた)