Skip to content

VALUES produces invalid SQLite query #326

Open
@bgamari

Description

@bgamari

This example:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeSynonymInstances #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}

module Main where

import GHC.Generics
import Data.Text (Text)
import Database.Beam
import Database.Beam.Sqlite
import Database.Beam.Backend.SQL
import Database.Beam.Backend.Types
import Database.SQLite.Simple as SQLite
import Database.SQLite.Simple.FromField

data TestDb f
    = TestDb
    { _tdbUsers          :: f (TableEntity UserT)
    }
    deriving (Generic)

instance Database be TestDb

testDb :: DatabaseSettings be TestDb
testDb = defaultDbSettings

type Username = Text

mkUsername = id

--newtype Username = Username Text
--                    deriving (Show, Eq, Ord)
--
--deriving instance HasSqlValueSyntax be Text => HasSqlValueSyntax be Username
--deriving instance FromField Username
--instance FromBackendRow Sqlite Username
--mkUsername :: Text -> Username
--mkUsername = Username

data UserT f
    = User
    { _userId   :: Columnar f Int
    , _userName :: Columnar f Username
    }
    deriving (Generic)

type User = UserT Identity
type UserId = PrimaryKey UserT Identity
deriving instance Show (PrimaryKey UserT Identity)
deriving instance Show User

instance Table UserT where
    data PrimaryKey UserT f = UserId (Columnar f Int) deriving Generic
    primaryKey = UserId . _userId

instance Beamable UserT
instance Beamable (PrimaryKey UserT)

missingUsers :: [Username]
             -> Q Sqlite TestDb s (QGenExpr QValueContext Sqlite s Username)
missingUsers users =
    let userNames :: Q Sqlite TestDb s (QGenExpr QValueContext Sqlite s Username)
        userNames = fmap _userName (all_ $ _tdbUsers testDb)

        userNames' :: Q Sqlite TestDb s (QGenExpr w Sqlite s Username)
        userNames' = values_ $ map val_ users
    in userNames `except_` userNames'

main :: IO ()
main = do
    conn <- SQLite.open "test.sqlite"
    let users = map mkUsername ["a", "b", "c"]
    runBeamSqliteDebug putStrLn conn $
        runSelectReturningList (select $ missingUsers users) >>= liftIO . print

Fails with:

SQLite3 returned ErrorError while attempting to perform prepare "SELECT \"t0\".\"name\" AS \"res0\" FROM \"users\" AS \"t0\" EXCEPT SELECT \"t0\".\"res0\" AS \"res0\" FROM (VALUES (?), (?), (?)) AS \"t0\"(\"res0\")": near "(": syntax error

Metadata

Metadata

Assignees

No one assigned

    Type

    No type

    Projects

    No projects

    Milestone

    No milestone

    Relationships

    None yet

    Development

    No branches or pull requests

    Issue actions