module Database.Beam.Query.Operator
( SqlBool
, (&&.), (||.), not_, div_, mod_
, (&&?.), (||?.), sqlNot_
, like_, similarTo_
, concat_
) where
import Database.Beam.Backend.SQL
import Database.Beam.Query.Internal
import Control.Applicative
import qualified Data.Text as T
data SqlBool
(&&.) :: BeamSqlBackend be
=> QGenExpr context be s Bool
-> QGenExpr context be s Bool
-> QGenExpr context be s Bool
(&&.) = qBinOpE andE
(||.) :: BeamSqlBackend be
=> QGenExpr context be s Bool
-> QGenExpr context be s Bool
-> QGenExpr context be
s Bool
(||.) = qBinOpE orE
(&&?.) :: BeamSqlBackend be
=> QGenExpr context be s SqlBool
-> QGenExpr context be s SqlBool
-> QGenExpr context be s SqlBool
(&&?.) = qBinOpE andE
(||?.) :: BeamSqlBackend be
=> QGenExpr context be s SqlBool
-> QGenExpr context be s SqlBool
-> QGenExpr context be s SqlBool
(||?.) = qBinOpE orE
infixr 3 &&., &&?.
infixr 2 ||., ||?.
like_ :: ( BeamSqlBackendIsString be text
, BeamSqlBackend be )
=> QGenExpr ctxt be s text -> QGenExpr ctxt be s text -> QGenExpr ctxt be s Bool
like_ (QExpr scrutinee) (QExpr search) =
QExpr (liftA2 likeE scrutinee search)
similarTo_ :: ( BeamSqlBackendIsString be text
, BeamSql99ExpressionBackend be )
=> QGenExpr ctxt be s text -> QGenExpr ctxt be s text -> QGenExpr ctxt be s text
similarTo_ (QExpr scrutinee) (QExpr search) =
QExpr (liftA2 similarToE scrutinee search)
infix 4 `like_`, `similarTo_`
not_ :: forall be context s
. BeamSqlBackend be
=> QGenExpr context be s Bool
-> QGenExpr context be s Bool
not_ (QExpr a) = QExpr (fmap notE a)
sqlNot_ :: forall be context s
. BeamSqlBackend be
=> QGenExpr context be s SqlBool
-> QGenExpr context be s SqlBool
sqlNot_ (QExpr a) = QExpr (fmap notE a)
div_ :: (Integral a, BeamSqlBackend be)
=> QGenExpr context be s a -> QGenExpr context be s a
-> QGenExpr context be s a
div_ = qBinOpE divE
infixl 7 `div_`, `mod_`
mod_ :: (Integral a, BeamSqlBackend be)
=> QGenExpr context be s a -> QGenExpr context be s a
-> QGenExpr context be s a
mod_ = qBinOpE modE
concat_ :: BeamSql99ConcatExpressionBackend be
=> [ QGenExpr context be s T.Text ] -> QGenExpr context be s T.Text
concat_ es = QExpr (concatE <$> mapM (\(QExpr e) -> e) es)