generated from tpl/purs
README: add query
usage example
This commit is contained in:
parent
e21bd27173
commit
85e01d38fe
36
README.md
36
README.md
@ -18,33 +18,33 @@ module Test.Example where
|
|||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
|
|
||||||
import Database.PostgreSQL (defaultPoolConfiguration, execute, newPool, Query(Query), withConnection)
|
import Database.PostgreSQL (defaultPoolConfiguration, execute, newPool, query, Query(Query), withConnection)
|
||||||
import Database.PostgreSQL.Row (Row0(Row0), Row3(Row3))
|
import Database.PostgreSQL.Row (Row0(Row0), Row3(Row3))
|
||||||
import Data.Decimal as Decimal
|
import Data.Decimal as Decimal
|
||||||
import Data.Maybe (Maybe(..))
|
import Data.Maybe (Maybe(..))
|
||||||
import Data.Tuple.Nested ((/\))
|
import Data.Tuple.Nested ((/\))
|
||||||
import Effect.Aff (Aff)
|
import Effect.Aff (Aff)
|
||||||
|
import Effect.Class (liftEffect)
|
||||||
|
import Test.Assert (assert)
|
||||||
|
|
||||||
-- Our interaction with db is performed asynchronously in `Aff`
|
-- Our interaction with db is performed asynchronously in `Aff`
|
||||||
run ∷ Aff Unit
|
run ∷ Aff Unit
|
||||||
run = do
|
run = do
|
||||||
|
|
||||||
-- Now we are able to setup connection. We are assuming here
|
-- We assume here that postgres is running on a standard local port together
|
||||||
-- that postgres is running on a standard local port.
|
-- with `ident` authentication so configuration can be nearly empty.
|
||||||
-- We use `ident` authentication so configuration can be nearly empty.
|
|
||||||
-- It requires only database name which we pass to `newPool` function.
|
-- It requires only database name which we pass to `newPool` function.
|
||||||
-- We want to close connection after a second (`idleTimeoutMillis` setting) because this code
|
-- We setup also `idleTimeoutMillis` setting because this code
|
||||||
-- would be run by our test suite ;-)
|
-- would be run by our test suite and we want to finish quickly ;-)
|
||||||
-- Of course you can provide additional configuration settings if you need to.
|
|
||||||
|
|
||||||
pool <- newPool ((defaultPoolConfiguration "purspg") { idleTimeoutMillis = Just 1000 })
|
pool <- newPool ((defaultPoolConfiguration "purspg") { idleTimeoutMillis = Just 1000 })
|
||||||
withConnection pool \conn -> do
|
withConnection pool \conn -> do
|
||||||
|
|
||||||
-- We can now create our temporary table which we are going to query in this example.
|
-- We can now create our temporary table which we are going to query in this example.
|
||||||
-- `execute` performs this query. It ignores result value by default.
|
-- `execute` ignores result value which is what we want in this case.
|
||||||
|
|
||||||
execute conn (Query """
|
execute conn (Query """
|
||||||
CREATE TEMPORARY TABLE foods (
|
CREATE TEMPORARY TABLE fruits (
|
||||||
name text NOT NULL,
|
name text NOT NULL,
|
||||||
delicious boolean NOT NULL,
|
delicious boolean NOT NULL,
|
||||||
price NUMERIC(4,2) NOT NULL,
|
price NUMERIC(4,2) NOT NULL,
|
||||||
@ -60,18 +60,28 @@ run = do
|
|||||||
-- provides instances for automatic conversions from and to SQL values.
|
-- provides instances for automatic conversions from and to SQL values.
|
||||||
|
|
||||||
execute conn (Query """
|
execute conn (Query """
|
||||||
INSERT INTO foods (name, delicious, price)
|
INSERT INTO fruits (name, delicious, price)
|
||||||
VALUES ($1, $2, $3)
|
VALUES ($1, $2, $3)
|
||||||
""") (Row3 "pork" true (Decimal.fromString "8.30"))
|
""") (Row3 "coconut" true (Decimal.fromString "8.30"))
|
||||||
|
|
||||||
|
|
||||||
-- You can also use nested tuples instead of `Row*` types but this can be a bit more
|
-- You can also use nested tuples instead of `Row*` types but this can be a bit more
|
||||||
-- verbose. `/\` is just an alias for `Tuple` constructor.
|
-- verbose. `/\` is just an alias for `Tuple` constructor.
|
||||||
|
|
||||||
execute conn (Query """
|
execute conn (Query """
|
||||||
INSERT INTO foods (name, delicious, price)
|
INSERT INTO fruits (name, delicious, price)
|
||||||
VALUES ($1, $2, $3)
|
VALUES ($1, $2, $3)
|
||||||
""") ("sauerkraut" /\ false /\ Decimal.fromString "3.30")
|
""") ("lemon" /\ false /\ Decimal.fromString "3.30")
|
||||||
|
|
||||||
|
-- Of course `Row*` typees and nested tuples can be also used when we are fetching
|
||||||
|
-- data from db.
|
||||||
|
|
||||||
|
names <- query conn (Query """
|
||||||
|
SELECT name, delicious
|
||||||
|
FROM fruits
|
||||||
|
ORDER BY name ASC
|
||||||
|
""") Row0
|
||||||
|
liftEffect <<< assert $ names == ["coconut" /\ true, "lemon" /\ false]
|
||||||
|
|
||||||
```
|
```
|
||||||
|
|
||||||
|
@ -20,7 +20,9 @@ class FromSQLRow a where
|
|||||||
instance toSQLRowForeignArray :: ToSQLRow (Array Foreign) where
|
instance toSQLRowForeignArray :: ToSQLRow (Array Foreign) where
|
||||||
toSQLRow = identity
|
toSQLRow = identity
|
||||||
|
|
||||||
instance toSQLRowTuple :: (ToSQLValue a, ToSQLRow (Tuple b t)) => ToSQLRow (Tuple a (Tuple b t)) where
|
instance toSQLRowTupleOfTuples :: (ToSQLRow (Tuple a ta), ToSQLRow (Tuple b t)) => ToSQLRow (Tuple (Tuple a ta) (Tuple b t)) where
|
||||||
|
toSQLRow (Tuple a t) = toSQLRow a <> toSQLRow t
|
||||||
|
else instance toSQLRowTuple :: (ToSQLValue a, ToSQLRow (Tuple b t)) => ToSQLRow (Tuple a (Tuple b t)) where
|
||||||
toSQLRow (Tuple a t) = toSQLValue a : toSQLRow t
|
toSQLRow (Tuple a t) = toSQLValue a : toSQLRow t
|
||||||
else instance toSQLRowTupleEnd :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Tuple a b) where
|
else instance toSQLRowTupleEnd :: (ToSQLValue a, ToSQLValue b) => ToSQLRow (Tuple a b) where
|
||||||
toSQLRow (Tuple a b) = [ toSQLValue a, toSQLValue b ]
|
toSQLRow (Tuple a b) = [ toSQLValue a, toSQLValue b ]
|
||||||
|
@ -128,9 +128,9 @@ main = do
|
|||||||
INSERT INTO foods (name, delicious, price)
|
INSERT INTO foods (name, delicious, price)
|
||||||
VALUES ($1, $2, $3), ($4, $5, $6), ($7, $8, $9)
|
VALUES ($1, $2, $3), ($4, $5, $6), ($7, $8, $9)
|
||||||
""")
|
""")
|
||||||
( "pork" /\ true /\ (D.fromString "8.30")
|
( ("pork" /\ true /\ (D.fromString "8.30"))
|
||||||
/\ "sauerkraut" /\ false /\ (D.fromString "3.30")
|
/\ ("sauerkraut" /\ false /\ (D.fromString "3.30"))
|
||||||
/\ "rookworst" /\ true /\ (D.fromString "5.60"))
|
/\ ("rookworst" /\ true /\ (D.fromString "5.60")))
|
||||||
names <- query conn (Query """
|
names <- query conn (Query """
|
||||||
SELECT name, delicious
|
SELECT name, delicious
|
||||||
FROM foods
|
FROM foods
|
||||||
|
Loading…
Reference in New Issue
Block a user