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 {}
- newtype Tuple r = Tuple r
- data UnlocatedFieldError
- data FieldError = FieldError {}
- data PgType
- data TypeMismatch = TypeMismatch {}
- data QueryError
- data RowDecoder (n :: Nat) a
- data Query (n :: Nat)
- 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)
- fieldParser :: FieldDecoder a -> BinaryParser a
- notNull :: FieldDecoder a -> RowDecoder 1 a
- nullable :: FieldDecoder a -> RowDecoder 1 (Maybe a)
- throwLocated :: UnlocatedFieldError -> InternalDecoder a
- newtype Composite a = Composite (BinaryParser a)
- newtype Tuple r = Tuple r
- composite :: Int -> Composite a -> BinaryParser a
- valueComposite :: FieldDecoder a -> Composite a
- intOfSize :: (Integral a, Bits a) => Int -> BinaryParser a
- onContent :: BinaryParser a -> BinaryParser (Maybe 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
- fromSqlJsonField :: FromJSON a => FieldDecoder a
- data IsolationLevel
- data Connection
- decodeVector :: KnownNat n => Connection -> RowDecoder n a -> Result -> IO (Either QueryError (Vector a))
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. This is convenient when you define your
own Postgres types, since they should be instances of both type classes.
Minimal complete definition
Nothing
Methods
fromSql :: RowDecoder (Width a) a Source #
default fromSql :: (FromSqlField a, Width a ~ 1) => RowDecoder (Width a) a Source #
Instances
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
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 |
Wrapper for Postgres anonymous row types (sometimes called record types), so instance resolution picks the right decoder. The useful instances are for (Haskell) tuples. Postgres allows row types with a single field, but the instances would overlap with those for nested row types, so we do not provide them.
Constructors
Tuple r |
Instances
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 Oid | A Postgres type with a known ID, and the matching array 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.
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. This is convenient when you define your
own Postgres types, since they should be instances of both type classes.
Minimal complete definition
Nothing
Methods
fromSql :: RowDecoder (Width a) a Source #
default fromSql :: (FromSqlField a, Width a ~ 1) => RowDecoder (Width a) a Source #
Instances
class FromSqlField a where 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
.
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 # |
fieldParser :: FieldDecoder a -> BinaryParser a Source #
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.
Helper for decoding composites
Constructors
Composite (BinaryParser a) |
Wrapper for Postgres anonymous row types (sometimes called record types), so instance resolution picks the right decoder. The useful instances are for (Haskell) tuples. Postgres allows row types with a single field, but the instances would overlap with those for nested row types, so we do not provide them.
Constructors
Tuple r |
Instances
valueComposite :: FieldDecoder a -> Composite a Source #
onContent :: BinaryParser a -> BinaryParser (Maybe a) Source #
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 #
fromSqlJsonField :: FromJSON a => FieldDecoder a Source #
data IsolationLevel Source #
Constructors
ReadCommitted | |
RepeatableRead | |
Serializable |
Instances
data Connection Source #
We make the type cache part of the Connection to offer the option of
per-Connection (or striped) caches. It's also reasonable to share a single
cache for an entire multi-threaded program; the IORef
supports this usage.
Instances
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 |
Defined in Preql.Effect Methods runTransaction' :: IsolationLevel -> Transaction a -> ReaderT Connection IO a Source # withConnection :: (Connection -> ReaderT Connection IO a) -> ReaderT Connection IO a Source # queryOn :: (ToSql p, FromSql r, KnownNat (Width r)) => Connection -> (Query (Width r), p) -> ReaderT Connection IO (Vector r) Source # queryOn_ :: ToSql p => Connection -> (Query 0, p) -> ReaderT Connection IO () Source # |
decodeVector :: KnownNat n => Connection -> RowDecoder n a -> Result -> IO (Either QueryError (Vector a)) Source #