beam icon indicating copy to clipboard operation
beam copied to clipboard

Foreign key constraints are not generated during migration

Open prsteele opened this issue 5 years ago • 10 comments

I'm attempting to use beam-migrate to create my tables. This works fine except for a missing foreign key constraint.

(I haven't actually been able to find any documentation that suggests whether this should be explicitly supported, so I apologize if this is documented and I missed it.)

Expected behavior

Tables declared with a foreign key have a foreign key constraint generated by beam-migrate.

Observed behavior

Tables declared with a foreign key lack a foreign key constraint.

Demonstration

Below is a simple example demonstrating this issue.

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}

module Main where

import Data.Int (Int64)
import Database.Beam
import Database.Beam.Migrate
import Database.Beam.Migrate.Simple
import Database.Beam.Sqlite
import Database.Beam.Sqlite.Migrate
import Database.SQLite.Simple hiding (field)

data TableAT f = TableA
  { _tableAId :: Columnar f Int64
  }
  deriving
    ( Generic,
      Beamable
    )

instance Table TableAT where
  data PrimaryKey TableAT f = TableAId (Columnar f Int64)
    deriving (Generic, Beamable)

  primaryKey = TableAId <$> _tableAId

data TableBT f = TableB
  { _tableBId :: Columnar f Int64,
    _tableARef :: PrimaryKey TableAT f
  }
  deriving
    ( Generic,
      Beamable
    )

instance Table TableBT where
  data PrimaryKey TableBT f = TableBId (Columnar f Int64)
    deriving (Generic, Beamable)

  primaryKey = TableBId <$> _tableBId

data DemoDb f = DemoDb
  { _demoA :: f (TableEntity TableAT),
    _demoB :: f (TableEntity TableBT)
  }
  deriving
    ( Generic,
      Database be
    )

initialSetup :: Migration Sqlite (CheckedDatabaseSettings Sqlite DemoDb)
initialSetup =
  DemoDb
    <$> ( createTable "table_a" $
            TableA
              { _tableAId = field "id" sqliteBigInt notNull unique
              }
        )
    <*> ( createTable "table_b" $
            TableB
              { _tableBId = field "id" sqliteBigInt notNull unique,
                _tableARef = TableAId $ field "a_id" sqliteBigInt notNull
              }
        )

initialSetupSteps :: MigrationSteps Sqlite () (CheckedDatabaseSettings Sqlite DemoDb)
initialSetupSteps = migrationStep "initial_setup" (const initialSetup)

demoDb :: DatabaseSettings Sqlite DemoDb
demoDb = unCheckDatabase $ evaluateDatabase initialSetupSteps

main :: IO ()
main = do
  conn <- open "demo.sqlite"
  let destructionHook = defaultUpToDateHooks {runIrreversibleHook = pure True}
  _ <-
    runBeamSqliteDebug putStrLn conn $
      bringUpToDateWithHooks
        destructionHook
        migrationBackend
        initialSetupSteps
  pure ()

This is compiled using GHC 8.6.5 and

beam-core ==0.8.0.0,                                                                                                                                                                                                                                              
beam-migrate ==0.4.0.1,                                                                                                                                                                                                                                                  
beam-sqlite ==0.4.0.0,                                                                                                                         

When run, we get the output

$ cabal exec demo        
CREATE TABLE "beam_version"("version" INTEGER NOT NULL , PRIMARY KEY("version"));
-- With values: []
CREATE TABLE "beam_migration"("id" INTEGER NOT NULL , "commitId" VARCHAR NOT NULL , "date" TIMESTAMP NOT NULL , PRIMARY KEY("id"));
-- With values: []
INSERT INTO "beam_version"("version") VALUES (?);
-- With values: [SQLInteger 1]
SELECT "t0"."id" AS "res0", "t0"."commitId" AS "res1", "t0"."date" AS "res2" FROM "beam_migration" AS "t0";
-- With values: []
CREATE TABLE "table_a"("id" BIGINT NOT NULL  UNIQUE , PRIMARY KEY("id"));
-- With values: []
CREATE TABLE "table_b"("id" BIGINT NOT NULL  UNIQUE , "a_id" BIGINT NOT NULL , PRIMARY KEY("id"));
-- With values: []
INSERT INTO "beam_migration"("id", "commitId", "date") VALUES (?, ?, CURRENT_TIMESTAMP);
-- With values: [SQLInteger 0,SQLText "initial_setup"]

As shown, the table generated for TableBT lacks a foreign key constraint; this is confirmed by inspecting the table schema with sqlite3 directly:

sqlite> .schema table_b                                                                                                                                         
CREATE TABLE IF NOT EXISTS "table_b"("id" BIGINT NOT NULL  UNIQUE , "a_id" BIGINT NOT NULL , PRIMARY KEY("id"));

prsteele avatar Aug 02 '20 15:08 prsteele

Yes this a known "missing feature." However it's an important feature and we should add it.

3noch avatar Aug 02 '20 16:08 3noch

Thanks for confirming!

prsteele avatar Aug 02 '20 16:08 prsteele

I was looking through the code and noticing there seems to be partial (?) support for references in the syntax typeclasses:

https://github.com/haskell-beam/beam/blob/0d9f6d8db8115f756a5e8175adf7fc1c95328019/beam-migrate/Database/Beam/Migrate/SQL/SQL92.hs#L186-L190

There are corresponding instances in Database.Beam.Postgres and Database.Beam.Sqlite. However, there is no references function exposed to allow users to construct these constraints (like how we do with notNull and unique).

Could it be that writing such a function would allow us to add these constraints manually? I'd be fine with that if I could get them to appear in my migrations. Or is there more work to be done?

thomasjm avatar Jan 09 '21 05:01 thomasjm

Any new developments regarding this issue? It's a deal breaker for me. I'd have to resort to sql scripts otherwise.

dciug avatar Feb 17 '21 21:02 dciug

Do we have any news or some workarounds in beam code?

GulinSS avatar Sep 05 '21 13:09 GulinSS

Try to define your own reference constraint:

referenceUsersTable :: BeamMigrateSqlBackend be => Constraint be
referenceUsersTable = Constraint $ referencesConstraintSyntax "users" ["user_id"] 
      Nothing
      (Just referentialActionCascadeSyntax) 
      Nothing

It add the following SQL for Postgres table DDL:

"user_id" INT NOT NULL REFERENCES "users"("user_id") ON UPDATE CASCADE

And later use this reference as a constraint at field definition:

(UserId (field "created_by" int notNull referenceUsersTable))

Yeah, it looks not so flexible as it would be. Need to put manually table name and column name. But in general it works.

GulinSS avatar Sep 05 '21 18:09 GulinSS

I just tried the solution by @GulinSS above, and while it does work for adding the SQL to the DDL, I wasn't able to run the migration successfully because it tried to create the tables in the wrong order. (I.e., it tried to create the table using referenceUsersTable before it created the users table.)

It seems like beam-migrate needs to topological sort the tables by references, or am I missing something?

EDIT: oh, I just realized tables are created in the order they appear as fields in your database ADT. So I can reorder those so that it works.

EDIT 2: however, this doesn't seem to work for multi-column foreign keys. Is there perhaps a way to emit a separate FOREIGN KEY statement as part of the table DDL?

thomasjm avatar Sep 09 '21 02:09 thomasjm

I don't think topological sorting is a good approach since there can be cyclic references and we'd need to break them by adding the constraints after creating the tables. So we might as well just always do it like that.

kmicklas avatar Sep 14 '21 01:09 kmicklas

@kmicklas what can you suggest to update beam-migrations code to allow foreign references fully with FOREIGN KEY statement involved?

GulinSS avatar Sep 18 '21 23:09 GulinSS

I'm going to comment in here because there seems to be some confusion as to what table types are versus a database type.

In general, if you have a table type PersonT, and another table type 'PersonCartT' with a foreign key to PersonT, then that foreign key says nothing as to which person table PersonCartT refers to.

A Database type can have multiple tables with type PersonT and multiple tables of PersonCartT. A table type represents a table schema. A table schema can be instantiated multiple times within a database schema. Beam-migrate, and beam more generally, supports all possible ways in which joining can occur among these tables.

I would love to auto-generate these references as it is obvious to me that each individual instance of a table schema has one foreign key that would make sense, but this would require us to be able to annotate fields in GHC records with arbitrary data (like how rust does). GHC unfortunately doesn't quite have this functionality.

As others mentioned, you can do this manually.

If there are other suggestions for how to make this work in general, I'm more than happy to consider or implement them. I too would like beam to have this functionality.

tathougies avatar Sep 23 '21 21:09 tathougies