Portability | unknown |
---|---|
Stability | experimental |
Maintainer | [email protected] |
Safe Haskell | None |
Database.Relational.Query.Projectable
Contents
Description
This module defines operators on various polymorphic projections.
- expr :: Projection p a -> Expr p a
- class SqlProjectable p where
- unsafeProjectSqlTerms :: [String] -> p t
- unsafeProjectSql :: SqlProjectable p => String -> p t
- value :: (ShowConstantTermsSQL t, SqlProjectable p) => t -> p t
- valueTrue :: (SqlProjectable p, ProjectableMaybe p) => p (Maybe Bool)
- valueFalse :: (SqlProjectable p, ProjectableMaybe p) => p (Maybe Bool)
- values :: (ShowConstantTermsSQL t, SqlProjectable p) => [t] -> ListProjection p t
- unsafeValueNull :: SqlProjectable p => p (Maybe a)
- data PlaceHolders p
- addPlaceHolders :: Functor f => f a -> f (PlaceHolders p, a)
- unsafePlaceHolders :: PlaceHolders p
- placeholder' :: (PersistableWidth t, SqlProjectable p) => (p t -> a) -> (PlaceHolders t, a)
- placeholder :: (PersistableWidth t, SqlProjectable p, Monad m) => (p t -> m a) -> m (PlaceHolders t, a)
- unsafeShowSqlExpr :: Expr p t -> String
- unsafeShowSqlProjection :: Projection c r -> String
- class ProjectableShowSql p where
- unsafeShowSql :: p a -> String
- type SqlBinOp = Keyword -> Keyword -> Keyword
- unsafeBinOp :: (SqlProjectable p, ProjectableShowSql p) => SqlBinOp -> p a -> p b -> p c
- unsafeUniOp :: (ProjectableShowSql p0, SqlProjectable p1) => (Keyword -> Keyword) -> p0 a -> p1 b
- (.=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.<.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.<=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.>=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.<>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- casesOrElse :: (SqlProjectable p, ProjectableShowSql p) => [(p (Maybe Bool), p a)] -> p a -> p a
- casesOrElse' :: (SqlProjectable p, ProjectableShowSql p) => (p a, [(p a, p b)]) -> p b -> p b
- caseSearch :: (SqlProjectable p, ProjectableShowSql p) => [(p (Maybe Bool), p a)] -> p a -> p a
- caseSearchMaybe :: (ProjectableShowSql p, SqlProjectable p) => [(p (Maybe Bool), p (Maybe a))] -> p (Maybe a)
- case' :: (SqlProjectable p, ProjectableShowSql p) => p a -> [(p a, p b)] -> p b -> p b
- caseMaybe :: (SqlProjectable p, ProjectableShowSql p, ProjectableMaybe p) => p a -> [(p a, p (Maybe b))] -> p (Maybe b)
- in' :: (SqlProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool)
- and' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- or' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- isNothing :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)
- isJust :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)
- fromMaybe :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c r
- fromMaybe' :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c r
- not' :: (SqlProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool)
- exists :: (SqlProjectable p, ProjectableShowSql p) => ListProjection (Projection Exists) r -> p (Maybe Bool)
- (.||.) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p a
- (?||?) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
- (.+.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- (.-.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- (./.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- (.*.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- negate' :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a
- fromIntegral' :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p a -> p b
- showNum :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p a -> p b
- (?+?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
- (?-?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
- (?/?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
- (?*?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
- negateMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a)
- fromIntegralMaybe :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p (Maybe a) -> p (Maybe b)
- showNumMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p (Maybe a) -> p (Maybe b)
- rank :: Projection OverWindow Int64
- denseRank :: Projection OverWindow Int64
- rowNumber :: Projection OverWindow Int64
- percentRank :: Projection OverWindow Double
- cumeDist :: Projection OverWindow Double
- dense_rank :: Projection OverWindow Int64
- row_number :: Projection OverWindow Int64
- percent_rank :: Projection OverWindow Double
- cume_dist :: Projection OverWindow Double
- projectZip :: ProjectableApplicative p => p a -> p b -> p (a, b)
- (><) :: ProjectableApplicative p => p a -> p b -> p (a, b)
- class ProjectableApplicative p => ProjectableIdZip p where
- class ProjectableMaybe p where
- class ProjectableFunctor p where
- (|$|) :: ProductConstructor (a -> b) => (a -> b) -> p a -> p b
- class ProjectableFunctor p => ProjectableApplicative p where
- (|*|) :: p (a -> b) -> p a -> p b
- ipfmap :: (ProjectableFunctor p, ProductConstructor (a -> b)) => p a -> p b
Conversion between individual Projections
expr :: Projection p a -> Expr p aSource
Project from Projection type into expression type.
Projectable from SQL strings
class SqlProjectable p whereSource
Interface to project SQL terms unsafely.
Methods
Arguments
:: [String] | SQL expression strings |
-> p t | Result projection object |
Unsafely project from SQL expression strings.
Instances
SqlProjectable (Expr p) | Unsafely make |
SqlProjectable (Projection OverWindow) | Unsafely make |
SqlProjectable (Projection Aggregated) | Unsafely make |
SqlProjectable (Projection Flat) | Unsafely make |
unsafeProjectSql :: SqlProjectable p => String -> p tSource
Unsafely Project single SQL term.
Projections of values
value :: (ShowConstantTermsSQL t, SqlProjectable p) => t -> p tSource
Generate polymorphic projection of SQL constant values from Haskell value.
valueTrue :: (SqlProjectable p, ProjectableMaybe p) => p (Maybe Bool)Source
Polymorphic proejction of SQL true value.
valueFalse :: (SqlProjectable p, ProjectableMaybe p) => p (Maybe Bool)Source
Polymorphic proejction of SQL false value.
values :: (ShowConstantTermsSQL t, SqlProjectable p) => [t] -> ListProjection p tSource
Polymorphic proejction of SQL set value from Haskell list.
unsafeValueNull :: SqlProjectable p => p (Maybe a)Source
Polymorphic projection of SQL null value.
Placeholders
data PlaceHolders p Source
Placeholder parameter type which has real parameter type arguemnt p
.
Instances
ProjectableApplicative PlaceHolders | Compose record type |
ProjectableFunctor PlaceHolders | Compose seed of record type |
ProjectableIdZip PlaceHolders | Zipping except for identity element laws against placeholder parameter type. |
ProjectableMaybe PlaceHolders | Control phantom |
addPlaceHolders :: Functor f => f a -> f (PlaceHolders p, a)Source
Unsafely add placeholder parameter to queries.
unsafePlaceHolders :: PlaceHolders pSource
Unsafely get placeholder parameter
placeholder' :: (PersistableWidth t, SqlProjectable p) => (p t -> a) -> (PlaceHolders t, a)Source
Provide scoped placeholder and return its parameter object.
placeholder :: (PersistableWidth t, SqlProjectable p, Monad m) => (p t -> m a) -> m (PlaceHolders t, a)Source
Provide scoped placeholder and return its parameter object. Monadic version.
Projectable into SQL strings
unsafeShowSqlExpr :: Expr p t -> StringSource
Unsafely get SQL term from Expr
.
unsafeShowSqlProjection :: Projection c r -> StringSource
Unsafely get SQL term from Proejction
.
class ProjectableShowSql p whereSource
Interface to get SQL term from projections.
Methods
Arguments
:: p a | Source projection object |
-> String | Result SQL expression string. |
Unsafely generate SQL expression string from projection object.
Instances
ProjectableShowSql (Expr p) | Unsafely get SQL term from |
ProjectableShowSql (Projection c) | Unsafely get SQL term from |
Operators
unsafeBinOp :: (SqlProjectable p, ProjectableShowSql p) => SqlBinOp -> p a -> p b -> p cSource
Unsafely make projection binary operator from string binary operator.
unsafeUniOp :: (ProjectableShowSql p0, SqlProjectable p1) => (Keyword -> Keyword) -> p0 a -> p1 bSource
Unsafely make projection unary operator from SQL keyword.
(.=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Compare operator corresponding SQL = .
(.<.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Compare operator corresponding SQL < .
(.<=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Compare operator corresponding SQL <= .
(.>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Compare operator corresponding SQL > .
(.>=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Compare operator corresponding SQL >= .
(.<>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Compare operator corresponding SQL <> .
Arguments
:: (SqlProjectable p, ProjectableShowSql p) | |
=> [(p (Maybe Bool), p a)] | Each when clauses |
-> p a | Else result projection |
-> p a | Result projection |
Same as caseSearch
, but you can write like list casesOrElse
clause.
Arguments
:: (SqlProjectable p, ProjectableShowSql p) | |
=> (p a, [(p a, p b)]) | Projection value to match and each when clauses list |
-> p b | Else result projection |
-> p b | Result projection |
Uncurry version of case'
, and you can write like ... casesOrElse'
clause.
Arguments
:: (SqlProjectable p, ProjectableShowSql p) | |
=> [(p (Maybe Bool), p a)] | Each when clauses |
-> p a | Else result projection |
-> p a | Result projection |
Search case operator correnponding SQL search CASE. Like, CASE WHEN p0 THEN a WHEN p1 THEN b ... ELSE c END
Arguments
:: (ProjectableShowSql p, SqlProjectable p) | |
=> [(p (Maybe Bool), p (Maybe a))] | Each when clauses |
-> p (Maybe a) | Result projection |
Null default version of caseSearch
.
Arguments
:: (SqlProjectable p, ProjectableShowSql p) | |
=> p a | Projection value to match |
-> [(p a, p b)] | Each when clauses |
-> p b | Else result projection |
-> p b | Result projection |
Simple case operator correnponding SQL simple CASE. Like, CASE x WHEN v THEN a WHEN w THEN b ... ELSE c END
Arguments
:: (SqlProjectable p, ProjectableShowSql p, ProjectableMaybe p) | |
=> p a | Projection value to match |
-> [(p a, p (Maybe b))] | Each when clauses |
-> p (Maybe b) | Result projection |
Null default version of case'
.
in' :: (SqlProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool)Source
Binary operator corresponding SQL IN .
and' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Logical operator corresponding SQL AND .
or' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)Source
Logical operator corresponding SQL OR .
isNothing :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)Source
Operator corresponding SQL IS NULL , and extended against record types.
isJust :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)Source
Operator corresponding SQL NOT (... IS NULL) , and extended against record type.
fromMaybe :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c rSource
Operator from maybe type using record extended isNull
.
fromMaybe' :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c rSource
Deprecated: Use fromMaybe instead of this.
Deprecated. Operator from maybe type using record extended isNull
.
not' :: (SqlProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool)Source
Logical operator corresponding SQL NOT .
exists :: (SqlProjectable p, ProjectableShowSql p) => ListProjection (Projection Exists) r -> p (Maybe Bool)Source
Logical operator corresponding SQL EXISTS .
(.||.) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p aSource
Concatinate operator corresponding SQL || .
(?||?) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)Source
Concatinate operator corresponding SQL || . Maybe type version.
(.+.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p aSource
Number operator corresponding SQL + .
(.-.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p aSource
Number operator corresponding SQL - .
(./.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p aSource
Number operator corresponding SQL / .
(.*.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p aSource
Number operator corresponding SQL * .
negate' :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p aSource
Number negate uni-operator corresponding SQL -.
fromIntegral' :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p a -> p bSource
Number fromIntegral uni-operator.
showNum :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p a -> p bSource
Unsafely show number into string-like type in projections.
(?+?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)Source
Number operator corresponding SQL + .
(?-?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)Source
Number operator corresponding SQL - .
(?/?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)Source
Number operator corresponding SQL / .
(?*?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)Source
Number operator corresponding SQL * .
negateMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a)Source
Number negate uni-operator corresponding SQL -.
fromIntegralMaybe :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p (Maybe a) -> p (Maybe b)Source
Number fromIntegral uni-operator.
showNumMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p (Maybe a) -> p (Maybe b)Source
Unsafely show number into string-like type in projections.
Terms for Window function types
rank :: Projection OverWindow Int64Source
RANK() term.
denseRank :: Projection OverWindow Int64Source
DENSE_RANK() term.
rowNumber :: Projection OverWindow Int64Source
ROW_NUMBER() term.
percentRank :: Projection OverWindow DoubleSource
PERCENT_RANK() term.
cumeDist :: Projection OverWindow DoubleSource
CUME_DIST() term.
dense_rank :: Projection OverWindow Int64Source
Deprecated: Use denseRank instead of this.
DENSE_RANK() term.
row_number :: Projection OverWindow Int64Source
Deprecated: Use rowNumber instead of this.
ROW_NUMBER() term.
percent_rank :: Projection OverWindow DoubleSource
Deprecated: Use percentRank instead of this.
PERCENT_RANK() term.
cume_dist :: Projection OverWindow DoubleSource
Deprecated: Use cumeDist instead of this.
CUME_DIST() term.
Zipping projections
projectZip :: ProjectableApplicative p => p a -> p b -> p (a, b)Source
Zipping projections.
(><) :: ProjectableApplicative p => p a -> p b -> p (a, b)Source
Binary operator the same as projectZip
.
class ProjectableApplicative p => ProjectableIdZip p whereSource
Zipping except for identity element laws.
Instances
ProjectableIdZip PlaceHolders | Zipping except for identity element laws against placeholder parameter type. |
Maybe
type projecitoins
class ProjectableMaybe p whereSource
Interface to control Maybe
of phantom type in projections.
Methods
just :: p a -> p (Maybe a)Source
Cast projection phantom type into Maybe
.
flattenMaybe :: p (Maybe (Maybe a)) -> p (Maybe a)Source
Compose nested Maybe
phantom type on projection.
Instances
ProjectableMaybe PlaceHolders | Control phantom |
ProjectableMaybe (Expr p) | |
ProjectableMaybe (Projection c) | Control phantom |
ProjectableFunctor and ProjectableApplicative
class ProjectableFunctor p whereSource
Weaken functor on projections.
Instances
ProjectableFunctor PlaceHolders | Compose seed of record type |
ProjectableFunctor (Pi a) | Compose seed of projection path |
ProjectableFunctor (Projection c) | Compose seed of record type |
class ProjectableFunctor p => ProjectableApplicative p whereSource
Weaken applicative functor on projections.
Instances
ProjectableApplicative PlaceHolders | Compose record type |
ProjectableApplicative (Pi a) | Compose projection path |
ProjectableApplicative (Projection c) | Compose record type |
ipfmap :: (ProjectableFunctor p, ProductConstructor (a -> b)) => p a -> p bSource
Same as |$|
other than using infered record constructor.