purescript-selda icon indicating copy to clipboard operation
purescript-selda copied to clipboard

Question about data intermediate representations

Open jim108dev opened this issue 3 years ago • 9 comments

I have coded a findByCredentials query with selda. Email, password goes in, User record comes out. The User record has restricted newtypes inside of it (LongString, ShortString).

The same information User(bio,...) is now represented 4 times in the code (see below) + database table definition in sql. Can you help me getting the number down?

Thanks.

findByCredentials :: PG.Pool -> Credentials -> Aff (Either InputError User)
findByCredentials pool { email, password } =
  PG.withConnection pool case _ of
    Left pgError -> throwError $ error $ ("PostgreSQL connection error: " <> show pgError)
    Right conn -> do
      runSelda conn (app email password) >>= validate

validate :: forall a. Either PGError (Array a) -> Aff (Either InputError a)
validate result = do
  case result of
    Left e -> case e of
      IntegrityError detail -> case detail.constraint of
        "email_unique" -> pure $ Left EMAIL_EXISTS
        "username_unique" -> pure $ Left USERNAME_EXISTS
        otherwise -> throwError $ error $ show e
      otherwise -> throwError $ error $ show e
    Right rows -> case head rows of
      Nothing -> pure $ Left NOT_FOUND
      Just row -> pure $ Right row

user ∷
  Table
    ( bio :: Maybe String -- 1. representation
    , email :: String
    , id :: Auto Int
    , image :: Maybe String
    , password :: String
    , username :: String
    )
user =
  Source "user"
    $ case _ of
        Nothing → "\"user\""
        Just alias → "\"user\"" <> " " <> alias

type InterUser 
  = { bio :: Maybe String -- 2. representation
    , email :: String
    , id :: Int
    , image :: Maybe String
    , password :: String
    , username :: String
    }

mkUser :: InterUser -> User 
mkUser i =
  unsafePartial
    { bio: LongString.unsafeFromString <$> i.bio -- 3. representation
    , email: ShortString.unsafeFromString (i.email)
    , id: i.id
    , image: LongString.unsafeFromString <$> i.image
    , password: ShortString.unsafeFromString i.password
    , username: ShortString.unsafeFromString i.username
    }

selectUser ∷
  ∀ s.
  Email ->
  Password ->
  FullQuery s
    { bio :: Col s (Maybe String)  -- 4. representation
    , email ∷ Col s String
    , id ∷ Col s Int
    , image :: Col s (Maybe String)
    , password :: Col s String
    , username :: Col s String
    }
selectUser email password =
  selectFrom user \r → do
    restrict $ r.email .== lit (ShortString.toString email) && r.password .== lit (ShortString.toString password)
    pure r

queryUser ∷
  ∀ m.
  MonadSeldaPG m =>
  Email -> Password -> m (Array InterUser)
queryUser email password = query (selectUser email password)

app ∷ ∀ m. MonadSeldaPG m => Email -> Password -> m (Array User)
app email password = do
  logQuery $ selectUser email password
  rows <- queryUser email password
  pure $ mkUser <$> rows

logQuery ∷ ∀ s i m. GetCols i ⇒ MonadEffect m ⇒ FullQuery s { | i } → m Unit
logQuery q = do
  let
    { strQuery, params } = showPG $ showQuery q
  log strQuery
  log $ unsafeStringify params
  log ""

jim108dev avatar Feb 04 '21 13:02 jim108dev

So it's nothing specific to selda, but it's still worth mentioning as this problem shows up pretty often.

We can use type synonym trickery to reuse some of this structure on the type level (for representations 1,2,4)

-- general synonym for a row type
-- we wrap element's type with `f` so we can insert `Col s` before or drop `f`
-- `id` is sometimes `Auto Int`, sometimes `Int` so additional parameter `auto` for adding `Auto`
-- optionally sometimes it's useful to define a tail `r` in `( ..., username :: f String | r )`
--   which we can use to extend the record further
type UserR auto f =
  ( bio :: f (Maybe String)
  , email :: f String
  , id :: f (auto Int)
  , image :: f (Maybe String)
  , password :: f String
  , username :: f String
  )

-- this type synonym will allow us to drop `f` or `auto`
type Id a = a

-- 1.
-- Insert Auto for `id`, drop `f`
-- since these are type synonyms they will be simplified to exactly what you had before
user ∷ Table ( | UserR Auto Id )
user = ...

-- 2. drop both `f` and `auto`
type InterUser = { | UserR Id Id }

-- 3. drop `auto`, insert `Col s` for each element's type
type ColUser s = { | UserR Id (Col s) }

Kamirus avatar Feb 04 '21 20:02 Kamirus

Since fields that are Auto cannot be passed to insert query (because we want for the DB to generate these values Automatically) it might be better to separate these fields from UserR

-- only non-auto fields
type UserCommonR f r =
  ( bio :: f (Maybe String)
  , email :: f String
  , image :: f (Maybe String)
  , password :: f String
  , username :: f String
  | r
  )

-- auto fields here
type UserAutosR auto f =
  ( id :: f (auto Int)
  )

-- combine them to get what we had before
type UserR auto f =
  UserCommonR f (UserAutosR auto f)

Kamirus avatar Feb 04 '21 20:02 Kamirus

Thank you. That was very informative. The second version of my findByCredentials function uses the crypt function. litPG works, lit although password is a string, double escapes. So I guess, for custom functions onlylitPG should be used.?

selectUser ∷
  forall s.
  Email ->
  Password ->
  FullQuery s (ColUser s)
selectUser email password =
  selectFrom user \r → do
    restrict $ r.email .== lit email && r.password .== crypt (litPG password) r.password
    pure r

crypt ∷ forall s. Col s String -> Col s String -> Col s String
crypt value passwordHashCol =
  Col
    $ Any do
        s <- showCol passwordHashCol
        v <- showCol value
        pure $ "crypt(" <> v <> ", " <> s <> ")"

jim108dev avatar Feb 05 '21 12:02 jim108dev

Hi @jim108dev,

Thanks for the report and sorry for this inconvenience. I think this is fixed on the devel branch:

https://github.com/Kamirus/purescript-selda/compare/scope-as-backend-with-new-pg-client#diff-daa2106d7c44284034da75283832f24fc92122c7a91e8678df4e989fafc2b615R167

but the branch comes with other dependencies and this complicates the situation :-( Additionally I don't think we are able to easily merge this bug fix into the current master... @Kamirus do you think that we can apply this patch by hand?

We have ambitious plan to publish multiple libs next week but... that is only the plan.

paluh avatar Feb 05 '21 13:02 paluh

@paluh if it's only removing primPGEscape call from Any then it shouldn't be problematic to apply this change for master. At least there's a workaround - use litPG for now 😏

Kamirus avatar Feb 05 '21 13:02 Kamirus

OK, what is intended way to insert and update the password with crypt(password, gen_salt('bf'))? It's not clear, the methods are super general.

jim108dev avatar Feb 05 '21 23:02 jim108dev

Right, this is really interesting as there are two things

  1. how to insert query expressions (of type Col s a), guide only mentions inserting non-query expressions (of type a)
  2. how to cope with a super general type of insert

Ad 1. It would be best to have a way to construct INSERT statement from a SELECT query, but afaik it's not yet implemented. So, for now, you need to create a query that creates these values, use query on it to get PS values and then insert_ them.

Ad 2. Super general type of insert is necessary as Auto (cannot insert) and Default (optional to insert) change which columns are insertable. But it would be nice to have more type inference: Say we have the table definition user so we should define insertUser = insert_ user and let type inference figure out the type. But this is not the case right now as Default columns are optional so it is possible to assign many types to insert_ user.

Although it is possible with update: Define a concrete updateUser function and inspect the inferred type.

updateUser conn pred up = PG.Aff.update conn user pred up
  • pred function specifies which records to update
  • up function specifies how to update them

Since both pred and up work on Col s a query expressions then you can use crypt directly there in the up function.

Improvement:

  • we could provide a version of insert that requires all columns: then the type of insertAll user should be inferrable.
  • insertAll might have types of default columns wrapped with additional Maybe so that the type could be inferred but values could be still optional but on value-level instead of on type-level
  • I'll open a separate issue for it (#47 )

@jim108dev

For now, I'd tackle the problem with insert in the following way:

  • say we have all aliases like UserCommonR already defined.
  • pick either insert or insert_ whether you want RETURNING or not
  • pick either version of insert from PG.Class or PG.Aff (simpler one is from Aff)
  • define a monomorphic version of insert for a conrete table: user
  • start with:
<insert-your-table>
  ∷ Database.PostgreSQL.Connection
  → Array { | <nonauto-columns-alias> Id () }
  → Aff (Either PGError Unit)
<insert-your-table> conn = PG.Aff.insert_ conn <your-table>

Filling out details for your user table definition we have:

insertUser
  ∷ Database.PostgreSQL.Connection
  → Array { | UserCommonR Id () }
  → Aff (Either PGError Unit)
insertUser conn = PG.Aff.insert_ conn user

Was it helpful? Feel free to ask me to clarify certain statements in case sth is unclear.

Kamirus avatar Feb 06 '21 15:02 Kamirus

Ok thanks. I have created a fake table with my function in it and fed it to insert.

selectPassword :: forall s. Password -> FullQuery s { password :: Col s LongString }
selectPassword password =
  selectFrom (encryptedTable password) \r -> do
    pure r

encryptedTable :: Password -> Table ( password ∷ LongString )
encryptedTable password =
  Source "encrypted"
    $ case _ of
        Nothing -> "\"encrypted\""
        Just alias -> "crypt('" <> (LongString.toString password) <> "', gen_salt('bf'))" <> " " <> alias <> " (password)"

insert :: Pool -> Raw -> Aff (Either InputError User)
insert pool r =
  withConnection pool
    ( \conn ->
        runSelda conn do
          _ <- logQuery $ selectPassword r.password
          encrypted <- S.query1_ $ selectPassword r.password
          S.insert userTable [ { bio: r.bio, email: r.email, image: r.image, password: encrypted.password, username: r.username } ]
    )
    >>= validate

jim108dev avatar Feb 06 '21 22:02 jim108dev

I see, that's very clever ;) This points out that we cannot create a query without a FROM clause. I've opened an issue #46 for it. Nice workaround using Source there :smirk:

Kamirus avatar Feb 07 '21 17:02 Kamirus