{-# language DataKinds #-}
module Rel8.Expr.Text
(
(++.)
, (~.), (~*), (!~), (!~*)
, bitLength, charLength, lower, octetLength, upper
, ascii, btrim, chr, convert, convertFrom, convertTo, decode, encode
, initcap, left, length, lengthEncoding, lpad, ltrim, md5
, pgClientEncoding, quoteIdent, quoteLiteral, quoteNullable, regexpReplace
, regexpSplitToArray, repeat, replace, reverse, right, rpad, rtrim
, splitPart, strpos, substr, translate
)
where
import Data.Bool ( Bool )
import Data.Int ( Int32 )
import Data.Maybe ( Maybe( Nothing, Just ) )
import Prelude ()
import Data.ByteString ( ByteString )
import Rel8.Expr ( Expr )
import Rel8.Expr.Function ( binaryOperator, function, nullaryFunction )
import Data.Text (Text)
(++.) :: Expr Text -> Expr Text -> Expr Text
++. :: Expr Text -> Expr Text -> Expr Text
(++.) = String -> Expr Text -> Expr Text -> Expr Text
forall c a b. Sql DBType c => String -> Expr a -> Expr b -> Expr c
binaryOperator String
"||"
infixr 6 ++.
(~.) :: Expr Text -> Expr Text -> Expr Bool
~. :: Expr Text -> Expr Text -> Expr Bool
(~.) = String -> Expr Text -> Expr Text -> Expr Bool
forall c a b. Sql DBType c => String -> Expr a -> Expr b -> Expr c
binaryOperator String
"~."
infix 2 ~.
(~*) :: Expr Text -> Expr Text -> Expr Bool
~* :: Expr Text -> Expr Text -> Expr Bool
(~*) = String -> Expr Text -> Expr Text -> Expr Bool
forall c a b. Sql DBType c => String -> Expr a -> Expr b -> Expr c
binaryOperator String
"~*"
infix 2 ~*
(!~) :: Expr Text -> Expr Text -> Expr Bool
!~ :: Expr Text -> Expr Text -> Expr Bool
(!~) = String -> Expr Text -> Expr Text -> Expr Bool
forall c a b. Sql DBType c => String -> Expr a -> Expr b -> Expr c
binaryOperator String
"!~"
infix 2 !~
(!~*) :: Expr Text -> Expr Text -> Expr Bool
!~* :: Expr Text -> Expr Text -> Expr Bool
(!~*) = String -> Expr Text -> Expr Text -> Expr Bool
forall c a b. Sql DBType c => String -> Expr a -> Expr b -> Expr c
binaryOperator String
"!~*"
infix 2 !~*
bitLength :: Expr Text -> Expr Int32
bitLength :: Expr Text -> Expr Int32
bitLength = String -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"bit_length"
charLength :: Expr Text -> Expr Int32
charLength :: Expr Text -> Expr Int32
charLength = String -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"char_length"
lower :: Expr Text -> Expr Text
lower :: Expr Text -> Expr Text
lower = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"lower"
octetLength :: Expr Text -> Expr Int32
octetLength :: Expr Text -> Expr Int32
octetLength = String -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"octet_length"
upper :: Expr Text -> Expr Text
upper :: Expr Text -> Expr Text
upper = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"upper"
ascii :: Expr Text -> Expr Int32
ascii :: Expr Text -> Expr Int32
ascii = String -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"ascii"
btrim :: Expr Text -> Maybe (Expr Text) -> Expr Text
btrim :: Expr Text -> Maybe (Expr Text) -> Expr Text
btrim Expr Text
a (Just Expr Text
b) = String -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"btrim" Expr Text
a Expr Text
b
btrim Expr Text
a Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"btrim" Expr Text
a
chr :: Expr Int32 -> Expr Text
chr :: Expr Int32 -> Expr Text
chr = String -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"chr"
convert :: Expr ByteString -> Expr Text -> Expr Text -> Expr ByteString
convert :: Expr ByteString -> Expr Text -> Expr Text -> Expr ByteString
convert = String
-> Expr ByteString -> Expr Text -> Expr Text -> Expr ByteString
forall args result.
Function args result =>
String -> args -> result
function String
"convert"
convertFrom :: Expr ByteString -> Expr Text -> Expr Text
convertFrom :: Expr ByteString -> Expr Text -> Expr Text
convertFrom = String -> Expr ByteString -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"convert_from"
convertTo :: Expr Text -> Expr Text -> Expr ByteString
convertTo :: Expr Text -> Expr Text -> Expr ByteString
convertTo = String -> Expr Text -> Expr Text -> Expr ByteString
forall args result.
Function args result =>
String -> args -> result
function String
"convert_to"
decode :: Expr Text -> Expr Text -> Expr ByteString
decode :: Expr Text -> Expr Text -> Expr ByteString
decode = String -> Expr Text -> Expr Text -> Expr ByteString
forall args result.
Function args result =>
String -> args -> result
function String
"decode"
encode :: Expr ByteString -> Expr Text -> Expr Text
encode :: Expr ByteString -> Expr Text -> Expr Text
encode = String -> Expr ByteString -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"encode"
initcap :: Expr Text -> Expr Text
initcap :: Expr Text -> Expr Text
initcap = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"initcap"
left :: Expr Text -> Expr Int32 -> Expr Text
left :: Expr Text -> Expr Int32 -> Expr Text
left = String -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"left"
length :: Expr Text -> Expr Int32
length :: Expr Text -> Expr Int32
length = String -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"length"
lengthEncoding :: Expr ByteString -> Expr Text -> Expr Int32
lengthEncoding :: Expr ByteString -> Expr Text -> Expr Int32
lengthEncoding = String -> Expr ByteString -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"length"
lpad :: Expr Text -> Expr Int32 -> Maybe (Expr Text) -> Expr Text
lpad :: Expr Text -> Expr Int32 -> Maybe (Expr Text) -> Expr Text
lpad Expr Text
a Expr Int32
b (Just Expr Text
c) = String -> Expr Text -> Expr Int32 -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"lpad" Expr Text
a Expr Int32
b Expr Text
c
lpad Expr Text
a Expr Int32
b Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"lpad" Expr Text
a Expr Int32
b
ltrim :: Expr Text -> Maybe (Expr Text) -> Expr Text
ltrim :: Expr Text -> Maybe (Expr Text) -> Expr Text
ltrim Expr Text
a (Just Expr Text
b) = String -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"ltrim" Expr Text
a Expr Text
b
ltrim Expr Text
a Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"ltrim" Expr Text
a
md5 :: Expr Text -> Expr Text
md5 :: Expr Text -> Expr Text
md5 = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"md5"
pgClientEncoding :: Expr Text
pgClientEncoding :: Expr Text
pgClientEncoding = String -> Expr Text
forall a. Sql DBType a => String -> Expr a
nullaryFunction String
"pg_client_encoding"
quoteIdent :: Expr Text -> Expr Text
quoteIdent :: Expr Text -> Expr Text
quoteIdent = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"quote_ident"
quoteLiteral :: Expr Text -> Expr Text
quoteLiteral :: Expr Text -> Expr Text
quoteLiteral = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"quote_literal"
quoteNullable :: Expr Text -> Expr Text
quoteNullable :: Expr Text -> Expr Text
quoteNullable = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"quote_nullable"
regexpReplace :: ()
=> Expr Text -> Expr Text -> Expr Text -> Maybe (Expr Text) -> Expr Text
regexpReplace :: Expr Text
-> Expr Text -> Expr Text -> Maybe (Expr Text) -> Expr Text
regexpReplace Expr Text
a Expr Text
b Expr Text
c (Just Expr Text
d) = String
-> Expr Text -> Expr Text -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"regexp_replace" Expr Text
a Expr Text
b Expr Text
c Expr Text
d
regexpReplace Expr Text
a Expr Text
b Expr Text
c Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"regexp_replace" Expr Text
a Expr Text
b Expr Text
c
regexpSplitToArray :: ()
=> Expr Text -> Expr Text -> Maybe (Expr Text) -> Expr [Text]
regexpSplitToArray :: Expr Text -> Expr Text -> Maybe (Expr Text) -> Expr [Text]
regexpSplitToArray Expr Text
a Expr Text
b (Just Expr Text
c) = String -> Expr Text -> Expr Text -> Expr Text -> Expr [Text]
forall args result.
Function args result =>
String -> args -> result
function String
"regexp_split_to_array" Expr Text
a Expr Text
b Expr Text
c
regexpSplitToArray Expr Text
a Expr Text
b Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Text -> Expr [Text]
forall args result.
Function args result =>
String -> args -> result
function String
"regexp_split_to_array" Expr Text
a Expr Text
b
repeat :: Expr Text -> Expr Int32 -> Expr Text
repeat :: Expr Text -> Expr Int32 -> Expr Text
repeat = String -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"repeat"
replace :: Expr Text -> Expr Text -> Expr Text -> Expr Text
replace :: Expr Text -> Expr Text -> Expr Text -> Expr Text
replace = String -> Expr Text -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"replace"
reverse :: Expr Text -> Expr Text
reverse :: Expr Text -> Expr Text
reverse = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"reverse"
right :: Expr Text -> Expr Int32 -> Expr Text
right :: Expr Text -> Expr Int32 -> Expr Text
right = String -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"right"
rpad :: Expr Text -> Expr Int32 -> Maybe (Expr Text) -> Expr Text
rpad :: Expr Text -> Expr Int32 -> Maybe (Expr Text) -> Expr Text
rpad Expr Text
a Expr Int32
b (Just Expr Text
c) = String -> Expr Text -> Expr Int32 -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"rpad" Expr Text
a Expr Int32
b Expr Text
c
rpad Expr Text
a Expr Int32
b Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"rpad" Expr Text
a Expr Int32
b
rtrim :: Expr Text -> Maybe (Expr Text) -> Expr Text
rtrim :: Expr Text -> Maybe (Expr Text) -> Expr Text
rtrim Expr Text
a (Just Expr Text
b) = String -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"rtrim" Expr Text
a Expr Text
b
rtrim Expr Text
a Maybe (Expr Text)
Nothing = String -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"rtrim" Expr Text
a
splitPart :: Expr Text -> Expr Text -> Expr Int32 -> Expr Text
splitPart :: Expr Text -> Expr Text -> Expr Int32 -> Expr Text
splitPart = String -> Expr Text -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"split_part"
strpos :: Expr Text -> Expr Text -> Expr Int32
strpos :: Expr Text -> Expr Text -> Expr Int32
strpos = String -> Expr Text -> Expr Text -> Expr Int32
forall args result.
Function args result =>
String -> args -> result
function String
"strpos"
substr :: Expr Text -> Expr Int32 -> Maybe (Expr Int32) -> Expr Text
substr :: Expr Text -> Expr Int32 -> Maybe (Expr Int32) -> Expr Text
substr Expr Text
a Expr Int32
b (Just Expr Int32
c) = String -> Expr Text -> Expr Int32 -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"substr" Expr Text
a Expr Int32
b Expr Int32
c
substr Expr Text
a Expr Int32
b Maybe (Expr Int32)
Nothing = String -> Expr Text -> Expr Int32 -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"substr" Expr Text
a Expr Int32
b
translate :: Expr Text -> Expr Text -> Expr Text -> Expr Text
translate :: Expr Text -> Expr Text -> Expr Text -> Expr Text
translate = String -> Expr Text -> Expr Text -> Expr Text -> Expr Text
forall args result.
Function args result =>
String -> args -> result
function String
"translate"