{-# LANGUAGE
AllowAmbiguousTypes
, ConstraintKinds
, DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MagicHash
, OverloadedStrings
, ScopedTypeVariables
, StandaloneDeriving
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, UndecidableInstances
, RankNTypes
#-}
module Squeal.PostgreSQL.Expression
(
Expression (..)
, Expr
, type (-->)
, Fun
, unsafeFunction
, function
, unsafeLeftOp
, unsafeRightOp
, Operator
, OperatorDB
, unsafeBinaryOp
, PGSubset (..)
, PGIntersect (..)
, FunctionVar
, unsafeFunctionVar
, type (--->)
, FunN
, unsafeFunctionN
, functionN
, (&)
) where
import Control.Category
import Control.DeepSeq
import Data.Binary.Builder (toLazyByteString)
import Data.ByteString (ByteString)
import Data.ByteString.Builder (doubleDec, floatDec, int16Dec, int32Dec, int64Dec)
import Data.ByteString.Builder.Scientific (scientificBuilder)
import Data.ByteString.Lazy (toStrict)
import Data.Function ((&))
import Data.Semigroup hiding (All)
import Data.String
import Generics.SOP hiding (All, from)
import GHC.OverloadedLabels
import GHC.TypeLits
import Numeric
import Prelude hiding (id, (.))
import qualified GHC.Generics as GHC
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
newtype Expression
(grp :: Grouping)
(lat :: FromType)
(with :: FromType)
(db :: SchemasType)
(params :: [NullType])
(from :: FromType)
(ty :: NullType)
= UnsafeExpression { Expression grp lat with db params from ty -> ByteString
renderExpression :: ByteString }
deriving stock ((forall x.
Expression grp lat with db params from ty
-> Rep (Expression grp lat with db params from ty) x)
-> (forall x.
Rep (Expression grp lat with db params from ty) x
-> Expression grp lat with db params from ty)
-> Generic (Expression grp lat with db params from ty)
forall x.
Rep (Expression grp lat with db params from ty) x
-> Expression grp lat with db params from ty
forall x.
Expression grp lat with db params from ty
-> Rep (Expression grp lat with db params from ty) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType) x.
Rep (Expression grp lat with db params from ty) x
-> Expression grp lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType) x.
Expression grp lat with db params from ty
-> Rep (Expression grp lat with db params from ty) x
$cto :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType) x.
Rep (Expression grp lat with db params from ty) x
-> Expression grp lat with db params from ty
$cfrom :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType) x.
Expression grp lat with db params from ty
-> Rep (Expression grp lat with db params from ty) x
GHC.Generic,Int -> Expression grp lat with db params from ty -> ShowS
[Expression grp lat with db params from ty] -> ShowS
Expression grp lat with db params from ty -> String
(Int -> Expression grp lat with db params from ty -> ShowS)
-> (Expression grp lat with db params from ty -> String)
-> ([Expression grp lat with db params from ty] -> ShowS)
-> Show (Expression grp lat with db params from ty)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Int -> Expression grp lat with db params from ty -> ShowS
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
[Expression grp lat with db params from ty] -> ShowS
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty -> String
showList :: [Expression grp lat with db params from ty] -> ShowS
$cshowList :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
[Expression grp lat with db params from ty] -> ShowS
show :: Expression grp lat with db params from ty -> String
$cshow :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty -> String
showsPrec :: Int -> Expression grp lat with db params from ty -> ShowS
$cshowsPrec :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Int -> Expression grp lat with db params from ty -> ShowS
Show,Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
(Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool)
-> Eq (Expression grp lat with db params from ty)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
/= :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
$c/= :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
== :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
$c== :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
Eq,Eq (Expression grp lat with db params from ty)
Eq (Expression grp lat with db params from ty)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Ordering)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty)
-> (Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty)
-> Ord (Expression grp lat with db params from ty)
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Ordering
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Eq (Expression grp lat with db params from ty)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Ordering
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
min :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
$cmin :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
max :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
$cmax :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
>= :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
$c>= :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
> :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
$c> :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
<= :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
$c<= :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
< :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
$c< :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Bool
compare :: Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Ordering
$ccompare :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty
-> Expression grp lat with db params from ty -> Ordering
$cp1Ord :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Eq (Expression grp lat with db params from ty)
Ord)
deriving newtype (Expression grp lat with db params from ty -> ()
(Expression grp lat with db params from ty -> ())
-> NFData (Expression grp lat with db params from ty)
forall a. (a -> ()) -> NFData a
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty -> ()
rnf :: Expression grp lat with db params from ty -> ()
$crnf :: forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty -> ()
NFData)
instance RenderSQL (Expression grp lat with db params from ty) where
renderSQL :: Expression grp lat with db params from ty -> ByteString
renderSQL = Expression grp lat with db params from ty -> ByteString
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
Expression grp lat with db params from ty -> ByteString
renderExpression
type Expr x
= forall grp lat with db params from
. Expression grp lat with db params from x
type Operator x1 x2 y = forall db. OperatorDB db x1 x2 y
type OperatorDB db x1 x2 y
= forall grp lat with params from
. Expression grp lat with db params from x1
-> Expression grp lat with db params from x2
-> Expression grp lat with db params from y
type (-->) x y = forall db. Fun db x y
type Fun db x y
= forall grp lat with params from
. Expression grp lat with db params from x
-> Expression grp lat with db params from y
type (--->) xs y = forall db. FunN db xs y
type FunN db xs y
= forall grp lat with params from
. NP (Expression grp lat with db params from) xs
-> Expression grp lat with db params from y
type FunctionVar x0 x1 y
= forall grp lat with db params from
. [Expression grp lat with db params from x0]
-> Expression grp lat with db params from x1
-> Expression grp lat with db params from y
unsafeFunctionVar :: ByteString -> FunctionVar x0 x1 y
unsafeFunctionVar :: ByteString -> FunctionVar x0 x1 y
unsafeFunctionVar ByteString
fun [Expression grp lat with db params from x0]
xs Expression grp lat with db params from x1
x = ByteString -> Expression grp lat with db params from y
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from y)
-> ByteString -> Expression grp lat with db params from y
forall a b. (a -> b) -> a -> b
$ ByteString
fun ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized
([ByteString] -> ByteString
commaSeparated (Expression grp lat with db params from x0 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (Expression grp lat with db params from x0 -> ByteString)
-> [Expression grp lat with db params from x0] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Expression grp lat with db params from x0]
xs) ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
", " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from x1 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from x1
x)
instance (HasUnique tab (Join from lat) row, Has col row ty)
=> IsLabel col (Expression 'Ungrouped lat with db params from ty) where
fromLabel :: Expression 'Ungrouped lat with db params from ty
fromLabel = ByteString -> Expression 'Ungrouped lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression 'Ungrouped lat with db params from ty)
-> ByteString -> Expression 'Ungrouped lat with db params from ty
forall a b. (a -> b) -> a -> b
$ Alias col -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (Alias col
forall (alias :: Symbol). Alias alias
Alias @col)
instance (HasUnique tab (Join from lat) row, Has col row ty, tys ~ '[ty])
=> IsLabel col (NP (Expression 'Ungrouped lat with db params from) tys) where
fromLabel :: NP (Expression 'Ungrouped lat with db params from) tys
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col Expression 'Ungrouped lat with db params from ty
-> NP (Expression 'Ungrouped lat with db params from) '[]
-> NP (Expression 'Ungrouped lat with db params from) '[ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (Expression 'Ungrouped lat with db params from) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance (HasUnique tab (Join from lat) row, Has col row ty, column ~ (col ::: ty))
=> IsLabel col
(Aliased (Expression 'Ungrouped lat with db params from) column) where
fromLabel :: Aliased (Expression 'Ungrouped lat with db params from) column
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col Expression 'Ungrouped lat with db params from ty
-> Alias col
-> Aliased
(Expression 'Ungrouped lat with db params from) (col ::: ty)
forall k (alias :: Symbol) (expression :: k -> *) (ty :: k).
KnownSymbol alias =>
expression ty -> Alias alias -> Aliased expression (alias ::: ty)
`As` Alias col
forall (alias :: Symbol). Alias alias
Alias
instance (HasUnique tab (Join from lat) row, Has col row ty, columns ~ '[col ::: ty])
=> IsLabel col
(NP (Aliased (Expression 'Ungrouped lat with db params from)) columns) where
fromLabel :: NP
(Aliased (Expression 'Ungrouped lat with db params from)) columns
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col Aliased
(Expression 'Ungrouped lat with db params from) (col ::: ty)
-> NP (Aliased (Expression 'Ungrouped lat with db params from)) '[]
-> NP
(Aliased (Expression 'Ungrouped lat with db params from))
'[col ::: ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (Aliased (Expression 'Ungrouped lat with db params from)) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance (Has tab (Join from lat) row, Has col row ty)
=> IsQualified tab col (Expression 'Ungrouped lat with db params from ty) where
Alias tab
tab ! :: Alias tab
-> Alias col -> Expression 'Ungrouped lat with db params from ty
! Alias col
col = ByteString -> Expression 'Ungrouped lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression 'Ungrouped lat with db params from ty)
-> ByteString -> Expression 'Ungrouped lat with db params from ty
forall a b. (a -> b) -> a -> b
$
Alias tab -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias tab
tab ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"." ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Alias col -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias col
col
instance (Has tab (Join from lat) row, Has col row ty, tys ~ '[ty])
=> IsQualified tab col (NP (Expression 'Ungrouped lat with db params from) tys) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> NP (Expression 'Ungrouped lat with db params from) tys
! Alias col
col = Alias tab
tab Alias tab
-> Alias col -> Expression 'Ungrouped lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col Expression 'Ungrouped lat with db params from ty
-> NP (Expression 'Ungrouped lat with db params from) '[]
-> NP (Expression 'Ungrouped lat with db params from) '[ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (Expression 'Ungrouped lat with db params from) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance (Has tab (Join from lat) row, Has col row ty, column ~ (col ::: ty))
=> IsQualified tab col
(Aliased (Expression 'Ungrouped lat with db params from) column) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> Aliased (Expression 'Ungrouped lat with db params from) column
! Alias col
col = Alias tab
tab Alias tab
-> Alias col -> Expression 'Ungrouped lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col Expression 'Ungrouped lat with db params from ty
-> Alias col
-> Aliased
(Expression 'Ungrouped lat with db params from) (col ::: ty)
forall k (alias :: Symbol) (expression :: k -> *) (ty :: k).
KnownSymbol alias =>
expression ty -> Alias alias -> Aliased expression (alias ::: ty)
`As` Alias col
col
instance (Has tab (Join from lat) row, Has col row ty, columns ~ '[col ::: ty])
=> IsQualified tab col
(NP (Aliased (Expression 'Ungrouped lat with db params from)) columns) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> NP
(Aliased (Expression 'Ungrouped lat with db params from)) columns
! Alias col
col = Alias tab
tab Alias tab
-> Alias col
-> Aliased
(Expression 'Ungrouped lat with db params from) (col ::: ty)
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col Aliased
(Expression 'Ungrouped lat with db params from) (col ::: ty)
-> NP (Aliased (Expression 'Ungrouped lat with db params from)) '[]
-> NP
(Aliased (Expression 'Ungrouped lat with db params from))
'[col ::: ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (Aliased (Expression 'Ungrouped lat with db params from)) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance
( HasUnique tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
) => IsLabel col
(Expression ('Grouped bys) lat with db params from ty) where
fromLabel :: Expression ('Grouped bys) lat with db params from ty
fromLabel = ByteString -> Expression ('Grouped bys) lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression ('Grouped bys) lat with db params from ty)
-> ByteString
-> Expression ('Grouped bys) lat with db params from ty
forall a b. (a -> b) -> a -> b
$ Alias col -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (Alias col
forall (alias :: Symbol). Alias alias
Alias @col)
instance
( HasUnique tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
, tys ~ '[ty]
) => IsLabel col
(NP (Expression ('Grouped bys) lat with db params from) tys) where
fromLabel :: NP (Expression ('Grouped bys) lat with db params from) tys
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col Expression ('Grouped bys) lat with db params from ty
-> NP (Expression ('Grouped bys) lat with db params from) '[]
-> NP (Expression ('Grouped bys) lat with db params from) '[ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (Expression ('Grouped bys) lat with db params from) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance
( HasUnique tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
, column ~ (col ::: ty)
) => IsLabel col
(Aliased (Expression ('Grouped bys) lat with db params from) column) where
fromLabel :: Aliased (Expression ('Grouped bys) lat with db params from) column
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col Expression ('Grouped bys) lat with db params from ty
-> Alias col
-> Aliased
(Expression ('Grouped bys) lat with db params from) (col ::: ty)
forall k (alias :: Symbol) (expression :: k -> *) (ty :: k).
KnownSymbol alias =>
expression ty -> Alias alias -> Aliased expression (alias ::: ty)
`As` Alias col
forall (alias :: Symbol). Alias alias
Alias
instance
( HasUnique tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
, columns ~ '[col ::: ty]
) => IsLabel col
(NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns) where
fromLabel :: NP
(Aliased (Expression ('Grouped bys) lat with db params from))
columns
fromLabel = forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col Aliased
(Expression ('Grouped bys) lat with db params from) (col ::: ty)
-> NP
(Aliased (Expression ('Grouped bys) lat with db params from)) '[]
-> NP
(Aliased (Expression ('Grouped bys) lat with db params from))
'[col ::: ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP
(Aliased (Expression ('Grouped bys) lat with db params from)) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance
( Has tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
) => IsQualified tab col
(Expression ('Grouped bys) lat with db params from ty) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> Expression ('Grouped bys) lat with db params from ty
! Alias col
col = ByteString -> Expression ('Grouped bys) lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression ('Grouped bys) lat with db params from ty)
-> ByteString
-> Expression ('Grouped bys) lat with db params from ty
forall a b. (a -> b) -> a -> b
$
Alias tab -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias tab
tab ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
"." ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Alias col -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias col
col
instance
( Has tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
, tys ~ '[ty]
) => IsQualified tab col
(NP (Expression ('Grouped bys) lat with db params from) tys) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> NP (Expression ('Grouped bys) lat with db params from) tys
! Alias col
col = Alias tab
tab Alias tab
-> Alias col
-> Expression ('Grouped bys) lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col Expression ('Grouped bys) lat with db params from ty
-> NP (Expression ('Grouped bys) lat with db params from) '[]
-> NP (Expression ('Grouped bys) lat with db params from) '[ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP (Expression ('Grouped bys) lat with db params from) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance
( Has tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
, column ~ (col ::: ty)
) => IsQualified tab col
(Aliased (Expression ('Grouped bys) lat with db params from) column) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> Aliased
(Expression ('Grouped bys) lat with db params from) column
! Alias col
col = Alias tab
tab Alias tab
-> Alias col
-> Expression ('Grouped bys) lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col Expression ('Grouped bys) lat with db params from ty
-> Alias col
-> Aliased
(Expression ('Grouped bys) lat with db params from) (col ::: ty)
forall k (alias :: Symbol) (expression :: k -> *) (ty :: k).
KnownSymbol alias =>
expression ty -> Alias alias -> Aliased expression (alias ::: ty)
`As` Alias col
col
instance
( Has tab (Join from lat) row
, Has col row ty
, GroupedBy tab col bys
, columns ~ '[col ::: ty]
) => IsQualified tab col
(NP (Aliased (Expression ('Grouped bys) lat with db params from)) columns) where
Alias tab
tab ! :: Alias tab
-> Alias col
-> NP
(Aliased (Expression ('Grouped bys) lat with db params from))
columns
! Alias col
col = Alias tab
tab Alias tab
-> Alias col
-> Aliased
(Expression ('Grouped bys) lat with db params from) (col ::: ty)
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col Aliased
(Expression ('Grouped bys) lat with db params from) (col ::: ty)
-> NP
(Aliased (Expression ('Grouped bys) lat with db params from)) '[]
-> NP
(Aliased (Expression ('Grouped bys) lat with db params from))
'[col ::: ty]
forall k (a :: k -> *) (x :: k) (xs :: [k]).
a x -> NP a xs -> NP a (x : xs)
:* NP
(Aliased (Expression ('Grouped bys) lat with db params from)) '[]
forall k (a :: k -> *). NP a '[]
Nil
instance (KnownSymbol label, label `In` labels) => IsPGlabel label
(Expression grp lat with db params from (null ('PGenum labels))) where
label :: Expression grp lat with db params from (null ('PGenum labels))
label = ByteString
-> Expression grp lat with db params from (null ('PGenum labels))
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from (null ('PGenum labels)))
-> ByteString
-> Expression grp lat with db params from (null ('PGenum labels))
forall a b. (a -> b) -> a -> b
$ PGlabel label -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL (PGlabel label
forall (label :: Symbol). PGlabel label
PGlabel @label)
unsafeBinaryOp :: ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp :: ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
op Expression grp lat with db params from ty0
x Expression grp lat with db params from ty1
y = ByteString -> Expression grp lat with db params from ty2
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from ty2)
-> ByteString -> Expression grp lat with db params from ty2
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
parenthesized (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
Expression grp lat with db params from ty0 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ty0
x ByteString -> ByteString -> ByteString
<+> ByteString
op ByteString -> ByteString -> ByteString
<+> Expression grp lat with db params from ty1 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ty1
y
unsafeLeftOp :: ByteString -> x --> y
unsafeLeftOp :: ByteString -> x --> y
unsafeLeftOp ByteString
op Expression grp lat with db params from x
x = ByteString -> Expression grp lat with db params from y
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from y)
-> ByteString -> Expression grp lat with db params from y
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
parenthesized (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString
op ByteString -> ByteString -> ByteString
<+> Expression grp lat with db params from x -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from x
x
unsafeRightOp :: ByteString -> x --> y
unsafeRightOp :: ByteString -> x --> y
unsafeRightOp ByteString
op Expression grp lat with db params from x
x = ByteString -> Expression grp lat with db params from y
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from y)
-> ByteString -> Expression grp lat with db params from y
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
parenthesized (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Expression grp lat with db params from x -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from x
x ByteString -> ByteString -> ByteString
<+> ByteString
op
unsafeFunction :: ByteString -> x --> y
unsafeFunction :: ByteString -> x --> y
unsafeFunction ByteString
fun Expression grp lat with db params from x
x = ByteString -> Expression grp lat with db params from y
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from y)
-> ByteString -> Expression grp lat with db params from y
forall a b. (a -> b) -> a -> b
$
ByteString
fun ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized (Expression grp lat with db params from x -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from x
x)
function
:: (Has sch db schema, Has fun schema ('Function ('[x] :=> 'Returns y)))
=> QualifiedAlias sch fun
-> Fun db x y
function :: QualifiedAlias sch fun -> Fun db x y
function QualifiedAlias sch fun
f = ByteString -> x --> y
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction (ByteString -> x --> y) -> ByteString -> x --> y
forall a b. (a -> b) -> a -> b
$ QualifiedAlias sch fun -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch fun
f
unsafeFunctionN :: SListI xs => ByteString -> xs ---> y
unsafeFunctionN :: ByteString -> xs ---> y
unsafeFunctionN ByteString
fun NP (Expression grp lat with db params from) xs
xs = ByteString -> Expression grp lat with db params from y
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from y)
-> ByteString -> Expression grp lat with db params from y
forall a b. (a -> b) -> a -> b
$
ByteString
fun ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized ((forall (x :: NullType).
Expression grp lat with db params from x -> ByteString)
-> NP (Expression grp lat with db params from) xs -> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated forall sql. RenderSQL sql => sql -> ByteString
forall (x :: NullType).
Expression grp lat with db params from x -> ByteString
renderSQL NP (Expression grp lat with db params from) xs
xs)
functionN
:: ( Has sch db schema
, Has fun schema ('Function (xs :=> 'Returns y))
, SListI xs )
=> QualifiedAlias sch fun
-> FunN db xs y
functionN :: QualifiedAlias sch fun -> FunN db xs y
functionN QualifiedAlias sch fun
f = ByteString -> xs ---> y
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN (ByteString -> xs ---> y) -> ByteString -> xs ---> y
forall a b. (a -> b) -> a -> b
$ QualifiedAlias sch fun -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch fun
f
instance
Num (Expression grp lat with db params from (null 'PGint2)) where
+ :: Expression grp lat with db params from (null 'PGint2)
-> Expression grp lat with db params from (null 'PGint2)
-> Expression grp lat with db params from (null 'PGint2)
(+) = ByteString -> Operator (null 'PGint2) (null 'PGint2) (null 'PGint2)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"+"
(-) = ByteString -> Operator (null 'PGint2) (null 'PGint2) (null 'PGint2)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
* :: Expression grp lat with db params from (null 'PGint2)
-> Expression grp lat with db params from (null 'PGint2)
-> Expression grp lat with db params from (null 'PGint2)
(*) = ByteString -> Operator (null 'PGint2) (null 'PGint2) (null 'PGint2)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"*"
abs :: Expression grp lat with db params from (null 'PGint2)
-> Expression grp lat with db params from (null 'PGint2)
abs = ByteString -> null 'PGint2 --> null 'PGint2
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"abs"
signum :: Expression grp lat with db params from (null 'PGint2)
-> Expression grp lat with db params from (null 'PGint2)
signum = ByteString -> null 'PGint2 --> null 'PGint2
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sign"
fromInteger :: Integer -> Expression grp lat with db params from (null 'PGint2)
fromInteger
= ByteString -> Expression grp lat with db params from (null 'PGint2)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGint2))
-> (Integer -> ByteString)
-> Integer
-> Expression grp lat with db params from (null 'PGint2)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: int2")
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
toStrict
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString
(Builder -> ByteString)
-> (Integer -> Builder) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int16 -> Builder
int16Dec
(Int16 -> Builder) -> (Integer -> Int16) -> Integer -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> Int16
forall a. Num a => Integer -> a
fromInteger
instance
Num (Expression grp lat with db params from (null 'PGint4)) where
+ :: Expression grp lat with db params from (null 'PGint4)
-> Expression grp lat with db params from (null 'PGint4)
-> Expression grp lat with db params from (null 'PGint4)
(+) = ByteString -> Operator (null 'PGint4) (null 'PGint4) (null 'PGint4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"+"
(-) = ByteString -> Operator (null 'PGint4) (null 'PGint4) (null 'PGint4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
* :: Expression grp lat with db params from (null 'PGint4)
-> Expression grp lat with db params from (null 'PGint4)
-> Expression grp lat with db params from (null 'PGint4)
(*) = ByteString -> Operator (null 'PGint4) (null 'PGint4) (null 'PGint4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"*"
abs :: Expression grp lat with db params from (null 'PGint4)
-> Expression grp lat with db params from (null 'PGint4)
abs = ByteString -> null 'PGint4 --> null 'PGint4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"abs"
signum :: Expression grp lat with db params from (null 'PGint4)
-> Expression grp lat with db params from (null 'PGint4)
signum = ByteString -> null 'PGint4 --> null 'PGint4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sign"
fromInteger :: Integer -> Expression grp lat with db params from (null 'PGint4)
fromInteger
= ByteString -> Expression grp lat with db params from (null 'PGint4)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGint4))
-> (Integer -> ByteString)
-> Integer
-> Expression grp lat with db params from (null 'PGint4)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: int4")
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
toStrict
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString
(Builder -> ByteString)
-> (Integer -> Builder) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Int32 -> Builder
int32Dec
(Int32 -> Builder) -> (Integer -> Int32) -> Integer -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> Int32
forall a. Num a => Integer -> a
fromInteger
instance
Num (Expression grp lat with db params from (null 'PGint8)) where
+ :: Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
(+) = ByteString -> Operator (null 'PGint8) (null 'PGint8) (null 'PGint8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"+"
(-) = ByteString -> Operator (null 'PGint8) (null 'PGint8) (null 'PGint8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
* :: Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
(*) = ByteString -> Operator (null 'PGint8) (null 'PGint8) (null 'PGint8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"*"
abs :: Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
abs = ByteString -> null 'PGint8 --> null 'PGint8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"abs"
signum :: Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
signum = ByteString -> null 'PGint8 --> null 'PGint8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sign"
fromInteger :: Integer -> Expression grp lat with db params from (null 'PGint8)
fromInteger Integer
x =
let
y :: Int64
y = Integer -> Int64
forall a. Num a => Integer -> a
fromInteger Integer
x
in
if Int64
y Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
forall a. Bounded a => a
minBound
then Integer -> Expression grp lat with db params from (null 'PGint8)
forall a. Num a => Integer -> a
fromInteger (Integer
xInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1) Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
-> Expression grp lat with db params from (null 'PGint8)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGint8)
1
else ByteString -> Expression grp lat with db params from (null 'PGint8)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGint8))
-> (Builder -> ByteString)
-> Builder
-> Expression grp lat with db params from (null 'PGint8)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: int8")
(ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
toStrict
(ByteString -> ByteString)
-> (Builder -> ByteString) -> Builder -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString
(Builder -> Expression grp lat with db params from (null 'PGint8))
-> Builder -> Expression grp lat with db params from (null 'PGint8)
forall a b. (a -> b) -> a -> b
$ Int64 -> Builder
int64Dec Int64
y
instance
Num (Expression grp lat with db params from (null 'PGfloat4)) where
+ :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
(+) = ByteString
-> Operator (null 'PGfloat4) (null 'PGfloat4) (null 'PGfloat4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"+"
(-) = ByteString
-> Operator (null 'PGfloat4) (null 'PGfloat4) (null 'PGfloat4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
* :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
(*) = ByteString
-> Operator (null 'PGfloat4) (null 'PGfloat4) (null 'PGfloat4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"*"
abs :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
abs = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"abs"
signum :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
signum = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sign"
fromInteger :: Integer -> Expression grp lat with db params from (null 'PGfloat4)
fromInteger Integer
x
= ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGfloat4))
-> (ByteString -> ByteString)
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: float4") (ByteString
-> Expression grp lat with db params from (null 'PGfloat4))
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall a b. (a -> b) -> a -> b
$
let
y :: Float
y = Integer -> Float
forall a. Num a => Integer -> a
fromInteger Integer
x
decimal :: Float -> ByteString
decimal = ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Float -> ByteString) -> Float -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString (Builder -> ByteString)
-> (Float -> Builder) -> Float -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Builder
floatDec
in
if Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
y Bool -> Bool -> Bool
|| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
y
then ByteString -> ByteString
singleQuotedUtf8 (Float -> ByteString
decimal Float
y)
else Float -> ByteString
decimal Float
y
instance
Num (Expression grp lat with db params from (null 'PGfloat8)) where
+ :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
(+) = ByteString
-> Operator (null 'PGfloat8) (null 'PGfloat8) (null 'PGfloat8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"+"
(-) = ByteString
-> Operator (null 'PGfloat8) (null 'PGfloat8) (null 'PGfloat8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
* :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
(*) = ByteString
-> Operator (null 'PGfloat8) (null 'PGfloat8) (null 'PGfloat8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"*"
abs :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
abs = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"abs"
signum :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
signum = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sign"
fromInteger :: Integer -> Expression grp lat with db params from (null 'PGfloat8)
fromInteger Integer
x
= ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGfloat8))
-> (ByteString -> ByteString)
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: float8") (ByteString
-> Expression grp lat with db params from (null 'PGfloat8))
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall a b. (a -> b) -> a -> b
$
let
y :: Double
y = Integer -> Double
forall a. Num a => Integer -> a
fromInteger Integer
x
decimal :: Double -> ByteString
decimal = ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Double -> ByteString) -> Double -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString (Builder -> ByteString)
-> (Double -> Builder) -> Double -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Builder
doubleDec
in
if Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
y Bool -> Bool -> Bool
|| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
y
then ByteString -> ByteString
singleQuotedUtf8 (Double -> ByteString
decimal Double
y)
else Double -> ByteString
decimal Double
y
instance
Num (Expression grp lat with db params from (null 'PGnumeric)) where
+ :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
(+) = ByteString
-> Operator (null 'PGnumeric) (null 'PGnumeric) (null 'PGnumeric)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"+"
(-) = ByteString
-> Operator (null 'PGnumeric) (null 'PGnumeric) (null 'PGnumeric)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
* :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
(*) = ByteString
-> Operator (null 'PGnumeric) (null 'PGnumeric) (null 'PGnumeric)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"*"
abs :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
abs = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"abs"
signum :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
signum = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sign"
fromInteger :: Integer -> Expression grp lat with db params from (null 'PGnumeric)
fromInteger
= ByteString
-> Expression grp lat with db params from (null 'PGnumeric)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGnumeric))
-> (Integer -> ByteString)
-> Integer
-> Expression grp lat with db params from (null 'PGnumeric)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: numeric")
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
toStrict
(ByteString -> ByteString)
-> (Integer -> ByteString) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString
(Builder -> ByteString)
-> (Integer -> Builder) -> Integer -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Scientific -> Builder
scientificBuilder
(Scientific -> Builder)
-> (Integer -> Scientific) -> Integer -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Integer -> Scientific
forall a. Num a => Integer -> a
fromInteger
instance Fractional
(Expression grp lat with db params from (null 'PGfloat4)) where
/ :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
(/) = ByteString
-> Operator (null 'PGfloat4) (null 'PGfloat4) (null 'PGfloat4)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"/"
fromRational :: Rational -> Expression grp lat with db params from (null 'PGfloat4)
fromRational Rational
x
= ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGfloat4))
-> (ByteString -> ByteString)
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: float4") (ByteString
-> Expression grp lat with db params from (null 'PGfloat4))
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall a b. (a -> b) -> a -> b
$
let
y :: Float
y = Rational -> Float
forall a. Fractional a => Rational -> a
fromRational Rational
x
decimal :: Float -> ByteString
decimal = ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Float -> ByteString) -> Float -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString (Builder -> ByteString)
-> (Float -> Builder) -> Float -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Float -> Builder
floatDec
in
if Float -> Bool
forall a. RealFloat a => a -> Bool
isNaN Float
y Bool -> Bool -> Bool
|| Float -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Float
y
then ByteString -> ByteString
singleQuotedUtf8 (Float -> ByteString
decimal Float
y)
else Float -> ByteString
decimal Float
y
instance Fractional
(Expression grp lat with db params from (null 'PGfloat8)) where
/ :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
(/) = ByteString
-> Operator (null 'PGfloat8) (null 'PGfloat8) (null 'PGfloat8)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"/"
fromRational :: Rational -> Expression grp lat with db params from (null 'PGfloat8)
fromRational Rational
x
= ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGfloat8))
-> (ByteString -> ByteString)
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: float8") (ByteString
-> Expression grp lat with db params from (null 'PGfloat8))
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall a b. (a -> b) -> a -> b
$
let
y :: Double
y = Rational -> Double
forall a. Fractional a => Rational -> a
fromRational Rational
x
decimal :: Double -> ByteString
decimal = ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Double -> ByteString) -> Double -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString (Builder -> ByteString)
-> (Double -> Builder) -> Double -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Double -> Builder
doubleDec
in
if Double -> Bool
forall a. RealFloat a => a -> Bool
isNaN Double
y Bool -> Bool -> Bool
|| Double -> Bool
forall a. RealFloat a => a -> Bool
isInfinite Double
y
then ByteString -> ByteString
singleQuotedUtf8 (Double -> ByteString
decimal Double
y)
else Double -> ByteString
decimal Double
y
instance Fractional
(Expression grp lat with db params from (null 'PGnumeric)) where
/ :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
(/) = ByteString
-> Operator (null 'PGnumeric) (null 'PGnumeric) (null 'PGnumeric)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"/"
fromRational :: Rational
-> Expression grp lat with db params from (null 'PGnumeric)
fromRational
= ByteString
-> Expression grp lat with db params from (null 'PGnumeric)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGnumeric))
-> (Rational -> ByteString)
-> Rational
-> Expression grp lat with db params from (null 'PGnumeric)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (Rational -> ByteString) -> Rational -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: numeric")
(ByteString -> ByteString)
-> (Rational -> ByteString) -> Rational -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
toStrict
(ByteString -> ByteString)
-> (Rational -> ByteString) -> Rational -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Builder -> ByteString
toLazyByteString
(Builder -> ByteString)
-> (Rational -> Builder) -> Rational -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Scientific -> Builder
scientificBuilder
(Scientific -> Builder)
-> (Rational -> Scientific) -> Rational -> Builder
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. Rational -> Scientific
forall a. Fractional a => Rational -> a
fromRational
instance Floating
(Expression grp lat with db params from (null 'PGfloat4)) where
pi :: Expression grp lat with db params from (null 'PGfloat4)
pi = ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"pi()"
exp :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
exp = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"exp"
log :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
log = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"ln"
sqrt :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
sqrt = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sqrt"
Expression grp lat with db params from (null 'PGfloat4)
b ** :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
** Expression grp lat with db params from (null 'PGfloat4)
x = ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from (null 'PGfloat4))
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat4)
forall a b. (a -> b) -> a -> b
$
ByteString
"power(" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from (null 'PGfloat4)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from (null 'PGfloat4)
b ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
", " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from (null 'PGfloat4)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from (null 'PGfloat4)
x ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
")"
logBase :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
logBase Expression grp lat with db params from (null 'PGfloat4)
b Expression grp lat with db params from (null 'PGfloat4)
y = Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
log Expression grp lat with db params from (null 'PGfloat4)
y Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
log Expression grp lat with db params from (null 'PGfloat4)
b
sin :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
sin = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sin"
cos :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
cos = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"cos"
tan :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
tan = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"tan"
asin :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
asin = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"asin"
acos :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
acos = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"acos"
atan :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
atan = ByteString -> null 'PGfloat4 --> null 'PGfloat4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"atan"
sinh :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
sinh Expression grp lat with db params from (null 'PGfloat4)
x = (Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
exp Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
exp (-Expression grp lat with db params from (null 'PGfloat4)
x)) Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat4)
2
cosh :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
cosh Expression grp lat with db params from (null 'PGfloat4)
x = (Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
exp Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
exp (-Expression grp lat with db params from (null 'PGfloat4)
x)) Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat4)
2
tanh :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
tanh Expression grp lat with db params from (null 'PGfloat4)
x = Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
sinh Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
cosh Expression grp lat with db params from (null 'PGfloat4)
x
asinh :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
asinh Expression grp lat with db params from (null 'PGfloat4)
x = Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
log (Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
sqrt (Expression grp lat with db params from (null 'PGfloat4)
xExpression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
*Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat4)
1))
acosh :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
acosh Expression grp lat with db params from (null 'PGfloat4)
x = Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
log (Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
sqrt (Expression grp lat with db params from (null 'PGfloat4)
xExpression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
*Expression grp lat with db params from (null 'PGfloat4)
x Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGfloat4)
1))
atanh :: Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
atanh Expression grp lat with db params from (null 'PGfloat4)
x = Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Floating a => a -> a
log ((Expression grp lat with db params from (null 'PGfloat4)
1 Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat4)
x) Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Fractional a => a -> a -> a
/ (Expression grp lat with db params from (null 'PGfloat4)
1 Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGfloat4)
x)) Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
-> Expression grp lat with db params from (null 'PGfloat4)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat4)
2
instance Floating
(Expression grp lat with db params from (null 'PGfloat8)) where
pi :: Expression grp lat with db params from (null 'PGfloat8)
pi = ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"pi()"
exp :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
exp = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"exp"
log :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
log = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"ln"
sqrt :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
sqrt = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sqrt"
Expression grp lat with db params from (null 'PGfloat8)
b ** :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
** Expression grp lat with db params from (null 'PGfloat8)
x = ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from (null 'PGfloat8))
-> ByteString
-> Expression grp lat with db params from (null 'PGfloat8)
forall a b. (a -> b) -> a -> b
$
ByteString
"power(" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from (null 'PGfloat8)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from (null 'PGfloat8)
b ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
", " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from (null 'PGfloat8)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from (null 'PGfloat8)
x ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
")"
logBase :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
logBase Expression grp lat with db params from (null 'PGfloat8)
b Expression grp lat with db params from (null 'PGfloat8)
y = Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
log Expression grp lat with db params from (null 'PGfloat8)
y Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
log Expression grp lat with db params from (null 'PGfloat8)
b
sin :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
sin = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sin"
cos :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
cos = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"cos"
tan :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
tan = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"tan"
asin :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
asin = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"asin"
acos :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
acos = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"acos"
atan :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
atan = ByteString -> null 'PGfloat8 --> null 'PGfloat8
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"atan"
sinh :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
sinh Expression grp lat with db params from (null 'PGfloat8)
x = (Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
exp Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
exp (-Expression grp lat with db params from (null 'PGfloat8)
x)) Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat8)
2
cosh :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
cosh Expression grp lat with db params from (null 'PGfloat8)
x = (Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
exp Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
exp (-Expression grp lat with db params from (null 'PGfloat8)
x)) Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat8)
2
tanh :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
tanh Expression grp lat with db params from (null 'PGfloat8)
x = Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
sinh Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
cosh Expression grp lat with db params from (null 'PGfloat8)
x
asinh :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
asinh Expression grp lat with db params from (null 'PGfloat8)
x = Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
log (Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
sqrt (Expression grp lat with db params from (null 'PGfloat8)
xExpression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
*Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat8)
1))
acosh :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
acosh Expression grp lat with db params from (null 'PGfloat8)
x = Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
log (Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
sqrt (Expression grp lat with db params from (null 'PGfloat8)
xExpression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
*Expression grp lat with db params from (null 'PGfloat8)
x Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGfloat8)
1))
atanh :: Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
atanh Expression grp lat with db params from (null 'PGfloat8)
x = Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Floating a => a -> a
log ((Expression grp lat with db params from (null 'PGfloat8)
1 Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGfloat8)
x) Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Fractional a => a -> a -> a
/ (Expression grp lat with db params from (null 'PGfloat8)
1 Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGfloat8)
x)) Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
-> Expression grp lat with db params from (null 'PGfloat8)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGfloat8)
2
instance Floating
(Expression grp lat with db params from (null 'PGnumeric)) where
pi :: Expression grp lat with db params from (null 'PGnumeric)
pi = ByteString
-> Expression grp lat with db params from (null 'PGnumeric)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"pi()"
exp :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
exp = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"exp"
log :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
log = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"ln"
sqrt :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
sqrt = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sqrt"
Expression grp lat with db params from (null 'PGnumeric)
b ** :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
** Expression grp lat with db params from (null 'PGnumeric)
x = ByteString
-> Expression grp lat with db params from (null 'PGnumeric)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString
-> Expression grp lat with db params from (null 'PGnumeric))
-> ByteString
-> Expression grp lat with db params from (null 'PGnumeric)
forall a b. (a -> b) -> a -> b
$
ByteString
"power(" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from (null 'PGnumeric)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from (null 'PGnumeric)
b ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
", " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression grp lat with db params from (null 'PGnumeric)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from (null 'PGnumeric)
x ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
")"
logBase :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
logBase Expression grp lat with db params from (null 'PGnumeric)
b Expression grp lat with db params from (null 'PGnumeric)
y = Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
log Expression grp lat with db params from (null 'PGnumeric)
y Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
log Expression grp lat with db params from (null 'PGnumeric)
b
sin :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
sin = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"sin"
cos :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
cos = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"cos"
tan :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
tan = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"tan"
asin :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
asin = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"asin"
acos :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
acos = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"acos"
atan :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
atan = ByteString -> null 'PGnumeric --> null 'PGnumeric
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"atan"
sinh :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
sinh Expression grp lat with db params from (null 'PGnumeric)
x = (Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
exp Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
exp (-Expression grp lat with db params from (null 'PGnumeric)
x)) Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGnumeric)
2
cosh :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
cosh Expression grp lat with db params from (null 'PGnumeric)
x = (Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
exp Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
exp (-Expression grp lat with db params from (null 'PGnumeric)
x)) Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGnumeric)
2
tanh :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
tanh Expression grp lat with db params from (null 'PGnumeric)
x = Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
sinh Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
cosh Expression grp lat with db params from (null 'PGnumeric)
x
asinh :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
asinh Expression grp lat with db params from (null 'PGnumeric)
x = Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
log (Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
sqrt (Expression grp lat with db params from (null 'PGnumeric)
xExpression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
*Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGnumeric)
1))
acosh :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
acosh Expression grp lat with db params from (null 'PGnumeric)
x = Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
log (Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
sqrt (Expression grp lat with db params from (null 'PGnumeric)
xExpression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
*Expression grp lat with db params from (null 'PGnumeric)
x Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGnumeric)
1))
atanh :: Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
atanh Expression grp lat with db params from (null 'PGnumeric)
x = Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Floating a => a -> a
log ((Expression grp lat with db params from (null 'PGnumeric)
1 Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
+ Expression grp lat with db params from (null 'PGnumeric)
x) Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Fractional a => a -> a -> a
/ (Expression grp lat with db params from (null 'PGnumeric)
1 Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Num a => a -> a -> a
- Expression grp lat with db params from (null 'PGnumeric)
x)) Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
-> Expression grp lat with db params from (null 'PGnumeric)
forall a. Fractional a => a -> a -> a
/ Expression grp lat with db params from (null 'PGnumeric)
2
class PGSubset ty where
(@>) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(@>) = ByteString -> Operator (null0 ty) (null1 ty) ('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"@>"
(<@) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(<@) = ByteString -> Operator (null0 ty) (null1 ty) ('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"<@"
infix 4 @>
infix 4 <@
instance PGSubset 'PGjsonb
instance PGSubset 'PGtsquery
instance PGSubset ('PGvararray ty)
instance PGSubset ('PGrange ty)
class PGIntersect ty where
(@&&) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(@&&) = ByteString -> Operator (null0 ty) (null1 ty) ('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"&&"
instance PGIntersect ('PGvararray ty)
instance PGIntersect ('PGrange ty)
instance IsString
(Expression grp lat with db params from (null 'PGtext)) where
fromString :: String -> Expression grp lat with db params from (null 'PGtext)
fromString
= ByteString -> Expression grp lat with db params from (null 'PGtext)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGtext))
-> (String -> ByteString)
-> String
-> Expression grp lat with db params from (null 'PGtext)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (String -> ByteString) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: text")
(ByteString -> ByteString)
-> (String -> ByteString) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString
escapeQuotedString
instance IsString
(Expression grp lat with db params from (null 'PGtsvector)) where
fromString :: String -> Expression grp lat with db params from (null 'PGtsvector)
fromString
= ByteString
-> Expression grp lat with db params from (null 'PGtsvector)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGtsvector))
-> (String -> ByteString)
-> String
-> Expression grp lat with db params from (null 'PGtsvector)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (String -> ByteString) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: tsvector")
(ByteString -> ByteString)
-> (String -> ByteString) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString
escapeQuotedString
instance IsString
(Expression grp lat with db params from (null 'PGtsquery)) where
fromString :: String -> Expression grp lat with db params from (null 'PGtsquery)
fromString
= ByteString
-> Expression grp lat with db params from (null 'PGtsquery)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression
(ByteString
-> Expression grp lat with db params from (null 'PGtsquery))
-> (String -> ByteString)
-> String
-> Expression grp lat with db params from (null 'PGtsquery)
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. ByteString -> ByteString
parenthesized
(ByteString -> ByteString)
-> (String -> ByteString) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. (ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
" :: tsquery")
(ByteString -> ByteString)
-> (String -> ByteString) -> String -> ByteString
forall k (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k).
Category cat =>
cat b c -> cat a b -> cat a c
. String -> ByteString
escapeQuotedString
instance Semigroup
(Expression grp lat with db params from (null ('PGvararray ty))) where
<> :: Expression grp lat with db params from (null ('PGvararray ty))
-> Expression grp lat with db params from (null ('PGvararray ty))
-> Expression grp lat with db params from (null ('PGvararray ty))
(<>) = ByteString
-> Operator
(null ('PGvararray ty))
(null ('PGvararray ty))
(null ('PGvararray ty))
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"||"
instance Semigroup
(Expression grp lat with db params from (null 'PGjsonb)) where
<> :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGjsonb)
(<>) = ByteString
-> Operator (null 'PGjsonb) (null 'PGjsonb) (null 'PGjsonb)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"||"
instance Semigroup
(Expression grp lat with db params from (null 'PGtext)) where
<> :: Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
(<>) = ByteString -> Operator (null 'PGtext) (null 'PGtext) (null 'PGtext)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"||"
instance Semigroup
(Expression grp lat with db params from (null 'PGtsvector)) where
<> :: Expression grp lat with db params from (null 'PGtsvector)
-> Expression grp lat with db params from (null 'PGtsvector)
-> Expression grp lat with db params from (null 'PGtsvector)
(<>) = ByteString
-> Operator
(null 'PGtsvector) (null 'PGtsvector) (null 'PGtsvector)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"||"
instance Monoid
(Expression grp lat with db params from (null 'PGtext)) where
mempty :: Expression grp lat with db params from (null 'PGtext)
mempty = String -> Expression grp lat with db params from (null 'PGtext)
forall a. IsString a => String -> a
fromString String
""
mappend :: Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
mappend = Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
forall a. Semigroup a => a -> a -> a
(<>)
instance Monoid
(Expression grp lat with db params from (null 'PGtsvector)) where
mempty :: Expression grp lat with db params from (null 'PGtsvector)
mempty = String -> Expression grp lat with db params from (null 'PGtsvector)
forall a. IsString a => String -> a
fromString String
""
mappend :: Expression grp lat with db params from (null 'PGtsvector)
-> Expression grp lat with db params from (null 'PGtsvector)
-> Expression grp lat with db params from (null 'PGtsvector)
mappend = Expression grp lat with db params from (null 'PGtsvector)
-> Expression grp lat with db params from (null 'PGtsvector)
-> Expression grp lat with db params from (null 'PGtsvector)
forall a. Semigroup a => a -> a -> a
(<>)