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 where
- type Width a :: Nat
- fromSql :: RowDecoder (Width a) a
- class FromSqlField a
- class ToSql a where
- toSql :: RowEncoder a
- class ToSqlField a
- data QueryError
- data FieldError = FieldError {}
- data UnlocatedFieldError
- data TypeMismatch = TypeMismatch {}
- data UnlocatedFieldError
- data FieldError = FieldError {}
- data PgType
- data TypeMismatch = TypeMismatch {}
- data QueryError
- data RowDecoder (n :: Nat) a
- data Query (n :: Nat)
- decodeVector :: KnownNat n => (PgType -> IO (Either QueryError Oid)) -> RowDecoder n a -> Result -> IO (Either QueryError (Vector a))
- class FromSql a where
- type Width a :: Nat
- fromSql :: RowDecoder (Width a) a
- class FromSqlField a where
- fromSqlField :: FieldDecoder a
- data FieldDecoder a = FieldDecoder PgType (BinaryParser a)
- notNull :: FieldDecoder a -> RowDecoder 1 a
- nullable :: FieldDecoder a -> RowDecoder 1 (Maybe a)
- throwLocated :: UnlocatedFieldError -> InternalDecoder a
- newtype PgName = PgName Text
- 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
- data IsolationLevel
Decoding rows
class FromSql a where 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
Minimal complete definition
Nothing
Methods
fromSql :: RowDecoder (Width a) a Source #
default fromSql :: (FromSqlField a, Width a ~ 1) => RowDecoder (Width a) a Source #
Instances
FromSql Bool Source # | |
FromSql Char Source # | |
FromSql Double Source # | |
FromSql Float Source # | |
FromSql Int16 Source # | |
FromSql Int32 Source # | |
FromSql Int64 Source # | |
FromSql ByteString Source # | |
Defined in Preql.FromSql.Instances Associated Types type Width ByteString :: Nat Source # Methods fromSql :: RowDecoder (Width ByteString) ByteString Source # | |
FromSql ByteString Source # | |
Defined in Preql.FromSql.Instances Associated Types type Width ByteString :: Nat Source # Methods fromSql :: RowDecoder (Width ByteString) ByteString Source # | |
FromSql String Source # | |
FromSql Text Source # | |
FromSql UTCTime Source # | |
FromSql Value Source # | |
FromSql Text Source # | |
FromSql UUID Source # | |
FromSql Day Source # | |
FromSql TimeOfDay Source # | |
FromSql Oid Source # | |
FromSql PgName Source # | |
FromSql TimeTZ Source # | |
FromSqlField a => FromSql (Maybe a) Source # | |
(FromSql a, FromSql b) => FromSql (a, b) Source # | |
Defined in Preql.FromSql.Instances Methods fromSql :: RowDecoder (Width (a, b)) (a, b) Source # | |
(FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 #
Minimal complete definition
Instances
Encoding parameters
ToSql a
is sufficient to pass a
as parameters to a paramaterized query.
Methods
toSql :: RowEncoder a Source #
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 # |
Constructors
Oid Oid | A Postgres type with a known ID |
TypeName Text | A Postgres type which we will need to lookup by name |
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 (n :: Nat) a Source #
RowDecoder
is Functor
but not Monad
so that we can index
the type by the number of columns that it consumes. We also know &
verify all of the OIDs before we read any of the field data sent by
Postgres, which would admit an Applicative
instance but not Monad
Instances
Functor (RowDecoder n) Source # | |
Defined in Preql.Wire.Internal Methods fmap :: (a -> b) -> RowDecoder n a -> RowDecoder n b # (<$) :: a -> RowDecoder n b -> RowDecoder n a # |
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.
decodeVector :: KnownNat n => (PgType -> IO (Either QueryError Oid)) -> RowDecoder n a -> Result -> IO (Either QueryError (Vector a)) Source #
class FromSql a where 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
Minimal complete definition
Nothing
Methods
fromSql :: RowDecoder (Width a) a Source #
default fromSql :: (FromSqlField a, Width a ~ 1) => RowDecoder (Width a) a Source #
Instances
FromSql Bool Source # | |
FromSql Char Source # | |
FromSql Double Source # | |
FromSql Float Source # | |
FromSql Int16 Source # | |
FromSql Int32 Source # | |
FromSql Int64 Source # | |
FromSql ByteString Source # | |
Defined in Preql.FromSql.Instances Associated Types type Width ByteString :: Nat Source # Methods fromSql :: RowDecoder (Width ByteString) ByteString Source # | |
FromSql ByteString Source # | |
Defined in Preql.FromSql.Instances Associated Types type Width ByteString :: Nat Source # Methods fromSql :: RowDecoder (Width ByteString) ByteString Source # | |
FromSql String Source # | |
FromSql Text Source # | |
FromSql UTCTime Source # | |
FromSql Value Source # | |
FromSql Text Source # | |
FromSql UUID Source # | |
FromSql Day Source # | |
FromSql TimeOfDay Source # | |
FromSql Oid Source # | |
FromSql PgName Source # | |
FromSql TimeTZ Source # | |
FromSqlField a => FromSql (Maybe a) Source # | |
(FromSql a, FromSql b) => FromSql (a, b) Source # | |
Defined in Preql.FromSql.Instances Methods fromSql :: RowDecoder (Width (a, b)) (a, b) Source # | |
(FromSql a, FromSql b, FromSql c) => FromSql (a, b, c) Source # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
Defined in Preql.FromSql.Instances 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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 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 PgType (BinaryParser a) |
Instances
Functor FieldDecoder Source # | |
Defined in Preql.FromSql.Class Methods fmap :: (a -> b) -> FieldDecoder a -> FieldDecoder b # (<$) :: a -> FieldDecoder b -> FieldDecoder a # |
notNull :: FieldDecoder a -> RowDecoder 1 a Source #
Construct a decoder for a single non-nullable column.
nullable :: FieldDecoder a -> RowDecoder 1 (Maybe a) Source #
Construct a decoder for a single nullable column.
Instances
Eq TimeTZ Source # | |
Show TimeTZ Source # | |
FromSql TimeTZ Source # | |
FromSqlField TimeTZ Source # | |
Defined in Preql.FromSql.Instances Methods | |
ToSql TimeTZ Source # | |
Defined in Preql.Wire.ToSql Methods toSql :: RowEncoder TimeTZ Source # | |
ToSqlField TimeTZ Source # | |
Defined in Preql.Wire.ToSql Methods | |
type Width TimeTZ Source # | |
Defined in Preql.FromSql.Instances |
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 #
data IsolationLevel Source #
Constructors
ReadCommitted | |
RepeatableRead | |
Serializable |