| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Preql.Wire
Description
This module re-exports definitions from Wire.* that are expected to be useful
Synopsis
- class FromSql a
- class FromSqlField a
- class ToSql a
- class ToSqlField a
- data QueryError
- data FieldError = FieldError {}
- data UnlocatedFieldError
- data TypeMismatch = TypeMismatch {}
- data UnlocatedFieldError
- data FieldError = FieldError {}
- data TypeMismatch = TypeMismatch {}
- data QueryError
- data RowDecoder a
- data Query
- data TimeTZ = TimeTZ !TimeOfDay !TimeZone
- class ToSql a where- toSql :: RowEncoder a
 
- class ToSqlField a where- toSqlField :: FieldEncoder a
 
- type RowEncoder a = a -> [(Oid, ByteString)]
- data FieldEncoder a = FieldEncoder Oid (a -> Builder)
- runFieldEncoder :: FieldEncoder p -> p -> (Oid, ByteString)
- runEncoder :: RowEncoder p -> p -> [Maybe (Oid, ByteString, Format)]
- oneField :: FieldEncoder a -> RowEncoder a
- toSqlJsonField :: ToJSON a => FieldEncoder a
- class FromSql a where- fromSql :: RowDecoder a
 
- class FromSqlField a where- fromSqlField :: FieldDecoder a
 
- data FieldDecoder a = FieldDecoder Oid (BinaryParser a)
- throwLocated :: UnlocatedFieldError -> InternalDecoder a
- decodeVector :: RowDecoder a -> Result -> IO (Either QueryError (Vector a))
- notNull :: FieldDecoder a -> RowDecoder a
- nullable :: FieldDecoder a -> RowDecoder (Maybe a)
- fromSqlJsonField :: FromJSON a => FieldDecoder a
Decoding rows
Minimal complete definition
Instances
| FromSql Bool Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Bool Source # | |
| FromSql Double Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Float Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Int16 Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Int32 Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Int64 Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql ByteString Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql ByteString Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Text Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Text Source # | |
| FromSql UTCTime Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Value Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Text Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Text Source # | |
| FromSql String Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql UUID Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder UUID Source # | |
| FromSql Day Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Day Source # | |
| FromSql TimeOfDay Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql TimeTZ Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSqlField a => FromSql (Maybe a) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (Maybe a) Source # | |
| (FromSql a, FromSql b) => FromSql (a, b) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b) Source # | |
| (FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d) => FromSql (a, b, c, d) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e) => FromSql (a, b, c, d, e) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f) => FromSql (a, b, c, d, e, f) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g) => FromSql (a, b, c, d, e, f, g) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h) => FromSql (a, b, c, d, e, f, g, h) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i) => FromSql (a, b, c, d, e, f, g, h, i) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j) => FromSql (a, b, c, d, e, f, g, h, i, j) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k) => FromSql (a, b, c, d, e, f, g, h, i, j, k) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w, FromSql x) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w, FromSql x, FromSql y) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | |
class FromSqlField a Source #
Minimal complete definition
Instances
Encoding parameters
ToSql a is sufficient to pass a as parameters to a paramaterized query.
Minimal complete definition
Instances
class ToSqlField a Source #
Types which can be encoded to a single Postgres field.
Minimal complete definition
Instances
Errors
data QueryError Source #
Constructors
| ConnectionError Text | |
| DecoderError FieldError | |
| PgTypeMismatch [TypeMismatch] | 
Instances
| Eq QueryError Source # | |
| Defined in Preql.Wire.Errors | |
| Show QueryError Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> QueryError -> ShowS # show :: QueryError -> String # showList :: [QueryError] -> ShowS # | |
| ToJSON QueryError Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: QueryError -> Value # toEncoding :: QueryError -> Encoding # toJSONList :: [QueryError] -> Value # toEncodingList :: [QueryError] -> Encoding # | |
| FromJSON QueryError Source # | |
| Defined in Preql.Wire.Errors | |
| Exception QueryError Source # | |
| Defined in Preql.Wire.Errors Methods toException :: QueryError -> SomeException # fromException :: SomeException -> Maybe QueryError # displayException :: QueryError -> String # | |
data FieldError Source #
A decoding error with information about the row & column of the result where it occured.
Constructors
| FieldError | |
| Fields 
 | |
Instances
| Eq FieldError Source # | |
| Defined in Preql.Wire.Errors | |
| Show FieldError Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> FieldError -> ShowS # show :: FieldError -> String # showList :: [FieldError] -> ShowS # | |
| ToJSON FieldError Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: FieldError -> Value # toEncoding :: FieldError -> Encoding # toJSONList :: [FieldError] -> Value # toEncodingList :: [FieldError] -> Encoding # | |
| FromJSON FieldError Source # | |
| Defined in Preql.Wire.Errors | |
| Exception FieldError Source # | |
| Defined in Preql.Wire.Errors Methods toException :: FieldError -> SomeException # fromException :: SomeException -> Maybe FieldError # displayException :: FieldError -> String # | |
data UnlocatedFieldError Source #
Errors that can occur in decoding a single field.
Constructors
| UnexpectedNull | |
| ParseFailure Text | 
Instances
| Eq UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods (==) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # (/=) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # | |
| Show UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> UnlocatedFieldError -> ShowS # show :: UnlocatedFieldError -> String # showList :: [UnlocatedFieldError] -> ShowS # | |
| ToJSON UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: UnlocatedFieldError -> Value # toEncoding :: UnlocatedFieldError -> Encoding # toJSONList :: [UnlocatedFieldError] -> Value # toEncodingList :: [UnlocatedFieldError] -> Encoding # | |
| FromJSON UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods parseJSON :: Value -> Parser UnlocatedFieldError # parseJSONList :: Value -> Parser [UnlocatedFieldError] # | |
data TypeMismatch Source #
Constructors
| TypeMismatch | |
Instances
| Eq TypeMismatch Source # | |
| Defined in Preql.Wire.Errors | |
| Show TypeMismatch Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> TypeMismatch -> ShowS # show :: TypeMismatch -> String # showList :: [TypeMismatch] -> ShowS # | |
| ToJSON TypeMismatch Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: TypeMismatch -> Value # toEncoding :: TypeMismatch -> Encoding # toJSONList :: [TypeMismatch] -> Value # toEncodingList :: [TypeMismatch] -> Encoding # | |
| FromJSON TypeMismatch Source # | |
| Defined in Preql.Wire.Errors | |
data UnlocatedFieldError Source #
Errors that can occur in decoding a single field.
Constructors
| UnexpectedNull | |
| ParseFailure Text | 
Instances
| Eq UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods (==) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # (/=) :: UnlocatedFieldError -> UnlocatedFieldError -> Bool # | |
| Show UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> UnlocatedFieldError -> ShowS # show :: UnlocatedFieldError -> String # showList :: [UnlocatedFieldError] -> ShowS # | |
| ToJSON UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: UnlocatedFieldError -> Value # toEncoding :: UnlocatedFieldError -> Encoding # toJSONList :: [UnlocatedFieldError] -> Value # toEncodingList :: [UnlocatedFieldError] -> Encoding # | |
| FromJSON UnlocatedFieldError Source # | |
| Defined in Preql.Wire.Errors Methods parseJSON :: Value -> Parser UnlocatedFieldError # parseJSONList :: Value -> Parser [UnlocatedFieldError] # | |
data FieldError Source #
A decoding error with information about the row & column of the result where it occured.
Constructors
| FieldError | |
| Fields 
 | |
Instances
| Eq FieldError Source # | |
| Defined in Preql.Wire.Errors | |
| Show FieldError Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> FieldError -> ShowS # show :: FieldError -> String # showList :: [FieldError] -> ShowS # | |
| ToJSON FieldError Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: FieldError -> Value # toEncoding :: FieldError -> Encoding # toJSONList :: [FieldError] -> Value # toEncodingList :: [FieldError] -> Encoding # | |
| FromJSON FieldError Source # | |
| Defined in Preql.Wire.Errors | |
| Exception FieldError Source # | |
| Defined in Preql.Wire.Errors Methods toException :: FieldError -> SomeException # fromException :: SomeException -> Maybe FieldError # displayException :: FieldError -> String # | |
data TypeMismatch Source #
Constructors
| TypeMismatch | |
Instances
| Eq TypeMismatch Source # | |
| Defined in Preql.Wire.Errors | |
| Show TypeMismatch Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> TypeMismatch -> ShowS # show :: TypeMismatch -> String # showList :: [TypeMismatch] -> ShowS # | |
| ToJSON TypeMismatch Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: TypeMismatch -> Value # toEncoding :: TypeMismatch -> Encoding # toJSONList :: [TypeMismatch] -> Value # toEncodingList :: [TypeMismatch] -> Encoding # | |
| FromJSON TypeMismatch Source # | |
| Defined in Preql.Wire.Errors | |
data QueryError Source #
Constructors
| ConnectionError Text | |
| DecoderError FieldError | |
| PgTypeMismatch [TypeMismatch] | 
Instances
| Eq QueryError Source # | |
| Defined in Preql.Wire.Errors | |
| Show QueryError Source # | |
| Defined in Preql.Wire.Errors Methods showsPrec :: Int -> QueryError -> ShowS # show :: QueryError -> String # showList :: [QueryError] -> ShowS # | |
| ToJSON QueryError Source # | |
| Defined in Preql.Wire.Errors Methods toJSON :: QueryError -> Value # toEncoding :: QueryError -> Encoding # toJSONList :: [QueryError] -> Value # toEncodingList :: [QueryError] -> Encoding # | |
| FromJSON QueryError Source # | |
| Defined in Preql.Wire.Errors | |
| Exception QueryError Source # | |
| Defined in Preql.Wire.Errors Methods toException :: QueryError -> SomeException # fromException :: SomeException -> Maybe QueryError # displayException :: QueryError -> String # | |
data RowDecoder a Source #
RowDecoder is Applicative but not Monad so that we can
 assemble all of the OIDs before we read any of the field data sent
 by Postgresj.
Instances
| Functor RowDecoder Source # | |
| Defined in Preql.Wire.Internal Methods fmap :: (a -> b) -> RowDecoder a -> RowDecoder b # (<$) :: a -> RowDecoder b -> RowDecoder a # | |
| Applicative RowDecoder Source # | |
| Defined in Preql.Wire.Internal Methods pure :: a -> RowDecoder a # (<*>) :: RowDecoder (a -> b) -> RowDecoder a -> RowDecoder b # liftA2 :: (a -> b -> c) -> RowDecoder a -> RowDecoder b -> RowDecoder c # (*>) :: RowDecoder a -> RowDecoder b -> RowDecoder b # (<*) :: RowDecoder a -> RowDecoder b -> RowDecoder a # | |
The IsString instance does no validation; the limited instances discourage directly manipulating strings, with the high risk of SQL injection.
Instances
| Eq TimeTZ Source # | |
| Show TimeTZ Source # | |
| ToSql TimeTZ Source # | |
| Defined in Preql.Wire.ToSql Methods toSql :: RowEncoder TimeTZ Source # | |
| ToSqlField TimeTZ Source # | |
| Defined in Preql.Wire.ToSql Methods | |
| FromSql TimeTZ Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSqlField TimeTZ Source # | |
| Defined in Preql.Wire.FromSql Methods | |
ToSql a is sufficient to pass a as parameters to a paramaterized query.
Methods
toSql :: RowEncoder a Source #
Instances
class ToSqlField a where Source #
Types which can be encoded to a single Postgres field.
Methods
toSqlField :: FieldEncoder a Source #
Instances
type RowEncoder a = a -> [(Oid, ByteString)] Source #
data FieldEncoder a Source #
A FieldEncoder for a type a consists of a function from a to
 it's binary representation, and an Postgres OID which tells
 Postgres it's type & how to decode it.
Constructors
| FieldEncoder Oid (a -> Builder) | 
Instances
| Contravariant FieldEncoder Source # | |
| Defined in Preql.Wire.ToSql Methods contramap :: (a -> b) -> FieldEncoder b -> FieldEncoder a # (>$) :: b -> FieldEncoder b -> FieldEncoder a # | |
runFieldEncoder :: FieldEncoder p -> p -> (Oid, ByteString) Source #
runEncoder :: RowEncoder p -> p -> [Maybe (Oid, ByteString, Format)] Source #
oneField :: FieldEncoder a -> RowEncoder a Source #
toSqlJsonField :: ToJSON a => FieldEncoder a Source #
class FromSql a where Source #
Methods
fromSql :: RowDecoder a Source #
Instances
| FromSql Bool Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Bool Source # | |
| FromSql Double Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Float Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Int16 Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Int32 Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Int64 Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql ByteString Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql ByteString Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Text Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Text Source # | |
| FromSql UTCTime Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Value Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql Text Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Text Source # | |
| FromSql String Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql UUID Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder UUID Source # | |
| FromSql Day Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder Day Source # | |
| FromSql TimeOfDay Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSql TimeTZ Source # | |
| Defined in Preql.Wire.FromSql Methods | |
| FromSqlField a => FromSql (Maybe a) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (Maybe a) Source # | |
| (FromSql a, FromSql b) => FromSql (a, b) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b) Source # | |
| (FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d) => FromSql (a, b, c, d) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e) => FromSql (a, b, c, d, e) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f) => FromSql (a, b, c, d, e, f) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g) => FromSql (a, b, c, d, e, f, g) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h) => FromSql (a, b, c, d, e, f, g, h) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i) => FromSql (a, b, c, d, e, f, g, h, i) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j) => FromSql (a, b, c, d, e, f, g, h, i, j) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k) => FromSql (a, b, c, d, e, f, g, h, i, j, k) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w, FromSql x) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # | |
| (FromSql a, FromSql b, FromSql c, FromSql d, FromSql e, FromSql f, FromSql g, FromSql h, FromSql i, FromSql j, FromSql k, FromSql l, FromSql m, FromSql n, FromSql o, FromSql p, FromSql q, FromSql r, FromSql s, FromSql t, FromSql u, FromSql v, FromSql w, FromSql x, FromSql y) => FromSql (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | |
| Defined in Preql.Wire.FromSql Methods fromSql :: RowDecoder (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # | |
class FromSqlField a where Source #
Methods
fromSqlField :: FieldDecoder a Source #
Instances
data FieldDecoder a Source #
A FieldDecoder for a type a consists of an OID indicating the
 Postgres type which can be decoded, and a parser from the binary
 representation of that type to the Haskell representation.
Constructors
| FieldDecoder Oid (BinaryParser a) | 
Instances
| Functor FieldDecoder Source # | |
| Defined in Preql.Wire.FromSql Methods fmap :: (a -> b) -> FieldDecoder a -> FieldDecoder b # (<$) :: a -> FieldDecoder b -> FieldDecoder a # | |
decodeVector :: RowDecoder a -> Result -> IO (Either QueryError (Vector a)) Source #
notNull :: FieldDecoder a -> RowDecoder a Source #
nullable :: FieldDecoder a -> RowDecoder (Maybe a) Source #
fromSqlJsonField :: FromJSON a => FieldDecoder a Source #