esqueleto-3.5.8.1: Type-safe EDSL for SQL queries on persistent backends.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Esqueleto.Experimental.From.Join

Synopsis

Documentation

data a :& b infixl 2 Source #

A left-precedence pair. Pronounced "and". Used to represent expressions that have been joined together.

The precedence behavior can be demonstrated by:

a :& b :& c == ((a :& b) :& c)

See the examples at the beginning of this module to see how this operator is used in JOIN operations.

Constructors

a :& b infixl 2 

Instances

Instances details
(ToFrom a a', ToFrom b b') => DoCrossJoin NotLateral a b (a' :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy NotLateral -> a -> b -> From (a' :& b') Source #

(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => DoInnerJoin NotLateral a rhs (a' :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& b') Source #

(ToFrom a a', ToFrom b b', ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (a' :& mb), rhs ~ (b, (a' :& mb) -> SqlExpr (Value Bool))) => DoLeftJoin NotLateral a rhs (a' :& mb) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& mb) Source #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) Source #

(Show a, Show b) => Show (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

showsPrec :: Int -> (a :& b) -> ShowS #

show :: (a :& b) -> String #

showList :: [a :& b] -> ShowS #

(ToAlias a, ToAlias b) => ToAlias (a :& b) Source #

Identical to the tuple instance and provided for convenience.

Since: 3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAlias :: (a :& b) -> SqlQuery (a :& b) Source #

(ToAliasReference a, ToAliasReference b) => ToAliasReference (a :& b) Source #

Identical to the tuple instance and provided for convenience.

Since: 3.5.3.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toAliasReference :: Ident -> (a :& b) -> SqlQuery (a :& b) Source #

(ToMaybe a, ToMaybe b) => ToMaybe (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Associated Types

type ToMaybeT (a :& b) Source #

Methods

toMaybe :: (a :& b) -> ToMaybeT (a :& b) Source #

(Eq a, Eq b) => Eq (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

(==) :: (a :& b) -> (a :& b) -> Bool #

(/=) :: (a :& b) -> (a :& b) -> Bool #

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (ma :& mb), ErrorOnLateral b, rhs ~ (b, (ma :& mb) -> SqlExpr (Value Bool))) => ToFrom (FullOuterJoin a rhs) (ma :& mb) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: FullOuterJoin a rhs -> From (ma :& mb) Source #

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, HasOnClause rhs (ma :& b'), ErrorOnLateral b, rhs ~ (b, (ma :& b') -> SqlExpr (Value Bool))) => ToFrom (RightOuterJoin a rhs) (ma :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

toFrom :: RightOuterJoin a rhs -> From (ma :& b') Source #

(SqlSelect a ra, SqlSelect b rb) => SqlSelect (a :& b) (ra :& rb) Source #

You may return joined values from a select query - this is identical to the tuple instance, but is provided for convenience.

Since: 3.5.2.0

Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

type ToMaybeT (a :& b) = ToMaybeT a :& ToMaybeT b

class ValidOnClause a Source #

Instances

Instances details
ToFrom a a' => ValidOnClause a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

ValidOnClause (a -> SqlQuery b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

on :: ValidOnClause a => a -> (b -> SqlExpr (Value Bool)) -> (a, b -> SqlExpr (Value Bool)) infix 9 Source #

An ON clause that describes how two tables are related. This should be used as an infix operator after a JOIN. For example,

select $
from $ table @Person
`innerJoin` table @BlogPost
`on` (\(p :& bP) ->
        p ^. PersonId ==. bP ^. BlogPostAuthorId)

type family ErrorOnLateral a :: Constraint where ... Source #

Equations

ErrorOnLateral (a -> SqlQuery b) = TypeError ('Text "LATERAL can only be used for INNER, LEFT, and CROSS join kinds.") 
ErrorOnLateral _ = () 

type family HasOnClause actual expected :: Constraint where ... Source #

Equations

HasOnClause (a, b -> SqlExpr (Value Bool)) c = () 
HasOnClause a expected = TypeError (((((('Text "Missing ON clause for join with" :$$: 'ShowType a) :$$: 'Text "") :$$: 'Text "Expected: ") :$$: 'ShowType a) :$$: ('Text "`on` " :<>: 'ShowType (expected -> SqlExpr (Value Bool)))) :$$: 'Text "") 

innerJoin :: (ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& b') infixl 2 Source #

INNER JOIN

Used as an infix operator `innerJoin`

select $
from $ table @Person
`innerJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ^. PersonId ==. bp ^. BlogPostAuthorId)

Since: 3.5.0.0

innerJoinLateral :: (ToFrom a a', HasOnClause rhs (a' :& b), SqlSelect b r, ToAlias b, ToAliasReference b, rhs ~ (a' -> SqlQuery b, (a' :& b) -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& b) infixl 2 Source #

INNER JOIN LATERAL

A Lateral subquery join allows the joined query to reference entities from the left hand side of the join. Discards rows that don't match the on clause

Used as an infix operator `innerJoinLateral`

See example 6

Since: 3.5.0.0

crossJoin :: (ToFrom a a', ToFrom b b') => a -> b -> From (a' :& b') infixl 2 Source #

CROSS JOIN

Used as an infix `crossJoin`

select $ do
from $ table @Person
`crossJoin` table @BlogPost

Since: 3.5.0.0

crossJoinLateral :: (ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => a -> (a' -> SqlQuery b) -> From (a' :& b) infixl 2 Source #

CROSS JOIN LATERAL

A Lateral subquery join allows the joined query to reference entities from the left hand side of the join.

Used as an infix operator `crossJoinLateral`

See example 6

Since: 3.5.0.0

leftJoin :: (ToFrom a a', ToFrom b b', ToMaybe b', HasOnClause rhs (a' :& ToMaybeT b'), rhs ~ (b, (a' :& ToMaybeT b') -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& ToMaybeT b') infixl 2 Source #

LEFT OUTER JOIN

Join where the right side may not exist. If the on clause fails then the right side will be NULL'ed Because of this the right side needs to be handled as a Maybe

Used as an infix operator `leftJoin`

select $
from $ table @Person
`leftJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ^. PersonId ==. bp ?. BlogPostAuthorId)

Since: 3.5.0.0

leftJoinLateral :: (ToFrom a a', SqlSelect b r, HasOnClause rhs (a' :& ToMaybeT b), ToAlias b, ToAliasReference b, ToMaybe b, rhs ~ (a' -> SqlQuery b, (a' :& ToMaybeT b) -> SqlExpr (Value Bool))) => a -> rhs -> From (a' :& ToMaybeT b) infixl 2 Source #

LEFT OUTER JOIN LATERAL

Lateral join where the right side may not exist. In the case that the query returns nothing or the on clause fails the right side of the join will be NULL'ed Because of this the right side needs to be handled as a Maybe

Used as an infix operator `leftJoinLateral`

See example 6 for how to use LATERAL

Since: 3.5.0.0

rightJoin :: (ToFrom a a', ToFrom b b', ToMaybe a', HasOnClause rhs (ToMaybeT a' :& b'), rhs ~ (b, (ToMaybeT a' :& b') -> SqlExpr (Value Bool))) => a -> rhs -> From (ToMaybeT a' :& b') infixl 2 Source #

RIGHT OUTER JOIN

Join where the left side may not exist. If the on clause fails then the left side will be NULL'ed Because of this the left side needs to be handled as a Maybe

Used as an infix operator `rightJoin`

select $
from $ table @Person
`rightJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ?. PersonId ==. bp ^. BlogPostAuthorId)

Since: 3.5.0.0

fullOuterJoin :: (ToFrom a a', ToFrom b b', ToMaybe a', ToMaybe b', HasOnClause rhs (ToMaybeT a' :& ToMaybeT b'), rhs ~ (b, (ToMaybeT a' :& ToMaybeT b') -> SqlExpr (Value Bool))) => a -> rhs -> From (ToMaybeT a' :& ToMaybeT b') infixl 2 Source #

FULL OUTER JOIN

Join where both sides of the join may not exist. Because of this the result needs to be handled as a Maybe

Used as an infix operator `fullOuterJoin`

select $
from $ table @Person
`fullOuterJoin` table @BlogPost
`on` (\(p :& bp) ->
        p ?. PersonId ==. bp ?. BlogPostAuthorId)

Since: 3.5.0.0

data Lateral Source #

Instances

Instances details
(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d Source #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d Source #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) Source #

data NotLateral Source #

Instances

Instances details
(ToFrom a a', ToFrom b b') => DoCrossJoin NotLateral a b (a' :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy NotLateral -> a -> b -> From (a' :& b') Source #

(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => DoInnerJoin NotLateral a rhs (a' :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& b') Source #

(ToFrom a a', ToFrom b b', ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (a' :& mb), rhs ~ (b, (a' :& mb) -> SqlExpr (Value Bool))) => DoLeftJoin NotLateral a rhs (a' :& mb) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& mb) Source #

type family IsLateral a where ... Source #

Equations

IsLateral (a -> SqlQuery b, c) = Lateral 
IsLateral (a -> SqlQuery b) = Lateral 
IsLateral a = NotLateral 

class DoInnerJoin lateral lhs rhs res | lateral rhs lhs -> res where Source #

Methods

doInnerJoin :: Proxy lateral -> lhs -> rhs -> From res Source #

Instances

Instances details
(ToFrom a a', ToFrom b b', HasOnClause rhs (a' :& b'), rhs ~ (b, (a' :& b') -> SqlExpr (Value Bool))) => DoInnerJoin NotLateral a rhs (a' :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& b') Source #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doInnerJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d Source #

class DoLeftJoin lateral lhs rhs res | lateral rhs lhs -> res where Source #

Methods

doLeftJoin :: Proxy lateral -> lhs -> rhs -> From res Source #

Instances

Instances details
(ToFrom a a', ToFrom b b', ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (a' :& mb), rhs ~ (b, (a' :& mb) -> SqlExpr (Value Bool))) => DoLeftJoin NotLateral a rhs (a' :& mb) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy NotLateral -> a -> rhs -> From (a' :& mb) Source #

(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doLeftJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) -> From d Source #

class DoCrossJoin lateral lhs rhs res | lateral lhs rhs -> res where Source #

Methods

doCrossJoin :: Proxy lateral -> lhs -> rhs -> From res Source #

Instances

Instances details
(ToFrom a a', ToFrom b b') => DoCrossJoin NotLateral a b (a' :& b') Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy NotLateral -> a -> b -> From (a' :& b') Source #

(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b) => DoCrossJoin Lateral a (a' -> SqlQuery b) (a' :& b) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

doCrossJoin :: Proxy Lateral -> a -> (a' -> SqlQuery b) -> From (a' :& b) Source #

Orphan instances

(DoCrossJoin lateral lhs rhs r, IsLateral rhs ~ lateral) => ToFrom (CrossJoin lhs rhs) r Source # 
Instance details

Methods

toFrom :: CrossJoin lhs rhs -> From r Source #

(DoInnerJoin lateral lhs rhs r, lateral ~ IsLateral rhs) => ToFrom (InnerJoin lhs rhs) r Source # 
Instance details

Methods

toFrom :: InnerJoin lhs rhs -> From r Source #

(DoLeftJoin lateral lhs rhs r, lateral ~ IsLateral rhs) => ToFrom (LeftOuterJoin lhs rhs) r Source # 
Instance details

Methods

toFrom :: LeftOuterJoin lhs rhs -> From r Source #

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (ma :& mb), ErrorOnLateral b, rhs ~ (b, (ma :& mb) -> SqlExpr (Value Bool))) => ToFrom (FullOuterJoin a rhs) (ma :& mb) Source # 
Instance details

Methods

toFrom :: FullOuterJoin a rhs -> From (ma :& mb) Source #

(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, HasOnClause rhs (ma :& b'), ErrorOnLateral b, rhs ~ (b, (ma :& b') -> SqlExpr (Value Bool))) => ToFrom (RightOuterJoin a rhs) (ma :& b') Source # 
Instance details

Methods

toFrom :: RightOuterJoin a rhs -> From (ma :& b') Source #