generated from tpl/purs
feat: int8 support
This commit is contained in:
parent
f8e31d1d67
commit
1fe1639265
@ -20,6 +20,7 @@ package:
|
|||||||
- "foreign-object"
|
- "foreign-object"
|
||||||
- "identity"
|
- "identity"
|
||||||
- "integers"
|
- "integers"
|
||||||
|
- js-bigints
|
||||||
- "js-date"
|
- "js-date"
|
||||||
- "lists"
|
- "lists"
|
||||||
- "maybe"
|
- "maybe"
|
||||||
|
@ -6,11 +6,10 @@ module Database.PostgreSQL.Value where
|
|||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Control.Monad.Error.Class (throwError)
|
import Control.Monad.Error.Class (liftMaybe, throwError)
|
||||||
import Control.Monad.Except (ExceptT, except, runExcept, runExceptT)
|
import Control.Monad.Except (ExceptT, except, runExcept, runExceptT)
|
||||||
import Data.Argonaut (Json)
|
import Data.Argonaut (Json)
|
||||||
import Data.Argonaut (stringify) as Argonaut
|
import Data.Argonaut (stringify) as Argonaut
|
||||||
import Data.Foldable (foldl)
|
|
||||||
import Data.Array as Array
|
import Data.Array as Array
|
||||||
import Data.Bifunctor (lmap)
|
import Data.Bifunctor (lmap)
|
||||||
import Data.ByteString (ByteString)
|
import Data.ByteString (ByteString)
|
||||||
@ -20,6 +19,7 @@ import Data.Decimal (Decimal)
|
|||||||
import Data.Decimal as Decimal
|
import Data.Decimal as Decimal
|
||||||
import Data.Either (Either(..), note)
|
import Data.Either (Either(..), note)
|
||||||
import Data.Enum (fromEnum, toEnum)
|
import Data.Enum (fromEnum, toEnum)
|
||||||
|
import Data.Foldable (foldl)
|
||||||
import Data.Identity (Identity)
|
import Data.Identity (Identity)
|
||||||
import Data.Int (fromString)
|
import Data.Int (fromString)
|
||||||
import Data.JSDate (JSDate)
|
import Data.JSDate (JSDate)
|
||||||
@ -34,6 +34,8 @@ import Data.Traversable (sequence, traverse)
|
|||||||
import Foreign (Foreign, ForeignError(..), MultipleErrors, isNull, readArray, readBoolean, readChar, readInt, readNumber, readString, renderForeignError, unsafeFromForeign, unsafeToForeign)
|
import Foreign (Foreign, ForeignError(..), MultipleErrors, isNull, readArray, readBoolean, readChar, readInt, readNumber, readString, renderForeignError, unsafeFromForeign, unsafeToForeign)
|
||||||
import Foreign.Generic.Internal (readObject)
|
import Foreign.Generic.Internal (readObject)
|
||||||
import Foreign.Object (Object)
|
import Foreign.Object (Object)
|
||||||
|
import JS.BigInt (BigInt)
|
||||||
|
import JS.BigInt as BigInt
|
||||||
|
|
||||||
-- | Convert things to SQL values.
|
-- | Convert things to SQL values.
|
||||||
class ToSQLValue a where
|
class ToSQLValue a where
|
||||||
@ -49,6 +51,13 @@ instance fromSQLValueBoolean :: FromSQLValue Boolean where
|
|||||||
else instance fromSQLValueChar :: FromSQLValue Char where
|
else instance fromSQLValueChar :: FromSQLValue Char where
|
||||||
fromSQLValue = lmap show <<< runExcept <<< readChar
|
fromSQLValue = lmap show <<< runExcept <<< readChar
|
||||||
|
|
||||||
|
else instance fromSQLValueBigInt :: FromSQLValue BigInt where
|
||||||
|
fromSQLValue =
|
||||||
|
lmap show
|
||||||
|
<<< runExcept
|
||||||
|
<<< flip bind (\s -> liftMaybe (pure $ ForeignError $ "invalid bigint: " <> s) $ BigInt.fromString s)
|
||||||
|
<<< readString
|
||||||
|
|
||||||
else instance fromSQLValueInt :: FromSQLValue Int where
|
else instance fromSQLValueInt :: FromSQLValue Int where
|
||||||
fromSQLValue = lmap show <<< runExcept <<< readInt
|
fromSQLValue = lmap show <<< runExcept <<< readInt
|
||||||
|
|
||||||
@ -130,6 +139,9 @@ instance toSQLValueBoolean :: ToSQLValue Boolean where
|
|||||||
else instance toSQLValueChar :: ToSQLValue Char where
|
else instance toSQLValueChar :: ToSQLValue Char where
|
||||||
toSQLValue = unsafeToForeign
|
toSQLValue = unsafeToForeign
|
||||||
|
|
||||||
|
else instance toSQLValueBigInt :: ToSQLValue BigInt where
|
||||||
|
toSQLValue = unsafeToForeign <<< BigInt.toString
|
||||||
|
|
||||||
else instance toSQLValueInt :: ToSQLValue Int where
|
else instance toSQLValueInt :: ToSQLValue Int where
|
||||||
toSQLValue = unsafeToForeign
|
toSQLValue = unsafeToForeign
|
||||||
|
|
||||||
|
@ -23,7 +23,7 @@ import Data.Newtype (unwrap)
|
|||||||
import Data.Number ((%))
|
import Data.Number ((%))
|
||||||
import Data.Tuple (Tuple(..))
|
import Data.Tuple (Tuple(..))
|
||||||
import Data.Tuple.Nested ((/\))
|
import Data.Tuple.Nested ((/\))
|
||||||
import Database.PostgreSQL (Client, Configuration, Connection(..), PGConnectionURI, PGError(..), Pool, Query(Query), Row0(Row0), Row1(Row1), Row2(Row2), Row3(Row3), Row9(Row9), fromClient, fromPool, parseURI)
|
import Database.PostgreSQL (Client, Configuration, Connection(..), PGConnectionURI, PGError(..), Pool, Query(Query), Row0(Row0), Row1(Row1), Row12(..), Row2(Row2), Row3(Row3), Row9(Row9), fromClient, fromPool, parseURI)
|
||||||
import Database.PostgreSQL.PG (command, execute, onIntegrityError, query, scalar)
|
import Database.PostgreSQL.PG (command, execute, onIntegrityError, query, scalar)
|
||||||
import Database.PostgreSQL.PG (withClient, withClientTransaction) as PG
|
import Database.PostgreSQL.PG (withClient, withClientTransaction) as PG
|
||||||
import Database.PostgreSQL.Pool (new) as Pool
|
import Database.PostgreSQL.Pool (new) as Pool
|
||||||
@ -34,6 +34,8 @@ import Effect.Class (liftEffect)
|
|||||||
import Effect.Exception (message)
|
import Effect.Exception (message)
|
||||||
import Foreign.Object (Object)
|
import Foreign.Object (Object)
|
||||||
import Foreign.Object (fromFoldable) as Object
|
import Foreign.Object (fromFoldable) as Object
|
||||||
|
import JS.BigInt (BigInt)
|
||||||
|
import JS.BigInt as BigInt
|
||||||
import JS.Unsafe.Stringify (unsafeStringify)
|
import JS.Unsafe.Stringify (unsafeStringify)
|
||||||
import Partial.Unsafe (unsafePartial)
|
import Partial.Unsafe (unsafePartial)
|
||||||
import Test.Assert (assert)
|
import Test.Assert (assert)
|
||||||
@ -45,6 +47,9 @@ import Test.Unit as Test.Unit
|
|||||||
import Test.Unit.Assert (equal)
|
import Test.Unit.Assert (equal)
|
||||||
import Test.Unit.Main (runTest)
|
import Test.Unit.Main (runTest)
|
||||||
|
|
||||||
|
bigintFromString :: String -> BigInt
|
||||||
|
bigintFromString = unsafePartial fromJust <<< BigInt.fromString
|
||||||
|
|
||||||
withClient :: forall a. Pool -> (Client -> AppM a) -> AppM a
|
withClient :: forall a. Pool -> (Client -> AppM a) -> AppM a
|
||||||
withClient = PG.withClient runExceptT
|
withClient = PG.withClient runExceptT
|
||||||
|
|
||||||
@ -124,6 +129,7 @@ main = do
|
|||||||
delicious boolean NOT NULL,
|
delicious boolean NOT NULL,
|
||||||
price NUMERIC(4,2) NOT NULL,
|
price NUMERIC(4,2) NOT NULL,
|
||||||
added TIMESTAMP WITH TIME ZONE NOT NULL DEFAULT CURRENT_TIMESTAMP,
|
added TIMESTAMP WITH TIME ZONE NOT NULL DEFAULT CURRENT_TIMESTAMP,
|
||||||
|
huge_number INT8 NULL,
|
||||||
PRIMARY KEY (name)
|
PRIMARY KEY (name)
|
||||||
);
|
);
|
||||||
CREATE TEMPORARY TABLE dates (
|
CREATE TEMPORARY TABLE dates (
|
||||||
@ -263,20 +269,23 @@ main = do
|
|||||||
execute handle
|
execute handle
|
||||||
( Query
|
( Query
|
||||||
"""
|
"""
|
||||||
INSERT INTO foods (name, delicious, price)
|
INSERT INTO foods (name, delicious, price, huge_number)
|
||||||
VALUES ($1, $2, $3), ($4, $5, $6), ($7, $8, $9)
|
VALUES ($1, $2, $3, $4), ($5, $6, $7, $8), ($9, $10, $11, $12)
|
||||||
"""
|
"""
|
||||||
)
|
)
|
||||||
( Row9
|
( Row12
|
||||||
"pork"
|
"pork"
|
||||||
true
|
true
|
||||||
(D.fromString "8.30")
|
(D.fromString "8.30")
|
||||||
|
(bigintFromString "123")
|
||||||
"sauerkraut"
|
"sauerkraut"
|
||||||
false
|
false
|
||||||
(D.fromString "3.30")
|
(D.fromString "3.30")
|
||||||
|
(bigintFromString "456")
|
||||||
"rookworst"
|
"rookworst"
|
||||||
true
|
true
|
||||||
(D.fromString "5.60")
|
(D.fromString "5.60")
|
||||||
|
(bigintFromString "789")
|
||||||
)
|
)
|
||||||
test handle "select column subset"
|
test handle "select column subset"
|
||||||
$ do
|
$ do
|
||||||
@ -358,6 +367,20 @@ main = do
|
|||||||
)
|
)
|
||||||
Row0
|
Row0
|
||||||
liftEffect <<< assert $ sauerkrautPrice == [ Row1 (D.fromString "3.30") ]
|
liftEffect <<< assert $ sauerkrautPrice == [ Row1 (D.fromString "3.30") ]
|
||||||
|
test handle "handling bigint value"
|
||||||
|
$ do
|
||||||
|
insertFood
|
||||||
|
hugeNumber <-
|
||||||
|
query handle
|
||||||
|
( Query
|
||||||
|
"""
|
||||||
|
SELECT huge_number
|
||||||
|
FROM foods
|
||||||
|
WHERE NOT delicious
|
||||||
|
"""
|
||||||
|
)
|
||||||
|
Row0
|
||||||
|
liftEffect <<< assert $ hugeNumber == [ Row1 (bigintFromString "456") ]
|
||||||
transactionTest "integrity error handling"
|
transactionTest "integrity error handling"
|
||||||
$ do
|
$ do
|
||||||
withRollback client do
|
withRollback client do
|
||||||
|
Loading…
Reference in New Issue
Block a user