relational-query-0.8.3.3: Typeful, Modular, Relational, algebraic query engine

Copyright2013 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Database.Relational.Query.Projectable

Contents

Description

This module defines operators on various polymorphic projections.

Synopsis

Projectable from SQL strings

class SqlProjectable p where Source #

Interface to project SQL terms unsafely.

Minimal complete definition

unsafeProjectSqlTerms'

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> p t Source #

Unsafely project from SQL expression terms.

Instances

SqlProjectable (Projection OverWindow) Source #

Unsafely make Projection from SQL terms.

SqlProjectable (Projection Aggregated) Source #

Unsafely make Projection from SQL terms.

SqlProjectable (Projection Flat) Source #

Unsafely make Projection from SQL terms.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection Flat t Source #

unsafeProjectSql' :: SqlProjectable p => StringSQL -> p t Source #

Unsafely Project single SQL term.

unsafeProjectSqlTerms Source #

Arguments

:: SqlProjectable p 
=> [String]

SQL expression strings

-> p t

Result projection object

Unsafely project from SQL strings. String interface of unsafeProjectSqlTerms'.

unsafeProjectSql :: SqlProjectable p => String -> p t Source #

Unsafely Project single SQL string. String interface of unsafeProjectSql'.

Projections of values

value :: (ShowConstantTermsSQL t, OperatorProjectable p) => t -> p t Source #

Generate polymorphic projection of SQL constant values from Haskell value.

valueTrue :: (OperatorProjectable p, ProjectableMaybe p) => p (Maybe Bool) Source #

Polymorphic proejction of SQL true value.

valueFalse :: (OperatorProjectable p, ProjectableMaybe p) => p (Maybe Bool) Source #

Polymorphic proejction of SQL false value.

values :: (ShowConstantTermsSQL t, OperatorProjectable p) => [t] -> ListProjection p t Source #

Polymorphic proejction of SQL set value from Haskell list.

unsafeValueNull :: OperatorProjectable 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 Source #

Compose record type PlaceHolders using applicative style.

Methods

(|*|) :: PlaceHolders (a -> b) -> PlaceHolders a -> PlaceHolders b Source #

ProjectableFunctor PlaceHolders Source #

Compose seed of record type PlaceHolders.

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> PlaceHolders a -> PlaceHolders b Source #

ProjectableIdZip PlaceHolders Source #

Zipping except for identity element laws against placeholder parameter type.

ProjectableMaybe PlaceHolders Source #

Control phantom Maybe type in placeholder parameters.

unsafeAddPlaceHolders :: Functor f => f a -> f (PlaceHolders p, a) Source #

Unsafely add placeholder parameter to queries.

unsafePlaceHolders :: PlaceHolders p Source #

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.

unitPlaceHolder :: PlaceHolders () Source #

No placeholder semantics

Projectable into SQL strings

class ProjectableShowSql p where Source #

Interface to get SQL term from projections.

Minimal complete definition

unsafeShowSql'

Methods

unsafeShowSql' :: p a -> StringSQL Source #

Unsafely generate SQL expression term from projection object.

Instances

ProjectableShowSql (Projection c) Source #

Unsafely get SQL term from Proejction.

Methods

unsafeShowSql' :: Projection c a -> StringSQL Source #

unsafeShowSql Source #

Arguments

:: ProjectableShowSql p 
=> p a

Source projection object

-> String

Result SQL expression string.

Unsafely generate SQL expression string from projection object. String interface of unsafeShowSql'.

Operators

(.=.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL = .

(.<.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL < .

(.<=.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL <= .

(.>.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL > .

(.>=.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL >= .

(.<>.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL <> .

and' :: (OperatorProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool) -> p (Maybe Bool) infixr 3 Source #

Logical operator corresponding SQL AND .

or' :: (OperatorProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool) -> p (Maybe Bool) infixr 2 Source #

Logical operator corresponding SQL OR .

in' :: (OperatorProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool) infix 4 Source #

Binary operator corresponding SQL IN .

(.||.) :: (OperatorProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p a infixl 5 Source #

Concatinate operator corresponding SQL || .

(?||?) :: (OperatorProjectable p, ProjectableShowSql p, IsString a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a) infixl 5 Source #

Concatinate operator corresponding SQL || . Maybe type version.

like :: (OperatorProjectable p, ProjectableShowSql p, IsString a, ShowConstantTermsSQL a) => p a -> a -> p (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

likeMaybe :: (OperatorProjectable p, ProjectableShowSql p, IsString a, ShowConstantTermsSQL a) => p (Maybe a) -> a -> p (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE . Maybe type version.

like' :: (OperatorProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

likeMaybe' :: (OperatorProjectable p, ProjectableShowSql p, IsString a) => p (Maybe a) -> p (Maybe a) -> p (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

(.+.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 6 Source #

Number operator corresponding SQL + .

(.-.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 6 Source #

Number operator corresponding SQL - .

(.*.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 7 Source #

Number operator corresponding SQL * .

(./.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 7 Source #

Number operator corresponding SQL /// .

(?+?) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a) infixl 6 Source #

Number operator corresponding SQL + .

(?-?) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a) infixl 6 Source #

Number operator corresponding SQL - .

(?*?) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a) infixl 7 Source #

Number operator corresponding SQL * .

(?/?) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a) infixl 7 Source #

Number operator corresponding SQL /// .

isNothing :: (OperatorProjectable (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 :: (OperatorProjectable (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 :: (OperatorProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c r Source #

Operator from maybe type using record extended isNull.

not' :: (OperatorProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool) Source #

Logical operator corresponding SQL NOT .

exists :: (OperatorProjectable p, ProjectableShowSql p) => ListProjection (Projection Exists) r -> p (Maybe Bool) Source #

Logical operator corresponding SQL EXISTS .

negate' :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a Source #

Number negate uni-operator corresponding SQL -.

fromIntegral' :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p a -> p b Source #

Number fromIntegral uni-operator.

showNum :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p a -> p b Source #

Unsafely show number into string-like type in projections.

negateMaybe :: (OperatorProjectable 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.

casesOrElse Source #

Arguments

:: (OperatorProjectable 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.

casesOrElse' Source #

Arguments

:: (OperatorProjectable 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.

caseSearch Source #

Arguments

:: (OperatorProjectable 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

caseSearchMaybe Source #

Arguments

:: (OperatorProjectable p, ProjectableShowSql p) 
=> [(p (Maybe Bool), p (Maybe a))]

Each when clauses

-> p (Maybe a)

Result projection

Null default version of caseSearch.

case' Source #

Arguments

:: (OperatorProjectable 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

caseMaybe Source #

Arguments

:: (OperatorProjectable 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'.

type SqlBinOp = Keyword -> Keyword -> Keyword Source #

Binary operator type for SQL String.

unsafeBinOp :: (SqlProjectable p, ProjectableShowSql p) => SqlBinOp -> p a -> p b -> p c Source #

Unsafely make projection binary operator from string binary operator.

unsafeUniOp :: (ProjectableShowSql p0, SqlProjectable p1) => (Keyword -> Keyword) -> p0 a -> p1 b Source #

Unsafely make projection unary operator from SQL keyword.

Terms for Window function types

rank :: Integral a => Projection OverWindow a Source #

RANK() term.

denseRank :: Integral a => Projection OverWindow a Source #

DENSE_RANK() term.

rowNumber :: Integral a => Projection OverWindow a Source #

ROW_NUMBER() 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) infixl 1 Source #

Binary operator the same as projectZip.

class ProjectableApplicative p => ProjectableIdZip p where Source #

Zipping except for identity element laws.

Minimal complete definition

leftId, rightId

Methods

leftId :: p ((), a) -> p a Source #

rightId :: p (a, ()) -> p a Source #

Instances

ProjectableIdZip PlaceHolders Source #

Zipping except for identity element laws against placeholder parameter type.

Maybe type projecitoins

class ProjectableMaybe p where Source #

Interface to control Maybe of phantom type in projections.

Minimal complete definition

just, flattenMaybe

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

Control phantom Maybe type in placeholder parameters.

ProjectableMaybe (Projection c) Source #

Control phantom Maybe type in projection type Projection.

ProjectableFunctor and ProjectableApplicative

class ProjectableFunctor p where Source #

Weaken functor on projections.

Minimal complete definition

(|$|)

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> p a -> p b infixl 4 Source #

Method like fmap.

Instances

ProjectableFunctor PlaceHolders Source #

Compose seed of record type PlaceHolders.

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> PlaceHolders a -> PlaceHolders b Source #

ProjectableFunctor (Pi a) Source #

Compose seed of projection path Pi which has record result type.

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> Pi a a -> Pi a b Source #

ProjectableFunctor (Projection c) Source #

Compose seed of record type Projection.

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> Projection c a -> Projection c b Source #

class ProjectableFunctor p => ProjectableApplicative p where Source #

Weaken applicative functor on projections.

Minimal complete definition

(|*|)

Methods

(|*|) :: p (a -> b) -> p a -> p b infixl 4 Source #

Method like <*>.

Instances

ProjectableApplicative PlaceHolders Source #

Compose record type PlaceHolders using applicative style.

Methods

(|*|) :: PlaceHolders (a -> b) -> PlaceHolders a -> PlaceHolders b Source #

ProjectableApplicative (Pi a) Source #

Compose projection path Pi which has record result type using applicative style.

Methods

(|*|) :: Pi a (a -> b) -> Pi a a -> Pi a b Source #

ProjectableApplicative (Projection c) Source #

Compose record type Projection using applicative style.

Methods

(|*|) :: Projection c (a -> b) -> Projection c a -> Projection c b Source #

ipfmap :: (ProjectableFunctor p, ProductConstructor (a -> b)) => p a -> p b Source #

Same as |$| other than using inferred record constructor.