ribbit-0.2.0.1: ribbit

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 the meaning of a query is immediately obvious to anyone who knows SQL, and that can be extended and deconstructed by library users for their own purposes.

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, 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 "id" Int
    :> Field "company_id" Int
    :> Field "name" Text
    :> Field "salary" (Maybe Int)
    :> Field "birth_date" Day

Building a Query

To write queries against these tables, use the query combinators 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" `X` Employee `As` "e"
  `Where`
    "c.id" `Equals` "e.company_id"
    `And` "c.name" `Equals` (?)

Using a Query

Now that we have some tables and a query, how do we make use of them? Well, the first thing to notice is that a query like this needs inputs (the query parameter), and provides outputs (the selected rows). These inputs and outputs need to be typed, and indeed they are thanks to a couple of special type families:

  • ArgsType - 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
ArgsType MyQuery Only Text
ResultType MyQuery Only Text :> Only (Maybe Int)

Schema Definition Types

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.

Constructors

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

Defined in Database.Ribbit

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

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

Methods

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

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

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

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

Defined in Database.Ribbit.PostgreSQL

Methods

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

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

Defined in Database.Ribbit.PostgreSQL

Methods

fromRow :: RowParser (a :> b)

class Table relation Source #

Associated Types

type DBSchema relation Source #

type Name relation :: Symbol Source #

Instances
(Table l, Table r, KnownSymbol lname, KnownSymbol rname) => Table (X (As l lname) (As r rname) :: Type) Source #

Cross product

Instance details

Defined in Database.Ribbit

Associated Types

type DBSchema (X (As l lname) (As r rname)) :: Type Source #

type Name (X (As l lname) (As r rname)) :: Symbol Source #

data Field name typ Source #

Define a field in a database schema.

Query Combinators

data Select fields Source #

SELECT combinator, used for starting a SELECT statement.

Instances
Render fields => Render (Select fields :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Select fields) -> Text Source #

data From proj relation infixl 6 Source #

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

Instances
(KnownSymbol (Name relation), Render proj, Table relation) => Render (From proj relation :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (From proj relation) -> Text Source #

data X l r infixr 7 Source #

Cross product operator for FROM clauses.

Instances
(Table l, Table r, KnownSymbol lname, KnownSymbol rname) => Table (X (As l lname) (As r rname) :: Type) Source #

Cross product

Instance details

Defined in Database.Ribbit

Associated Types

type DBSchema (X (As l lname) (As r rname)) :: Type Source #

type Name (X (As l lname) (As r rname)) :: Symbol Source #

type DBSchema (X (As l lname) (As r rname) :: Type) Source # 
Instance details

Defined in Database.Ribbit

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

Defined in Database.Ribbit

type Name (X (As l lname) (As r rname) :: Type) = AppendSymbol (AppendSymbol (AppendSymbol (AppendSymbol (AppendSymbol (AppendSymbol (Name l) " as ") lname) ", ") (Name r)) " as ") rname

data As relation name infix 8 Source #

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

Instances
(Table l, Table r, KnownSymbol lname, KnownSymbol rname) => Table (X (As l lname) (As r rname) :: Type) Source #

Cross product

Instance details

Defined in Database.Ribbit

Associated Types

type DBSchema (X (As l lname) (As r rname)) :: Type Source #

type Name (X (As l lname) (As r rname)) :: Symbol Source #

type DBSchema (X (As l lname) (As r rname) :: Type) Source # 
Instance details

Defined in Database.Ribbit

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

Defined in Database.Ribbit

type Name (X (As l lname) (As r rname) :: Type) = AppendSymbol (AppendSymbol (AppendSymbol (AppendSymbol (AppendSymbol (AppendSymbol (Name l) " as ") lname) ", ") (Name r)) " as ") rname

data Where query conditions infixl 6 Source #

WHERE combinator, used for attaching conditions to a query.

Instances
(Render query, Render conditions) => Render (Where query conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Where query conditions) -> Text Source #

Condition Conbinators

data And l r infixr 8 Source #

AND combinator for conditions.

Instances
(Render l, Render r) => Render (And l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (And l r) -> Text Source #

data Or l r infixr 7 Source #

OR combinator for conditions.

Instances
(Render l, Render r) => Render (Or l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Or l r) -> Text Source #

data Equals l r infix 9 Source #

"=" combinator for conditions.

Instances
(Render (Expr l), Render (Expr r)) => Render (Equals l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Equals l r) -> Text Source #

Query Parameters

data (?) Source #

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

Instances
Render (?) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (?) -> Text Source #

Transformations on Query Types

type family ArgsType query where ... Source #

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

Equations

ArgsType ((_ `From` relation) `Where` conditions) = ArgsType (DBSchema relation, conditions) 
ArgsType (schema, And a b) = StripUnit (Flatten (ArgsType (schema, a) :> ArgsType (schema, b))) 
ArgsType (schema, Or a b) = StripUnit (Flatten (ArgsType (schema, a) :> ArgsType (schema, b))) 
ArgsType (schema, Equals field (?)) = ProjectionType '[field] schema 
ArgsType (schema, Equals field expr) = If (ValidField expr schema) (If (ValidField field schema) () (NotInSchema field schema)) (NotInSchema expr schema) 
ArgsType _ = () 

type family ResultType query where ... Source #

Produce the type of rows return by a query.

Equations

ResultType (Select fields `From` relation) = ProjectionType fields (DBSchema relation) 
ResultType (query `Where` conditions) = ResultType query 
ResultType query = TypeError (Text "Malformed Query" :$$: ShowType query) 

Query Rendering

class Render query where Source #

Render a type-level query as text.

Methods

render :: proxy query -> Text Source #

Instances
Render (?) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (?) -> Text Source #

Render fields => Render (Select fields :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Select fields) -> Text Source #

(KnownSymbol field, Render more) => Render (field ': more :: [Symbol]) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (field ': more) -> Text Source #

KnownSymbol field => Render (field ': ([] :: [Symbol]) :: [Symbol]) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (field ': []) -> Text Source #

(Render l, Render r) => Render (Or l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Or l r) -> Text Source #

(Render l, Render r) => Render (And l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (And l r) -> Text Source #

(Render (Expr l), Render (Expr r)) => Render (Equals l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Equals l r) -> Text Source #

(Render query, Render conditions) => Render (Where query conditions :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Where query conditions) -> Text Source #

(KnownSymbol (Name relation), Render proj, Table relation) => Render (From proj relation :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (From proj relation) -> Text Source #