module Hasql.Encoders.Params where
import Hasql.Encoders.Value qualified as C
import Hasql.LibPq14 qualified as A
import Hasql.PostgresTypeInfo qualified as D
import Hasql.Prelude
import PostgreSQL.Binary.Encoding qualified as B
import Text.Builder qualified as E
renderReadable :: Params a -> a -> [Text]
renderReadable :: forall a. Params a -> a -> [Text]
renderReadable (Params Int
_ DList (Oid, Format)
_ Bool -> a -> DList (Maybe ByteString)
_ a -> DList Text
printer) a
params =
  a -> DList Text
printer a
params
    DList Text -> (DList Text -> [Text]) -> [Text]
forall a b. a -> (a -> b) -> b
& DList Text -> [Text]
DList Text -> [Item (DList Text)]
forall l. IsList l => l -> [Item l]
toList
compilePreparedStatementData :: Params a -> Bool -> a -> ([A.Oid], [Maybe (ByteString, A.Format)])
compilePreparedStatementData :: forall a.
Params a -> Bool -> a -> ([Oid], [Maybe (ByteString, Format)])
compilePreparedStatementData (Params Int
_ DList (Oid, Format)
columnsMetadata Bool -> a -> DList (Maybe ByteString)
serializer a -> DList Text
_) Bool
integerDatetimes a
input =
  ([Oid]
oidList, [Maybe (ByteString, Format)]
valueAndFormatList)
  where
    ([Oid]
oidList, [Format]
formatList) =
      DList (Oid, Format)
columnsMetadata DList (Oid, Format)
-> (DList (Oid, Format) -> [(Oid, Format)]) -> [(Oid, Format)]
forall a b. a -> (a -> b) -> b
& DList (Oid, Format) -> [(Oid, Format)]
DList (Oid, Format) -> [Item (DList (Oid, Format))]
forall l. IsList l => l -> [Item l]
toList [(Oid, Format)]
-> ([(Oid, Format)] -> ([Oid], [Format])) -> ([Oid], [Format])
forall a b. a -> (a -> b) -> b
& [(Oid, Format)] -> ([Oid], [Format])
forall a b. [(a, b)] -> ([a], [b])
unzip
    valueAndFormatList :: [Maybe (ByteString, Format)]
valueAndFormatList =
      Bool -> a -> DList (Maybe ByteString)
serializer Bool
integerDatetimes a
input
        DList (Maybe ByteString)
-> (DList (Maybe ByteString) -> [Maybe ByteString])
-> [Maybe ByteString]
forall a b. a -> (a -> b) -> b
& DList (Maybe ByteString) -> [Maybe ByteString]
DList (Maybe ByteString) -> [Item (DList (Maybe ByteString))]
forall l. IsList l => l -> [Item l]
toList
        [Maybe ByteString]
-> ([Maybe ByteString] -> [Maybe (ByteString, Format)])
-> [Maybe (ByteString, Format)]
forall a b. a -> (a -> b) -> b
& (Format -> Maybe ByteString -> Maybe (ByteString, Format))
-> [Format] -> [Maybe ByteString] -> [Maybe (ByteString, Format)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith (\Format
format Maybe ByteString
encoding -> (,Format
format) (ByteString -> (ByteString, Format))
-> Maybe ByteString -> Maybe (ByteString, Format)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe ByteString
encoding) [Format]
formatList
compileUnpreparedStatementData :: Params a -> Bool -> a -> [Maybe (A.Oid, ByteString, A.Format)]
compileUnpreparedStatementData :: forall a.
Params a -> Bool -> a -> [Maybe (Oid, ByteString, Format)]
compileUnpreparedStatementData (Params Int
_ DList (Oid, Format)
columnsMetadata Bool -> a -> DList (Maybe ByteString)
serializer a -> DList Text
printer) Bool
integerDatetimes a
input =
  ((Oid, Format)
 -> Maybe ByteString -> Maybe (Oid, ByteString, Format))
-> [(Oid, Format)]
-> [Maybe ByteString]
-> [Maybe (Oid, ByteString, Format)]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith
    ( \(Oid
oid, Format
format) Maybe ByteString
encoding ->
        (,,) (Oid -> ByteString -> Format -> (Oid, ByteString, Format))
-> Maybe Oid
-> Maybe (ByteString -> Format -> (Oid, ByteString, Format))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Oid -> Maybe Oid
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Oid
oid Maybe (ByteString -> Format -> (Oid, ByteString, Format))
-> Maybe ByteString -> Maybe (Format -> (Oid, ByteString, Format))
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe ByteString
encoding Maybe (Format -> (Oid, ByteString, Format))
-> Maybe Format -> Maybe (Oid, ByteString, Format)
forall a b. Maybe (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Format -> Maybe Format
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Format
format
    )
    (DList (Oid, Format) -> [Item (DList (Oid, Format))]
forall l. IsList l => l -> [Item l]
toList DList (Oid, Format)
columnsMetadata)
    (DList (Maybe ByteString) -> [Item (DList (Maybe ByteString))]
forall l. IsList l => l -> [Item l]
toList (Bool -> a -> DList (Maybe ByteString)
serializer Bool
integerDatetimes a
input))
data Params a = Params
  { forall a. Params a -> Int
size :: !Int,
    forall a. Params a -> DList (Oid, Format)
columnsMetadata :: !(DList (A.Oid, A.Format)),
    forall a. Params a -> Bool -> a -> DList (Maybe ByteString)
serializer :: Bool -> a -> DList (Maybe ByteString),
    forall a. Params a -> a -> DList Text
printer :: a -> DList Text
  }
instance Contravariant Params where
  contramap :: forall a' a. (a' -> a) -> Params a -> Params a'
contramap a' -> a
fn (Params Int
size DList (Oid, Format)
columnsMetadata Bool -> a -> DList (Maybe ByteString)
oldSerializer a -> DList Text
oldPrinter) = Params {Int
DList (Oid, Format)
a' -> DList Text
Bool -> a' -> DList (Maybe ByteString)
size :: Int
columnsMetadata :: DList (Oid, Format)
serializer :: Bool -> a' -> DList (Maybe ByteString)
printer :: a' -> DList Text
size :: Int
columnsMetadata :: DList (Oid, Format)
serializer :: Bool -> a' -> DList (Maybe ByteString)
printer :: a' -> DList Text
..}
    where
      serializer :: Bool -> a' -> DList (Maybe ByteString)
serializer Bool
idt = Bool -> a -> DList (Maybe ByteString)
oldSerializer Bool
idt (a -> DList (Maybe ByteString))
-> (a' -> a) -> a' -> DList (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a' -> a
fn
      printer :: a' -> DList Text
printer = a -> DList Text
oldPrinter (a -> DList Text) -> (a' -> a) -> a' -> DList Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a' -> a
fn
instance Divisible Params where
  divide :: forall a b c. (a -> (b, c)) -> Params b -> Params c -> Params a
divide
    a -> (b, c)
divisor
    (Params Int
leftSize DList (Oid, Format)
leftColumnsMetadata Bool -> b -> DList (Maybe ByteString)
leftSerializer b -> DList Text
leftPrinter)
    (Params Int
rightSize DList (Oid, Format)
rightColumnsMetadata Bool -> c -> DList (Maybe ByteString)
rightSerializer c -> DList Text
rightPrinter) =
      Params
        { size :: Int
size = Int
leftSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightSize,
          columnsMetadata :: DList (Oid, Format)
columnsMetadata = DList (Oid, Format)
leftColumnsMetadata DList (Oid, Format) -> DList (Oid, Format) -> DList (Oid, Format)
forall a. Semigroup a => a -> a -> a
<> DList (Oid, Format)
rightColumnsMetadata,
          serializer :: Bool -> a -> DList (Maybe ByteString)
serializer = \Bool
idt a
input -> case a -> (b, c)
divisor a
input of
            (b
leftInput, c
rightInput) -> Bool -> b -> DList (Maybe ByteString)
leftSerializer Bool
idt b
leftInput DList (Maybe ByteString)
-> DList (Maybe ByteString) -> DList (Maybe ByteString)
forall a. Semigroup a => a -> a -> a
<> Bool -> c -> DList (Maybe ByteString)
rightSerializer Bool
idt c
rightInput,
          printer :: a -> DList Text
printer = \a
input -> case a -> (b, c)
divisor a
input of
            (b
leftInput, c
rightInput) -> b -> DList Text
leftPrinter b
leftInput DList Text -> DList Text -> DList Text
forall a. Semigroup a => a -> a -> a
<> c -> DList Text
rightPrinter c
rightInput
        }
  conquer :: forall a. Params a
conquer =
    Params
      { size :: Int
size = Int
0,
        columnsMetadata :: DList (Oid, Format)
columnsMetadata = DList (Oid, Format)
forall a. Monoid a => a
mempty,
        serializer :: Bool -> a -> DList (Maybe ByteString)
serializer = Bool -> a -> DList (Maybe ByteString)
forall a. Monoid a => a
mempty,
        printer :: a -> DList Text
printer = a -> DList Text
forall a. Monoid a => a
mempty
      }
instance Semigroup (Params a) where
  Params Int
leftSize DList (Oid, Format)
leftColumnsMetadata Bool -> a -> DList (Maybe ByteString)
leftSerializer a -> DList Text
leftPrinter <> :: Params a -> Params a -> Params a
<> Params Int
rightSize DList (Oid, Format)
rightColumnsMetadata Bool -> a -> DList (Maybe ByteString)
rightSerializer a -> DList Text
rightPrinter =
    Params
      { size :: Int
size = Int
leftSize Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
rightSize,
        columnsMetadata :: DList (Oid, Format)
columnsMetadata = DList (Oid, Format)
leftColumnsMetadata DList (Oid, Format) -> DList (Oid, Format) -> DList (Oid, Format)
forall a. Semigroup a => a -> a -> a
<> DList (Oid, Format)
rightColumnsMetadata,
        serializer :: Bool -> a -> DList (Maybe ByteString)
serializer = \Bool
idt a
input -> Bool -> a -> DList (Maybe ByteString)
leftSerializer Bool
idt a
input DList (Maybe ByteString)
-> DList (Maybe ByteString) -> DList (Maybe ByteString)
forall a. Semigroup a => a -> a -> a
<> Bool -> a -> DList (Maybe ByteString)
rightSerializer Bool
idt a
input,
        printer :: a -> DList Text
printer = \a
input -> a -> DList Text
leftPrinter a
input DList Text -> DList Text -> DList Text
forall a. Semigroup a => a -> a -> a
<> a -> DList Text
rightPrinter a
input
      }
instance Monoid (Params a) where
  mempty :: Params a
mempty = Params a
forall a. Params a
forall (f :: * -> *) a. Divisible f => f a
conquer
value :: C.Value a -> Params a
value :: forall a. Value a -> Params a
value (C.Value OID
valueOID OID
_ Bool -> a -> Encoding
serialize a -> Builder
print) =
  Params
    { size :: Int
size = Int
1,
      columnsMetadata :: DList (Oid, Format)
columnsMetadata = (Oid, Format) -> DList (Oid, Format)
forall a. a -> DList a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Oid
pqOid, Format
format),
      serializer :: Bool -> a -> DList (Maybe ByteString)
serializer = \Bool
idt -> Maybe ByteString -> DList (Maybe ByteString)
forall a. a -> DList a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ByteString -> DList (Maybe ByteString))
-> (a -> Maybe ByteString) -> a -> DList (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (ByteString -> Maybe ByteString)
-> (a -> ByteString) -> a -> Maybe ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Encoding -> ByteString
B.encodingBytes (Encoding -> ByteString) -> (a -> Encoding) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Bool -> a -> Encoding
serialize Bool
idt,
      printer :: a -> DList Text
printer = Text -> DList Text
forall a. a -> DList a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> DList Text) -> (a -> Text) -> a -> DList Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> Text
E.run (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Builder
print
    }
  where
    D.OID Word32
_ Oid
pqOid Format
format = OID
valueOID
nullableValue :: C.Value a -> Params (Maybe a)
nullableValue :: forall a. Value a -> Params (Maybe a)
nullableValue (C.Value OID
valueOID OID
_ Bool -> a -> Encoding
serialize a -> Builder
print) =
  Params
    { size :: Int
size = Int
1,
      columnsMetadata :: DList (Oid, Format)
columnsMetadata = (Oid, Format) -> DList (Oid, Format)
forall a. a -> DList a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Oid
pqOid, Format
format),
      serializer :: Bool -> Maybe a -> DList (Maybe ByteString)
serializer = \Bool
idt -> Maybe ByteString -> DList (Maybe ByteString)
forall a. a -> DList a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe ByteString -> DList (Maybe ByteString))
-> (Maybe a -> Maybe ByteString)
-> Maybe a
-> DList (Maybe ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (a -> ByteString) -> Maybe a -> Maybe ByteString
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Encoding -> ByteString
B.encodingBytes (Encoding -> ByteString) -> (a -> Encoding) -> a -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Bool -> a -> Encoding
serialize Bool
idt),
      printer :: Maybe a -> DList Text
printer = Text -> DList Text
forall a. a -> DList a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> DList Text) -> (Maybe a -> Text) -> Maybe a -> DList Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Text -> (a -> Text) -> Maybe a -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"null" (Builder -> Text
E.run (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. a -> Builder
print)
    }
  where
    D.OID Word32
_ Oid
pqOid Format
format = OID
valueOID