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

Database.Esqueleto.Experimental.From

Synopsis

Documentation

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

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).

newtype From a Source #

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

Constructors

From 

Fields

Instances

Instances details
ToFrom (From a) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: From a -> From a Source #

class ToFrom a r | a -> r where Source #

A helper class primarily designed to allow using SqlQuery directly in a From expression. This is also useful for embedding a SqlSetOperation, as well as supporting backwards compatibility for the data constructor join tree used prior to 3.5.0.0

Since: 3.5.0.0

Methods

toFrom :: a -> From r Source #

Instances

Instances details
ToFrom (From a) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: From a -> From a Source #

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SubQuery (SqlQuery a)) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a Source #

ToAliasReference a => ToFrom (SqlSetOperation a) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From.SqlSetOperation

(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SqlQuery a) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SqlQuery a -> From a Source #

PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) Source #

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

Methods

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

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

Defined in Database.Esqueleto.Experimental.From.Join

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

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 #

data Table a Source #

Deprecated: @since 3.5.0.0 - use table instead

Constructors

Table

Deprecated: @since 3.5.0.0 - use table instead

Instances

Instances details
PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: Table ent -> From (SqlExpr (Entity ent)) Source #

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

Bring a PersistEntity into scope from a table

select $ from $ table @People

Since: 3.5.0.0

newtype SubQuery a Source #

Deprecated: Since: 3.4.0.0 - It is no longer necessary to tag SqlQuery values with SubQuery

Constructors

SubQuery a

Deprecated: Since: 3.4.0.0 - It is no longer necessary to tag SqlQuery values with SubQuery

Instances

Instances details
(SqlSelect a r, ToAlias a, ToAliasReference a) => ToFrom (SubQuery (SqlQuery a)) a Source # 
Instance details

Defined in Database.Esqueleto.Experimental.From

Methods

toFrom :: SubQuery (SqlQuery a) -> From a Source #

selectQuery :: (SqlSelect a r, ToAlias a, ToAliasReference a) => SqlQuery a -> From a Source #

Select from a subquery, often used in conjuction with joins but can be used without any joins. Because SqlQuery has a ToFrom instance you probably dont need to use this function directly.

select $
     p <- from $
             selectQuery do
             p <- from $ table @Person
             limit 5
             orderBy [ asc p ^. PersonAge ]
     ...

Since: 3.5.0.0