Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Literal
- data Statement
- data Insert = Insert {}
- data Delete = Delete {
- table :: !Name
- conditions :: Maybe Expr
- data Setting = Setting !Name !Expr
- data Update = Update {}
- data SelectStmt
- data Select = Select {}
- data SelectOptions = SelectOptions {}
- select :: Select
- selectOptions :: SelectOptions
- data TableRef
- data JoinedTable
- data Alias = Alias {
- aliasName :: Name
- columnNames :: [Name]
- data JoinType
- data JoinQual
- data DistinctClause
- data SetOp
- data AllOrDistinct
- data ResTarget
- data WindowDef = WindowDef Name WindowSpec
- data Over
- data WindowSpec = WindowSpec {
- refName :: Maybe Name
- partitionClause :: [Expr]
- orderClause :: [SortBy]
- noWindow :: Over
- data SortBy = SortBy {}
- data SortOrderOrUsing
- data SortOrder
- data NullsOrder
- data Locking = Locking {}
- data LockingStrength
- data LockWait
- data WithClause = With {
- commonTables :: [CTE]
- recursive :: Recursive
- data Recursive
- data Materialized
- data CTE = CommonTableExpr {
- name :: Name
- aliases :: [Name]
- materialized :: Materialized
- query :: Statement
- data Expr
- = Lit !Literal
- | CRef Name
- | NumberedParam !Word
- | HaskellParam !Text
- | BinOp !BinOp !Expr !Expr
- | Unary !UnaryOp !Expr
- | Indirection Expr (NonEmpty Indirection)
- | SelectExpr SelectStmt
- | L LikeE
- | Fun FunctionApplication
- | Cas Case
- type Indirection = Name
- data BinOp
- data UnaryOp
- data LikeOp
- data LikeE = LikeE {}
- like :: LikeOp -> Expr -> Expr -> LikeE
- data FunctionApplication = FApp {
- name :: Name
- indirection :: [Indirection]
- arguments :: FunctionArguments
- withinGroup :: [SortBy]
- filterClause :: Maybe Expr
- over :: Over
- fapp :: (Name, [Indirection]) -> FunctionArguments -> FunctionApplication
- fapp1 :: Name -> [Expr] -> FunctionApplication
- setSortBy :: FunctionApplication -> [SortBy] -> FunctionApplication
- data FunctionArguments
- data ArgsList = ArgsList {}
- argsList :: NonEmpty Argument -> ArgsList
- data Argument
- data Case = Case {
- whenClause :: [(Expr, Expr)]
- implicitArg :: Maybe Expr
- elseClause :: Maybe Expr
Documentation
Instances
Instances
Queries of the form INSERT INTO table (columns) VALUES (values);
Limitations:
* single row
* no ON CONFLICT
Instances
Eq Insert Source # | |
Data Insert Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Insert -> c Insert # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Insert # toConstr :: Insert -> Constr # dataTypeOf :: Insert -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Insert) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Insert) # gmapT :: (forall b. Data b => b -> b) -> Insert -> Insert # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Insert -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Insert -> r # gmapQ :: (forall d. Data d => d -> u) -> Insert -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Insert -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Insert -> m Insert # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Insert -> m Insert # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Insert -> m Insert # | |
Show Insert Source # | |
Generic Insert Source # | |
FormatSql Insert Source # | |
Lift Insert Source # | |
type Rep Insert Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Insert = D1 ('MetaData "Insert" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Insert" 'PrefixI 'True) (S1 ('MetaSel ('Just "table") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name) :*: (S1 ('MetaSel ('Just "columns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Name)) :*: S1 ('MetaSel ('Just "values") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Expr))))) |
Queries of the form DELETE FROM table WHERE conditions
.
Instances
Eq Delete Source # | |
Data Delete Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Delete -> c Delete # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Delete # toConstr :: Delete -> Constr # dataTypeOf :: Delete -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Delete) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Delete) # gmapT :: (forall b. Data b => b -> b) -> Delete -> Delete # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Delete -> r # gmapQ :: (forall d. Data d => d -> u) -> Delete -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Delete -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Delete -> m Delete # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Delete -> m Delete # | |
Show Delete Source # | |
Generic Delete Source # | |
FormatSql Delete Source # | |
Lift Delete Source # | |
type Rep Delete Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Delete = D1 ('MetaData "Delete" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Delete" 'PrefixI 'True) (S1 ('MetaSel ('Just "table") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name) :*: S1 ('MetaSel ('Just "conditions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr)))) |
Instances
Eq Setting Source # | |
Data Setting Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Setting -> c Setting # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Setting # toConstr :: Setting -> Constr # dataTypeOf :: Setting -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Setting) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Setting) # gmapT :: (forall b. Data b => b -> b) -> Setting -> Setting # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Setting -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Setting -> r # gmapQ :: (forall d. Data d => d -> u) -> Setting -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Setting -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Setting -> m Setting # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Setting -> m Setting # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Setting -> m Setting # | |
Show Setting Source # | |
Generic Setting Source # | |
FormatSql Setting Source # | |
Lift Setting Source # | |
type Rep Setting Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Setting = D1 ('MetaData "Setting" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Setting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr))) |
Queries of the form UPDATE table SET settings WHERE conditions
. Where each
Setting name literal
is like SQL name = literal
.
Instances
Eq Update Source # | |
Data Update Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Update -> c Update # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Update # toConstr :: Update -> Constr # dataTypeOf :: Update -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Update) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Update) # gmapT :: (forall b. Data b => b -> b) -> Update -> Update # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Update -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Update -> r # gmapQ :: (forall d. Data d => d -> u) -> Update -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Update -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Update -> m Update # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Update -> m Update # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Update -> m Update # | |
Show Update Source # | |
Generic Update Source # | |
FormatSql Update Source # | |
Lift Update Source # | |
type Rep Update Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Update = D1 ('MetaData "Update" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Update" 'PrefixI 'True) (S1 ('MetaSel ('Just "table") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Name) :*: (S1 ('MetaSel ('Just "settings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Setting)) :*: S1 ('MetaSel ('Just "conditions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr))))) |
data SelectStmt Source #
SelectValues (NonEmpty (NonEmpty Expr)) | |
Simple Select | |
S SelectStmt SelectOptions | |
Set SetOp AllOrDistinct SelectStmt SelectStmt |
Instances
Instances
data SelectOptions Source #
Instances
Instances
data JoinedTable Source #
Instances
Alias | |
|
Instances
Eq Alias Source # | |
Data Alias Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Alias -> c Alias # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Alias # dataTypeOf :: Alias -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Alias) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Alias) # gmapT :: (forall b. Data b => b -> b) -> Alias -> Alias # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Alias -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Alias -> r # gmapQ :: (forall d. Data d => d -> u) -> Alias -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Alias -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Alias -> m Alias # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Alias -> m Alias # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Alias -> m Alias # | |
Show Alias Source # | |
Generic Alias Source # | |
FormatSql Alias Source # | |
Lift Alias Source # | |
type Rep Alias Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Alias = D1 ('MetaData "Alias" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Alias" 'PrefixI 'True) (S1 ('MetaSel ('Just "aliasName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "columnNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]))) |
Instances
Bounded JoinType Source # | |
Enum JoinType Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax | |
Eq JoinType Source # | |
Data JoinType Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinType -> c JoinType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinType # toConstr :: JoinType -> Constr # dataTypeOf :: JoinType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinType) # gmapT :: (forall b. Data b => b -> b) -> JoinType -> JoinType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinType -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinType -> r # gmapQ :: (forall d. Data d => d -> u) -> JoinType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinType -> m JoinType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinType -> m JoinType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinType -> m JoinType # | |
Show JoinType Source # | |
Generic JoinType Source # | |
FormatSql JoinType Source # | |
Lift JoinType Source # | |
type Rep JoinType Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep JoinType = D1 ('MetaData "JoinType" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) ((C1 ('MetaCons "Inner" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LeftJoin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "RightJoin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Full" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Eq JoinQual Source # | |
Data JoinQual Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinQual -> c JoinQual # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinQual # toConstr :: JoinQual -> Constr # dataTypeOf :: JoinQual -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinQual) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinQual) # gmapT :: (forall b. Data b => b -> b) -> JoinQual -> JoinQual # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinQual -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinQual -> r # gmapQ :: (forall d. Data d => d -> u) -> JoinQual -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinQual -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinQual -> m JoinQual # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinQual -> m JoinQual # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinQual -> m JoinQual # | |
Show JoinQual Source # | |
Generic JoinQual Source # | |
Lift JoinQual Source # | |
type Rep JoinQual Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep JoinQual = D1 ('MetaData "JoinQual" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Using" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :+: (C1 ('MetaCons "On" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr)) :+: C1 ('MetaCons "Natural" 'PrefixI 'False) (U1 :: Type -> Type))) |
data DistinctClause Source #
Instances
Instances
Bounded SetOp Source # | |
Enum SetOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax | |
Eq SetOp Source # | |
Data SetOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetOp -> c SetOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetOp # dataTypeOf :: SetOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SetOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetOp) # gmapT :: (forall b. Data b => b -> b) -> SetOp -> SetOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetOp -> r # gmapQ :: (forall d. Data d => d -> u) -> SetOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SetOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetOp -> m SetOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetOp -> m SetOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetOp -> m SetOp # | |
Show SetOp Source # | |
Generic SetOp Source # | |
FormatSql SetOp Source # | |
Lift SetOp Source # | |
type Rep SetOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep SetOp = D1 ('MetaData "SetOp" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Union" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Intersect" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Except" 'PrefixI 'False) (U1 :: Type -> Type))) |
data AllOrDistinct Source #
Instances
Instances
Eq ResTarget Source # | |
Data ResTarget Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ResTarget -> c ResTarget # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ResTarget # toConstr :: ResTarget -> Constr # dataTypeOf :: ResTarget -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ResTarget) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ResTarget) # gmapT :: (forall b. Data b => b -> b) -> ResTarget -> ResTarget # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ResTarget -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ResTarget -> r # gmapQ :: (forall d. Data d => d -> u) -> ResTarget -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ResTarget -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ResTarget -> m ResTarget # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ResTarget -> m ResTarget # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ResTarget -> m ResTarget # | |
Show ResTarget Source # | |
Generic ResTarget Source # | |
FormatSql ResTarget Source # | |
Lift ResTarget Source # | |
type Rep ResTarget Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep ResTarget = D1 ('MetaData "ResTarget" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Star" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)))) |
Instances
Eq WindowDef Source # | |
Data WindowDef Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowDef -> c WindowDef # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WindowDef # toConstr :: WindowDef -> Constr # dataTypeOf :: WindowDef -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WindowDef) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowDef) # gmapT :: (forall b. Data b => b -> b) -> WindowDef -> WindowDef # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowDef -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowDef -> r # gmapQ :: (forall d. Data d => d -> u) -> WindowDef -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowDef -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowDef -> m WindowDef # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowDef -> m WindowDef # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowDef -> m WindowDef # | |
Show WindowDef Source # | |
Generic WindowDef Source # | |
FormatSql WindowDef Source # | |
Lift WindowDef Source # | |
type Rep WindowDef Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep WindowDef = D1 ('MetaData "WindowDef" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "WindowDef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WindowSpec))) |
Instances
Eq Over Source # | |
Data Over Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Over -> c Over # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Over # dataTypeOf :: Over -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Over) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Over) # gmapT :: (forall b. Data b => b -> b) -> Over -> Over # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Over -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Over -> r # gmapQ :: (forall d. Data d => d -> u) -> Over -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Over -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Over -> m Over # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Over -> m Over # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Over -> m Over # | |
Show Over Source # | |
Generic Over Source # | |
Lift Over Source # | |
type Rep Over Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Over = D1 ('MetaData "Over" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "WindowName" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name)) :+: C1 ('MetaCons "Window" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 WindowSpec))) |
data WindowSpec Source #
WindowSpec | |
|
Instances
SortBy | |
|
Instances
Eq SortBy Source # | |
Data SortBy Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortBy -> c SortBy # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortBy # toConstr :: SortBy -> Constr # dataTypeOf :: SortBy -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SortBy) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortBy) # gmapT :: (forall b. Data b => b -> b) -> SortBy -> SortBy # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortBy -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortBy -> r # gmapQ :: (forall d. Data d => d -> u) -> SortBy -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SortBy -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortBy -> m SortBy # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortBy -> m SortBy # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortBy -> m SortBy # | |
Show SortBy Source # | |
Generic SortBy Source # | |
FormatSql SortBy Source # | |
Lift SortBy Source # | |
type Rep SortBy Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep SortBy = D1 ('MetaData "SortBy" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "SortBy" 'PrefixI 'True) (S1 ('MetaSel ('Just "column") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "direction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SortOrderOrUsing) :*: S1 ('MetaSel ('Just "nulls") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 NullsOrder)))) |
data SortOrderOrUsing Source #
Instances
Instances
Bounded SortOrder Source # | |
Enum SortOrder Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax succ :: SortOrder -> SortOrder # pred :: SortOrder -> SortOrder # fromEnum :: SortOrder -> Int # enumFrom :: SortOrder -> [SortOrder] # enumFromThen :: SortOrder -> SortOrder -> [SortOrder] # enumFromTo :: SortOrder -> SortOrder -> [SortOrder] # enumFromThenTo :: SortOrder -> SortOrder -> SortOrder -> [SortOrder] # | |
Eq SortOrder Source # | |
Data SortOrder Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortOrder -> c SortOrder # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortOrder # toConstr :: SortOrder -> Constr # dataTypeOf :: SortOrder -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SortOrder) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortOrder) # gmapT :: (forall b. Data b => b -> b) -> SortOrder -> SortOrder # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortOrder -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortOrder -> r # gmapQ :: (forall d. Data d => d -> u) -> SortOrder -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SortOrder -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortOrder -> m SortOrder # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortOrder -> m SortOrder # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortOrder -> m SortOrder # | |
Show SortOrder Source # | |
Generic SortOrder Source # | |
FormatSql SortOrder Source # | |
Lift SortOrder Source # | |
type Rep SortOrder Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep SortOrder = D1 ('MetaData "SortOrder" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Ascending" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Descending" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DefaultSortOrder" 'PrefixI 'False) (U1 :: Type -> Type))) |
data NullsOrder Source #
Instances
Instances
Eq Locking Source # | |
Data Locking Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Locking -> c Locking # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Locking # toConstr :: Locking -> Constr # dataTypeOf :: Locking -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Locking) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Locking) # gmapT :: (forall b. Data b => b -> b) -> Locking -> Locking # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Locking -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Locking -> r # gmapQ :: (forall d. Data d => d -> u) -> Locking -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Locking -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Locking -> m Locking # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Locking -> m Locking # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Locking -> m Locking # | |
Show Locking Source # | |
Generic Locking Source # | |
FormatSql Locking Source # | |
Lift Locking Source # | |
type Rep Locking Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Locking = D1 ('MetaData "Locking" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Locking" 'PrefixI 'True) (S1 ('MetaSel ('Just "strength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LockingStrength) :*: (S1 ('MetaSel ('Just "tables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Just "wait") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LockWait)))) |
data LockingStrength Source #
Instances
Instances
Bounded LockWait Source # | |
Enum LockWait Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax | |
Eq LockWait Source # | |
Data LockWait Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LockWait -> c LockWait # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LockWait # toConstr :: LockWait -> Constr # dataTypeOf :: LockWait -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LockWait) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockWait) # gmapT :: (forall b. Data b => b -> b) -> LockWait -> LockWait # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LockWait -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LockWait -> r # gmapQ :: (forall d. Data d => d -> u) -> LockWait -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LockWait -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LockWait -> m LockWait # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LockWait -> m LockWait # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LockWait -> m LockWait # | |
Show LockWait Source # | |
Generic LockWait Source # | |
FormatSql LockWait Source # | |
Lift LockWait Source # | |
type Rep LockWait Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep LockWait = D1 ('MetaData "LockWait" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "LockWaitError" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LockWaitSkip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LockWaitBlock" 'PrefixI 'False) (U1 :: Type -> Type))) |
data WithClause Source #
With | |
|
Instances
Instances
data Materialized Source #
Instances
CommonTableExpr | |
|
Instances
Eq CTE Source # | |
Data CTE Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CTE -> c CTE # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CTE # dataTypeOf :: CTE -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CTE) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CTE) # gmapT :: (forall b. Data b => b -> b) -> CTE -> CTE # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CTE -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CTE -> r # gmapQ :: (forall d. Data d => d -> u) -> CTE -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CTE -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CTE -> m CTE # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CTE -> m CTE # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CTE -> m CTE # | |
Show CTE Source # | |
Generic CTE Source # | |
FormatSql CTE Source # | |
Lift CTE Source # | |
type Rep CTE Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep CTE = D1 ('MetaData "CTE" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "CommonTableExpr" 'PrefixI 'True) ((S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Just "aliases") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name])) :*: (S1 ('MetaSel ('Just "materialized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Materialized) :*: S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Statement)))) |
Instances
type Indirection = Name Source #
Instances
Bounded BinOp Source # | |
Enum BinOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax | |
Eq BinOp Source # | |
Data BinOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BinOp -> c BinOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BinOp # dataTypeOf :: BinOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BinOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BinOp) # gmapT :: (forall b. Data b => b -> b) -> BinOp -> BinOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BinOp -> r # gmapQ :: (forall d. Data d => d -> u) -> BinOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BinOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BinOp -> m BinOp # | |
Show BinOp Source # | |
Generic BinOp Source # | |
FormatSql BinOp Source # | |
Lift BinOp Source # | |
type Rep BinOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep BinOp = D1 ('MetaData "BinOp" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) ((((C1 ('MetaCons "Mul" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Div" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Add" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sub" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Exponent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Mod" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Eq" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LT" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "LTE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GT" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GTE" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NEq" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "IsDistinctFrom" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IsNotDistinctFrom" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "And" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Or" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Instances
Bounded UnaryOp Source # | |
Enum UnaryOp Source # | |
Eq UnaryOp Source # | |
Data UnaryOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UnaryOp -> c UnaryOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UnaryOp # toConstr :: UnaryOp -> Constr # dataTypeOf :: UnaryOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UnaryOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UnaryOp) # gmapT :: (forall b. Data b => b -> b) -> UnaryOp -> UnaryOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UnaryOp -> r # gmapQ :: (forall d. Data d => d -> u) -> UnaryOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> UnaryOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UnaryOp -> m UnaryOp # | |
Show UnaryOp Source # | |
Generic UnaryOp Source # | |
Lift UnaryOp Source # | |
type Rep UnaryOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep UnaryOp = D1 ('MetaData "UnaryOp" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) ((C1 ('MetaCons "Negate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Not" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "IsNull" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotNull" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Bounded LikeOp Source # | |
Enum LikeOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax | |
Eq LikeOp Source # | |
Data LikeOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LikeOp -> c LikeOp # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LikeOp # toConstr :: LikeOp -> Constr # dataTypeOf :: LikeOp -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LikeOp) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LikeOp) # gmapT :: (forall b. Data b => b -> b) -> LikeOp -> LikeOp # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LikeOp -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LikeOp -> r # gmapQ :: (forall d. Data d => d -> u) -> LikeOp -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LikeOp -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LikeOp -> m LikeOp # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LikeOp -> m LikeOp # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LikeOp -> m LikeOp # | |
Show LikeOp Source # | |
Generic LikeOp Source # | |
Lift LikeOp Source # | |
type Rep LikeOp Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep LikeOp = D1 ('MetaData "LikeOp" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Like" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ILike" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Similar" 'PrefixI 'False) (U1 :: Type -> Type))) |
Instances
Eq LikeE Source # | |
Data LikeE Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LikeE -> c LikeE # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LikeE # dataTypeOf :: LikeE -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LikeE) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LikeE) # gmapT :: (forall b. Data b => b -> b) -> LikeE -> LikeE # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LikeE -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LikeE -> r # gmapQ :: (forall d. Data d => d -> u) -> LikeE -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> LikeE -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> LikeE -> m LikeE # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LikeE -> m LikeE # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LikeE -> m LikeE # | |
Show LikeE Source # | |
Generic LikeE Source # | |
FormatSql LikeE Source # | |
Lift LikeE Source # | |
type Rep LikeE Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep LikeE = D1 ('MetaData "LikeE" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "LikeE" 'PrefixI 'True) ((S1 ('MetaSel ('Just "op") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LikeOp) :*: S1 ('MetaSel ('Just "string") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr)) :*: (S1 ('MetaSel ('Just "likePattern") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr) :*: (S1 ('MetaSel ('Just "escape") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr)) :*: S1 ('MetaSel ('Just "invert") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) |
data FunctionApplication Source #
FApp | |
|
Instances
fapp :: (Name, [Indirection]) -> FunctionArguments -> FunctionApplication Source #
setSortBy :: FunctionApplication -> [SortBy] -> FunctionApplication Source #
data FunctionArguments Source #
Instances
Instances
Eq ArgsList Source # | |
Data ArgsList Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ArgsList -> c ArgsList # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ArgsList # toConstr :: ArgsList -> Constr # dataTypeOf :: ArgsList -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ArgsList) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ArgsList) # gmapT :: (forall b. Data b => b -> b) -> ArgsList -> ArgsList # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ArgsList -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ArgsList -> r # gmapQ :: (forall d. Data d => d -> u) -> ArgsList -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> ArgsList -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> ArgsList -> m ArgsList # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgsList -> m ArgsList # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ArgsList -> m ArgsList # | |
Show ArgsList Source # | |
Generic ArgsList Source # | |
Lift ArgsList Source # | |
type Rep ArgsList Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep ArgsList = D1 ('MetaData "ArgsList" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "ArgsList" 'PrefixI 'True) (S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Argument)) :*: (S1 ('MetaSel ('Just "sortBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SortBy]) :*: S1 ('MetaSel ('Just "distinct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) |
Instances
Eq Argument Source # | |
Data Argument Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Argument -> c Argument # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Argument # toConstr :: Argument -> Constr # dataTypeOf :: Argument -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Argument) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Argument) # gmapT :: (forall b. Data b => b -> b) -> Argument -> Argument # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Argument -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Argument -> r # gmapQ :: (forall d. Data d => d -> u) -> Argument -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Argument -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Argument -> m Argument # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Argument -> m Argument # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Argument -> m Argument # | |
Show Argument Source # | |
Generic Argument Source # | |
FormatSql Argument Source # | |
Lift Argument Source # | |
type Rep Argument Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Argument = D1 ('MetaData "Argument" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "E" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr)) :+: C1 ('MetaCons "Named" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr))) |
Case | |
|
Instances
Eq Case Source # | |
Data Case Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Case -> c Case # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Case # dataTypeOf :: Case -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Case) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Case) # gmapT :: (forall b. Data b => b -> b) -> Case -> Case # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Case -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Case -> r # gmapQ :: (forall d. Data d => d -> u) -> Case -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Case -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Case -> m Case # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Case -> m Case # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Case -> m Case # | |
Show Case Source # | |
Generic Case Source # | |
FormatSql Case Source # | |
Lift Case Source # | |
type Rep Case Source # | |
Defined in Preql.QuasiQuoter.Syntax.Syntax type Rep Case = D1 ('MetaData "Case" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Case" 'PrefixI 'True) (S1 ('MetaSel ('Just "whenClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Expr, Expr)]) :*: (S1 ('MetaSel ('Just "implicitArg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr)) :*: S1 ('MetaSel ('Just "elseClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr))))) |