| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Opaleye.PGTypes
Description
Use Opaleye.SqlTypes instead. Will be deprecated in version 0.7.
Synopsis
- data PGRange a
- data PGJsonb
- data PGJson
- data PGBytea
- data PGArray a
- data PGCitext
- data PGUuid
- data PGTimestamptz
- data PGTimestamp
- data PGTime
- data PGText
- data PGNumeric
- data PGInt2
- data PGInt4
- data PGInt8
- data PGFloat8
- data PGFloat4
- data PGDate
- data PGBool
- 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)
- literalColumn :: Literal -> Column a
- unsafePgFormatTime :: FormatTime t => Name -> String -> t -> Column c
- class IsSqlType sqlType where- showPGType :: proxy sqlType -> String
- showSqlType :: proxy sqlType -> String
 
Documentation
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.Constant Methods def :: ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) # | |
| Default ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields (PGRange Day) (Column (SqlRange SqlDate)) Source # | |
| IsRangeType a => IsSqlType (PGRange a) Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy (PGRange a) -> String Source # showSqlType :: proxy (PGRange a) -> String Source # | |
| (Typeable b, FromField b, DefaultFromField a b) => QueryRunnerColumnDefault (PGRange a) (PGRange b) Source # | |
| Defined in Opaleye.Internal.RunQuery | |
Instances
| IsSqlType PGJsonb Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGJsonb -> String Source # showSqlType :: proxy PGJsonb -> String Source # | |
| PGIsJson SqlJsonb Source # | |
| Defined in Opaleye.Operators | |
| QueryRunnerColumnDefault PGJsonb Value Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGJsonb String Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields ByteString (Column SqlJsonb) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields ByteString (Column SqlJsonb) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields Value (Column SqlJsonb) Source # | |
| type Map Nulled (Column PGJsonb) Source # | |
Instances
| IsSqlType PGJson Source # | |
| Defined in Opaleye.PGTypes | |
| PGIsJson SqlJson Source # | |
| Defined in Opaleye.Operators | |
| QueryRunnerColumnDefault PGJson Value Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGJson String Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields ByteString (Column SqlJson) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields ByteString (Column SqlJson) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields Value (Column SqlJson) Source # | |
| type Map Nulled (Column PGJson) Source # | |
Instances
| IsSqlType PGBytea Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGBytea -> String Source # showSqlType :: proxy PGBytea -> String Source # | |
| QueryRunnerColumnDefault PGBytea ByteString Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGBytea ByteString Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields ByteString (Column SqlBytea) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields ByteString (Column SqlBytea) Source # | |
| Defined in Opaleye.Constant | |
| type Map Nulled (Column PGBytea) Source # | |
Instances
| (Default ToFields a (Column b), IsSqlType b) => Default ToFields [a] (Column (SqlArray b)) Source # | |
| IsSqlType a => IsSqlType (PGArray a) Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy (PGArray a) -> String Source # showSqlType :: proxy (PGArray a) -> String Source # | |
| (Typeable b, DefaultFromField a b) => QueryRunnerColumnDefault (PGArray a) [b] Source # | |
| Defined in Opaleye.Internal.RunQuery Methods queryRunnerColumnDefault :: FromField (PGArray a) [b] Source # defaultFromField :: FromField (PGArray a) [b] Source # | |
Instances
| PGString PGCitext Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGCitext Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGCitext -> String Source # showSqlType :: proxy PGCitext -> String Source # | |
| PGOrd SqlCitext Source # | |
| Defined in Opaleye.Order | |
| QueryRunnerColumnDefault PGCitext (CI Text) Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGCitext (CI Text) Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields (CI Text) (Column SqlCitext) Source # | |
| Default ToFields (CI Text) (Column SqlCitext) Source # | |
| type Map Nulled (Column PGCitext) Source # | |
data PGTimestamptz Source #
Instances
| IsSqlType PGTimestamptz Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGTimestamptz -> String Source # showSqlType :: proxy PGTimestamptz -> String Source # | |
| IsRangeType PGTimestamptz Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGTimestamptz -> String Source # | |
| PGOrd SqlTimestamptz Source # | |
| Defined in Opaleye.Order | |
| QueryRunnerColumnDefault PGTimestamptz UTCTime Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGTimestamptz ZonedTime Source # | |
| Default ToFields UTCTime (Column SqlTimestamptz) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields ZonedTime (Column SqlTimestamptz) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # | |
| Defined in Opaleye.Constant | |
| type Map Nulled (Column PGTimestamptz) Source # | |
| Defined in Opaleye.Internal.Join | |
data PGTimestamp Source #
Instances
| IsSqlType PGTimestamp Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGTimestamp -> String Source # showSqlType :: proxy PGTimestamp -> String Source # | |
| IsRangeType PGTimestamp Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGTimestamp -> String Source # | |
| PGOrd SqlTimestamp Source # | |
| Defined in Opaleye.Order | |
| QueryRunnerColumnDefault PGTimestamp LocalTime Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields LocalTime (Column SqlTimestamp) Source # | |
| Defined in Opaleye.Constant | |
| Default ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # | |
| Defined in Opaleye.Constant | |
| type Map Nulled (Column PGTimestamp) Source # | |
| Defined in Opaleye.Internal.Join | |
Instances
| PGString PGText Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGText Source # | |
| Defined in Opaleye.PGTypes | |
| PGOrd SqlText Source # | |
| Defined in Opaleye.Order | |
| PGJsonIndex SqlText Source # | |
| Defined in Opaleye.Operators | |
| QueryRunnerColumnDefault PGText Text Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGText Text Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGText 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 # | |
| type Map Nulled (Column PGText) Source # | |
| type Map Nulled (Column PGText) Source # | |
Instances
| PGIntegral PGNumeric Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGNumeric Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGNumeric -> String Source # showSqlType :: proxy PGNumeric -> String Source # | |
| IsRangeType PGNumeric Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGNumeric -> String Source # | |
| PGOrd SqlNumeric Source # | |
| Defined in Opaleye.Order | |
| QueryRunnerColumnDefault PGNumeric Scientific Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields Scientific (Column SqlNumeric) Source # | |
| Defined in Opaleye.Constant Methods def :: ToFields Scientific (Column SqlNumeric) # | |
| Default ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) Source # | |
| Defined in Opaleye.Constant Methods def :: ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) # | |
Instances
| PGIntegral PGInt2 Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGInt2 Source # | |
| Defined in Opaleye.PGTypes | |
| PGOrd SqlInt2 Source # | |
| Defined in Opaleye.Order | |
Instances
| PGIntegral PGInt4 Source # | |
| Defined in Opaleye.PGTypes | |
| PGNum PGInt4 Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGInt4 Source # | |
| Defined in Opaleye.PGTypes | |
| IsRangeType PGInt4 Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGInt4 -> String Source # | |
| PGOrd SqlInt4 Source # | |
| Defined in Opaleye.Order | |
| PGJsonIndex SqlInt4 Source # | |
| Defined in Opaleye.Operators | |
| QueryRunnerColumnDefault PGInt4 Int Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| QueryRunnerColumnDefault PGInt4 Int32 Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields Int (Column SqlInt4) Source # | |
| Default ToFields Int32 (Column SqlInt4) Source # | |
| Default ToFields (PGRange Int) (Column (SqlRange SqlInt4)) Source # | |
| type Map Nulled (Column PGInt4) Source # | |
Instances
| PGIntegral PGInt8 Source # | |
| Defined in Opaleye.PGTypes | |
| PGNum PGInt8 Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGInt8 Source # | |
| Defined in Opaleye.PGTypes | |
| IsRangeType PGInt8 Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGInt8 -> String Source # | |
| PGOrd SqlInt8 Source # | |
| Defined in Opaleye.Order | |
| PGJsonIndex SqlInt8 Source # | |
| Defined in Opaleye.Operators | |
| QueryRunnerColumnDefault PGInt8 Int64 Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields Int64 (Column SqlInt8) Source # | |
| Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) Source # | |
| type Map Nulled (Column PGInt8) Source # | |
Instances
| PGFractional PGFloat8 Source # | |
| Defined in Opaleye.PGTypes | |
| PGNum PGFloat8 Source # | |
| Defined in Opaleye.PGTypes | |
| IsSqlType PGFloat8 Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGFloat8 -> String Source # showSqlType :: proxy PGFloat8 -> String Source # | |
| PGOrd SqlFloat8 Source # | |
| Defined in Opaleye.Order | |
| QueryRunnerColumnDefault PGFloat8 Double Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields Double (Column SqlFloat8) Source # | |
| type Map Nulled (Column PGFloat8) Source # | |
Instances
| IsSqlType PGFloat4 Source # | |
| Defined in Opaleye.PGTypes Methods showPGType :: proxy PGFloat4 -> String Source # showSqlType :: proxy PGFloat4 -> String Source # | |
| PGOrd SqlFloat4 Source # | |
| Defined in Opaleye.Order | |
Instances
| IsSqlType PGDate Source # | |
| Defined in Opaleye.PGTypes | |
| IsRangeType PGDate Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGDate -> String Source # | |
| PGOrd SqlDate Source # | |
| Defined in Opaleye.Order | |
| QueryRunnerColumnDefault PGDate Day Source # | |
| Defined in Opaleye.Internal.RunQuery | |
| Default ToFields Day (Column SqlDate) Source # | |
| Default ToFields (PGRange Day) (Column (SqlRange SqlDate)) Source # | |
| type Map Nulled (Column PGDate) Source # | |
class IsSqlType pgType => IsRangeType pgType where Source #
Methods
showRangeType :: proxy pgType -> String Source #
Instances
| IsRangeType PGTimestamptz Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGTimestamptz -> String Source # | |
| IsRangeType PGTimestamp Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGTimestamp -> String Source # | |
| IsRangeType PGNumeric Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGNumeric -> String Source # | |
| IsRangeType PGInt4 Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGInt4 -> String Source # | |
| IsRangeType PGInt8 Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGInt8 -> String Source # | |
| IsRangeType PGDate Source # | |
| Defined in Opaleye.PGTypes Methods showRangeType :: proxy PGDate -> 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 #
literalColumn :: Literal -> Column a Source #
Deprecated: literalColumn has been moved to Opaleye.Internal.PGTypes and will be removed in version 0.7.
unsafePgFormatTime :: FormatTime t => Name -> String -> t -> Column c Source #
Deprecated: unsafePgFormatTime has been moved to Opaleye.Internal.PGTypes and will be removed in version 0.7.
class IsSqlType sqlType where Source #
Minimal complete definition
Methods
showPGType :: proxy sqlType -> String Source #
Deprecated: Use showSqlType instead. showPGType will be removed in version 0.7.
showSqlType :: proxy sqlType -> String Source #