{-# LANGUAGE
DataKinds
, OverloadedStrings
, RankNTypes
, ScopedTypeVariables
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.Text
(
lower
, upper
, charLength
, like
, ilike
, replace
, strpos
) where
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Type.Schema
lower :: null 'PGtext --> null 'PGtext
lower :: Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
lower = ByteString -> null 'PGtext --> null 'PGtext
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"lower"
upper :: null 'PGtext --> null 'PGtext
upper :: Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGtext)
upper = ByteString -> null 'PGtext --> null 'PGtext
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"upper"
charLength :: null 'PGtext --> null 'PGint4
charLength :: Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from (null 'PGint4)
charLength = ByteString -> null 'PGtext --> null 'PGint4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"char_length"
like :: Operator (null 'PGtext) (null 'PGtext) ('Null 'PGbool)
like :: 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 'PGbool)
like = ByteString
-> Operator (null 'PGtext) (null 'PGtext) ('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"LIKE"
ilike :: Operator (null 'PGtext) (null 'PGtext) ('Null 'PGbool)
ilike :: 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 'PGbool)
ilike = ByteString
-> Operator (null 'PGtext) (null 'PGtext) ('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"ILIKE"
strpos
:: '[null 'PGtext, null 'PGtext] ---> null 'PGint4
strpos :: NP
(Expression grp lat with db params from)
'[null 'PGtext, null 'PGtext]
-> Expression grp lat with db params from (null 'PGint4)
strpos = ByteString -> '[null 'PGtext, null 'PGtext] ---> null 'PGint4
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"strpos"
replace
:: '[ null 'PGtext, null 'PGtext, null 'PGtext ] ---> null 'PGtext
replace :: NP
(Expression grp lat with db params from)
'[null 'PGtext, null 'PGtext, null 'PGtext]
-> Expression grp lat with db params from (null 'PGtext)
replace = ByteString
-> '[null 'PGtext, null 'PGtext, null 'PGtext] ---> null 'PGtext
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"replace"