| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
ProjectM36.SQL.Select
Documentation
Constructors
| QuerySelect Select | |
| QueryValues [[ScalarExpr]] | |
| QueryTable TableName | |
| QueryOp QueryOperator Query Query |
Instances
data QueryOperator Source #
Instances
Constructors
| Select | |
Fields | |
Instances
| Generic Select Source # | |
| Show Select Source # | |
| NFData Select Source # | |
Defined in ProjectM36.SQL.Select | |
| Eq Select Source # | |
| Hashable Select Source # | |
| Serialise Select Source # | |
| type Rep Select Source # | |
Defined in ProjectM36.SQL.Select type Rep Select = D1 ('MetaData "Select" "ProjectM36.SQL.Select" "project-m36-1.1.1-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))))) | |
emptySelect :: Select Source #
type SelectItem = (ProjectionScalarExpr, Maybe ColumnAlias) Source #
data WithClause Source #
Constructors
| WithClause | |
Fields
| |
Instances
Constructors
| WithExpr WithExprAlias Select |
Instances
| Generic WithExpr Source # | |
| Show WithExpr Source # | |
| NFData WithExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| Eq WithExpr Source # | |
| Hashable WithExpr Source # | |
| Serialise WithExpr Source # | |
| type Rep WithExpr Source # | |
Defined in ProjectM36.SQL.Select type Rep WithExpr = D1 ('MetaData "WithExpr" "ProjectM36.SQL.Select" "project-m36-1.1.1-inplace" 'False) (C1 ('MetaCons "WithExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WithExprAlias) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Select))) | |
newtype WithExprAlias Source #
Constructors
| WithExprAlias Text |
Instances
| Generic WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select Methods from :: WithExprAlias -> Rep WithExprAlias x Source # to :: Rep WithExprAlias x -> WithExprAlias Source # | |
| Show WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select | |
| NFData WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select Methods rnf :: WithExprAlias -> () Source # | |
| Eq WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select Methods (==) :: WithExprAlias -> WithExprAlias -> Bool Source # (/=) :: WithExprAlias -> WithExprAlias -> Bool Source # | |
| Hashable WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select | |
| Serialise WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select | |
| type Rep WithExprAlias Source # | |
Defined in ProjectM36.SQL.Select type Rep WithExprAlias = D1 ('MetaData "WithExprAlias" "ProjectM36.SQL.Select" "project-m36-1.1.1-inplace" 'True) (C1 ('MetaCons "WithExprAlias" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) | |
data ComparisonOperator Source #
Instances
data QuantifiedComparisonPredicate Source #
Instances
Constructors
Instances
type ScalarExpr = ScalarExprBase ColumnName Source #
data ScalarExprBase n Source #
Constructors
| IntegerLiteral Integer | |
| DoubleLiteral Double | |
| StringLiteral Text | |
| BooleanLiteral Bool | |
| NullLiteral | |
| Identifier n | Interval |
| BinaryOperator (ScalarExprBase n) OperatorName (ScalarExprBase n) | |
| PrefixOperator OperatorName (ScalarExprBase n) | |
| PostfixOperator (ScalarExprBase n) OperatorName | |
| BetweenOperator (ScalarExprBase n) (ScalarExprBase n) (ScalarExprBase n) | |
| FunctionApplication FuncName [ScalarExprBase n] | |
| CaseExpr | |
Fields
| |
| QuantifiedComparison | |
Fields | |
| InExpr InFlag (ScalarExprBase n) InPredicateValue | |
| BooleanOperatorExpr (ScalarExprBase n) BoolOp (ScalarExprBase n) | ExistsSubQuery Select | UniqueSubQuery Select | ScalarSubQuery Select |
| ExistsExpr Select | |
Instances
data InPredicateValue Source #
Constructors
| InList [ScalarExpr] | |
| InQueryExpr Select | |
| InScalarExpr ScalarExpr |
Instances
newtype GroupByExpr Source #
Constructors
| GroupByExpr ProjectionScalarExpr |
Instances
| Generic GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select Methods from :: GroupByExpr -> Rep GroupByExpr x Source # to :: Rep GroupByExpr x -> GroupByExpr Source # | |
| Show GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| NFData GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select Methods rnf :: GroupByExpr -> () Source # | |
| Eq GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select Methods (==) :: GroupByExpr -> GroupByExpr -> Bool Source # (/=) :: GroupByExpr -> GroupByExpr -> Bool Source # | |
| Hashable GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| Serialise GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| type Rep GroupByExpr Source # | |
Defined in ProjectM36.SQL.Select type Rep GroupByExpr = D1 ('MetaData "GroupByExpr" "ProjectM36.SQL.Select" "project-m36-1.1.1-inplace" 'True) (C1 ('MetaCons "GroupByExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectionScalarExpr))) | |
newtype HavingExpr Source #
Constructors
| HavingExpr ProjectionScalarExpr |
Instances
| Generic HavingExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| Show HavingExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| NFData HavingExpr Source # | |
Defined in ProjectM36.SQL.Select Methods rnf :: HavingExpr -> () Source # | |
| Eq HavingExpr Source # | |
Defined in ProjectM36.SQL.Select Methods (==) :: HavingExpr -> HavingExpr -> Bool Source # (/=) :: HavingExpr -> HavingExpr -> Bool Source # | |
| Hashable HavingExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| Serialise HavingExpr Source # | |
Defined in ProjectM36.SQL.Select Methods schemaGen :: Proxy HavingExpr -> SchemaGen Schema Source # toBuilder :: HavingExpr -> Builder Source # extractor :: Extractor HavingExpr Source # | |
| type Rep HavingExpr Source # | |
Defined in ProjectM36.SQL.Select type Rep HavingExpr = D1 ('MetaData "HavingExpr" "ProjectM36.SQL.Select" "project-m36-1.1.1-inplace" 'True) (C1 ('MetaCons "HavingExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProjectionScalarExpr))) | |
Constructors
| SortExpr ScalarExpr (Maybe Direction) (Maybe NullsOrder) |
Instances
| Generic SortExpr Source # | |
| Show SortExpr Source # | |
| NFData SortExpr Source # | |
Defined in ProjectM36.SQL.Select | |
| Eq SortExpr Source # | |
| Hashable SortExpr Source # | |
| Serialise SortExpr Source # | |
| type Rep SortExpr Source # | |
Defined in ProjectM36.SQL.Select type Rep SortExpr = D1 ('MetaData "SortExpr" "ProjectM36.SQL.Select" "project-m36-1.1.1-inplace" 'False) (C1 ('MetaCons "SortExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScalarExpr) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Direction)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe NullsOrder))))) | |
Constructors
| Ascending | |
| Descending |
data NullsOrder Source #
Constructors
| NullsFirst | |
| NullsLast |
Instances
| Generic NullsOrder Source # | |
Defined in ProjectM36.SQL.Select | |
| Show NullsOrder Source # | |
Defined in ProjectM36.SQL.Select | |
| NFData NullsOrder Source # | |
Defined in ProjectM36.SQL.Select Methods rnf :: NullsOrder -> () Source # | |
| Eq NullsOrder Source # | |
Defined in ProjectM36.SQL.Select Methods (==) :: NullsOrder -> NullsOrder -> Bool Source # (/=) :: NullsOrder -> NullsOrder -> Bool Source # | |
| Hashable NullsOrder Source # | |
Defined in ProjectM36.SQL.Select | |
| Serialise NullsOrder Source # | |
Defined in ProjectM36.SQL.Select Methods schemaGen :: Proxy NullsOrder -> SchemaGen Schema Source # toBuilder :: NullsOrder -> Builder Source # extractor :: Extractor NullsOrder Source # | |
| type Rep NullsOrder Source # | |
Instances
| Generic JoinType Source # | |
| Show JoinType Source # | |
| NFData JoinType Source # | |
Defined in ProjectM36.SQL.Select | |
| Eq JoinType Source # | |
| Serialise JoinType Source # | |
| type Rep JoinType Source # | |
Defined in ProjectM36.SQL.Select type Rep JoinType = D1 ('MetaData "JoinType" "ProjectM36.SQL.Select" "project-m36-1.1.1-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 #
Constructors
| JoinOn JoinOnCondition | |
| JoinUsing [UnqualifiedColumnName] |
Instances
newtype JoinOnCondition Source #
Constructors
| JoinOnCondition ScalarExpr |
Instances
newtype ColumnProjectionName Source #
Constructors
| ColumnProjectionName [ProjectionName] |
Instances
data ProjectionName Source #
Constructors
| ProjectionName Text | |
| Asterisk |
Instances
newtype ColumnName Source #
Constructors
| ColumnName [Text] |
Instances
newtype UnqualifiedColumnName Source #
Constructors
| UnqualifiedColumnName Text |
Instances
Instances
| Generic TableName Source # | |
| Show TableName Source # | |
| NFData TableName Source # | |
Defined in ProjectM36.SQL.Select | |
| Eq TableName Source # | |
| Ord TableName Source # | |
Defined in ProjectM36.SQL.Select | |
| Hashable TableName Source # | |
| Serialise TableName Source # | |
| type Rep TableName Source # | |
Defined in ProjectM36.SQL.Select | |
newtype OperatorName Source #
Constructors
| OperatorName [Text] |
Instances
newtype ColumnAlias Source #
Constructors
| ColumnAlias | |
Fields | |
Instances
newtype TableAlias Source #
Constructors
| TableAlias | |
Fields
| |
Instances
Instances
| Generic FuncName Source # | |
| Show FuncName Source # | |
| NFData FuncName Source # | |
Defined in ProjectM36.SQL.Select | |
| Eq FuncName Source # | |
| Ord FuncName Source # | |
Defined in ProjectM36.SQL.Select | |
| Hashable FuncName Source # | |
| Serialise FuncName Source # | |
| type Rep FuncName Source # | |
Defined in ProjectM36.SQL.Select | |
data Distinctness Source #
Instances
| Generic Distinctness Source # | |
Defined in ProjectM36.SQL.Select Methods from :: Distinctness -> Rep Distinctness x Source # to :: Rep Distinctness x -> Distinctness Source # | |
| Show Distinctness Source # | |
Defined in ProjectM36.SQL.Select | |
| NFData Distinctness Source # | |
Defined in ProjectM36.SQL.Select Methods rnf :: Distinctness -> () Source # | |
| Eq Distinctness Source # | |
Defined in ProjectM36.SQL.Select Methods (==) :: Distinctness -> Distinctness -> Bool Source # (/=) :: Distinctness -> Distinctness -> Bool Source # | |
| Hashable Distinctness Source # | |
Defined in ProjectM36.SQL.Select | |
| Serialise Distinctness Source # | |
Defined in ProjectM36.SQL.Select | |
| type Rep Distinctness Source # | |
newtype RestrictionExpr Source #
Constructors
| RestrictionExpr ScalarExpr |
Instances
Constructors
| TableExpr | |
Fields
| |
Instances
data ScalarExprBaseF (n :: Type) r Source #
Constructors