preql-0.6: safe PostgreSQL queries using Quasiquoters
Safe HaskellNone
LanguageHaskell2010

Preql

Description

 
Synopsis

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.

Minimal complete definition

withConnection

Methods

runTransaction' :: IsolationLevel -> Transaction a -> m a Source #

Run multiple queries in a transaction.

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 #

default queryOn_ :: (ToSql p, MonadIO m) => Connection -> (Query 0, p) -> m () Source #

Instances

Instances details
SQL m => SQL (MaybeT m) Source # 
Instance details

Defined in Preql.Effect

SQL m => SQL (StateT s m) Source # 
Instance details

Defined in Preql.Effect

Methods

runTransaction' :: IsolationLevel -> Transaction a -> StateT s m a Source #

withConnection :: (Connection -> StateT s m a) -> StateT s m a Source #

queryOn :: (ToSql p, FromSql r, KnownNat (Width r)) => Connection -> (Query (Width r), p) -> StateT s m (Vector r) Source #

queryOn_ :: ToSql p => Connection -> (Query 0, p) -> StateT s m () Source #

SQL m => SQL (ReaderT r m) Source # 
Instance details

Defined in Preql.Effect

Methods

runTransaction' :: IsolationLevel -> Transaction a -> ReaderT r m a Source #

withConnection :: (Connection -> ReaderT r m a) -> ReaderT r m a Source #

queryOn :: (ToSql p, FromSql r0, KnownNat (Width r0)) => Connection -> (Query (Width r0), p) -> ReaderT r m (Vector r0) Source #

queryOn_ :: ToSql p => Connection -> (Query 0, p) -> ReaderT r m () Source #

SQL (ReaderT Connection IO) Source #

Most larger applications will define an instance; this one is suitable to test out the library. A safer version would use MVar Connection to ensure only one thread using it.

Instance details

Defined in Preql.Effect

SQL m => SQL (ExceptT e m) Source # 
Instance details

Defined in Preql.Effect

Methods

runTransaction' :: IsolationLevel -> Transaction a -> ExceptT e m a Source #

withConnection :: (Connection -> ExceptT e m a) -> ExceptT e m a Source #

queryOn :: (ToSql p, FromSql r, KnownNat (Width r)) => Connection -> (Query (Width r), p) -> ExceptT e m (Vector r) Source #

queryOn_ :: ToSql p => Connection -> (Query 0, p) -> ExceptT e m () Source #

SQL m => SQL (StateT s m) Source # 
Instance details

Defined in Preql.Effect

Methods

runTransaction' :: IsolationLevel -> Transaction a -> StateT s m a Source #

withConnection :: (Connection -> StateT s m a) -> StateT s m a Source #

queryOn :: (ToSql p, FromSql r, KnownNat (Width r)) => Connection -> (Query (Width r), p) -> StateT s m (Vector r) Source #

queryOn_ :: ToSql p => Connection -> (Query 0, p) -> StateT s m () Source #

(Monoid w, SQL m) => SQL (RWST r w s m) Source # 
Instance details

Defined in Preql.Effect

Methods

runTransaction' :: IsolationLevel -> Transaction a -> RWST r w s m a Source #

withConnection :: (Connection -> RWST r w s m a) -> RWST r w s m a Source #

queryOn :: (ToSql p, FromSql r0, KnownNat (Width r0)) => Connection -> (Query (Width r0), p) -> RWST r w s m (Vector r0) Source #

queryOn_ :: ToSql p => Connection -> (Query 0, p) -> RWST r w s m () Source #

(Monoid w, SQL m) => SQL (RWST r w s m) Source # 
Instance details

Defined in Preql.Effect

Methods

runTransaction' :: IsolationLevel -> Transaction a -> RWST r w s m a Source #

withConnection :: (Connection -> RWST r w s m a) -> RWST r w s m a Source #

queryOn :: (ToSql p, FromSql r0, KnownNat (Width r0)) => Connection -> (Query (Width r0), p) -> RWST r w s m (Vector r0) Source #

queryOn_ :: ToSql p => Connection -> (Query 0, p) -> RWST r w s m () Source #

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

SqlQuery is separate from SQL so that nested Transactions 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.

Methods

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.

Instances

Instances details
(Monad m, SQL m) => SqlQuery m Source # 
Instance details

Defined in Preql.Effect

Methods

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

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

SqlQuery Transaction Source # 
Instance details

Defined in Preql.Effect

Methods

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

query_ :: ToSql p => (Query 0, p) -> Transaction () 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))

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

Instances details
Monad Transaction Source # 
Instance details

Defined in Preql.Effect.Internal

Methods

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

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

return :: a -> Transaction a #

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 #

SqlQuery Transaction Source # 
Instance details

Defined in Preql.Effect

Methods

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

query_ :: ToSql p => (Query 0, p) -> 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.

Instances

Instances details
Show (Query n) Source # 
Instance details

Defined in Preql.Wire.Internal

Methods

showsPrec :: Int -> Query n -> ShowS #

show :: Query n -> String #

showList :: [Query n] -> ShowS #

IsString (Query n) Source # 
Instance details

Defined in Preql.Wire.Internal

Methods

fromString :: String -> Query n #

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

class FromSql a Source #

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. This is convenient when you define your own Postgres types, since they should be instances of both type classes.

Instances

Instances details
FromSql Bool Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Bool :: Nat Source #

FromSql Char Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Char :: Nat Source #

FromSql Double Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Double :: Nat Source #

FromSql Float Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Float :: Nat Source #

FromSql Int16 Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Int16 :: Nat Source #

FromSql Int32 Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Int32 :: Nat Source #

FromSql Int64 Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Int64 :: Nat Source #

FromSql ByteString Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width ByteString :: Nat Source #

FromSql ByteString Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width ByteString :: Nat Source #

FromSql String Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width String :: Nat Source #

FromSql Text Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Text :: Nat Source #

FromSql UTCTime Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width UTCTime :: Nat Source #

FromSql Value Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Value :: Nat Source #

FromSql Text Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Text :: Nat Source #

FromSql UUID Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width UUID :: Nat Source #

FromSql Day Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Day :: Nat Source #

FromSql TimeOfDay Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width TimeOfDay :: Nat Source #

FromSql Oid Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width Oid :: Nat Source #

FromSql PgName Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width PgName :: Nat Source #

FromSql TimeTZ Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width TimeTZ :: Nat Source #

FromSqlField [a] => FromSql [a] Source # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width [a] :: Nat Source #

Methods

fromSql :: RowDecoder (Width [a]) [a] Source #

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Maybe a) :: Nat Source #

Methods

fromSql :: RowDecoder (Width (Maybe a)) (Maybe a) Source #

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Vector a) :: Nat Source #

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b)) :: Nat Source #

Methods

fromSql :: RowDecoder (Width (Tuple (a, b))) (Tuple (a, b)) Source #

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m, n)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q)) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s) => FromSql (Tuple (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.FromSql.Instances

Associated Types

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

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t) => FromSql (Tuple (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.FromSql.Instances

Associated Types

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

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u) => FromSql (Tuple (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.FromSql.Instances

Associated Types

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

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v) => FromSql (Tuple (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.FromSql.Instances

Associated Types

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

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v, FromSqlField w) => FromSql (Tuple (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.FromSql.Instances

Associated Types

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

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v, FromSqlField w, FromSqlField x) => FromSql (Tuple (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.FromSql.Instances

Associated Types

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

Methods

fromSql :: RowDecoder (Width (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x))) (Tuple (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 #

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v, FromSqlField w, FromSqlField x, FromSqlField y) => FromSql (Tuple (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.FromSql.Instances

Associated Types

type Width (Tuple (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 #

Methods

fromSql :: RowDecoder (Width (Tuple (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))) (Tuple (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 #

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c) :: Nat Source #

Methods

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

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

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g, h) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g, h, i) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g, h, i, j) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g, h, i, j, k) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g, h, i, j, k, l) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

type Width (a, b, c, d, e, f, g, h, i, j, k, l, m) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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) :: Nat Source #

Methods

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 # 
Instance details

Defined in Preql.FromSql.Instances

Associated Types

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 #

Methods

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 #

A type which can be decoded from a single SQL field. This is mostly useful for defining what can be an element of an array or Tuple.

Minimal complete definition

fromSqlField

Instances

Instances details
FromSqlField Bool Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Char Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Double Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Float Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Int16 Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Int32 Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Int64 Source # 
Instance details

Defined in Preql.FromSql.Instances

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.FromSql.Instances

FromSqlField ByteString Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField String Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Text Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField UTCTime Source # 
Instance details

Defined in Preql.FromSql.Instances

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.FromSql.Instances

FromSqlField Text Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField UUID Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Day Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField TimeOfDay Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField Oid Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField PgName Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField TimeTZ Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField [[[[[a]]]]] Source # 
Instance details

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder [[[[[a]]]]] Source #

FromSqlField a => FromSqlField [[[[a]]]] Source # 
Instance details

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder [[[[a]]]] Source #

FromSqlField a => FromSqlField [[[a]]] Source # 
Instance details

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder [[[a]]] Source #

FromSqlField a => FromSqlField [[a]] Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField [a] Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField (Vector a) Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField (Vector (Vector a)) Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField (Vector (Vector (Vector a))) Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField (Vector (Vector (Vector (Vector a)))) Source # 
Instance details

Defined in Preql.FromSql.Instances

FromSqlField a => FromSqlField (Vector (Vector (Vector (Vector (Vector a))))) Source # 
Instance details

Defined in Preql.FromSql.Instances

(FromSqlField a, FromSqlField b) => FromSqlField (Tuple (a, b)) Source # 
Instance details

Defined in Preql.FromSql.Instances

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g, h)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g, h, i)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g, h, i, j)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g, h, i, j, k)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g, h, i, j, k, l)) Source #

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

Defined in Preql.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (a, b, c, d, e, f, g, h, i, j, k, l, m)) Source #

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

Defined in Preql.FromSql.Instances

Methods

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

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

Defined in Preql.FromSql.Instances

Methods

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

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

Defined in Preql.FromSql.Instances

Methods

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

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

Defined in Preql.FromSql.Instances

Methods

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

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

Defined in Preql.FromSql.Instances

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s) => FromSqlField (Tuple (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.FromSql.Instances

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t) => FromSqlField (Tuple (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.FromSql.Instances

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u) => FromSqlField (Tuple (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.FromSql.Instances

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v) => FromSqlField (Tuple (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.FromSql.Instances

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v, FromSqlField w) => FromSqlField (Tuple (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.FromSql.Instances

Methods

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

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v, FromSqlField w, FromSqlField x) => FromSqlField (Tuple (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.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (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 #

(FromSqlField a, FromSqlField b, FromSqlField c, FromSqlField d, FromSqlField e, FromSqlField f, FromSqlField g, FromSqlField h, FromSqlField i, FromSqlField j, FromSqlField k, FromSqlField l, FromSqlField m, FromSqlField n, FromSqlField o, FromSqlField p, FromSqlField q, FromSqlField r, FromSqlField s, FromSqlField t, FromSqlField u, FromSqlField v, FromSqlField w, FromSqlField x, FromSqlField y) => FromSqlField (Tuple (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.FromSql.Instances

Methods

fromSqlField :: FieldDecoder (Tuple (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 #

Encoding parameters

class ToSql a Source #

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

Minimal complete definition

toSql

Instances

Instances details
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 String 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 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

Instances details
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 String 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 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