opaleye-0.9.5.1: An SQL-generating DSL targeting PostgreSQL
Safe HaskellSafe-Inferred
LanguageHaskell2010

Opaleye.Internal.Column

Synopsis

Documentation

data Nullability Source #

Constructors

NonNullable 
Nullable 

Instances

Instances details
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
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 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 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 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 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 NullsT :: Arr Type (C Type) (TYPE LiftedRep)) ('C '(h, o, n) :: C Type) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

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

Defined in Opaleye.Internal.TypeFamilies

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

Defined in Opaleye.Internal.TypeFamilies

type A ('H OT :: Arr Type (C Type) (TYPE LiftedRep)) ('C '(h, o, NN) :: C Type) = Column o

newtype 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.

Constructors

Column PrimExpr 

Instances

Instances details
Default ToFields Value (Field SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Value (Field SqlJsonb) 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 ByteString (Field SqlBytea) 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 SqlJsonb) 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 SqlJson) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields ByteString (Field SqlJsonb) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Scientific (Field SqlNumeric) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Text (Field SqlText) 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 Text (Field SqlVarcharN) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields Day (Field SqlDate) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields UTCTime (Field SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields CalendarDiffTime (Field SqlInterval) 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 ZonedTime (Field SqlTimestamptz) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields UUID (Field SqlUuid) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields String (Field SqlText) Source # 
Instance details

Defined in Opaleye.Internal.Constant

Default ToFields String (Field SqlVarcharN) Source # 
Instance details

Defined in Opaleye.Internal.Constant

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 RelExprMaker String (Field_ n a) Source # 
Instance details

Defined in Opaleye.Internal.Operators

Methods

def :: RelExprMaker String (Field_ n a) #

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

Defined in Opaleye.Internal.TableMaker

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 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

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

Defined in Opaleye.Internal.Constant

Methods

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

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

Defined in Opaleye.Internal.Constant

Methods

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

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

Defined in Opaleye.Internal.Constant

Methods

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

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 Day) (Field (SqlRange SqlDate)) 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 Int) (Field (SqlRange SqlInt4)) Source # 
Instance details

Defined in Opaleye.Internal.Constant

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 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 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 NullMaker (Field a) (FieldNullable a) Source # 
Instance details

Defined in Opaleye.Internal.Join

Methods

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

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

Defined in Opaleye.Internal.Join

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 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 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 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) #

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) #

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) #

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) #

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

Defined in Opaleye.Internal.Column

Methods

fromString :: String -> 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 #

(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 #

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

Equivalent 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 #

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

Defined in Opaleye.Internal.Inferrable

Methods

def :: Inferrable ToFields (Field a) fieldA #

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 #

(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 #

(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 Nullable a Source #

Only used within a Field_, to indicate that it can be NULL. For example, a Field_ (Nullability SqlText) can be NULL but a Field_ SqlText cannot.

Constructors

Nullable_ 

type family Column a where ... Source #

Do not use. Use Field instead. Will be removed in a later version.

Equations

Column (Nullable a) = FieldNullable a 
Column a = Field a 

unsafeCoerceColumn :: Field_ n a -> Field_ n' b Source #

Treat a Field_ 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 -> Field_ n a -> Field_ n 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 -> Field_ n a -> Field_ n' b -> Field_ n'' c Source #

unOp :: UnOp -> Field_ n a -> Field_ n' b Source #

unsafeCase_ :: [(Field_ n pgBool, Field_ n' a)] -> Field_ n' a -> Field_ n' a Source #

unsafeIfThenElse :: Field_ n' pgBool -> Field_ n a -> Field_ n a -> Field_ n a Source #

unsafeGt :: Field_ n a -> Field_ n a -> Field_ n' pgBool Source #

unsafeEq :: Field_ n a -> Field_ n a -> Field_ n' pgBool Source #

class SqlIntegral a Source #

A dummy typeclass whose instances support integral operations.

Instances

Instances details
SqlIntegral SqlInt2 Source # 
Instance details

Defined in Opaleye.Internal.PGTypesExternal

SqlIntegral SqlInt4 Source # 
Instance details

Defined in Opaleye.Internal.PGTypesExternal

SqlIntegral SqlInt8 Source # 
Instance details

Defined in Opaleye.Internal.PGTypesExternal

SqlIntegral SqlNumeric Source # 
Instance details

Defined in Opaleye.Internal.PGTypesExternal