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

Opaleye.Internal.TypeFamilies

Synopsis

Documentation

type family IMap f a Source #

Instances

Instances details
type IMap Nulled NullsT Source # 
Instance details

Defined in Opaleye.Internal.Join

type IMap Nulled OT Source # 
Instance details

Defined in Opaleye.Internal.Join

data HT Source #

Instances

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

data OT Source #

Instances

Instances details
type IMap Nulled OT Source # 
Instance details

Defined in Opaleye.Internal.Join

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

data NullsT Source #

Instances

Instances details
type IMap Nulled NullsT Source # 
Instance details

Defined in Opaleye.Internal.Join

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

data WT Source #

Instances

Instances details
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 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 NN = 'NonNullable Source #

Used in RecordField and TableRecordField for a non-nullable field

type N = 'Nullable Source #

Used in RecordField and TableRecordField for a nullable field

data Optionality Source #

Constructors

OReq 
OOpt 

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 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 Req = 'OReq Source #

TableRecordField for a required field

type Opt = 'OOpt Source #

TableRecordField for an optional field

type family A (a :: Arr h k1 k2) (b :: k1) :: k2 Source #

Instances

Instances details
type A ('I :: Arr h k2 k2) (a :: k2) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('I :: Arr h k2 k2) (a :: k2) = a
type A ('K k5 :: Arr h k4 k2) (_1 :: k4) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('K k5 :: Arr h k4 k2) (_1 :: k4) = k5
type A ('S f x :: Arr h k1 k5) (a :: k1) Source # 
Instance details

Defined in Opaleye.Internal.TypeFamilies

type A ('S f x :: Arr h k1 k5) (a :: k1) = A f a (A x a)
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

data Arr h k1 k2 where Source #

Constructors

K :: k1 -> Arr h k2 k1 
S :: Arr h k1 (k2 -> k3) -> Arr h k1 k2 -> Arr h k1 k3 
I :: Arr h k1 k1 
H :: h -> Arr h k2 k3 

type (:<*>) = 'S Source #

type Pure = 'K Source #

type (:<$>) f = (:<*>) (Pure f) Source #

type Id = 'I Source #

type (:<|) f x = A f x Source #

data C a Source #

Constructors

C (a, a, Nullability) 

Instances

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

data TC a Source #

Constructors

TC ((a, a, Nullability), Optionality) 

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 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 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 H = 'H HT Source #

Type families parameter for Haskell types (String, Int, etc.)

type O = 'H OT Source #

Type families parameter for Opaleye types (Field SqlString, Field SqlInt4, etc.)

type Nulls = 'H NullsT Source #

Type families parameter for nulled Opaleye types (FieldNullable SqlString, FieldNullable SqlInt4, etc.)

type W = 'H WT Source #

Type families parameter for Opaleye write types (i.e. wrapped in Maybe for optional types)

type F = 'H Source #