Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class SqlQuery m => SQL (m :: * -> *) where
- runTransaction' :: IsolationLevel -> Transaction a -> m a
- withConnection :: (Connection -> m a) -> m a
- queryOn :: (ToSql p, FromSql r, KnownNat (Width r)) => Connection -> (Query (Width r), p) -> m (Vector r)
- queryOn_ :: ToSql p => Connection -> (Query 0, p) -> m ()
- class Monad m => SqlQuery (m :: * -> *) where
- sql :: QuasiQuoter
- select :: QuasiQuoter
- validSql :: QuasiQuoter
- data Transaction a
- data Query (n :: Nat)
- runTransactionIO :: IsolationLevel -> 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 SqlQuery 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 withConnection
.
Override the remaining methods to log errors before rethrowing, or not to rethrow.
runTransaction' :: IsolationLevel -> Transaction a -> m a Source #
Run multiple queries in a transaction.
default runTransaction' :: MonadIO m => IsolationLevel -> Transaction a -> m a Source #
withConnection :: (Connection -> m a) -> m a Source #
runTransaction
covers the most common patterns of
mult-statement transactions. withConnection
is useful when
you want more control, or want to override the defaults that
your instance defines. For example:
- change the number of retries
- interleave calls to other services with the Postgres transaction
- ensure a prepared statement is shared among successive transactions
queryOn :: (ToSql p, FromSql r, KnownNat (Width r)) => Connection -> (Query (Width r), p) -> m (Vector r) Source #
Run a query on the specified Connection
default queryOn :: (ToSql p, FromSql r, KnownNat (Width r), MonadIO m) => Connection -> (Query (Width r), p) -> m (Vector r) Source #
queryOn_ :: ToSql p => Connection -> (Query 0, p) -> m () Source #
Instances
class Monad m => SqlQuery (m :: * -> *) where Source #
SqlQuery is separate from SQL
so that nested Transaction
s are
statically prevented. query
can be used directly within any
SQL
monad (running a single-statement transaction), or within a
Transaction
.
Users should not need to define instances, as every SQL
instance
implies a SqlQuery
instance.
query :: (ToSql p, FromSql r, KnownNat (Width r)) => (Query (Width r), p) -> m (Vector r) Source #
Run a parameterized query that returns data. The tuple argument is typically provided by
one of the Quasiquoters: sql
or select
query_ :: ToSql p => (Query 0, p) -> m () Source #
Run a parameterized query that does not return data.
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))
select :: QuasiQuoter Source #
This quasiquoter will accept most syntactically valid SELECT
queries. Language features not yet implemented include type casts,
lateral joins, EXTRACT, INTO, string & XML operators, and
user-defined operators. For now, please fall back to
sql
for these less-frequently used SQL
features, or file a bug report if a commonly used feature is not
parsed correctly.
select
accepts antiquotes with the same syntax as sql
.
validSql :: QuasiQuoter Source #
This quasiquoter will accept all queries accepted by select
,
and limited INSERT, UPDATE, and DELETE queries. For details of
what can be parsed, consult Parser.y
data Transaction a Source #
A Transaction can only contain SQL queries (and pure functions).
Instances
Monad Transaction Source # | |
Defined in Preql.Effect.Internal (>>=) :: Transaction a -> (a -> Transaction b) -> Transaction b # (>>) :: Transaction a -> Transaction b -> Transaction b # return :: a -> Transaction a # | |
Functor Transaction Source # | |
Defined in Preql.Effect.Internal fmap :: (a -> b) -> Transaction a -> Transaction b # (<$) :: a -> Transaction b -> Transaction a # | |
Applicative Transaction Source # | |
Defined in Preql.Effect.Internal 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 # | |
SqlQuery Transaction Source # | |
data Query (n :: Nat) Source #
The IsString instance does no validation; the limited instances
discourage directly manipulating strings, with the high risk of SQL
injection. A Query
is tagged with a Nat
representing the width
of its return type.
functions for writing SQL instances
runTransactionIO :: IsolationLevel -> Transaction a -> Connection -> IO (Either QueryError a) Source #
Run the provided Transaction
. If it fails with a QueryError
, roll back.
Decoding rows
A type which can be decoded from a SQL row. Note that this includes the canonical order of fields.
The default (empty) instance works for any type with a
FromSqlField
instance
Instances
FromSql Bool Source # | |
FromSql Char Source # | |
FromSql Double Source # | |
FromSql Float Source # | |
FromSql Int16 Source # | |
FromSql Int32 Source # | |
FromSql Int64 Source # | |
FromSql ByteString Source # | |
Defined in Preql.FromSql.Instances type Width ByteString :: Nat Source # | |
FromSql ByteString Source # | |
Defined in Preql.FromSql.Instances type Width ByteString :: Nat Source # | |
FromSql String Source # | |
FromSql Text Source # | |
FromSql UTCTime Source # | |
FromSql Value Source # | |
FromSql Text Source # | |
FromSql UUID Source # | |
FromSql Day Source # | |
FromSql TimeOfDay Source # | |
FromSql Oid Source # | |
FromSql PgName Source # | |
FromSql TimeTZ Source # | |
FromSqlField a => FromSql (Maybe a) Source # | |
(FromSql a, FromSql b) => FromSql (a, b) Source # | |
Defined in Preql.FromSql.Instances fromSql :: RowDecoder (Width (a, b)) (a, b) Source # | |
(FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # | |
Defined in Preql.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c)) (a, b, c) Source # | |
(FromSql a, FromSql b, FromSql c, FromSql d) => FromSql (a, b, c, d) Source # | |
Defined in Preql.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w)) (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.FromSql.Instances fromSql :: RowDecoder (Width (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x)) (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.FromSql.Instances type Width (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) :: Nat Source # fromSql :: RowDecoder (Width (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)) (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 #
Instances
Encoding parameters
ToSql a
is sufficient to pass a
as parameters to a paramaterized query.
Instances
class ToSqlField a Source #
Types which can be encoded to a single Postgres field.
Instances
Errors
data QueryError Source #
Instances
Eq QueryError Source # | |
Defined in Preql.Wire.Errors (==) :: QueryError -> QueryError -> Bool # (/=) :: QueryError -> QueryError -> Bool # | |
Show QueryError Source # | |
Defined in Preql.Wire.Errors showsPrec :: Int -> QueryError -> ShowS # show :: QueryError -> String # showList :: [QueryError] -> ShowS # | |
ToJSON QueryError Source # | |
Defined in Preql.Wire.Errors toJSON :: QueryError -> Value # toEncoding :: QueryError -> Encoding # toJSONList :: [QueryError] -> Value # toEncodingList :: [QueryError] -> Encoding # | |
FromJSON QueryError Source # | |
Defined in Preql.Wire.Errors parseJSON :: Value -> Parser QueryError # parseJSONList :: Value -> Parser [QueryError] # | |
Exception QueryError Source # | |
Defined in Preql.Wire.Errors 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.
Instances
Eq FieldError Source # | |
Defined in Preql.Wire.Errors (==) :: FieldError -> FieldError -> Bool # (/=) :: FieldError -> FieldError -> Bool # | |
Show FieldError Source # | |
Defined in Preql.Wire.Errors showsPrec :: Int -> FieldError -> ShowS # show :: FieldError -> String # showList :: [FieldError] -> ShowS # | |
ToJSON FieldError Source # | |
Defined in Preql.Wire.Errors toJSON :: FieldError -> Value # toEncoding :: FieldError -> Encoding # toJSONList :: [FieldError] -> Value # toEncodingList :: [FieldError] -> Encoding # | |
FromJSON FieldError Source # | |
Defined in Preql.Wire.Errors parseJSON :: Value -> Parser FieldError # parseJSONList :: Value -> Parser [FieldError] # | |
Exception FieldError Source # | |
Defined in Preql.Wire.Errors toException :: FieldError -> SomeException # fromException :: SomeException -> Maybe FieldError # displayException :: FieldError -> String # |
data UnlocatedFieldError Source #
Errors that can occur in decoding a single field.
Instances
Eq UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors (==) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # (/=) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # | |
Show UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors showsPrec :: Int -> UnlocatedFieldError -> ShowS # show :: UnlocatedFieldError -> String # showList :: [UnlocatedFieldError] -> ShowS # | |
ToJSON UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors toJSON :: UnlocatedFieldError -> Value # toEncoding :: UnlocatedFieldError -> Encoding # toJSONList :: [UnlocatedFieldError] -> Value # toEncodingList :: [UnlocatedFieldError] -> Encoding # | |
FromJSON UnlocatedFieldError Source # | |
Defined in Preql.Wire.Errors parseJSON :: Value -> Parser UnlocatedFieldError # parseJSONList :: Value -> Parser [UnlocatedFieldError] # |
data TypeMismatch Source #
Instances
Eq TypeMismatch Source # | |
Defined in Preql.Wire.Errors (==) :: TypeMismatch -> TypeMismatch -> Bool # (/=) :: TypeMismatch -> TypeMismatch -> Bool # | |
Show TypeMismatch Source # | |
Defined in Preql.Wire.Errors showsPrec :: Int -> TypeMismatch -> ShowS # show :: TypeMismatch -> String # showList :: [TypeMismatch] -> ShowS # | |
ToJSON TypeMismatch Source # | |
Defined in Preql.Wire.Errors toJSON :: TypeMismatch -> Value # toEncoding :: TypeMismatch -> Encoding # toJSONList :: [TypeMismatch] -> Value # toEncodingList :: [TypeMismatch] -> Encoding # | |
FromJSON TypeMismatch Source # | |
Defined in Preql.Wire.Errors parseJSON :: Value -> Parser TypeMismatch # parseJSONList :: Value -> Parser [TypeMismatch] # |
encoding & decoding to wire format
module Preql.Wire