opaleye-0.6.7003.1: 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.

Constructors

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

Defined in Opaleye.Internal.TableMaker

Default RelExprMaker String (Column a) # 
Instance details

Defined in Opaleye.Internal.Operators

Default Constant Bool (Column SqlBool) # 
Instance details

Defined in Opaleye.Constant

Default Constant Double (Column SqlFloat8) # 
Instance details

Defined in Opaleye.Constant

Default Constant Int (Column SqlInt4) # 
Instance details

Defined in Opaleye.Constant

Default Constant Int32 (Column SqlInt4) # 
Instance details

Defined in Opaleye.Constant

Default Constant Int64 (Column SqlInt8) # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJsonb) # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJson) # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlBytea) # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJsonb) # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlJson) # 
Instance details

Defined in Opaleye.Constant

Default Constant ByteString (Column SqlBytea) # 
Instance details

Defined in Opaleye.Constant

Default Constant Scientific (Column SqlNumeric) # 
Instance details

Defined in Opaleye.Constant

Default Constant String (Column SqlText) # 
Instance details

Defined in Opaleye.Constant

Default Constant Text (Column SqlText) # 
Instance details

Defined in Opaleye.Constant

Default Constant UTCTime (Column SqlTimestamptz) # 
Instance details

Defined in Opaleye.Constant

Default Constant Value (Column SqlJsonb) # 
Instance details

Defined in Opaleye.Constant

Default Constant Value (Column SqlJson) # 
Instance details

Defined in Opaleye.Constant

Default Constant Text (Column SqlText) # 
Instance details

Defined in Opaleye.Constant

Default Constant ZonedTime (Column SqlTimestamptz) # 
Instance details

Defined in Opaleye.Constant

Default Constant LocalTime (Column SqlTimestamp) # 
Instance details

Defined in Opaleye.Constant

Default Constant TimeOfDay (Column SqlTime) # 
Instance details

Defined in Opaleye.Constant

Default Constant Day (Column SqlDate) # 
Instance details

Defined in Opaleye.Constant

Default Constant UUID (Column SqlUuid) # 
Instance details

Defined in Opaleye.Constant

QueryRunnerColumnDefault a b => Default QueryRunner (Column a) b # 
Instance details

Defined in Opaleye.Internal.RunQuery

Methods

def :: QueryRunner (Column a) b #

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

Defined in Opaleye.Internal.Unpackspec

Methods

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

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

Defined in Opaleye.Internal.Values

Methods

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

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

Defined in Opaleye.Internal.Binary

Methods

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

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

Defined in Opaleye.Internal.Operators

Methods

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

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

Defined in Opaleye.Internal.Operators

Methods

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

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

Defined in Opaleye.Internal.Join

Methods

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

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

Defined in Opaleye.Internal.Join

Methods

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

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

Defined in Opaleye.Constant

Methods

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

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

Defined in Opaleye.Constant

Methods

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

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

Defined in Opaleye.Constant

Methods

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

Default Constant (CI Text) (Column SqlCitext) # 
Instance details

Defined in Opaleye.Constant

Default Constant (CI Text) (Column SqlCitext) # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Int) (Column (SqlRange SqlInt4)) # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Int64) (Column (SqlRange SqlInt8)) # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Scientific) (Column (SqlRange SqlNumeric)) # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange UTCTime) (Column (SqlRange SqlTimestamptz)) # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange LocalTime) (Column (SqlRange SqlTimestamp)) # 
Instance details

Defined in Opaleye.Constant

Default Constant (PGRange Day) (Column (SqlRange SqlDate)) # 
Instance details

Defined in Opaleye.Constant

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

Defined in Opaleye.Internal.Distinct

Methods

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

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

Defined in Opaleye.Internal.Manipulation

Methods

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

Default Updater (Column a) (Column a) # 
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

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 NullMaker (Column a) (Column (Nullable a)) # 
Instance details

Defined in Opaleye.Internal.Join

Methods

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

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

Defined in Opaleye.Internal.Join

Methods

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

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

Defined in Opaleye.Constant

Methods

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

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

Defined in Opaleye.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

QueryRunnerColumnDefault 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