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

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

Database.Relational.Projectable

Contents

Description

This module defines operators on various projected records.

Synopsis

Projectable from SQL strings

class SqlContext c where Source #

Interface to project SQL terms unsafely.

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Record c t Source #

Unsafely project from SQL expression terms.

Instances
SqlContext OverWindow Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext Aggregated Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

SqlContext Flat Source #

Unsafely make Record from SQL terms.

Instance details

Defined in Database.Relational.Projectable.Instances

unsafeProjectSql' :: SqlContext c => StringSQL -> Record c t Source #

Unsafely Project single SQL term.

unsafeProjectSql :: SqlContext c => String -> Record c t Source #

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

Records of values

value :: (ShowConstantTermsSQL t, OperatorContext c) => t -> Record c t Source #

Generate record with polymorphic type of SQL constant values from Haskell value.

valueTrue :: OperatorContext c => Record c (Maybe Bool) Source #

Record with polymorphic type of SQL true value.

valueFalse :: OperatorContext c => Record c (Maybe Bool) Source #

Record with polymorphic type of SQL false value.

values :: (ShowConstantTermsSQL t, OperatorContext c) => [t] -> RecordList (Record c) t Source #

RecordList with polymorphic type of SQL set value from Haskell list.

nothing :: (OperatorContext c, SqlContext c, PersistableWidth a) => Record c (Maybe a) Source #

Record with polymorphic phantom type of SQL null value. Semantics of comparing is unsafe.

Placeholders

data PlaceHolders p Source #

Placeholder parameter type which has real parameter type arguemnt p.

Instances
ProductIsoFunctor PlaceHolders Source #

Compose seed of record type PlaceHolders.

Instance details

Defined in Database.Relational.Projectable.Instances

Methods

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

ProductIsoApplicative PlaceHolders Source #

Compose record type PlaceHolders using applicative style.

Instance details

Defined in Database.Relational.Projectable.Instances

ProjectableMaybe PlaceHolders Source #

Control phantom Maybe type in placeholder parameters.

Instance details

Defined in Database.Relational.Projectable

ProductIsoEmpty PlaceHolders () Source #

Zipping except for identity element laws against placeholder parameter type.

Instance details

Defined in Database.Relational.Projectable.Instances

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

Unsafely add placeholder parameter to queries.

unsafePlaceHolders :: PlaceHolders p Source #

Unsafely get placeholder parameter

pwPlaceholder :: SqlContext c => PersistableRecordWidth a -> (Record c a -> b) -> (PlaceHolders a, b) Source #

Provide scoped placeholder from width and return its parameter object.

placeholder' :: (PersistableWidth t, SqlContext c) => (Record c t -> a) -> (PlaceHolders t, a) Source #

Provide scoped placeholder and return its parameter object.

placeholder :: (PersistableWidth t, SqlContext c, Monad m) => (Record c t -> m a) -> m (PlaceHolders t, a) Source #

Provide scoped placeholder and return its parameter object. Monadic version.

unitPlaceHolder :: PlaceHolders () Source #

No placeholder semantics

unitPH :: PlaceHolders () Source #

No placeholder semantics. Same as unitPlaceHolder

Projectable into SQL strings

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

Unsafely generate SQL expression term from record object.

unsafeShowSql Source #

Arguments

:: Record c a

Source record object

-> String

Result SQL expression string.

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

Operators

(.=.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL = .

(.<.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL < .

(.<=.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL <= .

(.>.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL > .

(.>=.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL >= .

(.<>.) :: OperatorContext c => Record c ft -> Record c ft -> Record c (Maybe Bool) infix 4 Source #

Compare operator corresponding SQL <> .

and' :: OperatorContext c => Record c (Maybe Bool) -> Record c (Maybe Bool) -> Record c (Maybe Bool) infixr 3 Source #

Logical operator corresponding SQL AND .

or' :: OperatorContext c => Record c (Maybe Bool) -> Record c (Maybe Bool) -> Record c (Maybe Bool) infixr 2 Source #

Logical operator corresponding SQL OR .

in' :: OperatorContext c => Record c t -> RecordList (Record c) t -> Record c (Maybe Bool) infix 4 Source #

Binary operator corresponding SQL IN .

(.||.) :: OperatorContext c => Record c a -> Record c a -> Record c a infixl 5 Source #

Concatinate operator corresponding SQL || .

(?||?) :: (OperatorContext c, IsString a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 5 Source #

Concatinate operator corresponding SQL || . Maybe type version.

like :: (OperatorContext c, IsString a, ShowConstantTermsSQL a) => Record c a -> a -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

likeMaybe :: (OperatorContext c, IsString a, ShowConstantTermsSQL a) => Record c (Maybe a) -> a -> Record c (Maybe Bool) infix 4 Source #

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

like' :: (OperatorContext c, IsString a) => Record c a -> Record c a -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

likeMaybe' :: (OperatorContext c, IsString a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe Bool) infix 4 Source #

String-compare operator corresponding SQL LIKE .

(.+.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 6 Source #

Number operator corresponding SQL + .

(.-.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 6 Source #

Number operator corresponding SQL - .

(.*.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 7 Source #

Number operator corresponding SQL * .

(./.) :: (OperatorContext c, Num a) => Record c a -> Record c a -> Record c a infixl 7 Source #

Number operator corresponding SQL /// .

(?+?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 6 Source #

Number operator corresponding SQL + .

(?-?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 6 Source #

Number operator corresponding SQL - .

(?*?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 7 Source #

Number operator corresponding SQL * .

(?/?) :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) -> Record c (Maybe a) infixl 7 Source #

Number operator corresponding SQL /// .

isNothing :: (OperatorContext c, HasColumnConstraint NotNull r) => Record c (Maybe r) -> Predicate c Source #

Operator corresponding SQL IS NULL , and extended against record types.

isJust :: (OperatorContext c, HasColumnConstraint NotNull r) => Record c (Maybe r) -> Predicate c Source #

Operator corresponding SQL NOT (... IS NULL) , and extended against record type.

fromMaybe :: (OperatorContext c, HasColumnConstraint NotNull r) => Record c r -> Record c (Maybe r) -> Record c r Source #

Operator from maybe type using record extended isNull.

not' :: OperatorContext c => Record c (Maybe Bool) -> Record c (Maybe Bool) Source #

Logical operator corresponding SQL NOT .

exists :: OperatorContext c => RecordList (Record Exists) r -> Record c (Maybe Bool) Source #

Logical operator corresponding SQL EXISTS .

negate' :: (OperatorContext c, Num a) => Record c a -> Record c a Source #

Number negate uni-operator corresponding SQL -.

fromIntegral' :: (SqlContext c, Integral a, Num b) => Record c a -> Record c b Source #

Number fromIntegral uni-operator.

showNum :: (SqlContext c, Num a, IsString b) => Record c a -> Record c b Source #

Unsafely show number into string-like type in records.

negateMaybe :: (OperatorContext c, Num a) => Record c (Maybe a) -> Record c (Maybe a) Source #

Number negate uni-operator corresponding SQL -.

fromIntegralMaybe :: (SqlContext c, Integral a, Num b) => Record c (Maybe a) -> Record c (Maybe b) Source #

Number fromIntegral uni-operator.

showNumMaybe :: (SqlContext c, Num a, IsString b) => Record c (Maybe a) -> Record c (Maybe b) Source #

Unsafely show number into string-like type in records.

casesOrElse Source #

Arguments

:: OperatorContext c 
=> [(Predicate c, Record c a)]

Each when clauses

-> Record c a

Else result record

-> Record c a

Result record

Same as caseSearch, but you can write like list casesOrElse clause.

casesOrElse' Source #

Arguments

:: OperatorContext c 
=> (Record c a, [(Record c a, Record c b)])

Record value to match and each when clauses list

-> Record c b

Else result record

-> Record c b

Result record

Uncurry version of case', and you can write like ... casesOrElse' clause.

caseSearch Source #

Arguments

:: OperatorContext c 
=> [(Predicate c, Record c a)]

Each when clauses

-> Record c a

Else result record

-> Record c a

Result record

Search case operator correnponding SQL search CASE. Like, CASE WHEN p0 THEN a WHEN p1 THEN b ... ELSE c END

caseSearchMaybe Source #

Arguments

:: (OperatorContext c, PersistableWidth a) 
=> [(Predicate c, Record c (Maybe a))]

Each when clauses

-> Record c (Maybe a)

Result record

Null default version of caseSearch.

case' Source #

Arguments

:: OperatorContext c 
=> Record c a

Record value to match

-> [(Record c a, Record c b)]

Each when clauses

-> Record c b

Else result record

-> Record c b

Result record

Simple case operator correnponding SQL simple CASE. Like, CASE x WHEN v THEN a WHEN w THEN b ... ELSE c END

caseMaybe Source #

Arguments

:: (OperatorContext c, PersistableWidth b) 
=> Record c a

Record value to match

-> [(Record c a, Record c (Maybe b))]

Each when clauses

-> Record c (Maybe b)

Result record

Null default version of case'.

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

Binary operator type for SQL String.

unsafeBinOp :: SqlContext k => SqlBinOp -> Record k a -> Record k b -> Record k c Source #

Unsafely make binary operator for records from string binary operator.

unsafeUniOp :: SqlContext c2 => (Keyword -> Keyword) -> Record c1 a -> Record c2 b Source #

Unsafely make unary operator for records from SQL keyword.

Terms for Window function types

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

RANK() term.

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

DENSE_RANK() term.

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

ROW_NUMBER() term.

percentRank :: Record OverWindow Double Source #

PERCENT_RANK() term.

cumeDist :: Record OverWindow Double Source #

CUME_DIST() term.

Zipping projections

projectZip :: ProductIsoApplicative p => p a -> p b -> p (a, b) Source #

Zipping projections.

(><) :: ProductIsoApplicative p => p a -> p b -> p (a, b) infixl 1 Source #

Binary operator the same as projectZip.

Maybe type projecitoins

class ProjectableMaybe p where Source #

Interface to control Maybe of phantom type in records.

Methods

just :: p a -> p (Maybe a) Source #

Cast record phantom type into Maybe.

flattenMaybe :: p (Maybe (Maybe a)) -> p (Maybe a) Source #

Compose nested Maybe phantom type on record.

Instances
ProjectableMaybe PlaceHolders Source #

Control phantom Maybe type in placeholder parameters.

Instance details

Defined in Database.Relational.Projectable

ProjectableMaybe (Record c) Source #

Control phantom Maybe type in record type Record.

Instance details

Defined in Database.Relational.Projectable

Methods

just :: Record c a -> Record c (Maybe a) Source #

flattenMaybe :: Record c (Maybe (Maybe a)) -> Record c (Maybe a) Source #

Projection for nested Maybes

class ProjectableFlattenMaybe a b where Source #

Interface to compose phantom Maybe nested type.

Methods

flatten :: ProjectableMaybe p => p a -> p b Source #

Instances
ProjectableFlattenMaybe (Maybe a) b => ProjectableFlattenMaybe (Maybe (Maybe a)) b Source #

Compose Maybe type in record phantom type.

Instance details

Defined in Database.Relational.Projectable

Methods

flatten :: ProjectableMaybe p => p (Maybe (Maybe a)) -> p b Source #

ProjectableFlattenMaybe (Maybe a) (Maybe a) Source #

Not Maybe type is not processed.

Instance details

Defined in Database.Relational.Projectable

Methods

flatten :: ProjectableMaybe p => p (Maybe a) -> p (Maybe a) Source #

flattenPiMaybe Source #

Arguments

:: (PersistableWidth a, ProjectableFlattenMaybe (Maybe b) c) 
=> Record cont (Maybe a)

Source Record. Maybe phantom type

-> Pi a b

Projection path

-> Record cont c

Narrower Record. Flatten Maybe phantom type

Get narrower record with flatten leaf phantom Maybe types along with projection path.

Get narrower records

(!) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c a

Source Record

-> Pi a b

Record path

-> Record c b

Narrower projected object

Get narrower record along with projection path.

(?) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe type

-> Pi a b

Record path

-> Record c (Maybe b)

Narrower projected object. Maybe type result

Same as '(?!)'. Use this operator like '(? #foo) mayX'.

(??) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe phantom type

-> Pi a (Maybe b)

Record path. Maybe type leaf

-> Record c (Maybe b)

Narrower projected object. Maybe phantom type result

Same as '(?!?)'. Use this operator like '(?? #foo) mayX'.

(?!) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe type

-> Pi a b

Record path

-> Record c (Maybe b)

Narrower projected object. Maybe type result

Get narrower record along with projection path Maybe phantom functor is map-ed.

(?!?) infixl 8 Source #

Arguments

:: PersistableWidth a 
=> Record c (Maybe a)

Source Record. Maybe phantom type

-> Pi a (Maybe b)

Record path. Maybe type leaf

-> Record c (Maybe b)

Narrower projected object. Maybe phantom type result

Get narrower record along with projection path and project into result record type. Source record Maybe phantom functor and projection path leaf Maybe functor are join-ed.

(!??) infixl 8 Source #

Arguments

:: (PersistableWidth a, ProjectableFlattenMaybe (Maybe b) c) 
=> Record cont (Maybe a)

Source Record. Maybe phantom type

-> Pi a b

Projection path

-> Record cont c

Narrower flatten and projected object.

Get narrower record with flatten leaf phantom Maybe types along with projection path.

Aggregate functions

unsafeAggregateOp :: (AggregatedContext ac, SqlContext ac) => Keyword -> Record Flat a -> Record ac b Source #

Unsafely make aggregation uni-operator from SQL keyword.

count :: (Integral b, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac b Source #

Aggregation function COUNT.

sum' :: (Num a, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe a) Source #

Aggregation function SUM.

sumMaybe :: (Num a, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe a) Source #

Aggregation function SUM.

avg :: (Num a, Fractional b, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe b) Source #

Aggregation function AVG.

avgMaybe :: (Num a, Fractional b, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe b) Source #

Aggregation function AVG.

max' :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe a) Source #

Aggregation function MAX.

maxMaybe :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe a) Source #

Aggregation function MAX.

min' :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat a -> Record ac (Maybe a) Source #

Aggregation function MIN.

minMaybe :: (Ord a, AggregatedContext ac, SqlContext ac) => Record Flat (Maybe a) -> Record ac (Maybe a) Source #

Aggregation function MIN.

every :: (AggregatedContext ac, SqlContext ac) => Predicate Flat -> Record ac (Maybe Bool) Source #

Aggregation function EVERY.

any' :: (AggregatedContext ac, SqlContext ac) => Predicate Flat -> Record ac (Maybe Bool) Source #

Aggregation function ANY.

some' :: (AggregatedContext ac, SqlContext ac) => Predicate Flat -> Record ac (Maybe Bool) Source #

Aggregation function SOME.