ribbit-1.1.0.0: Type-level Relational DB combinators.

Safe HaskellSafe
LanguageHaskell2010

Database.Ribbit

Contents

Description

This module attepts to define a type-level language for describing database shcemas (i.e. schemas "as a type"), and the queries that operate on them in such a way that:

1) The schema and/or query is completely defined at the type level (sans runtime arguments to query parameters).

2) The meaning of a schema and/or query is immediately obvious to anyone who knows SQL, and

3) The schema and/or query can be extended, deconstructed, or interpreted by third parties for their own purposes.

To that end, each schema is a new type, defined by you, using the constructors provided by this library. The same goes for queries. Each query is a separate type defined with constructors from this library.

We provide a PostgreSQL backend so that real work can be accomplished, but if the backend is missing something you need, then the idea is that you can use your own type families and type classes to extend the schema and query languages, or interpret them differently for your own needs including writing entirely new backends if need be.

Synopsis

Quick Start

Defining a Table

To define a table you need a type:

data Company

(Note: It is not required that the type contain any data, but it can if you like. Unlike some db frameworks, the set of columns stored in the table represented by this type is not directly tied to the Haskell record fields it contains. It is mainly used as a type-level symbol to reference your table.)

And you need a type class instance Table:

instance Table Company where
  type Name Company = "companies"
  type DBSchema Company =
    Field "id" Int
    :> Field "name" Text
    :> Field "address" (Maybe Text)

The different parts of this typeclass instance include:

  • A Name:
  type Name Company = "companies"
  • And a schema definition:
  type DBSchema Company =
    Field "id" Int
    :> Field "name" Text
    :> Field "address" (Maybe Text)

Let's go ahead and define another table. We will use these two tables in the following examples:

data Employee
instance Table Employee where
  type Name Employee = "employees"
  type DBSchema Employee =
    Field "company_id" Int
    :> Field "id" Int
    :> Field "name" Text
    :> Field "salary" (Maybe Int)
    :> Field "quit_date" (Maybe Day)
    :> Field "birth_date" Day

Building a Query

To write queries against these tables, use the query constructors defined in this module:

-- Given a company name as a query parameter, return all the
-- employees that work at that company along with their salary.

type MyQuery =
  Select '["e.name", "e.salary"]
  `From`
      '[
        Company `As` "c",
        Employee `As` "e"
      ]
  `Where`
    "c.id" `Equals` "e.company_id"
    `And` "c.name" `Equals` (?)

Using a Query

The easiest way to use a query is to pass it to the query or execute functions.

It is worth looking at the type signature for query:

query ::
     forall m query.
     ( MonadIO m
     , KnownSymbol (Render query)
     , ToRow (ParamsType query)
     , FromRow (ResultType query)
     )
  => Connection
  -> Proxy query
  -> ParamsType query
  -> m [ResultType query]

In particular, I want to point how how, in addition to the query itself, query accepts an ParamsType query as a parameter, and produces a list of ResultType query items.

ParamsType and ResultType are where the type safety magic happens. They are type families that, given a query type, produce the haskell type of the arguments to that query, and the rows produce by that query, respectively:

  • ParamsType - Given a query, produce the type of the embedded query parameters.
  • ResultType - Given a query, produce the type of rows produced by that query.
Example Resulting type Reason
ParamsType MyQuery Only Text Our query on only has one parameter, which is compared against the company "name" field, indicating it must be of type Text, because that is what we have defined the "name" column to be in our database schema using: Field "name" Text
ResultType MyQuery Only Text :> Only (Maybe Int) The Fields that MyQuery is selecting are employee "name" and "salary". Name is a non-null Text, and salary is a nullable integer.

Therefore, we can invoke the query thusly:

do 
  results <- query conn (Proxy :: Proxy MyQuery) (Only "Some Company")
  sequence_
    [
      putStrLn (show name <> " - " <> show salary)
      | (Only name :> Only salary) <- results
    ]

Inserting values

To insert values into our example tables above, we need to write a couple of insert statements:

E.g.:

type InsertCompany = InsertInto Company '["id", "name", "address"]
type InsertEmployee = InsertInto Employee '["company_id", "id", "name", "birth_date"]

That's it really. Insert statements are much simpler than select queries. These statement will automatically be parameterized according to the listed fields.

There is a little bit of important nuance here: Note that InsertEmployee omits the "salary" field. That field is nullable, and so the database will insert a null value when this insert statement is used.

This can be particularly useful for allowing the database to supply default values, such as auto-incremented id fields. This library is not (yet) sophisticated enough understand which fields can safely be omitted, so it lets you omit any field. If you omit a field for which the database cannot supply a default value then that will result in a runtime error. This is a problem we plan to fix in a future version. On the other hand if you try to include a field that is not part of the schema, you will get a compile time error like you are supposed to.

To execute these insert statements, use Database.Ribbit.PostgreSQL's execute function:

do
  let
    myBirthday :: Day
    myBirthday = ...
  execute
    conn
    (Proxy :: Proxy InsertCompany)
    (Only 1 :> Only "Owens Murray" :> Only (Just "Austin, Tx"))
  execute
    conn
    (Proxy :: Proxy InsertEmployee)
    (Only 1 :> Only 1 :> Only "Rick" :> Only myBirthday)

Deleting values

Deleting a value is similar to inserting a value, but simpler because you only have to specify the delete conditions (if there are any).

e.g.:

type DeleteAllEmployees = DeleteFrom Employee
type DeleteEmployeeById =
  DeleteFrom Employee
  `Where`
    "company_id" `Equals` (?)
    `And` "id" `Equals` (?)

Then just execute the query, providing the appropriate query params.

do
  let
    employeeId :: Int
    employeeId = ...
  execute
    conn
    (Proxy :: Proxy DeleteEmployeeById)
    (Only employeeId)

  -- Or maybe delete all employees.
  execute
    conn
    (Proxy :: Proxy DeleteAllEmployees)
    ()

Updating values

Updating values is almost the same as inserting values. Instead of specifying the fields that get inserted, you specify the fields that get updated, along with the conditions that match the rows to be updated.

{- Update an employee's salary (hopefully a raise!). -}
type UpdateSalary =
  Update '[ "salary" ]
  `Where` 
    "company_id" `Equals` (?)
    "id" `Equals` (?)

...

let
  newSalary :: Int
  newSalary = 2

  targetCompany :: Int
  targetCompany = 1

  targetEmployee :: Int
  targetEmployee = 1

in
  execute
    conn
    (Proxy :: Proxy UpdateSalary)
    (Only newSalary :> Only targetCompany :> Only targetEmployee)

Schema Definition Types

The Table type is the core of how one defines table schemas. It is a type class with two associated types: Name, which provides the name of the table as it is known to SQL, and DBSchema, which provides a schema for the table.

e.g.

An 'employees' table:

data Employee
instance Table Employee where
  type Name Employee = "employees"
  type DBSchema Employee =
    Field "id" Int
    :> Field "name" Text
    :> Field "salary" (Maybe Int)
    :> Field "birth_date" Day

class Table relation Source #

Type class for defining your own tables. The primary way for you to introduce a new schema is to instantiate this type class for one of your types.

E.g.:

data MyTable
instance Table MyTable where
  type Name MyTable = "my_table"
  type DBSchema MyTable =
    Field "id" Int
    :> Field "my_non_nullable_text_field" Text
    :> Field "my_nullable_int_field" (Maybe Int)

Associated Types

type Name relation :: Symbol Source #

type DBSchema relation Source #

Instances
Table table => Table (As table alias ': more :: [Type]) Source #

Cross Product

Instance details

Defined in Database.Ribbit.Select

Associated Types

type Name (As table alias ': more) :: Symbol Source #

type DBSchema (As table alias ': more) :: Type Source #

Table (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

Associated Types

type Name (On (LeftJoin (As l lname) (As r rname)) conditions) :: Symbol Source #

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions) :: Type Source #

data Field name typ Source #

Define a field in a database schema, where:

  • name: is the name of the database column, expressed as a type-level string literal, and
  • typ: is the Haskell type whose values get stored in the column.

E.g:

Instances
(KnownSymbol name, HasFields more) => HasFields (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy (Field name typ :> more) -> [Text]

(HasIsNullable typ, HasPsqlType typ, HasPsqlTypes more) => HasPsqlTypes (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlTypes :: proxy (Field name typ :> more) -> [Text]

KnownSymbol name => HasFields (Field name typ :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy (Field name typ) -> [Text]

(HasIsNullable typ, HasPsqlType typ) => HasPsqlTypes (Field name typ :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlTypes :: proxy (Field name typ) -> [Text]

data a :> b infixr 5 Source #

String two types together. Int :> Int :> Int is similar in principal to the nested tuple (Int, (Int, Int)), but looks a whole lot nicer when the number of elements becomes large.

This is how you build up a schema from a collection of Field types.

E.g.:

Field "foo" Int
:> Field "bar" Text
:> Field "baz" (Maybe Text)

It also the mechanism by which this library builds up the Haskell types for query parameters and resulting rows that get returned. So if you have a query that accepts three text query parameters, that type represented in Haskell is going to be (Only Text :> Only Text :> Only Text).

If that query returns rows that contain a Text, an Int, and a Text, then the type of the rows will be (Only Text :> Only Int :> Only Text).

Constructors

a :> b infixr 5 
Instances
(KnownSymbol name, HasFields more) => HasFields (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy (Field name typ :> more) -> [Text]

(HasIsNullable typ, HasPsqlType typ, HasPsqlTypes more) => HasPsqlTypes (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlTypes :: proxy (Field name typ :> more) -> [Text]

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

Defined in Database.Ribbit.Table

Methods

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

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

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

Defined in Database.Ribbit.Table

Methods

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

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

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

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

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

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

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

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

Defined in Database.Ribbit.Table

Methods

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

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

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

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

Defined in Database.Ribbit.PostgreSQL

Methods

fromRow :: RowParser (a :> b)

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

Defined in Database.Ribbit.PostgreSQL

Methods

toRow :: (a :> b) -> [Action]

SQL Statement Constructors

Query Constructors

Types in the section are used to construct SELECT queries.

e.g.

List all employees who have quit, for all companies. (Left Joined version, which shows companies that have had no employees quit.)

Select '["c.name", "e.name", "e.quit_date"]
`From`
  Company `As` "c"
  `LeftJoin`  Employee `As` "e" `On` "c.id" `Equals` "e.company_id"
`Where`
  NotNull "e.quit_date"

List all employees who have quit, for all companies. (Inner join version, which omits companies from which no employee has quit.)

Select '["c.name", "e.name", "e.quit_date"]
`From` '[Company `As` "c", Employee `As` "e"]
`Where`
  "c.id" `Equals` "e.company_id"
  `And` NotNull "e.quit_date"

data Select fields Source #

SELECT constructor, used for starting a SELECT statement.

Instances
type Render (From (Select proj) table) Source # 
Instance details

Defined in Database.Ribbit.Select

type Render (From (Select proj) table)
type ResultType (From (Select fields) relation) Source # 
Instance details

Defined in Database.Ribbit.Select

type ResultType (From (Select fields) relation)
type ParamsType (From (Select proj) relation) Source # 
Instance details

Defined in Database.Ribbit.Select

type ParamsType (From (Select proj) relation) = ()

data From proj relation infixl 6 Source #

FROM constructor, used for attaching a SELECT projection to a relation in the database.

Instances
type Render (Where (From proj table) conditions) Source # 
Instance details

Defined in Database.Ribbit.Select

type Render (Where (From proj table) conditions)
type Render (From (Select proj) table) Source # 
Instance details

Defined in Database.Ribbit.Select

type Render (From (Select proj) table)
type ResultType (From (Select fields) relation) Source # 
Instance details

Defined in Database.Ribbit.Select

type ResultType (From (Select fields) relation)
type ParamsType (Where (From _ relation) conditions) Source # 
Instance details

Defined in Database.Ribbit.Select

type ParamsType (Where (From _ relation) conditions) = ParamsTypeSchema (DBSchema relation) conditions
type ParamsType (From (Select proj) relation) Source # 
Instance details

Defined in Database.Ribbit.Select

type ParamsType (From (Select proj) relation) = ()

data As relation (name :: Symbol) infix 9 Source #

AS constructor, used for attaching a name to a table in a FROM clause.

Instances
Table table => Table (As table alias ': more :: [Type]) Source #

Cross Product

Instance details

Defined in Database.Ribbit.Select

Associated Types

type Name (As table alias ': more) :: Symbol Source #

type DBSchema (As table alias ': more) :: Type Source #

Table (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

Associated Types

type Name (On (LeftJoin (As l lname) (As r rname)) conditions) :: Symbol Source #

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions) :: Type Source #

type Name (As table alias ': more :: [Type]) Source # 
Instance details

Defined in Database.Ribbit.Select

type Name (As table alias ': more :: [Type])
type Name (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

type Name (On (LeftJoin (As l lname) (As r rname)) conditions :: Type)
type DBSchema (As table alias ': more :: [Type]) Source # 
Instance details

Defined in Database.Ribbit.Select

type DBSchema (As table alias ': more :: [Type])
type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions :: Type)

data On join (conditions :: *) infix 7 Source #

ON keyword, for joins.

Instances
Table (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

Associated Types

type Name (On (LeftJoin (As l lname) (As r rname)) conditions) :: Symbol Source #

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions) :: Type Source #

type Name (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

type Name (On (LeftJoin (As l lname) (As r rname)) conditions :: Type)
type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions :: Type)

data LeftJoin left right infix 8 Source #

Left Joins.

Instances
Table (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

Associated Types

type Name (On (LeftJoin (As l lname) (As r rname)) conditions) :: Symbol Source #

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions) :: Type Source #

type Name (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

type Name (On (LeftJoin (As l lname) (As r rname)) conditions :: Type)
type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit.Select

type DBSchema (On (LeftJoin (As l lname) (As r rname)) conditions :: Type)

Insert Constructors

Construct insert statements.

e.g.

Insert one row into the Employee Table.

InsertInto Employee '["id", "company_id", "name"]

The values which are inserted into the specified fields are provided as query parameters.

data InsertInto table fields Source #

Insert statement.

Instances
type Render (InsertInto table fields) Source # 
Instance details

Defined in Database.Ribbit.Insert

type Render (InsertInto table fields)
type ParamsType (InsertInto relation fields) Source # 
Instance details

Defined in Database.Ribbit.Insert

type ParamsType (InsertInto relation fields)

Delete Constructors

Construct delete statements.

e.g.

Delete all rows from the Company table:

type Statement = DeleteFrom Company

Delete a specific row from the Company table:

type Statement = DeleteFrom Company `Where` "id" `Equals` (?)

data DeleteFrom table Source #

Delete statement.

Instances
type Render (DeleteFrom table) Source # 
Instance details

Defined in Database.Ribbit.Delete

type Render (DeleteFrom table) = AppendSymbol "DELETE FROM " (Name table)
type ParamsType (DeleteFrom relation) Source # 
Instance details

Defined in Database.Ribbit.Delete

type ParamsType (DeleteFrom relation) = ()
type Render (Where (DeleteFrom table) conditions) Source # 
Instance details

Defined in Database.Ribbit.Delete

type Render (Where (DeleteFrom table) conditions)
type ParamsType (Where (DeleteFrom relation) conditions) Source # 
Instance details

Defined in Database.Ribbit.Delete

type ParamsType (Where (DeleteFrom relation) conditions) = ParamsTypeSchema (DBSchema relation) conditions

Update Constructors

Construct update statements

e.g.

Update a specific employee's salary:

type Statement =
  Update Employee '["salary"]
  `Where`
    "company_id" `Equals` (?)
    `And` "id" `Equals` (?)

The values which are inserted into the specified fields are provided as query parameters.

e.g.

execute
  conn
  Statement
  (Only newSalary :> Only companyId :> Only employeeId)

data Update table (fields :: [Symbol]) Source #

Update statement.

Instances
type Render (Update table fields) Source # 
Instance details

Defined in Database.Ribbit.Update

type Render (Update table fields)
type ParamsType (Update relation fields) Source # 
Instance details

Defined in Database.Ribbit.Update

type ParamsType (Update relation fields)
type Render (Where (Update table fields) conditions) Source # 
Instance details

Defined in Database.Ribbit.Update

type Render (Where (Update table fields) conditions)
type ParamsType (Where (Update relation fields) conditions) Source # 
Instance details

Defined in Database.Ribbit.Update

type ParamsType (Where (Update relation fields) conditions)

Condition Constructors

Use these types to construct a WHERE clause.

data Where query conditions infixl 6 Source #

WHERE constructor, used for attaching conditions to a query.

Instances
type Render (Where (From proj table) conditions) Source # 
Instance details

Defined in Database.Ribbit.Select

type Render (Where (From proj table) conditions)
type Render (Where (DeleteFrom table) conditions) Source # 
Instance details

Defined in Database.Ribbit.Delete

type Render (Where (DeleteFrom table) conditions)
type Render (Where (Update table fields) conditions) Source # 
Instance details

Defined in Database.Ribbit.Update

type Render (Where (Update table fields) conditions)
type ResultType (Where query conditions) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ResultType (Where query conditions) = ResultType query
type ParamsType (Where (From _ relation) conditions) Source # 
Instance details

Defined in Database.Ribbit.Select

type ParamsType (Where (From _ relation) conditions) = ParamsTypeSchema (DBSchema relation) conditions
type ParamsType (Where (DeleteFrom relation) conditions) Source # 
Instance details

Defined in Database.Ribbit.Delete

type ParamsType (Where (DeleteFrom relation) conditions) = ParamsTypeSchema (DBSchema relation) conditions
type ParamsType (Where (Update relation fields) conditions) Source # 
Instance details

Defined in Database.Ribbit.Update

type ParamsType (Where (Update relation fields) conditions)

data Equals (l :: k1) (r :: k2) infix 9 Source #

"=" constructor for conditions.

Instances
type ParamsTypeSchema schema (Equals l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Equals l r)

data NotEquals l r infix 9 Source #

"!=" constructor for conditions.

Instances
type ParamsTypeSchema schema (NotEquals l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (NotEquals l r)

data Lt l r infix 9 Source #

"<" constructor for conditions.

Instances
type ParamsTypeSchema schema (Lt l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Lt l r)

data Lte l r infix 9 Source #

"<=" constructor for conditions.

Instances
type ParamsTypeSchema schema (Lte l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Lte l r)

data Gt l r infix 9 Source #

">" constructor for conditions.

Instances
type ParamsTypeSchema schema (Gt l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Gt l r)

data Gte l r infix 9 Source #

">=" constructor for conditions.

Instances
type ParamsTypeSchema schema (Gte l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Gte l r)

data And l r infixr 8 Source #

AND constructor for conditions.

Instances
type ParamsTypeSchema schema (And a b) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (And a b)

data Or (l :: k1) (r :: k2) infixr 7 Source #

OR constructor for conditions.

Instances
type ParamsTypeSchema schema (Or a b) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Or a b)

data Not a Source #

NOT conditional constructor.

Instances
type ParamsTypeSchema schema (Not a) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Not a) = ParamsTypeSchema schema a

data IsNull (field :: Symbol) Source #

Is a field null?

data NotNull (field :: Symbol) Source #

Is a field not null?

data (?) Source #

"?" constructor, used to indicate the presence of a query parameter.

Transformations on Statement Types

These type families are useful for transforming the query types in various ways, or extracting certain information from them.

e.g.

Given the query:

type Query = Select '["name"] `From` Company `Where` "id" `Equals` (?)

Render the query as a String value (using symbolVal):

symbolVal (Proxy :: Proxy (Render Query)) == "SELECT name FROM companies WHERE id = ?"

Produce the Haskell type corresponding to the query parameters for a select statement:

ParamsType Query ~ Only Int -- Our statement has only one parameter, which is an int.

Produce the Haskell type corresponding to the rows produced by the query:

ResultType Query ~ Only Text -- Our query procudes only one column, a text.

type family ParamsType query Source #

Produce the type represeting the placeholder ("?") values in a paramaterized query.

This type family is open and extendable.

Instances
type ParamsType (DeleteFrom relation) Source # 
Instance details

Defined in Database.Ribbit.Delete

type ParamsType (DeleteFrom relation) = ()
type ParamsType (Update relation fields) Source # 
Instance details

Defined in Database.Ribbit.Update

type ParamsType (Update relation fields)
type ParamsType (InsertInto relation fields) Source # 
Instance details

Defined in Database.Ribbit.Insert

type ParamsType (InsertInto relation fields)
type ParamsType (Where (From _ relation) conditions) Source # 
Instance details

Defined in Database.Ribbit.Select

type ParamsType (Where (From _ relation) conditions) = ParamsTypeSchema (DBSchema relation) conditions
type ParamsType (Where (DeleteFrom relation) conditions) Source # 
Instance details

Defined in Database.Ribbit.Delete

type ParamsType (Where (DeleteFrom relation) conditions) = ParamsTypeSchema (DBSchema relation) conditions
type ParamsType (Where (Update relation fields) conditions) Source # 
Instance details

Defined in Database.Ribbit.Update

type ParamsType (Where (Update relation fields) conditions)
type ParamsType (From (Select proj) relation) Source # 
Instance details

Defined in Database.Ribbit.Select

type ParamsType (From (Select proj) relation) = ()

type family ParamsTypeSchema schema a Source #

Produce the parameters type in relation to a particiular schema.

This type family is open and extendable.

Instances
type ParamsTypeSchema schema (Not a) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Not a) = ParamsTypeSchema schema a
type ParamsTypeSchema schema (Gte l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Gte l r)
type ParamsTypeSchema schema (Gt l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Gt l r)
type ParamsTypeSchema schema (Lte l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Lte l r)
type ParamsTypeSchema schema (Lt l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Lt l r)
type ParamsTypeSchema schema (NotEquals l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (NotEquals l r)
type ParamsTypeSchema schema (Equals l r) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Equals l r)
type ParamsTypeSchema schema (Or a b) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (Or a b)
type ParamsTypeSchema schema (And a b) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ParamsTypeSchema schema (And a b)

type family ResultType query Source #

Produce the type of rows return by a query.

Instances
type ResultType (Where query conditions) Source # 
Instance details

Defined in Database.Ribbit.Conditions

type ResultType (Where query conditions) = ResultType query
type ResultType (From (Select fields) relation) Source # 
Instance details

Defined in Database.Ribbit.Select

type ResultType (From (Select fields) relation)

type family Render a :: Symbol Source #

Render a query.

Instances
type Render (DeleteFrom table) Source # 
Instance details

Defined in Database.Ribbit.Delete

type Render (DeleteFrom table) = AppendSymbol "DELETE FROM " (Name table)
type Render (Update table fields) Source # 
Instance details

Defined in Database.Ribbit.Update

type Render (Update table fields)
type Render (InsertInto table fields) Source # 
Instance details

Defined in Database.Ribbit.Insert

type Render (InsertInto table fields)
type Render (Where (From proj table) conditions) Source # 
Instance details

Defined in Database.Ribbit.Select

type Render (Where (From proj table) conditions)
type Render (Where (DeleteFrom table) conditions) Source # 
Instance details

Defined in Database.Ribbit.Delete

type Render (Where (DeleteFrom table) conditions)
type Render (Where (Update table fields) conditions) Source # 
Instance details

Defined in Database.Ribbit.Update

type Render (Where (Update table fields) conditions)
type Render (From (Select proj) table) Source # 
Instance details

Defined in Database.Ribbit.Select

type Render (From (Select proj) table)