Safe Haskell | None |
---|---|
Language | Haskell2010 |
Opaleye.Internal.PGTypesExternal
Synopsis
- type PGRange = SqlRange
- type PGJsonb = SqlJsonb
- type PGJson = SqlJson
- type PGBytea = SqlBytea
- type PGArray = SqlArray
- type PGCitext = SqlCitext
- type PGUuid = SqlUuid
- type PGTimestamptz = SqlTimestamptz
- type PGTimestamp = SqlTimestamp
- type PGTime = SqlTime
- type PGText = SqlText
- type PGNumeric = SqlNumeric
- type PGInterval = SqlInterval
- type PGInt2 = SqlInt2
- type PGInt4 = SqlInt4
- type PGInt8 = SqlInt8
- type PGFloat8 = SqlFloat8
- type PGFloat4 = SqlFloat4
- type PGDate = SqlDate
- type PGBool = SqlBool
- data SqlRange a
- data SqlJsonb
- data SqlJson
- data SqlBytea
- type SqlArray = SqlArray_ NonNullable
- data SqlArray_ (n :: Nullability) a
- data SqlCitext
- data SqlUuid
- data SqlTimestamptz
- data SqlTimestamp
- data SqlTime
- data SqlVarcharN
- data SqlText
- data SqlNumeric
- data SqlInterval
- data SqlInt2
- data SqlInt4
- data SqlInt8
- data SqlFloat8
- data SqlFloat4
- data SqlDate
- data SqlBool
- class IsSqlType pgType => IsRangeType pgType where
- showRangeType :: proxy pgType -> String
- pgString :: String -> Field PGText
- pgLazyByteString :: ByteString -> Field PGBytea
- pgStrictByteString :: ByteString -> Field PGBytea
- pgStrictText :: Text -> Field PGText
- pgLazyText :: Text -> Field PGText
- sqlStringVarcharN :: String -> Field SqlVarcharN
- sqlStrictTextVarcharN :: Text -> Field SqlVarcharN
- sqlLazyTextVarcharN :: Text -> Field SqlVarcharN
- pgNumeric :: Scientific -> Field PGNumeric
- pgInt4 :: Int -> Field PGInt4
- pgInt8 :: Int64 -> Field PGInt8
- pgDouble :: Double -> Field PGFloat8
- pgBool :: Bool -> Field PGBool
- pgUUID :: UUID -> Field PGUuid
- pgDay :: Day -> Field PGDate
- pgUTCTime :: UTCTime -> Field PGTimestamptz
- pgLocalTime :: LocalTime -> Field PGTimestamp
- pgZonedTime :: ZonedTime -> Field PGTimestamptz
- pgTimeOfDay :: TimeOfDay -> Field PGTime
- sqlInterval :: CalendarDiffTime -> Field PGInterval
- pgCiStrictText :: CI Text -> Field PGCitext
- pgCiLazyText :: CI Text -> Field PGCitext
- pgJSON :: String -> Field PGJson
- pgStrictJSON :: ByteString -> Field PGJson
- pgLazyJSON :: ByteString -> Field PGJson
- pgValueJSON :: ToJSON a => a -> Field PGJson
- pgJSONB :: String -> Field PGJsonb
- pgStrictJSONB :: ByteString -> Field PGJsonb
- pgLazyJSONB :: ByteString -> Field PGJsonb
- pgValueJSONB :: ToJSON a => a -> Field PGJsonb
- pgArray :: forall a b n. IsSqlType b => (a -> Field_ n b) -> [a] -> Field (SqlArray_ n b)
- pgRange :: forall a b n n'. IsRangeType b => (a -> Field_ n b) -> RangeBound a -> RangeBound a -> Field_ n' (SqlRange b)
- class IsSqlType sqlType where
- showSqlType :: proxy sqlType -> String
Documentation
type PGTimestamptz = SqlTimestamptz Source #
type PGTimestamp = SqlTimestamp Source #
type PGNumeric = SqlNumeric Source #
type PGInterval = SqlInterval Source #
Instances
Default ToFields (PGRange Int) (Field (SqlRange SqlInt4)) Source # | |
Default ToFields (PGRange Int64) (Field (SqlRange SqlInt8)) Source # | |
Default ToFields (PGRange Scientific) (Field (SqlRange SqlNumeric)) Source # | |
Defined in Opaleye.Internal.Constant Methods def :: ToFields (PGRange Scientific) (Field (SqlRange SqlNumeric)) # | |
Default ToFields (PGRange UTCTime) (Field (SqlRange SqlTimestamptz)) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange LocalTime) (Field (SqlRange SqlTimestamp)) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange Day) (Field (SqlRange SqlDate)) Source # | |
IsRangeType a => IsSqlType (SqlRange a) Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy (SqlRange a) -> String Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (SqlRange a) (PGRange b) Source # | |
Defined in Opaleye.Internal.RunQuery |
Instances
IsSqlType SqlJsonb Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlJsonb -> String Source # | |
SqlIsJson SqlJsonb Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlJsonb String Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlJsonb ByteString Source # | |
Defined in Opaleye.Internal.RunQuery Methods | |
DefaultFromField SqlJsonb ByteString Source # | |
Defined in Opaleye.Internal.RunQuery Methods | |
DefaultFromField SqlJsonb Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlJsonb Value Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlJsonb Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields ByteString (Field SqlJsonb) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ByteString (Field SqlJsonb) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields Value (Field SqlJsonb) Source # | |
Instances
IsSqlType SqlJson Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlJson -> String Source # | |
SqlIsJson SqlJson Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlJson String Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlJson ByteString Source # | |
Defined in Opaleye.Internal.RunQuery Methods | |
DefaultFromField SqlJson ByteString Source # | |
Defined in Opaleye.Internal.RunQuery Methods | |
DefaultFromField SqlJson Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlJson Value Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlJson Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields ByteString (Field SqlJson) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ByteString (Field SqlJson) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields Value (Field SqlJson) Source # | |
Instances
IsSqlType SqlBytea Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlBytea -> String Source # | |
DefaultFromField SqlBytea ByteString Source # | |
Defined in Opaleye.Internal.RunQuery Methods | |
DefaultFromField SqlBytea ByteString Source # | |
Defined in Opaleye.Internal.RunQuery Methods | |
Default ToFields ByteString (Field SqlBytea) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ByteString (Field SqlBytea) Source # | |
Defined in Opaleye.Internal.Constant | |
bytestring ~ ByteString => Default (Inferrable FromField) SqlBytea bytestring Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlBytea bytestring # |
type SqlArray = SqlArray_ NonNullable Source #
data SqlArray_ (n :: Nullability) a Source #
Instances
(Default ToFields a (Field_ n b), IsSqlType b) => Default ToFields [a] (Field (SqlArray_ n b)) Source # | |
(Typeable h, Default (Inferrable FromField) f h, hs ~ [h]) => Default (Inferrable FromField) (SqlArray f) hs Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField (SqlArray f) hs # | |
(Typeable h, Default (Inferrable FromField) f h, hs ~ [Maybe h]) => Default (Inferrable FromField) (SqlArray_ 'Nullable f) hs Source # | |
Defined in Opaleye.Internal.Inferrable | |
IsSqlType a => IsSqlType (SqlArray_ n a) Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy (SqlArray_ n a) -> String Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (SqlArray_ 'NonNullable a) [b] Source # | |
Defined in Opaleye.Internal.RunQuery Methods defaultFromField :: FromField (SqlArray_ 'NonNullable a) [b] Source # |
Instances
SqlString SqlCitext Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlCitext Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlCitext -> String Source # | |
SqlOrd SqlCitext Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlCitext (CI Text) Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlCitext (CI Text) Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields (CI Text) (Field SqlCitext) Source # | |
Default ToFields (CI Text) (Field SqlCitext) Source # | |
cttext ~ CI Text => Default (Inferrable FromField) SqlCitext cttext Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlCitext cttext # |
Instances
IsSqlType SqlUuid Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlUuid -> String Source # | |
SqlOrd SqlUuid Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlUuid UUID Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields UUID (Field SqlUuid) Source # | |
uuid ~ UUID => Default (Inferrable FromField) SqlUuid uuid Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlUuid uuid # |
data SqlTimestamptz Source #
Be careful if you use Haskell's 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.
Therefore, although when you roundtrip an input ZonedTime
to
obtain an output 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.
Instances
data SqlTimestamp Source #
Instances
Instances
IsSqlType SqlTime Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlTime -> String Source # | |
SqlOrd SqlTime Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlTime TimeOfDay Source # | |
Defined in Opaleye.Internal.RunQuery | |
IntervalNum SqlTime SqlTime Source # | |
Defined in Opaleye.Operators | |
Default ToFields TimeOfDay (Field SqlTime) Source # | |
timeofday ~ TimeOfDay => Default (Inferrable FromField) SqlTime timeofday Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlTime timeofday # |
data SqlVarcharN Source #
VARCHAR(n)
for any n
. Opaleye does not do anything to check
that the n
you choose is correctly adhered to!
Instances
Instances
SqlString SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlText -> String Source # | |
SqlOrd SqlText Source # | |
Defined in Opaleye.Order | |
SqlJsonIndex SqlText Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlText String Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlText Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlText Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields String (Field SqlText) Source # | |
Default ToFields Text (Field SqlText) Source # | |
Default ToFields Text (Field SqlText) Source # | |
text ~ Text => Default (Inferrable FromField) SqlText text Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlText text # |
data SqlNumeric Source #
Instances
data SqlInterval Source #
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;
.
Instances
IsSqlType SqlInterval Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlInterval -> String Source # | |
DefaultFromField SqlInterval CalendarDiffTime Source # | |
Defined in Opaleye.Internal.RunQuery Methods defaultFromField :: FromField SqlInterval CalendarDiffTime Source # | |
IntervalNum SqlInterval SqlInterval Source # | |
Defined in Opaleye.Operators | |
Default ToFields CalendarDiffTime (Field SqlInterval) Source # | |
Defined in Opaleye.Internal.Constant Methods | |
calendardifftime ~ CalendarDiffTime => Default (Inferrable FromField) SqlInterval calendardifftime Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlInterval calendardifftime # |
Instances
SqlIntegral SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlInt2 -> String Source # | |
SqlOrd SqlInt2 Source # | |
Defined in Opaleye.Order |
Instances
SqlIntegral SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlInt4 -> String Source # | |
IsRangeType SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlInt4 -> String Source # | |
SqlOrd SqlInt4 Source # | |
Defined in Opaleye.Order | |
SqlJsonIndex SqlInt4 Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlInt4 Int Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlInt4 Int32 Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Int (Field SqlInt4) Source # | |
Default ToFields Int32 (Field SqlInt4) Source # | |
Default ToFields (PGRange Int) (Field (SqlRange SqlInt4)) Source # | |
int ~ Int => Default (Inferrable FromField) SqlInt4 int Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlInt4 int # |
Instances
SqlIntegral SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlInt8 -> String Source # | |
IsRangeType SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlInt8 -> String Source # | |
SqlOrd SqlInt8 Source # | |
Defined in Opaleye.Order | |
SqlJsonIndex SqlInt8 Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlInt8 Int64 Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Int64 (Field SqlInt8) Source # | |
Default ToFields (PGRange Int64) (Field (SqlRange SqlInt8)) Source # | |
int64 ~ Int64 => Default (Inferrable FromField) SqlInt8 int64 Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlInt8 int64 # |
Instances
SqlFractional SqlFloat8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlFloat8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlFloat8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlFloat8 -> String Source # | |
SqlOrd SqlFloat8 Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlFloat8 Double Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Double (Field SqlFloat8) Source # | |
double ~ Double => Default (Inferrable FromField) SqlFloat8 double Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlFloat8 double # |
Instances
IsSqlType SqlFloat4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlFloat4 -> String Source # | |
SqlOrd SqlFloat4 Source # | |
Defined in Opaleye.Order |
Instances
IsSqlType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlDate -> String Source # | |
IsRangeType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlDate -> String Source # | |
SqlOrd SqlDate Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlDate Day Source # | |
Defined in Opaleye.Internal.RunQuery | |
IntervalNum SqlDate SqlTimestamp Source # | |
Defined in Opaleye.Operators | |
Default ToFields Day (Field SqlDate) Source # | |
Default ToFields (PGRange Day) (Field (SqlRange SqlDate)) Source # | |
day ~ Day => Default (Inferrable FromField) SqlDate day Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlDate day # |
Instances
IsSqlType SqlBool Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlBool -> String Source # | |
SqlOrd SqlBool Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlBool Bool Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Bool (Field SqlBool) Source # | |
bool ~ Bool => Default (Inferrable FromField) SqlBool bool Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlBool bool # |
class IsSqlType pgType => IsRangeType pgType where Source #
Methods
showRangeType :: proxy pgType -> String Source #
Instances
IsRangeType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlTimestamptz -> String Source # | |
IsRangeType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlTimestamp -> String Source # | |
IsRangeType SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlNumeric -> String Source # | |
IsRangeType SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlInt4 -> String Source # | |
IsRangeType SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlInt8 -> String Source # | |
IsRangeType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlDate -> String Source # |
pgLocalTime :: LocalTime -> Field PGTimestamp Source #
pgStrictJSON :: ByteString -> Field PGJson Source #
pgLazyJSON :: ByteString -> Field PGJson Source #
pgStrictJSONB :: ByteString -> Field PGJsonb Source #
pgLazyJSONB :: ByteString -> Field PGJsonb Source #
pgRange :: forall a b n n'. IsRangeType b => (a -> Field_ n b) -> RangeBound a -> RangeBound a -> Field_ n' (SqlRange b) Source #
class IsSqlType sqlType where Source #
Methods
showSqlType :: proxy sqlType -> String Source #