Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This is an internal module, anything exported by this module may change without a major version bump. Please use only Database.Esqueleto if possible.
If you use this module, please report what your use case is on the issue tracker so we can safely support it.
Synopsis
- fromStart :: forall a. (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (PreprocessedFrom (SqlExpr (Entity a)))
- newtype DBName = DBName {}
- fromStartMaybe :: (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (PreprocessedFrom (SqlExpr (Maybe (Entity a))))
- fromJoin :: IsJoinKind join => PreprocessedFrom a -> PreprocessedFrom b -> SqlQuery (PreprocessedFrom (join a b))
- fromFinish :: PreprocessedFrom a -> SqlQuery a
- where_ :: SqlExpr (Value Bool) -> SqlQuery ()
- on :: SqlExpr (Value Bool) -> SqlQuery ()
- groupBy :: ToSomeValues a => a -> SqlQuery ()
- orderBy :: [SqlExpr OrderBy] -> SqlQuery ()
- asc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- desc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy
- orderByExpr :: Builder -> SqlExpr (Value a) -> SqlExpr OrderBy
- limit :: Int64 -> SqlQuery ()
- offset :: Int64 -> SqlQuery ()
- distinct :: SqlQuery a -> SqlQuery a
- distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a
- don :: SqlExpr (Value a) -> SqlExpr DistinctOn
- distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a
- rand :: SqlExpr OrderBy
- having :: SqlExpr (Value Bool) -> SqlQuery ()
- locking :: LockingKind -> SqlQuery ()
- sub_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a)
- subSelect :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value (Maybe a))
- subSelectMaybe :: PersistField a => SqlQuery (SqlExpr (Value (Maybe a))) -> SqlExpr (Value (Maybe a))
- subSelectCount :: (Num a, PersistField a) => SqlQuery ignored -> SqlExpr (Value a)
- subSelectList :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a)
- subSelectForeign :: (BackendCompatible SqlBackend (PersistEntityBackend val1), PersistEntity val1, PersistEntity val2, PersistField a) => SqlExpr (Entity val2) -> EntityField val2 (Key val1) -> (SqlExpr (Entity val1) -> SqlExpr (Value a)) -> SqlExpr (Value a)
- subSelectUnsafe :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a)
- (^.) :: forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
- withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a
- (?.) :: (PersistEntity val, PersistField typ) => SqlExpr (Maybe (Entity val)) -> EntityField val typ -> SqlExpr (Value (Maybe typ))
- val :: PersistField typ => typ -> SqlExpr (Value typ)
- isNothing :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool)
- just :: SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ))
- nothing :: SqlExpr (Value (Maybe typ))
- joinV :: SqlExpr (Value (Maybe (Maybe typ))) -> SqlExpr (Value (Maybe typ))
- countHelper :: Num a => Builder -> Builder -> SqlExpr (Value typ) -> SqlExpr (Value a)
- countRows :: Num a => SqlExpr (Value a)
- count :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a)
- countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a)
- not_ :: SqlExpr (Value Bool) -> SqlExpr (Value Bool)
- (==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (>=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (>.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (<=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (<.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (!=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
- (&&.) :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
- (||.) :: SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
- (+.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- (-.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- (/.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- (*.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a)
- between :: PersistField a => SqlExpr (Value a) -> (SqlExpr (Value a), SqlExpr (Value a)) -> SqlExpr (Value Bool)
- random_ :: (PersistField a, Num a) => SqlExpr (Value a)
- round_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- ceiling_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- floor_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- sum_ :: (PersistField a, PersistField b) => SqlExpr (Value a) -> SqlExpr (Value (Maybe b))
- min_ :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value (Maybe a))
- max_ :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value (Maybe a))
- avg_ :: (PersistField a, PersistField b) => SqlExpr (Value a) -> SqlExpr (Value (Maybe b))
- castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (Value b)
- castNumM :: (Num a, Num b) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b))
- coalesce :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value (Maybe a))
- coalesceDefault :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a)
- lower_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s)
- upper_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s)
- trim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s)
- rtrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s)
- ltrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s)
- length_ :: (SqlString s, Num a) => SqlExpr (Value s) -> SqlExpr (Value a)
- left_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s)
- right_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s)
- like :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool)
- ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool)
- (%) :: SqlString s => SqlExpr (Value s)
- concat_ :: SqlString s => [SqlExpr (Value s)] -> SqlExpr (Value s)
- (++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value s)
- castString :: (SqlString s, SqlString r) => SqlExpr (Value s) -> SqlExpr (Value r)
- subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a)
- valList :: PersistField typ => [typ] -> SqlExpr (ValueList typ)
- justList :: SqlExpr (ValueList typ) -> SqlExpr (ValueList (Maybe typ))
- in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
- notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
- exists :: SqlQuery () -> SqlExpr (Value Bool)
- notExists :: SqlQuery () -> SqlExpr (Value Bool)
- set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
- (=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
- (+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update
- (-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update
- (*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update
- (/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update
- (<#) :: (a -> b) -> SqlExpr (Value a) -> SqlExpr (Insertion b)
- (<&>) :: SqlExpr (Insertion (a -> b)) -> SqlExpr (Value a) -> SqlExpr (Insertion b)
- case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a)
- toBaseId :: ToBaseId ent => SqlExpr (Value (Key ent)) -> SqlExpr (Value (Key (BaseEnt ent)))
- when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a)
- then_ :: ()
- else_ :: expr a -> expr a
- newtype Value a = Value {
- unValue :: a
- newtype ValueList a = ValueList a
- data SomeValue where
- class ToSomeValues a where
- toSomeValues :: a -> [SomeValue]
- type family KnowResult a where ...
- class FinalResult a where
- finalR :: a -> KnowResult a
- toUniqueDef :: forall a val. (KnowResult a ~ Unique val, PersistEntity val, FinalResult a) => a -> UniqueDef
- renderUpdates :: BackendCompatible SqlBackend backend => backend -> [SqlExpr (Entity val) -> SqlExpr Update] -> (Builder, [PersistValue])
- data InnerJoin a b = a `InnerJoin` b
- data CrossJoin a b = a `CrossJoin` b
- data LeftOuterJoin a b = a `LeftOuterJoin` b
- data RightOuterJoin a b = a `RightOuterJoin` b
- data FullOuterJoin a b = a `FullOuterJoin` b
- data JoinKind
- class IsJoinKind join where
- smartJoin :: a -> b -> join a b
- reifyJoinKind :: join a b -> JoinKind
- data OnClauseWithoutMatchingJoinException = OnClauseWithoutMatchingJoinException String
- data OrderBy
- data DistinctOn
- data Update
- data Insertion a
- data LockingKind
- class PersistField a => SqlString a
- class ToBaseId ent where
- from :: From a => (a -> SqlQuery b) -> SqlQuery b
- class From a where
- class FromPreprocess a where
- data EsqueletoError
- data UnexpectedValueError
- type CompositeKeyError = UnexpectedValueError
- data UnexpectedCaseError
- data SqlBinOpCompositeError
- newtype SqlQuery a = Q {
- unQ :: WriterT SideData (State IdentState) a
- type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend)
- data SideData = SideData {
- sdDistinctClause :: !DistinctClause
- sdFromClause :: ![FromClause]
- sdSetClause :: ![SetClause]
- sdWhereClause :: !WhereClause
- sdGroupByClause :: !GroupByClause
- sdHavingClause :: !HavingClause
- sdOrderByClause :: ![OrderByClause]
- sdLimitClause :: !LimitClause
- sdLockingClause :: !LockingClause
- sdCteClause :: ![CommonTableExpressionClause]
- data DistinctClause
- data FromClause
- = FromStart Ident EntityDef
- | FromJoin FromClause JoinKind FromClause (Maybe (SqlExpr (Value Bool)))
- | OnClause (SqlExpr (Value Bool))
- | FromRaw (NeedParens -> IdentInfo -> (Builder, [PersistValue]))
- data CommonTableExpressionKind
- data CommonTableExpressionClause = CommonTableExpressionClause CommonTableExpressionKind Ident (IdentInfo -> (Builder, [PersistValue]))
- data SubQueryType
- collectIdents :: FromClause -> Set Ident
- newtype SetClause = SetClause (SqlExpr Update)
- collectOnClauses :: SqlBackend -> [FromClause] -> Either (SqlExpr (Value Bool)) [FromClause]
- data WhereClause
- newtype GroupByClause = GroupBy [SomeValue]
- type HavingClause = WhereClause
- type OrderByClause = SqlExpr OrderBy
- data LimitClause = Limit (Maybe Int64) (Maybe Int64)
- type LockingClause = Last LockingKind
- newtype Ident = I Text
- newtype IdentState = IdentState {}
- initialIdentState :: IdentState
- newIdentFor :: DBName -> SqlQuery Ident
- type IdentInfo = (SqlBackend, IdentState)
- useIdent :: IdentInfo -> Ident -> Builder
- data SqlExprMeta = SqlExprMeta {}
- noMeta :: SqlExprMeta
- hasCompositeKeyMeta :: SqlExprMeta -> Bool
- entityAsValue :: SqlExpr (Entity val) -> SqlExpr (Value (Entity val))
- entityAsValueMaybe :: SqlExpr (Maybe (Entity val)) -> SqlExpr (Value (Maybe (Entity val)))
- data SqlExpr a = ERaw SqlExprMeta (NeedParens -> IdentInfo -> (Builder, [PersistValue]))
- data PreprocessedFrom a = PreprocessedFrom a FromClause
- data InsertFinal
- data NeedParens
- parensM :: NeedParens -> Builder -> Builder
- data OrderByType
- fieldName :: (PersistEntity val, PersistField typ) => IdentInfo -> EntityField val typ -> Builder
- setAux :: (PersistEntity val, PersistField typ) => EntityField val typ -> (SqlExpr (Entity val) -> SqlExpr (Value typ)) -> SqlExpr (Entity val) -> SqlExpr Update
- sub :: PersistField a => Mode -> SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a)
- fromDBName :: IdentInfo -> DBName -> Builder
- existsHelper :: SqlQuery () -> SqlExpr (Value Bool)
- unsafeSqlCase :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a)
- unsafeSqlBinOp :: Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c)
- unsafeSqlBinOpComposite :: Builder -> Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c)
- unsafeSqlValue :: Builder -> SqlExpr (Value a)
- unsafeSqlEntity :: PersistEntity ent => Ident -> SqlExpr (Entity ent)
- valueToFunctionArg :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue])
- unsafeSqlFunction :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b)
- unsafeSqlExtractSubField :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b)
- unsafeSqlFunctionParens :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b)
- unsafeSqlCastAs :: Text -> SqlExpr (Value a) -> SqlExpr (Value b)
- class UnsafeSqlFunctionArgument a where
- veryUnsafeCoerceSqlExprValue :: SqlExpr (Value a) -> SqlExpr (Value b)
- veryUnsafeCoerceSqlExprValueList :: SqlExpr (ValueList a) -> SqlExpr (Value a)
- rawSelectSource :: (SqlSelect a r, MonadIO m1, MonadIO m2, SqlBackendCanRead backend) => Mode -> SqlQuery a -> ReaderT backend m1 (Acquire (ConduitT () r m2 ()))
- selectSource :: (SqlSelect a r, BackendCompatible SqlBackend backend, IsPersistBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend, MonadResource m) => SqlQuery a -> ConduitT () r (ReaderT backend m) ()
- select :: (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m [r]
- selectOne :: (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m (Maybe r)
- runSource :: Monad m => ConduitT () r (ReaderT backend m) () -> ReaderT backend m [r]
- rawEsqueleto :: (MonadIO m, SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> SqlQuery a -> ReaderT backend m Int64
- delete :: (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m ()
- deleteCount :: (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m Int64
- update :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m ()
- updateCount :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m Int64
- builderToText :: Builder -> Text
- toRawSql :: (SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue])
- renderQueryToText :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => Mode -> SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQuerySelect :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQueryDelete :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQueryUpdate :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- renderQueryInsertInto :: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) => SqlQuery a -> ReaderT backend m (Text, [PersistValue])
- data Mode
- = SELECT
- | DELETE
- | UPDATE
- | INSERT_INTO
- uncommas :: [Builder] -> Builder
- intersperseB :: Builder -> [Builder] -> Builder
- uncommas' :: Monoid a => [(Builder, a)] -> (Builder, a)
- makeCte :: IdentInfo -> [CommonTableExpressionClause] -> (Builder, [PersistValue])
- makeInsertInto :: SqlSelect a r => IdentInfo -> Mode -> a -> (Builder, [PersistValue])
- makeSelect :: SqlSelect a r => IdentInfo -> Mode -> DistinctClause -> a -> (Builder, [PersistValue])
- makeFrom :: IdentInfo -> Mode -> [FromClause] -> (Builder, [PersistValue])
- makeSet :: IdentInfo -> [SetClause] -> (Builder, [PersistValue])
- makeWhere :: IdentInfo -> WhereClause -> (Builder, [PersistValue])
- makeGroupBy :: IdentInfo -> GroupByClause -> (Builder, [PersistValue])
- makeHaving :: IdentInfo -> WhereClause -> (Builder, [PersistValue])
- makeOrderByNoNewline :: IdentInfo -> [OrderByClause] -> (Builder, [PersistValue])
- makeOrderBy :: IdentInfo -> [OrderByClause] -> (Builder, [PersistValue])
- makeLimit :: IdentInfo -> LimitClause -> (Builder, [PersistValue])
- makeLocking :: LockingClause -> (Builder, [PersistValue])
- parens :: Builder -> Builder
- aliasedEntityColumnIdent :: Ident -> FieldDef -> Ident
- aliasedColumnName :: Ident -> IdentInfo -> Text -> Builder
- class SqlSelect a r | a -> r, r -> a where
- sqlSelectCols :: IdentInfo -> a -> (Builder, [PersistValue])
- sqlSelectColCount :: Proxy a -> Int
- sqlSelectProcessRow :: [PersistValue] -> Either Text r
- sqlInsertInto :: IdentInfo -> a -> (Builder, [PersistValue])
- unescapedColumnNames :: EntityDef -> [DBName]
- getEntityVal :: Proxy (SqlExpr (Entity a)) -> Proxy a
- materializeExpr :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue])
- from3P :: Proxy (a, b, c) -> Proxy ((a, b), c)
- from3 :: (a, b, c) -> ((a, b), c)
- to3 :: ((a, b), c) -> (a, b, c)
- from4P :: Proxy (a, b, c, d) -> Proxy ((a, b), (c, d))
- from4 :: (a, b, c, d) -> ((a, b), (c, d))
- to4 :: ((a, b), (c, d)) -> (a, b, c, d)
- from5P :: Proxy (a, b, c, d, e) -> Proxy ((a, b), (c, d), e)
- from5 :: (a, b, c, d, e) -> ((a, b), (c, d), e)
- to5 :: ((a, b), (c, d), e) -> (a, b, c, d, e)
- from6P :: Proxy (a, b, c, d, e, f) -> Proxy ((a, b), (c, d), (e, f))
- from6 :: (a, b, c, d, e, f) -> ((a, b), (c, d), (e, f))
- to6 :: ((a, b), (c, d), (e, f)) -> (a, b, c, d, e, f)
- from7P :: Proxy (a, b, c, d, e, f, g) -> Proxy ((a, b), (c, d), (e, f), g)
- from7 :: (a, b, c, d, e, f, g) -> ((a, b), (c, d), (e, f), g)
- to7 :: ((a, b), (c, d), (e, f), g) -> (a, b, c, d, e, f, g)
- from8P :: Proxy (a, b, c, d, e, f, g, h) -> Proxy ((a, b), (c, d), (e, f), (g, h))
- from8 :: (a, b, c, d, e, f, g, h) -> ((a, b), (c, d), (e, f), (g, h))
- to8 :: ((a, b), (c, d), (e, f), (g, h)) -> (a, b, c, d, e, f, g, h)
- from9P :: Proxy (a, b, c, d, e, f, g, h, i) -> Proxy ((a, b), (c, d), (e, f), (g, h), i)
- from9 :: (a, b, c, d, e, f, g, h, i) -> ((a, b), (c, d), (e, f), (g, h), i)
- to9 :: ((a, b), (c, d), (e, f), (g, h), i) -> (a, b, c, d, e, f, g, h, i)
- from10P :: Proxy (a, b, c, d, e, f, g, h, i, j) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j))
- from10 :: (a, b, c, d, e, f, g, h, i, j) -> ((a, b), (c, d), (e, f), (g, h), (i, j))
- to10 :: ((a, b), (c, d), (e, f), (g, h), (i, j)) -> (a, b, c, d, e, f, g, h, i, j)
- from11P :: Proxy (a, b, c, d, e, f, g, h, i, j, k) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), k)
- to11 :: ((a, b), (c, d), (e, f), (g, h), (i, j), k) -> (a, b, c, d, e, f, g, h, i, j, k)
- from12P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l))
- to12 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l)) -> (a, b, c, d, e, f, g, h, i, j, k, l)
- from13P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m)
- to13 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m)
- from14P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n))
- to14 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n)
- from15P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o)
- to15 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)
- from16P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p))
- to16 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)
- insertSelect :: (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m ()
- insertSelectCount :: (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m Int64
- renderExpr :: SqlBackend -> SqlExpr (Value Bool) -> Text
- data RenderExprException = RenderExprUnexpectedECompositeKey Text
- valkey :: (ToBackendKey SqlBackend entity, PersistField (Key entity)) => Int64 -> SqlExpr (Value (Key entity))
- valJ :: PersistField (Key entity) => Value (Key entity) -> SqlExpr (Value (Key entity))
- deleteKey :: (PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, MonadIO m, PersistEntity val) => Key val -> ReaderT backend m ()
- associateJoin :: forall e1 e0. Ord (Key e0) => [(Entity e0, e1)] -> Map (Key e0) (e0, [e1])
Documentation
fromStart :: forall a. (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (PreprocessedFrom (SqlExpr (Entity a))) Source #
(Internal) Start a from
query with an entity. from
does two kinds of magic using fromStart
, fromJoin
and
fromFinish
:
- The simple but tedious magic of allowing tuples to be used.
- The more advanced magic of creating
JOIN
s. TheJOIN
is processed from right to left. The rightmost entity of theJOIN
is created withfromStart
. EachJOIN
step is then translated into a call tofromJoin
. In the end,fromFinish
is called to materialize theJOIN
.
fromStartMaybe :: (PersistEntity a, BackendCompatible SqlBackend (PersistEntityBackend a)) => SqlQuery (PreprocessedFrom (SqlExpr (Maybe (Entity a)))) Source #
(Internal) Same as fromStart
, but entity may be missing.
fromJoin :: IsJoinKind join => PreprocessedFrom a -> PreprocessedFrom b -> SqlQuery (PreprocessedFrom (join a b)) Source #
(Internal) Do a JOIN
.
fromFinish :: PreprocessedFrom a -> SqlQuery a Source #
(Internal) Finish a JOIN
.
on :: SqlExpr (Value Bool) -> SqlQuery () Source #
An ON
clause, useful to describe how two tables are related. Cross joins
and tuple-joins do not need an on
clause, but InnerJoin
and the various
outer joins do.
Database.Esqueleto.Experimental in version 4.0.0.0 of the library. The
Experimental
module has a dramatically improved means for introducing
tables and entities that provides more power and less potential for runtime
errors.
If you don't include an on
clause (or include too many!) then a runtime
exception will be thrown.
As an example, consider this simple join:
select
$from
$ \(foo `InnerJoin
` bar) -> doon
(foo^.
FooId==.
bar^.
BarFooId) ...
We need to specify the clause for joining the two columns together. If we had this:
select
$from
$ \(foo `CrossJoin
` bar) -> do ...
Then we can safely omit the on
clause, because the cross join will make
pairs of all records possible.
You can do multiple on
clauses in a query. This query joins three tables,
and has two on
clauses:
select
$from
$ \(foo `InnerJoin
` bar `InnerJoin
` baz) -> doon
(baz^.
BazId==.
bar^.
BarBazId)on
(foo^.
FooId==.
bar^.
BarFooId) ...
Old versions of esqueleto required that you provide the on
clauses in
reverse order. This restriction has been lifted - you can now provide on
clauses in any order, and the SQL should work itself out. The above query is
now totally equivalent to this:
select
$from
$ \(foo `InnerJoin
` bar `InnerJoin
` baz) -> doon
(foo^.
FooId==.
bar^.
BarFooId)on
(baz^.
BazId==.
bar^.
BarBazId) ...
groupBy :: ToSomeValues a => a -> SqlQuery () Source #
GROUP BY
clause. You can enclose multiple columns
in a tuple.
select $from
\(foo `InnerJoin
` bar) -> doon
(foo^.
FooBarId==.
bar^.
BarId)groupBy
(bar^.
BarId, bar^.
BarName) return (bar^.
BarId, bar^.
BarName, countRows)
With groupBy you can sort by aggregate functions, like so
(we used let
to restrict the more general countRows
to
SqlSqlExpr (Value Int)
to avoid ambiguity---the second use of
countRows
has its type restricted by the :: Int
below):
r <- select $from
\(foo `InnerJoin
` bar) -> doon
(foo^.
FooBarId==.
bar^.
BarId)groupBy
$ bar^.
BarName let countRows' =countRows
orderBy
[asc
countRows'] return (bar^.
BarName, countRows') forM_ r $ \(Value
name,Value
count) -> do print name print (count :: Int)
Need more columns?
The ToSomeValues
class is defined for SqlExpr
and tuples of SqlExpr
s.
We only have definitions for up to 8 elements in a tuple right now, so it's
possible that you may need to have more than 8 elements.
For example, consider a query with a groupBy
call like this:
groupBy (e0, e1, e2, e3, e4, e5, e6, e7)
This is the biggest you can get with a single tuple. However, you can easily nest the tuples to add more:
groupBy ((e0, e1, e2, e3, e4, e5, e6, e7), e8, e9)
orderBy :: [SqlExpr OrderBy] -> SqlQuery () Source #
ORDER BY
clause. See also asc
and desc
.
Multiple calls to orderBy
get concatenated on the final
query, including distinctOnOrderBy
.
asc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #
Ascending order of this field or SqlExpression.
desc :: PersistField a => SqlExpr (Value a) -> SqlExpr OrderBy Source #
Descending order of this field or SqlExpression.
distinctOn :: [SqlExpr DistinctOn] -> SqlQuery a -> SqlQuery a Source #
DISTINCT ON
. Change the current SELECT
into
SELECT DISTINCT ON (SqlExpressions)
. For example:
select $from
\foo ->distinctOn
[don
(foo ^. FooName),don
(foo ^. FooState)] $ do ...
You can also chain different calls to distinctOn
. The
above is equivalent to:
select $from
\foo ->distinctOn
[don
(foo ^. FooName)] $distinctOn
[don
(foo ^. FooState)] $ do ...
Each call to distinctOn
adds more SqlExpressions. Calls to
distinctOn
override any calls to distinct
.
Note that PostgreSQL requires the SqlExpressions on DISTINCT
ON
to be the first ones to appear on a ORDER BY
. This is
not managed automatically by esqueleto, keeping its spirit
of trying to be close to raw SQL.
Supported by PostgreSQL only.
Since: 2.2.4
don :: SqlExpr (Value a) -> SqlExpr DistinctOn Source #
Erase an SqlExpression's type so that it's suitable to
be used by distinctOn
.
Since: 2.2.4
distinctOnOrderBy :: [SqlExpr OrderBy] -> SqlQuery a -> SqlQuery a Source #
A convenience function that calls both distinctOn
and
orderBy
. In other words,
distinctOnOrderBy
[asc foo, desc bar, desc quux] $ do
...
is the same as:
distinctOn
[don foo, don bar, don quux] $ doorderBy
[asc foo, desc bar, desc quux] ...
Since: 2.2.4
rand :: SqlExpr OrderBy Source #
Deprecated: Since 2.6.0: rand
ordering function is not uniform across all databases! To avoid accidental partiality it will be removed in the next major version.
ORDER BY random()
clause.
Since: 1.3.10
locking :: LockingKind -> SqlQuery () Source #
Add a locking clause to the query. Please read
LockingKind
documentation and your RDBMS manual.
If multiple calls to locking
are made on the same query,
the last one is used.
Since: 2.2.7
sub_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) Source #
Deprecated: sub_select sub_select is an unsafe function to use. If used with a SqlQuery that returns 0 results, then it may return NULL despite not mentioning Maybe in the return type. If it returns more than 1 result, then it will throw a SQL error. Instead, consider using one of the following alternatives: - subSelect: attaches a LIMIT 1 and the Maybe return type, totally safe. - subSelectMaybe: Attaches a LIMIT 1, useful for a query that already has a Maybe in the return type. - subSelectCount: Performs a count of the query - this is always safe. - subSelectUnsafe: Performs no checks or guarantees. Safe to use with countRows and friends.
Execute a subquery SELECT
in an SqlExpression. Returns a
simple value so should be used only when the SELECT
query
is guaranteed to return just one row.
Deprecated in 3.2.0.
subSelect :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value (Maybe a)) Source #
Execute a subquery SELECT
in a SqlExpr
. The query passed to this
function will only return a single result - it has a LIMIT 1
passed in to
the query to make it safe, and the return type is Maybe
to indicate that
the subquery might result in 0 rows.
If you find yourself writing
, then consider using
joinV
. subSelect
subSelectMaybe
.
If you're performing a countRows
, then you can use subSelectCount
which
is safe.
If you know that the subquery will always return exactly one row (eg
a foreign key constraint guarantees that you'll get exactly one row), then
consider subSelectUnsafe
, along with a comment explaining why it is safe.
Since: 3.2.0
subSelectMaybe :: PersistField a => SqlQuery (SqlExpr (Value (Maybe a))) -> SqlExpr (Value (Maybe a)) Source #
Execute a subquery SELECT
in a SqlExpr
. This function is a shorthand
for the common
idiom, where you are calling
joinV
. subSelect
subSelect
on an expression that would be Maybe
already.
As an example, you would use this function when calling sum_
or max_
,
which have Maybe
in the result type (for a 0 row query).
Since: 3.2.0
subSelectCount :: (Num a, PersistField a) => SqlQuery ignored -> SqlExpr (Value a) Source #
Performs a COUNT
of the given query in a subSelect
manner. This is
always guaranteed to return a result value, and is completely safe.
Since: 3.2.0
subSelectList :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) Source #
Execute a subquery SELECT
in a SqlExpr
that returns a list. This is an
alias for subList_select
and is provided for symmetry with the other safe
subselect functions.
Since: 3.2.0
:: (BackendCompatible SqlBackend (PersistEntityBackend val1), PersistEntity val1, PersistEntity val2, PersistField a) | |
=> SqlExpr (Entity val2) | An expression representing the table you have access to now. |
-> EntityField val2 (Key val1) | The foreign key field on the table. |
-> (SqlExpr (Entity val1) -> SqlExpr (Value a)) | A function to extract a value from the foreign reference table. |
-> SqlExpr (Value a) |
Performs a sub-select using the given foreign key on the entity. This is useful to extract values that are known to be present by the database schema.
As an example, consider the following persistent definition:
User profile ProfileId Profile name Text
The following query will return the name of the user.
getUserWithName =select
$from
$ user ->pure
(user,subSelectForeign
user UserProfile (^. ProfileName)
Since: 3.2.0
subSelectUnsafe :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (Value a) Source #
Execute a subquery SELECT
in a SqlExpr
. This function is unsafe,
because it can throw runtime exceptions in two cases:
- If the query passed has 0 result rows, then it will return a
NULL
value. Thepersistent
parsing operations will fail on an unexpectedNULL
. - If the query passed returns more than one row, then the SQL engine will fail with an error like "More than one row returned by a subquery used as an expression".
This function is safe if you guarantee that exactly one row will be returned,
or if the result already has a Maybe
type for some reason.
For variants with the safety encoded already, see subSelect
and
subSelectMaybe
. For the most common safe use of this, see subSelectCount
.
Since: 3.2.0
(^.) :: forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) infixl 9 Source #
Project a field of an entity.
withNonNull :: PersistField typ => SqlExpr (Value (Maybe typ)) -> (SqlExpr (Value typ) -> SqlQuery a) -> SqlQuery a Source #
Project an SqlExpression that may be null, guarding against null cases.
(?.) :: (PersistEntity val, PersistField typ) => SqlExpr (Maybe (Entity val)) -> EntityField val typ -> SqlExpr (Value (Maybe typ)) Source #
Project a field of an entity that may be null.
val :: PersistField typ => typ -> SqlExpr (Value typ) Source #
Lift a constant value from Haskell-land to the query.
isNothing :: PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool) Source #
IS NULL
comparison.
For IS NOT NULL
, you can negate this with not_
, as in not_ (isNothing (person ^. PersonAge))
Warning: Persistent and Esqueleto have different behavior for != Nothing
:
Haskell | SQL | |
---|---|---|
Persistent |
| IS NOT NULL |
Esqueleto |
| != NULL |
In SQL, = NULL
and != NULL
return NULL instead of true or false. For this reason, you very likely do not want to use
in Esqueleto.
You may find these !=.
Nothinghlint
rules helpful to enforce this:
- error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing} - error: {lhs: v Database.Esqueleto.==. Database.Esqueleto.val Nothing, rhs: Database.Esqueleto.isNothing v, name: Use Esqueleto's isNothing} - error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing} - error: {lhs: v Database.Esqueleto.!=. Database.Esqueleto.val Nothing, rhs: not_ (Database.Esqueleto.isNothing v), name: Use Esqueleto's not isNothing}
countDistinct :: Num a => SqlExpr (Value typ) -> SqlExpr (Value a) Source #
COUNT(DISTINCT x)
.
Since: 2.4.1
(==.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #
(>=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #
(>.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #
(<=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #
(<.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #
(!=.) :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) infix 4 Source #
(+.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 6 Source #
(-.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 6 Source #
(/.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 7 Source #
(*.) :: PersistField a => SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value a) infixl 7 Source #
between :: PersistField a => SqlExpr (Value a) -> (SqlExpr (Value a), SqlExpr (Value a)) -> SqlExpr (Value Bool) Source #
BETWEEN
.
@since: 3.1.0
round_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) Source #
ceiling_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) Source #
floor_ :: (PersistField a, Num a, PersistField b, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) Source #
sum_ :: (PersistField a, PersistField b) => SqlExpr (Value a) -> SqlExpr (Value (Maybe b)) Source #
avg_ :: (PersistField a, PersistField b) => SqlExpr (Value a) -> SqlExpr (Value (Maybe b)) Source #
castNum :: (Num a, Num b) => SqlExpr (Value a) -> SqlExpr (Value b) Source #
Allow a number of one type to be used as one of another type via an implicit cast. An explicit cast is not made, this function changes only the types on the Haskell side.
Caveat: Trying to use castNum
from Double
to Int
will not result in an integer, the original fractional
number will still be used! Use round_
, ceiling_
or
floor_
instead.
Safety: This operation is mostly safe due to the Num
constraint between the types and the fact that RDBMSs
usually allow numbers of different types to be used
interchangeably. However, there may still be issues with
the query not being accepted by the RDBMS or persistent
not being able to parse it.
Since: 2.2.9
castNumM :: (Num a, Num b) => SqlExpr (Value (Maybe a)) -> SqlExpr (Value (Maybe b)) Source #
Same as castNum
, but for nullable values.
Since: 2.2.9
coalesce :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value (Maybe a)) Source #
COALESCE
function. Evaluates the arguments in order and
returns the value of the first non-NULL SqlExpression, or NULL
(Nothing) otherwise. Some RDBMSs (such as SQLite) require
at least two arguments; please refer to the appropriate
documentation.
Since: 1.4.3
coalesceDefault :: PersistField a => [SqlExpr (Value (Maybe a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #
Like coalesce
, but takes a non-nullable SqlExpression
placed at the end of the SqlExpression list, which guarantees
a non-NULL result.
Since: 1.4.3
upper_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) Source #
UPPER
function.
@since 3.3.0
rtrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) Source #
RTRIM
function.
@since 3.3.0
ltrim_ :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) Source #
LTRIM
function.
@since 3.3.0
length_ :: (SqlString s, Num a) => SqlExpr (Value s) -> SqlExpr (Value a) Source #
LENGTH
function.
@since 3.3.0
left_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) Source #
LEFT
function.
@since 3.3.0
right_ :: (SqlString s, Num a) => (SqlExpr (Value s), SqlExpr (Value a)) -> SqlExpr (Value s) Source #
RIGHT
function.
@since 3.3.0
like :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) infixr 2 Source #
LIKE
operator.
ilike :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value Bool) infixr 2 Source #
ILIKE
operator (case-insensitive LIKE
).
Supported by PostgreSQL only.
Since: 2.2.3
concat_ :: SqlString s => [SqlExpr (Value s)] -> SqlExpr (Value s) Source #
The CONCAT
function with a variable number of
parameters. Supported by MySQL and PostgreSQL.
(++.) :: SqlString s => SqlExpr (Value s) -> SqlExpr (Value s) -> SqlExpr (Value s) infixr 5 Source #
castString :: (SqlString s, SqlString r) => SqlExpr (Value s) -> SqlExpr (Value r) Source #
Cast a string type into Text
. This function
is very useful if you want to use newtype
s, or if you want
to apply functions such as like
to strings of different
types.
Safety: This is a slightly unsafe function, especially if
you have defined your own instances of SqlString
. Also,
since Maybe
is an instance of SqlString
, it's possible
to turn a nullable value into a non-nullable one. Avoid
using this function if possible.
subList_select :: PersistField a => SqlQuery (SqlExpr (Value a)) -> SqlExpr (ValueList a) Source #
Execute a subquery SELECT
in an SqlExpression. Returns a
list of values.
valList :: PersistField typ => [typ] -> SqlExpr (ValueList typ) Source #
Lift a list of constant value from Haskell-land to the query.
in_ :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #
IN
operator. For example if you want to select all Person
s by a list
of IDs:
SELECT * FROM Person WHERE Person.id IN (?)
In esqueleto
, we may write the same query above as:
select $from
$ \person -> dowhere_
$ person^.
PersonId `in_
`valList
personIds return person
Where personIds
is of type [Key Person]
.
notIn :: PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) Source #
NOT IN
operator.
set :: PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Source #
SET
clause used on UPDATE
s. Note that while it's not
a type error to use this function on a SELECT
, it will
most certainly result in a runtime error.
(=.) :: (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #
(+=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #
(-=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #
(*=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #
(/=.) :: (PersistEntity val, PersistField a) => EntityField val a -> SqlExpr (Value a) -> SqlExpr (Entity val) -> SqlExpr Update infixr 3 Source #
(<#) :: (a -> b) -> SqlExpr (Value a) -> SqlExpr (Insertion b) Source #
Apply a PersistField
constructor to SqlExpr Value
arguments.
(<&>) :: SqlExpr (Insertion (a -> b)) -> SqlExpr (Value a) -> SqlExpr (Insertion b) Source #
Apply extra SqlExpr Value
arguments to a PersistField
constructor
case_ :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #
CASE
statement. For example:
select $ return $case_
[when_
(exists
$from
$ \p -> dowhere_
(p^.
PersonName==.
val
"Mike"))then_
(sub_select
$from
$ \v -> do let sub =from
$ \c -> dowhere_
(c^.
PersonName==.
val
"Mike") return (c^.
PersonFavNum)where_
(v^.
PersonFavNum >.sub_select
sub) return $count
(v^.
PersonName) +.val
(1 :: Int)) ] (else_
$val
(-1))
This query is a bit complicated, but basically it checks if a person
named "Mike"
exists, and if that person does, run the subquery to find
out how many people have a ranking (by Fav Num) higher than "Mike"
.
NOTE: There are a few things to be aware about this statement.
- This only implements the full CASE statement, it does not implement the "simple" CASE statement.
- At least one
when_
andthen_
is mandatory otherwise it will emit an error. - The
else_
is also mandatory, unlike the SQL statement in which if theELSE
is omitted it will return aNULL
. You can reproduce this vianothing
.
Since: 2.1.2
toBaseId :: ToBaseId ent => SqlExpr (Value (Key ent)) -> SqlExpr (Value (Key (BaseEnt ent))) Source #
Convert an entity's key into another entity's.
This function is to be used when you change an entity's Id
to be
that of another entity. For example:
Bar barNum Int Foo bar BarId fooNum Int Primary bar
In this example, Bar is said to be the BaseEnt(ity), and Foo the child. To model this in Esqueleto, declare:
instance ToBaseId Foo where type BaseEnt Foo = Bar toBaseIdWitness barId = FooKey barId
Now you're able to write queries such as:
select
$from
$ (bar `InnerJoin
` foo) -> doon
(toBaseId
(foo^.
FooId)==.
bar^.
BarId) return (bar, foo)
Note: this function may be unsafe to use in conditions not like the one of the example above.
Since: 2.4.3
when_ :: expr (Value Bool) -> () -> expr a -> (expr (Value Bool), expr a) Source #
Syntax sugar for case_
.
Since: 2.1.2
A single value (as opposed to a whole entity). You may use
(
or ^.
)(
to get a ?.
)Value
from an Entity
.
Instances
Applicative Value Source # | |
Functor Value Source # | Since: 1.4.4 |
Monad Value Source # | |
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Entity rec)) (SqlExpr (Value typ)) Source # | 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: 3.5.4.0 |
(PersistEntity rec, PersistField typ, SymbolToField sym rec typ) => HasField (sym :: Symbol) (SqlExpr (Maybe (Entity rec))) (SqlExpr (Value (Maybe typ))) Source # | 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: 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 Source # | |
(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 Source # | |
Show a => Show (Value a) Source # | |
ToAlias (SqlExpr (Value a)) Source # | |
ToAliasReference (SqlExpr (Value a)) Source # | |
ToMaybe (SqlExpr (Value a)) Source # | |
ToSomeValues (SqlExpr (Value a)) Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
Eq a => Eq (Value a) Source # | |
Ord a => Ord (Value a) Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
PersistField a => SqlSelect (SqlExpr (Value a)) (Value a) Source # | You may return any single value (i.e. a single column) from
a |
Defined in Database.Esqueleto.Internal.Internal sqlSelectCols :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) Source # sqlSelectColCount :: Proxy (SqlExpr (Value a)) -> Int Source # sqlSelectProcessRow :: [PersistValue] -> Either Text (Value a) Source # sqlInsertInto :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) Source # | |
type ToMaybeT (SqlExpr (Value a)) Source # | |
A list of single values. There's a limited set of functions
able to work with this data type (such as subList_select
,
valList
, in_
and exists
).
Instances
Show a => Show (ValueList a) Source # | |
Eq a => Eq (ValueList a) Source # | |
Ord a => Ord (ValueList a) Source # | |
Defined in Database.Esqueleto.Internal.Internal |
A wrapper type for for any expr (Value a)
for all a.
class ToSomeValues a where Source #
A class of things that can be converted into a list of SomeValue. It has
instances for tuples and is the reason why groupBy
can take tuples, like
.groupBy
(foo ^.
FooId, foo ^.
FooName, foo ^.
FooType)
toSomeValues :: a -> [SomeValue] Source #
Instances
type family KnowResult a where ... Source #
KnowResult (i -> o) = KnowResult o | |
KnowResult a = a |
class FinalResult a where Source #
A class for constructors or function which result type is known.
Since: 3.1.3
finalR :: a -> KnowResult a Source #
Instances
FinalResult (Unique val) Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
FinalResult b => FinalResult (a -> b) Source # | |
Defined in Database.Esqueleto.Internal.Internal finalR :: (a -> b) -> KnowResult (a -> b) Source # |
toUniqueDef :: forall a val. (KnowResult a ~ Unique val, PersistEntity val, FinalResult a) => a -> UniqueDef Source #
renderUpdates :: BackendCompatible SqlBackend backend => backend -> [SqlExpr (Entity val) -> SqlExpr Update] -> (Builder, [PersistValue]) Source #
Render updates to be use in a SET clause for a given sql backend.
Since: 3.1.3
data InnerJoin a b infixl 2 Source #
Data type that represents an INNER JOIN
(see LeftOuterJoin
for an example).
a `InnerJoin` b infixl 2 |
Instances
IsJoinKind InnerJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
FromPreprocess (InnerJoin a b) => From (InnerJoin a b) Source # | |
(DoInnerJoin lateral lhs rhs r, lateral ~ IsLateral rhs) => ToFrom (InnerJoin lhs rhs) r Source # | |
data CrossJoin a b infixl 2 Source #
Data type that represents a CROSS JOIN
(see LeftOuterJoin
for an example).
a `CrossJoin` b infixl 2 |
Instances
IsJoinKind CrossJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
FromPreprocess (CrossJoin a b) => From (CrossJoin a b) Source # | |
(DoCrossJoin lateral lhs rhs r, IsLateral rhs ~ lateral) => ToFrom (CrossJoin lhs rhs) r Source # | |
data LeftOuterJoin a b infixl 2 Source #
Data type that represents a LEFT OUTER JOIN
. For example,
select $from
$ \(person `LeftOuterJoin
` pet) -> ...
is translated into
SELECT ... FROM Person LEFT OUTER JOIN Pet ...
See also: from
.
a `LeftOuterJoin` b infixl 2 |
Instances
IsJoinKind LeftOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> LeftOuterJoin a b Source # reifyJoinKind :: LeftOuterJoin a b -> JoinKind Source # | |
FromPreprocess (LeftOuterJoin a b) => From (LeftOuterJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal from_ :: SqlQuery (LeftOuterJoin a b) Source # | |
(DoLeftJoin lateral lhs rhs r, lateral ~ IsLateral rhs) => ToFrom (LeftOuterJoin lhs rhs) r Source # | |
Defined in Database.Esqueleto.Experimental.From.Join toFrom :: LeftOuterJoin lhs rhs -> From r Source # |
data RightOuterJoin a b infixl 2 Source #
Data type that represents a RIGHT OUTER JOIN
(see LeftOuterJoin
for an example).
a `RightOuterJoin` b infixl 2 |
Instances
IsJoinKind RightOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> RightOuterJoin a b Source # reifyJoinKind :: RightOuterJoin a b -> JoinKind Source # | |
FromPreprocess (RightOuterJoin a b) => From (RightOuterJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal from_ :: SqlQuery (RightOuterJoin a b) Source # | |
(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, HasOnClause rhs (ma :& b'), ErrorOnLateral b, rhs ~ (b, (ma :& b') -> SqlExpr (Value Bool))) => ToFrom (RightOuterJoin a rhs) (ma :& b') Source # | |
Defined in Database.Esqueleto.Experimental.From.Join |
data FullOuterJoin a b infixl 2 Source #
Data type that represents a FULL OUTER JOIN
(see LeftOuterJoin
for an example).
a `FullOuterJoin` b infixl 2 |
Instances
IsJoinKind FullOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> FullOuterJoin a b Source # reifyJoinKind :: FullOuterJoin a b -> JoinKind Source # | |
FromPreprocess (FullOuterJoin a b) => From (FullOuterJoin a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal from_ :: SqlQuery (FullOuterJoin a b) Source # | |
(ToFrom a a', ToFrom b b', ToMaybe a', ToMaybeT a' ~ ma, ToMaybe b', ToMaybeT b' ~ mb, HasOnClause rhs (ma :& mb), ErrorOnLateral b, rhs ~ (b, (ma :& mb) -> SqlExpr (Value Bool))) => ToFrom (FullOuterJoin a rhs) (ma :& mb) Source # | |
Defined in Database.Esqueleto.Experimental.From.Join |
(Internal) A kind of JOIN
.
InnerJoinKind | INNER JOIN |
CrossJoinKind | CROSS JOIN |
LeftOuterJoinKind | LEFT OUTER JOIN |
RightOuterJoinKind | RIGHT OUTER JOIN |
FullOuterJoinKind | FULL OUTER JOIN |
class IsJoinKind join where Source #
(Internal) Functions that operate on types (that should be)
of kind JoinKind
.
smartJoin :: a -> b -> join a b Source #
(Internal) smartJoin a b
is a JOIN
of the correct kind.
reifyJoinKind :: join a b -> JoinKind Source #
(Internal) Reify a JoinKind
from a JOIN
. This
function is non-strict.
Instances
IsJoinKind CrossJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
IsJoinKind FullOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> FullOuterJoin a b Source # reifyJoinKind :: FullOuterJoin a b -> JoinKind Source # | |
IsJoinKind InnerJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
IsJoinKind LeftOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> LeftOuterJoin a b Source # reifyJoinKind :: LeftOuterJoin a b -> JoinKind Source # | |
IsJoinKind RightOuterJoin Source # | |
Defined in Database.Esqueleto.Internal.Internal smartJoin :: a -> b -> RightOuterJoin a b Source # reifyJoinKind :: RightOuterJoin a b -> JoinKind Source # |
data OnClauseWithoutMatchingJoinException Source #
Exception thrown whenever on
is used to create an ON
clause but no matching JOIN
is found.
Instances
data DistinctOn Source #
Phantom type used by distinctOn
and don
.
Phantom type used by insertSelect
.
Instances
PersistEntity e => SqlSelect (SqlExpr (Insertion e)) (Insertion e) Source # |
|
Defined in Database.Esqueleto.Internal.Internal sqlSelectCols :: IdentInfo -> SqlExpr (Insertion e) -> (Builder, [PersistValue]) Source # sqlSelectColCount :: Proxy (SqlExpr (Insertion e)) -> Int Source # sqlSelectProcessRow :: [PersistValue] -> Either Text (Insertion e) Source # sqlInsertInto :: IdentInfo -> SqlExpr (Insertion e) -> (Builder, [PersistValue]) Source # |
data LockingKind Source #
Different kinds of locking clauses supported by locking
.
Note that each RDBMS has different locking support. The
constructors of this datatype specify only the syntax of the
locking mechanism, not its semantics. For example, even
though both MySQL and PostgreSQL support ForUpdate
, there
are no guarantees that they will behave the same.
Since: 2.2.7
ForUpdate |
Since: 2.2.7 |
ForUpdateSkipLocked |
Since: 2.2.7 |
ForShare |
Since: 2.2.7 |
LockInShareMode |
Since: 2.2.7 |
class PersistField a => SqlString a Source #
Phantom class of data types that are treated as strings by the RDBMS. It has no methods because it's only used to avoid type errors such as trying to concatenate integers.
If you have a custom data type or newtype
, feel free to make
it an instance of this class.
Since: 2.4.0
Instances
SqlString Html Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString ByteString Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString Text Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString Text Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal | |
SqlString a => SqlString (Maybe a) Source # | Since: 2.4.0 |
Defined in Database.Esqueleto.Internal.Internal | |
a ~ Char => SqlString [a] Source # | Since: 2.3.0 |
Defined in Database.Esqueleto.Internal.Internal |
from :: From a => (a -> SqlQuery b) -> SqlQuery b Source #
FROM
clause: bring entities into scope.
Note that this function will be replaced by the one in
Database.Esqueleto.Experimental in version 4.0.0.0 of the library. The
Experimental
module has a dramatically improved means for introducing
tables and entities that provides more power and less potential for runtime
errors.
This function internally uses two type classes in order to provide some flexibility of how you may call it. Internally we refer to these type classes as the two different magics.
The innermost magic allows you to use from
with the
following types:
expr (Entity val)
, which brings a single entity into scope.expr (Maybe (Entity val))
, which brings a single entity that may beNULL
into scope. Used forOUTER JOIN
s.- A
JOIN
of any other two types allowed by the innermost magic, where aJOIN
may be anInnerJoin
, aCrossJoin
, aLeftOuterJoin
, aRightOuterJoin
, or aFullOuterJoin
. TheJOINs
have left fixity.
The outermost magic allows you to use from
on any tuples of
types supported by innermost magic (and also tuples of tuples,
and so on), up to 8-tuples.
Note that using from
for the same entity twice does work and
corresponds to a self-join. You don't even need to use two
different calls to from
, you may use a JOIN
or a tuple.
The following are valid examples of uses of from
(the types
of the arguments of the lambda are inside square brackets):
from
$ \person -> ...from
$ \(person, blogPost) -> ...from
$ \(p `LeftOuterJoin
` mb) -> ...from
$ \(p1 `InnerJoin
` f `InnerJoin
` p2) -> ...from
$ \((p1 `InnerJoin
` f) `InnerJoin
` p2) -> ...
The types of the arguments to the lambdas above are, respectively:
person :: ( Esqueleto query expr backend , PersistEntity Person , PersistEntityBackend Person ~ backend ) => expr (Entity Person) (person, blogPost) :: (...) => (expr (Entity Person), expr (Entity BlogPost)) (p `LeftOuterJoin
` mb) :: (...) => InnerJoin (expr (Entity Person)) (expr (Maybe (Entity BlogPost))) (p1 `InnerJoin
` f `InnerJoin
` p2) :: (...) => InnerJoin (InnerJoin (expr (Entity Person)) (expr (Entity Follow))) (expr (Entity Person)) (p1 `InnerJoin
` (f `InnerJoin
` p2)) :: :: (...) => InnerJoin (expr (Entity Person)) (InnerJoin (expr (Entity Follow)) (expr (Entity Person)))
Note that some backends may not support all kinds of JOIN
s.
Instances
class FromPreprocess a where Source #
Instances
(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Entity val)) Source # | |
Defined in Database.Esqueleto.Internal.Internal fromPreprocess :: SqlQuery (PreprocessedFrom (SqlExpr (Entity val))) Source # | |
(PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => FromPreprocess (SqlExpr (Maybe (Entity val))) Source # | |
Defined in Database.Esqueleto.Internal.Internal fromPreprocess :: SqlQuery (PreprocessedFrom (SqlExpr (Maybe (Entity val)))) Source # | |
(FromPreprocess a, FromPreprocess b, IsJoinKind join) => FromPreprocess (join a b) Source # | |
Defined in Database.Esqueleto.Internal.Internal fromPreprocess :: SqlQuery (PreprocessedFrom (join a b)) Source # |
data EsqueletoError Source #
Exception data type for esqueleto
internal errors
CompositeKeyErr CompositeKeyError | |
AliasedValueErr UnexpectedValueError | |
UnexpectedCaseErr UnexpectedCaseError | |
SqlBinOpCompositeErr SqlBinOpCompositeError |
Instances
Exception EsqueletoError Source # | |
Defined in Database.Esqueleto.Internal.Internal | |
Show EsqueletoError Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> EsqueletoError -> ShowS # show :: EsqueletoError -> String # showList :: [EsqueletoError] -> ShowS # |
data UnexpectedValueError Source #
Instances
Show UnexpectedValueError Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> UnexpectedValueError -> ShowS # show :: UnexpectedValueError -> String # showList :: [UnexpectedValueError] -> ShowS # |
data UnexpectedCaseError Source #
EmptySqlExprValueList | |
MakeFromError | |
UnsupportedSqlInsertIntoType | |
InsertionFinalError | |
NewIdentForError | |
UnsafeSqlCaseError | |
OperationNotSupported | |
NotImplemented |
Instances
Show UnexpectedCaseError Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> UnexpectedCaseError -> ShowS # show :: UnexpectedCaseError -> String # showList :: [UnexpectedCaseError] -> ShowS # |
data SqlBinOpCompositeError Source #
Instances
Show SqlBinOpCompositeError Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> SqlBinOpCompositeError -> ShowS # show :: SqlBinOpCompositeError -> String # showList :: [SqlBinOpCompositeError] -> ShowS # |
SQL backend for esqueleto
using SqlPersistT
.
Instances
type SqlEntity ent = (PersistEntity ent, PersistEntityBackend ent ~ SqlBackend) Source #
Constraint synonym for persistent
entities whose backend
is SqlBackend
.
Side data written by SqlQuery
.
data DistinctClause Source #
The DISTINCT
"clause".
DistinctAll | The default, everything. |
DistinctStandard | Only |
DistinctOn [SqlExpr DistinctOn] |
|
Instances
Monoid DistinctClause Source # | |
Defined in Database.Esqueleto.Internal.Internal mappend :: DistinctClause -> DistinctClause -> DistinctClause # mconcat :: [DistinctClause] -> DistinctClause # | |
Semigroup DistinctClause Source # | |
Defined in Database.Esqueleto.Internal.Internal (<>) :: DistinctClause -> DistinctClause -> DistinctClause # sconcat :: NonEmpty DistinctClause -> DistinctClause # stimes :: Integral b => b -> DistinctClause -> DistinctClause # |
data FromClause Source #
A part of a FROM
clause.
FromStart Ident EntityDef | |
FromJoin FromClause JoinKind FromClause (Maybe (SqlExpr (Value Bool))) | |
OnClause (SqlExpr (Value Bool)) | |
FromRaw (NeedParens -> IdentInfo -> (Builder, [PersistValue])) |
Instances
Show FromClause Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> FromClause -> ShowS # show :: FromClause -> String # showList :: [FromClause] -> ShowS # |
data CommonTableExpressionKind Source #
Instances
data SubQueryType Source #
Instances
Show SubQueryType Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> SubQueryType -> ShowS # show :: SubQueryType -> String # showList :: [SubQueryType] -> ShowS # |
collectIdents :: FromClause -> Set Ident Source #
collectOnClauses :: SqlBackend -> [FromClause] -> Either (SqlExpr (Value Bool)) [FromClause] Source #
data WhereClause Source #
A complete WHERE
clause.
Instances
Monoid WhereClause Source # | |
Defined in Database.Esqueleto.Internal.Internal mempty :: WhereClause # mappend :: WhereClause -> WhereClause -> WhereClause # mconcat :: [WhereClause] -> WhereClause # | |
Semigroup WhereClause Source # | |
Defined in Database.Esqueleto.Internal.Internal (<>) :: WhereClause -> WhereClause -> WhereClause # sconcat :: NonEmpty WhereClause -> WhereClause # stimes :: Integral b => b -> WhereClause -> WhereClause # |
newtype GroupByClause Source #
A GROUP BY
clause.
Instances
Monoid GroupByClause Source # | |
Defined in Database.Esqueleto.Internal.Internal mempty :: GroupByClause # mappend :: GroupByClause -> GroupByClause -> GroupByClause # mconcat :: [GroupByClause] -> GroupByClause # | |
Semigroup GroupByClause Source # | |
Defined in Database.Esqueleto.Internal.Internal (<>) :: GroupByClause -> GroupByClause -> GroupByClause # sconcat :: NonEmpty GroupByClause -> GroupByClause # stimes :: Integral b => b -> GroupByClause -> GroupByClause # |
type HavingClause = WhereClause Source #
A HAVING
cause.
type OrderByClause = SqlExpr OrderBy Source #
A ORDER BY
clause.
data LimitClause Source #
A LIMIT
clause.
Instances
Monoid LimitClause Source # | |
Defined in Database.Esqueleto.Internal.Internal mempty :: LimitClause # mappend :: LimitClause -> LimitClause -> LimitClause # mconcat :: [LimitClause] -> LimitClause # | |
Semigroup LimitClause Source # | |
Defined in Database.Esqueleto.Internal.Internal (<>) :: LimitClause -> LimitClause -> LimitClause # sconcat :: NonEmpty LimitClause -> LimitClause # stimes :: Integral b => b -> LimitClause -> LimitClause # | |
Eq LimitClause Source # | |
Defined in Database.Esqueleto.Internal.Internal (==) :: LimitClause -> LimitClause -> Bool # (/=) :: LimitClause -> LimitClause -> Bool # |
type LockingClause = Last LockingKind Source #
A locking clause.
newtype IdentState Source #
List of identifiers already in use and supply of temporary identifiers.
type IdentInfo = (SqlBackend, IdentState) Source #
Information needed to escape and use identifiers.
data SqlExprMeta Source #
noMeta :: SqlExprMeta Source #
Empty SqlExprMeta
if you are constructing an ERaw
probably use this
for your meta
hasCompositeKeyMeta :: SqlExprMeta -> Bool Source #
Does this meta contain values for composite fields. This field is field out for composite key values
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.
ERaw SqlExprMeta (NeedParens -> IdentInfo -> (Builder, [PersistValue])) |
Instances
data InsertFinal Source #
Phantom type used to mark a INSERT INTO
query.
data NeedParens Source #
Instances
Eq NeedParens Source # | |
Defined in Database.Esqueleto.Internal.Internal (==) :: NeedParens -> NeedParens -> Bool # (/=) :: NeedParens -> NeedParens -> Bool # |
data OrderByType Source #
fieldName :: (PersistEntity val, PersistField typ) => IdentInfo -> EntityField val typ -> Builder Source #
setAux :: (PersistEntity val, PersistField typ) => EntityField val typ -> (SqlExpr (Entity val) -> SqlExpr (Value typ)) -> SqlExpr (Entity val) -> SqlExpr Update Source #
unsafeSqlCase :: PersistField a => [(SqlExpr (Value Bool), SqlExpr (Value a))] -> SqlExpr (Value a) -> SqlExpr (Value a) Source #
(Internal) Create a case statement.
Since: 2.1.1
unsafeSqlBinOp :: Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) Source #
(Internal) Create a custom binary operator. You should not use this function directly since its type is very general, you should always use it with an explicit type signature. For example:
(==.) :: SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value Bool) (==.) = unsafeSqlBinOp " = "
In the example above, we constraint the arguments to be of the same type and constraint the result to be a boolean value.
unsafeSqlBinOpComposite :: Builder -> Builder -> SqlExpr (Value a) -> SqlExpr (Value b) -> SqlExpr (Value c) Source #
Similar to unsafeSqlBinOp
, but may also be applied to
composite keys. Uses the operator given as the second
argument whenever applied to composite keys.
Usage example:
(==.) :: SqlExpr (Value a) -> SqlExpr (Value a) -> SqlExpr (Value Bool) (==.) = unsafeSqlBinOpComposite " = " " AND "
Persistent has a hack for implementing composite keys (see
ECompositeKey
doc for more details), so we're forced to use
a hack here as well. We deconstruct ERaw
values based on
two rules:
- If it is a single placeholder, then it's assumed to be
coming from a
PersistList
and thus its components are separated so that they may be applied to a composite key. - If it is not a single placeholder, then it's assumed to be a foreign (composite or not) key, so we enforce that it has no placeholders and split it on the commas.
unsafeSqlValue :: Builder -> SqlExpr (Value a) Source #
(Internal) A raw SQL value. The same warning from
unsafeSqlBinOp
applies to this function as well.
unsafeSqlEntity :: PersistEntity ent => Ident -> SqlExpr (Entity ent) Source #
valueToFunctionArg :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) Source #
unsafeSqlFunction :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) Source #
(Internal) A raw SQL function. Once again, the same warning
from unsafeSqlBinOp
applies to this function as well.
unsafeSqlExtractSubField :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) Source #
(Internal) An unsafe SQL function to extract a subfield from a compound
field, e.g. datetime. See unsafeSqlBinOp
for warnings.
Since: 1.3.6.
unsafeSqlFunctionParens :: UnsafeSqlFunctionArgument a => Builder -> a -> SqlExpr (Value b) Source #
(Internal) A raw SQL function. Preserves parentheses around arguments.
See unsafeSqlBinOp
for warnings.
unsafeSqlCastAs :: Text -> SqlExpr (Value a) -> SqlExpr (Value b) Source #
(Internal) An explicit SQL type cast using CAST(value as type).
See unsafeSqlBinOp
for warnings.
class UnsafeSqlFunctionArgument a where Source #
(Internal) This class allows unsafeSqlFunction
to work with different
numbers of arguments; specifically it allows providing arguments to a sql
function via an n-tuple of SqlExpr (Value _)
values, which are not all
necessarily required to be the same type. There are instances for up to
10-tuples, but for sql functions which take more than 10 arguments, you can
also nest tuples, as e.g. toArgList ((a,b),(c,d))
is the same as
toArgList (a,b,c,d)
.
Instances
veryUnsafeCoerceSqlExprValue :: SqlExpr (Value a) -> SqlExpr (Value b) Source #
(Internal) Coerce a value's type from 'SqlExpr (Value a)' to 'SqlExpr (Value b)'. You should not use this function unless you know what you're doing!
veryUnsafeCoerceSqlExprValueList :: SqlExpr (ValueList a) -> SqlExpr (Value a) Source #
(Internal) Coerce a value's type from 'SqlExpr (ValueList a)' to 'SqlExpr (Value a)'. Does not work with empty lists.
rawSelectSource :: (SqlSelect a r, MonadIO m1, MonadIO m2, SqlBackendCanRead backend) => Mode -> SqlQuery a -> ReaderT backend m1 (Acquire (ConduitT () r m2 ())) Source #
(Internal) Execute an esqueleto
SELECT
SqlQuery
inside
persistent
's SqlPersistT
monad.
selectSource :: (SqlSelect a r, BackendCompatible SqlBackend backend, IsPersistBackend backend, PersistQueryRead backend, PersistStoreRead backend, PersistUniqueRead backend, MonadResource m) => SqlQuery a -> ConduitT () r (ReaderT backend m) () Source #
Execute an esqueleto
SELECT
query inside persistent
's
SqlPersistT
monad and return a Source
of rows.
select :: (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m [r] Source #
Execute an esqueleto
SELECT
query inside persistent
's
SqlPersistT
monad and return a list of rows.
We've seen that from
has some magic about which kinds of
things you may bring into scope. This select
function also
has some magic for which kinds of things you may bring back to
Haskell-land by using SqlQuery
's return
:
- You may return a
SqlExpr (
for an entityEntity
v)v
(i.e., like the*
in SQL), which is then returned to Haskell-land as justEntity v
. - You may return a
SqlExpr (Maybe (Entity v))
for an entityv
that may beNULL
, which is then returned to Haskell-land asMaybe (Entity v)
. Used forOUTER JOIN
s. - You may return a
SqlExpr (
for a valueValue
t)t
(i.e., a single column), wheret
is any instance ofPersistField
, which is then returned to Haskell-land asValue t
. You may useValue
to return projections of anEntity
(see(
and^.
)(
) or to return any other value calculated on the query (e.g.,?.
)countRows
orsubSelect
).
The SqlSelect a r
class has functional dependencies that
allow type information to flow both from a
to r
and
vice-versa. This means that you'll almost never have to give
any type signatures for esqueleto
queries. For example, the
query
alone is ambiguous, but
in the context ofselect
$ from $ \p -> return p
do ps <-select
$from
$ \p -> return p liftIO $ mapM_ (putStrLn . personName . entityVal) ps
we are able to infer from that single personName . entityVal
function composition that the p
inside the query is of type
SqlExpr (Entity Person)
.
selectOne :: (SqlSelect a r, MonadIO m, SqlBackendCanRead backend) => SqlQuery a -> ReaderT backend m (Maybe r) Source #
Execute an esqueleto
SELECT
query inside persistent
's
SqlPersistT
monad and return the first entry wrapped in a Maybe
.
@since 3.5.1.0
Example usage
firstPerson :: MonadIO m => SqlPersistT m (Maybe (Entity Person)) firstPerson =selectOne
$ do person <-from
$table
@Person return person
The above query is equivalent to a select
combined with limit
but you
would still have to transform the results from a list:
firstPerson :: MonadIO m => SqlPersistT m [Entity Person] firstPerson =select
$ do person <-from
$table
@Personlimit
1 return person
runSource :: Monad m => ConduitT () r (ReaderT backend m) () -> ReaderT backend m [r] Source #
(Internal) Run a Source
of rows.
rawEsqueleto :: (MonadIO m, SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> SqlQuery a -> ReaderT backend m Int64 Source #
(Internal) Execute an esqueleto
statement inside
persistent
's SqlPersistT
monad.
delete :: (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m () Source #
Execute an esqueleto
DELETE
query inside persistent
's
SqlPersistT
monad. Note that currently there are no type
checks for statements that should not appear on a DELETE
query.
Example of usage:
delete
$from
$ \appointment ->where_
(appointment^.
AppointmentDate<.
val
now)
Unlike select
, there is a useful way of using delete
that
will lead to type ambiguities. If you want to delete all rows
(i.e., no where_
clause), you'll have to use a type signature:
delete
$from
$ \(appointment ::SqlExpr
(Entity
Appointment)) -> return ()
Database.Esqueleto.Experimental:
delete $ do
userFeature <- from $ table @UserFeature
where_ ((userFeature ^. UserFeatureFeature) notIn
valList allKnownFeatureFlags)
deleteCount :: (MonadIO m, SqlBackendCanWrite backend) => SqlQuery () -> ReaderT backend m Int64 Source #
Same as delete
, but returns the number of rows affected.
update :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m () Source #
Execute an esqueleto
UPDATE
query inside persistent
's
SqlPersistT
monad. Note that currently there are no type
checks for statements that should not appear on a UPDATE
query.
Example of usage:
update
$ \p -> doset
p [ PersonAge=.
just
(val
thisYear) -. p^.
PersonBorn ]where_
$ isNothing (p^.
PersonAge)
updateCount :: (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val), SqlBackendCanWrite backend) => (SqlExpr (Entity val) -> SqlQuery ()) -> ReaderT backend m Int64 Source #
Same as update
, but returns the number of rows affected.
builderToText :: Builder -> Text Source #
toRawSql :: (SqlSelect a r, BackendCompatible SqlBackend backend) => Mode -> (backend, IdentState) -> SqlQuery a -> (Builder, [PersistValue]) Source #
(Internal) Pretty prints a SqlQuery
into a SQL query.
Note: if you're curious about the SQL query being generated by
esqueleto
, instead of manually using this function (which is
possible but tedious), see the renderQueryToText
function (along with
renderQuerySelect
, renderQueryUpdate
, etc).
:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) | |
=> Mode | |
-> SqlQuery a | The SQL query you want to render. |
-> ReaderT backend m (Text, [PersistValue]) |
Renders a SqlQuery
into a Text
value along with the list of
PersistValue
s that would be supplied to the database for ?
placeholders.
You must ensure that the Mode
you pass to this function corresponds with
the actual SqlQuery
. If you pass a query that uses incompatible features
(like an INSERT
statement with a SELECT
mode) then you'll get a weird
result.
Since: 3.1.1
:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) | |
=> SqlQuery a | The SQL query you want to render. |
-> ReaderT backend m (Text, [PersistValue]) |
Renders a SqlQuery
into a Text
value along with the list of
PersistValue
s that would be supplied to the database for ?
placeholders.
Since: 3.1.1
:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) | |
=> SqlQuery a | The SQL query you want to render. |
-> ReaderT backend m (Text, [PersistValue]) |
Renders a SqlQuery
into a Text
value along with the list of
PersistValue
s that would be supplied to the database for ?
placeholders.
Since: 3.1.1
:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) | |
=> SqlQuery a | The SQL query you want to render. |
-> ReaderT backend m (Text, [PersistValue]) |
Renders a SqlQuery
into a Text
value along with the list of
PersistValue
s that would be supplied to the database for ?
placeholders.
Since: 3.1.1
renderQueryInsertInto Source #
:: (SqlSelect a r, BackendCompatible SqlBackend backend, Monad m) | |
=> SqlQuery a | The SQL query you want to render. |
-> ReaderT backend m (Text, [PersistValue]) |
Renders a SqlQuery
into a Text
value along with the list of
PersistValue
s that would be supplied to the database for ?
placeholders.
Since: 3.1.1
(Internal) Mode of query being converted by toRawSql
.
makeCte :: IdentInfo -> [CommonTableExpressionClause] -> (Builder, [PersistValue]) Source #
makeInsertInto :: SqlSelect a r => IdentInfo -> Mode -> a -> (Builder, [PersistValue]) Source #
makeSelect :: SqlSelect a r => IdentInfo -> Mode -> DistinctClause -> a -> (Builder, [PersistValue]) Source #
makeFrom :: IdentInfo -> Mode -> [FromClause] -> (Builder, [PersistValue]) Source #
makeWhere :: IdentInfo -> WhereClause -> (Builder, [PersistValue]) Source #
makeGroupBy :: IdentInfo -> GroupByClause -> (Builder, [PersistValue]) Source #
makeHaving :: IdentInfo -> WhereClause -> (Builder, [PersistValue]) Source #
makeOrderByNoNewline :: IdentInfo -> [OrderByClause] -> (Builder, [PersistValue]) Source #
makeOrderBy :: IdentInfo -> [OrderByClause] -> (Builder, [PersistValue]) Source #
makeLimit :: IdentInfo -> LimitClause -> (Builder, [PersistValue]) Source #
makeLocking :: LockingClause -> (Builder, [PersistValue]) Source #
class SqlSelect a r | a -> r, r -> a where Source #
(Internal) Class for mapping results coming from SqlQuery
into actual results.
This looks very similar to RawSql
, and it is! However,
there are some crucial differences and ultimately they're
different classes.
sqlSelectCols :: IdentInfo -> a -> (Builder, [PersistValue]) Source #
Creates the variable part of the SELECT
query and
returns the list of PersistValue
s that will be given to
rawQuery
.
sqlSelectColCount :: Proxy a -> Int Source #
Number of columns that will be consumed.
sqlSelectProcessRow :: [PersistValue] -> Either Text r Source #
Transform a row of the result into the data type.
sqlInsertInto :: IdentInfo -> a -> (Builder, [PersistValue]) Source #
Create INSERT INTO
clause instead.
Instances
unescapedColumnNames :: EntityDef -> [DBName] Source #
materializeExpr :: IdentInfo -> SqlExpr (Value a) -> (Builder, [PersistValue]) Source #
Materialize a SqlExpr (Value a)
.
from10P :: Proxy (a, b, c, d, e, f, g, h, i, j) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j)) Source #
from11P :: Proxy (a, b, c, d, e, f, g, h, i, j, k) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), k) Source #
from12P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l)) Source #
to12 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l)) -> (a, b, c, d, e, f, g, h, i, j, k, l) Source #
from13P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m) Source #
to13 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #
from14P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n)) Source #
to14 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #
from15P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o) Source #
to15 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #
from16P :: Proxy (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) -> Proxy ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p)) Source #
to16 :: ((a, b), (c, d), (e, f), (g, h), (i, j), (k, l), (m, n), (o, p)) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #
insertSelect :: (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m () Source #
Insert a PersistField
for every selected value.
Since: 2.4.2
insertSelectCount :: (MonadIO m, PersistEntity a, SqlBackendCanWrite backend) => SqlQuery (SqlExpr (Insertion a)) -> ReaderT backend m Int64 Source #
Insert a PersistField
for every selected value, return the count afterward
renderExpr :: SqlBackend -> SqlExpr (Value Bool) -> Text Source #
Renders an expression into Text
. Only useful for creating a textual
representation of the clauses passed to an On clause.
Since: 3.2.0
data RenderExprException Source #
An exception thrown by RenderExpr
- it's not designed to handle composite
keys, and will blow up if you give it one.
Since: 3.2.0
Instances
Exception RenderExprException Source # | Since: 3.2.0 |
Show RenderExprException Source # | |
Defined in Database.Esqueleto.Internal.Internal showsPrec :: Int -> RenderExprException -> ShowS # show :: RenderExprException -> String # showList :: [RenderExprException] -> ShowS # |
valkey :: (ToBackendKey SqlBackend entity, PersistField (Key entity)) => Int64 -> SqlExpr (Value (Key entity)) Source #
valkey i =
(https://github.com/prowdsponsor/esqueleto/issues/9).val
. toSqlKey
valJ :: PersistField (Key entity) => Value (Key entity) -> SqlExpr (Value (Key entity)) Source #
valJ
is like val
but for something that is already a Value
. The use
case it was written for was, given a Value
lift the Key
for that Value
into the query expression in a type safe way. However, the implementation is
more generic than that so we call it valJ
.
Its important to note that the input entity and the output entity are constrained to be the same by the type signature on the function (https://github.com/prowdsponsor/esqueleto/pull/69).
Since: 1.4.2
deleteKey :: (PersistStore backend, BaseBackend backend ~ PersistEntityBackend val, MonadIO m, PersistEntity val) => Key val -> ReaderT backend m () Source #
associateJoin :: forall e1 e0. Ord (Key e0) => [(Entity e0, e1)] -> Map (Key e0) (e0, [e1]) Source #
Avoid N+1 queries and join entities into a map structure.
This function is useful to call on the result of a single JOIN
. For
example, suppose you have this query:
getFoosAndNestedBarsFromParent :: ParentId -> SqlPersistT IO [(Entity Foo, Maybe (Entity Bar))] getFoosAndNestedBarsFromParent parentId =select
$ do (foo :& bar) <- from $ tableFoo
Bar`LeftOuterJoin`
table`on`
do \(foo :& bar) -> foo ^. FooId ==. bar ?. BarFooId where_ $ foo ^. FooParentId ==. val parentId pure (foo, bar)
This is a natural result type for SQL - a list of tuples. However, it's not
what we usually want in Haskell - each Foo
in the list will be represented
multiple times, once for each Bar
.
We can write
and it will translate it into a fmap
associateJoin
Map
that is keyed on the Key
of the left Entity
, and the value is a tuple of
the entity's value as well as the list of each coresponding entity.
getFoosAndNestedBarsFromParentHaskellese :: ParentId -> SqlPersistT (Map (Key Foo) (Foo, [Maybe (Entity Bar)])) getFoosAndNestedBarsFromParentHaskellese parentId =fmap
associateJoin
$ getFoosdAndNestedBarsFromParent parentId
What if you have multiple joins?
Let's use associateJoin
with a *two* join query.
userPostComments :: SqlQuery (SqlExpr (Entity User, Entity Post, Entity Comment)) userPostsComment = do (u :& p :& c) <- from $ tableUser
Post`InnerJoin`
tableon
do \(u :& p) -> u ^. UserId ==. p ^. PostUserId`InnerJoin`
table @Comment`on`
do \(_ :& p :& c) -> p ^. PostId ==. c ^. CommentPostId pure (u, p, c)
This query returns a User, with all of the users Posts, and then all of the Comments on that post.
First, we *nest* the tuple.
nest :: (a, b, c) -> (a, (b, c)) nest (a, b, c) = (a, (b, c))
This makes the return of the query conform to the input expected from
associateJoin
.
nestedUserPostComments :: SqlPersistT IO [(Entity User, (Entity Post, Entity Comment))] nestedUserPostComments = fmap nest $ select userPostsComments
Now, we can call associateJoin
on it.
associateUsers :: [(Entity User, (Entity Post, Entity Comment))] -> Map UserId (User, [(Entity Post, Entity Comment)]) associateUsers = associateJoin
Next, we'll use the Functor
instances for Map
and tuple to call
associateJoin
on the [(Entity Post, Entity Comment)]
.
associatePostsAndComments :: Map UserId (User, [(Entity Post, Entity Comment)]) -> Map UserId (User, Map PostId (Post, [Entity Comment])) associatePostsAndComments = fmap (fmap associateJoin)
For more reading on this topic, see this Foxhound Systems blog post.
Since: 3.1.2