| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Opaleye.Internal.Column
Synopsis
- data Nullability
 - newtype Field_ (n :: Nullability) sqlType = Column PrimExpr
 - type Field = Field_ NonNullable
 - type FieldNullable = Field_ 'Nullable
 - data Nullable a = Nullable_
 - type family Column a where ...
 - unColumn :: Field_ n a -> PrimExpr
 - unsafeCoerceColumn :: Field_ n a -> Field_ n' b
 - unsafeCast :: String -> Field_ n a -> Field_ n b
 - unsafeCompositeField :: Field_ n a -> String -> Field_ n' b
 - unsafeFromNullable :: Field_ n a -> Field_ n' a
 - binOp :: BinOp -> Field_ n a -> Field_ n' b -> Field_ n'' c
 - unOp :: UnOp -> Field_ n a -> Field_ n' b
 - unsafeCase_ :: [(Field_ n pgBool, Field_ n' a)] -> Field_ n' a -> Field_ n' a
 - unsafeIfThenElse :: Field_ n' pgBool -> Field_ n a -> Field_ n a -> Field_ n a
 - unsafeGt :: Field_ n a -> Field_ n a -> Field_ n' pgBool
 - unsafeEq :: Field_ n a -> Field_ n a -> Field_ n' pgBool
 - class SqlNum a where
- pgFromInteger :: Integer -> Field a
 - sqlFromInteger :: Integer -> Field a
 
 - type PGNum = SqlNum
 - class SqlFractional a where
- pgFromRational :: Rational -> Field a
 - sqlFromRational :: Rational -> Field a
 
 - type PGFractional = SqlFractional
 - class SqlIntegral a
 - type PGIntegral = SqlIntegral
 - class SqlString a where
- pgFromString :: String -> Field a
 - sqlFromString :: String -> Field a
 
 - type PGString = SqlString
 
Documentation
data Nullability Source #
Constructors
| NonNullable | |
| Nullable | 
Instances
| type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
| type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) Source # | |
| type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) Source # | |
| type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
| type A ('H NullsT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
| type A ('H OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
| type A ('H WT :: Arr Type (TC a) k2) ('TC '(t, Req) :: TC a) Source # | |
| type A ('H NullsT :: Arr Type (C Type) (TYPE LiftedRep)) ('C '(h, o, n) :: C Type) Source # | |
| type A ('H OT :: Arr Type (C Type) (TYPE LiftedRep)) ('C '(h, o, N) :: C Type) Source # | |
| type A ('H OT :: Arr Type (C Type) (TYPE LiftedRep)) ('C '(h, o, NN) :: C Type) Source # | |
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.
Instances
type Field = Field_ NonNullable Source #
type FieldNullable = Field_ 'Nullable Source #
Only used within a Field_, to indicate that it can be NULL.
 For example, a  can be Field_ (Nullability SqlText)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.
unsafeFromNullable :: Field_ n a -> Field_ n' a Source #
Minimal complete definition
Instances
| SqlNum SqlFloat8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlNum SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlNum SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlNum SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods pgFromInteger :: Integer -> Field SqlNumeric Source # sqlFromInteger :: Integer -> Field SqlNumeric Source #  | |
class SqlFractional a where Source #
Minimal complete definition
Methods
pgFromRational :: Rational -> Field a Source #
sqlFromRational :: Rational -> Field a Source #
Instances
type PGFractional = SqlFractional Source #
class SqlIntegral a Source #
A dummy typeclass whose instances support integral operations.
Instances
| SqlIntegral SqlInt2 Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlIntegral SqlInt4 Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlIntegral SqlInt8 Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlIntegral SqlNumeric Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
type PGIntegral = SqlIntegral Source #
class SqlString a where Source #
Minimal complete definition
Instances
| SqlString SqlCitext Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlString SqlText Source # | |
Defined in Opaleye.Internal.PGTypesExternal  | |
| SqlString SqlVarcharN Source # | |
Defined in Opaleye.Internal.PGTypesExternal Methods pgFromString :: String -> Field SqlVarcharN Source # sqlFromString :: String -> Field SqlVarcharN Source #  | |