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

Database.Selda.MakeSelectors

Description

Utilities for creating selectors for non-record types. In general, you should really use record types for your tables and their record labels (i.e. #label) as selectors using the OverloadedLabels extension instead.

Synopsis

Documentation

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

An inductive tuple of selectors for the given relation.

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

Any table type that can have selectors generated.

Minimal complete definition

mkSel

Instances

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

Defined in Database.Selda.MakeSelectors

Methods

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

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

Defined in Database.Selda.MakeSelectors

Methods

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

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

Defined in Database.Selda.MakeSelectors

Methods

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

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

Defined in Database.Selda.MakeSelectors

Methods

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

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

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

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

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

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

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

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

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