opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Internal.Column

Synopsis

Documentation

newtype Column pgType Source #

A column of a Query, of type pgType. For example Column PGInt4 is an int4 column and a Column PGText is a text column.

Do not use the Show instance of Column. It is considered deprecated and will be removed in version 0.7.

The name Column will be replaced by Field in version 0.7. 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.

Constructors

Column PrimExpr 
Instances
Default ViewColumnMaker String (Column a) Source # 
Instance details

Defined in Opaleye.Internal.TableMaker

IsSqlType b => Default Nullspec a (Column b) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: Nullspec a (Column b) #

Default RelExprMaker String (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Operators

Default ToFields Bool (Column SqlBool) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Double (Column SqlFloat8) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Int (Column SqlInt4) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Int32 (Column SqlInt4) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Int64 (Column SqlInt8) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ByteString (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ByteString (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ByteString (Column SqlBytea) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ByteString (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ByteString (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ByteString (Column SqlBytea) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Scientific (Column SqlNumeric) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Text (Column SqlText) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields UTCTime (Column SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Value (Column SqlJsonb) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Value (Column SqlJson) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Text (Column SqlText) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields String (Column SqlText) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields ZonedTime (Column SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields LocalTime (Column SqlTimestamp) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields TimeOfDay (Column SqlTime) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields Day (Column SqlDate) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields UUID (Column SqlUuid) Source # 
Instance details

Defined in Opaleye.Constant

DefaultFromField a b => Default FromFields (Column a) b Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

def :: FromFields (Column a) b #

Default Unpackspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

def :: Unpackspec (Column a) (Column a) #

Default Binaryspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

def :: Binaryspec (Column a) (Column a) #

IsSqlType a => Default ValuesspecSafe (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: ValuesspecSafe (Column a) (Column a) #

Default Valuesspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: Valuesspec (Column a) (Column a) #

Default IfPP (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Operators

Methods

def :: IfPP (Column a) (Column a) #

Default EqPP (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Operators

Methods

def :: EqPP (Column a) (Column a) #

(Default ToFields a (Column b), IsSqlType b) => Default ToFields [a] (Column (SqlArray b)) Source # 
Instance details

Defined in Opaleye.Constant

Methods

def :: ToFields [a] (Column (SqlArray b)) #

Default ToFields haskell (Column sql) => Default ToFields (Maybe haskell) (Maybe (Column sql)) Source # 
Instance details

Defined in Opaleye.Constant

Methods

def :: ToFields (Maybe haskell) (Maybe (Column sql)) #

Default ToFields haskell (Column sql) => Default ToFields (Maybe haskell) (Column (Nullable sql)) Source # 
Instance details

Defined in Opaleye.Constant

Methods

def :: ToFields (Maybe haskell) (Column (Nullable sql)) #

Default ToFields (CI Text) (Column SqlCitext) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (CI Text) (Column SqlCitext) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (PGRange Int) (Column (SqlRange SqlInt4)) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (PGRange Int64) (Column (SqlRange SqlInt8)) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (PGRange Scientific) (Column (SqlRange SqlNumeric)) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) Source # 
Instance details

Defined in Opaleye.Constant

Default ToFields (PGRange Day) (Column (SqlRange SqlDate)) Source # 
Instance details

Defined in Opaleye.Constant

Default NullMaker (Column a) (Column (Nullable a)) Source # 
Instance details

Defined in Opaleye.Internal.Join

Methods

def :: NullMaker (Column a) (Column (Nullable a)) #

Default NullMaker (Column (Nullable a)) (Column (Nullable a)) Source # 
Instance details

Defined in Opaleye.Internal.Join

Methods

def :: NullMaker (Column (Nullable a)) (Column (Nullable a)) #

Default Distinctspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

def :: Distinctspec (Column a) (Column a) #

Default Updater (Column a) (Maybe (Column a)) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

def :: Updater (Column a) (Maybe (Column a)) #

Default Updater (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

def :: Updater (Column a) (Column a) #

(SqlNum a, SqlFractional a) => Fractional (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Column

Methods

(/) :: Column a -> Column a -> Column a #

recip :: Column a -> Column a #

fromRational :: Rational -> Column a #

SqlNum a => Num (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Column

Methods

(+) :: Column a -> Column a -> Column a #

(-) :: Column a -> Column a -> Column a #

(*) :: Column a -> Column a -> Column a #

negate :: Column a -> Column a #

abs :: Column a -> Column a #

signum :: Column a -> Column a #

fromInteger :: Integer -> Column a #

Show (Column pgType) Source # 
Instance details

Defined in Opaleye.Internal.Column

Methods

showsPrec :: Int -> Column pgType -> ShowS #

show :: Column pgType -> String #

showList :: [Column pgType] -> ShowS #

SqlString a => IsString (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Column

Methods

fromString :: String -> Column a #

TableColumn (Maybe (Column a)) a Source # 
Instance details

Defined in Opaleye.Internal.Table

TableColumn (Column a) a Source # 
Instance details

Defined in Opaleye.Internal.Table

(Profunctor p, IsSqlType a, Default p (Column a) (Column a)) => Default (WithNulls p) (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Methods

def :: WithNulls p (Column a) (Column a) #

type Map Nulled (Column (Nullable a)) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGJson) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGBytea) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGCitext) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGUuid) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGTimestamp) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGTime) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGText) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGText) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGInt4) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGInt8) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGFloat8) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGDate) Source # 
Instance details

Defined in Opaleye.Internal.Join

type Map Nulled (Column PGBool) Source # 
Instance details

Defined in Opaleye.Internal.Join

data Nullable a Source #

Only used within a Column, to indicate that it can be NULL. For example, a Column (Nullable PGText) can be NULL but a Column PGText cannot.

Constructors

Nullable 
Instances
Default ToFields haskell (Column sql) => Default ToFields (Maybe haskell) (Column (Nullable sql)) Source # 
Instance details

Defined in Opaleye.Constant

Methods

def :: ToFields (Maybe haskell) (Column (Nullable sql)) #

Default NullMaker (Column a) (Column (Nullable a)) Source # 
Instance details

Defined in Opaleye.Internal.Join

Methods

def :: NullMaker (Column a) (Column (Nullable a)) #

Default NullMaker (Column (Nullable a)) (Column (Nullable a)) Source # 
Instance details

Defined in Opaleye.Internal.Join

Methods

def :: NullMaker (Column (Nullable a)) (Column (Nullable a)) #

IsSqlType a => IsSqlType (Nullable a) Source # 
Instance details

Defined in Opaleye.Internal.PGTypes

Methods

showPGType :: proxy (Nullable a) -> String Source #

showSqlType :: proxy (Nullable a) -> String Source #

PGOrd a => PGOrd (Nullable a) Source # 
Instance details

Defined in Opaleye.Order

DefaultFromField a b => QueryRunnerColumnDefault (Nullable a) (Maybe b) Source # 
Instance details

Defined in Opaleye.Internal.RunQuery

type Map Nulled (Column (Nullable a)) Source # 
Instance details

Defined in Opaleye.Internal.Join

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.

binOp :: BinOp -> Column a -> Column b -> Column c Source #

unOp :: UnOp -> Column a -> Column b Source #

unsafeCase_ :: [(Column pgBool, Column a)] -> Column a -> Column a Source #

unsafeGt :: Column a -> Column a -> Column pgBool Source #

unsafeEq :: Column a -> Column a -> Column pgBool Source #

class PGIntegral a Source #

A dummy typeclass whose instances support integral operations.

Instances
PGIntegral PGNumeric Source # 
Instance details

Defined in Opaleye.PGTypes

PGIntegral PGInt2 Source # 
Instance details

Defined in Opaleye.PGTypes

PGIntegral PGInt4 Source # 
Instance details

Defined in Opaleye.PGTypes

PGIntegral PGInt8 Source # 
Instance details

Defined in Opaleye.PGTypes