module Hasura.Backends.Postgres.SQL.Value
( PGScalarValue (..),
pgScalarValueToJson,
withConstructorFn,
parsePGValue,
scientificToInteger,
scientificToFloat,
textToScalarValue,
TxtEncodedVal (..),
txtEncodedVal,
binEncoder,
txtEncoder,
toPrepParam,
withScalarTypeAnn,
withTypeAnn,
)
where
import Data.Aeson
import Data.Aeson.Text qualified as AE
import Data.Aeson.Types qualified as AT
import Data.ByteString qualified as B
import Data.Int
import Data.Scientific
import Data.Text qualified as T
import Data.Text.Conversions qualified as TC
import Data.Text.Encoding qualified as TE
import Data.Text.Lazy qualified as TL
import Data.Time
import Data.UUID qualified as UUID
import Database.PG.Query qualified as Q
import Database.PG.Query.PTI qualified as PTI
import Database.PostgreSQL.LibPQ qualified as PQ
import Hasura.Backends.Postgres.SQL.DML qualified as S
import Hasura.Backends.Postgres.SQL.Types
import Hasura.Prelude
import Hasura.SQL.GeoJSON
import Hasura.SQL.Time
import Hasura.SQL.Types
import Hasura.SQL.Value (TxtEncodedVal (..))
import PostgreSQL.Binary.Encoding qualified as PE
newtype RasterWKB = RasterWKB {RasterWKB -> Base16 ByteString
getRasterWKB :: TC.Base16 B.ByteString}
deriving (Int -> RasterWKB -> ShowS
[RasterWKB] -> ShowS
RasterWKB -> String
(Int -> RasterWKB -> ShowS)
-> (RasterWKB -> String)
-> ([RasterWKB] -> ShowS)
-> Show RasterWKB
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RasterWKB] -> ShowS
$cshowList :: [RasterWKB] -> ShowS
show :: RasterWKB -> String
$cshow :: RasterWKB -> String
showsPrec :: Int -> RasterWKB -> ShowS
$cshowsPrec :: Int -> RasterWKB -> ShowS
Show, RasterWKB -> RasterWKB -> Bool
(RasterWKB -> RasterWKB -> Bool)
-> (RasterWKB -> RasterWKB -> Bool) -> Eq RasterWKB
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RasterWKB -> RasterWKB -> Bool
$c/= :: RasterWKB -> RasterWKB -> Bool
== :: RasterWKB -> RasterWKB -> Bool
$c== :: RasterWKB -> RasterWKB -> Bool
Eq)
instance FromJSON RasterWKB where
parseJSON :: Value -> Parser RasterWKB
parseJSON = \case
String Text
t -> case Text -> Maybe (Base16 ByteString)
forall a. FromText a => Text -> a
TC.fromText Text
t of
Just Base16 ByteString
v -> RasterWKB -> Parser RasterWKB
forall (m :: * -> *) a. Monad m => a -> m a
return (RasterWKB -> Parser RasterWKB) -> RasterWKB -> Parser RasterWKB
forall a b. (a -> b) -> a -> b
$ Base16 ByteString -> RasterWKB
RasterWKB Base16 ByteString
v
Maybe (Base16 ByteString)
Nothing ->
String -> Parser RasterWKB
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
String
"invalid hexadecimal representation of raster well known binary format"
Value
_ -> String -> Parser RasterWKB
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"expecting String for raster"
instance ToJSON RasterWKB where
toJSON :: RasterWKB -> Value
toJSON = Text -> Value
forall a. ToJSON a => a -> Value
toJSON (Text -> Value) -> (RasterWKB -> Text) -> RasterWKB -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base16 ByteString -> Text
forall a. ToText a => a -> Text
TC.toText (Base16 ByteString -> Text)
-> (RasterWKB -> Base16 ByteString) -> RasterWKB -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RasterWKB -> Base16 ByteString
getRasterWKB
newtype Ltree = Ltree Text
deriving (Int -> Ltree -> ShowS
[Ltree] -> ShowS
Ltree -> String
(Int -> Ltree -> ShowS)
-> (Ltree -> String) -> ([Ltree] -> ShowS) -> Show Ltree
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Ltree] -> ShowS
$cshowList :: [Ltree] -> ShowS
show :: Ltree -> String
$cshow :: Ltree -> String
showsPrec :: Int -> Ltree -> ShowS
$cshowsPrec :: Int -> Ltree -> ShowS
Show, Ltree -> Ltree -> Bool
(Ltree -> Ltree -> Bool) -> (Ltree -> Ltree -> Bool) -> Eq Ltree
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Ltree -> Ltree -> Bool
$c/= :: Ltree -> Ltree -> Bool
== :: Ltree -> Ltree -> Bool
$c== :: Ltree -> Ltree -> Bool
Eq)
instance ToJSON Ltree where
toJSON :: Ltree -> Value
toJSON (Ltree Text
t) = Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
instance FromJSON Ltree where
parseJSON :: Value -> Parser Ltree
parseJSON = \case
String Text
t ->
if (Text -> Bool) -> [Text] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any Text -> Bool
T.null ([Text] -> Bool) -> [Text] -> Bool
forall a b. (a -> b) -> a -> b
$ Text -> Text -> [Text]
T.splitOn (String -> Text
T.pack String
".") Text
t
then String -> Parser Ltree
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
message
else Ltree -> Parser Ltree
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ltree -> Parser Ltree) -> Ltree -> Parser Ltree
forall a b. (a -> b) -> a -> b
$ Text -> Ltree
Ltree Text
t
Value
_ -> String -> Parser Ltree
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
message
where
message :: String
message = String
"Expecting label path: a sequence of zero or more labels separated by dots, for example L1.L2.L3"
data PGScalarValue
= PGValInteger Int32
| PGValSmallInt Int16
| PGValBigInt Int64
| PGValFloat Float
| PGValDouble Double
| PGValNumeric Scientific
| PGValMoney Scientific
| PGValBoolean Bool
| PGValChar Char
| PGValVarchar Text
| PGValText Text
| PGValCitext Text
| PGValDate Day
| PGValTimeStamp LocalTime
| PGValTimeStampTZ UTCTime
| PGValTimeTZ ZonedTimeOfDay
| PGNull PGScalarType
| PGValJSON Q.JSON
| PGValJSONB Q.JSONB
| PGValGeo GeometryWithCRS
| PGValRaster RasterWKB
| PGValUUID UUID.UUID
| PGValLtree Ltree
| PGValLquery Text
| PGValLtxtquery Text
| PGValUnknown Text
| PGValArray [PGScalarValue]
deriving (Int -> PGScalarValue -> ShowS
[PGScalarValue] -> ShowS
PGScalarValue -> String
(Int -> PGScalarValue -> ShowS)
-> (PGScalarValue -> String)
-> ([PGScalarValue] -> ShowS)
-> Show PGScalarValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PGScalarValue] -> ShowS
$cshowList :: [PGScalarValue] -> ShowS
show :: PGScalarValue -> String
$cshow :: PGScalarValue -> String
showsPrec :: Int -> PGScalarValue -> ShowS
$cshowsPrec :: Int -> PGScalarValue -> ShowS
Show, PGScalarValue -> PGScalarValue -> Bool
(PGScalarValue -> PGScalarValue -> Bool)
-> (PGScalarValue -> PGScalarValue -> Bool) -> Eq PGScalarValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PGScalarValue -> PGScalarValue -> Bool
$c/= :: PGScalarValue -> PGScalarValue -> Bool
== :: PGScalarValue -> PGScalarValue -> Bool
$c== :: PGScalarValue -> PGScalarValue -> Bool
Eq)
pgScalarValueToJson :: PGScalarValue -> Value
pgScalarValueToJson :: PGScalarValue -> Value
pgScalarValueToJson = \case
PGValInteger Int32
i -> Int32 -> Value
forall a. ToJSON a => a -> Value
toJSON Int32
i
PGValSmallInt Int16
i -> Int16 -> Value
forall a. ToJSON a => a -> Value
toJSON Int16
i
PGValBigInt Int64
i -> Int64 -> Value
forall a. ToJSON a => a -> Value
toJSON Int64
i
PGValFloat Float
f -> Float -> Value
forall a. ToJSON a => a -> Value
toJSON Float
f
PGValDouble Double
d -> Double -> Value
forall a. ToJSON a => a -> Value
toJSON Double
d
PGValNumeric Scientific
sc -> Scientific -> Value
forall a. ToJSON a => a -> Value
toJSON Scientific
sc
PGValMoney Scientific
m -> Scientific -> Value
forall a. ToJSON a => a -> Value
toJSON Scientific
m
PGValBoolean Bool
b -> Bool -> Value
forall a. ToJSON a => a -> Value
toJSON Bool
b
PGValChar Char
t -> Char -> Value
forall a. ToJSON a => a -> Value
toJSON Char
t
PGValVarchar Text
t -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
PGValText Text
t -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
PGValCitext Text
t -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
PGValDate Day
d -> Day -> Value
forall a. ToJSON a => a -> Value
toJSON Day
d
PGValTimeStamp LocalTime
u -> Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ LocalTime -> Text
forall t. FormatTime t => t -> Text
formatTimestamp LocalTime
u
PGValTimeStampTZ UTCTime
u -> Text -> Value
String (Text -> Value) -> Text -> Value
forall a b. (a -> b) -> a -> b
$ UTCTime -> Text
forall t. FormatTime t => t -> Text
formatTimestamp UTCTime
u
PGValTimeTZ (ZonedTimeOfDay TimeOfDay
tod TimeZone
tz) ->
String -> Value
forall a. ToJSON a => a -> Value
toJSON (TimeOfDay -> String
forall a. Show a => a -> String
show TimeOfDay
tod String -> ShowS
forall a. [a] -> [a] -> [a]
++ TimeZone -> String
timeZoneOffsetString TimeZone
tz)
PGNull PGScalarType
_ -> Value
Null
PGValJSON (Q.JSON Value
j) -> Value
j
PGValJSONB (Q.JSONB Value
j) -> Value
j
PGValGeo GeometryWithCRS
o -> GeometryWithCRS -> Value
forall a. ToJSON a => a -> Value
toJSON GeometryWithCRS
o
PGValRaster RasterWKB
r -> RasterWKB -> Value
forall a. ToJSON a => a -> Value
toJSON RasterWKB
r
PGValUUID UUID
u -> UUID -> Value
forall a. ToJSON a => a -> Value
toJSON UUID
u
PGValLtree Ltree
t -> Ltree -> Value
forall a. ToJSON a => a -> Value
toJSON Ltree
t
PGValLquery Text
t -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
PGValLtxtquery Text
t -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
PGValUnknown Text
t -> Text -> Value
forall a. ToJSON a => a -> Value
toJSON Text
t
PGValArray [PGScalarValue]
a -> [Value] -> Value
forall a. ToJSON a => a -> Value
toJSON ((PGScalarValue -> Value) -> [PGScalarValue] -> [Value]
forall a b. (a -> b) -> [a] -> [b]
map PGScalarValue -> Value
pgScalarValueToJson [PGScalarValue]
a)
textToScalarValue :: Maybe Text -> PGScalarValue
textToScalarValue :: Maybe Text -> PGScalarValue
textToScalarValue = PGScalarValue
-> (Text -> PGScalarValue) -> Maybe Text -> PGScalarValue
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (PGScalarType -> PGScalarValue
PGNull PGScalarType
PGText) Text -> PGScalarValue
PGValText
withConstructorFn :: PGScalarType -> S.SQLExp -> S.SQLExp
withConstructorFn :: PGScalarType -> SQLExp -> SQLExp
withConstructorFn PGScalarType
ty SQLExp
v
| PGScalarType -> Bool
isGeoType PGScalarType
ty = Text -> [SQLExp] -> Maybe OrderByExp -> SQLExp
S.SEFnApp Text
"ST_GeomFromGeoJSON" [SQLExp
v] Maybe OrderByExp
forall a. Maybe a
Nothing
| PGScalarType
ty PGScalarType -> PGScalarType -> Bool
forall a. Eq a => a -> a -> Bool
== PGScalarType
PGRaster = Text -> [SQLExp] -> Maybe OrderByExp -> SQLExp
S.SEFnApp Text
"ST_RastFromHexWKB" [SQLExp
v] Maybe OrderByExp
forall a. Maybe a
Nothing
| Bool
otherwise = SQLExp
v
withScalarTypeAnn :: PGScalarType -> S.SQLExp -> S.SQLExp
withScalarTypeAnn :: PGScalarType -> SQLExp -> SQLExp
withScalarTypeAnn PGScalarType
colTy SQLExp
v = SQLExp -> TypeAnn -> SQLExp
S.SETyAnn SQLExp
v (TypeAnn -> SQLExp)
-> (CollectableType PGScalarType -> TypeAnn)
-> CollectableType PGScalarType
-> SQLExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CollectableType PGScalarType -> TypeAnn
S.mkTypeAnn (CollectableType PGScalarType -> SQLExp)
-> CollectableType PGScalarType -> SQLExp
forall a b. (a -> b) -> a -> b
$ PGScalarType -> CollectableType PGScalarType
forall a. a -> CollectableType a
CollectableTypeScalar PGScalarType
colTy
withTypeAnn :: CollectableType PGScalarType -> S.SQLExp -> S.SQLExp
withTypeAnn :: CollectableType PGScalarType -> SQLExp -> SQLExp
withTypeAnn CollectableType PGScalarType
ty SQLExp
expr = (SQLExp -> TypeAnn -> SQLExp) -> TypeAnn -> SQLExp -> SQLExp
forall a b c. (a -> b -> c) -> b -> a -> c
flip SQLExp -> TypeAnn -> SQLExp
S.SETyAnn (CollectableType PGScalarType -> TypeAnn
S.mkTypeAnn CollectableType PGScalarType
ty) (SQLExp -> SQLExp) -> SQLExp -> SQLExp
forall a b. (a -> b) -> a -> b
$
case CollectableType PGScalarType
ty of
CollectableTypeScalar PGScalarType
baseTy -> PGScalarType -> SQLExp -> SQLExp
withConstructorFn PGScalarType
baseTy SQLExp
expr
CollectableTypeArray PGScalarType
_ -> SQLExp
expr
scientificToInteger :: (Integral i, Bounded i) => Scientific -> AT.Parser i
scientificToInteger :: Scientific -> Parser i
scientificToInteger Scientific
num =
Scientific -> Maybe i
forall i. (Integral i, Bounded i) => Scientific -> Maybe i
toBoundedInteger Scientific
num
Maybe i -> Parser i -> Parser i
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` String -> Parser i
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
( String
"The value " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
num String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" lies outside the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"bounds or is not an integer. Maybe it is a "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"float, or is there integer overflow?"
)
scientificToFloat :: (RealFloat f) => Scientific -> AT.Parser f
scientificToFloat :: Scientific -> Parser f
scientificToFloat Scientific
num =
Scientific -> Either f f
forall a. RealFloat a => Scientific -> Either a a
toBoundedRealFloat Scientific
num
Either f f -> (f -> Parser f) -> Parser f
forall (m :: * -> *) e a.
Applicative m =>
Either e a -> (e -> m a) -> m a
`onLeft` \f
_ ->
String -> Parser f
forall (m :: * -> *) a. MonadFail m => String -> m a
fail
( String
"The value " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Scientific -> String
forall a. Show a => a -> String
show Scientific
num String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" lies outside the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"bounds. Is it overflowing the float bounds?"
)
parsePGValue :: PGScalarType -> Value -> AT.Parser PGScalarValue
parsePGValue :: PGScalarType -> Value -> Parser PGScalarValue
parsePGValue PGScalarType
ty Value
val = case (PGScalarType
ty, Value
val) of
(PGScalarType
_, Value
Null) -> PGScalarValue -> Parser PGScalarValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PGScalarValue -> Parser PGScalarValue)
-> PGScalarValue -> Parser PGScalarValue
forall a b. (a -> b) -> a -> b
$ PGScalarType -> PGScalarValue
PGNull PGScalarType
ty
(PGUnknown Text
_, String Text
t) -> PGScalarValue -> Parser PGScalarValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (PGScalarValue -> Parser PGScalarValue)
-> PGScalarValue -> Parser PGScalarValue
forall a b. (a -> b) -> a -> b
$ Text -> PGScalarValue
PGValUnknown Text
t
(PGScalarType
PGRaster, Value
_) -> Parser PGScalarValue
parseTyped
(PGScalarType
PGLtree, Value
_) -> Parser PGScalarValue
parseTyped
(PGScalarType
_, String Text
t) -> Parser PGScalarValue
parseTyped Parser PGScalarValue
-> Parser PGScalarValue -> Parser PGScalarValue
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> PGScalarValue -> Parser PGScalarValue
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Text -> PGScalarValue
PGValUnknown Text
t)
(PGScalarType
_, Value
_) -> Parser PGScalarValue
parseTyped
where
parseBoundedInt :: forall i. (Integral i, Bounded i) => Value -> AT.Parser i
parseBoundedInt :: Value -> Parser i
parseBoundedInt = String -> (Scientific -> Parser i) -> Value -> Parser i
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific (String
"Integer expected for input type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PGScalarType -> String
forall a. Show a => a -> String
show PGScalarType
ty) Scientific -> Parser i
forall i. (Integral i, Bounded i) => Scientific -> Parser i
scientificToInteger
parseBoundedFloat :: forall a. (RealFloat a) => Value -> AT.Parser a
parseBoundedFloat :: Value -> Parser a
parseBoundedFloat = String -> (Scientific -> Parser a) -> Value -> Parser a
forall a. String -> (Scientific -> Parser a) -> Value -> Parser a
withScientific (String
"Float expected for input type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ PGScalarType -> String
forall a. Show a => a -> String
show PGScalarType
ty) Scientific -> Parser a
forall f. RealFloat f => Scientific -> Parser f
scientificToFloat
parseTyped :: Parser PGScalarValue
parseTyped = case PGScalarType
ty of
PGScalarType
PGSmallInt -> Int16 -> PGScalarValue
PGValSmallInt (Int16 -> PGScalarValue) -> Parser Int16 -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int16
forall i. (Integral i, Bounded i) => Value -> Parser i
parseBoundedInt Value
val
PGScalarType
PGInteger -> Int32 -> PGScalarValue
PGValInteger (Int32 -> PGScalarValue) -> Parser Int32 -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int32
forall i. (Integral i, Bounded i) => Value -> Parser i
parseBoundedInt Value
val
PGScalarType
PGBigInt -> Int64 -> PGScalarValue
PGValBigInt (Int64 -> PGScalarValue) -> Parser Int64 -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int64
forall i. (Integral i, Bounded i) => Value -> Parser i
parseBoundedInt Value
val
PGScalarType
PGSerial -> Int32 -> PGScalarValue
PGValInteger (Int32 -> PGScalarValue) -> Parser Int32 -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int32
forall i. (Integral i, Bounded i) => Value -> Parser i
parseBoundedInt Value
val
PGScalarType
PGBigSerial -> Int64 -> PGScalarValue
PGValBigInt (Int64 -> PGScalarValue) -> Parser Int64 -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Int64
forall i. (Integral i, Bounded i) => Value -> Parser i
parseBoundedInt Value
val
PGScalarType
PGFloat -> Float -> PGScalarValue
PGValFloat (Float -> PGScalarValue) -> Parser Float -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Float
forall a. RealFloat a => Value -> Parser a
parseBoundedFloat Value
val
PGScalarType
PGDouble -> Double -> PGScalarValue
PGValDouble (Double -> PGScalarValue) -> Parser Double -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Double
forall a. RealFloat a => Value -> Parser a
parseBoundedFloat Value
val
PGScalarType
PGNumeric -> Scientific -> PGScalarValue
PGValNumeric (Scientific -> PGScalarValue)
-> Parser Scientific -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Scientific
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGMoney -> Scientific -> PGScalarValue
PGValMoney (Scientific -> PGScalarValue)
-> Parser Scientific -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Scientific
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGBoolean -> Bool -> PGScalarValue
PGValBoolean (Bool -> PGScalarValue) -> Parser Bool -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Bool
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGChar -> Char -> PGScalarValue
PGValChar (Char -> PGScalarValue) -> Parser Char -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Char
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGVarchar -> Text -> PGScalarValue
PGValVarchar (Text -> PGScalarValue) -> Parser Text -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGText -> Text -> PGScalarValue
PGValText (Text -> PGScalarValue) -> Parser Text -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGCitext -> Text -> PGScalarValue
PGValCitext (Text -> PGScalarValue) -> Parser Text -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGDate -> Day -> PGScalarValue
PGValDate (Day -> PGScalarValue) -> Parser Day -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Day
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGTimeStamp -> LocalTime -> PGScalarValue
PGValTimeStamp (LocalTime -> PGScalarValue)
-> Parser LocalTime -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser LocalTime
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGTimeStampTZ -> UTCTime -> PGScalarValue
PGValTimeStampTZ (UTCTime -> PGScalarValue)
-> Parser UTCTime -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser UTCTime
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGTimeTZ -> ZonedTimeOfDay -> PGScalarValue
PGValTimeTZ (ZonedTimeOfDay -> PGScalarValue)
-> Parser ZonedTimeOfDay -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser ZonedTimeOfDay
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGJSON -> JSON -> PGScalarValue
PGValJSON (JSON -> PGScalarValue)
-> (Value -> JSON) -> Value -> PGScalarValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> JSON
Q.JSON (Value -> PGScalarValue) -> Parser Value -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Value
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGJSONB -> JSONB -> PGScalarValue
PGValJSONB (JSONB -> PGScalarValue)
-> (Value -> JSONB) -> Value -> PGScalarValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> JSONB
Q.JSONB (Value -> PGScalarValue) -> Parser Value -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Value
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGGeometry -> GeometryWithCRS -> PGScalarValue
PGValGeo (GeometryWithCRS -> PGScalarValue)
-> Parser GeometryWithCRS -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser GeometryWithCRS
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGGeography -> GeometryWithCRS -> PGScalarValue
PGValGeo (GeometryWithCRS -> PGScalarValue)
-> Parser GeometryWithCRS -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser GeometryWithCRS
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGRaster -> RasterWKB -> PGScalarValue
PGValRaster (RasterWKB -> PGScalarValue)
-> Parser RasterWKB -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser RasterWKB
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGUUID -> UUID -> PGScalarValue
PGValUUID (UUID -> PGScalarValue) -> Parser UUID -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser UUID
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGLtree -> Ltree -> PGScalarValue
PGValLtree (Ltree -> PGScalarValue) -> Parser Ltree -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Ltree
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGLquery -> Text -> PGScalarValue
PGValLquery (Text -> PGScalarValue) -> Parser Text -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGScalarType
PGLtxtquery -> Text -> PGScalarValue
PGValLtxtquery (Text -> PGScalarValue) -> Parser Text -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value -> Parser Text
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val
PGUnknown Text
tyName ->
String -> Parser PGScalarValue
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser PGScalarValue) -> String -> Parser PGScalarValue
forall a b. (a -> b) -> a -> b
$ String
"A string is expected for type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
tyName
PGCompositeScalar Text
tyName ->
String -> Parser PGScalarValue
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser PGScalarValue) -> String -> Parser PGScalarValue
forall a b. (a -> b) -> a -> b
$ String
"A string is expected for type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
tyName
PGEnumScalar Text
tyName ->
String -> Parser PGScalarValue
forall (m :: * -> *) a. MonadFail m => String -> m a
fail (String -> Parser PGScalarValue) -> String -> Parser PGScalarValue
forall a b. (a -> b) -> a -> b
$ String
"A string is expected for type: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Text -> String
T.unpack Text
tyName
PGArray PGScalarType
s -> Value -> Parser [Value]
forall a. FromJSON a => Value -> Parser a
parseJSON Value
val Parser [Value]
-> ([Value] -> Parser PGScalarValue) -> Parser PGScalarValue
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= ([PGScalarValue] -> PGScalarValue)
-> Parser [PGScalarValue] -> Parser PGScalarValue
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [PGScalarValue] -> PGScalarValue
PGValArray (Parser [PGScalarValue] -> Parser PGScalarValue)
-> ([Value] -> Parser [PGScalarValue])
-> [Value]
-> Parser PGScalarValue
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value -> Parser PGScalarValue)
-> [Value] -> Parser [PGScalarValue]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (PGScalarType -> Value -> Parser PGScalarValue
parsePGValue PGScalarType
s)
txtEncodedVal :: PGScalarValue -> TxtEncodedVal
txtEncodedVal :: PGScalarValue -> TxtEncodedVal
txtEncodedVal = \case
PGValInteger Int32
i -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Int32 -> Text
forall a. Show a => a -> Text
tshow Int32
i
PGValSmallInt Int16
i -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Int16 -> Text
forall a. Show a => a -> Text
tshow Int16
i
PGValBigInt Int64
i -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Int64 -> Text
forall a. Show a => a -> Text
tshow Int64
i
PGValFloat Float
f -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Float -> Text
forall a. Show a => a -> Text
tshow Float
f
PGValDouble Double
d -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Double -> Text
forall a. Show a => a -> Text
tshow Double
d
PGValNumeric Scientific
sc -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Scientific -> Text
forall a. Show a => a -> Text
tshow Scientific
sc
PGValMoney Scientific
m -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ FPFormat -> Maybe Int -> Scientific -> String
formatScientific FPFormat
Fixed (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
2) Scientific
m
PGValBoolean Bool
b -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text -> Bool -> Text
forall a. a -> a -> Bool -> a
bool Text
"false" Text
"true" Bool
b
PGValChar Char
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
t
PGValVarchar Text
t -> Text -> TxtEncodedVal
TELit Text
t
PGValText Text
t -> Text -> TxtEncodedVal
TELit Text
t
PGValCitext Text
t -> Text -> TxtEncodedVal
TELit Text
t
PGValDate Day
d -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ Day -> String
showGregorian Day
d
PGValTimeStamp LocalTime
u -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ LocalTime -> Text
forall t. FormatTime t => t -> Text
formatTimestamp LocalTime
u
PGValTimeStampTZ UTCTime
u -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ UTCTime -> Text
forall t. FormatTime t => t -> Text
formatTimestamp UTCTime
u
PGValTimeTZ (ZonedTimeOfDay TimeOfDay
tod TimeZone
tz) ->
Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (TimeOfDay -> String
forall a. Show a => a -> String
show TimeOfDay
tod String -> ShowS
forall a. [a] -> [a] -> [a]
++ TimeZone -> String
timeZoneOffsetString TimeZone
tz)
PGNull PGScalarType
_ ->
TxtEncodedVal
TENull
PGValJSON (Q.JSON Value
j) ->
Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$
Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$
Value -> Text
forall a. ToJSON a => a -> Text
AE.encodeToLazyText Value
j
PGValJSONB (Q.JSONB Value
j) ->
Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$
Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$
Value -> Text
forall a. ToJSON a => a -> Text
AE.encodeToLazyText Value
j
PGValGeo GeometryWithCRS
o ->
Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$
Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$
GeometryWithCRS -> Text
forall a. ToJSON a => a -> Text
AE.encodeToLazyText GeometryWithCRS
o
PGValRaster RasterWKB
r -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Base16 ByteString -> Text
forall a. ToText a => a -> Text
TC.toText (Base16 ByteString -> Text) -> Base16 ByteString -> Text
forall a b. (a -> b) -> a -> b
$ RasterWKB -> Base16 ByteString
getRasterWKB RasterWKB
r
PGValUUID UUID
u -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ UUID -> Text
UUID.toText UUID
u
PGValLtree (Ltree Text
t) -> Text -> TxtEncodedVal
TELit Text
t
PGValLquery Text
t -> Text -> TxtEncodedVal
TELit Text
t
PGValLtxtquery Text
t -> Text -> TxtEncodedVal
TELit Text
t
PGValUnknown Text
t -> Text -> TxtEncodedVal
TELit Text
t
PGValArray [PGScalarValue]
ts -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ [PGScalarValue] -> Text
buildArrayLiteral [PGScalarValue]
ts
binEncoder :: PGScalarValue -> Q.PrepArg
binEncoder :: PGScalarValue -> PrepArg
binEncoder = \case
PGValInteger Int32
i -> Int32 -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Int32
i
PGValSmallInt Int16
i -> Int16 -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Int16
i
PGValBigInt Int64
i -> Int64 -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Int64
i
PGValFloat Float
f -> Float -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Float
f
PGValDouble Double
d -> Double -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Double
d
PGValNumeric Scientific
sc -> Scientific -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Scientific
sc
PGValMoney Scientific
m -> Scientific -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Scientific
m
PGValBoolean Bool
b -> Bool -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Bool
b
PGValChar Char
t -> Char -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Char
t
PGValVarchar Text
t -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Text
t
PGValText Text
t -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Text
t
PGValCitext Text
t -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Text
t
PGValDate Day
d -> Day -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Day
d
PGValTimeStamp LocalTime
u -> LocalTime -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal LocalTime
u
PGValTimeStampTZ UTCTime
u -> UTCTime -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal UTCTime
u
PGValTimeTZ (ZonedTimeOfDay TimeOfDay
t TimeZone
z) -> Oid
-> ((TimeOfDay, TimeZone) -> Encoding)
-> (TimeOfDay, TimeZone)
-> PrepArg
forall a. Oid -> (a -> Encoding) -> a -> PrepArg
Q.toPrepValHelper Oid
PTI.timetz (TimeOfDay, TimeZone) -> Encoding
PE.timetz_int (TimeOfDay
t, TimeZone
z)
PGNull PGScalarType
ty -> (PGScalarType -> Oid
pgTypeOid PGScalarType
ty, Maybe (ByteString, Format)
forall a. Maybe a
Nothing)
PGValJSON JSON
u -> JSON -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal JSON
u
PGValJSONB JSONB
u -> JSONB -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal JSONB
u
PGValGeo GeometryWithCRS
o -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal (Text -> PrepArg) -> Text -> PrepArg
forall a b. (a -> b) -> a -> b
$ Text -> Text
TL.toStrict (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ GeometryWithCRS -> Text
forall a. ToJSON a => a -> Text
AE.encodeToLazyText GeometryWithCRS
o
PGValRaster RasterWKB
r -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal (Text -> PrepArg) -> Text -> PrepArg
forall a b. (a -> b) -> a -> b
$ Base16 ByteString -> Text
forall a. ToText a => a -> Text
TC.toText (Base16 ByteString -> Text) -> Base16 ByteString -> Text
forall a b. (a -> b) -> a -> b
$ RasterWKB -> Base16 ByteString
getRasterWKB RasterWKB
r
PGValUUID UUID
u -> UUID -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal UUID
u
PGValLtree (Ltree Text
t) -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Text
t
PGValLquery Text
t -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Text
t
PGValLtxtquery Text
t -> Text -> PrepArg
forall a. ToPrepArg a => a -> PrepArg
Q.toPrepVal Text
t
PGValUnknown Text
t -> (Oid
PTI.auto, (ByteString, Format) -> Maybe (ByteString, Format)
forall a. a -> Maybe a
Just (Text -> ByteString
TE.encodeUtf8 Text
t, Format
PQ.Text))
PGValArray [PGScalarValue]
s -> (Oid
PTI.auto, (ByteString, Format) -> Maybe (ByteString, Format)
forall a. a -> Maybe a
Just (Text -> ByteString
TE.encodeUtf8 (Text -> ByteString) -> Text -> ByteString
forall a b. (a -> b) -> a -> b
$ [PGScalarValue] -> Text
buildArrayLiteral [PGScalarValue]
s, Format
PQ.Text))
formatTimestamp :: FormatTime t => t -> Text
formatTimestamp :: t -> Text
formatTimestamp = String -> Text
T.pack (String -> Text) -> (t -> String) -> t -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TimeLocale -> String -> t -> String
forall t. FormatTime t => TimeLocale -> String -> t -> String
formatTime TimeLocale
defaultTimeLocale String
"%0Y-%m-%dT%T%QZ"
txtEncoder :: PGScalarValue -> S.SQLExp
txtEncoder :: PGScalarValue -> SQLExp
txtEncoder PGScalarValue
colVal = case PGScalarValue -> TxtEncodedVal
txtEncodedVal PGScalarValue
colVal of
TxtEncodedVal
TENull -> SQLExp
S.SENull
TELit Text
t -> Text -> SQLExp
S.SELit Text
t
buildArrayLiteral :: [PGScalarValue] -> Text
buildArrayLiteral :: [PGScalarValue] -> Text
buildArrayLiteral [PGScalarValue]
ts =
[Text] -> Text
T.concat [Text
"{", Text -> [Text] -> Text
T.intercalate Text
"," ((PGScalarValue -> Text) -> [PGScalarValue] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (TxtEncodedVal -> Text
inner (TxtEncodedVal -> Text)
-> (PGScalarValue -> TxtEncodedVal) -> PGScalarValue -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGScalarValue -> TxtEncodedVal
encodeElement) [PGScalarValue]
ts), Text
"}"]
where
encodeElement :: PGScalarValue -> TxtEncodedVal
encodeElement = \case
PGValChar Char
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Char -> Text
T.singleton Char
t
PGValVarchar Text
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow Text
t
PGValText Text
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow Text
t
PGValCitext Text
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow Text
t
PGValLquery Text
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow Text
t
PGValLtxtquery Text
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow Text
t
PGValUnknown Text
t -> Text -> TxtEncodedVal
TELit (Text -> TxtEncodedVal) -> Text -> TxtEncodedVal
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a. Show a => a -> Text
tshow Text
t
PGScalarValue
other -> PGScalarValue -> TxtEncodedVal
txtEncodedVal PGScalarValue
other
inner :: TxtEncodedVal -> Text
inner = \case
TxtEncodedVal
TENull -> Text
"null"
TELit Text
t -> Text
t
toPrepParam :: Int -> PGScalarType -> S.SQLExp
toPrepParam :: Int -> PGScalarType -> SQLExp
toPrepParam Int
i PGScalarType
ty =
PGScalarType -> SQLExp -> SQLExp
withScalarTypeAnn PGScalarType
ty (SQLExp -> SQLExp) -> (SQLExp -> SQLExp) -> SQLExp -> SQLExp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PGScalarType -> SQLExp -> SQLExp
withConstructorFn PGScalarType
ty (SQLExp -> SQLExp) -> SQLExp -> SQLExp
forall a b. (a -> b) -> a -> b
$ Int -> SQLExp
S.SEPrep Int
i