Hasql: inserting many values that aren't tuples

The example in the docs is clear and understandable:

insertMultipleLocations :: Statement (Vector (UUID, Double, Double)) ()
insertMultipleLocations =
  Statement sql encoder decoder True
  where
    sql = "insert into location (id, x, y) select * from unnest ($1, $2, $3)"
    encoder =
      Data.Vector.unzip3 >$<
        Contravariant.Extras.contrazip3
          (Encoders.param $ Encoders.nonNullable $ Encoders.foldableArray $ Encoders.nonNullable Encoders.uuid)
          (Encoders.param $ Encoders.nonNullable $ Encoders.foldableArray $ Encoders.nonNullable Encoders.float8)
          (Encoders.param $ Encoders.nonNullable $ Encoders.foldableArray $ Encoders.nonNullable Encoders.float8)
    decoder = Decoders.noResult

However, I’m struggling with finding a way to adapt to cases where the params aren’t a vector/list of tuples. For instance, something like this

data MyType = MyType { id_ :: UUID, x :: Double, y :: Double}

insertMultipleLocations :: Statement (Vector MyType) ()
insertMultipleLocations =
  Statement sql encoder decoder True
  where
    sql = "insert into location (id, x, y) select * from unnest ($1, $2, $3)"
    encoder = ???
    decoder = Decoders.noResult

I could write a function myTypeToTuple :: MyType -> (UUID, Double, Double) and compose it with unzip3, but when the number of fields grow it becomes increasingly painful.

What patterns are people using for writing the encoder in such cases?

1 Like

I don’t have any experience with hasql, but from the docs it looks like you’ll have to construct something of type ‘Params (Vector MyType)’, so I would look at the docs of ‘Params’. From the looks of it, you can essentially construct something of type ‘Params Double’ and then combine those using (<>) (from Semigroup) and (>$<) from the Contravariant typeclass.

Yes, indeed, but I don’t see how to do that. Making an encoder for a single MyType is easy, that’s done like this (with a bit of qualified imports):

encMyType :: Enc.Params MyType
encMyType =
  (id_ >$< Enc.param (Enc.nonNullable Enc.uuid))
    <> (x >$< Enc.param (Enc.nonNullable Enc.float8))
    <> (y >$< Enc.param (Enc.nonNullable Enc.float8))

but how I turn that into an encoder for [MyType] is unclear. (At least without going via list of tuples, that is.)

Params is an instance of Divisible, which has (morally) the operation you want: divide :: (a -> (b, c)) -> f b -> f c -> f a.

Unfortunately, I don’t know of any good story for making this primitive work smoothly with records. I’d normally point at George Wilson’s talk, Contravariant functors: The other side of the coin, but YOW seems to have removed all their Lambda Jam videos and not re-uploaded all of them to the main channel. It provided reasonably usable operators (>*), (>*<), (*<), (>|), (>|<), and (|<). Some discussion on the contravariant issue tracker might give you the flavour.

A haskellforall blog post also proposes an (>*<) operator but needs helper adapt :: Record -> (Field1, (Field2, (Field3, Field4))) functions to get any useful work done. The comments section offers a solution using Generic, but that’s not much better.

I tried using a HKD record but the barbies library didn’t provide the typeclass I needed: you need a version of TraversableB that combines results using divide instead of (<*>). There’s an issue on the contravariant bugtracker about a possible class Contraverse; adapting that to barbies naming and idioms gives something reasonable (the ContraversableB instance is probably derivable using generics):

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}

import Data.Functor.Barbie (FunctorB (..), Rec (..))
import Data.Functor.Compose (Compose (..))
import Data.Functor.Contravariant (Contravariant (..))
import Data.Functor.Contravariant.Divisible (Divisible (..), divided)
import Data.Functor.Identity (Identity (..))
import GHC.Generics (Generic)

-- machinery that could (should?) exist in `barbies`:
class (FunctorB b) => ContraversableB b where
  bcontraverse :: (Divisible e) => (forall a. f a -> e (g a)) -> b f -> e (b g)

bconsequence :: (ContraversableB b, Divisible e) => b (Compose e g) -> e (b g)
bconsequence = bcontraverse getCompose

bconsequence' :: (ContraversableB b, Divisible e) => b e -> e (b Identity)
bconsequence' = bcontraverse (contramap runIdentity)

-- mockup of the `Param` type, with sample encoders:
data Param a

instance Contravariant Param

instance Divisible Param

pInt :: Param Int
pInt = undefined

pBool :: Param Bool
pBool = undefined

pChar :: Param Char
pChar = undefined

pString :: Param String
pString = undefined

-- HKD record:
data MyRecord f = MyRecord
  { f1 :: f Int,
    f2 :: f Bool,
    f3 :: f Char,
    f4 :: f String
  }
  deriving stock (Generic)
  deriving anyclass (FunctorB)

instance ContraversableB MyRecord where
  bcontraverse nt r =
    divide adapt (nt (f1 r))
      . divided (nt (f2 r))
      $ divided (nt (f3 r)) (nt (f4 r))
    where
      adapt (MyRecord {f1, f2, f3, f4}) = (f1, (f2, (f3, f4)))

myRecordParam :: Param (MyRecord Identity)
myRecordParam =
  bconsequence'
    MyRecord
      { f1 = pInt,
        f2 = pBool,
        f3 = pChar,
        f4 = pString
      }

Also, if you don’t want to chase PRs around the ecosystem, you can use generics-eot to avoid writing adapt by hand.

It sounds like the easiest way forward is to just do one insertion at a time and loop over the [MyType].

You may be looking for foldableArray, composite, and field. I believe you might need to also declare the type to PostgreSQL before it’ll accept it as a parameter to a query (like CREATE TYPE MyType_row(a uuid, b number, c number) then your query can do e.g. SELECT r.id, r.x, r.y FROM unnest($1::MyType_row[]) AS r).

Something like E.foldableArray (E.nonNullable (E.composite rowEncMyType)) where rowEncMyType looks just like your encMyType except using field instead of param.

If you can’t be bothered with all that probably the easiest way is just to go via jsonb. There’s absolutely also a way to get it all derived/inferred for you from just the type but and generics which might be a fun exercise :slight_smile: . There are a few packages that provide default/implicit hasql decoders/encoders but they all seem varying degrees of complete to me.