preql-0.2: safe PostgreSQL queries using Quasiquoters

Safe HaskellNone
LanguageHaskell2010

Preql

Contents

Synopsis

Documentation

class Monad m => SQL (m :: * -> *) where Source #

An Effect class for running SQL queries. You can think of this as a context specifying a particular Postgres connection (or connection pool). A minimal instance defines runTransaction. A typical instance will use runTransactionIO or functions in Query and log & rethrow errors.

Minimal complete definition

runTransaction

Methods

query :: (ToSql p, FromSql r) => (Query, p) -> m (Vector r) Source #

Run a parameterized query that returns data. The tuple argument is typically provided by the sql Quasiquoter.

query_ :: ToSql p => (Query, p) -> m () Source #

Run a parameterized query that does not return data.

runTransaction :: Transaction a -> m a Source #

Run multiple queries in a transaction.

Instances
SQL Transaction Source #

The same query methods can be used within a Transaction. Nested Transactions are implemented using savepoints.

Instance details

Defined in Preql.Effect.Internal

(MonadTrans t, Monad (t m), SQL m) => SQL (t m) Source #

Lift through any monad transformer without a more specific instance.

Instance details

Defined in Preql.Effect.Internal

Methods

query :: (ToSql p, FromSql r) => (Query, p) -> t m (Vector r) Source #

query_ :: ToSql p => (Query, p) -> t m () Source #

runTransaction :: Transaction a -> t m a Source #

SQL (ReaderT Connection IO) Source #

Most larger applications will define an instance; this one is suitable to test out the library.

Instance details

Defined in Preql.Effect.Internal

sql :: QuasiQuoter Source #

Given a SQL query with ${} antiquotes, splice a pair (Query p r, p) or a function p' -> (Query p r, p) if the SQL string includes both antiquote and positional parameters.

The sql Quasiquoter allows passing parameters to a query by name, inside a ${} antiquote. For example: [sql| SELECT name, age FROM cats WHERE age >= ${minAge} and age < ${maxAge} |] The Haskell term within {} must be a variable in scope; more complex expressions are not supported.

Antiquotes are replaced by positional ($1, $2) parameters supported by Postgres, and the encoded values are sent with PexecParams

Mixed named & numbered parameters are also supported. It is hoped that this will be useful when migrating existing queries. For example: query $ [sql| SELECT name, age FROM cats WHERE age >= ${minAge} and age < $1 |] maxAge Named parameters will be assigned numbers higher than the highest numbered paramater placeholder.

A quote with only named parameters is converted to a tuple '(Query, p)'. For example: ("SELECT name, age FROM cats WHERE age >= $1 and age < $2", (minAge, maxAge)) If there are no parameters, the inner tuple is (), like ("SELECT * FROM cats", ()). If there are both named & numbered params, the splice is a function taking a tuple and returning (Query, p) where p includes both named & numbered params. For example: a -> ("SELECT name, age FROM cats WHERE age >= $1 and age < $2", (a, maxAge))

data Transaction a Source #

A Transaction can only contain SQL queries (and pure functions).

Instances
Monad Transaction Source # 
Instance details

Defined in Preql.Effect.Internal

Functor Transaction Source # 
Instance details

Defined in Preql.Effect.Internal

Methods

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

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

Applicative Transaction Source # 
Instance details

Defined in Preql.Effect.Internal

Methods

pure :: a -> Transaction a #

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

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

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

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

SQL Transaction Source #

The same query methods can be used within a Transaction. Nested Transactions are implemented using savepoints.

Instance details

Defined in Preql.Effect.Internal

data Query Source #

The IsString instance does no validation; the limited instances discourage directly manipulating strings, with the high risk of SQL injection.

Instances
Show Query Source # 
Instance details

Defined in Preql.Wire.Internal

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query Source # 
Instance details

Defined in Preql.Wire.Internal

Methods

fromString :: String -> Query #

functions for writing SQL instances

runTransactionIO :: Transaction a -> Connection -> IO (Either QueryError a) Source #

Run the provided Transaction. If it fails with a QueryError, roll back.

Decoding rows

class FromSql a Source #

Minimal complete definition

fromSql

Instances
FromSql Bool Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Double Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Float Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Int16 Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Int32 Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Int64 Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql ByteString Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql ByteString Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Text Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql UTCTime Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Value Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Text Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql String Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql UUID Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql Day Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql TimeOfDay Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSql TimeTZ Source # 
Instance details

Defined in Preql.Wire.FromSql

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

Defined in Preql.Wire.FromSql

(FromSql a, FromSql b) => FromSql (a, b) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b) Source #

(FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c) Source #

(FromSql a, FromSql b, FromSql c, FromSql d) => FromSql (a, b, c, d) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e) => FromSql (a, b, c, d, e) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f) => FromSql (a, b, c, d, e, f) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g) => FromSql (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h) => FromSql (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i) => FromSql (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j) => FromSql (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k) => FromSql (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w, FromSql x) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

(FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w, FromSql x, FromSql y) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 
Instance details

Defined in Preql.Wire.FromSql

Methods

fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

class FromSqlField a Source #

Minimal complete definition

fromSqlField

Instances
FromSqlField Bool Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Double Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Float Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Int16 Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Int32 Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Int64 Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField ByteString Source #

If you want to encode some more specific Haskell type via JSON, it is more efficient to use encode and jsonb_bytes directly, rather than this instance.

Instance details

Defined in Preql.Wire.FromSql

FromSqlField ByteString Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Text Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField UTCTime Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Value Source #

If you want to encode some more specific Haskell type via JSON, it is more efficient to use fromSqlJsonField rather than this instance.

Instance details

Defined in Preql.Wire.FromSql

FromSqlField Text Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField String Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField UUID Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField Day Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField TimeOfDay Source # 
Instance details

Defined in Preql.Wire.FromSql

FromSqlField TimeTZ Source # 
Instance details

Defined in Preql.Wire.FromSql

Encoding parameters

class ToSql a Source #

ToSql a is sufficient to pass a as parameters to a paramaterized query.

Minimal complete definition

toSql

Instances
ToSql Bool Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Char Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Double Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Float Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Int16 Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Int32 Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Int64 Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql () Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder () Source #

ToSql ByteString Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql ByteString Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Text Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql UTCTime Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Value Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Text Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql String Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql UUID Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql Day Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql TimeOfDay Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSql TimeTZ Source # 
Instance details

Defined in Preql.Wire.ToSql

(ToSqlField a, ToSqlField b) => ToSql (a, b) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b) Source #

(ToSqlField a, ToSqlField b, ToSqlField c) => ToSql (a, b, c) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d) => ToSql (a, b, c, d) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e) => ToSql (a, b, c, d, e) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f) => ToSql (a, b, c, d, e, f) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g) => ToSql (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h) => ToSql (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i) => ToSql (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j) => ToSql (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k) => ToSql (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s, ToSqlField t) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s, ToSqlField t, ToSqlField u) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s, ToSqlField t, ToSqlField u, ToSqlField v) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s, ToSqlField t, ToSqlField u, ToSqlField v, ToSqlField w) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s, ToSqlField t, ToSqlField u, ToSqlField v, ToSqlField w, ToSqlField x) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

(ToSqlField a, ToSqlField b, ToSqlField c, ToSqlField d, ToSqlField e, ToSqlField f, ToSqlField g, ToSqlField h, ToSqlField i, ToSqlField j, ToSqlField k, ToSqlField l, ToSqlField m, ToSqlField n, ToSqlField o, ToSqlField p, ToSqlField q, ToSqlField r, ToSqlField s, ToSqlField t, ToSqlField u, ToSqlField v, ToSqlField w, ToSqlField x, ToSqlField y) => ToSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 
Instance details

Defined in Preql.Wire.ToSql

Methods

toSql :: RowEncoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

class ToSqlField a Source #

Types which can be encoded to a single Postgres field.

Minimal complete definition

toSqlField

Instances
ToSqlField Bool Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Char Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Double Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Float Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Int16 Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Int32 Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Int64 Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField ByteString Source #

If you want to encode some more specific Haskell type via JSON, it is more efficient to use encode and jsonb_bytes directly, rather than this instance.

Instance details

Defined in Preql.Wire.ToSql

ToSqlField ByteString Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Text Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField UTCTime Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Value Source #

If you want to encode some more specific Haskell type via JSON, it is more efficient to use toSqlJsonField rather than this instance.

Instance details

Defined in Preql.Wire.ToSql

ToSqlField Text Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField String Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField UUID Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField Day Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField TimeOfDay Source # 
Instance details

Defined in Preql.Wire.ToSql

ToSqlField TimeTZ Source # 
Instance details

Defined in Preql.Wire.ToSql

Errors

data FieldError Source #

A decoding error with information about the row & column of the result where it occured.

encoding & decoding to wire format

module Preql.Wire