user3716072
user3716072

Reputation: 197

Haskell Persistent: upsert to update list fields

I want to create a table where one of the columns is a list of Int. For example:

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
    PersonTest
      name String
      listi [Int]
      UniquePerson name
      deriving Show Eq Ord
|]

Then I want to use upsert to insert a new person if it is not there yet, otherwise I want to update the list to include the int numbers in the new record. I wrote this small test:

test_experiment :: IO ()
test_experiment = do
let p1 = [PersonTest "Dan" [1,2]
          ,PersonTest "Jo" []
          ,PersonTest "Dan" [4]] -- This triggers an update
    upse = (\pl -> runSqlite "dbe.sqlite" $ do
                   runMigration migrateAll
                   mapM_ (\p -> upsert p [PersonTestListi +=. p.personTestListi]) pl )
upse p1 

When I run this I get the runtime error:

PersistMarshalError "getBy: Couldn't parse field listi from table person_test. Failed to parse Haskell type List; expected list, string, bytestring or null from database, but received: PersistByteString "0". Potential solution: Check that your database schema matches your Persistent model definitions."

What am I doing wrong? I was under the impression that this was supported?

Are there workarounds?

Upvotes: 0

Views: 61

Answers (1)

Sibi
Sibi

Reputation: 48766

Sqlite doesn't support arrays, that's why you see that error message. I confirmed that this works without an array:

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DerivingStrategies         #-}
{-# LANGUAGE UndecidableInstances       #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE EmptyDataDecls             #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE GADTs                      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE QuasiQuotes                #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-# LANGUAGE TemplateHaskell            #-}
{-# LANGUAGE TypeFamilies               #-}
import           Control.Monad.IO.Class  (liftIO)
import           Database.Persist
import           Database.Persist.Sqlite
import           Database.Persist.TH

share [mkPersist sqlSettings, mkMigrate "migrateAll"] [persistLowerCase|
PersonTest
    name String
    listi Int
    UniquePerson name
    deriving Show Eq Ord
|]


main :: IO ()
main = runSqlite ":memory:" $ do
    runMigration migrateAll
    let p1 = [PersonTest "Dan" 1
             ,PersonTest "Jo" 2
             ,PersonTest "Dan" 3
             ]
    mapM_ (\p -> upsert p [PersonTestListi +=. (personTestListi p)]) p1
    persons :: [Entity PersonTest] <- selectList [] []
    liftIO $ print persons

One way to solve this issue would be to use JSON's serialization using Aeson support in persistent.

Upvotes: 0

Related Questions