fix: tagOf is not instanceof

This commit is contained in:
orion 2024-05-22 15:42:43 -05:00
parent bead3d81c3
commit 7ed85ae22b
Signed by: orion
GPG Key ID: 6D4165AE4C928719
3 changed files with 17 additions and 6 deletions

View File

@ -1,5 +1,9 @@
import Pg from 'pg' import Pg from 'pg'
import Range from 'postgres-range' import Range from 'postgres-range'
import { Buffer } from 'buffer'
/** @type {(a: unknown) => boolean} */
export const isInstanceOfBuffer = a => a instanceof Buffer
export const modifyPgTypes = () => { export const modifyPgTypes = () => {
// https://github.com/brianc/node-pg-types/blob/master/lib/textParsers.js // https://github.com/brianc/node-pg-types/blob/master/lib/textParsers.js

View File

@ -3,7 +3,7 @@ module Data.Postgres where
import Prelude import Prelude
import Control.Alt ((<|>)) import Control.Alt ((<|>))
import Control.Monad.Error.Class (liftEither, liftMaybe) import Control.Monad.Error.Class (liftEither, liftMaybe, throwError)
import Control.Monad.Except (ExceptT, runExceptT) import Control.Monad.Except (ExceptT, runExceptT)
import Control.Monad.Morph (hoist) import Control.Monad.Morph (hoist)
import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Class (lift)
@ -19,7 +19,7 @@ import Data.RFC3339String as DateTime.ISO
import Data.Traversable (traverse) import Data.Traversable (traverse)
import Effect (Effect) import Effect (Effect)
import Effect.Exception (error) import Effect.Exception (error)
import Foreign (ForeignError(..), unsafeToForeign) import Foreign (ForeignError(..), tagOf, unsafeFromForeign, unsafeToForeign)
import Foreign as F import Foreign as F
import JS.BigInt (BigInt) import JS.BigInt (BigInt)
import JS.BigInt as BigInt import JS.BigInt as BigInt
@ -40,6 +40,8 @@ derive newtype instance ReadForeign a => ReadForeign (JSON a)
-- | for some types to unmarshal as strings rather than JS values. -- | for some types to unmarshal as strings rather than JS values.
foreign import modifyPgTypes :: Effect Unit foreign import modifyPgTypes :: Effect Unit
foreign import isInstanceOfBuffer :: F.Foreign -> Boolean
-- | The serialization & deserialization monad. -- | The serialization & deserialization monad.
type RepT = ExceptT (NonEmptyList ForeignError) Effect type RepT = ExceptT (NonEmptyList ForeignError) Effect
@ -142,7 +144,12 @@ instance ReadForeign a => Deserialize (JSON a) where
-- | `bytea` -- | `bytea`
instance Deserialize Buffer where instance Deserialize Buffer where
deserialize = (F.unsafeReadTagged "Buffer") <<< Raw.asForeign deserialize =
let
notBuffer a = pure $ TypeMismatch (tagOf a) "Buffer"
readBuffer a = when (not $ isInstanceOfBuffer a) (throwError $ notBuffer a) $> unsafeFromForeign a
in
readBuffer <<< Raw.asForeign
-- | `int2`, `int4` -- | `int2`, `int4`
instance Deserialize Int where instance Deserialize Int where

View File

@ -41,9 +41,9 @@ stdin q = do
pipe = Pipes.mapM releaseOnEOS >-> fromWritable (O.fromBufferWritable stream) pipe = Pipes.mapM releaseOnEOS >-> fromWritable (O.fromBufferWritable stream)
err e = do err e = do
liftAff $ void $ Client.exec "rollback" client liftAff $ void $ Client.exec "rollback" client
liftEffect $ Pool.release pool client liftEffect $ Pool.release pool client
throwError e throwError e
catchError pipe err catchError pipe err