mirror of
https://github.com/nikita-volkov/hasql.git
synced 2024-11-22 10:05:27 +03:00
Get rid of the decidable instance
This commit is contained in:
commit
7d4a3b14f4
@ -1,3 +1,7 @@
|
|||||||
|
# 1.7
|
||||||
|
|
||||||
|
- Decidable instance on `Encoders.Params` removed. It was useless and limited the design.
|
||||||
|
|
||||||
# 1.6.3.1
|
# 1.6.3.1
|
||||||
|
|
||||||
- Moved to "postgresql-libpq-0.10"
|
- Moved to "postgresql-libpq-0.10"
|
||||||
|
@ -61,7 +61,7 @@ import Text.Builder qualified as C
|
|||||||
-- Female -> "female"
|
-- Female -> "female"
|
||||||
-- @
|
-- @
|
||||||
newtype Params a = Params (Params.Params a)
|
newtype Params a = Params (Params.Params a)
|
||||||
deriving (Contravariant, Divisible, Decidable, Monoid, Semigroup)
|
deriving (Contravariant, Divisible, Monoid, Semigroup)
|
||||||
|
|
||||||
-- |
|
-- |
|
||||||
-- No parameters. Same as `mempty` and `conquered`.
|
-- No parameters. Same as `mempty` and `conquered`.
|
||||||
|
@ -9,23 +9,70 @@ import Text.Builder qualified as E
|
|||||||
|
|
||||||
-- |
|
-- |
|
||||||
-- Encoder of some representation of a parameters product.
|
-- Encoder of some representation of a parameters product.
|
||||||
newtype Params a
|
data Params a = Params
|
||||||
= Params (Op (DList (A.Oid, A.Format, Bool -> Maybe ByteString, Text)) a)
|
{ size :: !Int,
|
||||||
deriving (Contravariant, Divisible, Decidable, Semigroup, Monoid)
|
columnsMetadata :: !(DList (A.Oid, A.Format)),
|
||||||
|
serializer :: Bool -> a -> DList (Maybe ByteString),
|
||||||
|
printer :: a -> DList Text
|
||||||
|
}
|
||||||
|
|
||||||
|
instance Contravariant Params where
|
||||||
|
contramap fn (Params size columnsMetadata oldSerializer oldPrinter) = Params {..}
|
||||||
|
where
|
||||||
|
serializer idt = oldSerializer idt . fn
|
||||||
|
printer = oldPrinter . fn
|
||||||
|
|
||||||
|
instance Divisible Params where
|
||||||
|
divide
|
||||||
|
divisor
|
||||||
|
(Params leftSize leftColumnsMetadata leftSerializer leftPrinter)
|
||||||
|
(Params rightSize rightColumnsMetadata rightSerializer rightPrinter) =
|
||||||
|
Params
|
||||||
|
{ size = leftSize + rightSize,
|
||||||
|
columnsMetadata = leftColumnsMetadata <> rightColumnsMetadata,
|
||||||
|
serializer = \idt input -> case divisor input of
|
||||||
|
(leftInput, rightInput) -> leftSerializer idt leftInput <> rightSerializer idt rightInput,
|
||||||
|
printer = \input -> case divisor input of
|
||||||
|
(leftInput, rightInput) -> leftPrinter leftInput <> rightPrinter rightInput
|
||||||
|
}
|
||||||
|
conquer =
|
||||||
|
Params
|
||||||
|
{ size = 0,
|
||||||
|
columnsMetadata = mempty,
|
||||||
|
serializer = mempty,
|
||||||
|
printer = mempty
|
||||||
|
}
|
||||||
|
|
||||||
|
instance Semigroup (Params a) where
|
||||||
|
Params leftSize leftColumnsMetadata leftSerializer leftPrinter <> Params rightSize rightColumnsMetadata rightSerializer rightPrinter =
|
||||||
|
Params
|
||||||
|
{ size = leftSize + rightSize,
|
||||||
|
columnsMetadata = leftColumnsMetadata <> rightColumnsMetadata,
|
||||||
|
serializer = \idt input -> leftSerializer idt input <> rightSerializer idt input,
|
||||||
|
printer = \input -> leftPrinter input <> rightPrinter input
|
||||||
|
}
|
||||||
|
|
||||||
|
instance Monoid (Params a) where
|
||||||
|
mempty = conquer
|
||||||
|
|
||||||
value :: C.Value a -> Params a
|
value :: C.Value a -> Params a
|
||||||
value =
|
value (C.Value valueOID _ serialize print) =
|
||||||
contramap Just . nullableValue
|
Params
|
||||||
|
{ size = 1,
|
||||||
|
columnsMetadata = pure (pqOid, format),
|
||||||
|
serializer = \idt -> pure . Just . B.encodingBytes . serialize idt,
|
||||||
|
printer = pure . E.run . print
|
||||||
|
}
|
||||||
|
where
|
||||||
|
D.OID _ pqOid format = valueOID
|
||||||
|
|
||||||
nullableValue :: C.Value a -> Params (Maybe a)
|
nullableValue :: C.Value a -> Params (Maybe a)
|
||||||
nullableValue (C.Value valueOID arrayOID encode render) =
|
nullableValue (C.Value valueOID _ serialize print) =
|
||||||
Params
|
Params
|
||||||
$ Op
|
{ size = 1,
|
||||||
$ \input ->
|
columnsMetadata = pure (pqOid, format),
|
||||||
let D.OID _ pqOid format =
|
serializer = \idt -> pure . fmap (B.encodingBytes . serialize idt),
|
||||||
valueOID
|
printer = pure . maybe "null" (E.run . print)
|
||||||
encoder env =
|
}
|
||||||
fmap (B.encodingBytes . encode env) input
|
where
|
||||||
rendering =
|
D.OID _ pqOid format = valueOID
|
||||||
maybe "null" (E.run . render) input
|
|
||||||
in pure (pqOid, format, encoder, rendering)
|
|
||||||
|
@ -114,16 +114,17 @@ sendPreparedParametricStatement ::
|
|||||||
ParamsEncoders.Params a ->
|
ParamsEncoders.Params a ->
|
||||||
a ->
|
a ->
|
||||||
IO (Either CommandError ())
|
IO (Either CommandError ())
|
||||||
sendPreparedParametricStatement connection registry integerDatetimes template (ParamsEncoders.Params (Op encoderOp)) input =
|
sendPreparedParametricStatement connection registry integerDatetimes template (ParamsEncoders.Params size columnsMetadata serializer _) input =
|
||||||
let (oidList, valueAndFormatList) =
|
runExceptT $ do
|
||||||
let step (oid, format, encoder, _) ~(oidList, bytesAndFormatList) =
|
key <- ExceptT $ getPreparedStatementKey connection registry template oidList
|
||||||
(,)
|
ExceptT $ checkedSend connection $ LibPQ.sendQueryPrepared connection key valueAndFormatList LibPQ.Binary
|
||||||
(oid : oidList)
|
where
|
||||||
(fmap (\bytes -> (bytes, format)) (encoder integerDatetimes) : bytesAndFormatList)
|
(oidList, formatList) =
|
||||||
in foldr step ([], []) (encoderOp input)
|
columnsMetadata & toList & unzip
|
||||||
in runExceptT $ do
|
valueAndFormatList =
|
||||||
key <- ExceptT $ getPreparedStatementKey connection registry template oidList
|
serializer integerDatetimes input
|
||||||
ExceptT $ checkedSend connection $ LibPQ.sendQueryPrepared connection key valueAndFormatList LibPQ.Binary
|
& toList
|
||||||
|
& zipWith (\format encoding -> (,format) <$> encoding) formatList
|
||||||
|
|
||||||
{-# INLINE sendUnpreparedParametricStatement #-}
|
{-# INLINE sendUnpreparedParametricStatement #-}
|
||||||
sendUnpreparedParametricStatement ::
|
sendUnpreparedParametricStatement ::
|
||||||
@ -133,11 +134,14 @@ sendUnpreparedParametricStatement ::
|
|||||||
ParamsEncoders.Params a ->
|
ParamsEncoders.Params a ->
|
||||||
a ->
|
a ->
|
||||||
IO (Either CommandError ())
|
IO (Either CommandError ())
|
||||||
sendUnpreparedParametricStatement connection integerDatetimes template (ParamsEncoders.Params (Op encoderOp)) input =
|
sendUnpreparedParametricStatement connection integerDatetimes template (ParamsEncoders.Params _ columnsMetadata serializer printer) input =
|
||||||
let params =
|
let params =
|
||||||
let step (oid, format, encoder, _) acc =
|
zipWith
|
||||||
((,,) <$> pure oid <*> encoder integerDatetimes <*> pure format) : acc
|
( \(oid, format) encoding ->
|
||||||
in foldr step [] (encoderOp input)
|
(,,) <$> pure oid <*> encoding <*> pure format
|
||||||
|
)
|
||||||
|
(toList columnsMetadata)
|
||||||
|
(toList (serializer integerDatetimes input))
|
||||||
in checkedSend connection $ LibPQ.sendQueryParams connection template params LibPQ.Binary
|
in checkedSend connection $ LibPQ.sendQueryParams connection template params LibPQ.Binary
|
||||||
|
|
||||||
{-# INLINE sendParametricStatement #-}
|
{-# INLINE sendParametricStatement #-}
|
||||||
|
@ -46,7 +46,7 @@ sql sql =
|
|||||||
-- |
|
-- |
|
||||||
-- Parameters and a specification of a parametric single-statement query to apply them to.
|
-- Parameters and a specification of a parametric single-statement query to apply them to.
|
||||||
statement :: params -> Statement.Statement params result -> Session result
|
statement :: params -> Statement.Statement params result -> Session result
|
||||||
statement input (Statement.Statement template (Encoders.Params paramsEncoder) decoder preparable) =
|
statement input (Statement.Statement template (Encoders.Params paramsEncoder@(Encoders.Params.Params _ _ _ printer)) decoder preparable) =
|
||||||
Session
|
Session
|
||||||
$ ReaderT
|
$ ReaderT
|
||||||
$ \(Connection.Connection pqConnectionRef integerDatetimes registry) ->
|
$ \(Connection.Connection pqConnectionRef integerDatetimes registry) ->
|
||||||
@ -59,7 +59,5 @@ statement input (Statement.Statement template (Encoders.Params paramsEncoder) de
|
|||||||
return $ r1 *> r2
|
return $ r1 *> r2
|
||||||
where
|
where
|
||||||
inputReps =
|
inputReps =
|
||||||
let Encoders.Params.Params (Op encoderOp) = paramsEncoder
|
printer input
|
||||||
step (_, _, _, rendering) acc =
|
& toList
|
||||||
rendering : acc
|
|
||||||
in foldr step [] (encoderOp input)
|
|
||||||
|
@ -372,32 +372,6 @@ tree =
|
|||||||
Encoders.param (Encoders.nonNullable (Encoders.unknown))
|
Encoders.param (Encoders.nonNullable (Encoders.unknown))
|
||||||
in Session.statement "ok" statement
|
in Session.statement "ok" statement
|
||||||
in actualIO >>= assertEqual "" (Right True),
|
in actualIO >>= assertEqual "" (Right True),
|
||||||
testCase "Textual Unknown"
|
|
||||||
$ let actualIO =
|
|
||||||
Session.runSessionOnLocalDb $ do
|
|
||||||
let statement =
|
|
||||||
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 Session.statement () statement
|
|
||||||
let statement =
|
|
||||||
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;"
|
|
||||||
in Session.statement () statement
|
|
||||||
let statement =
|
|
||||||
Statement.Statement sql encoder decoder True
|
|
||||||
where
|
|
||||||
sql =
|
|
||||||
"select overloaded($1, $2) || overloaded($3, $4, $5)"
|
|
||||||
decoder =
|
|
||||||
(Decoders.singleRow ((Decoders.column . Decoders.nonNullable) (Decoders.text)))
|
|
||||||
encoder =
|
|
||||||
contramany (Encoders.param (Encoders.nonNullable (Encoders.unknown)))
|
|
||||||
in Session.statement ["1", "2", "4", "5", "6"] statement
|
|
||||||
in actualIO >>= assertEqual "" (Right "3456"),
|
|
||||||
testCase "Enum"
|
testCase "Enum"
|
||||||
$ let actualIO =
|
$ let actualIO =
|
||||||
Session.runSessionOnLocalDb $ do
|
Session.runSessionOnLocalDb $ do
|
||||||
|
Loading…
Reference in New Issue
Block a user