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

Preql.QuasiQuoter.Syntax.Printer

Description

Print the types in Syntax as valid SQL. The emphasis is on queries to send to the database, not on legibilty; no extra whitespace is introduced.

Documentation

class FormatSql a where Source #

Minimal complete definition

Nothing

Methods

fmt :: a -> Builder Source #

fmtPrec :: Int -> a -> Builder Source #

Instances

Instances details
FormatSql Builder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Name Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Case Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Argument Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql FunctionArguments Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql FunctionApplication Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql LikeE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql BinOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Expr Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql CTE Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Materialized Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql WithClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql LockWait Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql LockingStrength Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Locking Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql NullsOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql SortOrder Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql SortOrderOrUsing Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql SortBy Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql WindowSpec Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql WindowDef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql ResTarget Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql SetOp Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql DistinctClause Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql JoinType Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Alias Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql JoinedTable Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql TableRef Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql SelectOptions Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Select Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql SelectStmt Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Update Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Setting Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Delete Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Insert Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Statement Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

FormatSql Literal Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

commas :: (FormatSql a, Foldable f) => f a -> Builder Source #

spaces :: (FormatSql a, Foldable f) => f a -> Builder Source #

data Assoc Source #

Constructors

LeftAssoc 
RightAssoc 
NonAssoc 

Instances

Instances details
Bounded Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Enum Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Eq Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Methods

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

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

Data Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Methods

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

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

toConstr :: Assoc -> Constr #

dataTypeOf :: Assoc -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Methods

showsPrec :: Int -> Assoc -> ShowS #

show :: Assoc -> String #

showList :: [Assoc] -> ShowS #

Generic Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Associated Types

type Rep Assoc :: Type -> Type #

Methods

from :: Assoc -> Rep Assoc x #

to :: Rep Assoc x -> Assoc #

Lift Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

Methods

lift :: Assoc -> Q Exp #

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

type Rep Assoc Source # 
Instance details

Defined in Preql.QuasiQuoter.Syntax.Printer

type Rep Assoc = D1 ('MetaData "Assoc" "Preql.QuasiQuoter.Syntax.Printer" "preql-0.6-2SuksC0wmUqELanFUsURCy" 'False) (C1 ('MetaCons "LeftAssoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "RightAssoc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NonAssoc" 'PrefixI 'False) (U1 :: Type -> Type)))