selda-0.3.3.0: Multi-backend, high-level EDSL for interacting with SQL databases.

Safe HaskellNone
LanguageHaskell2010

Database.Selda

Contents

Description

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

Running queries

class MonadIO m => MonadSelda m Source #

Some monad with Selda SQL capabilitites.

Note that the default implementations of invalidateTable and wrapTransaction flush the entire cache and disable caching when invoked. If you want to use Selda's built-in caching mechanism, you will need to implement these operations yourself.

Minimal complete definition

seldaConnection

Instances
(MonadIO m, MonadMask m) => MonadSelda (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

data SeldaError Source #

Thrown by any function in SeldaT if an error occurs.

Constructors

DbError String

Unable to open or connect to database.

SqlError String

An error occurred while executing query.

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.

data SeldaT m a Source #

Monad transformer adding Selda SQL capabilities.

Instances
MonadTrans SeldaT Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

lift :: Monad m => m a -> SeldaT m a #

Monad m => Monad (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

(>>=) :: SeldaT m a -> (a -> SeldaT m b) -> SeldaT m b #

(>>) :: SeldaT m a -> SeldaT m b -> SeldaT m b #

return :: a -> SeldaT m a #

fail :: String -> SeldaT m a #

Functor m => Functor (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

fmap :: (a -> b) -> SeldaT m a -> SeldaT m b #

(<$) :: a -> SeldaT m b -> SeldaT m a #

Monad m => Applicative (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

pure :: a -> SeldaT m a #

(<*>) :: SeldaT m (a -> b) -> SeldaT m a -> SeldaT m b #

liftA2 :: (a -> b -> c) -> SeldaT m a -> SeldaT m b -> SeldaT m c #

(*>) :: SeldaT m a -> SeldaT m b -> SeldaT m b #

(<*) :: SeldaT m a -> SeldaT m b -> SeldaT m a #

MonadIO m => MonadIO (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

liftIO :: IO a -> SeldaT m a #

MonadThrow m => MonadThrow (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

throwM :: Exception e => e -> SeldaT m a #

MonadCatch m => MonadCatch (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

catch :: Exception e => SeldaT m a -> (e -> SeldaT m a) -> SeldaT m a #

MonadMask m => MonadMask (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

mask :: ((forall a. SeldaT m a -> SeldaT m a) -> SeldaT m b) -> SeldaT m b #

uninterruptibleMask :: ((forall a. SeldaT m a -> SeldaT m a) -> SeldaT m b) -> SeldaT m b #

generalBracket :: SeldaT m a -> (a -> ExitCase b -> SeldaT m c) -> (a -> SeldaT m b) -> SeldaT m (b, c) #

(MonadIO m, MonadMask m) => MonadSelda (SeldaT m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

type SeldaM = SeldaT IO Source #

The simplest form of Selda computation; SeldaT specialized to IO.

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.

newtype Only a Source #

Wrapper for single column tables. Use this when you need a table with only a single column, with table or selectValues.

Constructors

Only a 
Instances
Enum a => Enum (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

succ :: Only a -> Only a #

pred :: Only a -> Only a #

toEnum :: Int -> Only a #

fromEnum :: Only a -> Int #

enumFrom :: Only a -> [Only a] #

enumFromThen :: Only a -> Only a -> [Only a] #

enumFromTo :: Only a -> Only a -> [Only a] #

enumFromThenTo :: Only a -> Only a -> Only a -> [Only a] #

Eq a => Eq (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Fractional a => Fractional (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

(/) :: Only a -> Only a -> Only a #

recip :: Only a -> Only a #

fromRational :: Rational -> Only a #

Integral a => Integral (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

quot :: Only a -> Only a -> Only a #

rem :: Only a -> Only a -> Only a #

div :: Only a -> Only a -> Only a #

mod :: Only a -> Only a -> Only a #

quotRem :: Only a -> Only a -> (Only a, Only a) #

divMod :: Only a -> Only a -> (Only a, Only a) #

toInteger :: Only a -> Integer #

Num a => Num (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

(+) :: Only a -> Only a -> Only a #

(-) :: Only a -> Only a -> Only a #

(*) :: Only a -> Only a -> Only a #

negate :: Only a -> Only a #

abs :: Only a -> Only a #

signum :: Only a -> Only a #

fromInteger :: Integer -> Only a #

Ord a => Ord (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Read a => Read (Only a) Source # 
Instance details

Defined in Database.Selda

Real a => Real (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

toRational :: Only a -> Rational #

Show a => Show (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

IsString a => IsString (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

fromString :: String -> Only a #

Generic (Only a) Source # 
Instance details

Defined in Database.Selda

Associated Types

type Rep (Only a) :: * -> * #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

((TypeError (((Text "'Only " :<>: ShowType a) :<>: Text "' is not a proper SQL type.") :$$: Text "Use 'the' to access the value of the column.") :: Constraint), Typeable a) => SqlType (Only a) Source # 
Instance details

Defined in Database.Selda

SqlType a => SqlRow (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

nextResult :: ResultReader (Only a) Source #

nestedCols :: Proxy (Only a) -> Int Source #

The (Only a) Source # 
Instance details

Defined in Database.Selda

Associated Types

type TheOnly (Only a) :: * Source #

Methods

the :: Only a -> TheOnly (Only a) Source #

The (Row s (Only a)) Source # 
Instance details

Defined in Database.Selda

Associated Types

type TheOnly (Row s (Only a)) :: * Source #

Methods

the :: Row s (Only a) -> TheOnly (Row s (Only a)) Source #

type Rep (Only a) Source # 
Instance details

Defined in Database.Selda

type Rep (Only a) = D1 (MetaData "Only" "Database.Selda" "selda-0.3.3.0-GxVWUpfGA49LgGAKQcv3nM" True) (C1 (MetaCons "Only" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type TheOnly (Only a) Source # 
Instance details

Defined in Database.Selda

type TheOnly (Only a) = a
type TheOnly (Row s (Only a)) Source # 
Instance details

Defined in Database.Selda

type TheOnly (Row s (Only a)) = Col s a

class The a where Source #

Minimal complete definition

the

Associated Types

type TheOnly a Source #

Methods

the :: a -> TheOnly a Source #

Extract the value of a row from a singleton table.

Instances
The (Only a) Source # 
Instance details

Defined in Database.Selda

Associated Types

type TheOnly (Only a) :: * Source #

Methods

the :: Only a -> TheOnly (Only a) Source #

The (Row s (Only a)) Source # 
Instance details

Defined in Database.Selda

Associated Types

type TheOnly (Row s (Only a)) :: * Source #

Methods

the :: Row s (Only a) -> TheOnly (Row s (Only a)) Source #

data Table a Source #

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.

data Query s a Source #

An SQL query.

Instances
Monad (Query s) Source # 
Instance details

Defined in Database.Selda.Query.Type

Methods

(>>=) :: Query s a -> (a -> Query s b) -> Query s b #

(>>) :: Query s a -> Query s b -> Query s b #

return :: a -> Query s a #

fail :: String -> Query s a #

Functor (Query s) Source # 
Instance details

Defined in Database.Selda.Query.Type

Methods

fmap :: (a -> b) -> Query s a -> Query s b #

(<$) :: a -> Query s b -> Query s a #

Applicative (Query s) Source # 
Instance details

Defined in Database.Selda.Query.Type

Methods

pure :: a -> Query s a #

(<*>) :: Query s (a -> b) -> Query s a -> Query s b #

liftA2 :: (a -> b -> c) -> Query s a -> Query s b -> Query s c #

(*>) :: Query s a -> Query s b -> Query s b #

(<*) :: Query s a -> Query s b -> Query s a #

Set (Query s) Source # 
Instance details

Defined in Database.Selda

Methods

isIn :: SqlType a => Col s0 a -> Query s (Col s0 a) -> Col s0 Bool Source #

Result a => Preparable (Query s a) Source # 
Instance details

Defined in Database.Selda.Prepared

Methods

mkQuery :: MonadSelda m => Int -> Query s a -> [SqlTypeRep] -> m CompResult

data Row s a Source #

A database row. A row is a collection of one or more columns.

Instances
(SqlRow a, Columns b) => Columns (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Row s a :*: b

fromTup :: (Row s a :*: b) -> [UntypedCol SQL]

(SqlRow a, Result b) => Result (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Row s a :*: b) :: * Source #

Methods

toRes :: Proxy (Row s a :*: b) -> ResultReader (Res (Row s a :*: b))

finalCols :: (Row s a :*: b) -> [SomeCol SQL]

Columns (Row s a) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Row s a

fromTup :: Row s a -> [UntypedCol SQL]

SqlRow a => Result (Row s a) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Row s a) :: * Source #

Methods

toRes :: Proxy (Row s a) -> ResultReader (Res (Row s a))

finalCols :: Row s a -> [SomeCol SQL]

The (Row s (Only a)) Source # 
Instance details

Defined in Database.Selda

Associated Types

type TheOnly (Row s (Only a)) :: * Source #

Methods

the :: Row s (Only a) -> TheOnly (Row s (Only a)) Source #

type Res (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Row s a :*: b) = a :*: Res b
type Res (Row s a) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Row s a) = a
type TheOnly (Row s (Only a)) Source # 
Instance details

Defined in Database.Selda

type TheOnly (Row s (Only a)) = Col s a

data Col s a Source #

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 :: * -> * -> *) Source # 
Instance details

Defined in Database.Selda

Associated Types

type Container Col a :: * Source #

Methods

(.<$>) :: (SqlType a, SqlType b) => (Col s a -> Col s b) -> Col s (Container Col a) -> Col s (Container Col b) Source #

(SqlType a, Columns b) => Columns (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Col s a :*: b

fromTup :: (Col s a :*: b) -> [UntypedCol SQL]

(SqlType a, Result b) => Result (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Col s a :*: b) :: * Source #

Methods

toRes :: Proxy (Col s a :*: b) -> ResultReader (Res (Col s a :*: b))

finalCols :: (Col s a :*: b) -> [SomeCol SQL]

(SqlType a, Preparable b) => Preparable (Col s a -> b) Source # 
Instance details

Defined in Database.Selda.Prepared

Methods

mkQuery :: MonadSelda m => Int -> (Col s a -> b) -> [SqlTypeRep] -> m CompResult

Fractional (Col s Int) Source # 
Instance details

Defined in Database.Selda.Column

Methods

(/) :: Col s Int -> Col s Int -> Col s Int #

recip :: Col s Int -> Col s Int #

fromRational :: Rational -> Col s Int #

Fractional (Col s Double) Source # 
Instance details

Defined in Database.Selda.Column

(SqlType a, Num a) => Num (Col s a) Source # 
Instance details

Defined in Database.Selda.Column

Methods

(+) :: Col s a -> Col s a -> Col s a #

(-) :: Col s a -> Col s a -> Col s a #

(*) :: Col s a -> Col s a -> Col s a #

negate :: Col s a -> Col s a #

abs :: Col s a -> Col s a #

signum :: Col s a -> Col s a #

fromInteger :: Integer -> Col s a #

IsString (Col s Text) Source # 
Instance details

Defined in Database.Selda.Column

Methods

fromString :: String -> Col s Text #

Columns (Col s a) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Col s a

fromTup :: Col s a -> [UntypedCol SQL]

SqlType a => Result (Col s a) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Col s a) :: * Source #

Methods

toRes :: Proxy (Col s a) -> ResultReader (Res (Col s a))

finalCols :: Col s a -> [SomeCol SQL]

type Container (Col :: * -> * -> *) a Source # 
Instance details

Defined in Database.Selda

type Container (Col :: * -> * -> *) a = Maybe a
type Res (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Col s a :*: b) = a :*: Res b
type Res (Col s a) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Col s a) = a

type family Res r Source #

Instances
type Res (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Row s a :*: b) = a :*: Res b
type Res (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Col s a :*: b) = a :*: Res b
type Res (Col s a) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Col s a) = a
type Res (Row s a) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Row s a) = a

class Typeable (Res r) => Result r Source #

An acceptable query result type; one or more columns stitched together with :*:.

Minimal complete definition

toRes, finalCols

Instances
(SqlRow a, Result b) => Result (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Row s a :*: b) :: * Source #

Methods

toRes :: Proxy (Row s a :*: b) -> ResultReader (Res (Row s a :*: b))

finalCols :: (Row s a :*: b) -> [SomeCol SQL]

(SqlType a, Result b) => Result (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Col s a :*: b) :: * Source #

Methods

toRes :: Proxy (Col s a :*: b) -> ResultReader (Res (Col s a :*: b))

finalCols :: (Col s a :*: b) -> [SomeCol SQL]

SqlType a => Result (Col s a) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Col s a) :: * Source #

Methods

toRes :: Proxy (Col s a) -> ResultReader (Res (Col s a))

finalCols :: Col s a -> [SomeCol SQL]

SqlRow a => Result (Row s a) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Row s a) :: * Source #

Methods

toRes :: Proxy (Row s a) -> ResultReader (Res (Row s a))

finalCols :: Row s a -> [SomeCol SQL]

query :: (MonadSelda m, Result a) => Query s 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 s (Row s 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 => 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.

setLocalCache :: MonadIO m => Int -> m () Source #

Set the maximum local cache size to n. A cache size of zero disables local cache altogether. Changing the cache size will also flush all entries. Note that the cache is shared among all Selda computations running within the same process.

By default, local caching is turned off.

WARNING: local caching is guaranteed to be consistent with the underlying database, ONLY under the assumption that no other process will modify it. Also note that the cache is shared between ALL Selda computations running within the same process.

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.

Constructing queries

class Typeable a => SqlType a where Source #

Any datatype representable in (Selda's subset of) SQL.

Methods

mkLit :: a -> Lit a Source #

Create a literal of this type.

mkLit :: (Typeable a, SqlEnum a) => a -> Lit a Source #

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.

fromSql :: (Typeable a, SqlEnum a) => SqlValue -> a Source #

Convert an SqlValue into this type.

defaultValue :: Lit a Source #

Default value when using def at this type.

defaultValue :: (Typeable a, SqlEnum a) => Lit a Source #

Default value when using def at this type.

Instances
SqlType Bool Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Double Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Int Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Ordering Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType ByteString Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType ByteString Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType TimeOfDay Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType UTCTime Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Day Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType a => SqlType (Maybe a) Source # 
Instance details

Defined in Database.Selda.SqlType

Typeable a => SqlType (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

((TypeError (((Text "'Only " :<>: ShowType a) :<>: Text "' is not a proper SQL type.") :$$: Text "Use 'the' to access the value of the column.") :: Constraint), Typeable a) => SqlType (Only a) Source # 
Instance details

Defined in Database.Selda

class Typeable a => SqlRow a where Source #

Methods

nextResult :: ResultReader a Source #

Read the next, potentially composite, result from a stream of columns.

nextResult :: (Generic a, GSqlRow (Rep a)) => 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.

nestedCols :: (Generic a, GSqlRow (Rep a)) => Proxy a -> Int Source #

The number of nested columns contained in this type.

Instances
SqlRow a => SqlRow (Maybe a) Source # 
Instance details

Defined in Database.Selda.SqlRow

Methods

nextResult :: ResultReader (Maybe a) Source #

nestedCols :: Proxy (Maybe a) -> Int Source #

SqlType a => SqlRow (Only a) Source # 
Instance details

Defined in Database.Selda

Methods

nextResult :: ResultReader (Only a) Source #

nestedCols :: Proxy (Only a) -> Int Source #

(Typeable (a, b), GSqlRow (Rep (a, b))) => SqlRow (a, b) Source # 
Instance details

Defined in Database.Selda.SqlRow

Methods

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 # 
Instance details

Defined in Database.Selda.SqlRow

Methods

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 # 
Instance details

Defined in Database.Selda.SqlRow

Methods

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 # 
Instance details

Defined in Database.Selda.SqlRow

Methods

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 # 
Instance details

Defined in Database.Selda.SqlRow

Methods

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 # 
Instance details

Defined in Database.Selda.SqlRow

Methods

nextResult :: ResultReader (a, b, c, d, e, f, g) Source #

nestedCols :: Proxy (a, b, c, d, e, f, g) -> Int Source #

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.

Minimal complete definition

toText, fromText

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

Instances
(Typeable a, Bounded a, Enum a, Show a, Read a) => SqlEnum a Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

class Columns a Source #

Any column tuple.

Minimal complete definition

toTup, fromTup

Instances
(SqlRow a, Columns b) => Columns (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Row s a :*: b

fromTup :: (Row s a :*: b) -> [UntypedCol SQL]

(SqlType a, Columns b) => Columns (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Col s a :*: b

fromTup :: (Col s a :*: b) -> [UntypedCol SQL]

Columns (Col s a) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Col s a

fromTup :: Col s a -> [UntypedCol SQL]

Columns (Row s a) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Row s a

fromTup :: Row s a -> [UntypedCol SQL]

data Order Source #

The order in which to sort result rows.

Constructors

Asc 
Desc 
Instances
Eq Order Source # 
Instance details

Defined in Database.Selda.SQL

Methods

(==) :: Order -> Order -> Bool #

(/=) :: Order -> Order -> Bool #

Ord Order Source # 
Instance details

Defined in Database.Selda.SQL

Methods

compare :: Order -> Order -> Ordering #

(<) :: Order -> Order -> Bool #

(<=) :: Order -> Order -> Bool #

(>) :: Order -> Order -> Bool #

(>=) :: Order -> Order -> Bool #

max :: Order -> Order -> Order #

min :: Order -> Order -> Order #

Show Order Source # 
Instance details

Defined in Database.Selda.SQL

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

data a :*: b where infixr 1 Source #

An inductively defined "tuple", or heterogeneous, non-empty list.

Constructors

(:*:) :: a -> b -> a :*: b infixr 1 
Instances
(Eq a, Eq b) => Eq (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

Methods

(==) :: (a :*: b) -> (a :*: b) -> Bool #

(/=) :: (a :*: b) -> (a :*: b) -> Bool #

(Ord a, Ord b) => Ord (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

Methods

compare :: (a :*: b) -> (a :*: b) -> Ordering #

(<) :: (a :*: b) -> (a :*: b) -> Bool #

(<=) :: (a :*: b) -> (a :*: b) -> Bool #

(>) :: (a :*: b) -> (a :*: b) -> Bool #

(>=) :: (a :*: b) -> (a :*: b) -> Bool #

max :: (a :*: b) -> (a :*: b) -> a :*: b #

min :: (a :*: b) -> (a :*: b) -> a :*: b #

(Show a, Show b) => Show (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

Methods

showsPrec :: Int -> (a :*: b) -> ShowS #

show :: (a :*: b) -> String #

showList :: [a :*: b] -> ShowS #

Generic (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

Associated Types

type Rep (a :*: b) :: * -> * #

Methods

from :: (a :*: b) -> Rep (a :*: b) x #

to :: Rep (a :*: b) x -> a :*: b #

Tup (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

Methods

tupHead :: (a :*: b) -> Head (a :*: b)

(SqlRow a, Columns b) => Columns (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Row s a :*: b

fromTup :: (Row s a :*: b) -> [UntypedCol SQL]

(SqlType a, Columns b) => Columns (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Column

Methods

toTup :: [ColName] -> Col s a :*: b

fromTup :: (Col s a :*: b) -> [UntypedCol SQL]

Aggregates b => Aggregates (Aggr (Inner s) a :*: b) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: (Aggr (Inner s) a :*: b) -> [UntypedCol SQL]

(SqlRow a, Result b) => Result (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Row s a :*: b) :: * Source #

Methods

toRes :: Proxy (Row s a :*: b) -> ResultReader (Res (Row s a :*: b))

finalCols :: (Row s a :*: b) -> [SomeCol SQL]

(SqlType a, Result b) => Result (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Associated Types

type Res (Col s a :*: b) :: * Source #

Methods

toRes :: Proxy (Col s a :*: b) -> ResultReader (Res (Col s a :*: b))

finalCols :: (Col s a :*: b) -> [SomeCol SQL]

type Rep (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

type Rep (a :*: b) = D1 (MetaData ":*:" "Database.Selda.Types" "selda-0.3.3.0-GxVWUpfGA49LgGAKQcv3nM" False) (C1 (MetaCons ":*:" (InfixI RightAssociative 1) False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b)))
type Res (Row s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Row s a :*: b) = a :*: Res b
type Res (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

type Res (Col s a :*: b) = a :*: Res b

select :: Relational a => Table a -> Query s (Row s a) Source #

Query the given table.

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 :: Query s a -> Query s a Source #

Remove all duplicates from the result set.

restrict :: Col s Bool -> Query s () Source #

Restrict the query somehow. Roughly equivalent to WHERE.

limit :: Int -> Int -> Query (Inner s) a -> Query s (OuterCols a) Source #

Drop the first m rows, then get at most n of the remaining rows from the given subquery.

order :: SqlType a => Col s a -> Order -> Query s () 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.

ascending :: Order Source #

Ordering for order.

descending :: Order Source #

Ordering for order.

orderRandom :: Query s () Source #

Sort the result rows in random order.

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 suchThat p is generally more efficient than select q >>= x -> restrict (p x) >> pure x.

Working with selectors

data Selector t a Source #

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
(Relational t, HasField name t, FieldType name t ~ a) => IsLabel name (Selector t a) # 
Instance details

Defined in Database.Selda.Selectors.FieldSelectors

Methods

fromLabel :: Selector t a #

type family Coalesce a where ... Source #

Coalesce nested nullable column into a single level of nesting.

Equations

Coalesce (Maybe (Maybe a)) = Coalesce (Maybe a) 
Coalesce a = a 

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 # 
Instance details

Defined in Database.Selda.Selectors.FieldSelectors

type FieldType name t = GFieldType (Rep t) (NoSuchSelector t name) name Source #

The type of the name field, in the record type t.

class IsLabel (x :: Symbol) a #

Minimal complete definition

fromLabel

Instances
(Relational t, HasField name t, FieldType name t ~ a) => IsLabel name (Selector t a) # 
Instance details

Defined in Database.Selda.Selectors.FieldSelectors

Methods

fromLabel :: Selector t a #

(!) :: 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 Maybes will be squashed into a single level of nesting.

data Assignment s a where Source #

A selector-value assignment pair.

Constructors

(:=) :: 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

class Set set where Source #

Any container type for which we can check object membership.

Minimal complete definition

isIn

Methods

isIn :: SqlType a => Col s a -> set (Col s a) -> Col s Bool infixl 4 Source #

Is the given column contained in the given set?

Instances
Set [] Source # 
Instance details

Defined in Database.Selda

Methods

isIn :: SqlType a => Col s a -> [Col s a] -> Col s Bool Source #

Set (Query s) Source # 
Instance details

Defined in Database.Selda

Methods

isIn :: SqlType a => Col s0 a -> Query s (Col s0 a) -> Col s0 Bool Source #

data ID a Source #

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.

Instances
Eq (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: ID a -> ID a -> Bool #

(/=) :: ID a -> ID a -> Bool #

Ord (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: ID a -> ID a -> Ordering #

(<) :: ID a -> ID a -> Bool #

(<=) :: ID a -> ID a -> Bool #

(>) :: ID a -> ID a -> Bool #

(>=) :: ID a -> ID a -> Bool #

max :: ID a -> ID a -> ID a #

min :: ID a -> ID a -> ID a #

Show (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> ID a -> ShowS #

show :: ID a -> String #

showList :: [ID a] -> ShowS #

Typeable a => SqlType (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Typeable a => SqlOrd (ID a) Source # 
Instance details

Defined in Database.Selda

invalidId :: ID a Source #

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 -> Int Source #

Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.

toId :: Int -> ID a Source #

Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.

data RowID Source #

A row identifier for some table. This is the type of auto-incrementing primary keys.

Instances
Eq RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: RowID -> RowID -> Bool #

(/=) :: RowID -> RowID -> Bool #

Ord RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: RowID -> RowID -> Ordering #

(<) :: RowID -> RowID -> Bool #

(<=) :: RowID -> RowID -> Bool #

(>) :: RowID -> RowID -> Bool #

(>=) :: RowID -> RowID -> Bool #

max :: RowID -> RowID -> RowID #

min :: RowID -> RowID -> RowID #

Show RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> RowID -> ShowS #

show :: RowID -> String #

showList :: [RowID] -> ShowS #

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

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?

fromRowId :: RowID -> Int Source #

Inspect a row identifier.

toRowId :: Int -> RowID Source #

Create a row identifier from an integer. Use with caution, preferably only when reading user input.

(.==) :: SqlType a => Col s a -> Col s a -> Col s Bool infixl 4 Source #

(./=) :: SqlType a => Col s a -> Col s a -> Col s Bool infixl 4 Source #

(.>) :: SqlOrd a => Col s a -> Col s a -> Col s Bool infixl 4 Source #

(.<) :: SqlOrd a => Col s a -> Col s a -> Col s Bool infixl 4 Source #

(.>=) :: SqlOrd a => Col s a -> Col s a -> Col s Bool infixl 4 Source #

(.<=) :: SqlOrd a => Col s a -> Col s a -> Col s Bool infixl 4 Source #

like :: Col s Text -> Col s Text -> Col s Bool infixl 4 Source #

The SQL LIKE operator; matches strings with % wildcards. For instance:

"%gon" `like` "dragon" .== true

(.&&) :: Col s Bool -> Col s Bool -> Col s Bool infixr 3 Source #

(.||) :: Col s Bool -> Col s Bool -> Col s Bool infixr 2 Source #

not_ :: Col s Bool -> Col s Bool Source #

Boolean negation.

literal :: SqlType a => a -> Col s a Source #

A literal expression.

is :: 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.

int :: Int -> Col s Int Source #

Specialization of literal for integers.

float :: Double -> Col s Double Source #

Specialization of literal for doubles.

text :: Text -> Col s Text Source #

Specialization of literal for text.

true :: Col s Bool Source #

True and false boolean literals.

false :: Col s Bool Source #

True and false boolean literals.

null_ :: SqlType a => Col s (Maybe a) Source #

SQL NULL, at any type you like.

roundTo :: Col s Int -> Col s Double -> Col s Double Source #

Round a column to the given number of decimals places.

length_ :: Col s Text -> Col s Int Source #

Calculate the length of a string column.

isNull :: SqlType a => Col s (Maybe a) -> Col s Bool Source #

Is the given column null?

ifThenElse :: SqlType a => Col s Bool -> Col s a -> Col s a -> Col s a Source #

Perform a conditional on a column

ifNull :: SqlType a => Col s a -> Col s (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) => Col s b -> (Col s a -> Col s b) -> Col s (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 column with the given fields. Any unassigned fields will contain their default values.

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.

Minimal complete definition

(.<$>)

Associated Types

type Container f a Source #

Methods

(.<$>) :: (SqlType a, SqlType b) => (Col s a -> Col s b) -> f s (Container f a) -> f s (Container f b) infixl 4 Source #

Instances
Mappable Aggr Source # 
Instance details

Defined in Database.Selda

Associated Types

type Container Aggr a :: * Source #

Methods

(.<$>) :: (SqlType a, SqlType b) => (Col s a -> Col s b) -> Aggr s (Container Aggr a) -> Aggr s (Container Aggr b) Source #

Mappable (Col :: * -> * -> *) Source # 
Instance details

Defined in Database.Selda

Associated Types

type Container Col a :: * Source #

Methods

(.<$>) :: (SqlType a, SqlType b) => (Col s a -> Col s b) -> Col s (Container Col a) -> Col s (Container Col b) 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" []
sName :*: sAge :*: sPet = selectors people

peopleWithCats = do
  person <- select people
  restrict (person ! sPet .== just "cat")
  return (name ! sName)

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.

toString :: SqlType a => Col s a -> Col s Text Source #

Convert any SQL type to a string.

Inner queries

data Aggr s a Source #

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 # 
Instance details

Defined in Database.Selda

Associated Types

type Container Aggr a :: * Source #

Methods

(.<$>) :: (SqlType a, SqlType b) => (Col s a -> Col s b) -> Aggr s (Container Aggr a) -> Aggr s (Container Aggr b) Source #

Aggregates b => Aggregates (Aggr (Inner s) a :*: b) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: (Aggr (Inner s) a :*: b) -> [UntypedCol SQL]

Aggregates (Aggr (Inner s) a) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: Aggr (Inner s) a -> [UntypedCol SQL]

type Container Aggr a Source # 
Instance details

Defined in Database.Selda

type Container Aggr a = a

class Aggregates a Source #

One or more aggregate columns.

Minimal complete definition

unAggrs

Instances
Aggregates b => Aggregates (Aggr (Inner s) a :*: b) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: (Aggr (Inner s) a :*: b) -> [UntypedCol SQL]

Aggregates (Aggr (Inner s) a) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: Aggr (Inner s) a -> [UntypedCol SQL]

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.

Equations

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 #

Equations

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)

Equations

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.") 

data Inner s Source #

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 b => Aggregates (Aggr (Inner s) a :*: b) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: (Aggr (Inner s) a :*: b) -> [UntypedCol SQL]

Aggregates (Aggr (Inner s) a) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: Aggr (Inner s) a -> [UntypedCol SQL]

class SqlType a => SqlOrd a Source #

Any column type that can be used with the min_ and max_ functions.

Instances
(SqlType a, Num a) => SqlOrd a Source # 
Instance details

Defined in Database.Selda

SqlOrd Text Source # 
Instance details

Defined in Database.Selda

SqlOrd TimeOfDay Source # 
Instance details

Defined in Database.Selda

SqlOrd UTCTime Source # 
Instance details

Defined in Database.Selda

SqlOrd Day Source # 
Instance details

Defined in Database.Selda

SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

SqlOrd a => SqlOrd (Maybe a) Source # 
Instance details

Defined in Database.Selda

Typeable a => SqlOrd (ID a) Source # 
Instance details

Defined in Database.Selda

innerJoin Source #

Arguments

:: (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.

leftJoin Source #

Arguments

:: (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 :: SqlType a => Col (Inner s) a -> Query (Inner s) (Aggr (Inner s) 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, Relational a) => Table a -> (Row s a -> Col s 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, Relational a) => Table a -> (Row s a -> Col s 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.

update Source #

Arguments

:: (MonadSelda m, Relational a) 
=> Table a

Table to update.

-> (Row s a -> Col s Bool)

Predicate.

-> (Row s a -> Row s 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 s a -> Col s Bool) -> (Row s a -> Row s a) -> m () Source #

Like update, but doesn't return the number of updated rows.

upsert :: (MonadSelda m, Relational a) => Table a -> (Row s a -> Col s Bool) -> (Row s a -> Row s 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 s a -> Col s 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 s a -> Col s Bool) -> m () Source #

Like deleteFrom, but does not return the number of deleted rows.

Prepared statements

class Preparable q Source #

Minimal complete definition

mkQuery

Instances
(SqlType a, Preparable b) => Preparable (Col s a -> b) Source # 
Instance details

Defined in Database.Selda.Prepared

Methods

mkQuery :: MonadSelda m => Int -> (Col s a -> b) -> [SqlTypeRep] -> m CompResult

Result a => Preparable (Query s a) Source # 
Instance details

Defined in Database.Selda.Prepared

Methods

mkQuery :: MonadSelda m => Int -> Query s a -> [SqlTypeRep] -> m CompResult

class Prepare q f Source #

Some parameterized query q that can be prepared into a function f in some MonadSelda.

Minimal complete definition

mkFun

Instances
(Typeable a, MonadSelda m, a ~ Res (ResultT q), Result (ResultT q)) => Prepare q (m [a]) Source # 
Instance details

Defined in Database.Selda.Prepared

Methods

mkFun :: IORef (Maybe (BackendID, CompResult)) -> StmtID -> q -> [Param] -> m [a]

(SqlType a, Prepare q b) => Prepare q (a -> b) Source # 
Instance details

Defined in Database.Selda.Prepared

Methods

mkFun :: IORef (Maybe (BackendID, CompResult)) -> StmtID -> q -> [Param] -> a -> b

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.

A usage example:

ages :: Table (Text :*: Int)
ages = table "ages" $ primary "name" :*: required "age"

{-# NOINLINE ageOf #-}
ageOf :: Text -> SeldaM [Int]
ageOf = prepared $ \n -> do
  (name :*: age) <- select ages
  restrict $ name .== n
  return age

Defining schemas

class Generic a #

Representable types of kind *. This class is derivable in GHC with the DeriveGeneric flag on.

A Generic instance must satisfy the following laws:

from . toid
to . fromid

Minimal complete definition

from, to

Instances
Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: * -> * #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: * -> * #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: * -> * #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: * -> * #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: * -> * #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: * -> * #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: * -> * #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: * -> * #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: * -> * #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: * -> * #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: * -> * #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: * -> * #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: * -> * #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: * -> * #

Methods

from :: () -> Rep () x #

to :: Rep () x -> () #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: * -> * #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: * -> * #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: * -> * #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: * -> * #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Generic Any 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: * -> * #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: * -> * #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: * -> * #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: * -> * #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: * -> * #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: * -> * #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: * -> * #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: * -> * #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: * -> * #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: * -> * #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: * -> * #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: * -> * #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: * -> * #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: * -> * #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: * -> * #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: * -> * #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: * -> * #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic FixityDirection 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FixityDirection :: * -> * #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: * -> * #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: * -> * #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: * -> * #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: * -> * #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: * -> * #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: * -> * #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: * -> * #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: * -> * #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: * -> * #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: * -> * #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: * -> * #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: * -> * #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: * -> * #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: * -> * #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: * -> * #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: * -> * #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: * -> * #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: * -> * #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: * -> * #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: * -> * #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: * -> * #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: * -> * #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: * -> * #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: * -> * #

Generic TyVarBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyVarBndr :: * -> * #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: * -> * #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: * -> * #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: * -> * #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: * -> * #

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

type Rep [a] :: * -> * #

Methods

from :: [a] -> Rep [a] x #

to :: Rep [a] x -> [a] #

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Maybe a) :: * -> * #

Methods

from :: Maybe a -> Rep (Maybe a) x #

to :: Rep (Maybe a) x -> Maybe a #

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Par1 p) :: * -> * #

Methods

from :: Par1 p -> Rep (Par1 p) x #

to :: Rep (Par1 p) x -> Par1 p #

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

type Rep (Complex a) :: * -> * #

Methods

from :: Complex a -> Rep (Complex a) x #

to :: Rep (Complex a) x -> Complex a #

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Min a) :: * -> * #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Max a) :: * -> * #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Last a) :: * -> * #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (WrappedMonoid m) :: * -> * #

Generic (Option a) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Option a) :: * -> * #

Methods

from :: Option a -> Rep (Option a) x #

to :: Rep (Option a) x -> Option a #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (ZipList a) :: * -> * #

Methods

from :: ZipList a -> Rep (ZipList a) x #

to :: Rep (ZipList a) x -> ZipList a #

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

type Rep (Identity a) :: * -> * #

Methods

from :: Identity a -> Rep (Identity a) x #

to :: Rep (Identity a) x -> Identity a #

Generic (First a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (First a) :: * -> * #

Methods

from :: First a -> Rep (First a) x #

to :: Rep (First a) x -> First a #

Generic (Last a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Last a) :: * -> * #

Methods

from :: Last a -> Rep (Last a) x #

to :: Rep (Last a) x -> Last a #

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: * -> * #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Generic (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: * -> * #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: * -> * #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: * -> * #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (NonEmpty a) :: * -> * #

Methods

from :: NonEmpty a -> Rep (NonEmpty a) x #

to :: Rep (NonEmpty a) x -> NonEmpty a #

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

type Rep (Tree a) :: * -> * #

Methods

from :: Tree a -> Rep (Tree a) x #

to :: Rep (Tree a) x -> Tree a #

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewL a) :: * -> * #

Methods

from :: ViewL a -> Rep (ViewL a) x #

to :: Rep (ViewL a) x -> ViewL a #

Generic (ViewR a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (ViewR a) :: * -> * #

Methods

from :: ViewR a -> Rep (ViewR a) x #

to :: Rep (ViewR a) x -> ViewR a #

Generic (Only a) # 
Instance details

Defined in Database.Selda

Associated Types

type Rep (Only a) :: * -> * #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: * -> * #

Methods

from :: Either a b -> Rep (Either a b) x #

to :: Rep (Either a b) x -> Either a b #

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (V1 p) :: * -> * #

Methods

from :: V1 p -> Rep (V1 p) x #

to :: Rep (V1 p) x -> V1 p #

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (U1 p) :: * -> * #

Methods

from :: U1 p -> Rep (U1 p) x #

to :: Rep (U1 p) x -> U1 p #

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b) :: * -> * #

Methods

from :: (a, b) -> Rep (a, b) x #

to :: Rep (a, b) x -> (a, b) #

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

type Rep (Arg a b) :: * -> * #

Methods

from :: Arg a b -> Rep (Arg a b) x #

to :: Rep (Arg a b) x -> Arg a b #

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedMonad m a) :: * -> * #

Methods

from :: WrappedMonad m a -> Rep (WrappedMonad m a) x #

to :: Rep (WrappedMonad m a) x -> WrappedMonad m a #

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: * -> * #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Generic (a :*: b) # 
Instance details

Defined in Database.Selda.Types

Associated Types

type Rep (a :*: b) :: * -> * #

Methods

from :: (a :*: b) -> Rep (a :*: b) x #

to :: Rep (a :*: b) x -> a :*: b #

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Rec1 f p) :: * -> * #

Methods

from :: Rec1 f p -> Rep (Rec1 f p) x #

to :: Rep (Rec1 f p) x -> Rec1 f p #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: * -> * #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

Generic (URec Char p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Char p) :: * -> * #

Methods

from :: URec Char p -> Rep (URec Char p) x #

to :: Rep (URec Char p) x -> URec Char p #

Generic (URec Double p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Double p) :: * -> * #

Methods

from :: URec Double p -> Rep (URec Double p) x #

to :: Rep (URec Double p) x -> URec Double p #

Generic (URec Float p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Float p) :: * -> * #

Methods

from :: URec Float p -> Rep (URec Float p) x #

to :: Rep (URec Float p) x -> URec Float p #

Generic (URec Int p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Int p) :: * -> * #

Methods

from :: URec Int p -> Rep (URec Int p) x #

to :: Rep (URec Int p) x -> URec Int p #

Generic (URec Word p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec Word p) :: * -> * #

Methods

from :: URec Word p -> Rep (URec Word p) x #

to :: Rep (URec Word p) x -> URec Word p #

Generic (a, b, c) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c) :: * -> * #

Methods

from :: (a, b, c) -> Rep (a, b, c) x #

to :: Rep (a, b, c) x -> (a, b, c) #

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

type Rep (WrappedArrow a b c) :: * -> * #

Methods

from :: WrappedArrow a b c -> Rep (WrappedArrow a b c) x #

to :: Rep (WrappedArrow a b c) x -> WrappedArrow a b c #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

type Rep (Const a b) :: * -> * #

Methods

from :: Const a b -> Rep (Const a b) x #

to :: Rep (Const a b) x -> Const a b #

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: * -> * #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (K1 i c p) :: * -> * #

Methods

from :: K1 i c p -> Rep (K1 i c p) x #

to :: Rep (K1 i c p) x -> K1 i c p #

Generic ((f :+: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :+: g) p) :: * -> * #

Methods

from :: (f :+: g) p -> Rep ((f :+: g) p) x #

to :: Rep ((f :+: g) p) x -> (f :+: g) p #

Generic ((f :*: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :*: g) p) :: * -> * #

Methods

from :: (f :*: g) p -> Rep ((f :*: g) p) x #

to :: Rep ((f :*: g) p) x -> (f :*: g) p #

Generic (a, b, c, d) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d) :: * -> * #

Methods

from :: (a, b, c, d) -> Rep (a, b, c, d) x #

to :: Rep (a, b, c, d) x -> (a, b, c, d) #

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

type Rep (Product f g a) :: * -> * #

Methods

from :: Product f g a -> Rep (Product f g a) x #

to :: Rep (Product f g a) x -> Product f g a #

Generic (Sum f g a) 
Instance details

Defined in Data.Functor.Sum

Associated Types

type Rep (Sum f g a) :: * -> * #

Methods

from :: Sum f g a -> Rep (Sum f g a) x #

to :: Rep (Sum f g a) x -> Sum f g a #

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (M1 i c f p) :: * -> * #

Methods

from :: M1 i c f p -> Rep (M1 i c f p) x #

to :: Rep (M1 i c f p) x -> M1 i c f p #

Generic ((f :.: g) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep ((f :.: g) p) :: * -> * #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

Generic (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e) :: * -> * #

Methods

from :: (a, b, c, d, e) -> Rep (a, b, c, d, e) x #

to :: Rep (a, b, c, d, e) x -> (a, b, c, d, e) #

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

type Rep (Compose f g a) :: * -> * #

Methods

from :: Compose f g a -> Rep (Compose f g a) x #

to :: Rep (Compose f g a) x -> Compose f g a #

Generic (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f) :: * -> * #

Methods

from :: (a, b, c, d, e, f) -> Rep (a, b, c, d, e, f) x #

to :: Rep (a, b, c, d, e, f) x -> (a, b, c, d, e, f) #

Generic (a, b, c, d, e, f, g) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g) :: * -> * #

Methods

from :: (a, b, c, d, e, f, g) -> Rep (a, b, c, d, e, f, g) x #

to :: Rep (a, b, c, d, e, f, g) x -> (a, b, c, d, e, f, g) #

data TableName Source #

Name of a database table.

data ColName Source #

Name of a database column.

Instances
Eq ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

(==) :: ColName -> ColName -> Bool #

(/=) :: ColName -> ColName -> Bool #

Ord ColName Source # 
Instance details

Defined in Database.Selda.Types

Show ColName Source # 
Instance details

Defined in Database.Selda.Types

IsString ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

fromString :: String -> ColName #

data Attr a where Source #

A generic column attribute. Essentially a pair or a record selector over the type a and a column attribute.

Constructors

(:-) :: Selector a b -> Attribute a b -> Attr a 

data Attribute t c Source #

Some attribute that may be set on a column of type c, in a table of type t.

type Selectors r = Sels r (Rep r) Source #

An inductive tuple of selectors for the given relation.

class GSelectors t (f :: * -> *) Source #

Any table type that can have selectors generated.

Minimal complete definition

mkSel

Instances
(GSelectors t a, GSelectors t b, Sels t (a :*: b) ~ (Sels t a :*: Sels t b)) => GSelectors t (a :*: b) Source # 
Instance details

Defined in Database.Selda.Selectors.MakeSelectors

Methods

mkSel :: Proxy (a :*: b) -> Proxy t -> State Int (Sels t (a :*: b))

GSelectors t (a :*: (b :*: c)) => GSelectors t ((a :*: b) :*: c) Source # 
Instance details

Defined in Database.Selda.Selectors.MakeSelectors

Methods

mkSel :: Proxy ((a :*: b) :*: c) -> Proxy t -> State Int (Sels t ((a :*: b) :*: c))

(SqlRow t, SqlType a) => GSelectors t (K1 i a :: * -> *) Source # 
Instance details

Defined in Database.Selda.Selectors.MakeSelectors

Methods

mkSel :: Proxy (K1 i a) -> Proxy t -> State Int (Sels t (K1 i a))

(GSelectors t f, Sels t f ~ Sels t (M1 x y f)) => GSelectors t (M1 x y f) Source # 
Instance details

Defined in Database.Selda.Selectors.MakeSelectors

Methods

mkSel :: Proxy (M1 x y f) -> Proxy t -> State Int (Sels t (M1 x y f))

class ForeignKey a b where Source #

Minimal complete definition

foreignKey

Methods

foreignKey :: Table t -> Selector t a -> Attribute self b Source #

A foreign key constraint referencing the given table and column.

Instances
ForeignKey a a Source # 
Instance details

Defined in Database.Selda.Table

Methods

foreignKey :: Table t -> Selector t a -> Attribute self a Source #

ForeignKey a (Maybe a) Source # 
Instance details

Defined in Database.Selda.Table

Methods

foreignKey :: Table t -> Selector t a -> Attribute self (Maybe a) Source #

ForeignKey (Maybe a) a Source # 
Instance details

Defined in Database.Selda.Table

Methods

foreignKey :: Table t -> Selector t (Maybe a) -> Attribute self a Source #

table :: forall a. Relational a => TableName -> [Attr a] -> Table a Source #

Generate a table from the given table name and list of column attributes. All Maybe fields in the table's type will be represented by nullable columns, and all non-Maybe fields fill be represented by required columns. For example:

data Person = Person
  { id   :: ID Person
  , name :: Text
  , age  :: Int
  , pet  :: Maybe Text
  }
  deriving Generic

people :: Table Person
people = table "people" [pId :- autoPrimary]
pId :*: pName :*: pAge :*: pPet = selectors people

This will result in a table of Persons, with an auto-incrementing primary key.

If the given type does not have record selectors, the column names will be col_1, col_2, etc.

tableFieldMod :: forall a. Relational a => TableName -> [Attr a] -> (Text -> Text) -> Table a Source #

Generate a table from the given table name, a list of column attributes and a function that maps from field names to column names. Ex.:

data Person = Person
  { personId   :: Int
  , personName :: Text
  , personAge  :: Int
  , personPet  :: Maybe Text
  }
  deriving Generic

people :: Table Person
people = tableFieldMod "people" [personName :- autoPrimaryGen] (stripPrefix "person")

This will create a table with the columns named Id, Name, Age and Pet.

tableWithSelectors :: forall a. (Relational a, GSelectors a (Rep a)) => TableName -> [Attr a] -> (Table a, Selectors a) Source #

A pair of the table with the given name and columns, and all its selectors. For example:

tbl :: Table (Int, Text)
(tbl, tblBar :*: tblBaz)
  =  tableWithSelectors "foo" []

q :: Query s Text
q = tblBaz `from` select tbl

selectors :: forall a. (Relational a, GSelectors a (Rep a)) => Table a -> Selectors a Source #

Generate selector functions for the given table. Selectors can be used to access the fields of a query result tuple, avoiding the need to pattern match on the entire tuple.

tbl :: Table (Int, Text)
tbl = table "foo" []
(tblBar :*: tblBaz) = selectors tbl

q :: Query s Text
q = do
  row <- select tbl
  return (row ! tblBaz)

primary :: Attribute t c Source #

A primary key which does not auto-increment.

autoPrimary :: Attribute t (ID t) Source #

An auto-incrementing primary key.

untypedAutoPrimary :: Attribute t RowID Source #

An untyped auto-incrementing primary key. You should really only use this for ad hoc tables, such as tuples.

unique :: Attribute t c Source #

A table-unique value.

data IndexMethod Source #

Method to use for indexing with indexedUsing. Index methods are ignored by the SQLite backend, as SQLite doesn't support different index methods.

Constructors

BTreeIndex 
HashIndex 

index :: Attribute t c Source #

Create an index on this column.

indexUsing :: IndexMethod -> Attribute t c Source #

Create an index using the given index method on this column.

Creating and dropping tables

createTable :: MonadSelda m => Table a -> m () Source #

Create a table from the given schema.

tryCreateTable :: MonadSelda m => Table a -> m () Source #

Create a table from the given schema, unless it already exists.

dropTable :: MonadSelda m => Table a -> m () Source #

Drop the given table.

tryDropTable :: MonadSelda m => Table a -> m () Source #

Drop the given table, if it exists.

Compiling and inspecting queries

data OnError Source #

Constructors

Fail 
Ignore 
Instances
Eq OnError Source # 
Instance details

Defined in Database.Selda.Table.Compile

Methods

(==) :: OnError -> OnError -> Bool #

(/=) :: OnError -> OnError -> Bool #

Ord OnError Source # 
Instance details

Defined in Database.Selda.Table.Compile

Show OnError Source # 
Instance details

Defined in Database.Selda.Table.Compile

compile :: Result a => Query s a -> (Text, [Param]) Source #

Compile a query into a parameterised SQL statement.

The types given are tailored for SQLite. To translate SQLite types into whichever types are used by your backend, use compileWith.

compileCreateTable :: PPConfig -> OnError -> Table a -> [Text] Source #

Compile a sequence of queries to create the given table, including indexes. The first query in the sequence is always CREATE TABLE.

compileDropTable :: OnError -> Table a -> Text Source #

Compile a DROP TABLE query.

compileInsert :: Relational a => PPConfig -> Table a -> [a] -> [(Text, [Param])] Source #

Compile an INSERT query, given the keyword representing default values in the target SQL dialect, a table and a list of items corresponding to the table.

compileUpdate Source #

Arguments

:: (Relational a, SqlRow a) 
=> PPConfig 
-> Table a

Table to update.

-> (Row s a -> Row s a)

Update function.

-> (Row s a -> Col s Bool)

Predicate.

-> (Text, [Param]) 

Compile an UPDATE query.

Tuple convenience functions

class Tup a Source #

Minimal complete definition

tupHead

Instances
Head a ~ a => Tup a Source # 
Instance details

Defined in Database.Selda.Types

Methods

tupHead :: a -> Head a

Tup (a :*: b) Source # 
Instance details

Defined in Database.Selda.Types

Methods

tupHead :: (a :*: b) -> Head (a :*: b)

type family Head a where ... Source #

Equations

Head (a :*: b) = a 
Head a = a 

first :: Tup a => a -> Head a Source #

Get the first element of an inductive tuple.

second :: Tup b => (a :*: b) -> Head b Source #

Get the second element of an inductive tuple.

third :: Tup c => (a :*: (b :*: c)) -> Head c Source #

Get the third element of an inductive tuple.

fourth :: Tup d => (a :*: (b :*: (c :*: d))) -> Head d Source #

Get the fourth element of an inductive tuple.

fifth :: Tup e => (a :*: (b :*: (c :*: (d :*: e)))) -> Head e Source #

Get the fifth element of an inductive tuple.

sixth :: Tup f => (a :*: (b :*: (c :*: (d :*: (e :*: f))))) -> Head f Source #

Get the sixth element of an inductive tuple.

seventh :: Tup g => (a :*: (b :*: (c :*: (d :*: (e :*: (f :*: g)))))) -> Head g Source #

Get the seventh element of an inductive tuple.

eighth :: Tup h => (a :*: (b :*: (c :*: (d :*: (e :*: (f :*: (g :*: h))))))) -> Head h Source #

Get the eighth element of an inductive tuple.

ninth :: Tup i => (a :*: (b :*: (c :*: (d :*: (e :*: (f :*: (h :*: (h :*: i)))))))) -> Head i Source #

Get the ninth element of an inductive tuple.

tenth :: Tup j => (a :*: (b :*: (c :*: (d :*: (e :*: (f :*: (g :*: (h :*: (i :*: j))))))))) -> Head j Source #

Get the tenth element of an inductive tuple.

Useful re-exports

class Monad m => MonadIO (m :: * -> *) #

Monads in which IO computations may be embedded. Any monad built by applying a sequence of monad transformers to the IO monad will be an instance of this class.

Instances should satisfy the following laws, which state that liftIO is a transformer of monads:

Minimal complete definition

liftIO

Instances
MonadIO IO

Since: base-4.9.0.0

Instance details

Defined in Control.Monad.IO.Class

Methods

liftIO :: IO a -> IO a #

MonadIO Q 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

liftIO :: IO a -> Q a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

MonadIO m => MonadIO (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (SeldaT m) # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

liftIO :: IO a -> SeldaT m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadIO m => MonadIO (IdentityT m) 
Instance details

Defined in Control.Monad.Trans.Identity

Methods

liftIO :: IO a -> IdentityT m a #

(Error e, MonadIO m) => MonadIO (ErrorT e m) 
Instance details

Defined in Control.Monad.Trans.Error

Methods

liftIO :: IO a -> ErrorT e m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Lazy

Methods

liftIO :: IO a -> StateT s m a #

MonadIO m => MonadIO (StateT s m) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Lazy

Methods

liftIO :: IO a -> WriterT w m a #

(Monoid w, MonadIO m) => MonadIO (WriterT w m) 
Instance details

Defined in Control.Monad.Trans.Writer.Strict

Methods

liftIO :: IO a -> WriterT w m a #

MonadIO m => MonadIO (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

liftIO :: IO a -> ContT r m a #

MonadIO m => MonadIO (ReaderT r m) 
Instance details

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Lazy

Methods

liftIO :: IO a -> RWST r w s m a #

(Monoid w, MonadIO m) => MonadIO (RWST r w s m) 
Instance details

Defined in Control.Monad.Trans.RWS.Strict

Methods

liftIO :: IO a -> RWST r w s m a #

class MonadCatch m => MonadMask (m :: * -> *) #

A class for monads which provide for the ability to account for all possible exit points from a computation, and to mask asynchronous exceptions. Continuation-based monads are invalid instances of this class.

Instances should ensure that, in the following code:

fg = f `finally` g

The action g is called regardless of what occurs within f, including async exceptions. Some monads allow f to abort the computation via other effects than throwing an exception. For simplicity, we will consider aborting and throwing an exception to be two forms of "throwing an error".

If f and g both throw an error, the error thrown by fg depends on which errors we're talking about. In a monad transformer stack, the deeper layers override the effects of the inner layers; for example, ExceptT e1 (Except e2) a represents a value of type Either e2 (Either e1 a), so throwing both an e1 and an e2 will result in Left e2. If f and g both throw an error from the same layer, instances should ensure that the error from g wins.

Effects other than throwing an error are also overriden by the deeper layers. For example, StateT s Maybe a represents a value of type s -> Maybe (a, s), so if an error thrown from f causes this function to return Nothing, any changes to the state which f also performed will be erased. As a result, g will see the state as it was before f. Once g completes, f's error will be rethrown, so g' state changes will be erased as well. This is the normal interaction between effects in a monad transformer stack.

By contrast, lifted-base's version of finally always discards all of g's non-IO effects, and g never sees any of f's non-IO effects, regardless of the layer ordering and regardless of whether f throws an error. This is not the result of interacting effects, but a consequence of MonadBaseControl's approach.

Minimal complete definition

mask, uninterruptibleMask, generalBracket

Instances
MonadMask IO 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

uninterruptibleMask :: ((forall a. IO a -> IO a) -> IO b) -> IO b #

generalBracket :: IO a -> (a -> ExitCase b -> IO c) -> (a -> IO b) -> IO (b, c) #

e ~ SomeException => MonadMask (Either e)

Since: exceptions-0.8.3

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

uninterruptibleMask :: ((forall a. Either e a -> Either e a) -> Either e b) -> Either e b #

generalBracket :: Either e a -> (a -> ExitCase b -> Either e c) -> (a -> Either e b) -> Either e (b, c) #

MonadMask m => MonadMask (MaybeT m)

Since: exceptions-0.10.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

uninterruptibleMask :: ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b #

generalBracket :: MaybeT m a -> (a -> ExitCase b -> MaybeT m c) -> (a -> MaybeT m b) -> MaybeT m (b, c) #

MonadMask m => MonadMask (SeldaT m) # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

mask :: ((forall a. SeldaT m a -> SeldaT m a) -> SeldaT m b) -> SeldaT m b #

uninterruptibleMask :: ((forall a. SeldaT m a -> SeldaT m a) -> SeldaT m b) -> SeldaT m b #

generalBracket :: SeldaT m a -> (a -> ExitCase b -> SeldaT m c) -> (a -> SeldaT m b) -> SeldaT m (b, c) #

MonadMask m => MonadMask (ExceptT e m)

Since: exceptions-0.9.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

uninterruptibleMask :: ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b #

generalBracket :: ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) #

MonadMask m => MonadMask (IdentityT m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

uninterruptibleMask :: ((forall a. IdentityT m a -> IdentityT m a) -> IdentityT m b) -> IdentityT m b #

generalBracket :: IdentityT m a -> (a -> ExitCase b -> IdentityT m c) -> (a -> IdentityT m b) -> IdentityT m (b, c) #

(Error e, MonadMask m) => MonadMask (ErrorT e m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

uninterruptibleMask :: ((forall a. ErrorT e m a -> ErrorT e m a) -> ErrorT e m b) -> ErrorT e m b #

generalBracket :: ErrorT e m a -> (a -> ExitCase b -> ErrorT e m c) -> (a -> ErrorT e m b) -> ErrorT e m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

MonadMask m => MonadMask (StateT s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

uninterruptibleMask :: ((forall a. StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

generalBracket :: StateT s m a -> (a -> ExitCase b -> StateT s m c) -> (a -> StateT s m b) -> StateT s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

(MonadMask m, Monoid w) => MonadMask (WriterT w m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

uninterruptibleMask :: ((forall a. WriterT w m a -> WriterT w m a) -> WriterT w m b) -> WriterT w m b #

generalBracket :: WriterT w m a -> (a -> ExitCase b -> WriterT w m c) -> (a -> WriterT w m b) -> WriterT w m (b, c) #

MonadMask m => MonadMask (ReaderT r m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

uninterruptibleMask :: ((forall a. ReaderT r m a -> ReaderT r m a) -> ReaderT r m b) -> ReaderT r m b #

generalBracket :: ReaderT r m a -> (a -> ExitCase b -> ReaderT r m c) -> (a -> ReaderT r m b) -> ReaderT r m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

(MonadMask m, Monoid w) => MonadMask (RWST r w s m) 
Instance details

Defined in Control.Monad.Catch

Methods

mask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

uninterruptibleMask :: ((forall a. RWST r w s m a -> RWST r w s m a) -> RWST r w s m b) -> RWST r w s m b #

generalBracket :: RWST r w s m a -> (a -> ExitCase b -> RWST r w s m c) -> (a -> RWST r w s m b) -> RWST r w s m (b, c) #

liftIO :: MonadIO m => IO a -> m a #

Lift a computation from the IO monad.

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances
Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd Text Source # 
Instance details

Defined in Database.Selda

IsString (Col s Text) # 
Instance details

Defined in Database.Selda.Column

Methods

fromString :: String -> Col s Text #

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char

data Day #

The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.

Instances
Enum Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Data Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Day -> c Day #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Day #

toConstr :: Day -> Constr #

dataTypeOf :: Day -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Day) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Day) #

gmapT :: (forall b. Data b => b -> b) -> Day -> Day #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r #

gmapQ :: (forall d. Data d => d -> u) -> Day -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Day -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Day -> m Day #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day #

Ord Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Ix Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

range :: (Day, Day) -> [Day] #

index :: (Day, Day) -> Day -> Int #

unsafeIndex :: (Day, Day) -> Day -> Int

inRange :: (Day, Day) -> Day -> Bool #

rangeSize :: (Day, Day) -> Int #

unsafeRangeSize :: (Day, Day) -> Int

NFData Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

rnf :: Day -> () #

FormatTime Day 
Instance details

Defined in Data.Time.Format

ParseTime Day 
Instance details

Defined in Data.Time.Format.Parse

Methods

buildTime :: TimeLocale -> [(Char, String)] -> Maybe Day #

SqlType Day Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd Day Source # 
Instance details

Defined in Database.Selda

data TimeOfDay #

Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.

Instances
Eq TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Data TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay #

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) #

gmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeOfDay -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

Ord TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Show TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

NFData TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

rnf :: TimeOfDay -> () #

FormatTime TimeOfDay 
Instance details

Defined in Data.Time.Format

ParseTime TimeOfDay 
Instance details

Defined in Data.Time.Format.Parse

SqlType TimeOfDay Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd TimeOfDay Source # 
Instance details

Defined in Database.Selda

data UTCTime #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances
Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime #

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) #

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

FormatTime UTCTime 
Instance details

Defined in Data.Time.Format

ParseTime UTCTime 
Instance details

Defined in Data.Time.Format.Parse

SqlType UTCTime Source # 
Instance details

Defined in Database.Selda.SqlType

SqlOrd UTCTime Source # 
Instance details

Defined in Database.Selda