This commit is contained in:
Nikita Volkov 2022-09-25 15:27:40 +03:00
parent 9e57753e33
commit 75ffa3f13c
5 changed files with 0 additions and 32 deletions

View File

@ -31,8 +31,6 @@ main =
-- * Sessions
-------------------------
sessionWithManySmallParameters :: Vector (Int64, Int64) -> B.Session ()
sessionWithManySmallParameters =
error "TODO: sessionWithManySmallParameters"
@ -55,8 +53,6 @@ sessionWithManySmallResults =
-- * Statements
-------------------------
statementWithManyParameters :: C.Statement (Vector (Int64, Int64)) ()
statementWithManyParameters =
error "TODO: statementWithManyParameters"

View File

@ -19,8 +19,6 @@ import qualified PostgreSQL.Binary.Decoding as A
-- * Result
-------------------------
-- |
-- Decoder of a query result.
newtype Result a = Result (Results.Results a) deriving (Functor)
@ -52,8 +50,6 @@ refineResult refiner (Result results) = Result (Results.refine refiner results)
-- ** Multi-row traversers
-------------------------
-- |
-- Foldl multiple rows.
{-# INLINEABLE foldlRows #-}
@ -68,8 +64,6 @@ foldrRows step init (Row row) = Result (Results.single (Result.foldr step init r
-- ** Specialized multi-row results
-------------------------
-- |
-- Maybe one row or none.
{-# INLINEABLE rowMaybe #-}
@ -93,8 +87,6 @@ rowList = foldrRows strictCons []
-- * Row
-------------------------
-- |
-- Decoder of an individual row,
-- which gets composed of column value decoders.
@ -118,8 +110,6 @@ column = \case
-- * Nullability
-------------------------
-- |
-- Extensional specification of nullability over a generic decoder.
data NullableOrNot decoder a where
@ -138,8 +128,6 @@ nullable = Nullable
-- * Value
-------------------------
-- |
-- Decoder of a value.
newtype Value a = Value (Value.Value a)
@ -371,8 +359,6 @@ composite (Composite imp) = Value (Value.decoder (Composite.run imp))
-- * Array decoders
-------------------------
-- |
-- A generic array decoder.
--
@ -410,8 +396,6 @@ element = \case
-- * Composite decoders
-------------------------
-- |
-- Composable decoder of composite values (rows, records).
newtype Composite a = Composite (Composite.Composite a)

View File

@ -18,8 +18,6 @@ data Env
-- * Functions
-------------------------
{-# INLINE run #-}
run :: Row a -> (LibPQ.Result, LibPQ.Row, LibPQ.Column, Bool) -> IO (Either (Int, RowError) a)
run (Row impl) (result, row, columnsAmount, integerDatetimes) =

View File

@ -16,8 +16,6 @@ import qualified Text.Builder as C
-- * Parameters Product Encoder
-------------------------
-- |
-- Encoder of some representation of a parameters product.
--
@ -80,8 +78,6 @@ param = \case
-- * Nullability
-------------------------
-- |
-- Extensional specification of nullability over a generic encoder.
data NullableOrNot encoder a where
@ -100,8 +96,6 @@ nullable = Nullable
-- * Value
-------------------------
-- |
-- Value encoder.
newtype Value a = Value (Value.Value a)
@ -308,8 +302,6 @@ foldableArray = array . dimension foldl' . element
-- * Array
-------------------------
-- |
-- Generic array encoder.
--

View File

@ -19,8 +19,6 @@ mkPTI format oid arrayOID =
-- * Constants
-------------------------
abstime = mkPTI LibPQ.Binary 702 (Just 1023)
aclitem = mkPTI LibPQ.Binary 1033 (Just 1034)