{-# OPTIONS_HADDOCK not-home #-}

{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE DataKinds #-}

module Opaleye.Internal.PGTypesExternal
  (module Opaleye.Internal.PGTypesExternal, IsSqlType(..)) where

import           Opaleye.Internal.Column (Field_, Field)
import qualified Opaleye.Internal.Column as C
import qualified Opaleye.Internal.PGTypes as IPT
import           Opaleye.Internal.PGTypes (IsSqlType(..))

import qualified Opaleye.Internal.HaskellDB.PrimQuery as HPQ
import qualified Opaleye.Internal.HaskellDB.Sql.Default as HSD

import qualified Data.CaseInsensitive as CI
import qualified Data.Aeson as Ae
import qualified Data.Text as SText
import qualified Data.Text.Lazy as LText
import qualified Data.ByteString as SByteString
import qualified Data.ByteString.Lazy as LByteString
import           Data.Scientific as Sci
import qualified Data.Time.Compat as Time
import qualified Data.UUID as UUID

import           Data.Int (Int64)

import qualified Database.PostgreSQL.Simple.Range as R

instance C.SqlNum SqlFloat8 where
  sqlFromInteger :: Integer -> Field SqlFloat8
sqlFromInteger = Double -> Field SqlFloat8
pgDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger

instance C.SqlNum SqlInt4 where
  sqlFromInteger :: Integer -> Field SqlInt4
sqlFromInteger = Int -> Field SqlInt4
pgInt4 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger

instance C.SqlNum SqlInt8 where
  sqlFromInteger :: Integer -> Field SqlInt8
sqlFromInteger = Int64 -> Field SqlInt8
pgInt8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger

instance C.SqlNum SqlNumeric where
  sqlFromInteger :: Integer -> Field SqlNumeric
sqlFromInteger = Scientific -> Field SqlNumeric
pgNumeric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger

instance C.SqlFractional SqlFloat8 where
  sqlFromRational :: Rational -> Field SqlFloat8
sqlFromRational = Double -> Field SqlFloat8
pgDouble forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Fractional a => Rational -> a
fromRational

instance C.SqlIntegral SqlInt2
instance C.SqlIntegral SqlNumeric
instance C.SqlIntegral SqlInt4
instance C.SqlIntegral SqlInt8

instance C.SqlString SqlText where
  sqlFromString :: String -> Field SqlText
sqlFromString = String -> Field SqlText
pgString

instance C.SqlString SqlVarcharN where
  sqlFromString :: String -> Field SqlVarcharN
sqlFromString = String -> Field SqlVarcharN
sqlStringVarcharN

instance C.SqlString SqlCitext where
  sqlFromString :: String -> Field SqlCitext
sqlFromString = CI Text -> Field SqlCitext
pgCiLazyText forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. FoldCase s => s -> CI s
CI.mk forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
LText.pack

-- * Creating SQL values

pgString :: String -> Field PGText
pgString :: String -> Field SqlText
pgString = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit

pgLazyByteString :: LByteString.ByteString -> Field PGBytea
pgLazyByteString :: ByteString -> Field PGBytea
pgLazyByteString = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Literal
HPQ.ByteStringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LByteString.toStrict

pgStrictByteString :: SByteString.ByteString -> Field PGBytea
pgStrictByteString :: ByteString -> Field PGBytea
pgStrictByteString = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Literal
HPQ.ByteStringLit

pgStrictText :: SText.Text -> Field PGText
pgStrictText :: Text -> Field SqlText
pgStrictText = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
SText.unpack

pgLazyText :: LText.Text -> Field PGText
pgLazyText :: Text -> Field SqlText
pgLazyText = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
LText.unpack

sqlStringVarcharN :: String -> Field SqlVarcharN
sqlStringVarcharN :: String -> Field SqlVarcharN
sqlStringVarcharN = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit

sqlStrictTextVarcharN :: SText.Text -> Field SqlVarcharN
sqlStrictTextVarcharN :: Text -> Field SqlVarcharN
sqlStrictTextVarcharN = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
SText.unpack

sqlLazyTextVarcharN :: LText.Text -> Field SqlVarcharN
sqlLazyTextVarcharN :: Text -> Field SqlVarcharN
sqlLazyTextVarcharN = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
LText.unpack

pgNumeric :: Sci.Scientific -> Field PGNumeric
pgNumeric :: Scientific -> Field SqlNumeric
pgNumeric = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Literal
HPQ.NumericLit

pgInt4 :: Int -> Field PGInt4
pgInt4 :: Int -> Field SqlInt4
pgInt4 = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
HPQ.IntegerLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

pgInt8 :: Int64 -> Field PGInt8
pgInt8 :: Int64 -> Field SqlInt8
pgInt8 = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
HPQ.IntegerLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (Integral a, Num b) => a -> b
fromIntegral

pgDouble :: Double -> Field PGFloat8
pgDouble :: Double -> Field SqlFloat8
pgDouble = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Literal
HPQ.DoubleLit

pgBool :: Bool -> Field PGBool
pgBool :: Bool -> Field PGBool
pgBool = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Literal
HPQ.BoolLit

pgUUID :: UUID.UUID -> Field PGUuid
pgUUID :: UUID -> Field PGUuid
pgUUID = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
UUID.toString

pgDay :: Time.Day -> Field PGDate
pgDay :: Day -> Field PGDate
pgDay = forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"date"

pgUTCTime :: Time.UTCTime -> Field PGTimestamptz
pgUTCTime :: UTCTime -> Field PGTimestamptz
pgUTCTime = forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"timestamptz"

pgLocalTime :: Time.LocalTime -> Field PGTimestamp
pgLocalTime :: LocalTime -> Field PGTimestamp
pgLocalTime = forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"timestamp"

pgZonedTime :: Time.ZonedTime -> Field PGTimestamptz
pgZonedTime :: ZonedTime -> Field PGTimestamptz
pgZonedTime = forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"timestamptz"

pgTimeOfDay :: Time.TimeOfDay -> Field PGTime
pgTimeOfDay :: TimeOfDay -> Field PGTime
pgTimeOfDay = forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"time"

-- "We recommend not using the type time with time zone"
-- http://www.postgresql.org/docs/8.3/static/datatype-datetime.html

sqlInterval :: Time.CalendarDiffTime -> Field PGInterval
sqlInterval :: CalendarDiffTime -> Field PGInterval
sqlInterval = forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"interval"

pgCiStrictText :: CI.CI SText.Text -> Field PGCitext
pgCiStrictText :: CI Text -> Field SqlCitext
pgCiStrictText = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
SText.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. CI s -> s
CI.original

pgCiLazyText :: CI.CI LText.Text -> Field PGCitext
pgCiLazyText :: CI Text -> Field SqlCitext
pgCiLazyText = forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
LText.unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. CI s -> s
CI.original

-- No CI String instance since postgresql-simple doesn't define
-- FromField (CI String)

-- The json data type was introduced in PostgreSQL version 9.2
-- JSON values must be SQL string quoted
pgJSON :: String -> Field PGJson
pgJSON :: String -> Field PGJson
pgJSON = forall (n :: Nullability) c. String -> String -> Field_ n c
IPT.castToType String
"json" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
HSD.quote

pgStrictJSON :: SByteString.ByteString -> Field PGJson
pgStrictJSON :: ByteString -> Field PGJson
pgStrictJSON = String -> Field PGJson
pgJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
IPT.strictDecodeUtf8

pgLazyJSON :: LByteString.ByteString -> Field PGJson
pgLazyJSON :: ByteString -> Field PGJson
pgLazyJSON = String -> Field PGJson
pgJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
IPT.lazyDecodeUtf8

pgValueJSON :: Ae.ToJSON a => a -> Field PGJson
pgValueJSON :: forall a. ToJSON a => a -> Field PGJson
pgValueJSON = ByteString -> Field PGJson
pgLazyJSON forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
Ae.encode

-- The jsonb data type was introduced in PostgreSQL version 9.4
-- JSONB values must be SQL string quoted
--
-- TODO: We need to add literal JSON and JSONB types so we can say
-- `castToTypeTyped JSONB` rather than `castToType "jsonb"`.
pgJSONB :: String -> Field PGJsonb
pgJSONB :: String -> Field PGJsonb
pgJSONB = forall (n :: Nullability) c. String -> String -> Field_ n c
IPT.castToType String
"jsonb" forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> String
HSD.quote

pgStrictJSONB :: SByteString.ByteString -> Field PGJsonb
pgStrictJSONB :: ByteString -> Field PGJsonb
pgStrictJSONB = String -> Field PGJsonb
pgJSONB forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
IPT.strictDecodeUtf8

pgLazyJSONB :: LByteString.ByteString -> Field PGJsonb
pgLazyJSONB :: ByteString -> Field PGJsonb
pgLazyJSONB = String -> Field PGJsonb
pgJSONB forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
IPT.lazyDecodeUtf8

pgValueJSONB :: Ae.ToJSON a => a -> Field PGJsonb
pgValueJSONB :: forall a. ToJSON a => a -> Field PGJsonb
pgValueJSONB = ByteString -> Field PGJsonb
pgLazyJSONB forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ToJSON a => a -> ByteString
Ae.encode

pgArray :: forall a b n. IsSqlType b
        => (a -> Field_ n b) -> [a] -> Field (SqlArray_ n b)
pgArray :: forall a b (n :: Nullability).
IsSqlType b =>
(a -> Field_ n b) -> [a] -> Field (SqlArray_ n b)
pgArray a -> Field_ n b
pgEl [a]
xs = forall (n :: Nullability) a b. String -> Field_ n a -> Field_ n b
C.unsafeCast String
arrayTy forall a b. (a -> b) -> a -> b
$
  forall (n :: Nullability) sqlType. PrimExpr -> Field_ n sqlType
C.Column ([PrimExpr] -> PrimExpr
HPQ.ArrayExpr (forall a b. (a -> b) -> [a] -> [b]
map a -> PrimExpr
oneEl [a]
xs))
  where
    oneEl :: a -> PrimExpr
oneEl = forall (n :: Nullability) a. Field_ n a -> PrimExpr
C.unColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Field_ n b
pgEl
    arrayTy :: String
arrayTy = forall sqlType (proxy :: * -> *).
IsSqlType sqlType =>
proxy sqlType -> String
showSqlType ([] :: [SqlArray_ n b])

pgRange :: forall a b n n'. IsRangeType b
        => (a -> Field_ n b) -> R.RangeBound a -> R.RangeBound a
        -> Field_ n' (SqlRange b)
pgRange :: forall a b (n :: Nullability) (n' :: Nullability).
IsRangeType b =>
(a -> Field_ n b)
-> RangeBound a -> RangeBound a -> Field_ n' (SqlRange b)
pgRange a -> Field_ n b
pgEl RangeBound a
start RangeBound a
end =
  forall (n :: Nullability) sqlType. PrimExpr -> Field_ n sqlType
C.Column (String -> BoundExpr -> BoundExpr -> PrimExpr
HPQ.RangeExpr (forall pgType (proxy :: * -> *).
IsRangeType pgType =>
proxy pgType -> String
showRangeType ([] :: [b])) (RangeBound a -> BoundExpr
oneEl RangeBound a
start) (RangeBound a -> BoundExpr
oneEl RangeBound a
end))
  where oneEl :: RangeBound a -> BoundExpr
oneEl (R.Inclusive a
a) = PrimExpr -> BoundExpr
HPQ.Inclusive forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) a. Field_ n a -> PrimExpr
C.unColumn forall a b. (a -> b) -> a -> b
$ a -> Field_ n b
pgEl a
a
        oneEl (R.Exclusive a
a) = PrimExpr -> BoundExpr
HPQ.Exclusive forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) a. Field_ n a -> PrimExpr
C.unColumn forall a b. (a -> b) -> a -> b
$ a -> Field_ n b
pgEl a
a
        oneEl RangeBound a
R.NegInfinity   = BoundExpr
HPQ.NegInfinity
        oneEl RangeBound a
R.PosInfinity   = BoundExpr
HPQ.PosInfinity

instance IsSqlType SqlBool where
  showSqlType :: forall (proxy :: * -> *). proxy PGBool -> String
showSqlType proxy PGBool
_ = String
"boolean"
instance IsSqlType SqlDate where
  showSqlType :: forall (proxy :: * -> *). proxy PGDate -> String
showSqlType proxy PGDate
_ = String
"date"
instance IsSqlType SqlFloat4 where
  showSqlType :: forall (proxy :: * -> *). proxy SqlFloat4 -> String
showSqlType proxy SqlFloat4
_ = String
"real"
instance IsSqlType SqlFloat8 where
  showSqlType :: forall (proxy :: * -> *). proxy SqlFloat8 -> String
showSqlType proxy SqlFloat8
_ = String
"double precision"
instance IsSqlType SqlInt8 where
  showSqlType :: forall (proxy :: * -> *). proxy SqlInt8 -> String
showSqlType proxy SqlInt8
_ = String
"bigint"
instance IsSqlType SqlInt4 where
  showSqlType :: forall (proxy :: * -> *). proxy SqlInt4 -> String
showSqlType proxy SqlInt4
_ = String
"integer"
instance IsSqlType SqlInt2 where
  showSqlType :: forall (proxy :: * -> *). proxy SqlInt2 -> String
showSqlType proxy SqlInt2
_ = String
"smallint"
instance IsSqlType SqlInterval where
  showSqlType :: forall (proxy :: * -> *). proxy PGInterval -> String
showSqlType proxy PGInterval
_ = String
"interval"
instance IsSqlType SqlNumeric where
  showSqlType :: forall (proxy :: * -> *). proxy SqlNumeric -> String
showSqlType proxy SqlNumeric
_ = String
"numeric"
instance IsSqlType SqlText where
  showSqlType :: forall (proxy :: * -> *). proxy SqlText -> String
showSqlType proxy SqlText
_ = String
"text"
instance IsSqlType SqlVarcharN where
  showSqlType :: forall (proxy :: * -> *). proxy SqlVarcharN -> String
showSqlType proxy SqlVarcharN
_ = String
"varchar"
instance IsSqlType SqlTime where
  showSqlType :: forall (proxy :: * -> *). proxy PGTime -> String
showSqlType proxy PGTime
_ = String
"time"
instance IsSqlType SqlTimestamp where
  showSqlType :: forall (proxy :: * -> *). proxy PGTimestamp -> String
showSqlType proxy PGTimestamp
_ = String
"timestamp"
instance IsSqlType SqlTimestamptz where
  showSqlType :: forall (proxy :: * -> *). proxy PGTimestamptz -> String
showSqlType proxy PGTimestamptz
_ = String
"timestamp with time zone"
instance IsSqlType SqlUuid where
  showSqlType :: forall (proxy :: * -> *). proxy PGUuid -> String
showSqlType proxy PGUuid
_ = String
"uuid"
instance IsSqlType SqlCitext where
  showSqlType :: forall (proxy :: * -> *). proxy SqlCitext -> String
showSqlType proxy SqlCitext
_ =  String
"citext"
instance IsSqlType SqlBytea where
  showSqlType :: forall (proxy :: * -> *). proxy PGBytea -> String
showSqlType proxy PGBytea
_ = String
"bytea"
instance IsSqlType a => IsSqlType (SqlArray_ n a) where
  showSqlType :: forall (proxy :: * -> *). proxy (SqlArray_ n a) -> String
showSqlType proxy (SqlArray_ n a)
_ = forall sqlType (proxy :: * -> *).
IsSqlType sqlType =>
proxy sqlType -> String
showSqlType ([] :: [a]) forall a. [a] -> [a] -> [a]
++ String
"[]"
instance IsSqlType SqlJson where
  showSqlType :: forall (proxy :: * -> *). proxy PGJson -> String
showSqlType proxy PGJson
_ = String
"json"
instance IsSqlType SqlJsonb where
  showSqlType :: forall (proxy :: * -> *). proxy PGJsonb -> String
showSqlType proxy PGJsonb
_ = String
"jsonb"
instance IsRangeType a => IsSqlType (SqlRange a) where
  showSqlType :: forall (proxy :: * -> *). proxy (SqlRange a) -> String
showSqlType proxy (SqlRange a)
_ = forall pgType (proxy :: * -> *).
IsRangeType pgType =>
proxy pgType -> String
showRangeType ([] :: [a])

class IsSqlType pgType => IsRangeType pgType where
  showRangeType :: proxy pgType -> String

instance IsRangeType SqlInt4 where
  showRangeType :: forall (proxy :: * -> *). proxy SqlInt4 -> String
showRangeType proxy SqlInt4
_ = String
"int4range"

instance IsRangeType SqlInt8 where
  showRangeType :: forall (proxy :: * -> *). proxy SqlInt8 -> String
showRangeType proxy SqlInt8
_ = String
"int8range"

instance IsRangeType SqlNumeric where
  showRangeType :: forall (proxy :: * -> *). proxy SqlNumeric -> String
showRangeType proxy SqlNumeric
_ = String
"numrange"

instance IsRangeType SqlTimestamp where
  showRangeType :: forall (proxy :: * -> *). proxy PGTimestamp -> String
showRangeType proxy PGTimestamp
_ = String
"tsrange"

instance IsRangeType SqlTimestamptz where
  showRangeType :: forall (proxy :: * -> *). proxy PGTimestamptz -> String
showRangeType proxy PGTimestamptz
_ = String
"tstzrange"

instance IsRangeType SqlDate where
  showRangeType :: forall (proxy :: * -> *). proxy PGDate -> String
showRangeType proxy PGDate
_ = String
"daterange"

-- * SQL datatypes

data SqlBool
data SqlDate
data SqlFloat4
data SqlFloat8
data SqlInt8
data SqlInt4
data SqlInt2
-- | Requires you to configure @intervalstyle@ as @iso_8601@.
--
-- You can configure @intervalstyle@ on every connection with a @SET@ command,
-- but for better performance you may want to configure it permanently in the
-- file found with @SHOW config_file;@.
data SqlInterval
data SqlNumeric
data SqlText
-- | @VARCHAR(n)@ for any @n@.  Opaleye does not do anything to check
-- that the @n@ you choose is correctly adhered to!
data SqlVarcharN
data SqlTime
data SqlTimestamp
-- | Be careful if you use Haskell's `Time.ZonedTime` with
-- @SqlTimestamptz@. A Postgres @timestamptz@ does not actually
-- contain any time zone.  It is just a UTC time that is automatically
-- converted to or from local time on certain occasions, according to
-- the [timezone setting of the
-- server](https://www.postgresql.org/docs/9.1/runtime-config-client.html#GUC-TIMEZONE).
-- Therefore, although when you roundtrip an input 'Time.ZonedTime' to
-- obtain an output 'Time.ZonedTime' they each refer to the same
-- instant in time, the time zone attached to the output will not
-- necessarily the same as the time zone attached to the input.
data SqlTimestamptz
data SqlUuid
data SqlCitext
data SqlArray_ (n :: C.Nullability) a
type SqlArray = SqlArray_ C.NonNullable
data SqlBytea
data SqlJson
data SqlJsonb
data SqlRange a

type PGBool = SqlBool
type PGDate = SqlDate
type PGFloat4 = SqlFloat4
type PGFloat8 = SqlFloat8
type PGInt8 = SqlInt8
type PGInt4 = SqlInt4
type PGInt2 = SqlInt2
type PGInterval = SqlInterval
type PGNumeric = SqlNumeric
type PGText = SqlText
type PGTime = SqlTime
type PGTimestamp = SqlTimestamp
type PGTimestamptz = SqlTimestamptz
type PGUuid = SqlUuid
type PGCitext = SqlCitext
type PGArray = SqlArray
type PGBytea = SqlBytea
type PGJson = SqlJson
type PGJsonb = SqlJsonb
type PGRange = SqlRange