preql-0.5: safe PostgreSQL queries using Quasiquoters
Safe HaskellNone
LanguageHaskell2010

Preql.QuasiQuoter.Syntax.Syntax

Description

 
Synopsis

Documentation

data Literal Source #

Constructors

I !Word 
F !Double 
T !Text 
B !Bool 
Null 

Instances

Instances details
Eq Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Literal -> Literal -> Bool #

(/=) :: Literal -> Literal -> Bool #

Data Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Literal -> c Literal #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Literal #

toConstr :: Literal -> Constr #

dataTypeOf :: Literal -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Literal) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Literal) #

gmapT :: (forall b. Data b => b -> b) -> Literal -> Literal #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Literal -> r #

gmapQ :: (forall d. Data d => d -> u) -> Literal -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Literal -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Literal -> m Literal #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Literal -> m Literal #

Show Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Literal :: Type -> Type #

Methods

from :: Literal -> Rep Literal x #

to :: Rep Literal x -> Literal #

FormatSql Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Literal -> Q Exp #

liftTyped :: Literal -> Q (TExp Literal) #

type Rep Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data Statement Source #

Constructors

QI !Insert 
QD !Delete 
QU !Update 
QS !SelectStmt 

Instances

Instances details
Eq Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Statement -> c Statement #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Statement #

toConstr :: Statement -> Constr #

dataTypeOf :: Statement -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Statement) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Statement) #

gmapT :: (forall b. Data b => b -> b) -> Statement -> Statement #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Statement -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Statement -> r #

gmapQ :: (forall d. Data d => d -> u) -> Statement -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Statement -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Statement -> m Statement #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement -> m Statement #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Statement -> m Statement #

Show Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Statement :: Type -> Type #

FormatSql Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data Insert Source #

Queries of the form INSERT INTO table (columns) VALUES (values); Limitations: * single row * no ON CONFLICT

Constructors

Insert 

Instances

Instances details
Eq Insert Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Insert -> Insert -> Bool #

(/=) :: Insert -> Insert -> Bool #

Data Insert Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Insert Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Insert :: Type -> Type #

Methods

from :: Insert -> Rep Insert x #

to :: Rep Insert x -> Insert #

FormatSql Insert Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Insert Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Insert -> Q Exp #

liftTyped :: Insert -> Q (TExp Insert) #

type Rep Insert Source # 
Instance details

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

data Delete Source #

Queries of the form DELETE FROM table WHERE conditions.

Constructors

Delete 

Fields

Instances

Instances details
Eq Delete Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Delete -> Delete -> Bool #

(/=) :: Delete -> Delete -> Bool #

Data Delete Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Delete Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Delete :: Type -> Type #

Methods

from :: Delete -> Rep Delete x #

to :: Rep Delete x -> Delete #

FormatSql Delete Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Delete Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Delete -> Q Exp #

liftTyped :: Delete -> Q (TExp Delete) #

type Rep Delete Source # 
Instance details

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

data Setting Source #

Constructors

Setting !Name !Expr 

Instances

Instances details
Eq Setting Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Setting -> Setting -> Bool #

(/=) :: Setting -> Setting -> Bool #

Data Setting Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Setting Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Setting :: Type -> Type #

Methods

from :: Setting -> Rep Setting x #

to :: Rep Setting x -> Setting #

FormatSql Setting Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Setting Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Setting -> Q Exp #

liftTyped :: Setting -> Q (TExp Setting) #

type Rep Setting Source # 
Instance details

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

data Update Source #

Queries of the form UPDATE table SET settings WHERE conditions. Where each Setting name literal is like SQL name = literal.

Constructors

Update 

Instances

Instances details
Eq Update Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Update -> Update -> Bool #

(/=) :: Update -> Update -> Bool #

Data Update Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Update Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Update :: Type -> Type #

Methods

from :: Update -> Rep Update x #

to :: Rep Update x -> Update #

FormatSql Update Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Update Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Update -> Q Exp #

liftTyped :: Update -> Q (TExp Update) #

type Rep Update Source # 
Instance details

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 #

Instances

Instances details
Eq SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectStmt -> c SelectStmt #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectStmt #

toConstr :: SelectStmt -> Constr #

dataTypeOf :: SelectStmt -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectStmt) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectStmt) #

gmapT :: (forall b. Data b => b -> b) -> SelectStmt -> SelectStmt #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectStmt -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectStmt -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectStmt -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectStmt -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectStmt -> m SelectStmt #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectStmt -> m SelectStmt #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectStmt -> m SelectStmt #

Show SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep SelectStmt :: Type -> Type #

FormatSql SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data Select Source #

Instances

Instances details
Eq Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Select -> Select -> Bool #

(/=) :: Select -> Select -> Bool #

Data Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Select -> c Select #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Select #

toConstr :: Select -> Constr #

dataTypeOf :: Select -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Select) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Select) #

gmapT :: (forall b. Data b => b -> b) -> Select -> Select #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Select -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Select -> r #

gmapQ :: (forall d. Data d => d -> u) -> Select -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Select -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Select -> m Select #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Select -> m Select #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Select -> m Select #

Show Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Select :: Type -> Type #

Methods

from :: Select -> Rep Select x #

to :: Rep Select x -> Select #

FormatSql Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Select -> Q Exp #

liftTyped :: Select -> Q (TExp Select) #

type Rep Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data SelectOptions Source #

Instances

Instances details
Eq SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SelectOptions -> c SelectOptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SelectOptions #

toConstr :: SelectOptions -> Constr #

dataTypeOf :: SelectOptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SelectOptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SelectOptions) #

gmapT :: (forall b. Data b => b -> b) -> SelectOptions -> SelectOptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SelectOptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SelectOptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> SelectOptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SelectOptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SelectOptions -> m SelectOptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectOptions -> m SelectOptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SelectOptions -> m SelectOptions #

Show SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep SelectOptions :: Type -> Type #

FormatSql SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep SelectOptions = D1 ('MetaData "SelectOptions" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "SelectOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sortBy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SortBy]) :*: S1 ('MetaSel ('Just "offset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr))) :*: (S1 ('MetaSel ('Just "limit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Expr)) :*: (S1 ('MetaSel ('Just "locking") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Locking]) :*: S1 ('MetaSel ('Just "withClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe WithClause))))))

data TableRef Source #

Instances

Instances details
Eq TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableRef -> c TableRef #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableRef #

toConstr :: TableRef -> Constr #

dataTypeOf :: TableRef -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TableRef) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableRef) #

gmapT :: (forall b. Data b => b -> b) -> TableRef -> TableRef #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableRef -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableRef -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableRef -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableRef -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableRef -> m TableRef #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableRef -> m TableRef #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableRef -> m TableRef #

Show TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep TableRef :: Type -> Type #

Methods

from :: TableRef -> Rep TableRef x #

to :: Rep TableRef x -> TableRef #

FormatSql TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data JoinedTable Source #

Instances

Instances details
Eq JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JoinedTable -> c JoinedTable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JoinedTable #

toConstr :: JoinedTable -> Constr #

dataTypeOf :: JoinedTable -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JoinedTable) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JoinedTable) #

gmapT :: (forall b. Data b => b -> b) -> JoinedTable -> JoinedTable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JoinedTable -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JoinedTable -> r #

gmapQ :: (forall d. Data d => d -> u) -> JoinedTable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JoinedTable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JoinedTable -> m JoinedTable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinedTable -> m JoinedTable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JoinedTable -> m JoinedTable #

Show JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep JoinedTable :: Type -> Type #

FormatSql JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data Alias Source #

Constructors

Alias 

Fields

Instances

Instances details
Eq Alias Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Alias -> Alias -> Bool #

(/=) :: Alias -> Alias -> Bool #

Data Alias Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: Alias -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> Alias -> ShowS #

show :: Alias -> String #

showList :: [Alias] -> ShowS #

Generic Alias Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Alias :: Type -> Type #

Methods

from :: Alias -> Rep Alias x #

to :: Rep Alias x -> Alias #

FormatSql Alias Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Alias Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Alias -> Q Exp #

liftTyped :: Alias -> Q (TExp Alias) #

type Rep Alias Source # 
Instance details

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

data JoinType Source #

Constructors

Inner 
LeftJoin 
RightJoin 
Full 

Instances

Instances details
Bounded JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep JoinType :: Type -> Type #

Methods

from :: JoinType -> Rep JoinType x #

to :: Rep JoinType x -> JoinType #

FormatSql JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep JoinType Source # 
Instance details

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

data JoinQual Source #

Constructors

Using [Name] 
On Expr 
Natural 

Instances

Instances details
Eq JoinQual Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data JoinQual Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic JoinQual Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep JoinQual :: Type -> Type #

Methods

from :: JoinQual -> Rep JoinQual x #

to :: Rep JoinQual x -> JoinQual #

Lift JoinQual Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep JoinQual Source # 
Instance details

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 details
Eq DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DistinctClause -> c DistinctClause #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DistinctClause #

toConstr :: DistinctClause -> Constr #

dataTypeOf :: DistinctClause -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DistinctClause) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DistinctClause) #

gmapT :: (forall b. Data b => b -> b) -> DistinctClause -> DistinctClause #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DistinctClause -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DistinctClause -> r #

gmapQ :: (forall d. Data d => d -> u) -> DistinctClause -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DistinctClause -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DistinctClause -> m DistinctClause #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DistinctClause -> m DistinctClause #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DistinctClause -> m DistinctClause #

Show DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep DistinctClause :: Type -> Type #

FormatSql DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep DistinctClause = D1 ('MetaData "DistinctClause" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "DistinctAll" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DistinctOn" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Expr))))

data SetOp Source #

Constructors

Union 
Intersect 
Except 

Instances

Instances details
Bounded SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: SetOp -> SetOp -> Bool #

(/=) :: SetOp -> SetOp -> Bool #

Data SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: SetOp -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> SetOp -> ShowS #

show :: SetOp -> String #

showList :: [SetOp] -> ShowS #

Generic SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep SetOp :: Type -> Type #

Methods

from :: SetOp -> Rep SetOp x #

to :: Rep SetOp x -> SetOp #

FormatSql SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: SetOp -> Q Exp #

liftTyped :: SetOp -> Q (TExp SetOp) #

type Rep SetOp Source # 
Instance details

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 #

Constructors

All 
Distinct 

Instances

Instances details
Bounded AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AllOrDistinct -> c AllOrDistinct #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AllOrDistinct #

toConstr :: AllOrDistinct -> Constr #

dataTypeOf :: AllOrDistinct -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AllOrDistinct) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AllOrDistinct) #

gmapT :: (forall b. Data b => b -> b) -> AllOrDistinct -> AllOrDistinct #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AllOrDistinct -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AllOrDistinct -> r #

gmapQ :: (forall d. Data d => d -> u) -> AllOrDistinct -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AllOrDistinct -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AllOrDistinct -> m AllOrDistinct #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AllOrDistinct -> m AllOrDistinct #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AllOrDistinct -> m AllOrDistinct #

Show AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep AllOrDistinct :: Type -> Type #

Lift AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep AllOrDistinct Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep AllOrDistinct = D1 ('MetaData "AllOrDistinct" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "All" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Distinct" 'PrefixI 'False) (U1 :: Type -> Type))

data ResTarget Source #

Constructors

Star 
Column Expr (Maybe Name) 

Instances

Instances details
Eq ResTarget Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data ResTarget Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic ResTarget Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep ResTarget :: Type -> Type #

FormatSql ResTarget Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift ResTarget Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep ResTarget Source # 
Instance details

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

data WindowDef Source #

Constructors

WindowDef Name WindowSpec 

Instances

Instances details
Eq WindowDef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data WindowDef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic WindowDef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep WindowDef :: Type -> Type #

FormatSql WindowDef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift WindowDef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep WindowDef Source # 
Instance details

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

data Over Source #

Instances

Instances details
Eq Over Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Over -> Over -> Bool #

(/=) :: Over -> Over -> Bool #

Data Over Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: Over -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> Over -> ShowS #

show :: Over -> String #

showList :: [Over] -> ShowS #

Generic Over Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Over :: Type -> Type #

Methods

from :: Over -> Rep Over x #

to :: Rep Over x -> Over #

Lift Over Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Over -> Q Exp #

liftTyped :: Over -> Q (TExp Over) #

type Rep Over Source # 
Instance details

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 #

Constructors

WindowSpec 

Instances

Instances details
Eq WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowSpec -> c WindowSpec #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WindowSpec #

toConstr :: WindowSpec -> Constr #

dataTypeOf :: WindowSpec -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WindowSpec) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowSpec) #

gmapT :: (forall b. Data b => b -> b) -> WindowSpec -> WindowSpec #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowSpec -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowSpec -> r #

gmapQ :: (forall d. Data d => d -> u) -> WindowSpec -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowSpec -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowSpec -> m WindowSpec #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowSpec -> m WindowSpec #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowSpec -> m WindowSpec #

Show WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep WindowSpec :: Type -> Type #

FormatSql WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep WindowSpec = D1 ('MetaData "WindowSpec" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "WindowSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "refName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Name)) :*: (S1 ('MetaSel ('Just "partitionClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Expr]) :*: S1 ('MetaSel ('Just "orderClause") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [SortBy]))))

data SortBy Source #

Constructors

SortBy 

Instances

Instances details
Eq SortBy Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: SortBy -> SortBy -> Bool #

(/=) :: SortBy -> SortBy -> Bool #

Data SortBy Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic SortBy Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep SortBy :: Type -> Type #

Methods

from :: SortBy -> Rep SortBy x #

to :: Rep SortBy x -> SortBy #

FormatSql SortBy Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift SortBy Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: SortBy -> Q Exp #

liftTyped :: SortBy -> Q (TExp SortBy) #

type Rep SortBy Source # 
Instance details

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 details
Eq SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SortOrderOrUsing -> c SortOrderOrUsing #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SortOrderOrUsing #

toConstr :: SortOrderOrUsing -> Constr #

dataTypeOf :: SortOrderOrUsing -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SortOrderOrUsing) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SortOrderOrUsing) #

gmapT :: (forall b. Data b => b -> b) -> SortOrderOrUsing -> SortOrderOrUsing #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SortOrderOrUsing -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SortOrderOrUsing -> r #

gmapQ :: (forall d. Data d => d -> u) -> SortOrderOrUsing -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SortOrderOrUsing -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SortOrderOrUsing -> m SortOrderOrUsing #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SortOrderOrUsing -> m SortOrderOrUsing #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SortOrderOrUsing -> m SortOrderOrUsing #

Show SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep SortOrderOrUsing :: Type -> Type #

FormatSql SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep SortOrderOrUsing = D1 ('MetaData "SortOrderOrUsing" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "SortOrder" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SortOrder)) :+: C1 ('MetaCons "SortUsing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BinOp)))

data SortOrder Source #

Instances

Instances details
Bounded SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep SortOrder :: Type -> Type #

FormatSql SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep SortOrder Source # 
Instance details

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 details
Bounded NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NullsOrder -> c NullsOrder #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c NullsOrder #

toConstr :: NullsOrder -> Constr #

dataTypeOf :: NullsOrder -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c NullsOrder) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c NullsOrder) #

gmapT :: (forall b. Data b => b -> b) -> NullsOrder -> NullsOrder #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NullsOrder -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NullsOrder -> r #

gmapQ :: (forall d. Data d => d -> u) -> NullsOrder -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NullsOrder -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NullsOrder -> m NullsOrder #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NullsOrder -> m NullsOrder #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NullsOrder -> m NullsOrder #

Show NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep NullsOrder :: Type -> Type #

FormatSql NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep NullsOrder = D1 ('MetaData "NullsOrder" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "NullsFirst" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NullsLast" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NullsOrderDefault" 'PrefixI 'False) (U1 :: Type -> Type)))

data Locking Source #

Constructors

Locking 

Instances

Instances details
Eq Locking Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Locking -> Locking -> Bool #

(/=) :: Locking -> Locking -> Bool #

Data Locking Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Locking Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Locking :: Type -> Type #

Methods

from :: Locking -> Rep Locking x #

to :: Rep Locking x -> Locking #

FormatSql Locking Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Locking Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Locking -> Q Exp #

liftTyped :: Locking -> Q (TExp Locking) #

type Rep Locking Source # 
Instance details

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 details
Bounded LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LockingStrength -> c LockingStrength #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LockingStrength #

toConstr :: LockingStrength -> Constr #

dataTypeOf :: LockingStrength -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LockingStrength) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LockingStrength) #

gmapT :: (forall b. Data b => b -> b) -> LockingStrength -> LockingStrength #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LockingStrength -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LockingStrength -> r #

gmapQ :: (forall d. Data d => d -> u) -> LockingStrength -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LockingStrength -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LockingStrength -> m LockingStrength #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LockingStrength -> m LockingStrength #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LockingStrength -> m LockingStrength #

Show LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep LockingStrength :: Type -> Type #

FormatSql LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep LockingStrength = D1 ('MetaData "LockingStrength" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) ((C1 ('MetaCons "ForUpdate" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForNoKeyUpdate" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ForShare" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ForKeyShare" 'PrefixI 'False) (U1 :: Type -> Type)))

data LockWait Source #

Instances

Instances details
Bounded LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep LockWait :: Type -> Type #

Methods

from :: LockWait -> Rep LockWait x #

to :: Rep LockWait x -> LockWait #

FormatSql LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep LockWait Source # 
Instance details

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 #

Constructors

With 

Instances

Instances details
Eq WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WithClause -> c WithClause #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WithClause #

toConstr :: WithClause -> Constr #

dataTypeOf :: WithClause -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WithClause) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WithClause) #

gmapT :: (forall b. Data b => b -> b) -> WithClause -> WithClause #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WithClause -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WithClause -> r #

gmapQ :: (forall d. Data d => d -> u) -> WithClause -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WithClause -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WithClause -> m WithClause #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WithClause -> m WithClause #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WithClause -> m WithClause #

Show WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep WithClause :: Type -> Type #

FormatSql WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep WithClause = D1 ('MetaData "WithClause" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "With" 'PrefixI 'True) (S1 ('MetaSel ('Just "commonTables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CTE]) :*: S1 ('MetaSel ('Just "recursive") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Recursive)))

data Recursive Source #

Constructors

Recursive 
NotRecursive 

Instances

Instances details
Bounded Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Recursive -> c Recursive #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Recursive #

toConstr :: Recursive -> Constr #

dataTypeOf :: Recursive -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Recursive) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Recursive) #

gmapT :: (forall b. Data b => b -> b) -> Recursive -> Recursive #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Recursive -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Recursive -> r #

gmapQ :: (forall d. Data d => d -> u) -> Recursive -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Recursive -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Recursive -> m Recursive #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Recursive -> m Recursive #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Recursive -> m Recursive #

Show Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Recursive :: Type -> Type #

Lift Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Recursive Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Recursive = D1 ('MetaData "Recursive" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Recursive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NotRecursive" 'PrefixI 'False) (U1 :: Type -> Type))

data Materialized Source #

Instances

Instances details
Bounded Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Materialized -> c Materialized #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Materialized #

toConstr :: Materialized -> Constr #

dataTypeOf :: Materialized -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Materialized) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Materialized) #

gmapT :: (forall b. Data b => b -> b) -> Materialized -> Materialized #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Materialized -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Materialized -> r #

gmapQ :: (forall d. Data d => d -> u) -> Materialized -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Materialized -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Materialized -> m Materialized #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Materialized -> m Materialized #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Materialized -> m Materialized #

Show Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Materialized :: Type -> Type #

FormatSql Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Materialized = D1 ('MetaData "Materialized" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "Materialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NotMaterialized" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MaterializeDefault" 'PrefixI 'False) (U1 :: Type -> Type)))

data CTE Source #

Instances

Instances details
Eq CTE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: CTE -> CTE -> Bool #

(/=) :: CTE -> CTE -> Bool #

Data CTE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: CTE -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> CTE -> ShowS #

show :: CTE -> String #

showList :: [CTE] -> ShowS #

Generic CTE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep CTE :: Type -> Type #

Methods

from :: CTE -> Rep CTE x #

to :: Rep CTE x -> CTE #

FormatSql CTE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift CTE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: CTE -> Q Exp #

liftTyped :: CTE -> Q (TExp CTE) #

type Rep CTE Source # 
Instance details

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

data Expr Source #

Instances

Instances details
Eq Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Data Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Expr -> c Expr #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Expr #

toConstr :: Expr -> Constr #

dataTypeOf :: Expr -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Expr) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Expr) #

gmapT :: (forall b. Data b => b -> b) -> Expr -> Expr #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Expr -> r #

gmapQ :: (forall d. Data d => d -> u) -> Expr -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Expr -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Expr -> m Expr #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Expr -> m Expr #

Show Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Generic Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Expr :: Type -> Type #

Methods

from :: Expr -> Rep Expr x #

to :: Rep Expr x -> Expr #

FormatSql Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Expr -> Q Exp #

liftTyped :: Expr -> Q (TExp Expr) #

type Rep Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Expr = D1 ('MetaData "Expr" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (((C1 ('MetaCons "Lit" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Literal)) :+: C1 ('MetaCons "CRef" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))) :+: (C1 ('MetaCons "NumberedParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word)) :+: (C1 ('MetaCons "HaskellParam" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "BinOp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BinOp) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)))))) :+: ((C1 ('MetaCons "Unary" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnaryOp) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Expr)) :+: (C1 ('MetaCons "Indirection" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Expr) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty Indirection))) :+: C1 ('MetaCons "SelectExpr" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SelectStmt)))) :+: (C1 ('MetaCons "L" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LikeE)) :+: (C1 ('MetaCons "Fun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FunctionApplication)) :+: C1 ('MetaCons "Cas" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Case))))))

data BinOp Source #

Instances

Instances details
Bounded BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: BinOp -> BinOp -> Bool #

(/=) :: BinOp -> BinOp -> Bool #

Data BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: BinOp -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Generic BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep BinOp :: Type -> Type #

Methods

from :: BinOp -> Rep BinOp x #

to :: Rep BinOp x -> BinOp #

FormatSql BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: BinOp -> Q Exp #

liftTyped :: BinOp -> Q (TExp BinOp) #

type Rep BinOp Source # 
Instance details

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

data UnaryOp Source #

Constructors

Negate 
Not 
IsNull 
NotNull 

Instances

Instances details
Bounded UnaryOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum UnaryOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq UnaryOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: UnaryOp -> UnaryOp -> Bool #

(/=) :: UnaryOp -> UnaryOp -> Bool #

Data UnaryOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic UnaryOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep UnaryOp :: Type -> Type #

Methods

from :: UnaryOp -> Rep UnaryOp x #

to :: Rep UnaryOp x -> UnaryOp #

Lift UnaryOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: UnaryOp -> Q Exp #

liftTyped :: UnaryOp -> Q (TExp UnaryOp) #

type Rep UnaryOp Source # 
Instance details

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

data LikeOp Source #

Constructors

Like 
ILike 
Similar 

Instances

Instances details
Bounded LikeOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Enum LikeOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Eq LikeOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: LikeOp -> LikeOp -> Bool #

(/=) :: LikeOp -> LikeOp -> Bool #

Data LikeOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic LikeOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep LikeOp :: Type -> Type #

Methods

from :: LikeOp -> Rep LikeOp x #

to :: Rep LikeOp x -> LikeOp #

Lift LikeOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: LikeOp -> Q Exp #

liftTyped :: LikeOp -> Q (TExp LikeOp) #

type Rep LikeOp Source # 
Instance details

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

data LikeE Source #

Constructors

LikeE 

Instances

Instances details
Eq LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: LikeE -> LikeE -> Bool #

(/=) :: LikeE -> LikeE -> Bool #

Data LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: LikeE -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> LikeE -> ShowS #

show :: LikeE -> String #

showList :: [LikeE] -> ShowS #

Generic LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep LikeE :: Type -> Type #

Methods

from :: LikeE -> Rep LikeE x #

to :: Rep LikeE x -> LikeE #

FormatSql LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: LikeE -> Q Exp #

liftTyped :: LikeE -> Q (TExp LikeE) #

type Rep LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data FunctionApplication Source #

Instances

Instances details
Eq FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionApplication -> c FunctionApplication #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionApplication #

toConstr :: FunctionApplication -> Constr #

dataTypeOf :: FunctionApplication -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionApplication) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionApplication) #

gmapT :: (forall b. Data b => b -> b) -> FunctionApplication -> FunctionApplication #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionApplication -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionApplication -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionApplication -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionApplication -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionApplication -> m FunctionApplication #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionApplication -> m FunctionApplication #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionApplication -> m FunctionApplication #

Show FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep FunctionApplication :: Type -> Type #

FormatSql FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data FunctionArguments Source #

Constructors

StarArg 
NoArgs 
Args ArgsList 

Instances

Instances details
Eq FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FunctionArguments -> c FunctionArguments #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FunctionArguments #

toConstr :: FunctionArguments -> Constr #

dataTypeOf :: FunctionArguments -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c FunctionArguments) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FunctionArguments) #

gmapT :: (forall b. Data b => b -> b) -> FunctionArguments -> FunctionArguments #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FunctionArguments -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FunctionArguments -> r #

gmapQ :: (forall d. Data d => d -> u) -> FunctionArguments -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FunctionArguments -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FunctionArguments -> m FunctionArguments #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionArguments -> m FunctionArguments #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FunctionArguments -> m FunctionArguments #

Show FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep FunctionArguments :: Type -> Type #

FormatSql FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep FunctionArguments = D1 ('MetaData "FunctionArguments" "Preql.QuasiQuoter.Syntax.Syntax" "preql-0.5-FdfxHOOmFuA1g6eoMjPSbJ" 'False) (C1 ('MetaCons "StarArg" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "NoArgs" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Args" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ArgsList))))

data ArgsList Source #

Constructors

ArgsList 

Instances

Instances details
Eq ArgsList Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data ArgsList Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic ArgsList Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep ArgsList :: Type -> Type #

Methods

from :: ArgsList -> Rep ArgsList x #

to :: Rep ArgsList x -> ArgsList #

Lift ArgsList Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep ArgsList Source # 
Instance details

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

data Argument Source #

Constructors

E Expr 
Named Name Expr 

Instances

Instances details
Eq Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Data Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Generic Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Argument :: Type -> Type #

Methods

from :: Argument -> Rep Argument x #

to :: Rep Argument x -> Argument #

FormatSql Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

type Rep Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

data Case Source #

Constructors

Case 

Instances

Instances details
Eq Case Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

(==) :: Case -> Case -> Bool #

(/=) :: Case -> Case -> Bool #

Data Case Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

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 #

toConstr :: Case -> Constr #

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 # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

showsPrec :: Int -> Case -> ShowS #

show :: Case -> String #

showList :: [Case] -> ShowS #

Generic Case Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Associated Types

type Rep Case :: Type -> Type #

Methods

from :: Case -> Rep Case x #

to :: Rep Case x -> Case #

FormatSql Case Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Lift Case Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Syntax

Methods

lift :: Case -> Q Exp #

liftTyped :: Case -> Q (TExp Case) #

type Rep Case Source # 
Instance details

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