Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Column pgType = Column PrimExpr
- data Nullable a = Nullable
- unColumn :: Column a -> PrimExpr
- unsafeCoerceColumn :: Column a -> Column b
- unsafeCast :: String -> Column a -> Column b
- unsafeCompositeField :: Column a -> String -> Column b
- binOp :: BinOp -> Column a -> Column b -> Column c
- unOp :: UnOp -> Column a -> Column b
- unsafeCase_ :: [(Column pgBool, Column a)] -> Column a -> Column a
- unsafeIfThenElse :: Column pgBool -> Column a -> Column a -> Column a
- unsafeGt :: Column a -> Column a -> Column pgBool
- unsafeEq :: Column a -> Column a -> Column pgBool
- class SqlNum a where
- pgFromInteger :: Integer -> Column a
- sqlFromInteger :: Integer -> Column a
- type PGNum = SqlNum
- class SqlFractional a where
- pgFromRational :: Rational -> Column a
- sqlFromRational :: Rational -> Column a
- type PGFractional = SqlFractional
- class SqlIntegral a
- type PGIntegral = SqlIntegral
- class SqlString a where
- pgFromString :: String -> Column a
- sqlFromString :: String -> Column a
- type PGString = SqlString
Documentation
newtype Column pgType Source #
A column of a Query
, of type pgType
. For example Column
SqlInt4
is an int4
column and a Column
SqlText
is a text
column.
The name Column
will be replaced by Field
in version 0.8.
There already exists a Field
type family to help smooth the
transition. We recommend that you use Field_
, Field
or
FieldNullable
instead of Column
everywhere that it is
sufficient.
Instances
Only used within a Column
, to indicate that it can be NULL
.
For example, a Column
(Nullable
SqlText
) can be NULL
but a
Column
SqlText
cannot.
Instances
Default ToFields haskell (Column sql) => Default ToFields (Maybe haskell) (Column (Nullable sql)) Source # | |
Default NullMaker (Column a) (Column (Nullable a)) Source # | |
Default NullMaker (Column (Nullable a)) (Column (Nullable a)) Source # | |
IsSqlType a => IsSqlType (Nullable a) Source # | |
Defined in Opaleye.Internal.PGTypes showSqlType :: proxy (Nullable a) -> String Source # | |
SqlOrd a => SqlOrd (Nullable a) Source # | |
Defined in Opaleye.Order | |
DefaultFromField a b => DefaultFromField (Nullable a) (Maybe b) Source # | |
Defined in Opaleye.Internal.RunQuery | |
(Default (Inferrable FromField) a b, Maybe b ~ maybe_b) => Default (Inferrable FromFields) (Column (Nullable a)) maybe_b Source # | |
Defined in Opaleye.Internal.Inferrable def :: Inferrable FromFields (Column (Nullable a)) maybe_b # | |
type Map Nulled (Column (Nullable a)) Source # | |
unsafeCoerceColumn :: Column a -> Column b Source #
Treat a Column
as though it were of a different type. If such
a treatment is not valid then Postgres may fail with an error at
SQL run time.
unsafeCast :: String -> Column a -> Column b Source #
Cast a column to any other type. Implements Postgres's ::
or
CAST( ... AS ... )
operations. This is safe for some
conversions, such as uuid to text.
pgFromInteger :: Integer -> Column a Source #
sqlFromInteger :: Integer -> Column a Source #
Instances
SqlNum SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal pgFromInteger :: Integer -> Column SqlNumeric Source # sqlFromInteger :: Integer -> Column SqlNumeric Source # | |
SqlNum SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlNum SqlFloat8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal |
class SqlFractional a where Source #
pgFromRational :: Rational -> Column a Source #
sqlFromRational :: Rational -> Column a Source #
Instances
type PGFractional = SqlFractional Source #
class SqlIntegral a Source #
A dummy typeclass whose instances support integral operations.
Instances
SqlIntegral SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlIntegral SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlIntegral SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal | |
SqlIntegral SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal |
type PGIntegral = SqlIntegral Source #