persistent-sql-lifted-0.4.3.1: Monad classes for running queries with Persistent and Esqueleto
Safe HaskellSafe-Inferred
LanguageGHC2021

Database.Persist.Sql.Lifted.From

Synopsis

Type

data From a #

Data type defining the From language. This should not constructed directly in application code.

A From is a SqlQuery which returns a reference to the result of calling from and a function that produces a portion of a FROM clause. This gets passed to the FromRaw FromClause constructor directly when converting from a From to a SqlQuery using from

Since: esqueleto-3.5.0.0

Instances

Instances details
ToFrom (From a) a 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: From a -> From a #

Table

from :: ToFrom a a' => a -> SqlQuery a' #

FROM clause, used to bring entities into scope.

Internally, this function uses the From datatype. Unlike the old from, this does not take a function as a parameter, but rather a value that represents a JOIN tree constructed out of instances of From. This implementation eliminates certain types of runtime errors by preventing the construction of invalid SQL (e.g. illegal nested-from).

table :: PersistEntity ent => From (SqlExpr (Entity ent)) #

Bring a PersistEntity into scope from a table

select $ from $ table @People

Since: esqueleto-3.5.0.0

Joins

data a :& b infixl 2 #

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
Bifunctor (:&)

Since: esqueleto-3.5.14.0

Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

bimap :: (a -> b) -> (c -> d) -> (a :& c) -> b :& d #

first :: (a -> b) -> (a :& c) -> b :& c #

second :: (b -> c) -> (a :& b) -> a :& c #

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

(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) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

GetFirstTable t (t :& ts) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (t :& ts) -> t #

GetFirstTable t ts => GetFirstTable t (ts :& x) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (ts :& x) -> t #

GetFirstTable t (x :& t) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

Methods

getFirstTable :: (x :& t) -> t #

Functor ((:&) a) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

Methods

fmap :: (a0 -> b) -> (a :& a0) -> a :& b #

(<$) :: a0 -> (a :& b) -> a :& a0 #

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

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

(LockableEntity a, LockableEntity b) => LockableEntity (a :& b) 
Instance details

Defined in Database.Esqueleto.Internal.Internal

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

Defined in Database.Esqueleto.Internal.Internal

Methods

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

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

type ToMaybeT (a :& b) 
Instance details

Defined in Database.Esqueleto.Experimental.From.Join

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

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

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)

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 #

INNER JOIN

Used as an infix operator `innerJoin`

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

Since: esqueleto-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 #

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: esqueleto-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 #

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) ->
        just (p ^. PersonId) ==. bp ?. BlogPostAuthorId)

Since: esqueleto-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 #

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: esqueleto-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 #

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: esqueleto-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 #

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: esqueleto-3.5.0.0

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

CROSS JOIN

Used as an infix `crossJoin`

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

Since: esqueleto-3.5.0.0

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

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: esqueleto-3.5.0.0