Copyright | 2013 Kei Hibino |
---|---|
License | BSD3 |
Maintainer | ex8k.hibino@gmail.com |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
This module defines query projection type structure and interfaces.
- data Projection c t
- width :: Projection c r -> Int
- columns :: Projection c r -> [ColumnSQL]
- untype :: Projection c r -> UntypedProjection
- unsafeFromSqlTerms :: [StringSQL] -> Projection c t
- unsafeFromQualifiedSubQuery :: Qualified SubQuery -> Projection c t
- unsafeFromScalarSubQuery :: SubQuery -> Projection c t
- unsafeFromTable :: Table r -> Projection c r
- predicateProjectionFromExpr :: Expr c (Maybe Bool) -> Projection c (Maybe Bool)
- unsafeStringSql :: Projection c r -> StringSQL
- pi :: Projection c a -> Pi a b -> Projection c b
- piMaybe :: Projection c (Maybe a) -> Pi a b -> Projection c (Maybe b)
- piMaybe' :: Projection c (Maybe a) -> Pi a (Maybe b) -> Projection c (Maybe b)
- flattenMaybe :: Projection c (Maybe (Maybe a)) -> Projection c (Maybe a)
- just :: Projection c r -> Projection c (Maybe r)
- unsafeToAggregated :: Projection Flat r -> Projection Aggregated r
- unsafeToFlat :: Projection Aggregated r -> Projection Flat r
- unsafeChangeContext :: Projection c r -> Projection c' r
- unsafeStringSqlNotNullMaybe :: HasColumnConstraint NotNull r => Projection c (Maybe r) -> StringSQL
- pfmap :: ProductConstructor (a -> b) => (a -> b) -> Projection c a -> Projection c b
- pap :: Projection c (a -> b) -> Projection c a -> Projection c b
- data ListProjection p t
- list :: [p t] -> ListProjection p t
- unsafeListFromSubQuery :: SubQuery -> ListProjection p t
- unsafeStringSqlList :: (p t -> StringSQL) -> ListProjection p t -> StringSQL
Projection data structure and interface
data Projection c t Source
Phantom typed projection. Projected into Haskell record type t
.
ProjectableApplicative (Projection c) | Compose record type |
ProjectableFunctor (Projection c) | Compose seed of record type |
ProjectableMaybe (Projection c) | Control phantom |
ProjectableShowSql (Projection c) | Unsafely get SQL term from |
SqlProjectable (Projection OverWindow) | Unsafely make |
SqlProjectable (Projection Aggregated) | Unsafely make |
SqlProjectable (Projection Flat) | Unsafely make |
width :: Projection c r -> Int Source
Width of Projection
.
:: Projection c r | Source |
-> [ColumnSQL] | Result SQL string list |
Get column SQL string list of projection.
untype :: Projection c r -> UntypedProjection Source
Unsafely get untyped projection.
unsafeFromSqlTerms :: [StringSQL] -> Projection c t Source
Unsafely generate Projection
from SQL expression strings.
unsafeFromQualifiedSubQuery :: Qualified SubQuery -> Projection c t Source
Unsafely generate Projection
from qualified (joined) subquery.
unsafeFromScalarSubQuery :: SubQuery -> Projection c t Source
Unsafely generate Projection
from scalar subquery.
unsafeFromTable :: Table r -> Projection c r Source
Unsafely generate unqualified Projection
from Table
.
predicateProjectionFromExpr :: Expr c (Maybe Bool) -> Projection c (Maybe Bool) Source
Lift Expr
to Projection
to use as restrict predicate.
unsafeStringSql :: Projection c r -> StringSQL Source
Unsafely get SQL term from Proejction
.
Projections
:: Projection c a | Source |
-> Pi a b | Projection path |
-> Projection c b | Narrower |
Trace projection path to get narrower Projection
.
:: Projection c (Maybe a) | Source |
-> Pi a b | Projection path |
-> Projection c (Maybe b) | Narrower |
Trace projection path to get narrower Projection
. From Maybe
type to Maybe
type.
:: Projection c (Maybe a) | Source |
-> Pi a (Maybe b) | Projection path. |
-> Projection c (Maybe b) | Narrower |
Trace projection path to get narrower Projection
. From Maybe
type to Maybe
type.
Leaf type of projection path is Maybe
.
flattenMaybe :: Projection c (Maybe (Maybe a)) -> Projection c (Maybe a) Source
Composite nested Maybe
on projection phantom type.
just :: Projection c r -> Projection c (Maybe r) Source
Cast into Maybe
on projection phantom type.
unsafeToAggregated :: Projection Flat r -> Projection Aggregated r Source
Unsafely lift to aggregated context.
unsafeToFlat :: Projection Aggregated r -> Projection Flat r Source
Unsafely down to flat context.
unsafeChangeContext :: Projection c r -> Projection c' r Source
Unsafely cast context type tag.
unsafeStringSqlNotNullMaybe :: HasColumnConstraint NotNull r => Projection c (Maybe r) -> StringSQL Source
Unsafely get SQL string expression of not null key projection.
pfmap :: ProductConstructor (a -> b) => (a -> b) -> Projection c a -> Projection c b Source
Projectable fmap of Projection
type.
pap :: Projection c (a -> b) -> Projection c a -> Projection c b Source
Projectable ap of Projection
type.
List Projection
data ListProjection p t Source
Projection type for row list.
list :: [p t] -> ListProjection p t Source
Make row list projection from Projection
list.
unsafeListFromSubQuery :: SubQuery -> ListProjection p t Source
Make row list projection from SubQuery
.
unsafeStringSqlList :: (p t -> StringSQL) -> ListProjection p t -> StringSQL Source
Map projection show operatoions and concatinate to single SQL expression.