module Hasql.Private.PreparedStatementRegistry
  ( PreparedStatementRegistry,
    new,
    update,
    LocalKey (..),
  )
where

import qualified ByteString.StrictBuilder as B
import qualified Data.HashTable.IO as A
import Hasql.Private.Prelude hiding (lookup)

data PreparedStatementRegistry
  = PreparedStatementRegistry !(A.BasicHashTable LocalKey ByteString) !(IORef Word)

{-# INLINEABLE new #-}
new :: IO PreparedStatementRegistry
new :: IO PreparedStatementRegistry
new =
  BasicHashTable LocalKey ByteString
-> IORef Word -> PreparedStatementRegistry
PreparedStatementRegistry forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (h :: * -> * -> * -> *) k v.
HashTable h =>
IO (IOHashTable h k v)
A.new forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. a -> IO (IORef a)
newIORef Word
0

{-# INLINEABLE update #-}
update :: LocalKey -> (ByteString -> IO (Bool, a)) -> (ByteString -> IO a) -> PreparedStatementRegistry -> IO a
update :: forall a.
LocalKey
-> (ByteString -> IO (Bool, a))
-> (ByteString -> IO a)
-> PreparedStatementRegistry
-> IO a
update LocalKey
localKey ByteString -> IO (Bool, a)
onNewRemoteKey ByteString -> IO a
onOldRemoteKey (PreparedStatementRegistry BasicHashTable LocalKey ByteString
table IORef Word
counter) =
  IO (Maybe ByteString)
lookup forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall b a. b -> (a -> b) -> Maybe a -> b
maybe IO a
new ByteString -> IO a
old
  where
    lookup :: IO (Maybe ByteString)
lookup =
      forall (h :: * -> * -> * -> *) k v.
(HashTable h, Eq k, Hashable k) =>
IOHashTable h k v -> k -> IO (Maybe v)
A.lookup BasicHashTable LocalKey ByteString
table LocalKey
localKey
    new :: IO a
new =
      forall a. IORef a -> IO a
readIORef IORef Word
counter forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Word -> IO a
onN
      where
        onN :: Word -> IO a
onN Word
n =
          do
            (Bool
save, a
result) <- ByteString -> IO (Bool, a)
onNewRemoteKey ByteString
remoteKey
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
save forall a b. (a -> b) -> a -> b
$ do
              forall (h :: * -> * -> * -> *) k v.
(HashTable h, Eq k, Hashable k) =>
IOHashTable h k v -> k -> v -> IO ()
A.insert BasicHashTable LocalKey ByteString
table LocalKey
localKey ByteString
remoteKey
              forall a. IORef a -> a -> IO ()
writeIORef IORef Word
counter (forall a. Enum a => a -> a
succ Word
n)
            forall (m :: * -> *) a. Monad m => a -> m a
return a
result
          where
            remoteKey :: ByteString
remoteKey =
              Builder -> ByteString
B.builderBytes forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. forall a. Integral a => a -> Builder
B.asciiIntegral forall a b. (a -> b) -> a -> b
$ Word
n
    old :: ByteString -> IO a
old =
      ByteString -> IO a
onOldRemoteKey

-- |
-- Local statement key.
data LocalKey
  = LocalKey !ByteString ![Word32]
  deriving (Int -> LocalKey -> ShowS
[LocalKey] -> ShowS
LocalKey -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LocalKey] -> ShowS
$cshowList :: [LocalKey] -> ShowS
show :: LocalKey -> String
$cshow :: LocalKey -> String
showsPrec :: Int -> LocalKey -> ShowS
$cshowsPrec :: Int -> LocalKey -> ShowS
Show, LocalKey -> LocalKey -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LocalKey -> LocalKey -> Bool
$c/= :: LocalKey -> LocalKey -> Bool
== :: LocalKey -> LocalKey -> Bool
$c== :: LocalKey -> LocalKey -> Bool
Eq)

instance Hashable LocalKey where
  {-# INLINE hashWithSalt #-}
  hashWithSalt :: Int -> LocalKey -> Int
hashWithSalt Int
salt (LocalKey ByteString
template [Word32]
types) =
    forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt ByteString
template