module Hasql.Private.Encoders
where
import Hasql.Private.Prelude hiding (bool)
import qualified PostgreSQL.Binary.Encoding as A
import qualified PostgreSQL.Binary.Data as B
import qualified Text.Builder as C
import qualified Hasql.Private.Encoders.Params as Params
import qualified Hasql.Private.Encoders.Value as Value
import qualified Hasql.Private.Encoders.Array as Array
import qualified Hasql.Private.PTI as PTI
import qualified Hasql.Private.Prelude as Prelude
newtype Params a = Params (Params.Params a)
deriving (Contravariant, Divisible, Decidable, Monoid, Semigroup)
noParams :: Params ()
noParams = mempty
param :: NullableOrNot Value a -> Params a
param = \ case
NonNullable (Value valueEnc) -> Params (Params.value valueEnc)
Nullable (Value valueEnc) -> Params (Params.nullableValue valueEnc)
data NullableOrNot encoder a where
NonNullable :: encoder a -> NullableOrNot encoder a
Nullable :: encoder a -> NullableOrNot encoder (Maybe a)
nonNullable :: encoder a -> NullableOrNot encoder a
nonNullable = NonNullable
nullable :: encoder a -> NullableOrNot encoder (Maybe a)
nullable = Nullable
newtype Value a = Value (Value.Value a)
deriving (Contravariant)
{-# INLINABLE bool #-}
bool :: Value Bool
bool = Value (Value.unsafePTIWithShow PTI.bool (const A.bool))
{-# INLINABLE int2 #-}
int2 :: Value Int16
int2 = Value (Value.unsafePTIWithShow PTI.int2 (const A.int2_int16))
{-# INLINABLE int4 #-}
int4 :: Value Int32
int4 = Value (Value.unsafePTIWithShow PTI.int4 (const A.int4_int32))
{-# INLINABLE int8 #-}
int8 :: Value Int64
int8 = Value (Value.unsafePTIWithShow PTI.int8 (const A.int8_int64))
{-# INLINABLE float4 #-}
float4 :: Value Float
float4 = Value (Value.unsafePTIWithShow PTI.float4 (const A.float4))
{-# INLINABLE float8 #-}
float8 :: Value Double
float8 = Value (Value.unsafePTIWithShow PTI.float8 (const A.float8))
{-# INLINABLE numeric #-}
numeric :: Value B.Scientific
numeric = Value (Value.unsafePTIWithShow PTI.numeric (const A.numeric))
{-# INLINABLE char #-}
char :: Value Char
char = Value (Value.unsafePTIWithShow PTI.text (const A.char_utf8))
{-# INLINABLE text #-}
text :: Value Text
text = Value (Value.unsafePTIWithShow PTI.text (const A.text_strict))
{-# INLINABLE bytea #-}
bytea :: Value ByteString
bytea = Value (Value.unsafePTIWithShow PTI.bytea (const A.bytea_strict))
{-# INLINABLE date #-}
date :: Value B.Day
date = Value (Value.unsafePTIWithShow PTI.date (const A.date))
{-# INLINABLE timestamp #-}
timestamp :: Value B.LocalTime
timestamp = Value (Value.unsafePTIWithShow PTI.timestamp (Prelude.bool A.timestamp_float A.timestamp_int))
{-# INLINABLE timestamptz #-}
timestamptz :: Value B.UTCTime
timestamptz = Value (Value.unsafePTIWithShow PTI.timestamptz (Prelude.bool A.timestamptz_float A.timestamptz_int))
{-# INLINABLE time #-}
time :: Value B.TimeOfDay
time = Value (Value.unsafePTIWithShow PTI.time (Prelude.bool A.time_float A.time_int))
{-# INLINABLE timetz #-}
timetz :: Value (B.TimeOfDay, B.TimeZone)
timetz = Value (Value.unsafePTIWithShow PTI.timetz (Prelude.bool A.timetz_float A.timetz_int))
{-# INLINABLE interval #-}
interval :: Value B.DiffTime
interval = Value (Value.unsafePTIWithShow PTI.interval (Prelude.bool A.interval_float A.interval_int))
{-# INLINABLE uuid #-}
uuid :: Value B.UUID
uuid = Value (Value.unsafePTIWithShow PTI.uuid (const A.uuid))
{-# INLINABLE inet #-}
inet :: Value (B.NetAddr B.IP)
inet = Value (Value.unsafePTIWithShow PTI.inet (const A.inet))
{-# INLINABLE json #-}
json :: Value B.Value
json = Value (Value.unsafePTIWithShow PTI.json (const A.json_ast))
{-# INLINABLE jsonBytes #-}
jsonBytes :: Value ByteString
jsonBytes = Value (Value.unsafePTIWithShow PTI.json (const A.json_bytes))
{-# INLINABLE jsonb #-}
jsonb :: Value B.Value
jsonb = Value (Value.unsafePTIWithShow PTI.jsonb (const A.jsonb_ast))
{-# INLINABLE jsonbBytes #-}
jsonbBytes :: Value ByteString
jsonbBytes = Value (Value.unsafePTIWithShow PTI.jsonb (const A.jsonb_bytes))
{-# INLINABLE enum #-}
enum :: (a -> Text) -> Value a
enum mapping = Value (Value.unsafePTI PTI.text (const (A.text_strict . mapping)) (C.text . mapping))
{-# INLINABLE unknown #-}
unknown :: Value ByteString
unknown = Value (Value.unsafePTIWithShow PTI.unknown (const A.bytea_strict))
array :: Array a -> Value a
array (Array (Array.Array valueOID arrayOID arrayEncoder renderer)) = let
encoder env input = A.array (PTI.oidWord32 valueOID) (arrayEncoder env input)
in Value (Value.Value arrayOID arrayOID encoder renderer)
{-# INLINE foldableArray #-}
foldableArray :: Foldable foldable => NullableOrNot Value element -> Value (foldable element)
foldableArray = array . dimension foldl' . element
newtype Array a = Array (Array.Array a)
deriving (Contravariant)
element :: NullableOrNot Value a -> Array a
element = \ case
NonNullable (Value (Value.Value elementOID arrayOID encoder renderer)) ->
Array (Array.value elementOID arrayOID encoder renderer)
Nullable (Value (Value.Value elementOID arrayOID encoder renderer)) ->
Array (Array.nullableValue elementOID arrayOID encoder renderer)
{-# INLINABLE dimension #-}
dimension :: (forall a. (a -> b -> a) -> a -> c -> a) -> Array b -> Array c
dimension foldl (Array imp) = Array (Array.dimension foldl imp)