Safe Haskell | None |
---|---|
Language | Haskell2010 |
The types in this module have invariants which cannot be checked if their constructors are in scope. Preql.Wire exports the type names only.
Synopsis
- newtype Query (n :: Nat) = Query ByteString
- data RowDecoder (n :: Nat) a = RowDecoder (Vector n PgType) (InternalDecoder a)
- pureDecoder :: a -> RowDecoder 0 a
- applyDecoder :: RowDecoder m (a -> b) -> RowDecoder n a -> RowDecoder (m + n) b
- type InternalDecoder = ReaderT (IORef DecoderState) IO
- data DecoderState = DecoderState {}
- incrementColumn :: DecoderState -> DecoderState
- incrementRow :: DecoderState -> DecoderState
- decodeRow :: IORef DecoderState -> RowDecoder n a -> Result -> IO a
- getNextValue :: InternalDecoder (Maybe ByteString)
Documentation
newtype 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.
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
RowDecoder (Vector n PgType) (InternalDecoder a) |
Instances
Functor (RowDecoder n) Source # | |
Defined in Preql.Wire.Internal fmap :: (a -> b) -> RowDecoder n a -> RowDecoder n b # (<$) :: a -> RowDecoder n b -> RowDecoder n a # |
pureDecoder :: a -> RowDecoder 0 a Source #
Analogous to pure
, pureDecoder a
returns the value a
without consuming any input from Postgres.
applyDecoder :: RowDecoder m (a -> b) -> RowDecoder n a -> RowDecoder (m + n) b Source #
Analogous to <*>
, pureDecoder Constructor
supplies two arguments to applyDecoder
a
applyDecoder
bConstructor
, from the
RowDecoder
a
and b
.
type InternalDecoder = ReaderT (IORef DecoderState) IO Source #
Internal because we need IO for the libpq FFI, but we promise not
to do any IO besides decoding. We don't even make network calls to
Postgres in InternalDecoder
data DecoderState Source #
Instances
Eq DecoderState Source # | |
Defined in Preql.Wire.Internal (==) :: DecoderState -> DecoderState -> Bool # (/=) :: DecoderState -> DecoderState -> Bool # | |
Show DecoderState Source # | |
Defined in Preql.Wire.Internal showsPrec :: Int -> DecoderState -> ShowS # show :: DecoderState -> String # showList :: [DecoderState] -> ShowS # |
decodeRow :: IORef DecoderState -> RowDecoder n a -> Result -> IO a Source #
Can throw FieldError