Safe Haskell | None |
---|---|
Language | Haskell2010 |
Rel8.Array
Contents
Synopsis
- data ListTable (context :: Context) a
- head :: Table Expr a => ListTable Expr a -> NullTable Expr a
- headExpr :: Sql DBType a => Expr [a] -> Expr (Nullify a)
- index :: Table Expr a => Expr Int32 -> ListTable Expr a -> NullTable Expr a
- indexExpr :: Sql DBType a => Expr Int32 -> Expr [a] -> Expr (Nullify a)
- last :: Table Expr a => ListTable Expr a -> NullTable Expr a
- lastExpr :: Sql DBType a => Expr [a] -> Expr (Nullify a)
- length :: Table Expr a => ListTable Expr a -> Expr Int32
- lengthExpr :: Expr [a] -> Expr Int32
- elem :: Sql DBEq a => Expr a -> Expr [a] -> Expr Bool
- data NonEmptyTable (context :: Context) a
- head1 :: Table Expr a => NonEmptyTable Expr a -> a
- head1Expr :: Sql DBType a => Expr (NonEmpty a) -> Expr a
- index1 :: Table Expr a => Expr Int32 -> NonEmptyTable Expr a -> NullTable Expr a
- index1Expr :: Sql DBType a => Expr Int32 -> Expr (NonEmpty a) -> Expr (Nullify a)
- last1 :: Table Expr a => NonEmptyTable Expr a -> a
- last1Expr :: Sql DBType a => Expr (NonEmpty a) -> Expr a
- length1 :: Table Expr a => NonEmptyTable Expr a -> Expr Int32
- length1Expr :: Expr (NonEmpty a) -> Expr Int32
- elem1 :: Sql DBEq a => Expr a -> Expr (NonEmpty a) -> Expr Bool
- unsafeSubscript :: Sql DBType b => Expr a -> Expr i -> Expr b
- unsafeSubscripts :: (Table Expr i, Sql DBType b) => Expr a -> i -> Expr b
ListTable
data ListTable (context :: Context) a Source #
A ListTable
value contains zero or more instances of a
. You construct
ListTable
s with many
or listAgg
.
Instances
elem :: Sql DBEq a => Expr a -> Expr [a] -> Expr Bool infix 4 Source #
tests whether elem
a asa
is an element of the list as
.
NonEmptyTable
data NonEmptyTable (context :: Context) a Source #
A NonEmptyTable
value contains one or more instances of a
. You
construct NonEmptyTable
s with some
or nonEmptyAgg
.
Instances
(Table context a, context ~ context') => Table context' (NonEmptyTable context a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty Associated Types
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 # | |||||||||||||
Defined in Rel8.Table.NonEmpty Methods (<|>:) :: Table Expr a => NonEmptyTable context a -> NonEmptyTable context a -> NonEmptyTable context a Source # | |||||||||||||
Projectable (NonEmptyTable context) Source # | |||||||||||||
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 # | |||||||||||||
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 # | |||||||||||||
Defined in Rel8.Table.NonEmpty | |||||||||||||
(OrdTable a, context ~ Expr) => OrdTable (NonEmptyTable context a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty | |||||||||||||
(ToExprs exprs a, context ~ Expr) => ToExprs (NonEmptyTable context exprs) (NonEmpty a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty | |||||||||||||
type Transpose to (NonEmptyTable context a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty | |||||||||||||
type Columns (NonEmptyTable context a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty | |||||||||||||
type Context (NonEmptyTable context a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty | |||||||||||||
type FromExprs (NonEmptyTable context a) Source # | |||||||||||||
Defined in Rel8.Table.NonEmpty |
head1 :: Table Expr a => NonEmptyTable Expr a -> a Source #
Get the first element of a NonEmptyTable
.
last1 :: Table Expr a => NonEmptyTable Expr a -> a Source #
Get the last element of a NonEmptyTable
.
length1 :: Table Expr a => NonEmptyTable Expr a -> Expr Int32 Source #
Get the length of a NonEmptyTable
elem1 :: Sql DBEq a => Expr a -> Expr (NonEmpty a) -> Expr Bool infix 4 Source #
tests whether elem1
a asa
is an element of the non-empty list
as
.
Unsafe
unsafeSubscript :: Sql DBType b => Expr a -> Expr i -> Expr b Source #
will generate the SQL unsafeSubscript
a ia[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 #
will generate the SQL unsafeSubscripts
a (i, j)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!