esqueleto-compat-0.0.2.0: Compatibility operators for Persistent and Esqueleto
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Esqueleto.Compat.Operators

Synopsis

Documentation

class SqlAssignment a b c where Source #

A class for assigning a value in SQL, shared among the persistent and esqueleto libraries.

Methods

(=.) :: a -> b -> c infixr 3 Source #

(-=.) :: a -> b -> c Source #

(+=.) :: a -> b -> c Source #

(*=.) :: a -> b -> c Source #

Instances

Instances details
(PersistField typ, field ~ EntityField rec typ', typ ~ typ') => SqlAssignment field typ (Update rec) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

(=.) :: field -> typ -> Update rec Source #

(-=.) :: field -> typ -> Update rec Source #

(+=.) :: field -> typ -> Update rec Source #

(*=.) :: field -> typ -> Update rec Source #

(PersistEntity rec, PersistField typ, field ~ EntityField rec typ) => SqlAssignment field (SqlExpr (Value typ)) (SqlExpr (Entity rec) -> SqlExpr Update) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

(=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(-=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(+=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

(*=.) :: field -> SqlExpr (Value typ) -> SqlExpr (Entity rec) -> SqlExpr Update Source #

class SqlBoolean a where Source #

A class for abstracting over Bool-like operations.

Irritatingly, we can't have not_ in here, because persistent actually doesn't have such a function! That's why the SqlBooleanNot class exists.

Methods

true_ :: a Source #

false_ :: a Source #

(||.) :: a -> a -> a infixr 2 Source #

(&&.) :: a -> a -> a infixr 3 Source #

Instances

Instances details
a ~ Bool => SqlBoolean (SqlExpr (Value a)) Source #

SqlExpr can be compared as SqlBoolean values, provided that they contain a Value Bool.

The implementation uses the (a ~ Bool) equality constraint so that polymorphic definitions don't get too confused.

Instance details

Defined in Database.Esqueleto.Compat.Operators

SqlBoolean [Filter k] Source #

This is a bit of a weird definition.

Turns out, ||. is very rarely used in the codebase - we actually have more uses of FilterOr! And there *isn't* a &&. in persistent at all.

Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

true_ :: [Filter k] Source #

false_ :: [Filter k] Source #

(||.) :: [Filter k] -> [Filter k] -> [Filter k] Source #

(&&.) :: [Filter k] -> [Filter k] -> [Filter k] Source #

class SqlBoolean a => SqlBooleanNot a where Source #

Methods

not_ :: a -> a Source #

Instances

Instances details
a ~ Bool => SqlBooleanNot (SqlExpr (Value a)) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

not_ :: SqlExpr (Value a) -> SqlExpr (Value a) Source #

(TypeError ('Text "`persistent` does not have a `not_` operator for filters. Instead, use the " :$$: 'Text "inverse operator, like `<.` instead of `>=.`.") :: Constraint) => SqlBooleanNot [Filter t] Source #

A TypeError instance is provided so that folks don't get too confused, though I doubt they'll run into this.

Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

not_ :: [Filter t] -> [Filter t] Source #

class SqlComparison a b c | c a -> b, c b -> a, a b -> c where Source #

A class for comparing for equality in persistent and esqueleto. The first two type parameters are the inputs to the binary operator, and the final one is the result type.

Methods

(==.) :: a -> b -> c infix 4 Source #

(!=.) :: a -> b -> c infix 4 Source #

(>.) :: a -> b -> c infix 4 Source #

(>=.) :: a -> b -> c infix 4 Source #

(<.) :: a -> b -> c infix 4 Source #

(<=.) :: a -> b -> c infix 4 Source #

Instances

Instances details
(PersistField a, a ~ b, lhs ~ SqlExpr (Value a), c ~ Bool) => SqlComparison (SqlExpr (Value a)) (SqlExpr (Value b)) (SqlExpr (Value c)) Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

(lhs ~ EntityField rec typ, PersistField typ, typ ~ typ', NotSqlExprEq rec typ typ', rec ~ rec') => SqlComparison (EntityField rec typ) typ' (Filter rec') Source # 
Instance details

Defined in Database.Esqueleto.Compat.Operators

Methods

(==.) :: EntityField rec typ -> typ' -> Filter rec' Source #

(!=.) :: EntityField rec typ -> typ' -> Filter rec' Source #

(>.) :: EntityField rec typ -> typ' -> Filter rec' Source #

(>=.) :: EntityField rec typ -> typ' -> Filter rec' Source #

(<.) :: EntityField rec typ -> typ' -> Filter rec' Source #

(<=.) :: EntityField rec typ -> typ' -> Filter rec' Source #

type family NotSqlExprEq rec typ' typ :: Constraint where ... Source #

Equations

NotSqlExprEq rec typ' (SqlExpr (Value _)) = TypeError (NotSqlExprEqMessage rec typ') 
NotSqlExprEq _ _ _ = () 

type NotSqlExprEqMessage rec typ = (((('Text "You used a bare `" :<>: 'ShowType (EntityField rec typ)) :<>: 'Text "` field.") :$$: 'Text "If you're writing a Persistent expression, you don't need to use `val`.") :$$: 'Text "If you're writing an esqueleto expression, you need to project from a ") :$$: 'Text "table variable, like: e ^. FooName" Source #

(/=.) :: SqlComparison a b c => a -> b -> c infix 4 Source #

An alias for !=., in keeping with the convention of having Haskell-ish operators.