ribbit-0.4.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 combinators provided by this library. The same goes for queries. Each query is a separate type defined with combinators 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 "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",
        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)

The Database.Ribbit.PostgreSQL module provides a query function:

query :: (
    MonadIO m,
    Render query,
    ToRow (ArgsType query),
    FromRow (ResultType query)
  )
  => Connection
  -> Proxy query
  -> ArgsType query
  -> m [ResultType query]

Notice that it accepts an (ArgsType query) argument, and returns a list of (ResultType query) values.

Therefore, we can invoke the query thusly:

results <- query conn (Proxy :: Proxy MyQuery) (Only "Some Company")

The (Only "Some Company") argument fulfils the query parameters, and the results will be a list of rows which can be deconstructed using pattern matching. E.g.:

sequence_
  [
    putStrLn (show name <> " - " <> show sallary)
    | (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` "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)
    ()

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.

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
(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 more) => HasFields (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

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

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

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, KnownSymbol name) => Table (As table name ': moreTables :: [Type]) Source #

Cross product

Instance details

Defined in Database.Ribbit

Associated Types

type Name (As table name ': moreTables) :: Symbol Source #

type DBSchema (As table name ': moreTables) :: 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
(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 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 (Field name typ :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

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

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

Defined in Database.Ribbit.PostgreSQL

Methods

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

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 As relation name infix 8 Source #

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

Instances
(Table table, KnownSymbol name) => Table (As table name ': moreTables :: [Type]) Source #

Cross product

Instance details

Defined in Database.Ribbit

Associated Types

type Name (As table name ': moreTables) :: Symbol Source #

type DBSchema (As table name ': moreTables) :: Type Source #

type Name (As table name ': moreTables :: [Type]) Source # 
Instance details

Defined in Database.Ribbit

type Name (As table name ': moreTables :: [Type])
type DBSchema (As table name ': moreTables :: [Type]) Source # 
Instance details

Defined in Database.Ribbit

type DBSchema (As table name ': moreTables :: [Type])

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 #

Insert Combinators

data InsertInto table fields Source #

Insert statement.

Instances
(ReflectFields fields, KnownSymbol (Name table)) => Render (InsertInto table fields :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (InsertInto table fields) -> Text Source #

Delete Combinators

data DeleteFrom table Source #

Delete statement.

Instances
KnownSymbol (Name table) => Render (DeleteFrom table :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (DeleteFrom table) -> 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 #

data NotEquals l r infix 9 Source #

"!=" combinator for conditions.

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

Defined in Database.Ribbit

Methods

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

data Gt l r infix 9 Source #

">" combinator for conditions.

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

Defined in Database.Ribbit

Methods

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

data Gte l r infix 9 Source #

">=" combinator for conditions.

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

Defined in Database.Ribbit

Methods

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

data Lt l r infix 9 Source #

"<" combinator for conditions.

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

Defined in Database.Ribbit

Methods

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

data Lte l r infix 9 Source #

"<=" combinator for conditions.

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

Defined in Database.Ribbit

Methods

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

data Not a Source #

NOT conditional combinator.

Instances
Render a => Render (Not a :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Not a) -> 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 (DeleteFrom relation `Where` conditions) = ArgsType (DBSchema relation, conditions) 
ArgsType (InsertInto relation '[]) = TypeError (Text "Insert statement must specify at least one column.") 
ArgsType (InsertInto relation fields) = ProjectionType fields (DBSchema relation) 
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, Condition field (?)) = ProjectionType '[field] schema 
ArgsType (schema, Condition (?) field) = ProjectionType '[field] schema 
ArgsType (schema, Condition l r) = If (ValidField r schema) (If (ValidField l schema) () (NotInSchema l schema)) (NotInSchema r schema) 
ArgsType (schema, Equals l r) = ArgsType (schema, Condition l r) 
ArgsType (schema, NotEquals l r) = ArgsType (schema, Condition l r) 
ArgsType (schema, Lt l r) = ArgsType (schema, Condition l r) 
ArgsType (schema, Lte l r) = ArgsType (schema, Condition l r) 
ArgsType (schema, Gt l r) = ArgsType (schema, Condition l r) 
ArgsType (schema, Gte l r) = ArgsType (schema, Condition l r) 
ArgsType (schema, Not a) = ArgsType (schema, a) 
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) 

type family ValidField field schema where ... Source #

Type level check to see if the field is actually contained in the schema

Equations

ValidField name (Field name typ) = True 
ValidField name (Field _ typ) = False 
ValidField name (a :> b) = ValidField name a || ValidField name b 

type family ProjectionType proj schema where ... Source #

Equations

ProjectionType '[name] schema = LookupType name schema schema 
ProjectionType (name ': more) schema = LookupType name schema schema :> ProjectionType more schema 

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 #

KnownSymbol (Name table) => Render (DeleteFrom table :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (DeleteFrom table) -> Text Source #

Render a => Render (Not a :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (Not a) -> Text Source #

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

Defined in Database.Ribbit

Methods

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

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

Defined in Database.Ribbit

Methods

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

(ReflectFields fields, KnownSymbol (Name table)) => Render (InsertInto table fields :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

render :: proxy (InsertInto table fields) -> 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 (Gte l r :: Type) Source # 
Instance details

Defined in Database.Ribbit

Methods

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

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

Defined in Database.Ribbit

Methods

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

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

Defined in Database.Ribbit

Methods

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

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

Defined in Database.Ribbit

Methods

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

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

Defined in Database.Ribbit

Methods

render :: proxy (NotEquals 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 #