{-# LANGUAGE
AllowAmbiguousTypes
, ConstraintKinds
, DeriveGeneric
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, GADTs
, GeneralizedNewtypeDeriving
, LambdaCase
, MagicHash
, OverloadedStrings
, ScopedTypeVariables
, StandaloneDeriving
, TypeApplications
, TypeFamilies
, TypeInType
, TypeOperators
, UndecidableInstances
, RankNTypes
#-}
module Squeal.PostgreSQL.Expression
(
Expression (..)
, Expr
, (:-->)
, unsafeFunction
, unsafeUnaryOpL
, unsafeUnaryOpR
, Operator
, unsafeBinaryOp
, FunctionVar
, unsafeFunctionVar
, FunctionN
, unsafeFunctionN
, PGSubset (..)
, (&)
, K (..)
, unK
) where
import Control.Category
import Control.DeepSeq
import Data.ByteString (ByteString)
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.Alias
import Squeal.PostgreSQL.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Schema
newtype Expression
(outer :: FromType)
(commons :: FromType)
(grp :: Grouping)
(schemas :: SchemasType)
(params :: [NullityType])
(from :: FromType)
(ty :: NullityType)
= UnsafeExpression { renderExpression :: ByteString }
deriving (GHC.Generic,Show,Eq,Ord,NFData)
instance RenderSQL (Expression outer commons grp schemas params from ty) where
renderSQL = renderExpression
type Expr x
= forall outer commons grp schemas params from
. Expression outer commons grp schemas params from x
type Operator x1 x2 y
= forall outer commons grp schemas params from
. Expression outer commons grp schemas params from x1
-> Expression outer commons grp schemas params from x2
-> Expression outer commons grp schemas params from y
type (:-->) x y
= forall outer commons grp schemas params from
. Expression outer commons grp schemas params from x
-> Expression outer commons grp schemas params from y
type FunctionN xs y
= forall outer commons grp schemas params from
. NP (Expression outer commons grp schemas params from) xs
-> Expression outer commons grp schemas params from y
type FunctionVar x0 x1 y
= forall outer commons grp schemas params from
. [Expression outer commons grp schemas params from x0]
-> Expression outer commons grp schemas params from x1
-> Expression outer commons grp schemas params from y
unsafeFunctionVar :: ByteString -> FunctionVar x0 x1 y
unsafeFunctionVar fun xs x = UnsafeExpression $ fun <> parenthesized
(commaSeparated (renderSQL <$> xs) <> ", " <> renderSQL x)
instance (HasUnique tab (Join outer from) row, Has col row ty)
=> IsLabel col (Expression outer commons 'Ungrouped schemas params from ty) where
fromLabel = UnsafeExpression $ renderSQL (Alias @col)
instance (HasUnique tab (Join outer from) row, Has col row ty, tys ~ '[ty])
=> IsLabel col (NP (Expression outer commons 'Ungrouped schemas params from) tys) where
fromLabel = fromLabel @col :* Nil
instance (HasUnique tab (Join outer from) row, Has col row ty, column ~ (col ::: ty))
=> IsLabel col
(Aliased (Expression outer commons 'Ungrouped schemas params from) column) where
fromLabel = fromLabel @col `As` Alias
instance (HasUnique tab (Join outer from) row, Has col row ty, columns ~ '[col ::: ty])
=> IsLabel col
(NP (Aliased (Expression outer commons 'Ungrouped schemas params from)) columns) where
fromLabel = fromLabel @col :* Nil
instance (Has tab (Join outer from) row, Has col row ty)
=> IsQualified tab col (Expression outer commons 'Ungrouped schemas params from ty) where
tab ! col = UnsafeExpression $
renderSQL tab <> "." <> renderSQL col
instance (Has tab (Join outer from) row, Has col row ty, tys ~ '[ty])
=> IsQualified tab col (NP (Expression outer commons 'Ungrouped schemas params from) tys) where
tab ! col = tab ! col :* Nil
instance (Has tab (Join outer from) row, Has col row ty, column ~ (col ::: ty))
=> IsQualified tab col
(Aliased (Expression outer commons 'Ungrouped schemas params from) column) where
tab ! col = tab ! col `As` col
instance (Has tab (Join outer from) row, Has col row ty, columns ~ '[col ::: ty])
=> IsQualified tab col
(NP (Aliased (Expression outer commons 'Ungrouped schemas params from)) columns) where
tab ! col = tab ! col :* Nil
instance
( HasUnique tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
) => IsLabel col
(Expression outer commons ('Grouped bys) schemas params from ty) where
fromLabel = UnsafeExpression $ renderSQL (Alias @col)
instance
( HasUnique tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
, tys ~ '[ty]
) => IsLabel col
(NP (Expression outer commons ('Grouped bys) schemas params from) tys) where
fromLabel = fromLabel @col :* Nil
instance
( HasUnique tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
, column ~ (col ::: ty)
) => IsLabel col
(Aliased (Expression outer commons ('Grouped bys) schemas params from) column) where
fromLabel = fromLabel @col `As` Alias
instance
( HasUnique tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
, columns ~ '[col ::: ty]
) => IsLabel col
(NP (Aliased (Expression outer commons ('Grouped bys) schemas params from)) columns) where
fromLabel = fromLabel @col :* Nil
instance
( Has tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
) => IsQualified tab col
(Expression outer commons ('Grouped bys) schemas params from ty) where
tab ! col = UnsafeExpression $
renderSQL tab <> "." <> renderSQL col
instance
( Has tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
, tys ~ '[ty]
) => IsQualified tab col
(NP (Expression outer commons ('Grouped bys) schemas params from) tys) where
tab ! col = tab ! col :* Nil
instance
( Has tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
, column ~ (col ::: ty)
) => IsQualified tab col
(Aliased (Expression outer commons ('Grouped bys) schemas params from) column) where
tab ! col = tab ! col `As` col
instance
( Has tab (Join outer from) row
, Has col row ty
, GroupedBy tab col bys
, columns ~ '[col ::: ty]
) => IsQualified tab col
(NP (Aliased (Expression outer commons ('Grouped bys) schemas params from)) columns) where
tab ! col = tab ! col :* Nil
instance (KnownSymbol label, label `In` labels) => IsPGlabel label
(Expression outer commons grp schemas params from (null ('PGenum labels))) where
label = UnsafeExpression $ renderSQL (PGlabel @label)
unsafeBinaryOp :: ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp op x y = UnsafeExpression $ parenthesized $
renderSQL x <+> op <+> renderSQL y
unsafeUnaryOpL :: ByteString -> x :--> y
unsafeUnaryOpL op x = UnsafeExpression $ parenthesized $ op <+> renderSQL x
unsafeUnaryOpR :: ByteString -> x :--> y
unsafeUnaryOpR op x = UnsafeExpression $ parenthesized $ renderSQL x <+> op
unsafeFunction :: ByteString -> x :--> y
unsafeFunction fun x = UnsafeExpression $
fun <> parenthesized (renderSQL x)
unsafeFunctionN :: SListI xs => ByteString -> FunctionN xs y
unsafeFunctionN fun xs = UnsafeExpression $
fun <> parenthesized (renderCommaSeparated renderSQL xs)
instance ty `In` PGNum
=> Num (Expression outer commons grp schemas params from (null ty)) where
(+) = unsafeBinaryOp "+"
(-) = unsafeBinaryOp "-"
(*) = unsafeBinaryOp "*"
abs = unsafeFunction "abs"
signum = unsafeFunction "sign"
fromInteger
= UnsafeExpression
. fromString
. show
instance (ty `In` PGNum, ty `In` PGFloating) => Fractional
(Expression outer commons grp schemas params from (null ty)) where
(/) = unsafeBinaryOp "/"
fromRational
= UnsafeExpression
. fromString
. ($ "")
. showFFloat Nothing
. fromRat @Double
instance (ty `In` PGNum, ty `In` PGFloating) => Floating
(Expression outer commons grp schemas params from (null ty)) where
pi = UnsafeExpression "pi()"
exp = unsafeFunction "exp"
log = unsafeFunction "ln"
sqrt = unsafeFunction "sqrt"
b ** x = UnsafeExpression $
"power(" <> renderSQL b <> ", " <> renderSQL x <> ")"
logBase b y = log y / log b
sin = unsafeFunction "sin"
cos = unsafeFunction "cos"
tan = unsafeFunction "tan"
asin = unsafeFunction "asin"
acos = unsafeFunction "acos"
atan = unsafeFunction "atan"
sinh x = (exp x - exp (-x)) / 2
cosh x = (exp x + exp (-x)) / 2
tanh x = sinh x / cosh x
asinh x = log (x + sqrt (x*x + 1))
acosh x = log (x + sqrt (x*x - 1))
atanh x = log ((1 + x) / (1 - x)) / 2
class PGSubset container where
(@>) :: Operator (null0 container) (null1 container) ('Null 'PGbool)
(@>) = unsafeBinaryOp "@>"
(<@) :: Operator (null0 container) (null1 container) ('Null 'PGbool)
(<@) = unsafeBinaryOp "<@"
instance PGSubset 'PGjsonb
instance PGSubset 'PGtsquery
instance PGSubset ('PGvararray ty)
instance IsString
(Expression outer commons grp schemas params from (null 'PGtext)) where
fromString str = UnsafeExpression $
"E\'" <> fromString (escape =<< str) <> "\'"
instance IsString
(Expression outer commons grp schemas params from (null 'PGtsvector)) where
fromString str = UnsafeExpression . parenthesized . (<> " :: tsvector") $
"E\'" <> fromString (escape =<< str) <> "\'"
instance IsString
(Expression outer commons grp schemas params from (null 'PGtsquery)) where
fromString str = UnsafeExpression . parenthesized . (<> " :: tsquery") $
"E\'" <> fromString (escape =<< str) <> "\'"
instance Semigroup
(Expression outer commons grp schemas params from (null ('PGvararray ty))) where
(<>) = unsafeBinaryOp "||"
instance Semigroup
(Expression outer commons grp schemas params from (null 'PGjsonb)) where
(<>) = unsafeBinaryOp "||"
instance Semigroup
(Expression outer commons grp schemas params from (null 'PGtext)) where
(<>) = unsafeBinaryOp "||"
instance Semigroup
(Expression outer commons grp schemas params from (null 'PGtsvector)) where
(<>) = unsafeBinaryOp "||"
instance Monoid
(Expression outer commons grp schemas params from (null 'PGtext)) where
mempty = fromString ""
mappend = (<>)
instance Monoid
(Expression outer commons grp schemas params from (null 'PGtsvector)) where
mempty = fromString ""
mappend = (<>)