Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type family IMap f a
- data HT
- data OT
- data NullsT
- data WT
- type NN = 'NonNullable
- type N = 'Nullable
- data Optionality
- type Req = 'OReq
- type Opt = 'OOpt
- type family A (a :: Arr h k1 k2) (b :: k1) :: k2
- data Arr h k1 k2 where
- type (:<*>) = 'S
- type Pure = 'K
- type (:<$>) f = (:<*>) (Pure f)
- type Id = 'I
- type (:<|) f x = A f x
- data C a = C (a, a, Nullability)
- data TC a = TC ((a, a, Nullability), Optionality)
- type RecordField f a b c = A f ('C '(a, b, c))
- type TableRecordField f a b c d = A f ('TC '('(a, b, c), d))
- type TableField f a b c d = TableRecordField f a b c d
- type H = 'H HT
- type O = 'H OT
- type Nulls = 'H NullsT
- type W = 'H WT
- type F = 'H
Documentation
type NN = 'NonNullable Source #
Used in RecordField
and TableRecordField
for a non-nullable
field
Used in RecordField
and TableRecordField
for a nullable field
data Optionality Source #
Instances
type A ('H NullsT :: 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 OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) Source # | |
TableRecordField
for a required field
TableRecordField
for an optional field
type family A (a :: Arr h k1 k2) (b :: k1) :: k2 Source #
Instances
type A ('I :: Arr h k2 k2) (a :: k2) Source # | |
Defined in Opaleye.Internal.TypeFamilies | |
type A ('K k5 :: Arr h k4 k2) (_1 :: k4) Source # | |
Defined in Opaleye.Internal.TypeFamilies | |
type A ('S f x :: Arr h k1 k5) (a :: k1) Source # | |
type A ('H NullsT :: 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 OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) 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 NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) Source # | |
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) Source # | |
type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
C (a, a, Nullability) |
Instances
type A ('H HT :: Arr Type (C k2) k2) ('C '(h, o, NN) :: C k2) Source # | |
type A ('H NullsT :: Arr Type (C Type) Type) ('C '(h, o, n) :: C Type) Source # | |
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
type A ('H OT :: Arr Type (C Type) Type) ('C '(h, o, NN) :: C Type) Source # | |
type A ('H HT :: Arr Type (C Type) Type) ('C '(h, o, N) :: C Type) Source # | |
TC ((a, a, Nullability), Optionality) |
Instances
type A ('H NullsT :: 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 OT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H HT :: Arr Type (TC a) k2) ('TC '(t, b) :: TC a) Source # | |
type A ('H WT :: Arr Type (TC a) Type) ('TC '(t, Opt) :: TC a) Source # | |
type RecordField f a b c = A f ('C '(a, b, c)) Source #
type TableRecordField f a b c d = A f ('TC '('(a, b, c), d)) Source #
type TableField f a b c d = TableRecordField f a b c d Source #
Deprecated: Use TableRecordField
instead. Will be remoed in version 0.8.
type Nulls = 'H NullsT Source #
Type families parameter for nulled Opaleye types
(FieldNullable
SqlString
,
FieldNullable
SqlInt4
, etc.)
Type families parameter for Opaleye write types (i.e. wrapped in
Maybe
for optional types)