Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
Synopsis
- sqlInt4 :: Int -> Field SqlInt4
- sqlDouble :: Double -> Field SqlFloat8
- sqlInt8 :: Int64 -> Field SqlInt8
- sqlNumeric :: Scientific -> Field SqlNumeric
- data SqlInt4
- data SqlFloat8
- data SqlNumeric
- data SqlInt8
- data SqlInt2
- data SqlFloat4
- class SqlNum a
- class SqlIntegral a
- class SqlFractional a
- sqlDay :: Day -> Field SqlDate
- sqlUTCTime :: UTCTime -> Field SqlTimestamptz
- sqlLocalTime :: LocalTime -> Field SqlTimestamp
- sqlZonedTime :: ZonedTime -> Field SqlTimestamptz
- sqlTimeOfDay :: TimeOfDay -> Field SqlTime
- sqlInterval :: CalendarDiffTime -> Field PGInterval
- data SqlDate
- data SqlTime
- data SqlTimestamp
- data SqlTimestamptz
- data SqlInterval
- sqlJSON :: String -> Field SqlJson
- sqlStrictJSON :: ByteString -> Field SqlJson
- sqlLazyJSON :: ByteString -> Field SqlJson
- sqlValueJSON :: ToJSON a => a -> Field SqlJson
- data SqlJson
- sqlJSONB :: String -> Field SqlJsonb
- sqlStrictJSONB :: ByteString -> Field SqlJsonb
- sqlLazyJSONB :: ByteString -> Field SqlJsonb
- sqlValueJSONB :: ToJSON a => a -> Field SqlJsonb
- data SqlJsonb
- sqlString :: String -> Field SqlText
- sqlStrictText :: Text -> Field SqlText
- sqlLazyText :: Text -> Field SqlText
- sqlStringVarcharN :: String -> Field SqlVarcharN
- sqlStrictTextVarcharN :: Text -> Field SqlVarcharN
- sqlLazyTextVarcharN :: Text -> Field SqlVarcharN
- sqlCiStrictText :: CI Text -> Field SqlCitext
- sqlCiLazyText :: CI Text -> Field SqlCitext
- data SqlText
- data SqlVarcharN
- data SqlCitext
- class SqlString a
- sqlArray :: IsSqlType b => (a -> Field_ n b) -> [a] -> Field (SqlArray_ n b)
- type SqlArray = SqlArray_ NonNullable
- data SqlArray_ (n :: Nullability) a
- sqlRange :: IsRangeType b => (a -> Field b) -> RangeBound a -> RangeBound a -> Field (SqlRange b)
- data SqlRange a
- class IsSqlType pgType => IsRangeType pgType
- sqlBool :: Bool -> Field SqlBool
- sqlUUID :: UUID -> Field SqlUuid
- sqlLazyByteString :: ByteString -> Field SqlBytea
- sqlStrictByteString :: ByteString -> Field SqlBytea
- data SqlBool
- data SqlUuid
- data SqlBytea
- class IsSqlType sqlType where
- showSqlType :: proxy sqlType -> String
- sqlTypeWithSchema :: String -> String -> String
Numeric
Creating values
sqlNumeric :: Scientific -> Field SqlNumeric Source #
Types
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 # | |
SqlJsonIndex SqlInt4 Source # | |
Defined in Opaleye.Operators | |
SqlOrd SqlInt4 Source # | |
Defined in Opaleye.Order | |
DefaultFromField SqlInt4 Int32 Source # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlInt4 Int Source # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Int32 (Field SqlInt4) Source # | |
Default ToFields Int (Field SqlInt4) Source # | |
Default ToFields (PGRange Int) (Field (SqlRange SqlInt4)) Source # | |
int ~ Int => Default (Inferrable FromField) SqlInt4 int Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlInt4 int # |
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 # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Double (Field SqlFloat8) Source # | |
double ~ Double => Default (Inferrable FromField) SqlFloat8 double Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlFloat8 double # |
data SqlNumeric Source #
Instances
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 # | |
SqlJsonIndex SqlInt8 Source # | |
Defined in Opaleye.Operators | |
SqlOrd SqlInt8 Source # | |
Defined in Opaleye.Order | |
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 def :: Inferrable FromField SqlInt8 int64 # |
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
IsSqlType SqlFloat4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlFloat4 -> String Source # | |
SqlOrd SqlFloat4 Source # | |
Defined in Opaleye.Order |
Type classes
Instances
SqlNum SqlFloat8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal pgFromInteger :: Integer -> Field SqlNumeric Source # sqlFromInteger :: Integer -> Field SqlNumeric Source # |
class SqlIntegral a Source #
A dummy typeclass whose instances support integral operations.
Instances
SqlIntegral SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlIntegral SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlIntegral SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlIntegral SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal |
class SqlFractional a Source #
Instances
Date and time
Creating values
sqlUTCTime :: UTCTime -> Field SqlTimestamptz Source #
Types
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 # | |
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 def :: Inferrable FromField SqlDate day # |
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 # | |
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 def :: Inferrable FromField SqlTime timeofday # |
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 # | |
Defined in Opaleye.Internal.RunQuery | |
IntervalNum SqlDate SqlTimestamp Source # | |
Defined in Opaleye.Operators | |
IntervalNum SqlTimestamp SqlTimestamp Source # | |
Defined in Opaleye.Operators | |
Default ToFields LocalTime (Field SqlTimestamp) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange LocalTime) (Field (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 # |
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 # | |
Defined in Opaleye.Internal.RunQuery | |
DefaultFromField SqlTimestamptz ZonedTime Source # | |
Defined in Opaleye.Internal.RunQuery | |
IntervalNum SqlTimestamptz SqlTimestamptz Source # | |
Defined in Opaleye.Operators | |
Default ToFields UTCTime (Field SqlTimestamptz) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields ZonedTime (Field SqlTimestamptz) Source # | |
Defined in Opaleye.Internal.Constant | |
Default ToFields (PGRange UTCTime) (Field (SqlRange SqlTimestamptz)) Source # | |
Defined in Opaleye.Internal.Constant |
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 showSqlType :: proxy SqlInterval -> String Source # | |
DefaultFromField SqlInterval CalendarDiffTime Source # | |
IntervalNum SqlInterval SqlInterval Source # | |
Defined in Opaleye.Operators | |
Default ToFields CalendarDiffTime (Field SqlInterval) Source # | |
Defined in Opaleye.Internal.Constant | |
calendardifftime ~ CalendarDiffTime => Default (Inferrable FromField) SqlInterval calendardifftime Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlInterval calendardifftime # |
JSON
Creating values
sqlStrictJSON :: ByteString -> Field SqlJson Source #
sqlLazyJSON :: ByteString -> Field SqlJson Source #
Types
Instances
JSONB
Creating values
sqlStrictJSONB :: ByteString -> Field SqlJsonb Source #
sqlLazyJSONB :: ByteString -> Field SqlJsonb Source #
Types
Instances
Text
Creating values
Types
Instances
SqlString SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
IsSqlType SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy SqlText -> String Source # | |
SqlJsonIndex SqlText Source # | |
Defined in Opaleye.Operators | |
SqlOrd SqlText Source # | |
Defined in Opaleye.Order | |
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 (Field SqlText) Source # | |
Default ToFields Text (Field SqlText) Source # | |
Default ToFields String (Field SqlText) Source # | |
text ~ Text => Default (Inferrable FromField) SqlText text Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlText text # |
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 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) (Field SqlCitext) Source # | |
Default ToFields (CI Text) (Field SqlCitext) Source # | |
cttext ~ CI Text => Default (Inferrable FromField) SqlCitext cttext Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlCitext cttext # |
Type classes
Instances
SqlString SqlCitext Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlString SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlString SqlVarcharN Source # | |
Defined in Opaleye.Internal.PGTypesExternal pgFromString :: String -> Field SqlVarcharN Source # sqlFromString :: String -> Field SqlVarcharN Source # |
Array
Creating values
Types
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 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 showSqlType :: proxy (SqlArray_ n a) -> String Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (SqlArray_ 'NonNullable a) [b] Source # | |
Defined in Opaleye.Internal.RunQuery defaultFromField :: FromField (SqlArray_ 'NonNullable a) [b] Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (SqlArray_ 'Nullable a) [Maybe b] Source # | |
Defined in Opaleye.Internal.RunQuery |
Range
Creating values
sqlRange :: IsRangeType b => (a -> Field b) -> RangeBound a -> RangeBound a -> Field (SqlRange b) Source #
Types
Instances
Default ToFields (PGRange Int64) (Field (SqlRange SqlInt8)) Source # | |
Default ToFields (PGRange Scientific) (Field (SqlRange SqlNumeric)) Source # | |
Defined in Opaleye.Internal.Constant def :: ToFields (PGRange Scientific) (Field (SqlRange SqlNumeric)) # | |
Default ToFields (PGRange Day) (Field (SqlRange SqlDate)) Source # | |
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 Int) (Field (SqlRange SqlInt4)) Source # | |
IsRangeType a => IsSqlType (SqlRange a) Source # | |
Defined in Opaleye.Internal.PGTypesExternal showSqlType :: proxy (SqlRange a) -> String Source # | |
(Typeable b, DefaultFromField a b) => DefaultFromField (SqlRange a) (PGRange b) Source # | |
Defined in Opaleye.Internal.RunQuery |
class IsSqlType pgType => IsRangeType pgType Source #
Instances
IsRangeType SqlDate Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlDate -> 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 SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlNumeric -> String Source # | |
IsRangeType SqlTimestamp Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlTimestamp -> String Source # | |
IsRangeType SqlTimestamptz Source # | |
Defined in Opaleye.Internal.PGTypesExternal showRangeType :: proxy SqlTimestamptz -> String Source # |
Other
Creating values
Types
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 # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields Bool (Field SqlBool) Source # | |
bool ~ Bool => Default (Inferrable FromField) SqlBool bool Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlBool bool # |
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 # | |
Defined in Opaleye.Internal.RunQuery | |
Default ToFields UUID (Field SqlUuid) Source # | |
uuid ~ UUID => Default (Inferrable FromField) SqlUuid uuid Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromField SqlUuid uuid # |
Instances
IsSqlType SqlBytea Source # | |
Defined in Opaleye.Internal.PGTypesExternal 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 (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 def :: Inferrable FromField SqlBytea bytestring # |
IsSqlType
class IsSqlType sqlType where Source #
showSqlType :: proxy sqlType -> String Source #
Instances
sqlTypeWithSchema :: String -> String -> String Source #
Render the name of a type with a schema
> putStrLn (sqlTypeWithSchema "my_schema" "my_type") "my_schema"."my_type"
instanceIsSqlType
SqlMyTypeWithSchema whereshowSqlType
= \_ -> sqlTypeWithSchema "my_schema" "my_type"