selda-0.5.2.0: Multi-backend, high-level EDSL for interacting with SQL databases.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Selda

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.

Minimal complete definition

withConnection

Instances

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

Defined in Database.Selda.Backend.Internal

Associated Types

type Backend (SeldaT b m) Source #

Methods

withConnection :: (SeldaConnection (Backend (SeldaT b m)) -> SeldaT b m a) -> SeldaT b m a Source #

transact :: SeldaT b m a -> SeldaT b m a Source #

type family Backend m Source #

Type of database backend used by m.

Instances

Instances details
type Backend (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

type Backend (SeldaT b m) = b

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.

UnsafeError String

An error occurred due to improper use of an unsafe function.

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 b m a Source #

Monad transformer adding Selda SQL capabilities.

Instances

Instances details
MonadTrans (SeldaT b) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

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

MonadFail m => MonadFail (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

fail :: String -> SeldaT b m a #

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

Defined in Database.Selda.Backend.Internal

Methods

liftIO :: IO a -> SeldaT b m a #

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

Defined in Database.Selda.Backend.Internal

Methods

pure :: a -> SeldaT b m a #

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

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

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

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

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

Defined in Database.Selda.Backend.Internal

Methods

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

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

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

Defined in Database.Selda.Backend.Internal

Methods

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

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

return :: a -> SeldaT b m a #

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

Defined in Database.Selda.Backend.Internal

Methods

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

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

Defined in Database.Selda.Backend.Internal

Methods

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

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

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

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

Defined in Database.Selda.Backend.Internal

Methods

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

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

Defined in Database.Selda.Backend.Internal

Associated Types

type Backend (SeldaT b m) Source #

Methods

withConnection :: (SeldaConnection (Backend (SeldaT b m)) -> SeldaT b m a) -> SeldaT b m a Source #

transact :: SeldaT b m a -> SeldaT b m a Source #

type Backend (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

type Backend (SeldaT b m) = b

type SeldaM b = SeldaT b 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

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

Defined in Database.Selda

Methods

fromString :: String -> Only a #

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] #

Generic (Only a) Source # 
Instance details

Defined in Database.Selda

Associated Types

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

Methods

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

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

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 #

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

Defined in Database.Selda

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 #

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 #

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

Defined in Database.Selda

Methods

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

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

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 #

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 #

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

Defined in Database.Selda

Methods

nextResult :: ResultReader (Only a) Source #

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

(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

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.5.2.0-BxjrPcn64wf9X9ipyvItC2" '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 #

Associated Types

type TheOnly a Source #

Methods

the :: a -> TheOnly a Source #

Extract the value of a row from a singleton table.

Instances

Instances details
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

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

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 #

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 #

Set (Query s) Source # 
Instance details

Defined in Database.Selda

Methods

isIn :: (Same s0 t, SqlType a) => Col s0 a -> Query s (Col t 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

Instances details
(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

Methods

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

finalCols :: (Row s a :*: b) -> [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 #

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

Methods

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

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

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

Instances details
Mappable (Col :: Type -> TYPE LiftedRep -> TYPE LiftedRep) 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

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

IsString (Col s Text) Source # 
Instance details

Defined in Database.Selda.Column

Methods

fromString :: String -> Col s Text #

Monoid (Col s Text) Source # 
Instance details

Defined in Database.Selda

Methods

mempty :: Col s Text #

mappend :: Col s Text -> Col s Text -> Col s Text #

mconcat :: [Col s Text] -> Col s Text #

Semigroup (Col s Text) Source # 
Instance details

Defined in Database.Selda

Methods

(<>) :: Col s Text -> Col s Text -> Col s Text #

sconcat :: NonEmpty (Col s Text) -> Col s Text #

stimes :: Integral b => b -> Col s Text -> Col s Text #

(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 #

Fractional (Col s Double) Source # 
Instance details

Defined in Database.Selda.Column

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 #

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

Methods

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

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

type Container (Col :: Type -> TYPE LiftedRep -> TYPE LiftedRep) a Source # 
Instance details

Defined in Database.Selda

type family Res r where ... Source #

Equations

Res (Col s a :*: b) = a :*: Res b 
Res (Row s a :*: b) = a :*: Res b 
Res (Col s a) = a 
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

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

Defined in Database.Selda.Compile

Methods

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

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

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

Defined in Database.Selda.Compile

Methods

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

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

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

Defined in Database.Selda.Compile

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

Methods

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

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

query :: (MonadSelda m, Result a) => Query (Backend m) a -> m [Res a] Source #

Run a query within a Selda monad. In practice, this is often a SeldaT transformer on top of some other monad. Selda transformers are entered using backend-specific withX functions, such as withSQLite from the SQLite backend.

queryInto :: (MonadSelda m, Relational a) => Table a -> Query (Backend m) (Row (Backend m) a) -> m Int Source #

Perform the given query, and insert the result into the given table. Returns the number of inserted rows.

transaction :: (MonadSelda m, MonadMask m) => m a -> m a Source #

Perform the given computation atomically. If an exception is raised during its execution, the entire transaction will be rolled back and the exception re-thrown, even if the exception is caught and handled within the transaction.

withoutForeignKeyEnforcement :: (MonadSelda m, MonadMask m) => m a -> m a Source #

Run the given computation as a transaction without enforcing foreign key constraints.

If the computation finishes with the database in an inconsistent state with regards to foreign keys, the resulting behavior is undefined. Use with extreme caution, preferably only for migrations.

On the PostgreSQL backend, at least PostgreSQL 9.6 is required.

Using this should be avoided in favor of deferred foreign key constraints. See SQL backend documentation for deferred constraints.

newUuid :: (MonadIO m, IsUUID uuid) => m uuid Source #

Generate a new random UUID using the system's random number generator. UUIDs generated this way are (astronomically likely to be) unique, but not necessarily unpredictable.

For applications where unpredictability is crucial, take care to use a proper cryptographic PRNG to generate your UUIDs.

Constructing queries

class Typeable a => SqlType a where Source #

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

Minimal complete definition

Nothing

Methods

mkLit :: a -> Lit a Source #

Create a literal of this type.

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

sqlType :: Proxy a -> SqlTypeRep Source #

The SQL representation for this type.

fromSql :: SqlValue -> a Source #

Convert an SqlValue into this type.

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

defaultValue :: Lit a Source #

Default value when using def at this type.

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

Instances

Instances details
SqlType Int32 Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Int64 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 Ordering Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Day Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType UTCTime Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType TimeOfDay Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType UUID Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

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

(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

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

Defined in Database.Selda.SqlType

Typeable a => SqlType (UUID' a) Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

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

Defined in Database.Selda.SqlType

class Typeable a => SqlRow a where Source #

Minimal complete definition

Nothing

Methods

nextResult :: ResultReader a Source #

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

default nextResult :: (Generic a, GSqlRow (Rep a)) => ResultReader a Source #

nestedCols :: Proxy a -> Int Source #

The number of nested columns contained in this type.

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

Instances

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

Defined in Database.Selda

Methods

nextResult :: ResultReader (Only a) Source #

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

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 #

(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 GSqlRow f Source #

Minimal complete definition

gNextResult, gNestedCols

Instances

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

Defined in Database.Selda.SqlRow

Methods

gNextResult :: ResultReader ((a :*: b) x)

gNestedCols :: Proxy (a :*: b) -> Int

(TypeError ('Text "Selda currently does not support creating tables from sum types." :$$: 'Text "Restrict your table type to a single data constructor.") :: Constraint) => GSqlRow (a :+: b) Source # 
Instance details

Defined in Database.Selda.SqlRow

Methods

gNextResult :: ResultReader ((a :+: b) x)

gNestedCols :: Proxy (a :+: b) -> Int

SqlType a => GSqlRow (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Database.Selda.SqlRow

Methods

gNextResult :: ResultReader (K1 i a x)

gNestedCols :: Proxy (K1 i a) -> Int

GSqlRow f => GSqlRow (M1 c i f) Source # 
Instance details

Defined in Database.Selda.SqlRow

Methods

gNextResult :: ResultReader (M1 c i f x)

gNestedCols :: Proxy (M1 c i f) -> Int

class (Typeable a, Bounded a, Enum a) => SqlEnum a where Source #

Any type that's bounded, enumerable and has a text representation, and thus representable as a Selda enumerable.

While it would be more efficient to store enumerables as integers, this makes hand-rolled SQL touching the values inscrutable, and will break if the user a) derives Enum and b) changes the order of their constructors. Long-term, this should be implemented in PostgreSQL as a proper enum anyway, which mostly renders the performance argument moot.

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

Instances

Instances details
(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

Instances details
(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]

(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]

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]

class s ~ t => Same s t Source #

Denotes that scopes s and t are identical.

Instances

Instances details
Same (s :: k) (s :: k) Source # 
Instance details

Defined in Database.Selda.Column

Methods

liftC2 :: (Exp SQL a -> Exp SQL b -> Exp SQL c) -> Col s a -> Col s b -> Col s c

(s ~ t, TypeError ('Text "An identifier from an outer scope may not be used in an inner query.") :: Constraint) => Same (s :: k) (t :: k) Source # 
Instance details

Defined in Database.Selda.Column

Methods

liftC2 :: (Exp SQL a -> Exp SQL b -> Exp SQL c) -> Col s a -> Col t b -> Col s c

data Order Source #

The order in which to sort result rows.

Constructors

Asc 
Desc 

Instances

Instances details
Show Order Source # 
Instance details

Defined in Database.Selda.SQL

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

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 #

data a :*: b where infixr 1 Source #

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

Constructors

(:*:) :: a -> b -> a :*: b infixr 1 

Instances

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

Defined in Database.Selda.Types

Associated Types

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

Methods

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

to :: Rep (a :*: b) x -> 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 #

(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 #

(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]

(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, Result b) => Result (Col s a :*: b) Source # 
Instance details

Defined in Database.Selda.Compile

Methods

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

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

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

Defined in Database.Selda.Compile

Methods

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

finalCols :: (Row s a :*: b) -> [SomeCol 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]

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

Defined in Database.Selda.Types

Methods

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

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

Defined in Database.Selda.Types

type Rep (a :*: b) = D1 ('MetaData ":*:" "Database.Selda.Types" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" '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)))

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 :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query s (OuterCols a) Source #

Remove all duplicates from the result set.

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

Restrict the query somehow. Roughly equivalent to WHERE.

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

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

order :: (Same s t, SqlType a) => Col s a -> Order -> Query t () Source #

Sort the result rows in ascending or descending order on the given row.

If multiple order directives are given, later directives are given precedence but do not cancel out earlier ordering directives. To get a list of persons sorted primarily on age and secondarily on name:

peopleInAgeAndNameOrder = do
  person <- select people
  order (person ! name) ascending
  order (person ! age) ascending
  return (person ! name)

For a table [(Alice, 20), (Bob, 20), (Eve, 18)], this query will always return [Eve, Alice, Bob].

The reason for later orderings taking precedence and not the other way around is composability: order should always sort the current result set to avoid weird surprises when a previous order directive is buried somewhere deep in an earlier query. However, the ordering must always be stable, to ensure that previous calls to order are not simply erased.

ascending :: Order Source #

Ordering for order.

descending :: Order Source #

Ordering for order.

orderRandom :: Query s () Source #

Sort the result rows in random order.

union :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query (Inner s) a -> Query s (OuterCols a) Source #

The set union of two queries. Equivalent to the SQL UNION operator.

unionAll :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query (Inner s) a -> Query s (OuterCols a) Source #

The multiset union of two queries. Equivalent to the SQL UNION ALL operator.

inner :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> Query s (OuterCols a) Source #

Explicitly create an inner query. Equivalent to innerJoin (const true).

Sometimes it's handy, for performance reasons and otherwise, to perform a subquery and restrict only that query before adding the result of the query to the result set, instead of first adding the query to the result set and restricting the whole result set afterwards.

suchThat :: (Columns a, Columns (OuterCols a)) => Query (Inner s) a -> (a -> Col (Inner s) Bool) -> Query s (OuterCols a) infixr 7 Source #

Create and filter an inner query, before adding it to the current result set.

q 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

Instances details
SelectorLike Selector Source # 
Instance details

Defined in Database.Selda.Table

Methods

indices :: Selector t a -> [Int]

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

Defined in Database.Selda.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

Instances details
(Relational t, SqlType (FieldType name t), GRSel name (Rep t), NonError (FieldType name t)) => HasField name t Source # 
Instance details

Defined in Database.Selda.FieldSelectors

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

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

class IsLabel (x :: Symbol) a #

Minimal complete definition

fromLabel

Instances

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

Defined in Database.Selda.FieldSelectors

Methods

fromLabel :: Selector t a #

IsLabel x (Selector t a) => IsLabel x (Group t a) Source # 
Instance details

Defined in Database.Selda.Table

Methods

fromLabel :: Group 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.

Methods

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

Is the given column contained in the given set?

Instances

Instances details
Set [] Source # 
Instance details

Defined in Database.Selda

Methods

isIn :: (Same s t, SqlType a) => Col s a -> [Col t a] -> Col s Bool Source #

Set (Query s) Source # 
Instance details

Defined in Database.Selda

Methods

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

class Semigroup a => Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z (Semigroup law)
Concatenation
mconcat = foldr (<>) mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since mappend is a synonym for (<>), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid.

mconcat :: [a] -> a #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

>>> mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"

Instances

Instances details
Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid Builder 
Instance details

Defined in Data.ByteString.Builder.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Monoid ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Monoid IntSet 
Instance details

Defined in Data.IntSet.Internal

Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

mconcat :: [Down a] -> Down a #

(Ord a, Bounded a) => Monoid (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

(Ord a, Bounded a) => Monoid (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

Monoid (IntMap a) 
Instance details

Defined in Data.IntMap.Internal

Methods

mempty :: IntMap a #

mappend :: IntMap a -> IntMap a -> IntMap a #

mconcat :: [IntMap a] -> IntMap a #

Monoid (Seq a) 
Instance details

Defined in Data.Sequence.Internal

Methods

mempty :: Seq a #

mappend :: Seq a -> Seq a -> Seq a #

mconcat :: [Seq a] -> Seq a #

Monoid (MergeSet a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: MergeSet a #

mappend :: MergeSet a -> MergeSet a -> MergeSet a #

mconcat :: [MergeSet a] -> MergeSet a #

Ord a => Monoid (Set a) 
Instance details

Defined in Data.Set.Internal

Methods

mempty :: Set a #

mappend :: Set a -> Set a -> Set a #

mconcat :: [Set a] -> Set a #

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Monoid a => Monoid (Q a)

Since: template-haskell-2.17.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

mempty :: Q a #

mappend :: Q a -> Q a -> Q a #

mconcat :: [Q a] -> Q a #

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

mempty :: (a) #

mappend :: (a) -> (a) -> (a) #

mconcat :: [(a)] -> (a) #

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

mconcat :: [[a]] -> [a] #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

mappend :: ST s a -> ST s a -> ST s a #

mconcat :: [ST s a] -> ST s a #

Ord k => Monoid (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

mempty :: Map k v #

mappend :: Map k v -> Map k v -> Map k v #

mconcat :: [Map k v] -> Map k v #

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

(Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

Monoid (Col s Text) Source # 
Instance details

Defined in Database.Selda

Methods

mempty :: Col s Text #

mappend :: Col s Text -> Col s Text -> Col s Text #

mconcat :: [Col s Text] -> Col s Text #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

(Monoid (f a), Monoid (g a)) => Monoid (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

mempty :: Product f g a #

mappend :: Product f g a -> Product f g a -> Product f g a #

mconcat :: [Product f g a] -> Product f g a #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

Monoid (f (g a)) => Monoid (Compose f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Compose

Methods

mempty :: Compose f g a #

mappend :: Compose f g a -> Compose f g a -> Compose f g a #

mconcat :: [Compose f g a] -> Compose f g a #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

class Semigroup a where #

The class of semigroups (types with an associative binary operation).

Instances should satisfy the following:

Associativity
x <> (y <> z) = (x <> y) <> z

Since: base-4.9.0.0

Methods

(<>) :: a -> a -> a infixr 6 #

An associative operation.

>>> [1,2,3] <> [4,5,6]
[1,2,3,4,5,6]

Instances

Instances details
Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Semigroup Void

Since: base-4.9.0.0

Instance details

Defined in Data.Void

Methods

(<>) :: Void -> Void -> Void #

sconcat :: NonEmpty Void -> Void #

stimes :: Integral b => b -> Void -> Void #

Semigroup Builder 
Instance details

Defined in Data.ByteString.Builder.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Lazy.Internal

Semigroup ShortByteString 
Instance details

Defined in Data.ByteString.Short.Internal

Semigroup IntSet

Since: containers-0.5.7

Instance details

Defined in Data.IntSet.Internal

Semigroup Ordering

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Semigroup QueryFragment Source # 
Instance details

Defined in Database.Selda.SQL

Semigroup ()

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: () -> () -> () #

sconcat :: NonEmpty () -> () #

stimes :: Integral b => b -> () -> () #

Semigroup a => Semigroup (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

(<>) :: Identity a -> Identity a -> Identity a #

sconcat :: NonEmpty (Identity a) -> Identity a #

stimes :: Integral b => b -> Identity a -> Identity a #

Semigroup (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Semigroup a => Semigroup (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

(<>) :: Down a -> Down a -> Down a #

sconcat :: NonEmpty (Down a) -> Down a #

stimes :: Integral b => b -> Down a -> Down a #

Semigroup (First a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: First a -> First a -> First a #

sconcat :: NonEmpty (First a) -> First a #

stimes :: Integral b => b -> First a -> First a #

Semigroup (Last a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Last a -> Last a -> Last a #

sconcat :: NonEmpty (Last a) -> Last a #

stimes :: Integral b => b -> Last a -> Last a #

Ord a => Semigroup (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

Ord a => Semigroup (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

Monoid m => Semigroup (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Semigroup (Dual a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Semigroup (Endo a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Num a => Semigroup (Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Semigroup (Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Semigroup p => Semigroup (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: Par1 p -> Par1 p -> Par1 p #

sconcat :: NonEmpty (Par1 p) -> Par1 p #

stimes :: Integral b => b -> Par1 p -> Par1 p #

Semigroup (IntMap a)

Since: containers-0.5.7

Instance details

Defined in Data.IntMap.Internal

Methods

(<>) :: IntMap a -> IntMap a -> IntMap a #

sconcat :: NonEmpty (IntMap a) -> IntMap a #

stimes :: Integral b => b -> IntMap a -> IntMap a #

Semigroup (Seq a)

Since: containers-0.5.7

Instance details

Defined in Data.Sequence.Internal

Methods

(<>) :: Seq a -> Seq a -> Seq a #

sconcat :: NonEmpty (Seq a) -> Seq a #

stimes :: Integral b => b -> Seq a -> Seq a #

Semigroup (MergeSet a) 
Instance details

Defined in Data.Set.Internal

Methods

(<>) :: MergeSet a -> MergeSet a -> MergeSet a #

sconcat :: NonEmpty (MergeSet a) -> MergeSet a #

stimes :: Integral b => b -> MergeSet a -> MergeSet a #

Ord a => Semigroup (Set a)

Since: containers-0.5.7

Instance details

Defined in Data.Set.Internal

Methods

(<>) :: Set a -> Set a -> Set a #

sconcat :: NonEmpty (Set a) -> Set a #

stimes :: Integral b => b -> Set a -> Set a #

Semigroup a => Semigroup (IO a)

Since: base-4.10.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: IO a -> IO a -> IO a #

sconcat :: NonEmpty (IO a) -> IO a #

stimes :: Integral b => b -> IO a -> IO a #

Semigroup a => Semigroup (Q a)

Since: template-haskell-2.17.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

(<>) :: Q a -> Q a -> Q a #

sconcat :: NonEmpty (Q a) -> Q a #

stimes :: Integral b => b -> Q a -> Q a #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Semigroup a => Semigroup (Maybe a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: Maybe a -> Maybe a -> Maybe a #

sconcat :: NonEmpty (Maybe a) -> Maybe a #

stimes :: Integral b => b -> Maybe a -> Maybe a #

Semigroup a => Semigroup (a)

Since: base-4.15

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a) -> (a) #

stimes :: Integral b => b -> (a) -> (a) #

Semigroup [a]

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: [a] -> [a] -> [a] #

sconcat :: NonEmpty [a] -> [a] #

stimes :: Integral b => b -> [a] -> [a] #

Semigroup (Either a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b #

sconcat :: NonEmpty (Either a b) -> Either a b #

stimes :: Integral b0 => b0 -> Either a b -> Either a b #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Semigroup (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: U1 p -> U1 p -> U1 p #

sconcat :: NonEmpty (U1 p) -> U1 p #

stimes :: Integral b => b -> U1 p -> U1 p #

Semigroup (V1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: V1 p -> V1 p -> V1 p #

sconcat :: NonEmpty (V1 p) -> V1 p #

stimes :: Integral b => b -> V1 p -> V1 p #

Semigroup a => Semigroup (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

(<>) :: ST s a -> ST s a -> ST s a #

sconcat :: NonEmpty (ST s a) -> ST s a #

stimes :: Integral b => b -> ST s a -> ST s a #

Ord k => Semigroup (Map k v) 
Instance details

Defined in Data.Map.Internal

Methods

(<>) :: Map k v -> Map k v -> Map k v #

sconcat :: NonEmpty (Map k v) -> Map k v #

stimes :: Integral b => b -> Map k v -> Map k v #

Semigroup b => Semigroup (a -> b)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

sconcat :: NonEmpty (a -> b) -> a -> b #

stimes :: Integral b0 => b0 -> (a -> b) -> a -> b #

(Semigroup a, Semigroup b) => Semigroup (a, b)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b) -> (a, b) -> (a, b) #

sconcat :: NonEmpty (a, b) -> (a, b) #

stimes :: Integral b0 => b0 -> (a, b) -> (a, b) #

Semigroup a => Semigroup (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

(<>) :: Const a b -> Const a b -> Const a b #

sconcat :: NonEmpty (Const a b) -> Const a b #

stimes :: Integral b0 => b0 -> Const a b -> Const a b #

(Applicative f, Semigroup a) => Semigroup (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a #

sconcat :: NonEmpty (Ap f a) -> Ap f a #

stimes :: Integral b => b -> Ap f a -> Ap f a #

Alternative f => Semigroup (Alt f a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a #

sconcat :: NonEmpty (Alt f a) -> Alt f a #

stimes :: Integral b => b -> Alt f a -> Alt f a #

Semigroup (f p) => Semigroup (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: Rec1 f p -> Rec1 f p -> Rec1 f p #

sconcat :: NonEmpty (Rec1 f p) -> Rec1 f p #

stimes :: Integral b => b -> Rec1 f p -> Rec1 f p #

Semigroup (Col s Text) Source # 
Instance details

Defined in Database.Selda

Methods

(<>) :: Col s Text -> Col s Text -> Col s Text #

sconcat :: NonEmpty (Col s Text) -> Col s Text #

stimes :: Integral b => b -> Col s Text -> Col s Text #

(Semigroup a, Semigroup b, Semigroup c) => Semigroup (a, b, c)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c) -> (a, b, c) -> (a, b, c) #

sconcat :: NonEmpty (a, b, c) -> (a, b, c) #

stimes :: Integral b0 => b0 -> (a, b, c) -> (a, b, c) #

(Semigroup (f a), Semigroup (g a)) => Semigroup (Product f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Product

Methods

(<>) :: Product f g a -> Product f g a -> Product f g a #

sconcat :: NonEmpty (Product f g a) -> Product f g a #

stimes :: Integral b => b -> Product f g a -> Product f g a #

(Semigroup (f p), Semigroup (g p)) => Semigroup ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

sconcat :: NonEmpty ((f :*: g) p) -> (f :*: g) p #

stimes :: Integral b => b -> (f :*: g) p -> (f :*: g) p #

Semigroup c => Semigroup (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: K1 i c p -> K1 i c p -> K1 i c p #

sconcat :: NonEmpty (K1 i c p) -> K1 i c p #

stimes :: Integral b => b -> K1 i c p -> K1 i c p #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d) => Semigroup (a, b, c, d)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

sconcat :: NonEmpty (a, b, c, d) -> (a, b, c, d) #

stimes :: Integral b0 => b0 -> (a, b, c, d) -> (a, b, c, d) #

Semigroup (f (g a)) => Semigroup (Compose f g a)

Since: base-4.16.0.0

Instance details

Defined in Data.Functor.Compose

Methods

(<>) :: Compose f g a -> Compose f g a -> Compose f g a #

sconcat :: NonEmpty (Compose f g a) -> Compose f g a #

stimes :: Integral b => b -> Compose f g a -> Compose f g a #

Semigroup (f (g p)) => Semigroup ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

sconcat :: NonEmpty ((f :.: g) p) -> (f :.: g) p #

stimes :: Integral b => b -> (f :.: g) p -> (f :.: g) p #

Semigroup (f p) => Semigroup (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

(<>) :: M1 i c f p -> M1 i c f p -> M1 i c f p #

sconcat :: NonEmpty (M1 i c f p) -> M1 i c f p #

stimes :: Integral b => b -> M1 i c f p -> M1 i c f p #

(Semigroup a, Semigroup b, Semigroup c, Semigroup d, Semigroup e) => Semigroup (a, b, c, d, e)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

sconcat :: NonEmpty (a, b, c, d, e) -> (a, b, c, d, e) #

stimes :: Integral b0 => b0 -> (a, b, c, d, e) -> (a, b, c, d, e) #

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

Instances details
Generic (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (ID a) :: Type -> Type #

Methods

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

to :: Rep (ID a) x -> 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 #

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 #

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

Defined in Database.Selda

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

Defined in Database.Selda.SqlType

type Rep (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep (ID a) = D1 ('MetaData "ID" "Database.Selda.SqlType" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" 'True) (C1 ('MetaCons "ID" 'PrefixI 'True) (S1 ('MetaSel ('Just "untyped") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RowID)))

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

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

toId :: Int64 -> ID a Source #

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

class IsUUID a where Source #

Any type which is backed by an UUID.

Methods

uuid :: UUID -> a Source #

Instances

Instances details
IsUUID UUID Source # 
Instance details

Defined in Database.Selda

Methods

uuid :: UUID -> UUID Source #

IsUUID (UUID' a) Source # 
Instance details

Defined in Database.Selda

Methods

uuid :: UUID -> UUID' a Source #

data UUID' a Source #

An UUID identifying a database row.

Instances

Instances details
Generic (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (UUID' a) :: Type -> Type #

Methods

from :: UUID' a -> Rep (UUID' a) x #

to :: Rep (UUID' a) x -> UUID' a #

Show (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> UUID' a -> ShowS #

show :: UUID' a -> String #

showList :: [UUID' a] -> ShowS #

Eq (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: UUID' a -> UUID' a -> Bool #

(/=) :: UUID' a -> UUID' a -> Bool #

Ord (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: UUID' a -> UUID' a -> Ordering #

(<) :: UUID' a -> UUID' a -> Bool #

(<=) :: UUID' a -> UUID' a -> Bool #

(>) :: UUID' a -> UUID' a -> Bool #

(>=) :: UUID' a -> UUID' a -> Bool #

max :: UUID' a -> UUID' a -> UUID' a #

min :: UUID' a -> UUID' a -> UUID' a #

IsUUID (UUID' a) Source # 
Instance details

Defined in Database.Selda

Methods

uuid :: UUID -> UUID' a Source #

Typeable a => SqlType (UUID' a) Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

type Rep (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep (UUID' a) = D1 ('MetaData "UUID'" "Database.Selda.SqlType" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" 'True) (C1 ('MetaCons "UUID" 'PrefixI 'True) (S1 ('MetaSel ('Just "untypedUuid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID)))

typedUuid :: UUID -> UUID' a Source #

Convert an untyped UUID to a typed one. Use sparingly, preferably only during deserialization.

data RowID Source #

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

Instances

Instances details
Generic RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep RowID :: Type -> Type #

Methods

from :: RowID -> Rep RowID x #

to :: Rep RowID x -> RowID #

Show RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> RowID -> ShowS #

show :: RowID -> String #

showList :: [RowID] -> ShowS #

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 #

SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep RowID Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep RowID = D1 ('MetaData "RowID" "Database.Selda.SqlType" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" 'True) (C1 ('MetaCons "RowID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

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

Inspect a row identifier.

toRowId :: Int64 -> RowID Source #

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

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

Comparisons over columns. Note that when comparing nullable (i.e. Maybe) columns, SQL NULL semantics are used. This means that comparing to a NULL field will remove the row in question from the current set. To test for NULL, use isNull instead of .== literal Nothing.

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

Comparisons over columns. Note that when comparing nullable (i.e. Maybe) columns, SQL NULL semantics are used. This means that comparing to a NULL field will remove the row in question from the current set. To test for NULL, use isNull instead of .== literal Nothing.

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

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

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

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

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

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

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

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

(.||) :: Same s t => Col s Bool -> Col t 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 :: forall r s c. SqlType c => Selector r c -> c -> Row s r -> Col s Bool Source #

Returns true if the given field in the given row is equal to the given literal.

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 :: (Same s t, Same t u, SqlType a) => Col s Bool -> Col t a -> Col u a -> Col s a Source #

Perform a conditional on a column

ifNull :: (Same s t, SqlType a) => Col s a -> Col t (Maybe a) -> Col s a Source #

If the second value is Nothing, return the first value. Otherwise return the second value.

matchNull :: (SqlType a, SqlType b, Same s t) => Col s b -> (Col s a -> Col s b) -> Col t (Maybe a) -> Col s b Source #

Applies the given function to the given nullable column where it isn't null, and returns the given default value where it is.

This is the Selda equivalent of maybe.

toUpper :: Col s Text -> Col s Text Source #

Convert the given string to uppercase.

toLower :: Col s Text -> Col s Text Source #

Convert the given string to lowercase.

new :: forall s a. Relational a => [Assignment s a] -> Row s a Source #

Create a new row with the given fields. Any unassigned fields will contain their default values.

row :: forall s a. Relational a => a -> Row s a Source #

Create a new row from the given value. This can be useful when you want to update all or most of a row:

update users (#uid `is` user_id)
             (\old -> row user_info `with` [...])

only :: SqlType a => Col s a -> Row s (Only a) Source #

Create a singleton table column from an appropriate value.

class Mappable f where Source #

Any container type which can be mapped over. Sort of like Functor, if you squint a bit.

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

Instances details
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 :: Type -> TYPE LiftedRep -> TYPE LiftedRep) 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" []

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

fromBool :: (SqlType a, Num a) => Col s Bool -> Col s a Source #

Convert a boolean column to any numeric type.

fromInt :: (SqlType a, Num a) => Col s Int -> Col s a Source #

Convert an integer column to any numeric type.

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

Instances details
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 (Aggr (Inner s) a) Source # 
Instance details

Defined in Database.Selda.Inner

Methods

unAggrs :: Aggr (Inner s) a -> [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]

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

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

Defined in Database.Selda.Inner

Methods

unAggrs :: Aggr (Inner s) a -> [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]

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

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

Defined in Database.Selda.Inner

Methods

unAggrs :: Aggr (Inner s) a -> [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]

class SqlType a => SqlOrd a Source #

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

Instances

Instances details
SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

SqlOrd Text Source # 
Instance details

Defined in Database.Selda

SqlOrd Day Source # 
Instance details

Defined in Database.Selda

SqlOrd UTCTime Source # 
Instance details

Defined in Database.Selda

SqlOrd TimeOfDay Source # 
Instance details

Defined in Database.Selda

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

Defined in Database.Selda

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

Defined in Database.Selda

SqlOrd a => SqlOrd (Maybe 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 :: (Same s t, SqlType a) => Col (Inner s) a -> Query (Inner t) (Aggr (Inner t) a) Source #

Group an aggregate query by a column. Attempting to group a non-aggregate query is a type error. An aggregate representing the grouped-by column is returned, which can be returned from the aggregate query. For instance, if you want to find out how many people have a pet at home:

aggregate $ do
  person <- select people
  name' <- groupBy (person ! name)
  return (name' :*: count(person ! pet_name) .> 0)

count :: SqlType a => Col s a -> Aggr s Int Source #

The number of non-null values in the given column.

avg :: (SqlType a, Num a) => Col s a -> Aggr s (Maybe a) Source #

The average of all values in the given column.

sum_ :: forall a b s. (SqlType a, SqlType b, Num a, Num b) => Col s a -> Aggr s b Source #

Sum all values in the given column.

max_ :: SqlOrd a => Col s a -> Aggr s (Maybe a) Source #

The greatest value in the given column. Texts are compared lexically.

min_ :: SqlOrd a => Col s a -> Aggr s (Maybe a) Source #

The smallest value in the given column. Texts are compared lexically.

Modifying tables

insert :: (MonadSelda m, Relational a) => Table a -> [a] -> m Int Source #

Insert the given values into the given table. All columns of the table must be present. If your table has an auto-incrementing primary key, use the special value def for that column to get the auto-incrementing behavior. Returns the number of rows that were inserted.

To insert a list of tuples into a table with auto-incrementing primary key:

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

people :: Table Person
people = table "people" [autoPrimary :- id]

main = withSQLite "my_database.sqlite" $ do
  insert_ people
    [ Person def "Link" 125 (Just "horse")
    , Person def "Zelda" 119 Nothing
    , ...
    ]

Note that if one or more of the inserted rows would cause a constraint violation, NO rows will be inserted; the whole insertion fails atomically.

insert_ :: (MonadSelda m, Relational a) => Table a -> [a] -> m () Source #

Like insert, but does not return anything. Use this when you really don't care about how many rows were inserted.

insertWithPK :: (MonadSelda m, Relational a) => Table a -> [a] -> m (ID a) Source #

Like insert, but returns the primary key of the last inserted row. Attempting to run this operation on a table without an auto-incrementing primary key will always return a row identifier that is guaranteed to not match any row in any table.

tryInsert :: (MonadSelda m, MonadCatch m, Relational a) => Table a -> [a] -> m Bool Source #

Attempt to insert a list of rows into a table, but don't raise an error if the insertion fails. Returns True if the insertion succeeded, otherwise False.

Like insert, if even one of the inserted rows would cause a constraint violation, the whole insert operation fails.

insertUnless :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> [a] -> m (Maybe (ID a)) Source #

Perform the given insert, if no rows already present in the table match the given predicate. Returns the primary key of the last inserted row, if the insert was performed. If called on a table which doesn't have an auto-incrementing primary key, Just id is always returned on successful insert, where id is a row identifier guaranteed to not match any row in any table.

insertWhen :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> [a] -> m (Maybe (ID a)) Source #

Like insertUnless, but performs the insert when at least one row matches the predicate.

def :: SqlType a => a Source #

The default value for a column during insertion. For an auto-incrementing primary key, the default value is the next key.

Using def in any other context than insertion results in a runtime error.

update Source #

Arguments

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

Table to update.

-> (Row (Backend m) a -> Col (Backend m) Bool)

Predicate.

-> (Row (Backend m) a -> Row (Backend m) a)

Update function.

-> m Int 

Update the given table using the given update function, for all rows matching the given predicate. Returns the number of updated rows.

update_ :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> m () Source #

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

upsert :: (MonadSelda m, MonadMask m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> (Row (Backend m) a -> Row (Backend m) a) -> [a] -> m (Maybe (ID a)) Source #

Attempt to perform the given update. If no rows were updated, insert the given row. Returns the primary key of the inserted row, if the insert was performed. Calling this function on a table which does not have a primary key will return Just id on a successful insert, where id is a row identifier guaranteed to not match any row in any table.

Note that this may perform two separate queries: one update, potentially followed by one insert.

deleteFrom :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> m Int Source #

From the given table, delete all rows matching the given predicate. Returns the number of deleted rows.

deleteFrom_ :: (MonadSelda m, Relational a) => Table a -> (Row (Backend m) a -> Col (Backend m) Bool) -> m () Source #

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

Prepared statements

class Preparable q Source #

Minimal complete definition

mkQuery

Instances

Instances details
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

(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

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

Instances details
(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.

Note that when using a constrained backend type variable (i.e. foo :: Bar b => SeldaM b [Int]), optimizations must be enabled for prepared statements to be effective.

A usage example:

persons :: Table (Text, Int)
(persons, name :*: age) = tableWithSelectors "ages" [name :- primary]

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

Defining schemas

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

Instances details
Generic All 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

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 :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Generic Version 
Instance details

Defined in Data.Version

Associated Types

type Rep Version :: Type -> Type #

Methods

from :: Version -> Rep Version x #

to :: Rep Version x -> Version #

Generic Void 
Instance details

Defined in Data.Void

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

Generic Fingerprint 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fingerprint :: Type -> Type #

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: Type -> Type #

Generic DecidedStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic Fixity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Fixity :: Type -> Type #

Methods

from :: Fixity -> Rep Fixity x #

to :: Rep Fixity x -> Fixity #

Generic SourceStrictness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic ExitCode 
Instance details

Defined in GHC.IO.Exception

Associated Types

type Rep ExitCode :: Type -> Type #

Methods

from :: ExitCode -> Rep ExitCode x #

to :: Rep ExitCode x -> ExitCode #

Generic CCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep CCFlags :: Type -> Type #

Methods

from :: CCFlags -> Rep CCFlags x #

to :: Rep CCFlags x -> CCFlags #

Generic ConcFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ConcFlags :: Type -> Type #

Generic DebugFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DebugFlags :: Type -> Type #

Generic DoCostCentres 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoCostCentres :: Type -> Type #

Generic DoHeapProfile 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoHeapProfile :: Type -> Type #

Generic DoTrace 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep DoTrace :: Type -> Type #

Methods

from :: DoTrace -> Rep DoTrace x #

to :: Rep DoTrace x -> DoTrace #

Generic GCFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GCFlags :: Type -> Type #

Methods

from :: GCFlags -> Rep GCFlags x #

to :: Rep GCFlags x -> GCFlags #

Generic GiveGCStats 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep GiveGCStats :: Type -> Type #

Generic MiscFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep MiscFlags :: Type -> Type #

Generic ParFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ParFlags :: Type -> Type #

Methods

from :: ParFlags -> Rep ParFlags x #

to :: Rep ParFlags x -> ParFlags #

Generic ProfFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep ProfFlags :: Type -> Type #

Generic RTSFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep RTSFlags :: Type -> Type #

Methods

from :: RTSFlags -> Rep RTSFlags x #

to :: Rep RTSFlags x -> RTSFlags #

Generic TickyFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TickyFlags :: Type -> Type #

Generic TraceFlags 
Instance details

Defined in GHC.RTS.Flags

Associated Types

type Rep TraceFlags :: Type -> Type #

Generic SrcLoc 
Instance details

Defined in GHC.Generics

Associated Types

type Rep SrcLoc :: Type -> Type #

Methods

from :: SrcLoc -> Rep SrcLoc x #

to :: Rep SrcLoc x -> SrcLoc #

Generic GeneralCategory 
Instance details

Defined in GHC.Generics

Associated Types

type Rep GeneralCategory :: Type -> Type #

Generic ForeignSrcLang 
Instance details

Defined in GHC.ForeignSrcLang.Type

Associated Types

type Rep ForeignSrcLang :: Type -> Type #

Generic Extension 
Instance details

Defined in GHC.LanguageExtensions.Type

Associated Types

type Rep Extension :: Type -> Type #

Generic Ordering 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Ordering :: Type -> Type #

Methods

from :: Ordering -> Rep Ordering x #

to :: Rep Ordering x -> Ordering #

Generic RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep RowID :: Type -> Type #

Methods

from :: RowID -> Rep RowID x #

to :: Rep RowID x -> RowID #

Generic AnnLookup 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnLookup :: Type -> Type #

Generic AnnTarget 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep AnnTarget :: Type -> Type #

Generic Bang 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bang :: Type -> Type #

Methods

from :: Bang -> Rep Bang x #

to :: Rep Bang x -> Bang #

Generic Body 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Body :: Type -> Type #

Methods

from :: Body -> Rep Body x #

to :: Rep Body x -> Body #

Generic Bytes 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Bytes :: Type -> Type #

Methods

from :: Bytes -> Rep Bytes x #

to :: Rep Bytes x -> Bytes #

Generic Callconv 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Callconv :: Type -> Type #

Methods

from :: Callconv -> Rep Callconv x #

to :: Rep Callconv x -> Callconv #

Generic Clause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Clause :: Type -> Type #

Methods

from :: Clause -> Rep Clause x #

to :: Rep Clause x -> Clause #

Generic Con 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Con :: Type -> Type #

Methods

from :: Con -> Rep Con x #

to :: Rep Con x -> Con #

Generic Dec 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Dec :: Type -> Type #

Methods

from :: Dec -> Rep Dec x #

to :: Rep Dec x -> Dec #

Generic DecidedStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DecidedStrictness :: Type -> Type #

Generic DerivClause 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivClause :: Type -> Type #

Generic DerivStrategy 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DerivStrategy :: Type -> Type #

Generic DocLoc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep DocLoc :: Type -> Type #

Methods

from :: DocLoc -> Rep DocLoc x #

to :: Rep DocLoc x -> DocLoc #

Generic Exp 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Exp :: Type -> Type #

Methods

from :: Exp -> Rep Exp x #

to :: Rep Exp x -> Exp #

Generic FamilyResultSig 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FamilyResultSig :: Type -> Type #

Generic Fixity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Fixity :: Type -> Type #

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 :: Type -> Type #

Generic Foreign 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Foreign :: Type -> Type #

Methods

from :: Foreign -> Rep Foreign x #

to :: Rep Foreign x -> Foreign #

Generic FunDep 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep FunDep :: Type -> Type #

Methods

from :: FunDep -> Rep FunDep x #

to :: Rep FunDep x -> FunDep #

Generic Guard 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Guard :: Type -> Type #

Methods

from :: Guard -> Rep Guard x #

to :: Rep Guard x -> Guard #

Generic Info 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Info :: Type -> Type #

Methods

from :: Info -> Rep Info x #

to :: Rep Info x -> Info #

Generic InjectivityAnn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep InjectivityAnn :: Type -> Type #

Generic Inline 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Inline :: Type -> Type #

Methods

from :: Inline -> Rep Inline x #

to :: Rep Inline x -> Inline #

Generic Lit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Lit :: Type -> Type #

Methods

from :: Lit -> Rep Lit x #

to :: Rep Lit x -> Lit #

Generic Loc 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Loc :: Type -> Type #

Methods

from :: Loc -> Rep Loc x #

to :: Rep Loc x -> Loc #

Generic Match 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Match :: Type -> Type #

Methods

from :: Match -> Rep Match x #

to :: Rep Match x -> Match #

Generic ModName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModName :: Type -> Type #

Methods

from :: ModName -> Rep ModName x #

to :: Rep ModName x -> ModName #

Generic Module 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Module :: Type -> Type #

Methods

from :: Module -> Rep Module x #

to :: Rep Module x -> Module #

Generic ModuleInfo 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep ModuleInfo :: Type -> Type #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

Generic NameFlavour 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameFlavour :: Type -> Type #

Generic NameSpace 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep NameSpace :: Type -> Type #

Generic OccName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep OccName :: Type -> Type #

Methods

from :: OccName -> Rep OccName x #

to :: Rep OccName x -> OccName #

Generic Overlap 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Overlap :: Type -> Type #

Methods

from :: Overlap -> Rep Overlap x #

to :: Rep Overlap x -> Overlap #

Generic Pat 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pat :: Type -> Type #

Methods

from :: Pat -> Rep Pat x #

to :: Rep Pat x -> Pat #

Generic PatSynArgs 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynArgs :: Type -> Type #

Generic PatSynDir 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PatSynDir :: Type -> Type #

Generic Phases 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Phases :: Type -> Type #

Methods

from :: Phases -> Rep Phases x #

to :: Rep Phases x -> Phases #

Generic PkgName 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep PkgName :: Type -> Type #

Methods

from :: PkgName -> Rep PkgName x #

to :: Rep PkgName x -> PkgName #

Generic Pragma 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Pragma :: Type -> Type #

Methods

from :: Pragma -> Rep Pragma x #

to :: Rep Pragma x -> Pragma #

Generic Range 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Range :: Type -> Type #

Methods

from :: Range -> Rep Range x #

to :: Rep Range x -> Range #

Generic Role 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Role :: Type -> Type #

Methods

from :: Role -> Rep Role x #

to :: Rep Role x -> Role #

Generic RuleBndr 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleBndr :: Type -> Type #

Methods

from :: RuleBndr -> Rep RuleBndr x #

to :: Rep RuleBndr x -> RuleBndr #

Generic RuleMatch 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep RuleMatch :: Type -> Type #

Generic Safety 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Safety :: Type -> Type #

Methods

from :: Safety -> Rep Safety x #

to :: Rep Safety x -> Safety #

Generic SourceStrictness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceStrictness :: Type -> Type #

Generic SourceUnpackedness 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep SourceUnpackedness :: Type -> Type #

Generic Specificity 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Specificity :: Type -> Type #

Generic Stmt 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Stmt :: Type -> Type #

Methods

from :: Stmt -> Rep Stmt x #

to :: Rep Stmt x -> Stmt #

Generic TyLit 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TyLit :: Type -> Type #

Methods

from :: TyLit -> Rep TyLit x #

to :: Rep TyLit x -> TyLit #

Generic TySynEqn 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TySynEqn :: Type -> Type #

Methods

from :: TySynEqn -> Rep TySynEqn x #

to :: Rep TySynEqn x -> TySynEqn #

Generic Type 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Type :: Type -> Type #

Methods

from :: Type -> Rep Type x #

to :: Rep Type x -> Type #

Generic TypeFamilyHead 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep TypeFamilyHead :: Type -> Type #

Generic () 
Instance details

Defined in GHC.Generics

Associated Types

type Rep () :: Type -> Type #

Methods

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

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

Generic Bool 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Bool :: Type -> Type #

Methods

from :: Bool -> Rep Bool x #

to :: Rep Bool x -> Bool #

Generic (ZipList a) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Complex a) 
Instance details

Defined in Data.Complex

Associated Types

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

Methods

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

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

Generic (Identity a) 
Instance details

Defined in Data.Functor.Identity

Associated Types

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

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) :: Type -> Type #

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) :: Type -> Type #

Methods

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

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

Generic (Down a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Down a) :: Type -> Type #

Methods

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

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

Generic (First a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

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) :: Type -> Type #

Methods

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

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

Generic (Max a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (Min a) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Generic (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

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) :: Type -> Type #

Methods

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

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

Generic (Product a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Par1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Digit a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Digit a) :: Type -> Type #

Methods

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

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

Generic (Elem a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Elem a) :: Type -> Type #

Methods

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

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

Generic (FingerTree a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (FingerTree a) :: Type -> Type #

Methods

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

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

Generic (Node a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

type Rep (Node a) :: Type -> Type #

Methods

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

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

Generic (ViewL a) 
Instance details

Defined in Data.Sequence.Internal

Associated Types

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

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) :: Type -> Type #

Methods

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

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

Generic (Tree a) 
Instance details

Defined in Data.Tree

Associated Types

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

Methods

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

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

Generic (Only a) Source # 
Instance details

Defined in Database.Selda

Associated Types

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

Methods

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

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

Generic (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (ID a) :: Type -> Type #

Methods

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

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

Generic (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (UUID' a) :: Type -> Type #

Methods

from :: UUID' a -> Rep (UUID' a) x #

to :: Rep (UUID' a) x -> UUID' a #

Generic (TyVarBndr flag) 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep (TyVarBndr flag) :: Type -> Type #

Methods

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

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

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Maybe a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (a) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a) :: Type -> Type #

Methods

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

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

Generic [a] 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (WrappedMonad m a) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Either a b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Arg a b) 
Instance details

Defined in Data.Semigroup

Associated Types

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

Methods

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

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

Generic (U1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (V1 p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in Database.Selda.Types

Associated Types

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

Methods

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

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

Generic (a, b) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (WrappedArrow a b c) 
Instance details

Defined in Control.Applicative

Associated Types

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

Methods

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

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

Generic (Kleisli m a b) 
Instance details

Defined in Control.Arrow

Associated Types

type Rep (Kleisli m a b) :: Type -> Type #

Methods

from :: Kleisli m a b -> Rep (Kleisli m a b) x #

to :: Rep (Kleisli m a b) x -> Kleisli m a b #

Generic (Const a b) 
Instance details

Defined in Data.Functor.Const

Associated Types

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

Methods

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

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

Generic (Ap f a) 
Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

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

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

Generic (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

Associated Types

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

Methods

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

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

Generic (Rec1 f p) 
Instance details

Defined in GHC.Generics

Associated Types

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

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

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) :: Type -> Type #

Methods

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

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

Generic (Product f g a) 
Instance details

Defined in Data.Functor.Product

Associated Types

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

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) :: Type -> Type #

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

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) :: Type -> Type #

Methods

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

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

Generic (K1 i c p) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (Compose f g a) 
Instance details

Defined in Data.Functor.Compose

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Generic (M1 i c f p) 
Instance details

Defined in GHC.Generics

Associated Types

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

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 (a, b, c, d, e) 
Instance details

Defined in GHC.Generics

Associated Types

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

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 (a, b, c, d, e, f) 
Instance details

Defined in GHC.Generics

Associated Types

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

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) :: Type -> Type #

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) #

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

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

Methods

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

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

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

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j) :: Type -> Type #

Methods

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

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

Generic (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k) :: Type -> Type #

Methods

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

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

Generic (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l) x -> (a, b, c, d, e, f, g, h, i, j, k, l) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

Generic (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) :: Type -> Type #

Methods

from :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x #

to :: Rep (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) x -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

data TableName Source #

Name of a database table.

Instances

Instances details
IsString TableName Source # 
Instance details

Defined in Database.Selda.Types

Show TableName Source # 
Instance details

Defined in Database.Selda.Types

Eq TableName Source # 
Instance details

Defined in Database.Selda.Types

Ord TableName Source # 
Instance details

Defined in Database.Selda.Types

data ColName Source #

Name of a database column.

Instances

Instances details
IsString ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

fromString :: String -> ColName #

Show ColName Source # 
Instance details

Defined in Database.Selda.Types

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

data Attr a where Source #

A generic column attribute. Essentially a pair or a record selector over the type a and a column attribute. An attribute may be either a Group attribute, meaning that it can span multiple columns, or a Selector -- single column -- attribute.

Constructors

(:-) :: SelectorLike g => g t a -> Attribute g t a -> Attr t infixl 0 

data Attribute (g :: * -> * -> *) t c Source #

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

class ForeignKey a b where Source #

Methods

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

A foreign key constraint referencing the given table and column.

Instances

Instances details
ForeignKey a a Source # 
Instance details

Defined in Database.Selda.Table

Methods

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

ForeignKey a (Maybe a) Source # 
Instance details

Defined in Database.Selda.Table

Methods

foreignKey :: Table t -> Selector t a -> Attribute Selector 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 Selector self a Source #

class SelectorLike g Source #

Minimal complete definition

indices

Instances

Instances details
SelectorLike Selector Source # 
Instance details

Defined in Database.Selda.Table

Methods

indices :: Selector t a -> [Int]

SelectorLike Group Source # 
Instance details

Defined in Database.Selda.Table

Methods

indices :: Group t a -> [Int]

data Group t a where Source #

A non-empty list of selectors, where the element selectors need not have the same type. Used to specify constraints, such as uniqueness or primary key, potentially spanning multiple columns.

Constructors

(:+) :: Selector t a -> Group t b -> Group t (a :*: b) infixr 1 
Single :: Selector t a -> Group t a 

Instances

Instances details
SelectorLike Group Source # 
Instance details

Defined in Database.Selda.Table

Methods

indices :: Group t a -> [Int]

IsLabel x (Selector t a) => IsLabel x (Group t a) Source # 
Instance details

Defined in Database.Selda.Table

Methods

fromLabel :: Group t a #

sel :: Selector t a -> Selector t a Source #

Annotation to force the type of a polymorphic label (i.e. #foo) to be a selector. This is useful, for instance, when defining unique constraints: sel #foo :- unique.

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" [#id :- autoPrimary]

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]
  (fromJust . stripPrefix "person")

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

primary :: Attribute Group t a Source #

A primary key which does not auto-increment.

autoPrimary :: Attribute Selector t (ID t) Source #

An auto-incrementing primary key.

weakAutoPrimary :: Attribute Selector t (ID t) Source #

A "weakly auto-incrementing" primary key. Behaves like autoPrimary, but the sequence of generated keys is not guaranteed to be monotonically increasing.

This gives better performance on some backends, but means that the relation a > b = a was inserted at a later point in time than b does not hold.

untypedAutoPrimary :: Attribute Selector t RowID Source #

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

unique :: Attribute Group t a 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 Group t c Source #

Create an index on these column(s).

indexUsing :: IndexMethod -> Attribute Group 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.

Tuple convenience functions

class Tup a Source #

Minimal complete definition

tupHead

Instances

Instances details
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.

Useful re-exports

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

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

Instances details
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 (ListT m) 
Instance details

Defined in Control.Monad.Trans.List

Methods

liftIO :: IO a -> ListT m a #

MonadIO m => MonadIO (MaybeT m) 
Instance details

Defined in Control.Monad.Trans.Maybe

Methods

liftIO :: IO a -> MaybeT m a #

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

Defined in Database.Selda.Backend.Internal

Methods

liftIO :: IO a -> SeldaT b 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 (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 #

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

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r 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 #

(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 :: Type -> Type) #

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

Instances details
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 b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

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

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

generalBracket :: SeldaT b m a -> (a -> ExitCase b0 -> SeldaT b m c) -> (a -> SeldaT b m b0) -> SeldaT b m (b0, 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 (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) #

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 => 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, 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. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances

Instances details
Hashable Text 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Text -> Int #

hash :: Text -> Int #

SqlOrd Text Source # 
Instance details

Defined in Database.Selda

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

IsString (Col s Text) Source # 
Instance details

Defined in Database.Selda.Column

Methods

fromString :: String -> Col s Text #

Monoid (Col s Text) Source # 
Instance details

Defined in Database.Selda

Methods

mempty :: Col s Text #

mappend :: Col s Text -> Col s Text -> Col s Text #

mconcat :: [Col s Text] -> Col s Text #

Semigroup (Col s Text) Source # 
Instance details

Defined in Database.Selda

Methods

(<>) :: Col s Text -> Col s Text -> Col s Text #

sconcat :: NonEmpty (Col s Text) -> Col s Text #

stimes :: Integral b => b -> Col s Text -> 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

Instances details
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 :: forall r r'. (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 #

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] #

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 -> () #

Eq Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

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

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

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 #

SqlOrd Day Source # 
Instance details

Defined in Database.Selda

SqlType Day Source # 
Instance details

Defined in Database.Selda.SqlType

data TimeOfDay #

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

Instances

Instances details
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 :: forall r r'. (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 #

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 -> () #

Eq TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Ord TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

SqlOrd TimeOfDay Source # 
Instance details

Defined in Database.Selda

SqlType TimeOfDay Source # 
Instance details

Defined in Database.Selda.SqlType

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

Instances details
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 :: forall r r'. (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 #

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

SqlOrd UTCTime Source # 
Instance details

Defined in Database.Selda

SqlType UTCTime Source # 
Instance details

Defined in Database.Selda.SqlType

data UUID #

Type representing Universally Unique Identifiers (UUID) as specified in RFC 4122.

Instances

Instances details
Data UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

toConstr :: UUID -> Constr #

dataTypeOf :: UUID -> DataType #

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

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

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

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

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

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

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

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

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

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

Storable UUID

This Storable instance uses the memory layout as described in RFC 4122, but in contrast to the Binary instance, the fields are stored in host byte order.

Instance details

Defined in Data.UUID.Types.Internal

Methods

sizeOf :: UUID -> Int #

alignment :: UUID -> Int #

peekElemOff :: Ptr UUID -> Int -> IO UUID #

pokeElemOff :: Ptr UUID -> Int -> UUID -> IO () #

peekByteOff :: Ptr b -> Int -> IO UUID #

pokeByteOff :: Ptr b -> Int -> UUID -> IO () #

peek :: Ptr UUID -> IO UUID #

poke :: Ptr UUID -> UUID -> IO () #

Read UUID 
Instance details

Defined in Data.UUID.Types.Internal

Show UUID

Pretty prints a UUID (without quotation marks). See also toString.

>>> show nil
"00000000-0000-0000-0000-000000000000"
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Binary UUID

This Binary instance is compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instance details

Defined in Data.UUID.Types.Internal

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

Eq UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

Ord UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

compare :: UUID -> UUID -> Ordering #

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

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

(>) :: UUID -> UUID -> Bool #

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

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

Random UUID

This Random instance produces insecure version 4 UUIDs as specified in RFC 4122.

Instance details

Defined in Data.UUID.Types.Internal

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g) #

random :: RandomGen g => g -> (UUID, g) #

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID] #

randoms :: RandomGen g => g -> [UUID] #

Uniform UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

uniformM :: StatefulGen g m => g -> m UUID #

IsUUID UUID Source # 
Instance details

Defined in Database.Selda

Methods

uuid :: UUID -> UUID Source #

SqlType UUID Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

Lift UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

lift :: Quote m => UUID -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => UUID -> Code m UUID #

Orphan instances

Monoid (Col s Text) Source # 
Instance details

Methods

mempty :: Col s Text #

mappend :: Col s Text -> Col s Text -> Col s Text #

mconcat :: [Col s Text] -> Col s Text #

Semigroup (Col s Text) Source # 
Instance details

Methods

(<>) :: Col s Text -> Col s Text -> Col s Text #

sconcat :: NonEmpty (Col s Text) -> Col s Text #

stimes :: Integral b => b -> Col s Text -> Col s Text #