Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Database.Persist.Sql.Lifted.Expression.Type
Synopsis
- data SqlExpr a
Documentation
An expression on the SQL backend.
Raw expression: Contains a SqlExprMeta
and a function for
building the expr. It recieves a parameter telling it whether
it is in a parenthesized context, and takes information about the SQL
connection (mainly for escaping names) and returns both an
string (Builder
) and a list of values to be
interpolated by the SQL backend.
Instances
(TypeError SqlExprFunctorMessage :: Constraint) => Functor SqlExpr | Folks often want the ability to promote a Haskell function into the
fmap :: (a -> b) -> This type signature is making a pretty strong claim: "Give me a Haskell
function from Let's suppose we *could* do this - This is why If you do have a SQL function, then you can provide a safe type and introduce
it with Since: esqueleto-3.5.8.2 |
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ)) | This instance allows you to use Example: -- persistent model: BlogPost authorId PersonId title Text -- query: This is exactly equivalent to the following: blogPost :: SqlExpr (Entity BlogPost) blogPost ^. BlogPostTitle blogPost ^. #title blogPost.title There's another instance defined on Since: esqueleto-3.5.4.0 |
(PersistEntity rec, PersistField typ, PersistField typ', SymbolToField sym rec typ, NullableFieldProjection typ typ', HasField sym (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ')))) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ'))) | This instance allows you to use Example: -- persistent model: Person name Text BlogPost title Text authorId PersonId -- query: The following forms are all equivalent: blogPost :: SqlExpr (Maybe (Entity BlogPost)) blogPost ?. BlogPostTitle blogPost ?. #title blogPost.title Since: esqueleto-3.5.4.0 |
(ToFrom a a', SqlSelect b r, ToAlias b, ToAliasReference b, d ~ (a' :& b)) => DoInnerJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d | |
Defined in Database.Esqueleto.Experimental.From.Join | |
(ToFrom a a', ToMaybe b, d ~ (a' :& ToMaybeT b), SqlSelect b r, ToAlias b, ToAliasReference b) => DoLeftJoin Lateral a (a' -> SqlQuery b, d -> SqlExpr (Value Bool)) d | |
Defined in Database.Esqueleto.Experimental.From.Join | |
ToAlias (SqlExpr (Value a)) | |
ToAlias (SqlExpr (Entity a)) | |
ToAlias (SqlExpr (Maybe (Entity a))) | |
ToAliasReference (SqlExpr (Value a)) | |
ToAliasReference (SqlExpr (Entity a)) | |
ToAliasReference (SqlExpr (Maybe (Entity a))) | |
ToMaybe (SqlExpr (Value a)) | |
ToMaybe (SqlExpr (Entity a)) | |
ToMaybe (SqlExpr (Maybe a)) | |
FromPreprocess (SqlExpr (Entity val)) => From (SqlExpr (Entity val)) | |
FromPreprocess (SqlExpr (Maybe (Entity val))) => From (SqlExpr (Maybe (Entity val))) | |
(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) | |
Defined in Database.Esqueleto.Internal.Internal Methods fromPreprocess :: SqlQuery (PreprocessedFrom (SqlExpr (Entity val))) # | |
(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) | |
Defined in Database.Esqueleto.Internal.Internal Methods fromPreprocess :: SqlQuery (PreprocessedFrom (SqlExpr (Maybe (Entity val)))) # | |
PersistEntity val => LockableEntity (SqlExpr (Entity val)) | |
Defined in Database.Esqueleto.Internal.Internal Methods flattenLockableEntity :: SqlExpr (Entity val) -> NonEmpty LockableSqlExpr # | |
ToSomeValues (SqlExpr (Value a)) | |
Defined in Database.Esqueleto.Internal.Internal Methods toSomeValues :: SqlExpr (Value a) -> [SomeValue] # | |
a ~ Value b => UnsafeSqlFunctionArgument (SqlExpr a) | |
PersistEntity ent => ToFrom (Table ent) (SqlExpr (Entity ent)) | |
PersistEntity e => SqlSelect (SqlExpr (Insertion e)) (Insertion e) |
|
Defined in Database.Esqueleto.Internal.Internal Methods sqlSelectCols :: IdentInfo -> SqlExpr (Insertion e) -> (Builder, [PersistValue]) # sqlSelectColCount :: Proxy (SqlExpr (Insertion e)) -> Int # sqlSelectProcessRow :: [PersistValue] -> Either Text (Insertion e) # sqlInsertInto :: IdentInfo -> SqlExpr (Insertion e) -> (Builder, [PersistValue]) # | |
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) | You may return any single value (i.e. a single column) from
a |
Defined in Database.Esqueleto.Internal.Internal Methods sqlSelectCols :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) # sqlSelectColCount :: Proxy (SqlExpr (Value a)) -> Int # sqlSelectProcessRow :: [PersistValue] -> Either Text (Value a) # sqlInsertInto :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) # | |
PersistEntity a => SqlSelect (SqlExpr (Entity a)) (Entity a) | |
Defined in Database.Esqueleto.Internal.Internal Methods sqlSelectCols :: IdentInfo -> SqlExpr (Entity a) -> (Builder, [PersistValue]) # sqlSelectColCount :: Proxy (SqlExpr (Entity a)) -> Int # sqlSelectProcessRow :: [PersistValue] -> Either Text (Entity a) # sqlInsertInto :: IdentInfo -> SqlExpr (Entity a) -> (Builder, [PersistValue]) # | |
PersistEntity a => SqlSelect (SqlExpr (Maybe (Entity a))) (Maybe (Entity a)) | |
Defined in Database.Esqueleto.Internal.Internal Methods sqlSelectCols :: IdentInfo -> SqlExpr (Maybe (Entity a)) -> (Builder, [PersistValue]) # sqlSelectColCount :: Proxy (SqlExpr (Maybe (Entity a))) -> Int # sqlSelectProcessRow :: [PersistValue] -> Either Text (Maybe (Entity a)) # sqlInsertInto :: IdentInfo -> SqlExpr (Maybe (Entity a)) -> (Builder, [PersistValue]) # | |
type ToMaybeT (SqlExpr (Value a)) | |
type ToMaybeT (SqlExpr (Entity a)) | |
type ToMaybeT (SqlExpr (Maybe a)) | |