haskell-opaleye icon indicating copy to clipboard operation
haskell-opaleye copied to clipboard

HStore support

Open saurabhnanda opened this issue 7 years ago • 16 comments

Planning to raise a PR for this, once one of https://github.com/lpsmith/postgresql-simple/pull/214 or https://github.com/lpsmith/postgresql-simple/pull/215 is merged into PG-Simple.

However, in my development branch, I'm facing a very strange issue. Here's how I've defined the PGHStore data type:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

module Opaleye.PGHStore where

import Opaleye
import Data.Profunctor.Product.Default
import VacationLabs.Database.PostgreSQL.Simple.HStore
import Opaleye.Internal.RunQuery ()

data PGHStore

instance IsSqlType PGHStore where
  showPGType _ = "hstore"

pgHStore :: HStoreMap -> Column PGHStore
pgHStore h = unsafeCoerceColumn $ pgLazyByteString $ toLazyByteString (toHStore h)

instance QueryRunnerColumnDefault PGHStore HStoreMap where
  queryRunnerColumnDefault = fieldQueryRunnerColumn

instance Default Constant HStoreMap (Column PGHStore) where
  def = Constant pgHStore

A simple test fails:

testHStoreDB :: Connection -> Assertion
testHStoreDB conn = void $ withTransaction conn $ do
  _ <- execute_ conn "create table if not exists hstore_test(hstore_col hstore)"
  -- h <- generate (arbitrary :: Gen HStoreMap)
  let h = HStoreMap $ fromList $ [("a", "b")]
  (h_:_) <- runInsertManyReturning conn hstoreTestTable [constant h] Prelude.id
  -- _ <- execute conn "insert into hstore_test(hstore_col) values(?)" (Only h)
  assertEqual "not equal" h h_
  execute_ conn "drop table if exists hstore_test"

Generated SQL query:

INSERT INTO "hstore_test" ("hstore_col")
	VALUES (E'\\x2261223d3e226222')
	RETURNING "hstore_col"

Expected SQL query:

INSERT INTO "hstore_test" ("hstore_col") VALUES ('"a"=>"b"') RETURNING "hstore_col"

I've already validated that the pg-simple machinery is working almost correctly. So, I've done something really stupid one while defining PGHStore above.

saurabhnanda avatar Jun 16 '17 07:06 saurabhnanda

I guess toHStore ("a", "b") = "\\x2261223d3e226222". Can you check? Where is toHStore defined?

tomjaguarpaw avatar Jun 16 '17 09:06 tomjaguarpaw

toHStore is defined in pg-simple

instance ToHStore HStoreMap where
    toHStore (HStoreMap xs) = Map.foldrWithKey f mempty xs
      where f k v ys = hstore k v `mappend` ys

class ToHStore a where
   toHStore :: a -> HStoreBuilder

toLazyByteString :: HStoreBuilder -> BL.ByteString
toLazyByteString x = case x of
                       Empty -> BL.empty
                       Comma y -> BU.toLazyByteString y

saurabhnanda avatar Jun 16 '17 10:06 saurabhnanda

The core conversion to a lazy bytestring is correct. I checked:

 toLazyByteString $ H.toHStore $ HStoreMap $ fromList [("a", "b")]
"\"a\"=>\"b\""
 ```

saurabhnanda avatar Jun 16 '17 10:06 saurabhnanda

It's a bit confusing. Firstly, it seems like E'\\x2261223d3e226222' is actually a valid encoding of the Postgres string '"a"=>"b"'. Can you check? I don't have a server to hand.

Secondly, I looked at what pgLazyByteString does, and it converts to a bytea, not a text. I guess ideally you want the latter. Perhaps try converting the ByteString to an ASCII String first and going via pgString?

tomjaguarpaw avatar Jun 16 '17 10:06 tomjaguarpaw

See 8.4.2. here: https://www.postgresql.org/docs/9.0/static/datatype-binary.html

tomjaguarpaw avatar Jun 16 '17 10:06 tomjaguarpaw

Ok -- got it. Here's the correct code:

pgHStore :: HStoreMap -> Column PGHStore
pgHStore h = IPT.castToType "hstore" $ HSD.quote $ IPT.lazyDecodeUtf8 $ toLazyByteString (toHStore h)

saurabhnanda avatar Jun 16 '17 10:06 saurabhnanda

Cool. What's HSD.quote?

tomjaguarpaw avatar Jun 16 '17 10:06 tomjaguarpaw

import qualified Opaleye.Internal.HaskellDB.Sql.Default as HSD

saurabhnanda avatar Jun 16 '17 11:06 saurabhnanda

OK, this seems pretty reasonable.

tomjaguarpaw avatar Jun 16 '17 11:06 tomjaguarpaw

so, can we keep this issue open, while I chase down the PR on pg-simple?

saurabhnanda avatar Jun 16 '17 11:06 saurabhnanda

I guess it'll be a good idea to include all the hstore functions in the PGHStore PR as well, right?

saurabhnanda avatar Jun 16 '17 12:06 saurabhnanda

  • Feel free to keep the issue open if you like

  • Including all the hstore functions would be great

tomjaguarpaw avatar Jun 16 '17 12:06 tomjaguarpaw

(and tests)

tomjaguarpaw avatar Jun 16 '17 12:06 tomjaguarpaw

@tomjaguarpaw do you have any thoughts on how to deal with https://github.com/phadej/qc-instances/issues/9#issuecomment-310038062 Any tests in Opaleye based on QC would also be affected by this issue, right?

saurabhnanda avatar Jun 21 '17 15:06 saurabhnanda

The Opaleye QuickCheck tests only do round-tripping of Int and Bool at the moment so I have never come across this issue.

tomjaguarpaw avatar Jun 21 '17 16:06 tomjaguarpaw

I think patching quickcheck-text as you have done is the most sensible solution.

tomjaguarpaw avatar Jun 21 '17 16:06 tomjaguarpaw