hasqlator-mysql-0.2.1: composable SQL generation
Copyright(c) Kristof Bastiaensen 2020
LicenseBSD-3
Maintainer[email protected]
Stabilityunstable
Portabilityghc
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.MySQL.Hasqlator

Description

This module provides a lower level SQL combinator language. Hasqlator works on existing databases, and doesn't do schema creation or database migration.

example schema

Here is an example schema for a library loan system, that will be used in the following examples:

CREATE TABLE borrowers (
    id INT PRIMARY KEY,
    name VARCHAR(100) NOT NULL,
    date_of_birth DATETIME NOT NULL
);

CREATE TABLE authors (
    id INT PRIMARY KEY,
    name VARCHAR(100) NOT NULL,
    birth_year INT
);

CREATE TABLE books (
    id INT PRIMARY KEY,
    title VARCHAR(255) NOT NULL,
    author_id INT,
    published_year INT,
    age_rating INT,
    FOREIGN KEY (author_id) REFERENCES authors(id)
);

CREATE TABLE loans (
    id INT PRIMARY KEY,
    book_id INT,
    borrower_id INT,
    loan_date DATE NOT NULL,
    return_date DATE,
    FOREIGN KEY (book_id) REFERENCES books(id)
);

inserting data

You can insert data into the database using the insertValues function. This can insert any haskell datatype into the database. You have to create an Insertor first, which maps a haskell datatype to sql rows. There are several ways to do this:

extractor function.

Proved an extractor function for each field, match it to the sql field using into, and compose them using monoid append (<>):

data Author = Author
  { name
  , birth_year
  }

insertValues "authors" (name into "name" <> birth_year into "birth_year")
  [Author "George Orwell" 1903,
   Author "Aldous Huxley" 1894]

extractor lenses

Similarly, you can use a lens to match the fields, using lensInto

insertValues "authors" (_1 `lensInto` "name" <> _2 `lensInto` "birth_year")
  [("J.K. Rowling", 1965),
   ("Leo Tolstoy", 1828),
   ("Harper Lee", 1926)]

Data types

The insertData function uses Generics to match the input fields to the given sql columns. It works with any product type, including data declarations and records. It uses the position of the field. You can use skipInsert instead of the table name to skip fields you don't care about.

data Borrower = Borrower
  { name :: Text
  , date_of_birth :: Day
  }

insertValues "borrowers" (insertData ("name", "date_of_birth"))
   [Borrower "John Doe" (fromJulian 1985 6 15),
    Borrower "Jane Smith" (fromJulian 1990 11 23),
    Borrower "Emily Johnson" (fromJulian 2000 8 30),
    Borrower "Michael Brown" (fromJulian 1982 2 10),
    Borrower "Sarah Davis" (fromJulian 1995 03 12)]

Expressions

Insert values can have arbitrary SQL queries, by using the exprInto function. Here I create a subquery, from the query which fetches author_id from an author name.

data Book = Book
  { title :: String
  , author :: String
  , publishedYear :: Int
  , ageRating :: Int
  }

getBookAuthorId : Book -> Query Int
getBookAuthorId Book{author=a} =
   select (sel "id") $
   from "authors" <>
   where_ ["name" =. arg a]

insertValues (title `into` "title" <>
              (subQuery . getBookAuthorId `exprInto` "author_id") <>
              publishedYear `into` "published_year" <>
              ageRating `into` "age_rating")
  [ Book "1984" "George Orwell" 1903 16
  , Book "Brave New World" "Aldous Huxley" 1932 14,
  , Book "Harry Potter and the Philosopher\'s Stone" "J.K. Rowling" 1997 7
  , Book "War and Peace" "Leo Tolstoy" 1869 18
  ]

Querying

Queries are done using the select function. It takes a Selector, which tells how to match SQL fields with haskell values, and a QueryClauses, which contains the rest of the query (the select statement is emitted by the select function).

For example, a query that gives back all authors:

getAllAuthors :: Query Author
getAllAuthors =
  select (Author $ sel "name" * sel "birth_year" ) $
  from "author"

Here the selector is composed using the sel function for individual columns, and and applicative functor to turn it into the desired haskell datastructure.

The query body can be composed using Monoid mappend (<>). For example, here is a more complicated expression to get all books loaned by a specific borrower:

@ booksLoaned :: Borrower -> Query Book booksLoaned borrower = select (Book $

SELECT books.title, loans.loan_date, loans.return_date FROM loans JOIN books ON loans.book_id = books.id JOIN borrowers ON loans.borrower_id = borrowers.id WHERE borrowers.name = 'Jane Smith';

Insert Loans

Finally we can insert the loans in the table.

data Loan = Loan
  { bookTitle :: Text
  , bookAuthor :: Text
  , borrowerName :: Text
  , loanDate :: Day
  , return_date :: Day
  }

getLoanBookId :: Loan -> Query Int
getLoanBookId Loan{bookAuthor=bookAuthor, bookTitle=bookTitle} =
  select (sel "id") $
  from "books" <>
  leftJoin ["authors"] ["books.author_id" =. "authors.id"]  <>
  where_ ["books.title" =. arg bookTitle,
          "authors.name" =. arg bookAuthor]

getLoanBorrower_id :: Loan -> Query Int
getLoanBorrower_id Loan{borrowerName = borrowerName} =
  select (sel "id") $
  from "borrowers"
  

INSERT INTO loans (id, book_id, borrower_id, loan_date, return_date) VALUES (1, 1, 1, '2024-09-15', '2024-09-30'), -- John Doe borrowed '1984' and returned it (2, 3, 2, '2024-10-01', NULL), -- Jane Smith borrowed 'Brave New World' and hasn't returned it yet (3, 4, 3, '2024-10-05', NULL), -- Emily Johnson borrowed 'Harry Potter and the Philosopher's Stone' (4, 6, 4, '2024-09-20', '2024-09-27'), -- Michael Brown borrowed 'To Kill a Mockingbird' and returned it (5, 5, 5, '2024-10-08', NULL); -- Sarah Davis borrowed 'War and Peace' recen

Synopsis

Querying

data Query a Source #

`Query a` represents a query returning values of type a.

Instances

Instances details
ToQueryBuilder (Query a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

data Command Source #

A command is a database query that doesn't return a value, but is executed for the side effect (inserting, updating, deleteing).

Instances

Instances details
ToQueryBuilder Command Source # 
Instance details

Defined in Database.MySQL.Hasqlator

unionDistinct :: Query a -> Query a -> Query a Source #

UNION

unionAll :: Query a -> Query a -> Query a Source #

qry1 UNION ALL qry2

mergeSelect :: Query b -> (a -> b -> c) -> Selector a -> Query c Source #

Merge a new Selector in a query.

replaceSelect :: Selector a -> Query b -> Query a Source #

Replace the Selector from a Query.

Query Clauses

innerJoin Source #

Arguments

:: [QueryBuilder]

tables

-> [QueryBuilder]

on expressions, joined by AND

-> QueryClauses 

INNER JOIN table1, ... ON cond1, cond2, ...

leftJoin Source #

Arguments

:: [QueryBuilder]

tables

-> [QueryBuilder]

on expressions, joined by AND

-> QueryClauses 

LEFT JOIN

rightJoin Source #

Arguments

:: [QueryBuilder]

tables

-> [QueryBuilder]

on expressions, joined by AND

-> QueryClauses 

RIGHT JOIN

outerJoin Source #

Arguments

:: [QueryBuilder]

tables

-> [QueryBuilder]

on expressions, joined by AND

-> QueryClauses 

OUTER JOIN

emptyJoins :: QueryClauses Source #

remove all existing joins

where_ :: [QueryBuilder] -> QueryClauses Source #

WHERE expression1, expression2, ...

emptyWhere :: QueryClauses Source #

remove all existing where expressions

groupBy_ :: [QueryBuilder] -> QueryClauses Source #

GROUP BY e1, e2, ...

having :: [QueryBuilder] -> QueryClauses Source #

HAVING e1, e2, ...

emptyHaving :: QueryClauses Source #

remove having expression

orderBy :: [QueryOrdering] -> QueryClauses Source #

ORDER BY e1, e2, ...

limitOffset Source #

Arguments

:: Int

count

-> Int

offset

-> QueryClauses 

LIMIT count, offset

Selectors

data Selector a Source #

Selectors contain the target fields or expressions in a SQL SELECT statement, and perform the conversion to haskell. Selectors are instances of Applicative, so they can return the desired haskell type.

Instances

Instances details
Applicative Selector Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

pure :: a -> Selector a #

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

liftA2 :: (a -> b -> c) -> Selector a -> Selector b -> Selector c #

(*>) :: Selector a -> Selector b -> Selector b #

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

Functor Selector Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

fmap :: (a -> b) -> Selector a -> Selector b #

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

FromSql a => IsString (Selector a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

fromString :: String -> Selector a #

Monoid a => Monoid (Selector a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

mempty :: Selector a #

mappend :: Selector a -> Selector a -> Selector a #

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

Semigroup a => Semigroup (Selector a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

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

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

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

as :: QueryBuilder -> QueryBuilder -> QueryBuilder Source #

combinator for aliasing columns.

polymorphic selector

sel :: FromSql a => QueryBuilder -> Selector a Source #

The polymorphic selector. The return type is determined by type inference.

specialised selectors

The following are specialised versions of sel. Using these may make refactoring easier, for example accidently swapping sel "age" and sel "name" would not give a type error, while intSel "age" and textSel "name" most likely would.

intSel :: (Show a, Bounded a, Integral a) => QueryBuilder -> Selector a Source #

an integer field (TINYINT.. BIGINT). Any bounded haskell integer type can be used here , for example Int, Int32, Word32. An Overflow ur Underflow error will be raised if the value doesn't fit the type.

integerSel :: QueryBuilder -> Selector Integer Source #

Un unbounded integer field, either a bounded integer (TINYINT, etc...) or DECIMAL in the database. Will throw a type error if the stored value is actually fractional.

WARNING: this function could potentially create huge integers with DECIMAL, if the exponent is large, even fillup the space and crash your program! Only use this on trusted inputs, or use Scientific instead.

scientificSel :: QueryBuilder -> Selector Scientific Source #

A DECIMAL or NUMERIC field.

localTimeSel :: QueryBuilder -> Selector LocalTime Source #

a DATETIME or a TIMESTAMP field.

timeOfDaySel :: QueryBuilder -> Selector TimeOfDay Source #

A TIME field taken as a specific time.

diffTimeSel :: QueryBuilder -> Selector DiffTime Source #

a TIME field taken as a time duration.

daySel :: QueryBuilder -> Selector Day Source #

A DATE field.

other selectors

rawValues :: [QueryBuilder] -> Selector [MySQLValue] Source #

Read the columns directly as a MySQLValue type without conversion.

rawValues_ :: [QueryBuilder] -> Selector () Source #

Ignore the content of the given columns

Expressions

isNotNull :: QueryBuilder -> QueryBuilder Source #

IS NOT NULL expression

Insertion

data Insertor a Source #

An Insertor a provides a mapping of parts of values of type a to columns in the database. Insertors can be combined using <>.

Instances

Instances details
Contravariant Insertor Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

contramap :: (a' -> a) -> Insertor a -> Insertor a' #

(>$) :: b -> Insertor b -> Insertor a #

Monoid (Insertor a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

mempty :: Insertor a #

mappend :: Insertor a -> Insertor a -> Insertor a #

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

Semigroup (Insertor a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

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

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

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

insertValues :: QueryBuilder -> Insertor a -> [a] -> Command Source #

insert values using the given insertor.

insertData :: (Generic a, Generic b, InsertGeneric (Rep a ()) (Rep b ())) => a -> Insertor b Source #

insertData inserts a tuple or other product type into the given fields. It uses generics to match the input to the fields. For example:

insert "Person" (insertData ("name", "age"))
  [Person "Bart Simpson" 10, Person "Lisa Simpson" 8]

skipInsert :: Insertor a Source #

skipInsert is mempty specialized to an Insertor. It can be used to skip fields when using insertData.

into :: ToSql b => (a -> b) -> Text -> Insertor a Source #

into uses the given accessor function to map the part to a field. For example:

insertValues "Person" (fst `into` "name" <> snd `into` "age")
  [("Bart Simpson", 10), ("Lisa Simpson", 8)]

exprInto :: (a -> QueryBuilder) -> Text -> Insertor a Source #

insert an SQL expression. Takes a function that generates the SQL expression from the input.

type Getter s a = (a -> Const a a) -> s -> Const a s Source #

A Getter type compatible with the lens library

lensInto :: ToSql b => Getter a b -> Text -> Insertor a Source #

lensInto uses a lens to map the part to a field. For example:

insertValues "Person" (_1 `lensInto` "name" <> _2 `lensInto` "age")
  [("Bart Simpson", 10), ("Lisa Simpson", 8)]

insertOne :: ToSql a => Text -> Insertor a Source #

insert a single value directly

class ToSql a Source #

Minimal complete definition

toSqlValue

Instances

Instances details
ToSql Value Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql ByteString Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Scientific Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Text Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Day Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql DiffTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql LocalTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Integer Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Bool Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Double Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Float Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int Source # 
Instance details

Defined in Database.MySQL.Hasqlator

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

Defined in Database.MySQL.Hasqlator

Methods

toSqlValue :: Maybe a -> MySQLValue

insertLess :: Insertor a -> [Text] -> Insertor a Source #

Exclude fields to insert.

Updates

Deletes

Rendering Queries

class FromSql a Source #

Minimal complete definition

fromSql

Instances

Instances details
FromSql Value Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql ByteString Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Scientific Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Text Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Day Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql DiffTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql LocalTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Integer Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Bool Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Double Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Float Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int Source # 
Instance details

Defined in Database.MySQL.Hasqlator

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

Defined in Database.MySQL.Hasqlator

Executing Queries

executeQuery :: MySQLConn -> Query a -> IO [a] Source #

Execute a Query which returns a resultset. May throw a SQLError exception. See the mysql-haskell package for other exceptions it may throw.

executeCommand :: MySQLConn -> Command -> IO OK Source #

Execute a Command which doesn't return a result-set. May throw a SQLError exception. See the mysql-haskell package for other exceptions it may throw.