{-# 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 (Double -> Field SqlFloat8)
-> (Integer -> Double) -> Integer -> Field SqlFloat8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Double
forall a. Num a => Integer -> a
fromInteger
instance C.SqlNum SqlInt4 where
sqlFromInteger :: Integer -> Field SqlInt4
sqlFromInteger = Int -> Field SqlInt4
pgInt4 (Int -> Field SqlInt4)
-> (Integer -> Int) -> Integer -> Field SqlInt4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int
forall a. Num a => Integer -> a
fromInteger
instance C.SqlNum SqlInt8 where
sqlFromInteger :: Integer -> Field SqlInt8
sqlFromInteger = Int64 -> Field SqlInt8
pgInt8 (Int64 -> Field SqlInt8)
-> (Integer -> Int64) -> Integer -> Field SqlInt8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Int64
forall a. Num a => Integer -> a
fromInteger
instance C.SqlNum SqlNumeric where
sqlFromInteger :: Integer -> Field SqlNumeric
sqlFromInteger = Scientific -> Field SqlNumeric
pgNumeric (Scientific -> Field SqlNumeric)
-> (Integer -> Scientific) -> Integer -> Field SqlNumeric
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Scientific
forall a. Num a => Integer -> a
fromInteger
instance C.SqlFractional SqlFloat8 where
sqlFromRational :: Rational -> Field SqlFloat8
sqlFromRational = Double -> Field SqlFloat8
pgDouble (Double -> Field SqlFloat8)
-> (Rational -> Double) -> Rational -> Field SqlFloat8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Rational -> Double
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 (CI Text -> Field SqlCitext)
-> (String -> CI Text) -> String -> Field SqlCitext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> CI Text
forall s. FoldCase s => s -> CI s
CI.mk (Text -> CI Text) -> (String -> Text) -> String -> CI Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
LText.pack
pgString :: String -> Field PGText
pgString :: String -> Field SqlText
pgString = Literal -> Field SqlText
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlText)
-> (String -> Literal) -> String -> Field SqlText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit
pgLazyByteString :: LByteString.ByteString -> Field PGBytea
pgLazyByteString :: ByteString -> Field PGBytea
pgLazyByteString = Literal -> Field PGBytea
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field PGBytea)
-> (ByteString -> Literal) -> ByteString -> Field PGBytea
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Literal
HPQ.ByteStringLit (ByteString -> Literal)
-> (ByteString -> ByteString) -> ByteString -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
LByteString.toStrict
pgStrictByteString :: SByteString.ByteString -> Field PGBytea
pgStrictByteString :: ByteString -> Field PGBytea
pgStrictByteString = Literal -> Field PGBytea
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field PGBytea)
-> (ByteString -> Literal) -> ByteString -> Field PGBytea
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Literal
HPQ.ByteStringLit
pgStrictText :: SText.Text -> Field PGText
pgStrictText :: Text -> Field SqlText
pgStrictText = Literal -> Field SqlText
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlText)
-> (Text -> Literal) -> Text -> Field SqlText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (Text -> String) -> Text -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
SText.unpack
pgLazyText :: LText.Text -> Field PGText
pgLazyText :: Text -> Field SqlText
pgLazyText = Literal -> Field SqlText
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlText)
-> (Text -> Literal) -> Text -> Field SqlText
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (Text -> String) -> Text -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
LText.unpack
sqlStringVarcharN :: String -> Field SqlVarcharN
sqlStringVarcharN :: String -> Field SqlVarcharN
sqlStringVarcharN = Literal -> Field SqlVarcharN
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlVarcharN)
-> (String -> Literal) -> String -> Field SqlVarcharN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit
sqlStrictTextVarcharN :: SText.Text -> Field SqlVarcharN
sqlStrictTextVarcharN :: Text -> Field SqlVarcharN
sqlStrictTextVarcharN = Literal -> Field SqlVarcharN
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlVarcharN)
-> (Text -> Literal) -> Text -> Field SqlVarcharN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (Text -> String) -> Text -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
SText.unpack
sqlLazyTextVarcharN :: LText.Text -> Field SqlVarcharN
sqlLazyTextVarcharN :: Text -> Field SqlVarcharN
sqlLazyTextVarcharN = Literal -> Field SqlVarcharN
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlVarcharN)
-> (Text -> Literal) -> Text -> Field SqlVarcharN
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (Text -> String) -> Text -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
LText.unpack
pgNumeric :: Sci.Scientific -> Field PGNumeric
pgNumeric :: Scientific -> Field SqlNumeric
pgNumeric = Literal -> Field SqlNumeric
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlNumeric)
-> (Scientific -> Literal) -> Scientific -> Field SqlNumeric
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Scientific -> Literal
HPQ.NumericLit
pgInt4 :: Int -> Field PGInt4
pgInt4 :: Int -> Field SqlInt4
pgInt4 = Literal -> Field SqlInt4
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlInt4)
-> (Int -> Literal) -> Int -> Field SqlInt4
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
HPQ.IntegerLit (Integer -> Literal) -> (Int -> Integer) -> Int -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
pgInt8 :: Int64 -> Field PGInt8
pgInt8 :: Int64 -> Field SqlInt8
pgInt8 = Literal -> Field SqlInt8
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlInt8)
-> (Int64 -> Literal) -> Int64 -> Field SqlInt8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Literal
HPQ.IntegerLit (Integer -> Literal) -> (Int64 -> Integer) -> Int64 -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral
pgDouble :: Double -> Field PGFloat8
pgDouble :: Double -> Field SqlFloat8
pgDouble = Literal -> Field SqlFloat8
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlFloat8)
-> (Double -> Literal) -> Double -> Field SqlFloat8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Literal
HPQ.DoubleLit
pgBool :: Bool -> Field PGBool
pgBool :: Bool -> Field PGBool
pgBool = Literal -> Field PGBool
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field PGBool)
-> (Bool -> Literal) -> Bool -> Field PGBool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Literal
HPQ.BoolLit
pgUUID :: UUID.UUID -> Field PGUuid
pgUUID :: UUID -> Field PGUuid
pgUUID = Literal -> Field PGUuid
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field PGUuid)
-> (UUID -> Literal) -> UUID -> Field PGUuid
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (UUID -> String) -> UUID -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UUID -> String
UUID.toString
pgDay :: Time.Day -> Field PGDate
pgDay :: Day -> Field PGDate
pgDay = String -> Day -> Field PGDate
forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"date"
pgUTCTime :: Time.UTCTime -> Field PGTimestamptz
pgUTCTime :: UTCTime -> Field PGTimestamptz
pgUTCTime = String -> UTCTime -> Field PGTimestamptz
forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"timestamptz"
pgLocalTime :: Time.LocalTime -> Field PGTimestamp
pgLocalTime :: LocalTime -> Field PGTimestamp
pgLocalTime = String -> LocalTime -> Field PGTimestamp
forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"timestamp"
pgZonedTime :: Time.ZonedTime -> Field PGTimestamptz
pgZonedTime :: ZonedTime -> Field PGTimestamptz
pgZonedTime = String -> ZonedTime -> Field PGTimestamptz
forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"timestamptz"
pgTimeOfDay :: Time.TimeOfDay -> Field PGTime
pgTimeOfDay :: TimeOfDay -> Field PGTime
pgTimeOfDay = String -> TimeOfDay -> Field PGTime
forall t c. ISO8601 t => String -> t -> Field c
IPT.unsafePgFormatTime String
"time"
sqlInterval :: Time.CalendarDiffTime -> Field PGInterval
sqlInterval :: CalendarDiffTime -> Field PGInterval
sqlInterval = String -> CalendarDiffTime -> Field PGInterval
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 = Literal -> Field SqlCitext
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlCitext)
-> (CI Text -> Literal) -> CI Text -> Field SqlCitext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (CI Text -> String) -> CI Text -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
SText.unpack (Text -> String) -> (CI Text -> Text) -> CI Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI Text -> Text
forall s. CI s -> s
CI.original
pgCiLazyText :: CI.CI LText.Text -> Field PGCitext
pgCiLazyText :: CI Text -> Field SqlCitext
pgCiLazyText = Literal -> Field SqlCitext
forall a. IsSqlType a => Literal -> Field a
IPT.literalColumn (Literal -> Field SqlCitext)
-> (CI Text -> Literal) -> CI Text -> Field SqlCitext
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Literal
HPQ.StringLit (String -> Literal) -> (CI Text -> String) -> CI Text -> Literal
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
LText.unpack (Text -> String) -> (CI Text -> Text) -> CI Text -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CI Text -> Text
forall s. CI s -> s
CI.original
pgJSON :: String -> Field PGJson
pgJSON :: String -> Field PGJson
pgJSON = String -> String -> Field PGJson
forall (n :: Nullability) c. String -> String -> Field_ n c
IPT.castToType String
"json" (String -> Field PGJson)
-> (String -> String) -> String -> Field PGJson
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 (String -> Field PGJson)
-> (ByteString -> String) -> ByteString -> Field 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 (String -> Field PGJson)
-> (ByteString -> String) -> ByteString -> Field PGJson
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
IPT.lazyDecodeUtf8
pgValueJSON :: Ae.ToJSON a => a -> Field PGJson
pgValueJSON :: a -> Field PGJson
pgValueJSON = ByteString -> Field PGJson
pgLazyJSON (ByteString -> Field PGJson)
-> (a -> ByteString) -> a -> Field PGJson
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
forall a. ToJSON a => a -> ByteString
Ae.encode
pgJSONB :: String -> Field PGJsonb
pgJSONB :: String -> Field PGJsonb
pgJSONB = String -> String -> Field PGJsonb
forall (n :: Nullability) c. String -> String -> Field_ n c
IPT.castToType String
"jsonb" (String -> Field PGJsonb)
-> (String -> String) -> String -> Field PGJsonb
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 (String -> Field PGJsonb)
-> (ByteString -> String) -> ByteString -> Field 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 (String -> Field PGJsonb)
-> (ByteString -> String) -> ByteString -> Field PGJsonb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> String
IPT.lazyDecodeUtf8
pgValueJSONB :: Ae.ToJSON a => a -> Field PGJsonb
pgValueJSONB :: a -> Field PGJsonb
pgValueJSONB = ByteString -> Field PGJsonb
pgLazyJSONB (ByteString -> Field PGJsonb)
-> (a -> ByteString) -> a -> Field PGJsonb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ByteString
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 :: (a -> Field_ n b) -> [a] -> Field (SqlArray_ n b)
pgArray a -> Field_ n b
pgEl [a]
xs = String -> Field_ 'NonNullable Any -> Field (SqlArray_ n b)
forall (n' :: Nullability) a b.
String -> Field_ n' a -> Field_ n' b
C.unsafeCast String
arrayTy (Field_ 'NonNullable Any -> Field (SqlArray_ n b))
-> Field_ 'NonNullable Any -> Field (SqlArray_ n b)
forall a b. (a -> b) -> a -> b
$
PrimExpr -> Field_ 'NonNullable Any
forall (n :: Nullability) sqlType. PrimExpr -> Field_ n sqlType
C.Column ([PrimExpr] -> PrimExpr
HPQ.ArrayExpr ((a -> PrimExpr) -> [a] -> [PrimExpr]
forall a b. (a -> b) -> [a] -> [b]
map a -> PrimExpr
oneEl [a]
xs))
where
oneEl :: a -> PrimExpr
oneEl = Field_ n b -> PrimExpr
forall (n :: Nullability) a. Field_ n a -> PrimExpr
C.unColumn (Field_ n b -> PrimExpr) -> (a -> Field_ n b) -> a -> PrimExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Field_ n b
pgEl
arrayTy :: String
arrayTy = [SqlArray_ n b] -> String
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 :: (a -> Field_ n b)
-> RangeBound a -> RangeBound a -> Field_ n' (SqlRange b)
pgRange a -> Field_ n b
pgEl RangeBound a
start RangeBound a
end =
PrimExpr -> Field_ n' (SqlRange b)
forall (n :: Nullability) sqlType. PrimExpr -> Field_ n sqlType
C.Column (String -> BoundExpr -> BoundExpr -> PrimExpr
HPQ.RangeExpr ([b] -> String
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 (PrimExpr -> BoundExpr)
-> (Field_ n b -> PrimExpr) -> Field_ n b -> BoundExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field_ n b -> PrimExpr
forall (n :: Nullability) a. Field_ n a -> PrimExpr
C.unColumn (Field_ n b -> BoundExpr) -> Field_ n b -> BoundExpr
forall a b. (a -> b) -> a -> b
$ a -> Field_ n b
pgEl a
a
oneEl (R.Exclusive a
a) = PrimExpr -> BoundExpr
HPQ.Exclusive (PrimExpr -> BoundExpr)
-> (Field_ n b -> PrimExpr) -> Field_ n b -> BoundExpr
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Field_ n b -> PrimExpr
forall (n :: Nullability) a. Field_ n a -> PrimExpr
C.unColumn (Field_ n b -> BoundExpr) -> Field_ n b -> BoundExpr
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 :: proxy PGBool -> String
showSqlType proxy PGBool
_ = String
"boolean"
instance IsSqlType SqlDate where
showSqlType :: proxy PGDate -> String
showSqlType proxy PGDate
_ = String
"date"
instance IsSqlType SqlFloat4 where
showSqlType :: proxy SqlFloat4 -> String
showSqlType proxy SqlFloat4
_ = String
"real"
instance IsSqlType SqlFloat8 where
showSqlType :: proxy SqlFloat8 -> String
showSqlType proxy SqlFloat8
_ = String
"double precision"
instance IsSqlType SqlInt8 where
showSqlType :: proxy SqlInt8 -> String
showSqlType proxy SqlInt8
_ = String
"bigint"
instance IsSqlType SqlInt4 where
showSqlType :: proxy SqlInt4 -> String
showSqlType proxy SqlInt4
_ = String
"integer"
instance IsSqlType SqlInt2 where
showSqlType :: proxy SqlInt2 -> String
showSqlType proxy SqlInt2
_ = String
"smallint"
instance IsSqlType SqlInterval where
showSqlType :: proxy PGInterval -> String
showSqlType proxy PGInterval
_ = String
"interval"
instance IsSqlType SqlNumeric where
showSqlType :: proxy SqlNumeric -> String
showSqlType proxy SqlNumeric
_ = String
"numeric"
instance IsSqlType SqlText where
showSqlType :: proxy SqlText -> String
showSqlType proxy SqlText
_ = String
"text"
instance IsSqlType SqlVarcharN where
showSqlType :: proxy SqlVarcharN -> String
showSqlType proxy SqlVarcharN
_ = String
"varchar"
instance IsSqlType SqlTime where
showSqlType :: proxy PGTime -> String
showSqlType proxy PGTime
_ = String
"time"
instance IsSqlType SqlTimestamp where
showSqlType :: proxy PGTimestamp -> String
showSqlType proxy PGTimestamp
_ = String
"timestamp"
instance IsSqlType SqlTimestamptz where
showSqlType :: proxy PGTimestamptz -> String
showSqlType proxy PGTimestamptz
_ = String
"timestamp with time zone"
instance IsSqlType SqlUuid where
showSqlType :: proxy PGUuid -> String
showSqlType proxy PGUuid
_ = String
"uuid"
instance IsSqlType SqlCitext where
showSqlType :: proxy SqlCitext -> String
showSqlType proxy SqlCitext
_ = String
"citext"
instance IsSqlType SqlBytea where
showSqlType :: proxy PGBytea -> String
showSqlType proxy PGBytea
_ = String
"bytea"
instance IsSqlType a => IsSqlType (SqlArray_ n a) where
showSqlType :: proxy (SqlArray_ n a) -> String
showSqlType proxy (SqlArray_ n a)
_ = [a] -> String
forall sqlType (proxy :: * -> *).
IsSqlType sqlType =>
proxy sqlType -> String
showSqlType ([] :: [a]) String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"[]"
instance IsSqlType SqlJson where
showSqlType :: proxy PGJson -> String
showSqlType proxy PGJson
_ = String
"json"
instance IsSqlType SqlJsonb where
showSqlType :: proxy PGJsonb -> String
showSqlType proxy PGJsonb
_ = String
"jsonb"
instance IsRangeType a => IsSqlType (SqlRange a) where
showSqlType :: proxy (SqlRange a) -> String
showSqlType proxy (SqlRange a)
_ = [a] -> String
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 :: proxy SqlInt4 -> String
showRangeType proxy SqlInt4
_ = String
"int4range"
instance IsRangeType SqlInt8 where
showRangeType :: proxy SqlInt8 -> String
showRangeType proxy SqlInt8
_ = String
"int8range"
instance IsRangeType SqlNumeric where
showRangeType :: proxy SqlNumeric -> String
showRangeType proxy SqlNumeric
_ = String
"numrange"
instance IsRangeType SqlTimestamp where
showRangeType :: proxy PGTimestamp -> String
showRangeType proxy PGTimestamp
_ = String
"tsrange"
instance IsRangeType SqlTimestamptz where
showRangeType :: proxy PGTimestamptz -> String
showRangeType proxy PGTimestamptz
_ = String
"tstzrange"
instance IsRangeType SqlDate where
showRangeType :: proxy PGDate -> String
showRangeType proxy PGDate
_ = String
"daterange"
data SqlBool
data SqlDate
data SqlFloat4
data SqlFloat8
data SqlInt8
data SqlInt4
data SqlInt2
data SqlInterval
data SqlNumeric
data SqlText
data SqlVarcharN
data SqlTime
data SqlTimestamp
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