Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
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 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 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
Instances
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