rel8-1.6.0.0: Hey! Hey! Can u rel8?
Safe HaskellSafe-Inferred
LanguageHaskell2010

Rel8.Array

Synopsis

ListTable

data ListTable context a Source #

A ListTable value contains zero or more instances of a. You construct ListTables with many or listAgg.

Instances

Instances details
(Table context a, context ~ context') => Table context' (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

Associated Types

type Columns (ListTable context a) :: HTable Source #

type Context (ListTable context a) :: Context Source #

type FromExprs (ListTable context a) Source #

type Transpose context' (ListTable context a) Source #

Methods

toColumns :: ListTable context a -> Columns (ListTable context a) context' Source #

fromColumns :: Columns (ListTable context a) context' -> ListTable context a Source #

fromResult :: Columns (ListTable context a) Result -> FromExprs (ListTable context a) Source #

toResult :: FromExprs (ListTable context a) -> Columns (ListTable context a) Result Source #

context ~ Expr => AltTable (ListTable context) Source # 
Instance details

Defined in Rel8.Table.List

Methods

(<|>:) :: Table Expr a => ListTable context a -> ListTable context a -> ListTable context a Source #

context ~ Expr => AlternativeTable (ListTable context) Source # 
Instance details

Defined in Rel8.Table.List

Methods

emptyTable :: Table Expr a => ListTable context a Source #

Projectable (ListTable context) Source # 
Instance details

Defined in Rel8.Table.List

Methods

project :: Projecting a b => Projection a b -> ListTable context a -> ListTable context b Source #

(context ~ Expr, Table Expr a) => Monoid (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

Methods

mempty :: ListTable context a #

mappend :: ListTable context a -> ListTable context a -> ListTable context a #

mconcat :: [ListTable context a] -> ListTable context a #

(context ~ Expr, Table Expr a) => Semigroup (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

Methods

(<>) :: ListTable context a -> ListTable context a -> ListTable context a #

sconcat :: NonEmpty (ListTable context a) -> ListTable context a #

stimes :: Integral b => b -> ListTable context a -> ListTable context a #

(EqTable a, context ~ Expr) => EqTable (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

Methods

eqTable :: Columns (ListTable context a) (Dict (Sql DBEq)) Source #

(OrdTable a, context ~ Expr) => OrdTable (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

Methods

ordTable :: Columns (ListTable context a) (Dict (Sql DBOrd)) Source #

(ToExprs exprs a, context ~ Expr) => ToExprs (ListTable context exprs) [a] Source # 
Instance details

Defined in Rel8.Table.List

type Transpose to (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

type Transpose to (ListTable context a) = ListTable to (Transpose to a)
type Columns (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

type Columns (ListTable context a)
type Context (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

type Context (ListTable context a) = Context a
type FromExprs (ListTable context a) Source # 
Instance details

Defined in Rel8.Table.List

type FromExprs (ListTable context a) = [FromExprs a]

head :: Table Expr a => ListTable Expr a -> NullTable Expr a Source #

Get the first element of a ListTable (or nullTable if empty).

headExpr :: Sql DBType a => Expr [a] -> Expr (Nullify a) Source #

index :: Table Expr a => Expr Int32 -> ListTable Expr a -> NullTable Expr a Source #

index i as extracts a single element from as, returning nullTable if i is out of range. Note that although PostgreSQL array indexes are 1-based (by default), this function is always 0-based.

indexExpr :: Sql DBType a => Expr Int32 -> Expr [a] -> Expr (Nullify a) Source #

last :: Table Expr a => ListTable Expr a -> NullTable Expr a Source #

Get the last element of a ListTable (or nullTable if empty).

lastExpr :: Sql DBType a => Expr [a] -> Expr (Nullify a) Source #

length :: Table Expr a => ListTable Expr a -> Expr Int32 Source #

Get the length of a ListTable

NonEmptyTable

data NonEmptyTable context a Source #

A NonEmptyTable value contains one or more instances of a. You construct NonEmptyTables with some or nonEmptyAgg.

Instances

Instances details
(Table context a, context ~ context') => Table context' (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

Associated Types

type Columns (NonEmptyTable context a) :: HTable Source #

type Context (NonEmptyTable context a) :: Context Source #

type FromExprs (NonEmptyTable context a) Source #

type Transpose context' (NonEmptyTable context a) Source #

Methods

toColumns :: NonEmptyTable context a -> Columns (NonEmptyTable context a) context' Source #

fromColumns :: Columns (NonEmptyTable context a) context' -> NonEmptyTable context a Source #

fromResult :: Columns (NonEmptyTable context a) Result -> FromExprs (NonEmptyTable context a) Source #

toResult :: FromExprs (NonEmptyTable context a) -> Columns (NonEmptyTable context a) Result Source #

context ~ Expr => AltTable (NonEmptyTable context) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

Methods

(<|>:) :: Table Expr a => NonEmptyTable context a -> NonEmptyTable context a -> NonEmptyTable context a Source #

Projectable (NonEmptyTable context) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

Methods

project :: Projecting a b => Projection a b -> NonEmptyTable context a -> NonEmptyTable context b Source #

(Table Expr a, context ~ Expr) => Semigroup (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

Methods

(<>) :: NonEmptyTable context a -> NonEmptyTable context a -> NonEmptyTable context a #

sconcat :: NonEmpty (NonEmptyTable context a) -> NonEmptyTable context a #

stimes :: Integral b => b -> NonEmptyTable context a -> NonEmptyTable context a #

(EqTable a, context ~ Expr) => EqTable (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

Methods

eqTable :: Columns (NonEmptyTable context a) (Dict (Sql DBEq)) Source #

(OrdTable a, context ~ Expr) => OrdTable (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

Methods

ordTable :: Columns (NonEmptyTable context a) (Dict (Sql DBOrd)) Source #

(ToExprs exprs a, context ~ Expr) => ToExprs (NonEmptyTable context exprs) (NonEmpty a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

type Transpose to (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

type Transpose to (NonEmptyTable context a) = NonEmptyTable to (Transpose to a)
type Columns (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

type Columns (NonEmptyTable context a)
type Context (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

type Context (NonEmptyTable context a) = Context a
type FromExprs (NonEmptyTable context a) Source # 
Instance details

Defined in Rel8.Table.NonEmpty

type FromExprs (NonEmptyTable context a) = NonEmpty (FromExprs a)

head1 :: Table Expr a => NonEmptyTable Expr a -> a Source #

Get the first element of a NonEmptyTable.

index1 :: Table Expr a => Expr Int32 -> NonEmptyTable Expr a -> NullTable Expr a Source #

index1 i as extracts a single element from as, returning nullTable if i is out of range. Note that although PostgreSQL array indexes are 1-based (by default), this function is always 0-based.

index1Expr :: Sql DBType a => Expr Int32 -> Expr (NonEmpty a) -> Expr (Nullify a) Source #

last1 :: Table Expr a => NonEmptyTable Expr a -> a Source #

Get the last element of a NonEmptyTable.

Unsafe

unsafeSubscript :: Sql DBType b => Expr a -> Expr i -> Expr b Source #

unsafeSubscript a i will generate the SQL a[i].

Note that this function is not type checked and the generated SQL has no casts. This is only intended an escape hatch to be used if Rel8 cannot otherwise express the expression you need. If you find yourself using this function, please let us know, as it may indicate that something is missing from Rel8!

unsafeSubscripts :: (Table Expr i, Sql DBType b) => Expr a -> i -> Expr b Source #

unsafeSubscripts a (i, j) will generate the SQL a[i][j].

Note that this function is not type checked and the generated SQL has no casts. This is only intended an escape hatch to be used if Rel8 cannot otherwise express the expression you need. If you find yourself using this function, please let us know, as it may indicate that something is missing from Rel8!