Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Selda is not LINQ, but they're definitely related.
Selda is a high-level EDSL for interacting with relational databases.
All database computations are performed within some monad implementing
the MonadSelda
type class. The SeldaT
monad over any MonadIO
is the
only pre-defined instance of MonadSelda
.
SeldaM
is provided as a convenient short-hand for SeldaT IO
.
To actually execute a database computation, you need one of the database
backends: selda-sqlite
or selda-postgresql
.
All Selda functions may throw SeldaError
when something goes wrong.
This includes database connection errors, uniqueness constraint errors,
etc.
See https://selda.link/tutorial for a tutorial covering the language basics.
Synopsis
- class MonadIO m => MonadSelda m
- type family Backend m
- data SeldaError
- data ValidationError
- data SeldaT b m a
- type SeldaM b = SeldaT b IO
- type Relational a = (Generic a, SqlRow a, GRelation (Rep a))
- newtype Only a = Only a
- class The a where
- data Table a
- data Query s a
- data Row s a
- data Col s a
- type family Res r where ...
- class Typeable (Res r) => Result r
- query :: (MonadSelda m, Result a) => Query (Backend m) a -> m [Res a]
- queryInto :: (MonadSelda m, Relational a) => Table a -> Query (Backend m) (Row (Backend m) a) -> m Int
- transaction :: (MonadSelda m, MonadMask m) => m a -> m a
- withoutForeignKeyEnforcement :: (MonadSelda m, MonadMask m) => m a -> m a
- newUuid :: (MonadIO m, IsUUID uuid) => m uuid
- class Typeable a => SqlType a where
- mkLit :: a -> Lit a
- sqlType :: Proxy a -> SqlTypeRep
- fromSql :: SqlValue -> a
- defaultValue :: Lit a
- class Typeable a => SqlRow a where
- nextResult :: ResultReader a
- nestedCols :: Proxy a -> Int
- class GSqlRow f
- class (Typeable a, Bounded a, Enum a) => SqlEnum a where
- class Columns a
- class s ~ t => Same s t
- data Order
- data a :*: b where
- select :: Relational a => Table a -> Query s (Row s a)
- selectValues :: forall s a. Relational a => [a] -> Query s (Row s a)
- from :: (Typeable t, SqlType a) => Selector t a -> Query s (Row s t) -> Query s (Col s a)
- distinct :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query s (OuterCols a)
- restrict :: Same s t => Col s Bool -> Query t ()
- limit :: Same s t => Int -> Int -> Query (Inner s) a -> Query t (OuterCols a)
- order :: (Same s t, SqlType a) => Col s a -> Order -> Query t ()
- ascending :: Order
- descending :: Order
- orderRandom :: Query s ()
- union :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query (Inner s) a -> Query s (OuterCols a)
- unionAll :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query (Inner s) a -> Query s (OuterCols a)
- inner :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query s (OuterCols a)
- suchThat :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> (a -> Col (Inner s) Bool) -> Query s (OuterCols a)
- data Selector t a
- type family Coalesce a where ...
- class (Relational t, SqlType (FieldType name t), GRSel name (Rep t), NonError (FieldType name t)) => HasField (name :: Symbol) t
- type FieldType name t = GFieldType (Rep t) (NoSuchSelector t name) name
- class IsLabel (x :: Symbol) a
- (!) :: SqlType a => Row s t -> Selector t a -> Col s a
- (?) :: SqlType a => Row s (Maybe t) -> Selector t a -> Col s (Coalesce (Maybe a))
- data Assignment s a where
- (:=) :: Selector t a -> Col s a -> Assignment s t
- with :: Row s a -> [Assignment s a] -> Row s a
- (+=) :: (SqlType a, Num (Col s a)) => Selector t a -> Col s a -> Assignment s t
- (-=) :: (SqlType a, Num (Col s a)) => Selector t a -> Col s a -> Assignment s t
- (*=) :: (SqlType a, Num (Col s a)) => Selector t a -> Col s a -> Assignment s t
- (||=) :: Selector t Bool -> Col s Bool -> Assignment s t
- (&&=) :: Selector t Bool -> Col s Bool -> Assignment s t
- ($=) :: Selector t a -> (Col s a -> Col s a) -> Assignment s t
- class Set set where
- class Semigroup a => Monoid a where
- class Semigroup a where
- (<>) :: a -> a -> a
- data ID a
- invalidId :: ID a
- isInvalidId :: ID a -> Bool
- untyped :: ID a -> RowID
- fromId :: ID a -> Int64
- toId :: Int64 -> ID a
- class IsUUID a where
- data UUID' a
- typedUuid :: UUID -> UUID' a
- untypedUuid :: UUID' a -> UUID
- data RowID
- invalidRowId :: RowID
- isInvalidRowId :: RowID -> Bool
- fromRowId :: RowID -> Int64
- toRowId :: Int64 -> RowID
- (.==) :: (Same s t, SqlType a) => Col s a -> Col t a -> Col s Bool
- (./=) :: (Same s t, SqlType a) => Col s a -> Col t a -> Col s Bool
- (.>) :: (Same s t, SqlOrd a) => Col s a -> Col t a -> Col s Bool
- (.<) :: (Same s t, SqlOrd a) => Col s a -> Col t a -> Col s Bool
- (.>=) :: (Same s t, SqlOrd a) => Col s a -> Col t a -> Col s Bool
- (.<=) :: (Same s t, SqlOrd a) => Col s a -> Col t a -> Col s Bool
- like :: Same s t => Col s Text -> Col t Text -> Col s Bool
- (.&&) :: Same s t => Col s Bool -> Col t Bool -> Col s Bool
- (.||) :: Same s t => Col s Bool -> Col t Bool -> Col s Bool
- not_ :: Col s Bool -> Col s Bool
- literal :: SqlType a => a -> Col s a
- is :: forall r s c. SqlType c => Selector r c -> c -> Row s r -> Col s Bool
- int :: Int -> Col s Int
- float :: Double -> Col s Double
- text :: Text -> Col s Text
- true :: Col s Bool
- false :: Col s Bool
- null_ :: SqlType a => Col s (Maybe a)
- roundTo :: Col s Int -> Col s Double -> Col s Double
- length_ :: Col s Text -> Col s Int
- isNull :: SqlType a => Col s (Maybe a) -> Col s Bool
- ifThenElse :: (Same s t, Same t u, SqlType a) => Col s Bool -> Col t a -> Col u a -> Col s a
- ifNull :: (Same s t, SqlType a) => Col s a -> Col t (Maybe a) -> Col s a
- matchNull :: (SqlType a, SqlType b, Same s t) => Col s b -> (Col s a -> Col s b) -> Col t (Maybe a) -> Col s b
- toUpper :: Col s Text -> Col s Text
- toLower :: Col s Text -> Col s Text
- new :: forall s a. Relational a => [Assignment s a] -> Row s a
- row :: forall s a. Relational a => a -> Row s a
- only :: SqlType a => Col s a -> Row s (Only a)
- class Mappable f where
- round_ :: forall s a. (SqlType a, Num a) => Col s Double -> Col s a
- just :: SqlType a => Col s a -> Col s (Maybe a)
- fromBool :: (SqlType a, Num a) => Col s Bool -> Col s a
- fromInt :: (SqlType a, Num a) => Col s Int -> Col s a
- toString :: SqlType a => Col s a -> Col s Text
- data Aggr s a
- class Aggregates a
- type family OuterCols a where ...
- type family AggrCols a where ...
- type family LeftCols a where ...
- data Inner s
- class SqlType a => SqlOrd a
- innerJoin :: (Columns a, Columns (OuterCols a)) => (OuterCols a -> Col s Bool) -> Query (Inner s) a -> Query s (OuterCols a)
- leftJoin :: (Columns a, Columns (OuterCols a), Columns (LeftCols a)) => (OuterCols a -> Col s Bool) -> Query (Inner s) a -> Query s (LeftCols a)
- aggregate :: (Columns (AggrCols a), Aggregates a) => Query (Inner s) a -> Query s (AggrCols a)
- groupBy :: (Same s t, SqlType a) => Col (Inner s) a -> Query (Inner t) (Aggr (Inner t) a)
- count :: SqlType a => Col s a -> Aggr s Int
- avg :: (SqlType a, Num a) => Col s a -> Aggr s (Maybe a)
- sum_ :: forall a b s. (SqlType a, SqlType b, Num a, Num b) => Col s a -> Aggr s b
- max_ :: SqlOrd a => Col s a -> Aggr s (Maybe a)
- min_ :: SqlOrd a => Col s a -> Aggr s (Maybe a)
- insert :: (MonadSelda m, Relational a) => Table a -> [a] -> m Int
- insert_ :: (MonadSelda m, Relational a) => Table a -> [a] -> m ()
- insertWithPK :: (MonadSelda m, Relational a) => Table a -> [a] -> m (ID a)
- tryInsert :: (MonadSelda m, MonadCatch m, Relational a) => Table a -> [a] -> m Bool
- insertUnless :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> [a] -> m (Maybe (ID a))
- insertWhen :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> [a] -> m (Maybe (ID a))
- def :: SqlType a => a
- update :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> m Int
- update_ :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> m ()
- upsert :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> [a] -> m (Maybe (ID a))
- deleteFrom :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> m Int
- deleteFrom_ :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> m ()
- class Preparable q
- class Prepare q f
- prepared :: (Preparable q, Prepare q f, Equiv q f) => q -> f
- class Generic a
- data TableName
- data ColName
- data Attr a where
- (:-) :: SelectorLike g => g t a -> Attribute g t a -> Attr t
- data Attribute (g :: * -> * -> *) t c
- class ForeignKey a b where
- foreignKey :: Table t -> Selector t a -> Attribute Selector self b
- class SelectorLike g
- data Group t a where
- sel :: Selector t a -> Selector t a
- table :: forall a. Relational a => TableName -> [Attr a] -> Table a
- tableFieldMod :: forall a. Relational a => TableName -> [Attr a] -> (Text -> Text) -> Table a
- primary :: Attribute Group t a
- autoPrimary :: Attribute Selector t (ID t)
- weakAutoPrimary :: Attribute Selector t (ID t)
- untypedAutoPrimary :: Attribute Selector t RowID
- weakUntypedAutoPrimary :: Attribute Selector t RowID
- unique :: Attribute Group t a
- data IndexMethod
- index :: Attribute Group t c
- indexUsing :: IndexMethod -> Attribute Group t c
- createTable :: MonadSelda m => Table a -> m ()
- tryCreateTable :: MonadSelda m => Table a -> m ()
- dropTable :: MonadSelda m => Table a -> m ()
- tryDropTable :: MonadSelda m => Table a -> m ()
- class Tup a
- type family Head a where ...
- first :: Tup a => a -> Head a
- second :: Tup b => (a :*: b) -> Head b
- third :: Tup c => (a :*: (b :*: c)) -> Head c
- fourth :: Tup d => (a :*: (b :*: (c :*: d))) -> Head d
- fifth :: Tup e => (a :*: (b :*: (c :*: (d :*: e)))) -> Head e
- class Monad m => MonadIO (m :: Type -> Type)
- class MonadCatch m => MonadMask (m :: Type -> Type)
- liftIO :: MonadIO m => IO a -> m a
- data Text
- data Day
- data TimeOfDay
- data UTCTime
- data UUID
Running queries
class MonadIO m => MonadSelda m Source #
Some monad with Selda SQL capabilitites.
data SeldaError Source #
Thrown by any function in SeldaT
if an error occurs.
DbError String | Unable to open or connect to database. |
SqlError String | An error occurred while executing query. |
UnsafeError String | An error occurred due to improper use of an unsafe function. |
Instances
Exception SeldaError Source # | |
Defined in Database.Selda.Backend.Internal toException :: SeldaError -> SomeException # fromException :: SomeException -> Maybe SeldaError # displayException :: SeldaError -> String # | |
Show SeldaError Source # | |
Defined in Database.Selda.Backend.Internal showsPrec :: Int -> SeldaError -> ShowS # show :: SeldaError -> String # showList :: [SeldaError] -> ShowS # | |
Eq SeldaError Source # | |
Defined in Database.Selda.Backend.Internal (==) :: SeldaError -> SeldaError -> Bool # (/=) :: SeldaError -> SeldaError -> Bool # |
data ValidationError Source #
An error occurred when validating a database table. If this error is thrown, there is a bug in your database schema, and the particular table that triggered the error is unusable. Since validation is deterministic, this error will be thrown on every consecutive operation over the offending table.
Therefore, it is not meaningful to handle this exception in any way, just fix your bug instead.
Instances
Exception ValidationError Source # | |
Defined in Database.Selda.Table.Validation | |
Show ValidationError Source # | |
Defined in Database.Selda.Table.Validation showsPrec :: Int -> ValidationError -> ShowS # show :: ValidationError -> String # showList :: [ValidationError] -> ShowS # | |
Eq ValidationError Source # | |
Defined in Database.Selda.Table.Validation (==) :: ValidationError -> ValidationError -> Bool # (/=) :: ValidationError -> ValidationError -> Bool # |
Monad transformer adding Selda SQL capabilities.
Instances
type Relational a = (Generic a, SqlRow a, GRelation (Rep a)) Source #
Any type which has a corresponding relation.
To make a Relational
instance for some type, simply derive Generic
.
Note that only types which have a single data constructor, and where all
fields are instances of SqlValue
can be used with this module.
Attempting to use functions in this module with any type which doesn't
obey those constraints will result in a very confusing type error.
Wrapper for single column tables.
Use this when you need a table with only a single column, with table
or
selectValues
.
Only a |
Instances
A database table, based on some Haskell data type.
Any single constructor type can form the basis of a table, as long as
it derives Generic
and all of its fields are instances of SqlType
.
An SQL query.
A database row. A row is a collection of one or more columns.
A database column. A column is often a literal column table, but can also be an expression over such a column or a constant expression.
Instances
Mappable (Col :: Type -> TYPE LiftedRep -> TYPE LiftedRep) Source # | |
(SqlType a, Columns b) => Columns (Col s a :*: b) Source # | |
(SqlType a, Result b) => Result (Col s a :*: b) Source # | |
(SqlType a, Preparable b) => Preparable (Col s a -> b) Source # | |
Defined in Database.Selda.Prepared mkQuery :: MonadSelda m => Int -> (Col s a -> b) -> [SqlTypeRep] -> m CompResult | |
IsString (Col s Text) Source # | |
Defined in Database.Selda.Column fromString :: String -> Col s Text # | |
Monoid (Col s Text) Source # | |
Semigroup (Col s Text) Source # | |
(SqlType a, Num a) => Num (Col s a) Source # | |
Fractional (Col s Double) Source # | |
Fractional (Col s Int) Source # | |
Columns (Col s a) Source # | |
SqlType a => Result (Col s a) Source # | |
type Container (Col :: Type -> TYPE LiftedRep -> TYPE LiftedRep) a Source # | |
class Typeable (Res r) => Result r Source #
An acceptable query result type; one or more columns stitched together
with :*:
.
toRes, finalCols
query :: (MonadSelda m, Result a) => Query (Backend m) a -> m [Res a] Source #
Run a query within a Selda monad. In practice, this is often a SeldaT
transformer on top of some other monad.
Selda transformers are entered using backend-specific withX
functions,
such as withSQLite
from the SQLite backend.
queryInto :: (MonadSelda m, Relational a) => Table a -> Query (Backend m) (Row (Backend m) a) -> m Int Source #
Perform the given query, and insert the result into the given table. Returns the number of inserted rows.
transaction :: (MonadSelda m, MonadMask m) => m a -> m a Source #
Perform the given computation atomically. If an exception is raised during its execution, the entire transaction will be rolled back and the exception re-thrown, even if the exception is caught and handled within the transaction.
withoutForeignKeyEnforcement :: (MonadSelda m, MonadMask m) => m a -> m a Source #
Run the given computation as a transaction without enforcing foreign key constraints.
If the computation finishes with the database in an inconsistent state with regards to foreign keys, the resulting behavior is undefined. Use with extreme caution, preferably only for migrations.
On the PostgreSQL backend, at least PostgreSQL 9.6 is required.
Using this should be avoided in favor of deferred foreign key constraints. See SQL backend documentation for deferred constraints.
newUuid :: (MonadIO m, IsUUID uuid) => m uuid Source #
Generate a new random UUID using the system's random number generator. UUIDs generated this way are (astronomically likely to be) unique, but not necessarily unpredictable.
For applications where unpredictability is crucial, take care to use a proper cryptographic PRNG to generate your UUIDs.
Constructing queries
class Typeable a => SqlType a where Source #
Any datatype representable in (Selda's subset of) SQL.
Nothing
Create a literal of this type.
sqlType :: Proxy a -> SqlTypeRep Source #
The SQL representation for this type.
fromSql :: SqlValue -> a Source #
Convert an SqlValue into this type.
defaultValue :: Lit a Source #
Default value when using def
at this type.
Instances
class Typeable a => SqlRow a where Source #
Nothing
nextResult :: ResultReader a Source #
Read the next, potentially composite, result from a stream of columns.
nestedCols :: Proxy a -> Int Source #
The number of nested columns contained in this type.
Instances
SqlType a => SqlRow (Only a) Source # | |
Defined in Database.Selda nextResult :: ResultReader (Only a) Source # | |
SqlRow a => SqlRow (Maybe a) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (Maybe a) Source # | |
(Typeable (a, b), GSqlRow (Rep (a, b))) => SqlRow (a, b) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (a, b) Source # nestedCols :: Proxy (a, b) -> Int Source # | |
(Typeable (a, b, c), GSqlRow (Rep (a, b, c))) => SqlRow (a, b, c) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (a, b, c) Source # nestedCols :: Proxy (a, b, c) -> Int Source # | |
(Typeable (a, b, c, d), GSqlRow (Rep (a, b, c, d))) => SqlRow (a, b, c, d) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (a, b, c, d) Source # nestedCols :: Proxy (a, b, c, d) -> Int Source # | |
(Typeable (a, b, c, d, e), GSqlRow (Rep (a, b, c, d, e))) => SqlRow (a, b, c, d, e) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (a, b, c, d, e) Source # nestedCols :: Proxy (a, b, c, d, e) -> Int Source # | |
(Typeable (a, b, c, d, e, f), GSqlRow (Rep (a, b, c, d, e, f))) => SqlRow (a, b, c, d, e, f) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (a, b, c, d, e, f) Source # nestedCols :: Proxy (a, b, c, d, e, f) -> Int Source # | |
(Typeable (a, b, c, d, e, f, g), GSqlRow (Rep (a, b, c, d, e, f, g))) => SqlRow (a, b, c, d, e, f, g) Source # | |
Defined in Database.Selda.SqlRow nextResult :: ResultReader (a, b, c, d, e, f, g) Source # nestedCols :: Proxy (a, b, c, d, e, f, g) -> Int Source # |
gNextResult, gNestedCols
Instances
(GSqlRow a, GSqlRow b) => GSqlRow (a :*: b) Source # | |
Defined in Database.Selda.SqlRow gNextResult :: ResultReader ((a :*: b) x) gNestedCols :: Proxy (a :*: b) -> Int | |
(TypeError ('Text "Selda currently does not support creating tables from sum types." :$$: 'Text "Restrict your table type to a single data constructor.") :: Constraint) => GSqlRow (a :+: b) Source # | |
Defined in Database.Selda.SqlRow gNextResult :: ResultReader ((a :+: b) x) gNestedCols :: Proxy (a :+: b) -> Int | |
SqlType a => GSqlRow (K1 i a :: Type -> Type) Source # | |
Defined in Database.Selda.SqlRow gNextResult :: ResultReader (K1 i a x) gNestedCols :: Proxy (K1 i a) -> Int | |
GSqlRow f => GSqlRow (M1 c i f) Source # | |
Defined in Database.Selda.SqlRow gNextResult :: ResultReader (M1 c i f x) gNestedCols :: Proxy (M1 c i f) -> Int |
class (Typeable a, Bounded a, Enum a) => SqlEnum a where Source #
Any type that's bounded, enumerable and has a text representation, and thus representable as a Selda enumerable.
While it would be more efficient to store enumerables as integers, this makes hand-rolled SQL touching the values inscrutable, and will break if the user a) derives Enum and b) changes the order of their constructors. Long-term, this should be implemented in PostgreSQL as a proper enum anyway, which mostly renders the performance argument moot.
Any column tuple.
toTup, fromTup
class s ~ t => Same s t Source #
Denotes that scopes s
and t
are identical.
Instances
Same (s :: k) (s :: k) Source # | |
Defined in Database.Selda.Column | |
(s ~ t, TypeError ('Text "An identifier from an outer scope may not be used in an inner query.") :: Constraint) => Same (s :: k) (t :: k) Source # | |
Defined in Database.Selda.Column |
The order in which to sort result rows.
data a :*: b where infixr 1 Source #
An inductively defined "tuple", or heterogeneous, non-empty list.
Instances
selectValues :: forall s a. Relational a => [a] -> Query s (Row s a) Source #
Query an ad hoc table of type a
. Each element in the given list represents
one row in the ad hoc table.
from :: (Typeable t, SqlType a) => Selector t a -> Query s (Row s t) -> Query s (Col s a) infixr 7 Source #
Convenient shorthand for fmap (! sel) q
.
The following two queries are quivalent:
q1 = name `from` select people q2 = do person <- select people return (person ! name)
distinct :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query s (OuterCols a) Source #
Remove all duplicates from the result set.
restrict :: Same s t => Col s Bool -> Query t () Source #
Restrict the query somehow. Roughly equivalent to WHERE
.
limit :: Same s t => Int -> Int -> Query (Inner s) a -> Query t (OuterCols a) Source #
Drop the first m
rows, then get at most n
of the remaining rows from the
given subquery.
order :: (Same s t, SqlType a) => Col s a -> Order -> Query t () Source #
Sort the result rows in ascending or descending order on the given row.
If multiple order
directives are given, later directives are given
precedence but do not cancel out earlier ordering directives.
To get a list of persons sorted primarily on age and secondarily on name:
peopleInAgeAndNameOrder = do person <- select people order (person ! name) ascending order (person ! age) ascending return (person ! name)
For a table [(Alice, 20), (Bob, 20), (Eve, 18)]
, this query
will always return [Eve, Alice, Bob]
.
The reason for later orderings taking precedence and not the other way
around is composability: order
should always sort the current
result set to avoid weird surprises when a previous order
directive
is buried somewhere deep in an earlier query.
However, the ordering must always be stable, to ensure that previous
calls to order are not simply erased.
descending :: Order Source #
Ordering for order
.
orderRandom :: Query s () Source #
Sort the result rows in random order.
union :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query (Inner s) a -> Query s (OuterCols a) Source #
The set union of two queries. Equivalent to the SQL UNION
operator.
unionAll :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query (Inner s) a -> Query s (OuterCols a) Source #
The multiset union of two queries.
Equivalent to the SQL UNION ALL
operator.
inner :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query s (OuterCols a) Source #
Explicitly create an inner query. Equivalent to innerJoin (const true)
.
Sometimes it's handy, for performance reasons and otherwise, to perform a subquery and restrict only that query before adding the result of the query to the result set, instead of first adding the query to the result set and restricting the whole result set afterwards.
suchThat :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> (a -> Col (Inner s) Bool) -> Query s (OuterCols a) infixr 7 Source #
Create and filter an inner query, before adding it to the current result set.
q
is generally more efficient than
suchThat
pselect q >>= x -> restrict (p x) >> pure x
.
Working with selectors
A column selector. Column selectors can be used together with the !
and
with
functions to get and set values on rows, or to specify
foreign keys.
Instances
SelectorLike Selector Source # | |
Defined in Database.Selda.Table | |
(Relational t, HasField name t, FieldType name t ~ a) => IsLabel name (Selector t a) Source # | |
Defined in Database.Selda.FieldSelectors |
type family Coalesce a where ... Source #
Coalesce nested nullable column into a single level of nesting.
class (Relational t, SqlType (FieldType name t), GRSel name (Rep t), NonError (FieldType name t)) => HasField (name :: Symbol) t Source #
Any table type t
, which has a field named name
.
Instances
(Relational t, SqlType (FieldType name t), GRSel name (Rep t), NonError (FieldType name t)) => HasField name t Source # | |
Defined in Database.Selda.FieldSelectors |
type FieldType name t = GFieldType (Rep t) (NoSuchSelector t name) name Source #
The type of the name
field, in the record type t
.
(!) :: SqlType a => Row s t -> Selector t a -> Col s a infixl 9 Source #
Extract the given column from the given row.
(?) :: SqlType a => Row s (Maybe t) -> Selector t a -> Col s (Coalesce (Maybe a)) infixl 9 Source #
Extract the given column from the given nullable row.
Nullable rows usually result from left joins.
If a nullable column is extracted from a nullable row, the resulting
nested Maybe
s will be squashed into a single level of nesting.
data Assignment s a where Source #
A selector-value assignment pair.
(:=) :: Selector t a -> Col s a -> Assignment s t infixl 2 | Set the given column to the given value. |
with :: Row s a -> [Assignment s a] -> Row s a Source #
For each selector-value pair in the given list, on the given tuple, update the field pointed out by the selector with the corresponding value.
(+=) :: (SqlType a, Num (Col s a)) => Selector t a -> Col s a -> Assignment s t infixl 2 Source #
Add the given column to the column pointed to by the given selector.
(-=) :: (SqlType a, Num (Col s a)) => Selector t a -> Col s a -> Assignment s t infixl 2 Source #
Subtract the given column from the column pointed to by the given selector.
(*=) :: (SqlType a, Num (Col s a)) => Selector t a -> Col s a -> Assignment s t infixl 2 Source #
Multiply the column pointed to by the given selector, by the given column.
(||=) :: Selector t Bool -> Col s Bool -> Assignment s t infixl 2 Source #
Logically OR
the column pointed to by the given selector with
the given column.
(&&=) :: Selector t Bool -> Col s Bool -> Assignment s t infixl 2 Source #
Logically AND
the column pointed to by the given selector with
the given column.
($=) :: Selector t a -> (Col s a -> Col s a) -> Assignment s t infixl 2 Source #
Apply the given function to the given column.
Expressions over columns
Any container type for which we can check object membership.
class Semigroup a => Monoid a where #
The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:
- Right identity
x
<>
mempty
= x- Left identity
mempty
<>
x = x- Associativity
x
(<>
(y<>
z) = (x<>
y)<>
zSemigroup
law)- Concatenation
mconcat
=foldr
(<>
)mempty
The method names refer to the monoid of lists under concatenation, but there are many other instances.
Some types can be viewed as a monoid in more than one way,
e.g. both addition and multiplication on numbers.
In such cases we often define newtype
s and make those instances
of Monoid
, e.g. Sum
and Product
.
NOTE: Semigroup
is a superclass of Monoid
since base-4.11.0.0.
Identity of mappend
>>>
"Hello world" <> mempty
"Hello world"
An associative operation
NOTE: This method is redundant and has the default
implementation
since base-4.11.0.0.
Should it be implemented manually, since mappend
= (<>
)mappend
is a synonym for
(<>
), it is expected that the two functions are defined the same
way. In a future GHC release mappend
will be removed from Monoid
.
Fold a list using the monoid.
For most types, the default definition for mconcat
will be
used, but the function is included in the class definition so
that an optimized version can be provided for specific types.
>>>
mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"
Instances
Monoid All | Since: base-2.1 |
Monoid Any | Since: base-2.1 |
Monoid Builder | |
Monoid ByteString | |
Defined in Data.ByteString.Internal mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ByteString | |
Defined in Data.ByteString.Lazy.Internal mempty :: ByteString # mappend :: ByteString -> ByteString -> ByteString # mconcat :: [ByteString] -> ByteString # | |
Monoid ShortByteString | |
Defined in Data.ByteString.Short.Internal mappend :: ShortByteString -> ShortByteString -> ShortByteString # mconcat :: [ShortByteString] -> ShortByteString # | |
Monoid IntSet | |
Monoid Ordering | Since: base-2.1 |
Monoid () | Since: base-2.1 |
Monoid a => Monoid (Identity a) | Since: base-4.9.0.0 |
Monoid (First a) | Since: base-2.1 |
Monoid (Last a) | Since: base-2.1 |
Monoid a => Monoid (Down a) | Since: base-4.11.0.0 |
(Ord a, Bounded a) => Monoid (Max a) | Since: base-4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: base-4.9.0.0 |
Monoid m => Monoid (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup mempty :: WrappedMonoid m # mappend :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # mconcat :: [WrappedMonoid m] -> WrappedMonoid m # | |
Monoid a => Monoid (Dual a) | Since: base-2.1 |
Monoid (Endo a) | Since: base-2.1 |
Num a => Monoid (Product a) | Since: base-2.1 |
Num a => Monoid (Sum a) | Since: base-2.1 |
Monoid p => Monoid (Par1 p) | Since: base-4.12.0.0 |
Monoid (IntMap a) | |
Monoid (Seq a) | |
Monoid (MergeSet a) | |
Ord a => Monoid (Set a) | |
Monoid a => Monoid (IO a) | Since: base-4.9.0.0 |
Monoid a => Monoid (Q a) | Since: template-haskell-2.17.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Monoid a => Monoid (a) | Since: base-4.15 |
Monoid [a] | Since: base-2.1 |
Monoid (Proxy s) | Since: base-4.7.0.0 |
Monoid (U1 p) | Since: base-4.12.0.0 |
Monoid a => Monoid (ST s a) | Since: base-4.11.0.0 |
Ord k => Monoid (Map k v) | |
Monoid b => Monoid (a -> b) | Since: base-2.1 |
(Monoid a, Monoid b) => Monoid (a, b) | Since: base-2.1 |
Monoid a => Monoid (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Monoid a) => Monoid (Ap f a) | Since: base-4.12.0.0 |
Alternative f => Monoid (Alt f a) | Since: base-4.8.0.0 |
Monoid (f p) => Monoid (Rec1 f p) | Since: base-4.12.0.0 |
Monoid (Col s Text) Source # | |
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) | Since: base-2.1 |
(Monoid (f a), Monoid (g a)) => Monoid (Product f g a) | Since: base-4.16.0.0 |
(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p) | Since: base-4.12.0.0 |
Monoid c => Monoid (K1 i c p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) | Since: base-2.1 |
Monoid (f (g a)) => Monoid (Compose f g a) | Since: base-4.16.0.0 |
Monoid (f (g p)) => Monoid ((f :.: g) p) | Since: base-4.12.0.0 |
Monoid (f p) => Monoid (M1 i c f p) | Since: base-4.12.0.0 |
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e) | Since: base-2.1 |
The class of semigroups (types with an associative binary operation).
Instances should satisfy the following:
Since: base-4.9.0.0
Instances
Semigroup All | Since: base-4.9.0.0 |
Semigroup Any | Since: base-4.9.0.0 |
Semigroup Void | Since: base-4.9.0.0 |
Semigroup Builder | |
Semigroup ByteString | |
Defined in Data.ByteString.Internal (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Semigroup ByteString | |
Defined in Data.ByteString.Lazy.Internal (<>) :: ByteString -> ByteString -> ByteString # sconcat :: NonEmpty ByteString -> ByteString # stimes :: Integral b => b -> ByteString -> ByteString # | |
Semigroup ShortByteString | |
Defined in Data.ByteString.Short.Internal (<>) :: ShortByteString -> ShortByteString -> ShortByteString # sconcat :: NonEmpty ShortByteString -> ShortByteString # stimes :: Integral b => b -> ShortByteString -> ShortByteString # | |
Semigroup IntSet | Since: containers-0.5.7 |
Semigroup Ordering | Since: base-4.9.0.0 |
Semigroup QueryFragment Source # | |
Defined in Database.Selda.SQL (<>) :: QueryFragment -> QueryFragment -> QueryFragment # sconcat :: NonEmpty QueryFragment -> QueryFragment # stimes :: Integral b => b -> QueryFragment -> QueryFragment # | |
Semigroup () | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Identity a) | Since: base-4.9.0.0 |
Semigroup (First a) | Since: base-4.9.0.0 |
Semigroup (Last a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Down a) | Since: base-4.11.0.0 |
Semigroup (First a) | Since: base-4.9.0.0 |
Semigroup (Last a) | Since: base-4.9.0.0 |
Ord a => Semigroup (Max a) | Since: base-4.9.0.0 |
Ord a => Semigroup (Min a) | Since: base-4.9.0.0 |
Monoid m => Semigroup (WrappedMonoid m) | Since: base-4.9.0.0 |
Defined in Data.Semigroup (<>) :: WrappedMonoid m -> WrappedMonoid m -> WrappedMonoid m # sconcat :: NonEmpty (WrappedMonoid m) -> WrappedMonoid m # stimes :: Integral b => b -> WrappedMonoid m -> WrappedMonoid m # | |
Semigroup a => Semigroup (Dual a) | Since: base-4.9.0.0 |
Semigroup (Endo a) | Since: base-4.9.0.0 |
Num a => Semigroup (Product a) | Since: base-4.9.0.0 |
Num a => Semigroup (Sum a) | Since: base-4.9.0.0 |
Semigroup p => Semigroup (Par1 p) | Since: base-4.12.0.0 |
Semigroup (IntMap a) | Since: containers-0.5.7 |
Semigroup (Seq a) | Since: containers-0.5.7 |
Semigroup (MergeSet a) | |
Ord a => Semigroup (Set a) | Since: containers-0.5.7 |
Semigroup a => Semigroup (IO a) | Since: base-4.10.0.0 |
Semigroup a => Semigroup (Q a) | Since: template-haskell-2.17.0.0 |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (a) | Since: base-4.15 |
Semigroup [a] | Since: base-4.9.0.0 |
Semigroup (Either a b) | Since: base-4.9.0.0 |
Semigroup (Proxy s) | Since: base-4.9.0.0 |
Semigroup (U1 p) | Since: base-4.12.0.0 |
Semigroup (V1 p) | Since: base-4.12.0.0 |
Semigroup a => Semigroup (ST s a) | Since: base-4.11.0.0 |
Ord k => Semigroup (Map k v) | |
Semigroup b => Semigroup (a -> b) | Since: base-4.9.0.0 |
(Semigroup a, Semigroup b) => Semigroup (a, b) | Since: base-4.9.0.0 |
Semigroup a => Semigroup (Const a b) | Since: base-4.9.0.0 |
(Applicative f, Semigroup a) => Semigroup (Ap f a) | Since: base-4.12.0.0 |
Alternative f => Semigroup (Alt f a) | Since: base-4.9.0.0 |
Semigroup (f p) => Semigroup (Rec1 f p) | Since: base-4.12.0.0 |
Semigroup (Col s Text) Source # | |
(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c) | Since: base-4.9.0.0 |
(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a) | Since: base-4.16.0.0 |
(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p) | Since: base-4.12.0.0 |
Semigroup c => Semigroup (K1 i c p) | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d) | Since: base-4.9.0.0 |
Semigroup (f (g a)) => Semigroup (Compose f g a) | Since: base-4.16.0.0 |
Semigroup (f (g p)) => Semigroup ((f :.: g) p) | Since: base-4.12.0.0 |
Semigroup (f p) => Semigroup (M1 i c f p) | Since: base-4.12.0.0 |
(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e) | Since: base-4.9.0.0 |
A typed row identifier.
Generic tables should use this instead of RowID
.
Use untyped
to erase the type of a row identifier, and cast
from the
Database.Selda.Unsafe module if you for some reason need to add a type
to a row identifier.
A typed row identifier which is guaranteed to not match any row in any table.
isInvalidId :: ID a -> Bool Source #
Is the given typed row identifier invalid? I.e. is it guaranteed to not match any row in any table?
fromId :: ID a -> Int64 Source #
Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.
toId :: Int64 -> ID a Source #
Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.
Any type which is backed by an UUID.
An UUID identifying a database row.
typedUuid :: UUID -> UUID' a Source #
Convert an untyped UUID to a typed one. Use sparingly, preferably only during deserialization.
untypedUuid :: UUID' a -> UUID Source #
A row identifier for some table. This is the type of auto-incrementing primary keys.
invalidRowId :: RowID Source #
A row identifier which is guaranteed to not match any row in any table.
isInvalidRowId :: RowID -> Bool Source #
Is the given row identifier invalid? I.e. is it guaranteed to not match any row in any table?
toRowId :: Int64 -> RowID Source #
Create a row identifier from an integer. Use with caution, preferably only when reading user input.
(.==) :: (Same s t, SqlType a) => Col s a -> Col t a -> Col s Bool infixl 4 Source #
Comparisons over columns.
Note that when comparing nullable (i.e. Maybe
) columns, SQL NULL
semantics are used. This means that comparing to a NULL
field will remove
the row in question from the current set.
To test for NULL
, use isNull
instead of .== literal Nothing
.
(./=) :: (Same s t, SqlType a) => Col s a -> Col t a -> Col s Bool infixl 4 Source #
Comparisons over columns.
Note that when comparing nullable (i.e. Maybe
) columns, SQL NULL
semantics are used. This means that comparing to a NULL
field will remove
the row in question from the current set.
To test for NULL
, use isNull
instead of .== literal Nothing
.
like :: Same s t => Col s Text -> Col t Text -> Col s Bool infixl 4 Source #
The SQL LIKE
operator; matches strings with %
wildcards.
For instance:
"%gon" `like` "dragon" .== true
is :: forall r s c. SqlType c => Selector r c -> c -> Row s r -> Col s Bool Source #
Returns true
if the given field in the given row is equal to the given
literal.
roundTo :: Col s Int -> Col s Double -> Col s Double Source #
Round a column to the given number of decimals places.
ifThenElse :: (Same s t, Same t u, SqlType a) => Col s Bool -> Col t a -> Col u a -> Col s a Source #
Perform a conditional on a column
ifNull :: (Same s t, SqlType a) => Col s a -> Col t (Maybe a) -> Col s a Source #
If the second value is Nothing, return the first value. Otherwise return the second value.
matchNull :: (SqlType a, SqlType b, Same s t) => Col s b -> (Col s a -> Col s b) -> Col t (Maybe a) -> Col s b Source #
Applies the given function to the given nullable column where it isn't null, and returns the given default value where it is.
This is the Selda equivalent of maybe
.
new :: forall s a. Relational a => [Assignment s a] -> Row s a Source #
Create a new row with the given fields. Any unassigned fields will contain their default values.
row :: forall s a. Relational a => a -> Row s a Source #
Create a new row from the given value. This can be useful when you want to update all or most of a row:
update users (#uid `is` user_id) (\old -> row user_info `with` [...])
only :: SqlType a => Col s a -> Row s (Only a) Source #
Create a singleton table column from an appropriate value.
class Mappable f where Source #
Any container type which can be mapped over.
Sort of like Functor
, if you squint a bit.
(.<$>) :: (SqlType a, SqlType b) => (Col s a -> Col s b) -> f s (Container f a) -> f s (Container f b) infixl 4 Source #
Converting between column types
round_ :: forall s a. (SqlType a, Num a) => Col s Double -> Col s a Source #
Round a value to the nearest integer. Equivalent to roundTo 0
.
just :: SqlType a => Col s a -> Col s (Maybe a) Source #
Lift a non-nullable column to a nullable one. Useful for creating expressions over optional columns:
data Person = Person {name :: Text, age :: Int, pet :: Maybe Text} deriving Generic instance SqlRow Person people :: Table Person people = table "people" [] peopleWithCats = do person <- select people restrict (person ! #pet .== just "cat") return (person ! #name)
fromBool :: (SqlType a, Num a) => Col s Bool -> Col s a Source #
Convert a boolean column to any numeric type.
fromInt :: (SqlType a, Num a) => Col s Int -> Col s a Source #
Convert an integer column to any numeric type.
Inner queries
A single aggregate column.
Aggregate columns may not be used to restrict queries.
When returned from an aggregate
subquery, an aggregate column is
converted into a non-aggregate column.
Instances
Mappable Aggr Source # | |
Aggregates (Aggr (Inner s) a) Source # | |
Defined in Database.Selda.Inner | |
Aggregates b => Aggregates (Aggr (Inner s) a :*: b) Source # | |
Defined in Database.Selda.Inner | |
type Container Aggr a Source # | |
Defined in Database.Selda |
class Aggregates a Source #
One or more aggregate columns.
unAggrs
Instances
Aggregates (Aggr (Inner s) a) Source # | |
Defined in Database.Selda.Inner | |
Aggregates b => Aggregates (Aggr (Inner s) a :*: b) Source # | |
Defined in Database.Selda.Inner |
type family OuterCols a where ... Source #
Convert one or more inner column to equivalent columns in the outer query.
OuterCols (Aggr (Inner s) a :*: Aggr (Inner s) b) = Col s a :*: Col s b
,
for instance.
OuterCols (Col (Inner s) a :*: b) = Col s a :*: OuterCols b | |
OuterCols (Col (Inner s) a) = Col s a | |
OuterCols (Row (Inner s) a :*: b) = Row s a :*: OuterCols b | |
OuterCols (Row (Inner s) a) = Row s a | |
OuterCols (Col s a) = TypeError ('Text "An inner query can only return rows and columns from its own scope.") | |
OuterCols (Row s a) = TypeError ('Text "An inner query can only return rows and columns from its own scope.") | |
OuterCols a = TypeError ('Text "Only (inductive tuples of) row and columns can be returned from" :$$: 'Text "an inner query.") |
type family AggrCols a where ... Source #
AggrCols (Aggr (Inner s) a :*: b) = Col s a :*: AggrCols b | |
AggrCols (Aggr (Inner s) a) = Col s a | |
AggrCols (Aggr s a) = TypeError ('Text "An aggregate query can only return columns from its own" :$$: 'Text "scope.") | |
AggrCols a = TypeError ('Text "Only (inductive tuples of) aggregates can be returned from" :$$: 'Text "an aggregate query.") |
type family LeftCols a where ... Source #
The results of a left join are always nullable, as there is no guarantee
that all joined columns will be non-null.
JoinCols a
where a
is an extensible tuple is that same tuple, but in
the outer query and with all elements nullable.
For instance:
LeftCols (Col (Inner s) Int :*: Col (Inner s) Text) = Col s (Maybe Int) :*: Col s (Maybe Text)
LeftCols (Col (Inner s) (Maybe a) :*: b) = Col s (Maybe a) :*: LeftCols b | |
LeftCols (Col (Inner s) a :*: b) = Col s (Maybe a) :*: LeftCols b | |
LeftCols (Col (Inner s) (Maybe a)) = Col s (Maybe a) | |
LeftCols (Col (Inner s) a) = Col s (Maybe a) | |
LeftCols (Row (Inner s) (Maybe a) :*: b) = Row s (Maybe a) :*: LeftCols b | |
LeftCols (Row (Inner s) a :*: b) = Row s (Maybe a) :*: LeftCols b | |
LeftCols (Row (Inner s) (Maybe a)) = Row s (Maybe a) | |
LeftCols (Row (Inner s) a) = Row s (Maybe a) | |
LeftCols a = TypeError ('Text "Only (inductive tuples of) rows and columns can be returned" :$$: 'Text "from a join.") |
Denotes an inner query.
For aggregation, treating sequencing as the cartesian product of queries
does not work well.
Instead, we treat the sequencing of aggregate
with other
queries as the cartesian product of the aggregated result of the query,
a small but important difference.
However, for this to work, the aggregate query must not depend on any
columns in the outer product. Therefore, we let the aggregate query be
parameterized over Inner s
if the parent query is parameterized over s
,
to enforce this separation.
Instances
Aggregates (Aggr (Inner s) a) Source # | |
Defined in Database.Selda.Inner | |
Aggregates b => Aggregates (Aggr (Inner s) a :*: b) Source # | |
Defined in Database.Selda.Inner |
class SqlType a => SqlOrd a Source #
Instances
SqlOrd RowID Source # | |
Defined in Database.Selda | |
SqlOrd Text Source # | |
Defined in Database.Selda | |
SqlOrd Day Source # | |
Defined in Database.Selda | |
SqlOrd UTCTime Source # | |
Defined in Database.Selda | |
SqlOrd TimeOfDay Source # | |
Defined in Database.Selda | |
(SqlType a, Num a) => SqlOrd a Source # | |
Defined in Database.Selda | |
Typeable a => SqlOrd (ID a) Source # | |
Defined in Database.Selda | |
SqlOrd a => SqlOrd (Maybe a) Source # | |
Defined in Database.Selda |
:: (Columns a, Columns (OuterCols a)) | |
=> (OuterCols a -> Col s Bool) | Predicate determining which lines to join. | Right-hand query to join. |
-> Query (Inner s) a | |
-> Query s (OuterCols a) |
Perform an INNER JOIN
with the current result set and the given query.
:: (Columns a, Columns (OuterCols a), Columns (LeftCols a)) | |
=> (OuterCols a -> Col s Bool) | Predicate determining which lines to join. | Right-hand query to join. |
-> Query (Inner s) a | |
-> Query s (LeftCols a) |
Perform a LEFT JOIN
with the current result set (i.e. the outer query)
as the left hand side, and the given query as the right hand side.
Like with aggregate
, the inner (or right) query must not depend on the
outer (or right) one.
The given predicate over the values returned by the inner query determines for each row whether to join or not. This predicate may depend on any values from the outer query.
For instance, the following will list everyone in the people
table
together with their address if they have one; if they don't, the address
field will be NULL
.
getAddresses :: Query s (Col s Text :*: Col s (Maybe Text)) getAddresses = do (name :*: _) <- select people (_ :*: address) <- leftJoin (\(n :*: _) -> n .== name) (select addresses) return (name :*: address)
aggregate :: (Columns (AggrCols a), Aggregates a) => Query (Inner s) a -> Query s (AggrCols a) Source #
Execute a query, returning an aggregation of its results.
The query must return an inductive tuple of Aggregate
columns.
When aggregate
returns, those columns are converted into non-aggregate
columns, which may then be used to further restrict the query.
Note that aggregate queries must not depend on outer queries, nor must they return any non-aggregate columns. Attempting to do either results in a type error.
The SQL HAVING
keyword can be implemented by combining aggregate
and restrict
:
-- Find the number of people living on every address, for all addresses -- with more than one tenant: -- SELECT COUNT(name) AS c, address FROM housing GROUP BY name HAVING c > 1 numPpl = do (num_tenants :*: theAddress) <- aggregate $ do h <- select housing theAddress <- groupBy (h ! address) return (count (h ! address) :*: theAddress) restrict (num_tenants .> 1) return (num_tenants :*: theAddress)
groupBy :: (Same s t, SqlType a) => Col (Inner s) a -> Query (Inner t) (Aggr (Inner t) a) Source #
Group an aggregate query by a column. Attempting to group a non-aggregate query is a type error. An aggregate representing the grouped-by column is returned, which can be returned from the aggregate query. For instance, if you want to find out how many people have a pet at home:
aggregate $ do person <- select people name' <- groupBy (person ! name) return (name' :*: count(person ! pet_name) .> 0)
count :: SqlType a => Col s a -> Aggr s Int Source #
The number of non-null values in the given column.
avg :: (SqlType a, Num a) => Col s a -> Aggr s (Maybe a) Source #
The average of all values in the given column.
sum_ :: forall a b s. (SqlType a, SqlType b, Num a, Num b) => Col s a -> Aggr s b Source #
Sum all values in the given column.
max_ :: SqlOrd a => Col s a -> Aggr s (Maybe a) Source #
The greatest value in the given column. Texts are compared lexically.
min_ :: SqlOrd a => Col s a -> Aggr s (Maybe a) Source #
The smallest value in the given column. Texts are compared lexically.
Modifying tables
insert :: (MonadSelda m, Relational a) => Table a -> [a] -> m Int Source #
Insert the given values into the given table. All columns of the table
must be present. If your table has an auto-incrementing primary key,
use the special value def
for that column to get the auto-incrementing
behavior.
Returns the number of rows that were inserted.
To insert a list of tuples into a table with auto-incrementing primary key:
data Person = Person { id :: ID Person , name :: Text , age :: Int , pet :: Maybe Text } deriving Generic instance SqlResult Person people :: Table Person people = table "people" [autoPrimary :- id] main = withSQLite "my_database.sqlite" $ do insert_ people [ Person def "Link" 125 (Just "horse") , Person def "Zelda" 119 Nothing , ... ]
Note that if one or more of the inserted rows would cause a constraint violation, NO rows will be inserted; the whole insertion fails atomically.
insert_ :: (MonadSelda m, Relational a) => Table a -> [a] -> m () Source #
Like insert
, but does not return anything.
Use this when you really don't care about how many rows were inserted.
insertWithPK :: (MonadSelda m, Relational a) => Table a -> [a] -> m (ID a) Source #
Like insert
, but returns the primary key of the last inserted row.
Attempting to run this operation on a table without an auto-incrementing
primary key will always return a row identifier that is guaranteed to not
match any row in any table.
tryInsert :: (MonadSelda m, MonadCatch m, Relational a) => Table a -> [a] -> m Bool Source #
Attempt to insert a list of rows into a table, but don't raise an error
if the insertion fails. Returns True
if the insertion succeeded, otherwise
False
.
Like insert
, if even one of the inserted rows would cause a constraint
violation, the whole insert operation fails.
insertUnless :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> [a] -> m (Maybe (ID a)) Source #
Perform the given insert, if no rows already present in the table match
the given predicate.
Returns the primary key of the last inserted row,
if the insert was performed.
If called on a table which doesn't have an auto-incrementing primary key,
Just id
is always returned on successful insert, where id
is a row
identifier guaranteed to not match any row in any table.
insertWhen :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> [a] -> m (Maybe (ID a)) Source #
Like insertUnless
, but performs the insert when at least one row matches
the predicate.
def :: SqlType a => a Source #
The default value for a column during insertion. For an auto-incrementing primary key, the default value is the next key.
Using def
in any other context than insertion results in a runtime error.
:: (MonadSelda m, Relational a) | |
=> Table a | Table to update. |
-> (Row (Backend m) a -> Col (Backend m) Bool) | Predicate. |
-> (Row (Backend m) a -> Row (Backend m) a) | Update function. |
-> m Int |
Update the given table using the given update function, for all rows matching the given predicate. Returns the number of updated rows.
update_ :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> m () Source #
Like update
, but doesn't return the number of updated rows.
upsert :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> [a] -> m (Maybe (ID a)) Source #
Attempt to perform the given update. If no rows were updated, insert the
given row.
Returns the primary key of the inserted row, if the insert was performed.
Calling this function on a table which does not have a primary key will
return Just id
on a successful insert, where id
is a row identifier
guaranteed to not match any row in any table.
Note that this may perform two separate queries: one update, potentially followed by one insert.
deleteFrom :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> m Int Source #
From the given table, delete all rows matching the given predicate. Returns the number of deleted rows.
deleteFrom_ :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> m () Source #
Like deleteFrom
, but does not return the number of deleted rows.
Prepared statements
class Preparable q Source #
mkQuery
Instances
Result a => Preparable (Query s a) Source # | |
Defined in Database.Selda.Prepared mkQuery :: MonadSelda m => Int -> Query s a -> [SqlTypeRep] -> m CompResult | |
(SqlType a, Preparable b) => Preparable (Col s a -> b) Source # | |
Defined in Database.Selda.Prepared mkQuery :: MonadSelda m => Int -> (Col s a -> b) -> [SqlTypeRep] -> m CompResult |
Some parameterized query q
that can be prepared into a function f
in some MonadSelda
.
mkFun
prepared :: (Preparable q, Prepare q f, Equiv q f) => q -> f Source #
Create a prepared Selda function. A prepared function has zero or more arguments, and will get compiled into a prepared statement by the first backend to execute it. Any subsequent calls to the function for the duration of the connection to the database will reuse the prepared statement.
Preparable functions are of the form
(SqlType a, SqlType b, ...) => Col s a -> Col s b -> ... -> Query s r
.
The resulting prepared function will be of the form
MonadSelda m => a -> b -> ... -> m [Res r]
.
Note, however, that when using prepared
, you must give a concrete type
for m
due to how Haskell's type class resolution works.
Prepared functions rely on memoization for just-in-time preparation and
caching. This means that if GHC accidentally inlines your prepared function,
it may get prepared twice.
While this does not affect the correctness of your program, and is
fairly unlikely to happen, if you want to be absolutely sure that your
queries aren't re-prepared more than absolutely necessary,
consider adding a NOINLINE
annotation to each prepared function.
Note that when using a constrained backend type variable (i.e.
foo :: Bar b => SeldaM b [Int]
), optimizations must be enabled for
prepared statements to be effective.
A usage example:
persons :: Table (Text, Int) (persons, name :*: age) = tableWithSelectors "ages" [name :- primary] {-# NOINLINE ageOf #-} ageOf :: Text -> SeldaM [Int] ageOf = prepared $ \n -> do person <- select ages restrict $ (person!name .== n) return age
Defining schemas
Representable types of kind *
.
This class is derivable in GHC with the DeriveGeneric
flag on.
A Generic
instance must satisfy the following laws:
from
.to
≡id
to
.from
≡id
Instances
Name of a database table.