Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 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
- data SqlArray a
- data SqlCitext
- data SqlUuid
- data SqlTimestamptz
- data SqlTimestamp
- data SqlTime
- data SqlText
- data SqlNumeric
- 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 -> Column PGText
- pgLazyByteString :: ByteString -> Column PGBytea
- pgStrictByteString :: ByteString -> Column PGBytea
- pgStrictText :: Text -> Column PGText
- pgLazyText :: Text -> Column PGText
- pgNumeric :: Scientific -> Column PGNumeric
- pgInt4 :: Int -> Column PGInt4
- pgInt8 :: Int64 -> Column PGInt8
- pgDouble :: Double -> Column PGFloat8
- pgBool :: Bool -> Column PGBool
- pgUUID :: UUID -> Column PGUuid
- pgDay :: Day -> Column PGDate
- pgUTCTime :: UTCTime -> Column PGTimestamptz
- pgLocalTime :: LocalTime -> Column PGTimestamp
- pgZonedTime :: ZonedTime -> Column PGTimestamptz
- pgTimeOfDay :: TimeOfDay -> Column PGTime
- pgCiStrictText :: CI Text -> Column PGCitext
- pgCiLazyText :: CI Text -> Column PGCitext
- pgJSON :: String -> Column PGJson
- pgStrictJSON :: ByteString -> Column PGJson
- pgLazyJSON :: ByteString -> Column PGJson
- pgValueJSON :: ToJSON a => a -> Column PGJson
- pgJSONB :: String -> Column PGJsonb
- pgStrictJSONB :: ByteString -> Column PGJsonb
- pgLazyJSONB :: ByteString -> Column PGJsonb
- pgValueJSONB :: ToJSON a => a -> Column PGJsonb
- pgArray :: forall a b. IsSqlType b => (a -> Column b) -> [a] -> Column (PGArray b)
- pgRange :: forall a b. IsRangeType b => (a -> Column b) -> RangeBound a -> RangeBound a -> Column (PGRange b)
- class IsSqlType sqlType where
- showSqlType :: proxy sqlType -> String
Documentation
type PGTimestamptz = SqlTimestamptz Source #
type PGTimestamp = SqlTimestamp Source #
type PGNumeric = SqlNumeric Source #
Instances
Default ToFields (PGRange Int) (Column (SqlRange SqlInt4)) Source # | |
Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) Source # | |
Default ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) Source # | |
Defined in Opaleye.Internal.Constant def :: ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) # | |
Default ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange Day) (Column (SqlRange SqlDate)) Source # | |
IsRangeType a => IsSqlType (SqlRange a) Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy (SqlRange a) -> String Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (PGRange a) (PGRange b) Source # | |
Defined in Opaleye.Internal.RunQuery |
Instances
IsSqlType SqlJsonb Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlJsonb -> String Source # | |
SqlIsJson SqlJsonb Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlJsonb ByteString Source # | |
DefaultFromField SqlJsonb ByteString Source # | |
DefaultFromField SqlJsonb String Source # | |
DefaultFromField SqlJsonb Text Source # | |
DefaultFromField SqlJsonb Value Source # | |
DefaultFromField SqlJsonb Text Source # | |
Default ToFields ByteString (Column SqlJsonb) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ByteString (Column SqlJsonb) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields Value (Column SqlJsonb) Source # | |
type Map Nulled (Column PGJsonb) Source # | |
Instances
IsSqlType SqlJson Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlJson -> String Source # | |
SqlIsJson SqlJson Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlJson ByteString Source # | |
DefaultFromField SqlJson ByteString Source # | |
DefaultFromField SqlJson String Source # | |
DefaultFromField SqlJson Text Source # | |
DefaultFromField SqlJson Value Source # | |
DefaultFromField SqlJson Text Source # | |
Default ToFields ByteString (Column SqlJson) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ByteString (Column SqlJson) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields Value (Column SqlJson) Source # | |
type Map Nulled (Column PGJson) Source # | |
Instances
IsSqlType SqlBytea Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlBytea -> String Source # | |
DefaultFromField SqlBytea ByteString Source # | |
DefaultFromField SqlBytea ByteString Source # | |
Default ToFields ByteString (Column SqlBytea) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ByteString (Column SqlBytea) Source # | |
Defined in Opaleye.Internal.Constant | |
bytestring ~ ByteString => Default (Inferrable FromField) SqlBytea bytestring Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlBytea bytestring # | |
type Map Nulled (Column PGBytea) Source # | |
Instances
(Default ToFields a (Column b), IsSqlType b) => Default ToFields [a] (Column (SqlArray b)) Source # | |
IsSqlType a => IsSqlType (SqlArray a) Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy (SqlArray a) -> String Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (SqlArray a) [b] Source # | |
Defined in Opaleye.Internal.RunQuery queryRunnerColumnDefault :: FromField (SqlArray a) [b] Source # defaultFromField :: FromField (SqlArray a) [b] Source # | |
(Typeable h, Default (Inferrable FromField) f h, hs ~ [h]) => Default (Inferrable FromField) (SqlArray f) hs Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField (SqlArray f) hs # |
Instances
SqlString SqlCitext Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlCitext Source # | |
Defined in Opaleye.Internal.PGTypesExternal 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) (Column SqlCitext) Source # | |
Default ToFields (CI Text) (Column SqlCitext) Source # | |
cttext ~ CI Text => Default (Inferrable FromField) SqlCitext cttext Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlCitext cttext # | |
type Map Nulled (Column PGCitext) Source # | |
Instances
IsSqlType SqlUuid Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlUuid -> String Source # | |
SqlOrd SqlUuid Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlUuid UUID Source # | |
Default ToFields UUID (Column SqlUuid) Source # | |
uuid ~ UUID => Default (Inferrable FromField) SqlUuid uuid Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlUuid uuid # | |
type Map Nulled (Column PGUuid) Source # | |
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
IsSqlType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlTimestamptz -> String Source # | |
IsRangeType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlTimestamptz -> String Source # | |
SqlOrd SqlTimestamptz Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlTimestamptz UTCTime Source # | |
DefaultFromField SqlTimestamptz ZonedTime Source # | |
Default ToFields UTCTime (Column SqlTimestamptz) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ZonedTime (Column SqlTimestamptz) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # | |
Defined in Opaleye.Internal.Constant | |
type Map Nulled (Column PGTimestamptz) Source # | |
Defined in Opaleye.Internal.Join |
data SqlTimestamp Source #
Instances
IsSqlType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlTimestamp -> String Source # | |
IsRangeType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlTimestamp -> String Source # | |
SqlOrd SqlTimestamp Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlTimestamp LocalTime Source # | |
Default ToFields LocalTime (Column SqlTimestamp) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # | |
Defined in Opaleye.Internal.Constant | |
localtime ~ LocalTime => Default (Inferrable FromField) SqlTimestamp localtime Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlTimestamp localtime # | |
type Map Nulled (Column PGTimestamp) Source # | |
Defined in Opaleye.Internal.Join |
Instances
IsSqlType SqlTime Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlTime -> String Source # | |
SqlOrd SqlTime Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlTime TimeOfDay Source # | |
Default ToFields TimeOfDay (Column SqlTime) Source # | |
timeofday ~ TimeOfDay => Default (Inferrable FromField) SqlTime timeofday Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlTime timeofday # | |
type Map Nulled (Column PGTime) Source # | |
Instances
SqlString SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlText -> String Source # | |
SqlOrd SqlText Source # | |
Defined in Opaleye.Order | |
SqlJsonIndex SqlText Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlText String Source # | |
DefaultFromField SqlText Text Source # | |
DefaultFromField SqlText Text Source # | |
Default ToFields String (Column SqlText) Source # | |
Default ToFields Text (Column SqlText) Source # | |
Default ToFields Text (Column SqlText) Source # | |
text ~ Text => Default (Inferrable FromField) SqlText text Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlText text # | |
type Map Nulled (Column PGText) Source # | |
type Map Nulled (Column PGText) Source # | |
data SqlNumeric Source #
Instances
Instances
SqlIntegral SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal 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 showSqlType :: proxy SqlInt4 -> String Source # | |
IsRangeType SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlInt4 -> String Source # | |
SqlOrd SqlInt4 Source # | |
Defined in Opaleye.Order | |
SqlJsonIndex SqlInt4 Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlInt4 Int Source # | |
DefaultFromField SqlInt4 Int32 Source # | |
Default ToFields Int (Column SqlInt4) Source # | |
Default ToFields Int32 (Column SqlInt4) Source # | |
Default ToFields (PGRange Int) (Column (SqlRange SqlInt4)) Source # | |
int ~ Int => Default (Inferrable FromField) SqlInt4 int Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlInt4 int # | |
type Map Nulled (Column PGInt4) Source # | |
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 showSqlType :: proxy SqlInt8 -> String Source # | |
IsRangeType SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlInt8 -> String Source # | |
SqlOrd SqlInt8 Source # | |
Defined in Opaleye.Order | |
SqlJsonIndex SqlInt8 Source # | |
Defined in Opaleye.Operators | |
DefaultFromField SqlInt8 Int64 Source # | |
Default ToFields Int64 (Column SqlInt8) Source # | |
Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) Source # | |
int64 ~ Int64 => Default (Inferrable FromField) SqlInt8 int64 Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlInt8 int64 # | |
type Map Nulled (Column PGInt8) Source # | |
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 showSqlType :: proxy SqlFloat8 -> String Source # | |
SqlOrd SqlFloat8 Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlFloat8 Double Source # | |
Default ToFields Double (Column SqlFloat8) Source # | |
double ~ Double => Default (Inferrable FromField) SqlFloat8 double Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlFloat8 double # | |
type Map Nulled (Column PGFloat8) Source # | |
Instances
IsSqlType SqlFloat4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlFloat4 -> String Source # | |
SqlOrd SqlFloat4 Source # | |
Defined in Opaleye.Order |
Instances
IsSqlType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlDate -> String Source # | |
IsRangeType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlDate -> String Source # | |
SqlOrd SqlDate Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlDate Day Source # | |
Default ToFields Day (Column SqlDate) Source # | |
Default ToFields (PGRange Day) (Column (SqlRange SqlDate)) Source # | |
day ~ Day => Default (Inferrable FromField) SqlDate day Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlDate day # | |
type Map Nulled (Column PGDate) Source # | |
Instances
IsSqlType SqlBool Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlBool -> String Source # | |
SqlOrd SqlBool Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlBool Bool Source # | |
Default ToFields Bool (Column SqlBool) Source # | |
bool ~ Bool => Default (Inferrable FromField) SqlBool bool Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlBool bool # | |
type Map Nulled (Column PGBool) Source # | |
class IsSqlType pgType => IsRangeType pgType where Source #
showRangeType :: proxy pgType -> String Source #
Instances
IsRangeType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlTimestamptz -> String Source # | |
IsRangeType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlTimestamp -> String Source # | |
IsRangeType SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlNumeric -> String Source # | |
IsRangeType SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlInt4 -> String Source # | |
IsRangeType SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlInt8 -> String Source # | |
IsRangeType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlDate -> String Source # |
pgLocalTime :: LocalTime -> Column PGTimestamp Source #
pgStrictJSON :: ByteString -> Column PGJson Source #
pgLazyJSON :: ByteString -> Column PGJson Source #
pgStrictJSONB :: ByteString -> Column PGJsonb Source #
pgLazyJSONB :: ByteString -> Column PGJsonb Source #
pgRange :: forall a b. IsRangeType b => (a -> Column b) -> RangeBound a -> RangeBound a -> Column (PGRange b) Source #
class IsSqlType sqlType where Source #
showSqlType :: proxy sqlType -> String Source #