hasql/library/Hasql/Private/PreparedStatementRegistry.hs

54 lines
1.4 KiB
Haskell
Raw Normal View History

2015-12-21 16:11:14 +03:00
module Hasql.Private.PreparedStatementRegistry
2022-06-20 13:54:54 +03:00
( PreparedStatementRegistry,
new,
update,
LocalKey (..),
)
2015-11-08 21:09:42 +03:00
where
2017-03-21 00:29:27 +03:00
import qualified ByteString.StrictBuilder as B
2022-06-20 13:54:54 +03:00
import qualified Data.HashTable.IO as A
import Hasql.Private.Prelude hiding (lookup)
2015-11-08 21:09:42 +03:00
2022-06-20 13:54:54 +03:00
data PreparedStatementRegistry
= PreparedStatementRegistry !(A.BasicHashTable LocalKey ByteString) !(IORef Word)
2015-11-08 21:09:42 +03:00
2022-06-20 13:54:54 +03:00
{-# INLINEABLE new #-}
2015-11-08 21:09:42 +03:00
new :: IO PreparedStatementRegistry
new =
PreparedStatementRegistry <$> A.new <*> newIORef 0
2022-06-20 13:54:54 +03:00
{-# INLINEABLE update #-}
update :: LocalKey -> (ByteString -> IO (Bool, a)) -> (ByteString -> IO a) -> PreparedStatementRegistry -> IO a
update localKey onNewRemoteKey onOldRemoteKey (PreparedStatementRegistry table counter) =
lookup >>= maybe new old
where
lookup =
A.lookup table localKey
new =
readIORef counter >>= onN
where
onN n =
do
(save, result) <- onNewRemoteKey remoteKey
when save $ do
A.insert table localKey remoteKey
writeIORef counter (succ n)
return result
where
remoteKey =
2017-03-21 00:29:27 +03:00
B.builderBytes . B.asciiIntegral $ n
old =
onOldRemoteKey
2015-11-08 21:09:42 +03:00
-- |
-- Local statement key.
2022-06-20 13:54:54 +03:00
data LocalKey
= LocalKey !ByteString ![Word32]
2015-11-08 21:09:42 +03:00
deriving (Show, Eq)
instance Hashable LocalKey where
{-# INLINE hashWithSalt #-}
hashWithSalt salt (LocalKey template types) =
hashWithSalt salt template