Coder Social home page Coder Social logo

Comments (20)

tathougies avatar tathougies commented on August 16, 2024 1

The syntax for runInsertReturningList is runInsertReturningList <table reference> $ insertValues/insertExpressions/etc

So instead of

runInsertReturningList $
      insertReturning (shoppingCartDb ^. shoppingCartUserAddresses) $
      insertValues addresses

you would have

runInsertReturningList (shoppingCartDb ^. shoppingCartUserAddresses) $
      insertValues addresses

The confusion comes because beam-postgres has its own INSERT ... RETURNING ... syntax exposed by the insertReturning function. This is specific to beam-postgres though.

Some other questions

  1. _addressForUser refers to a PrimaryKey AddressT f I believe. addressForUserId is a lens from a user to the id of the address in the _addressForUser field. PrimaryKeyT AddressT f is a data type with one data constructor. This lens unwraps this data constructor. However, the relationship combinators want the entire PrimaryKey. There is currently no way to use the generics mechanisms to automatically get these lenses. If you really want lenses (and lenses are great), feel free to use template hasekll and makeLenses from Control.Lens. We do this at work, and it works out just fine.

  2. val_ takes a haskell literal (be it a scalar value, an entire table with scalar values, or a tuple of any of the above) and converts it into a sql expression with the given haskell type. That is to say you can think of it like

val_ :: a -> QExpr syntax s a

Except, if you give it a table of values (say ``UserT Identity`):

val_ :: UserT Identity -> UserT (QExpr syntax s a)
  1. Yes I think this is typo.

from beam.

scubacabra avatar scubacabra commented on August 16, 2024 1

It's like you were reading my mind! I was just documenting everything through most of tutorial 2 -- I put some PR's together for it -- though the big postgres one still isn't done.

I'm still getting errors trying to marshall ShippingCarrier from tutorial 3 when inserting shipping info data.

all of the error messages and the source are in the tutorial-3 branch (the errors are in the org file and should be marked TODO still). It was quite a bit of errors and I haven't been able to correctly finagle it to work.

After that, I assume the rest of tutorial 3 is smooth sailing, but I have to get past that first.

Would you mind still helping me out?

PS aside from tutorial 3 bogging me down a bit, I have successfully combined beam and servant to query a database and return from it as well! You have done an amazing job with beam -- seriously!

from beam.

tathougies avatar tathougies commented on August 16, 2024

Thanks for the feedback! I'll look through it tonight

from beam.

tathougies avatar tathougies commented on August 16, 2024

One quick question, for the postgres syntax errors... What version of postgres are you using? For the life of me, I can't see what the error would be based on the sql being executed. It looks well-formed to me.

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

I'm using 9.6.5

I couldn't see why something would be wrong either, and, though I am by no means a postgres expert, I don't think I have ever written an inner join without an on clause.

I inserted the sql at the terminal

      SELECT
        "t1"."email" AS "res0",
        "t1"."first_name" AS "res1",
        "t1"."last_name" AS "res2",
        "t1"."password" AS "res3",
        "t0"."id" AS "res4",
        "t0"."address1" AS "res5",
        "t0"."address2" AS "res6",
        "t0"."city" AS "res7",
        "t0"."state" AS "res8",
        "t0"."zip" AS "res9",
        "t0"."for_user__email" AS "res10"
      FROM "cart_user_addresses" AS "t0"
      INNER JOIN "cart_users" AS "t1";

And I'm getting

ERROR:  syntax error at or near ";"
LINE 14:       INNER JOIN "cart_users" AS "t1";

looking at the postgres docs, they say to use

SELECT *
    FROM weather, cities
    WHERE city = name;

or

SELECT *
    FROM weather INNER JOIN cities ON (weather.city = cities.name);

So maybe that is why?

If I change the sql above to

      SELECT
        "t1"."email" AS "res0",
        "t1"."first_name" AS "res1",
        "t1"."last_name" AS "res2",
        "t1"."password" AS "res3",
        "t0"."id" AS "res4",
        "t0"."address1" AS "res5",
        "t0"."address2" AS "res6",
        "t0"."city" AS "res7",
        "t0"."state" AS "res8",
        "t0"."zip" AS "res9",
        "t0"."for_user__email" AS "res10"
      FROM "cart_user_addresses" AS "t0", "cart_users" AS "t1";

I get the cartesian product of all the rows

       res0        | res1  |  res2  |               res3               | res4 |        res5        | res6  |   res7    | res8 | res9  |       res10
-------------------+-------+--------+----------------------------------+------+--------------------+-------+-----------+------+-------+-------------------
 [email protected] | James | Smith  | b4cc344d25a2efe540adbf2678e2304c |    1 | 123 Little Street  |       | Boston    | MA   | 12345 | [email protected]
 [email protected] | James | Smith  | b4cc344d25a2efe540adbf2678e2304c |    2 | 222 Main Street    | Ste 1 | Houston   | TX   | 8888  | [email protected]
 [email protected] | James | Smith  | b4cc344d25a2efe540adbf2678e2304c |    3 | 9999 Residence Ave |       | Sugarland | TX   | 8989  | [email protected]
 [email protected] | Betty | Jones  | 82b054bd83ffad9b6cf8bdb98ce3cc2f |    1 | 123 Little Street  |       | Boston    | MA   | 12345 | [email protected]
 [email protected] | Betty | Jones  | 82b054bd83ffad9b6cf8bdb98ce3cc2f |    2 | 222 Main Street    | Ste 1 | Houston   | TX   | 8888  | [email protected]
 [email protected] | Betty | Jones  | 82b054bd83ffad9b6cf8bdb98ce3cc2f |    3 | 9999 Residence Ave |       | Sugarland | TX   | 8989  | [email protected]
 [email protected]   | Sam   | Taylor | 332532dcfaa1cbf61e2a266bd723612c |    1 | 123 Little Street  |       | Boston    | MA   | 12345 | [email protected]
 [email protected]   | Sam   | Taylor | 332532dcfaa1cbf61e2a266bd723612c |    2 | 222 Main Street    | Ste 1 | Houston   | TX   | 8888  | [email protected]
 [email protected]   | Sam   | Taylor | 332532dcfaa1cbf61e2a266bd723612c |    3 | 9999 Residence Ave |       | Sugarland | TX   | 8989  | [email protected]

And if I add a where "t0"."for_user__email" = "t1"."email" to that on the foreign key, it behaves the same is an inner join with an on clause.

from beam.

tathougies avatar tathougies commented on August 16, 2024

So looking into it, it looks like the right join type to use in the absence of an ON clause is CROSS JOIN. Fixing in master now. This works on my machine. Would you mind testing later to confirm?

Thanks for bringing up this issue!

I've updated the docs too. I would absolutely welcome docs on the postgres backend. Feel free to submit PRs as needed.

from beam.

tathougies avatar tathougies commented on August 16, 2024

So a few more things from your notes.

  1. runInsertReturningList should work just fine in postgres.
  2. I'll look into the marshaling errors in a bit
  3. What's your question on the stack and cabal setup? It's marked TODO in your org file, but I don't see any question

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

The cross join fix is great!

a couple questions still in tutorial 2

  1. on clause with related_ mixes lens accessors and record accessors

       do
        address <- allAddresses
        user <- related_ (shoppingCartDb ^. shoppingCartUsers) (_addressForUser address)
        return (user, address)

    I'm guessing that is because _addressForUser address is of a different type than address ^. adressForUserId. The latter is PrimaryKey UserT f while the former is Text because of the lens definition UserId (LensFor addressForUserId). Is this correct? It isn't a very big deal at all, but if it could be uniform syntax that would be nice. Although I'm just trying to get an understanding of why (and maybe put that in the documentation as it wasn't obvious to me immediately).

  2. selecting a specific user with a UserId or with a Text value

    What does val_ do exactly?

    Again, I'm guessing it has to do with the same thing as above, but you could do that section two ways -- just trying to figure out why the syntax changes.

    If you had a UserId value, then the guard_ looks like

      guard_ (_addressForUser address ==. val_ bettyId)

    And if had a Text value, then it looks like

      guard_ (address ^. addressForUserId ==. val_ bettyEmail)

    Like I mentioned, I think it is the same answer as above, just wondering to better understand it.

  3. deleting betty's houston address

    I found that I needed to add val_ to get the compilation error to go away

      _addressForUser address `references_` val_ betty

    Typo in the docs?

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

Regarding the stack todo in my notes, it was a marker to ask you if this is how you would also set it up right now? I got a little hosed first starting the tutorial trying to install and than following the errors I noticed the versions were off of what was on master.

Then it dawned on me that it isn't released yet, and I found this solution in the mailing list.

It makes sense, but took me a bit to figure out.

I can put this in the docs so someone else can see it right away if this is the way to go.

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

I thought runInsertReturningList should work too after looking through the source, but when I have

insertAddresses :: Connection -> IO ()
insertAddresses conn =
  withDatabaseDebug putStrLn conn $ B.runInsert $
    runInsertReturningList $
    insertReturning (shoppingCartDb ^. shoppingCartUserAddresses) $
    insertValues addresses

I end up with

  error:
     • Variable not in scope:
         runInsertReturningList
     • Perhaps you meant one of these:
         ‘runSelectReturningList’ (imported from Database.Beam),
         ‘runInsertReturning’ (imported from Database.Beam.Postgres) 

It doesn't look like Postgres.Connection exports this, I only see runSelect, runInsert, runInsertReturning. It looks like Sqlite.Connection exports everything. Is this why I am getting the error?

from beam.

tathougies avatar tathougies commented on August 16, 2024

Oh you need to import Database.Beam.Backend.SQL.BeamExtensions. Since there's no standard insert returning syntax across databases, it's not imported by default.

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

I thought that and I imported it before, but I got a few more compiler errors that seemed like it wasn't the way to go. I feel like I'm doing something wrong or just not getting it....

{-# LANGUAGE PartialTypeSignatures #-}
import Database.Beam.Backend.SQL.BeamExtensions

insertAddresses :: Connection -> _
insertAddresses conn =
  withDatabaseDebug putStrLn conn $
    runInsertReturningList $
      insertReturning (shoppingCartDb ^. shoppingCartUserAddresses) $
      insertValues addresses

Gives two errors:

  • withDatabaseDebug

      error:
        Couldn't match type Pg
                        with (->)
                                (SqlInsertValues
                                   (Database.Beam.Backend.SQL.SQL92.Sql92InsertValuesSyntax
                                      (Database.Beam.Backend.SQL.SQL92.Sql92InsertSyntax syntax1))
                                   table)
           arising from a functional dependency between:
             constraint MonadBeam
                           syntax0
                           be0
                           Connection
                           ((->)
                              (SqlInsertValues
                                 (Database.Beam.Backend.SQL.SQL92.Sql92InsertValuesSyntax
                                    (Database.Beam.Backend.SQL.SQL92.Sql92InsertSyntax syntax1))
                                 table))
               arising from a use of withDatabaseDebug
             instance MonadBeam PgCommandSyntax Postgres Connection Pg
               at <no location info>
        In the expression: withDatabaseDebug putStrLn conn
         In the expression:
           withDatabaseDebug putStrLn conn
           $ runInsertReturningList
             $ insertReturning (shoppingCartDb ^. shoppingCartUserAddresses)
               $ insertValues addresses
         In an equation for insertAddresses’:
             insertAddresses conn
               = withDatabaseDebug putStrLn conn
                 $ runInsertReturningList
                   $ insertReturning (shoppingCartDb ^. shoppingCartUserAddresses)
                     $ insertValues addresses
        Relevant bindings include
           insertAddresses :: Connection -> IO (m [table Identity])
  • insertReturning

       error:
        Couldn't match expected type DatabaseEntity
                                         be1 db0 (TableEntity table)
                     with actual type PgInsertOnConflict
                                         PgInsertOnConflictSyntax AddressT
                                       -> Maybe
                                            (AddressT
                                               (QExpr
                                                  PgExpressionSyntax
                                                  beam-postgres-0.1.0.0:Database.Beam.Postgres.Syntax.PostgresInaccessible)
                                             -> a0)
                                       -> PgInsertReturning (QExprToIdentity a0)
        In the second argument of ($), namely
           insertReturning (shoppingCartDb ^. shoppingCartUserAddresses)
            $ insertValues addresses
         In the second argument of ($), namely
           runInsertReturningList
            $ insertReturning (shoppingCartDb ^. shoppingCartUserAddresses)
              $ insertValues addresses
         In the expression:
           withDatabaseDebug putStrLn conn
           $ runInsertReturningList
             $ insertReturning (shoppingCartDb ^. shoppingCartUserAddresses)
               $ insertValues addresses
        Relevant bindings include
           insertAddresses :: Connection -> IO (m [table Identity])

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

I thought I was getting caught up somewhere! Thanks for the info there, now insertReturningList works just great! 💪

for postgres, should I be using the insert and runInsert functions it exports or continue using the beam-core functions qualified like I am currently doing?

I'll try using TH for the lenses and see how that feels as well.

It feels good knowing some more of this stuff, thanks for taking the time to answer these questions! almost through with tutorial 3 😃

from beam.

tathougies avatar tathougies commented on August 16, 2024

@jacobono Anything else you encountered? Can I close this issue out? Did you want to share your doc changes?

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

I just thought I would clarify where I am in tutorial 3 that is giving me the error

{-# LANGUAGE UndecidableInstances #-}
import Database.Beam.Backend.SQL

instance HasSqlValueSyntax be String => HasSqlValueSyntax be ShippingCarrier where
  sqlValueSyntax = autoSqlValueSyntax

{-# LANGUAGE MultiParamTypeClasses #-}
import           Database.Beam.Backend
instance FromBackendRow Postgres ShippingCarrier

import           Database.PostgreSQL.Simple.FromField
import           Text.Read

instance FromField ShippingCarrier where
  fromField f = do x <- readMaybe <$> fromField f
                   case x of
                     Nothing -> returnError ConversionFailed f "Could not 'read' value for 'ShippingCarrier'"
                     Just x -> pure x

instance FromBackendRow Postgres ShippingCarrier

Is getting me the following error:

error:
      • Couldn't match expected type ‘Conversion String’
                    with actual type ‘Maybe
                                        bytestring-0.10.8.1:Data.ByteString.Internal.ByteString
                                      -> Conversion a0’
      • Probable cause: ‘fromField’ is applied to too few arguments
        In the second argument of ‘(<$>)’, namely ‘fromField f’
        In a stmt of a 'do' block: x <- readMaybe <$> fromField f
        In the expression:
          do { x <- readMaybe <$> fromField f;
              case x of {
                Nothing
                  -> returnError
                        ConversionFailed f "Could not 'read' value for 'ShippingCarrier'"
                Just x -> pure x } } (intero)

so that looks like something is off with postgresql-simple's FromField instance for ShippingCarrier

I'll take a look at that see if I can resolve it

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

This made that work, going through the last of the tutorial now

instance FromField ShippingCarrier where
  fromField f bs = do x <- readMaybe <$> fromField f bs
                      case x of
                        Nothing -> returnError ConversionFailed f "Could not 'read' value for 'ShippingCarrier'"
                        Just x -> pure x

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

Found something else in tutorial 3!

using the exists combinator

selectUsersWithNoOrdersExistsCombinator :: Connection -> IO [User]
selectUsersWithNoOrdersExistsCombinator conn =
   withDatabaseDebug putStrLn conn $
    runSelectReturningList $ select $ do
      user  <- all_ (shoppingCartDb ^. shoppingCartUsers)
      guard_ (not_ (exists_ (filter_ (\order -> _orderForUser order `references_` user) (all_ (shoppingCartDb ^. shoppingCartOrders)))))
      pure user

the sql looks the same as the tutorial

SELECT
  "t0"."email" AS "res0",
  "t0"."first_name" AS "res1",
  "t0"."last_name" AS "res2",
  "t0"."password" AS "res3"
FROM "cart_users" AS "t0"
WHERE NOT(EXISTS (SELECT
                    "t0"."id" AS "res0",
                    "t0"."date" AS "res1",
                    "t0"."for_user__email" AS "res2",
                    "t0"."ship_to_address__id" AS "res3",
                    "t0"."shipping_info__id" AS "res4"
                  FROM "orders" AS "t0"
                  WHERE ("t0"."for_user__email") = ("t0"."email")))

But there is an error:

*** Exception: SqlError {sqlState = "42703", sqlExecStatus = FatalError,
    sqlErrorMsg = "column t0.email does not exist", sqlErrorDetail = "",
    sqlErrorHint = "There is a column named \"email\" in table \"t0\", but it
    cannot be referenced from this part of the query."}

from psql postgres gives

ERROR:  column t0.email does not exist
LINE 14: ...                WHERE ("t0"."for_user__email") = ("t0"."emai...
                                                              ^
HINT:  There is a column named "email" in table "t0", but it cannot be referenced from this part of the query.

If I change the sql to

SELECT
  "t0"."email" AS "res0",
  "t0"."first_name" AS "res1",
  "t0"."last_name" AS "res2",
  "t0"."password" AS "res3"
FROM "cart_users" AS "t0"
WHERE NOT(EXISTS (SELECT
                    "t1"."id" AS "res0",
                    "t1"."date" AS "res1",
                    "t1"."for_user__email" AS "res2",
                    "t1"."ship_to_address__id" AS "res3",
                    "t1"."shipping_info__id" AS "res4"
                  FROM "orders" AS "t1"
                  WHERE ("t1"."for_user__email") = ("t0"."email")))

I get the expected result of sam being the only return with no orders.

from beam.

scubacabra avatar scubacabra commented on August 16, 2024

all the rest of tutorial 3 went by pretty smoothly! 😃

The only remaining items I are

  • 💥 selectUsersWithNoOrdersExistsCombinator sql error 💥

  • ❓ Since postgres defines its own insert and runInsert should I be using that instead of the functions provided by beam-core

    I can see the sqlite backend doesn't have these functions defined, so it doesn't matter for the
    tutorial -- but using the postgres backend I noticed these and was wondering which one to use.

from beam.

dpwiz avatar dpwiz commented on August 16, 2024

I just did all 3 parts of the tutorial in postgresql and other than fumbling with runInsertReturningList (which was resolved) everything went fine. Kudos for great library and docs!

from beam.

sevanspowell avatar sevanspowell commented on August 16, 2024

Thanks for this @jacobono, it has been super helpful for a newbie.

from beam.

Related Issues (20)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.