Safe Haskell | None |
---|---|
Language | Haskell2010 |
Preql
Synopsis
- class Monad m => SQL (m :: * -> *) where
- query :: (ToSql p, FromSql r) => (Query, p) -> m (Vector r)
- query_ :: ToSql p => (Query, p) -> m ()
- runTransaction :: Transaction a -> m a
- sql :: QuasiQuoter
- data Transaction a
- data Query
- runTransactionIO :: Transaction a -> Connection -> IO (Either QueryError a)
- class FromSql a
- class FromSqlField a
- class ToSql a
- class ToSqlField a
- data QueryError
- data FieldError = FieldError {}
- data UnlocatedFieldError
- data TypeMismatch = TypeMismatch {}
- module Preql.Wire
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
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 |
Defined in Preql.Effect.Internal Methods query :: (ToSql p, FromSql r) => (Query, p) -> Transaction (Vector r) Source # query_ :: ToSql p => (Query, p) -> Transaction () Source # runTransaction :: Transaction a -> Transaction a Source # | |
(MonadTrans t, Monad (t m), SQL m) => SQL (t m) Source # | Lift through any monad transformer without a more specific instance. |
SQL (ReaderT Connection IO) Source # | Most larger applications will define an instance; this one is suitable to test out the library. |
Defined in Preql.Effect.Internal Methods query :: (ToSql p, FromSql r) => (Query, p) -> ReaderT Connection IO (Vector r) Source # query_ :: ToSql p => (Query, p) -> ReaderT Connection IO () Source # runTransaction :: Transaction a -> ReaderT Connection IO a Source # |
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
The IsString instance does no validation; the limited instances discourage directly manipulating strings, with the high risk of SQL injection.
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
Minimal complete definition
Instances
FromSql Bool Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Bool Source # | |
FromSql Double Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Float Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Int16 Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Int32 Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Int64 Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql ByteString Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql ByteString Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Text Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Text Source # | |
FromSql UTCTime Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Value Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql Text Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Text Source # | |
FromSql String Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql UUID Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder UUID Source # | |
FromSql Day Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Day Source # | |
FromSql TimeOfDay Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSql TimeTZ Source # | |
Defined in Preql.Wire.FromSql Methods | |
FromSqlField a => FromSql (Maybe a) Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (Maybe a) Source # | |
(FromSql a, FromSql b) => FromSql (a, b) Source # | |
Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b) Source # | |
(FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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
Instances
Encoding parameters
ToSql a
is sufficient to pass a
as parameters to a paramaterized query.
Minimal complete definition
Instances
class ToSqlField a Source #
Types which can be encoded to a single Postgres field.
Minimal complete definition
Instances
Errors
data QueryError Source #
Constructors
ConnectionError Text | |
DecoderError FieldError | |
PgTypeMismatch [TypeMismatch] |
Instances
Eq QueryError Source # | |
Defined in Preql.Wire.Errors | |
Show QueryError Source # | |
Defined in Preql.Wire.Errors Methods showsPrec :: Int -> QueryError -> ShowS # show :: QueryError -> String # showList :: [QueryError] -> ShowS # | |
ToJSON QueryError Source # | |
Defined in Preql.Wire.Errors Methods toJSON :: QueryError -> Value # toEncoding :: QueryError -> Encoding # toJSONList :: [QueryError] -> Value # toEncodingList :: [QueryError] -> Encoding # | |
FromJSON QueryError Source # | |
Defined in Preql.Wire.Errors | |
Exception QueryError Source # | |
Defined in Preql.Wire.Errors Methods toException :: QueryError -> SomeException # fromException :: SomeException -> Maybe QueryError # displayException :: QueryError -> String # |
data FieldError Source #
A decoding error with information about the row & column of the result where it occured.
Constructors
FieldError | |
Fields
|
Instances
Eq FieldError Source # | |
Defined in Preql.Wire.Errors | |
Show FieldError Source # | |
Defined in Preql.Wire.Errors Methods showsPrec :: Int -> FieldError -> ShowS # show :: FieldError -> String # showList :: [FieldError] -> ShowS # | |
ToJSON FieldError Source # | |
Defined in Preql.Wire.Errors Methods toJSON :: FieldError -> Value # toEncoding :: FieldError -> Encoding # toJSONList :: [FieldError] -> Value # toEncodingList :: [FieldError] -> Encoding # | |
FromJSON FieldError Source # | |
Defined in Preql.Wire.Errors | |
Exception FieldError Source # | |
Defined in Preql.Wire.Errors Methods toException :: FieldError -> SomeException # fromException :: SomeException -> Maybe FieldError # displayException :: FieldError -> String # |
data UnlocatedFieldError Source #
Errors that can occur in decoding a single field.
Constructors
UnexpectedNull | |
ParseFailure Text |
Instances
Eq UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors Methods (==) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # (/=) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # | |
Show UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors Methods showsPrec :: Int -> UnlocatedFieldError -> ShowS # show :: UnlocatedFieldError -> String # showList :: [UnlocatedFieldError] -> ShowS # | |
ToJSON UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors Methods toJSON :: UnlocatedFieldError -> Value # toEncoding :: UnlocatedFieldError -> Encoding # toJSONList :: [UnlocatedFieldError] -> Value # toEncodingList :: [UnlocatedFieldError] -> Encoding # | |
FromJSON UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors Methods parseJSON :: Value -> Parser UnlocatedFieldError # parseJSONList :: Value -> Parser [UnlocatedFieldError] # |
data TypeMismatch Source #
Constructors
TypeMismatch | |
Instances
Eq TypeMismatch Source # | |
Defined in Preql.Wire.Errors | |
Show TypeMismatch Source # | |
Defined in Preql.Wire.Errors Methods showsPrec :: Int -> TypeMismatch -> ShowS # show :: TypeMismatch -> String # showList :: [TypeMismatch] -> ShowS # | |
ToJSON TypeMismatch Source # | |
Defined in Preql.Wire.Errors Methods toJSON :: TypeMismatch -> Value # toEncoding :: TypeMismatch -> Encoding # toJSONList :: [TypeMismatch] -> Value # toEncodingList :: [TypeMismatch] -> Encoding # | |
FromJSON TypeMismatch Source # | |
Defined in Preql.Wire.Errors |
encoding & decoding to wire format
module Preql.Wire