Rename unit to noResult

This commit is contained in:
Nikita Volkov 2019-05-21 13:25:22 +03:00
parent 8f78014876
commit db4261ddb5
10 changed files with 20 additions and 20 deletions

View File

@ -5,7 +5,7 @@ module Hasql.Decoders
(
-- * Result
Result,
unit,
noResult,
rowsAffected,
singleRow,
-- ** Specialized multi-row results

View File

@ -29,9 +29,9 @@ Decode no value from the result.
Useful for statements like @INSERT@ or @CREATE@.
-}
{-# INLINABLE unit #-}
unit :: Result ()
unit = Result (Results.single Result.unit)
{-# INLINABLE noResult #-}
noResult :: Result ()
noResult = Result (Results.single Result.noResult)
{-|
Get the amount of rows affected by such statements as

View File

@ -20,9 +20,9 @@ run :: Result a -> (Bool, LibPQ.Result) -> IO (Either ResultError a)
run (Result reader) env =
runExceptT (runReaderT reader env)
{-# INLINE unit #-}
unit :: Result ()
unit =
{-# INLINE noResult #-}
noResult :: Result ()
noResult =
checkExecStatus $ \case
LibPQ.CommandOk -> True
LibPQ.TuplesOk -> True

View File

@ -81,4 +81,4 @@ dropRemainders =
loop integerDatetimes connection <* checkErrors
where
checkErrors =
ExceptT $ fmap (mapLeft ResultError) $ Result.run Result.unit (integerDatetimes, result)
ExceptT $ fmap (mapLeft ResultError) $ Result.run Result.noResult (integerDatetimes, result)

View File

@ -88,7 +88,7 @@ getPreparedStatementKey connection registry template oidList =
sent <- LibPQ.sendPrepare connection key template (mfilter (not . null) (Just oidList))
let resultsDecoder =
if sent
then ResultsDecoders.single ResultDecoders.unit
then ResultsDecoders.single ResultDecoders.noResult
else ResultsDecoders.clientError
fmap resultsMapping $ getResults connection undefined resultsDecoder
where

View File

@ -40,7 +40,7 @@ sql sql =
return $ r1 *> r2
where
decoder =
Decoders.Results.single Decoders.Result.unit
Decoders.Results.single Decoders.Result.noResult
-- |
-- Parameters and a specification of a parametric single-statement query to apply them to.

View File

@ -25,7 +25,7 @@ module Hasql.Statement
-- Encoders.'Encoders.foldableDimension' .
-- Encoders.'Encoders.element' .
-- Encoders.'Encoders.nonNullable'
-- decoder = Decoders.'Decoders.unit'
-- decoder = Decoders.'Decoders.noResult'
-- @
--
-- This approach is much more efficient than executing a single-row Insert

View File

@ -184,7 +184,7 @@ tree =
encoder =
mempty
decoder =
Decoders.unit
Decoders.noResult
in io
,
testCase "Prepared statements after error" $
@ -319,14 +319,14 @@ tree =
DSL.session $ do
let
statement =
Statement.Statement sql mempty Decoders.unit True
Statement.Statement sql mempty Decoders.noResult True
where
sql =
"drop type if exists mood"
in DSL.statement () statement
let
statement =
Statement.Statement sql mempty Decoders.unit True
Statement.Statement sql mempty Decoders.noResult True
where
sql =
"create type mood as enum ('sad', 'ok', 'happy')"
@ -350,14 +350,14 @@ tree =
DSL.session $ do
let
statement =
Statement.Statement sql mempty Decoders.unit True
Statement.Statement sql mempty Decoders.noResult True
where
sql =
"create or replace function overloaded(a int, b int) returns int as $$ select a + b $$ language sql;"
in DSL.statement () statement
let
statement =
Statement.Statement sql mempty Decoders.unit True
Statement.Statement sql mempty Decoders.noResult True
where
sql =
"create or replace function overloaded(a text, b text, c text) returns text as $$ select a || b || c $$ language sql;"
@ -381,14 +381,14 @@ tree =
DSL.session $ do
let
statement =
Statement.Statement sql mempty Decoders.unit True
Statement.Statement sql mempty Decoders.noResult True
where
sql =
"drop type if exists mood"
in DSL.statement () statement
let
statement =
Statement.Statement sql mempty Decoders.unit True
Statement.Statement sql mempty Decoders.noResult True
where
sql =
"create type mood as enum ('sad', 'ok', 'happy')"

View File

@ -9,7 +9,7 @@ import qualified Main.Prelude as Prelude
plain :: ByteString -> HQ.Statement () ()
plain sql =
HQ.Statement sql mempty HD.unit False
HQ.Statement sql mempty HD.noResult False
dropType :: ByteString -> HQ.Statement () ()
dropType name =

View File

@ -15,6 +15,6 @@ selectSleep =
encoder =
E.param (E.nonNullable E.float8)
decoder =
D.unit
D.noResult