| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Opaleye.SqlTypes
Description
SQL types and functions to create Field_s of
those types. To create fields you may find it more convenient to use
Opaleye.ToFields instead.
Documentation
sqlNumeric :: Scientific -> Field SqlNumeric Source #
sqlUTCTime :: UTCTime -> Field SqlTimestamptz Source #
sqlStrictJSON :: ByteString -> Field SqlJson Source #
sqlLazyJSON :: ByteString -> Field SqlJson Source #
sqlStrictJSONB :: ByteString -> Field SqlJsonb Source #
sqlLazyJSONB :: ByteString -> Field SqlJsonb Source #
sqlRange :: IsRangeType b => (a -> Field b) -> RangeBound a -> RangeBound a -> Field (SqlRange b) Source #
class IsSqlType sqlType Source #
Minimal complete definition
Instances
class IsSqlType pgType => IsRangeType pgType Source #
Minimal complete definition
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 # | |
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 (Column SqlBool) Source # | |
| bool ~ Bool => Default (Inferrable FromField) SqlBool bool Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlBool bool # | |
| type Map Nulled (Column PGBool) Source # | |
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 | |
| 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 Methods def :: Inferrable FromField SqlDate day # | |
| type Map Nulled (Column PGDate) Source # | |
Instances
| IsSqlType SqlFloat4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlFloat4 -> String Source # | |
| SqlOrd SqlFloat4 Source # | |
Defined in Opaleye.Order | |
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 (Column SqlFloat8) Source # | |
| double ~ Double => Default (Inferrable FromField) SqlFloat8 double Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlFloat8 double # | |
| type Map Nulled (Column PGFloat8) 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 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 (Column SqlInt8) Source # | |
| Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) Source # | |
| int64 ~ Int64 => Default (Inferrable FromField) SqlInt8 int64 Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlInt8 int64 # | |
| type Map Nulled (Column PGInt8) Source # | |
Instances
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 | |
data SqlNumeric Source #
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 Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
| DefaultFromField SqlText Text Source # | |
Defined in Opaleye.Internal.RunQuery | |
| DefaultFromField SqlText String Source # | |
Defined in Opaleye.Internal.RunQuery | |
| Default ToFields Text (Column SqlText) Source # | |
| Default ToFields Text (Column SqlText) Source # | |
| Default ToFields String (Column SqlText) Source # | |
| text ~ Text => Default (Inferrable FromField) SqlText text Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlText text # | |
| type Map Nulled (Column PGText) Source # | |
| type Map Nulled (Column PGText) Source # | |
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 | |
| Default ToFields TimeOfDay (Column SqlTime) Source # | |
| timeofday ~ TimeOfDay => Default (Inferrable FromField) SqlTime timeofday Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlTime timeofday # | |
| type Map Nulled (Column PGTime) Source # | |
data SqlTimestamp Source #
Instances
| IsSqlType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlTimestamp -> String Source # | |
| IsRangeType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlTimestamp -> String Source # | |
| SqlOrd SqlTimestamp Source # | |
Defined in Opaleye.Order | |
| DefaultFromField SqlTimestamp LocalTime Source # | |
Defined in Opaleye.Internal.RunQuery | |
| 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 Methods def :: Inferrable FromField SqlTimestamp localtime # | |
| type Map Nulled (Column PGTimestamp) Source # | |
Defined in Opaleye.Internal.Join | |
data SqlTimestamptz Source #
Instances
| IsSqlType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlTimestamptz -> String Source # | |
| IsRangeType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showRangeType :: proxy SqlTimestamptz -> String Source # | |
| SqlOrd SqlTimestamptz Source # | |
Defined in Opaleye.Order | |
| DefaultFromField SqlTimestamptz UTCTime Source # | |
Defined in Opaleye.Internal.RunQuery | |
| 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 | |
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 (Column SqlUuid) Source # | |
| uuid ~ UUID => Default (Inferrable FromField) SqlUuid uuid Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlUuid uuid # | |
| type Map Nulled (Column PGUuid) 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) (Column SqlCitext) Source # | |
| Default ToFields (CI Text) (Column SqlCitext) Source # | |
| cttext ~ CI Text => Default (Inferrable FromField) SqlCitext cttext Source # | |
Defined in Opaleye.Internal.Inferrable Methods def :: Inferrable FromField SqlCitext cttext # | |
| type Map Nulled (Column PGCitext) 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 Methods showSqlType :: proxy (SqlArray a) -> String Source # | |
| (Typeable b, DefaultFromField a b) => DefaultFromField (SqlArray a) [b] Source # | |
Defined in Opaleye.Internal.RunQuery Methods 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 Methods def :: Inferrable FromField (SqlArray f) hs # | |
Instances
| IsSqlType SqlBytea Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlBytea -> String Source # | |
| DefaultFromField SqlBytea ByteString Source # | |
Defined in Opaleye.Internal.RunQuery | |
| DefaultFromField SqlBytea ByteString Source # | |
Defined in Opaleye.Internal.RunQuery | |
| 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 Methods def :: Inferrable FromField SqlBytea bytestring # | |
| type Map Nulled (Column PGBytea) 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 Value Source # | |
Defined in Opaleye.Internal.RunQuery | |
| DefaultFromField SqlJson String Source # | |
Defined in Opaleye.Internal.RunQuery | |
| 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 SqlJsonb Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods showSqlType :: proxy SqlJsonb -> String Source # | |
| SqlIsJson SqlJsonb Source # | |
Defined in Opaleye.Operators | |
| DefaultFromField SqlJsonb Value Source # | |
Defined in Opaleye.Internal.RunQuery | |
| DefaultFromField SqlJsonb String Source # | |
Defined in Opaleye.Internal.RunQuery | |
| 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
| 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 Methods 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 Methods showSqlType :: proxy (SqlRange a) -> String Source # | |
| (Typeable b, FromField b, DefaultFromField a b) => DefaultFromField (PGRange a) (PGRange b) Source # | |
Defined in Opaleye.Internal.RunQuery | |