project-m36-1.0.0: Relational Algebra Engine
Safe HaskellSafe-Inferred
LanguageHaskell2010

ProjectM36.SQL.Select

Documentation

data Query Source #

Instances

Instances details
Generic Query Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep Query :: Type -> Type Source #

Methods

from :: Query -> Rep Query x Source #

to :: Rep Query x -> Query Source #

Show Query Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData Query Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: Query -> () Source #

Eq Query Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

(==) :: Query -> Query -> Bool Source #

(/=) :: Query -> Query -> Bool Source #

Serialise Query Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Query Source # 
Instance details

Defined in ProjectM36.SQL.Select

data QueryOperator Source #

Instances

Instances details
Generic QueryOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep QueryOperator :: Type -> Type Source #

Show QueryOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData QueryOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: QueryOperator -> () Source #

Eq QueryOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise QueryOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep QueryOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep QueryOperator = D1 ('MetaData "QueryOperator" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "UnionQueryOperator" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "IntersectQueryOperator" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ExceptQueryOperator" 'PrefixI 'False) (U1 :: Type -> Type)))

data Select Source #

Instances

Instances details
Generic Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep Select :: Type -> Type Source #

Show Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: Select -> () Source #

Eq Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Select Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Select = D1 ('MetaData "Select" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "Select" 'PrefixI 'True) ((S1 ('MetaSel ('Just "distinctness") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Distinctness)) :*: S1 ('MetaSel ('Just "projectionClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SelectItem])) :*: (S1 ('MetaSel ('Just "tableExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TableExpr)) :*: S1 ('MetaSel ('Just "withClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WithClause)))))

data WithClause Source #

Instances

Instances details
Generic WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep WithClause :: Type -> Type Source #

Show WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: WithClause -> () Source #

Eq WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep WithClause Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep WithClause = D1 ('MetaData "WithClause" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "WithClause" 'PrefixI 'True) (S1 ('MetaSel ('Just "isRecursive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "withExprs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty WithExpr))))

data WithExpr Source #

Instances

Instances details
Generic WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep WithExpr :: Type -> Type Source #

Show WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: WithExpr -> () Source #

Eq WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep WithExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

newtype WithExprAlias Source #

Constructors

WithExprAlias Text 

Instances

Instances details
Generic WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep WithExprAlias :: Type -> Type Source #

Show WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: WithExprAlias -> () Source #

Eq WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep WithExprAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep WithExprAlias = D1 ('MetaData "WithExprAlias" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "WithExprAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

data InFlag Source #

Constructors

In 
NotIn 

Instances

Instances details
Generic InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep InFlag :: Type -> Type Source #

Show InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: InFlag -> () Source #

Eq InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep InFlag Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep InFlag = D1 ('MetaData "InFlag" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "In" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotIn" 'PrefixI 'False) (U1 :: Type -> Type))

data ComparisonOperator Source #

Constructors

OpLT 
OpGT 
OpGTE 
OpEQ 
OpNE 
OpLTE 

Instances

Instances details
Generic ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep ComparisonOperator :: Type -> Type Source #

Show ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: ComparisonOperator -> () Source #

Eq ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ComparisonOperator Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ComparisonOperator = D1 ('MetaData "ComparisonOperator" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) ((C1 ('MetaCons "OpLT" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OpGT" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpGTE" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "OpEQ" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "OpNE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpLTE" 'PrefixI 'False) (U1 :: Type -> Type))))

data QuantifiedComparisonPredicate Source #

Constructors

QCAny 
QCSome 
QCAll 

Instances

Instances details
Generic QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep QuantifiedComparisonPredicate :: Type -> Type Source #

Show QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

Eq QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep QuantifiedComparisonPredicate Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep QuantifiedComparisonPredicate = D1 ('MetaData "QuantifiedComparisonPredicate" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "QCAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "QCSome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "QCAll" 'PrefixI 'False) (U1 :: Type -> Type)))

data TableRef Source #

Instances

Instances details
Generic TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep TableRef :: Type -> Type Source #

Show TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: TableRef -> () Source #

Eq TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableRef Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableRef = D1 ('MetaData "TableRef" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (((C1 ('MetaCons "SimpleTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableName)) :+: C1 ('MetaCons "InnerJoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JoinCondition))) :+: (C1 ('MetaCons "RightOuterJoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JoinCondition)) :+: C1 ('MetaCons "LeftOuterJoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JoinCondition)))) :+: ((C1 ('MetaCons "FullOuterJoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JoinCondition)) :+: C1 ('MetaCons "CrossJoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef))) :+: (C1 ('MetaCons "NaturalJoinTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef)) :+: (C1 ('MetaCons "AliasedTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TableAlias)) :+: C1 ('MetaCons "QueryTableRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Select))))))

data ScalarExprBase n Source #

Instances

Instances details
Serialise ProjectionScalarExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ScalarExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Generic (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep (ScalarExprBase n) :: Type -> Type Source #

Show n => Show (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData n => NFData (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: ScalarExprBase n -> () Source #

Eq n => Eq (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

(Hashable n, Eq n) => Hashable (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Corecursive (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

embed :: Base (ScalarExprBase n) (ScalarExprBase n) -> ScalarExprBase n Source #

ana :: (a -> Base (ScalarExprBase n) a) -> a -> ScalarExprBase n Source #

apo :: (a -> Base (ScalarExprBase n) (Either (ScalarExprBase n) a)) -> a -> ScalarExprBase n Source #

postpro :: Recursive (ScalarExprBase n) => (forall b. Base (ScalarExprBase n) b -> Base (ScalarExprBase n) b) -> (a -> Base (ScalarExprBase n) a) -> a -> ScalarExprBase n Source #

gpostpro :: (Recursive (ScalarExprBase n), Monad m) => (forall b. m (Base (ScalarExprBase n) b) -> Base (ScalarExprBase n) (m b)) -> (forall c. Base (ScalarExprBase n) c -> Base (ScalarExprBase n) c) -> (a -> Base (ScalarExprBase n) (m a)) -> a -> ScalarExprBase n Source #

Recursive (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

project :: ScalarExprBase n -> Base (ScalarExprBase n) (ScalarExprBase n) Source #

cata :: (Base (ScalarExprBase n) a -> a) -> ScalarExprBase n -> a Source #

para :: (Base (ScalarExprBase n) (ScalarExprBase n, a) -> a) -> ScalarExprBase n -> a Source #

gpara :: (Corecursive (ScalarExprBase n), Comonad w) => (forall b. Base (ScalarExprBase n) (w b) -> w (Base (ScalarExprBase n) b)) -> (Base (ScalarExprBase n) (EnvT (ScalarExprBase n) w a) -> a) -> ScalarExprBase n -> a Source #

prepro :: Corecursive (ScalarExprBase n) => (forall b. Base (ScalarExprBase n) b -> Base (ScalarExprBase n) b) -> (Base (ScalarExprBase n) a -> a) -> ScalarExprBase n -> a Source #

gprepro :: (Corecursive (ScalarExprBase n), Comonad w) => (forall b. Base (ScalarExprBase n) (w b) -> w (Base (ScalarExprBase n) b)) -> (forall c. Base (ScalarExprBase n) c -> Base (ScalarExprBase n) c) -> (Base (ScalarExprBase n) (w a) -> a) -> ScalarExprBase n -> a Source #

type Rep (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep (ScalarExprBase n) = D1 ('MetaData "ScalarExprBase" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) ((((C1 ('MetaCons "IntegerLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "DoubleLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Double))) :+: (C1 ('MetaCons "StringLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "BooleanLiteral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :+: ((C1 ('MetaCons "NullLiteral" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Identifier" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n))) :+: (C1 ('MetaCons "BinaryOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OperatorName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)))) :+: C1 ('MetaCons "PrefixOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OperatorName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)))))) :+: (((C1 ('MetaCons "PostfixOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OperatorName)) :+: C1 ('MetaCons "BetweenOperator" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n))))) :+: (C1 ('MetaCons "FunctionApplication" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FuncName) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ScalarExprBase n])) :+: C1 ('MetaCons "CaseExpr" 'PrefixI 'True) (S1 ('MetaSel ('Just "caseWhens") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(ScalarExprBase n, ScalarExprBase n)]) :*: S1 ('MetaSel ('Just "caseElse") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (ScalarExprBase n)))))) :+: ((C1 ('MetaCons "QuantifiedComparison" 'PrefixI 'True) ((S1 ('MetaSel ('Just "qcExpr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: S1 ('MetaSel ('Just "qcOperator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ComparisonOperator)) :*: (S1 ('MetaSel ('Just "qcPredicate") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 QuantifiedComparisonPredicate) :*: S1 ('MetaSel ('Just "qcQuery") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Select))) :+: C1 ('MetaCons "InExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InFlag) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InPredicateValue)))) :+: (C1 ('MetaCons "BooleanOperatorExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BoolOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ScalarExprBase n)))) :+: C1 ('MetaCons "ExistsExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Select))))))
type Base (ScalarExprBase n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

data BoolOp Source #

Constructors

AndOp 
OrOp 

Instances

Instances details
Generic BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep BoolOp :: Type -> Type Source #

Show BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: BoolOp -> () Source #

Eq BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep BoolOp Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep BoolOp = D1 ('MetaData "BoolOp" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "AndOp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OrOp" 'PrefixI 'False) (U1 :: Type -> Type))

data InPredicateValue Source #

Instances

Instances details
Generic InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep InPredicateValue :: Type -> Type Source #

Show InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: InPredicateValue -> () Source #

Eq InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep InPredicateValue Source # 
Instance details

Defined in ProjectM36.SQL.Select

newtype GroupByExpr Source #

Instances

Instances details
Generic GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep GroupByExpr :: Type -> Type Source #

Show GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: GroupByExpr -> () Source #

Eq GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep GroupByExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep GroupByExpr = D1 ('MetaData "GroupByExpr" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "GroupByExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectionScalarExpr)))

newtype HavingExpr Source #

Instances

Instances details
Generic HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep HavingExpr :: Type -> Type Source #

Show HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: HavingExpr -> () Source #

Eq HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep HavingExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep HavingExpr = D1 ('MetaData "HavingExpr" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "HavingExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectionScalarExpr)))

data SortExpr Source #

Instances

Instances details
Generic SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep SortExpr :: Type -> Type Source #

Show SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: SortExpr -> () Source #

Eq SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep SortExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

data Direction Source #

Constructors

Ascending 
Descending 

Instances

Instances details
Generic Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep Direction :: Type -> Type Source #

Show Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: Direction -> () Source #

Eq Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Direction Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Direction = D1 ('MetaData "Direction" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "Ascending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Descending" 'PrefixI 'False) (U1 :: Type -> Type))

data NullsOrder Source #

Constructors

NullsFirst 
NullsLast 

Instances

Instances details
Generic NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep NullsOrder :: Type -> Type Source #

Show NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: NullsOrder -> () Source #

Eq NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep NullsOrder Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep NullsOrder = D1 ('MetaData "NullsOrder" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "NullsFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullsLast" 'PrefixI 'False) (U1 :: Type -> Type))

data JoinType Source #

Instances

Instances details
Generic JoinType Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep JoinType :: Type -> Type Source #

Show JoinType Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData JoinType Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: JoinType -> () Source #

Eq JoinType Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise JoinType Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep JoinType Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep JoinType = D1 ('MetaData "JoinType" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) ((C1 ('MetaCons "InnerJoin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RightOuterJoin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftOuterJoin" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "FullOuterJoin" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "CrossJoin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NaturalJoin" 'PrefixI 'False) (U1 :: Type -> Type))))

data JoinCondition Source #

Instances

Instances details
Generic JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep JoinCondition :: Type -> Type Source #

Show JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: JoinCondition -> () Source #

Eq JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep JoinCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

newtype JoinOnCondition Source #

Instances

Instances details
Generic JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep JoinOnCondition :: Type -> Type Source #

Show JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: JoinOnCondition -> () Source #

Eq JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep JoinOnCondition Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep JoinOnCondition = D1 ('MetaData "JoinOnCondition" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "JoinOnCondition" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScalarExpr)))

newtype ColumnProjectionName Source #

Instances

Instances details
Generic ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep ColumnProjectionName :: Type -> Type Source #

Show ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Eq ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ProjectionScalarExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ColumnProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ColumnProjectionName = D1 ('MetaData "ColumnProjectionName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "ColumnProjectionName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ProjectionName])))

data ProjectionName Source #

Instances

Instances details
Generic ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep ProjectionName :: Type -> Type Source #

Show ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: ProjectionName -> () Source #

Eq ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ProjectionName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ProjectionName = D1 ('MetaData "ProjectionName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "ProjectionName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Asterisk" 'PrefixI 'False) (U1 :: Type -> Type))

newtype ColumnName Source #

Constructors

ColumnName [Text] 

Instances

Instances details
Generic ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep ColumnName :: Type -> Type Source #

Show ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: ColumnName -> () Source #

Eq ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ScalarExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ColumnName = D1 ('MetaData "ColumnName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "ColumnName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

newtype UnqualifiedColumnName Source #

Instances

Instances details
Generic UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep UnqualifiedColumnName :: Type -> Type Source #

Show UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Eq UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep UnqualifiedColumnName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep UnqualifiedColumnName = D1 ('MetaData "UnqualifiedColumnName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "UnqualifiedColumnName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype TableName Source #

Constructors

TableName [Text] 

Instances

Instances details
Generic TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep TableName :: Type -> Type Source #

Show TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: TableName -> () Source #

Eq TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableName = D1 ('MetaData "TableName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "TableName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

newtype OperatorName Source #

Constructors

OperatorName [Text] 

Instances

Instances details
Generic OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep OperatorName :: Type -> Type Source #

Show OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: OperatorName -> () Source #

Eq OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep OperatorName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep OperatorName = D1 ('MetaData "OperatorName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "OperatorName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

newtype ColumnAlias Source #

Constructors

ColumnAlias 

Fields

Instances

Instances details
Generic ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep ColumnAlias :: Type -> Type Source #

Show ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: ColumnAlias -> () Source #

Eq ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ColumnAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep ColumnAlias = D1 ('MetaData "ColumnAlias" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "ColumnAlias" 'PrefixI 'True) (S1 ('MetaSel ('Just "unColumnAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype TableAlias Source #

Constructors

TableAlias 

Fields

Instances

Instances details
Monoid TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Semigroup TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Generic TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep TableAlias :: Type -> Type Source #

Show TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: TableAlias -> () Source #

Eq TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableAlias Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableAlias = D1 ('MetaData "TableAlias" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "TableAlias" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTableAlias") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

newtype FuncName Source #

Constructors

FuncName [Text] 

Instances

Instances details
Generic FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep FuncName :: Type -> Type Source #

Show FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: FuncName -> () Source #

Eq FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Ord FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep FuncName Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep FuncName = D1 ('MetaData "FuncName" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "FuncName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

data Distinctness Source #

Constructors

Distinct 
All 

Instances

Instances details
Generic Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep Distinctness :: Type -> Type Source #

Show Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: Distinctness -> () Source #

Eq Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Distinctness Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep Distinctness = D1 ('MetaData "Distinctness" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'False) (C1 ('MetaCons "Distinct" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "All" 'PrefixI 'False) (U1 :: Type -> Type))

newtype RestrictionExpr Source #

Instances

Instances details
Generic RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep RestrictionExpr :: Type -> Type Source #

Show RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: RestrictionExpr -> () Source #

Eq RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep RestrictionExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep RestrictionExpr = D1 ('MetaData "RestrictionExpr" "ProjectM36.SQL.Select" "project-m36-1.0.0-inplace" 'True) (C1 ('MetaCons "RestrictionExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScalarExpr)))

data TableExpr Source #

Instances

Instances details
Generic TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Associated Types

type Rep TableExpr :: Type -> Type Source #

Show TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

NFData TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

rnf :: TableExpr -> () Source #

Eq TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Hashable TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

Serialise TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

type Rep TableExpr Source # 
Instance details

Defined in ProjectM36.SQL.Select

data ScalarExprBaseF (n :: Type) r Source #

Instances

Instances details
Foldable (ScalarExprBaseF n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

fold :: Monoid m => ScalarExprBaseF n m -> m Source #

foldMap :: Monoid m => (a -> m) -> ScalarExprBaseF n a -> m Source #

foldMap' :: Monoid m => (a -> m) -> ScalarExprBaseF n a -> m Source #

foldr :: (a -> b -> b) -> b -> ScalarExprBaseF n a -> b Source #

foldr' :: (a -> b -> b) -> b -> ScalarExprBaseF n a -> b Source #

foldl :: (b -> a -> b) -> b -> ScalarExprBaseF n a -> b Source #

foldl' :: (b -> a -> b) -> b -> ScalarExprBaseF n a -> b Source #

foldr1 :: (a -> a -> a) -> ScalarExprBaseF n a -> a Source #

foldl1 :: (a -> a -> a) -> ScalarExprBaseF n a -> a Source #

toList :: ScalarExprBaseF n a -> [a] Source #

null :: ScalarExprBaseF n a -> Bool Source #

length :: ScalarExprBaseF n a -> Int Source #

elem :: Eq a => a -> ScalarExprBaseF n a -> Bool Source #

maximum :: Ord a => ScalarExprBaseF n a -> a Source #

minimum :: Ord a => ScalarExprBaseF n a -> a Source #

sum :: Num a => ScalarExprBaseF n a -> a Source #

product :: Num a => ScalarExprBaseF n a -> a Source #

Traversable (ScalarExprBaseF n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

traverse :: Applicative f => (a -> f b) -> ScalarExprBaseF n a -> f (ScalarExprBaseF n b) Source #

sequenceA :: Applicative f => ScalarExprBaseF n (f a) -> f (ScalarExprBaseF n a) Source #

mapM :: Monad m => (a -> m b) -> ScalarExprBaseF n a -> m (ScalarExprBaseF n b) Source #

sequence :: Monad m => ScalarExprBaseF n (m a) -> m (ScalarExprBaseF n a) Source #

Functor (ScalarExprBaseF n) Source # 
Instance details

Defined in ProjectM36.SQL.Select

Methods

fmap :: (a -> b) -> ScalarExprBaseF n a -> ScalarExprBaseF n b Source #

(<$) :: a -> ScalarExprBaseF n b -> ScalarExprBaseF n a Source #