Skip to content

Commit efd464b

Browse files
committed
Add checkSchema: like verifySchema but detecting unexpected predicates
1 parent e25001f commit efd464b

File tree

2 files changed

+72
-9
lines changed

2 files changed

+72
-9
lines changed

beam-migrate/ChangeLog.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,8 @@
88
## Added features
99

1010
* GHC 8.8 support
11+
* `checkSchema`: Like `verifySchema`, but detects and returns unexpected
12+
predicates found in the live database
1113

1214
## Bug fixes
1315

beam-migrate/Database/Beam/Migrate/Simple.hs

Lines changed: 70 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE AllowAmbiguousTypes #-}
2+
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
23
-- | Utility functions for common use cases
34
module Database.Beam.Migrate.Simple
45
( autoMigrate
@@ -10,6 +11,12 @@ module Database.Beam.Migrate.Simple
1011
, VerificationResult(..)
1112
, verifySchema
1213

14+
, IgnorePredicates(..)
15+
, CheckResult(..)
16+
, ignoreTables
17+
, ignoreAll
18+
, checkSchema
19+
1320
, createSchema
1421

1522
, BringUpToDateHooks(..)
@@ -28,7 +35,7 @@ import Database.Beam.Backend
2835
import Database.Beam.Haskell.Syntax
2936
import Database.Beam.Migrate.Actions
3037
import Database.Beam.Migrate.Backend
31-
import Database.Beam.Migrate.Checks (HasDataTypeCreatedCheck)
38+
import Database.Beam.Migrate.Checks (HasDataTypeCreatedCheck, TableExistsPredicate(..))
3239
import Database.Beam.Migrate.Log
3340
import Database.Beam.Migrate.SQL (BeamMigrateSqlBackendDataTypeSyntax)
3441
import Database.Beam.Migrate.Types
@@ -39,6 +46,8 @@ import Control.Monad.State
3946

4047
import qualified Data.HashSet as HS
4148
import Data.Semigroup (Max(..))
49+
import Data.Typeable
50+
import Data.Functor
4251
import qualified Data.Text as T
4352

4453
import qualified Control.Monad.Fail as Fail
@@ -261,16 +270,68 @@ verifySchema :: ( Database be db, MonadBeam be m )
261270
=> BeamMigrationBackend be m
262271
-> CheckedDatabaseSettings be db
263272
-> m VerificationResult
264-
verifySchema BeamMigrationBackend { backendGetDbConstraints = getConstraints } db =
265-
do actualSchema <- HS.fromList <$> getConstraints
266-
let expectedSchema = HS.fromList (collectChecks db)
267-
missingPredicates = expectedSchema `HS.difference` actualSchema
268-
if HS.null missingPredicates
269-
then pure VerificationSucceeded
270-
else pure (VerificationFailed (HS.toList missingPredicates))
273+
verifySchema backend db = do
274+
result <- checkSchema backend db ignoreAll
275+
if HS.null $ missingPredicates result
276+
then pure VerificationSucceeded
277+
else pure $ VerificationFailed $ HS.toList $ missingPredicates result
278+
279+
-- | Result type for 'checkSchema'
280+
data CheckResult = CheckResult
281+
{ -- | Expected predicates from the 'CheckedDatabaseSettings' which were not
282+
-- found in the live database
283+
missingPredicates :: HS.HashSet SomeDatabasePredicate
284+
, -- | Predicates found in the live database which are not present in the
285+
-- 'CheckedDatabaseSettings' and are not ignored
286+
unexpectedPredicates :: HS.HashSet SomeDatabasePredicate
287+
} deriving (Eq, Show)
288+
289+
-- | Selects a class of predicates to ignore if detected (e.g. metadata tables
290+
-- for migrations, other schemas, etc.).
291+
newtype IgnorePredicates = IgnorePredicates
292+
{ unIgnorePredicates :: SomeDatabasePredicate -> Any
293+
} deriving (Semigroup, Monoid)
294+
295+
-- | Ignore predicates relating to tables matching the given name predicate.
296+
ignoreTables :: (QualifiedName -> Bool) -> IgnorePredicates
297+
ignoreTables shouldIgnore = IgnorePredicates $ \(SomeDatabasePredicate dp) ->
298+
case cast dp of
299+
Just (TableExistsPredicate name) -> Any $ shouldIgnore name
300+
Nothing -> Any False
301+
302+
-- | Ignore any unknown predicates. This probably only makes sense to use if
303+
-- you are only querying and not writing to the database.
304+
ignoreAll :: IgnorePredicates
305+
ignoreAll = IgnorePredicates $ const $ Any True
306+
307+
-- | Checks the given database settings against the live database. This is
308+
-- similar to 'verifySchema', but detects and returns unknown predicates that
309+
-- are true about the live database (e.g. unknown tables, fields, etc.).
310+
checkSchema
311+
:: (Database be db, Monad m)
312+
=> BeamMigrationBackend be m
313+
-> CheckedDatabaseSettings be db
314+
-> IgnorePredicates
315+
-> m CheckResult
316+
checkSchema backend db (IgnorePredicates ignore) = do
317+
actual <- HS.fromList <$> backendGetDbConstraints backend
318+
let expected = HS.fromList $ collectChecks db
319+
missing = expected `HS.difference` actual
320+
extra = actual `HS.difference` expected
321+
ignored = HS.filter (getAny . ignore) extra
322+
unexpected = flip HS.filter extra $ \sdp@(SomeDatabasePredicate dp) ->
323+
not $ or
324+
[ sdp `HS.member` ignored
325+
, or $ HS.toList ignored <&> \(SomeDatabasePredicate ignoredDp) ->
326+
dp `predicateCascadesDropOn` ignoredDp
327+
]
328+
329+
return $ CheckResult
330+
{ missingPredicates = missing
331+
, unexpectedPredicates = unexpected
332+
}
271333

272334
-- | Run a sequence of commands on a database
273-
274335
runSimpleMigration :: MonadBeam be m
275336
=> (forall a. hdl -> m a -> IO a)
276337
-> hdl -> [BeamSqlBackendSyntax be] -> IO ()

0 commit comments

Comments
 (0)