opaleye-0.9.3.2: An SQL-generating DSL targeting PostgreSQL
Safe HaskellNone
LanguageHaskell2010

Opaleye.Field

Description

Functions for working directly with Field_s.

Please note that numeric Field_ types are instances of Num, so you can use *, /, +, - on them. To create Field_s, see Opaleye.ToFields and Opaleye.SqlTypes.

Field_ used to be called Column and for technical reasons there are still a few uses of the old name around. If you see Column SqlType then you can understand it as Field SqlType, and if you see Column (Nullable SqlType) then you can understand it as FieldNullable SqlType.

Column will be fully deprecated in version 0.10.

Synopsis

Documentation

data Field_ (n :: Nullability) sqlType Source #

A field of a Select, of type sqlType. For example a Field SqlInt4 is an int4 column and a Field SqlText is a text column.

Instances

Instances details
Default ToFields Bool (Field SqlBool) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Double (Field SqlFloat8) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Int (Field SqlInt4) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Int32 (Field SqlInt4) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Int64 (Field SqlInt8) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields String (Field SqlVarcharN) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields String (Field SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlBytea) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlBytea) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Scientific (Field SqlNumeric) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields UTCTime (Field SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Field SqlVarcharN) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Field SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Value (Field SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Value (Field SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Field SqlVarcharN) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Field SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ZonedTime (Field SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields LocalTime (Field SqlTimestamp) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields TimeOfDay (Field SqlTime) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields CalendarDiffTime (Field SqlInterval) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Day (Field SqlDate) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields UUID (Field SqlUuid) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ViewColumnMaker String (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.TableMaker

Default RelExprMaker String (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Operators

Methods

def :: RelExprMaker String (Field_ n a) #

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

Defined in Opaleye.Internal.Values

Methods

def :: Nullspec a (Field_ n b) #

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

Defined in Opaleye.Internal.RunQuery

Methods

def :: FromFields (Field a) b #

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

Defined in Opaleye.Internal.Operators

Methods

def :: EqPP (Field a) (Field a) #

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

Defined in Opaleye.Internal.RunQuery

Methods

def :: FromFields (FieldNullable a) (Maybe b) #

(Default ToFields a (Field_ n b), IsSqlType b) => Default ToFields [a] (Field (SqlArray_ n b)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields [a] (Field (SqlArray_ n b)) #

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

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Maybe haskell) (Maybe (Field_ n sql)) #

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

Defined in Opaleye.Internal.Constant

Methods

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

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

Defined in Opaleye.Internal.Constant

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

Defined in Opaleye.Internal.Constant

ToJSON a => Default ToFields (Aeson a) (Field SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Aeson a) (Field SqlJsonb) #

ToJSON a => Default ToFields (Aeson a) (Field SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Aeson a) (Field SqlJson) #

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

Defined in Opaleye.Internal.Constant

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

Defined in Opaleye.Internal.Constant

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

Defined in Opaleye.Internal.Constant

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

Defined in Opaleye.Internal.Constant

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

Defined in Opaleye.Internal.Constant

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

Defined in Opaleye.Internal.Constant

Default ToFields (Field a) (Field a) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Methods

def :: ToFields (Field a) (Field a) #

Default NullMaker (FieldNullable a) (FieldNullable a) Source # 
Instance details

Defined in Opaleye.Internal.Join

Default NullMaker (Field a) (FieldNullable a) Source # 
Instance details

Defined in Opaleye.Internal.Join

Methods

def :: NullMaker (Field a) (FieldNullable a) #

Default Updater (Field_ n a) (Maybe (Field_ n a)) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

def :: Updater (Field_ n a) (Maybe (Field_ n a)) #

Default Unpackspec (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

def :: Unpackspec (Field_ n a) (Field_ n a) #

Default Binaryspec (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Binary

Methods

def :: Binaryspec (Field_ n a) (Field_ n a) #

Default IfPP (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Operators

Methods

def :: IfPP (Field_ n a) (Field_ n a) #

IsSqlType a => Default Valuesspec (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: Valuesspec (Field_ n a) (Field_ n a) #

Default ValuesspecUnsafe (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Values

Methods

def :: ValuesspecUnsafe (Field_ n a) (Field_ n a) #

Default Distinctspec (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Distinct

Methods

def :: Distinctspec (Field_ n a) (Field_ n a) #

Default Updater (Field_ n a) (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Manipulation

Methods

def :: Updater (Field_ n a) (Field_ n a) #

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

Defined in Opaleye.Internal.Column

Methods

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

recip :: Field a -> Field a #

fromRational :: Rational -> Field a #

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

Defined in Opaleye.Internal.Column

Methods

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

(-) :: Field a -> Field a -> Field a #

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

negate :: Field a -> Field a #

abs :: Field a -> Field a #

signum :: Field a -> Field a #

fromInteger :: Integer -> Field a #

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

Defined in Opaleye.Internal.Column

Methods

fromString :: String -> Field a #

InferrableTableField (Maybe (Field_ n r)) n r Source #

Equivalaent to defining the column with optionalTableField. If the write type is Maybe (Field_ n r) (i.e. DEFAULT can be written to it) then the write type is Field_ n r.

Instance details

Defined in Opaleye.Internal.Table

Methods

tableField :: String -> TableFields (Maybe (Field_ n r)) (Field_ n r) Source #

(Default (Inferrable FromField) a b, Maybe b ~ maybe_b) => Default (Inferrable FromFields) (FieldNullable a) maybe_b Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromFields (FieldNullable a) maybe_b #

Default (Inferrable FromField) a b => Default (Inferrable FromFields) (Field a) b Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable FromFields (Field a) b #

Field a ~ fieldA => Default (Inferrable ToFields) (Field a) fieldA Source # 
Instance details

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (Field a) fieldA #

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

Defined in Opaleye.Internal.MaybeFields

Methods

def :: WithNulls p (Field_ n a) (Field_ n a) #

InferrableTableField (Field_ n r) n r Source #

Equivalent to defining the column with requiredTableField. If the write type is Field_ n r then the read type is also Field_ n r.

Instance details

Defined in Opaleye.Internal.Table

Methods

tableField :: String -> TableFields (Field_ n r) (Field_ n r) Source #

data Nullability Source #

Constructors

NonNullable 
Nullable 

Instances

Instances details
type A ('H NullsT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H NullsT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) = A ('H NullsT :: Arr Type (C a) k2) ('C t)
type A ('H WT :: Arr Type (TC a) k2) ('TC '(t, Req) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H WT :: Arr Type (TC a) k2) ('TC '(t, Req) :: TC a) = A ('H OT :: Arr Type (C a) k2) ('C t)
type A ('H OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) = A ('H OT :: Arr Type (C a) k2) ('C t)
type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) = A ('H HT :: Arr Type (C a) k2) ('C t)
type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) = h
type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) = Maybe (A ('H OT :: Arr Type (C a) Type) ('C t))
type A ('H NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) = Column (Nullable o)
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) = Column (Nullable o)
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) = Column o
type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) = Maybe h

Coercing fields

Working with NULL

Instead of working with NULL you are recommended to use Opaleye.MaybeFields instead.

null :: FieldNullable a Source #

A NULL of any type

isNull :: FieldNullable a -> Field PGBool Source #

TRUE if the value of the field is NULL, FALSE otherwise.

matchNullable Source #

Arguments

:: Field b 
-> (Field a -> Field b) 
-> FieldNullable a 
-> Field b 

If the Field 'Nullable a is NULL then return the Field 'NonNullable b otherwise map the underlying Field 'Nullable a using the provided function.

The Opaleye equivalent of maybe.

fromNullable Source #

Arguments

:: Field a 
-> FieldNullable a 
-> Field a 

If the FieldNullable a is NULL then return the provided Field a otherwise return the underlying Field a.

The Opaleye equivalent of fromMaybe and very similar to PostgreSQL's COALESCE.

toNullable :: Field a -> FieldNullable a Source #

Treat a field as though it were nullable. This is always safe.

The Opaleye equivalent of Just.

maybeToNullable :: Maybe (Field a) -> FieldNullable a Source #

If the argument is Nothing return NULL otherwise return the provided value coerced to a nullable type.