groundhog-0.8: Type-safe datatype-database mapping library.

Safe HaskellNone
LanguageHaskell98

Database.Groundhog.Generic.Sql

Contents

Description

This module defines the functions which are used only for backends creation.

Synopsis

SQL rendering utilities

renderCond :: SqlDb db => RenderConfig -> Cond db r -> Maybe (RenderS db r) Source #

Renders conditions for SQL backend. Returns Nothing if the fields don't have any columns.

renderOrders :: SqlDb db => RenderConfig -> [Order db r] -> RenderS db r Source #

renderFields :: StringLike s => (s -> s) -> [(String, DbType)] -> s Source #

mkExprWithConf :: (SqlDb db, PersistField a) => (RenderConfig -> Int -> Expr db r a) -> Expr db r a Source #

Helps creating an expression which depends on render configuration. It can be used in pair with prerenderExpr. myExpr x = mkExprWithConf $ conf _ -> let x' = prerenderExpr conf x in x' + x' * x' @

prerenderExpr :: SqlDb db => RenderConfig -> Expr db r a -> Expr db r a Source #

If we reuse complex expression several times, prerendering it saves time. RenderConfig can be obtained with mkExprWithConf

intercalateS :: StringLike s => s -> [s] -> s Source #

commasJoin :: StringLike s => [s] -> s Source #

flatten :: StringLike s => (s -> s) -> (String, DbType) -> [s] -> [s] Source #

data RenderS db r Source #

Constructors

RenderS 

Instances

IsString (RenderS db r) Source # 

Methods

fromString :: String -> RenderS db r #

Monoid (RenderS db r) Source # 

Methods

mempty :: RenderS db r #

mappend :: RenderS db r -> RenderS db r -> RenderS db r #

mconcat :: [RenderS db r] -> RenderS db r #

StringLike (RenderS db r) Source # 

Methods

fromChar :: Char -> RenderS db r Source #

newtype Utf8 Source #

Datatype for incremental building SQL queries

Constructors

Utf8 Builder 

newtype RenderConfig Source #

Constructors

RenderConfig 

Fields

class (Monoid a, IsString a) => StringLike a where Source #

Minimal complete definition

fromChar

Methods

fromChar :: Char -> a Source #

(<>) :: Monoid m => m -> m -> m infixr 6 #

An infix synonym for mappend.

Since: 4.5.0.0

function :: SqlDb db => String -> [UntypedExpr db r] -> Snippet db r Source #

operator :: (SqlDb db, Expression db r a, Expression db r b) => Int -> String -> a -> b -> Snippet db r Source #

parens :: Int -> Int -> RenderS db r -> RenderS db r Source #

mkExpr :: SqlDb db => Snippet db r -> Expr db r a Source #

newtype Snippet db r Source #

Escape function, priority of the outer operator. The result is a list for the embedded data which may expand to several RenderS.

Constructors

Snippet (RenderConfig -> Int -> [RenderS db r]) 

class (DbDescriptor db, QueryRaw db ~ Snippet db) => SqlDb db where Source #

This class distinguishes databases which support SQL-specific expressions. It contains ad hoc members for features whose syntax differs across the databases.

Minimal complete definition

append, signum', quotRem', equalsOperator, notEqualsOperator

Methods

append :: (ExpressionOf db r a String, ExpressionOf db r b String) => a -> b -> Expr db r String Source #

signum' :: (ExpressionOf db r x a, Num a) => x -> Expr db r a Source #

quotRem' :: (ExpressionOf db r x a, ExpressionOf db r y a, Integral a) => x -> y -> (Expr db r a, Expr db r a) Source #

equalsOperator :: RenderS db r -> RenderS db r -> RenderS db r Source #

notEqualsOperator :: RenderS db r -> RenderS db r -> RenderS db r Source #

class SqlDb db => FloatingSqlDb db where Source #

This class distinguishes databases which support trigonometry and other math functions. For example, PostgreSQL has them but Sqlite does not. It contains ad hoc members for features whose syntax differs across the databases.

Minimal complete definition

log', logBase'

Methods

log' :: (ExpressionOf db r x a, Floating a) => x -> Expr db r a Source #

Natural logarithm

logBase' :: (ExpressionOf db r b a, ExpressionOf db r x a, Floating a) => b -> x -> Expr db r a Source #

tableName :: StringLike s => (s -> s) -> EntityDef -> ConstructorDef -> s Source #

Returns escaped table name optionally qualified with schema

mainTableName :: StringLike s => (s -> s) -> EntityDef -> s Source #

Returns escaped main table name optionally qualified with schema

Orphan instances