{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE CPP #-}

-- | Defines common 'DatabasePredicate's that are shared among backends
module Database.Beam.Migrate.Checks where

import Database.Beam.Backend.SQL.SQL92
import Database.Beam.Migrate.SQL.SQL92
import Database.Beam.Migrate.SQL.Types
import Database.Beam.Migrate.Serialization
import Database.Beam.Migrate.Types.Predicates

import Data.Aeson ((.:), (.=), withObject, object)
import Data.Aeson.Types (Parser, Value)
import Data.Hashable (Hashable(..))
import Data.Text (Text)
import Data.Typeable (Typeable, cast)
#if !MIN_VERSION_base(4, 11, 0)
import Data.Semigroup
#endif

import GHC.Generics (Generic)

-- * Table checks

-- | Asserts that a table with the given name exists in a database
data TableExistsPredicate = TableExistsPredicate QualifiedName {-^ Table name -}
  deriving (Int -> TableExistsPredicate -> ShowS
[TableExistsPredicate] -> ShowS
TableExistsPredicate -> String
(Int -> TableExistsPredicate -> ShowS)
-> (TableExistsPredicate -> String)
-> ([TableExistsPredicate] -> ShowS)
-> Show TableExistsPredicate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableExistsPredicate] -> ShowS
$cshowList :: [TableExistsPredicate] -> ShowS
show :: TableExistsPredicate -> String
$cshow :: TableExistsPredicate -> String
showsPrec :: Int -> TableExistsPredicate -> ShowS
$cshowsPrec :: Int -> TableExistsPredicate -> ShowS
Show, TableExistsPredicate -> TableExistsPredicate -> Bool
(TableExistsPredicate -> TableExistsPredicate -> Bool)
-> (TableExistsPredicate -> TableExistsPredicate -> Bool)
-> Eq TableExistsPredicate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableExistsPredicate -> TableExistsPredicate -> Bool
$c/= :: TableExistsPredicate -> TableExistsPredicate -> Bool
== :: TableExistsPredicate -> TableExistsPredicate -> Bool
$c== :: TableExistsPredicate -> TableExistsPredicate -> Bool
Eq, Eq TableExistsPredicate
Eq TableExistsPredicate
-> (TableExistsPredicate -> TableExistsPredicate -> Ordering)
-> (TableExistsPredicate -> TableExistsPredicate -> Bool)
-> (TableExistsPredicate -> TableExistsPredicate -> Bool)
-> (TableExistsPredicate -> TableExistsPredicate -> Bool)
-> (TableExistsPredicate -> TableExistsPredicate -> Bool)
-> (TableExistsPredicate
    -> TableExistsPredicate -> TableExistsPredicate)
-> (TableExistsPredicate
    -> TableExistsPredicate -> TableExistsPredicate)
-> Ord TableExistsPredicate
TableExistsPredicate -> TableExistsPredicate -> Bool
TableExistsPredicate -> TableExistsPredicate -> Ordering
TableExistsPredicate
-> TableExistsPredicate -> TableExistsPredicate
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TableExistsPredicate
-> TableExistsPredicate -> TableExistsPredicate
$cmin :: TableExistsPredicate
-> TableExistsPredicate -> TableExistsPredicate
max :: TableExistsPredicate
-> TableExistsPredicate -> TableExistsPredicate
$cmax :: TableExistsPredicate
-> TableExistsPredicate -> TableExistsPredicate
>= :: TableExistsPredicate -> TableExistsPredicate -> Bool
$c>= :: TableExistsPredicate -> TableExistsPredicate -> Bool
> :: TableExistsPredicate -> TableExistsPredicate -> Bool
$c> :: TableExistsPredicate -> TableExistsPredicate -> Bool
<= :: TableExistsPredicate -> TableExistsPredicate -> Bool
$c<= :: TableExistsPredicate -> TableExistsPredicate -> Bool
< :: TableExistsPredicate -> TableExistsPredicate -> Bool
$c< :: TableExistsPredicate -> TableExistsPredicate -> Bool
compare :: TableExistsPredicate -> TableExistsPredicate -> Ordering
$ccompare :: TableExistsPredicate -> TableExistsPredicate -> Ordering
$cp1Ord :: Eq TableExistsPredicate
Ord, Typeable, (forall x. TableExistsPredicate -> Rep TableExistsPredicate x)
-> (forall x. Rep TableExistsPredicate x -> TableExistsPredicate)
-> Generic TableExistsPredicate
forall x. Rep TableExistsPredicate x -> TableExistsPredicate
forall x. TableExistsPredicate -> Rep TableExistsPredicate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableExistsPredicate x -> TableExistsPredicate
$cfrom :: forall x. TableExistsPredicate -> Rep TableExistsPredicate x
Generic)
instance Hashable TableExistsPredicate
instance DatabasePredicate TableExistsPredicate where
  englishDescription :: TableExistsPredicate -> String
englishDescription (TableExistsPredicate QualifiedName
t) =
    String
"Table " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> QualifiedName -> String
forall a. Show a => a -> String
show QualifiedName
t String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" must exist"

  serializePredicate :: TableExistsPredicate -> Value
serializePredicate (TableExistsPredicate QualifiedName
t) =
    [Pair] -> Value
object [ Text
"table-exists" Text -> QualifiedName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= QualifiedName
t ]

  predicateSpecificity :: proxy TableExistsPredicate -> PredicateSpecificity
predicateSpecificity proxy TableExistsPredicate
_ = PredicateSpecificity
PredicateSpecificityAllBackends

-- | A class that can check whether a particular data type is present
-- in a set of preconditions.
class HasDataTypeCreatedCheck dataType where
  dataTypeHasBeenCreated :: dataType -> (forall preCondition. Typeable preCondition => [ preCondition ]) -> Bool

-- | Asserts that the table specified has a column with the given data type. The
-- type paramater @syntax@ should be an instance of 'IsSql92ColumnSchemaSyntax'.
data TableHasColumn be where
  TableHasColumn
    :: ( HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be) )
    => { TableHasColumn be -> QualifiedName
hasColumn_table  :: QualifiedName {-^ Table name -}
       , TableHasColumn be -> Text
hasColumn_column :: Text {-^ Column name -}
       , TableHasColumn be -> BeamMigrateSqlBackendDataTypeSyntax be
hasColumn_type   :: BeamMigrateSqlBackendDataTypeSyntax be {-^ Data type -}
       }
    -> TableHasColumn be
instance Hashable (BeamMigrateSqlBackendDataTypeSyntax be) => Hashable (TableHasColumn be) where
  hashWithSalt :: Int -> TableHasColumn be -> Int
hashWithSalt Int
salt (TableHasColumn QualifiedName
t Text
c BeamMigrateSqlBackendDataTypeSyntax be
s) = Int
-> (QualifiedName, Text, BeamMigrateSqlBackendDataTypeSyntax be)
-> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (QualifiedName
t, Text
c, BeamMigrateSqlBackendDataTypeSyntax be
s)
instance Eq (BeamMigrateSqlBackendDataTypeSyntax be) => Eq (TableHasColumn be) where
  TableHasColumn QualifiedName
aTbl Text
aCol BeamMigrateSqlBackendDataTypeSyntax be
aDt == :: TableHasColumn be -> TableHasColumn be -> Bool
== TableHasColumn QualifiedName
bTbl Text
bCol BeamMigrateSqlBackendDataTypeSyntax be
bDt =
    QualifiedName
aTbl QualifiedName -> QualifiedName -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName
bTbl Bool -> Bool -> Bool
&& Text
aCol Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
bCol Bool -> Bool -> Bool
&& BeamMigrateSqlBackendDataTypeSyntax be
aDt BeamMigrateSqlBackendDataTypeSyntax be
-> BeamMigrateSqlBackendDataTypeSyntax be -> Bool
forall a. Eq a => a -> a -> Bool
== BeamMigrateSqlBackendDataTypeSyntax be
bDt
instance ( Typeable be
         , BeamMigrateOnlySqlBackend be
         , Hashable (BeamMigrateSqlBackendDataTypeSyntax be) ) =>
  DatabasePredicate (TableHasColumn be) where
  englishDescription :: TableHasColumn be -> String
englishDescription (TableHasColumn QualifiedName
tbl Text
col BeamMigrateSqlBackendDataTypeSyntax be
type_) =
    String
"Table " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> QualifiedName -> String
forall a. Show a => a -> String
show QualifiedName
tbl String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" must have a column " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
col String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" of " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> BeamMigrateSqlBackendDataTypeSyntax be -> String
forall syntax. Sql92DisplaySyntax syntax => syntax -> String
displaySyntax BeamMigrateSqlBackendDataTypeSyntax be
type_

  predicateSpecificity :: proxy (TableHasColumn be) -> PredicateSpecificity
predicateSpecificity proxy (TableHasColumn be)
_ = PredicateSpecificity
PredicateSpecificityAllBackends

  serializePredicate :: TableHasColumn be -> Value
serializePredicate (TableHasColumn QualifiedName
tbl Text
col BeamMigrateSqlBackendDataTypeSyntax be
type_) =
    [Pair] -> Value
object [ Text
"has-column" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object [ Text
"table" Text -> QualifiedName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= QualifiedName
tbl, Text
"column" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
col
                                    , Text
"type" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= BeamMigrateSqlBackendDataTypeSyntax be -> Value
forall dataType.
Sql92SerializableDataTypeSyntax dataType =>
dataType -> Value
serializeDataType BeamMigrateSqlBackendDataTypeSyntax be
type_ ]]

  predicateCascadesDropOn :: TableHasColumn be -> p' -> Bool
predicateCascadesDropOn (TableHasColumn QualifiedName
tblNm Text
_ BeamMigrateSqlBackendDataTypeSyntax be
_) p'
p'
    | Just (TableExistsPredicate QualifiedName
tblNm') <- p' -> Maybe TableExistsPredicate
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast p'
p' = QualifiedName
tblNm' QualifiedName -> QualifiedName -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName
tblNm
    | Bool
otherwise = Bool
False

-- | Asserts that a particular column of a table has a given constraint. The
-- @syntax@ type parameter should be an instance of 'IsSql92ColumnSchemaSyntax'
data TableColumnHasConstraint be
  = TableColumnHasConstraint
  { TableColumnHasConstraint be -> QualifiedName
hasConstraint_table  :: QualifiedName {-^ Table name -}
  , TableColumnHasConstraint be -> Text
hasConstraint_column :: Text {-^ Column name -}
  , TableColumnHasConstraint be
-> BeamSqlBackendColumnConstraintDefinitionSyntax be
hasConstraint_defn   :: BeamSqlBackendColumnConstraintDefinitionSyntax be {-^ Constraint definition -}
  } deriving (forall x.
 TableColumnHasConstraint be -> Rep (TableColumnHasConstraint be) x)
-> (forall x.
    Rep (TableColumnHasConstraint be) x -> TableColumnHasConstraint be)
-> Generic (TableColumnHasConstraint be)
forall x.
Rep (TableColumnHasConstraint be) x -> TableColumnHasConstraint be
forall x.
TableColumnHasConstraint be -> Rep (TableColumnHasConstraint be) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall be x.
Rep (TableColumnHasConstraint be) x -> TableColumnHasConstraint be
forall be x.
TableColumnHasConstraint be -> Rep (TableColumnHasConstraint be) x
$cto :: forall be x.
Rep (TableColumnHasConstraint be) x -> TableColumnHasConstraint be
$cfrom :: forall be x.
TableColumnHasConstraint be -> Rep (TableColumnHasConstraint be) x
Generic
instance Hashable (BeamSqlBackendColumnConstraintDefinitionSyntax be) => Hashable (TableColumnHasConstraint be)
deriving instance Eq (BeamSqlBackendColumnConstraintDefinitionSyntax be) => Eq (TableColumnHasConstraint be)
instance ( Typeable be, BeamMigrateOnlySqlBackend be
         , Hashable (BeamSqlBackendColumnConstraintDefinitionSyntax be) ) =>
         DatabasePredicate (TableColumnHasConstraint be) where
  englishDescription :: TableColumnHasConstraint be -> String
englishDescription (TableColumnHasConstraint QualifiedName
tbl Text
col BeamSqlBackendColumnConstraintDefinitionSyntax be
cns) =
    String
"Column " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> QualifiedName -> String
forall a. Show a => a -> String
show QualifiedName
tbl String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"." String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Text -> String
forall a. Show a => a -> String
show Text
col String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" has constraint " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> BeamSqlBackendColumnConstraintDefinitionSyntax be -> String
forall syntax. Sql92DisplaySyntax syntax => syntax -> String
displaySyntax BeamSqlBackendColumnConstraintDefinitionSyntax be
cns

  predicateSpecificity :: proxy (TableColumnHasConstraint be) -> PredicateSpecificity
predicateSpecificity proxy (TableColumnHasConstraint be)
_ = PredicateSpecificity
PredicateSpecificityAllBackends
  serializePredicate :: TableColumnHasConstraint be -> Value
serializePredicate (TableColumnHasConstraint QualifiedName
tbl Text
col BeamSqlBackendColumnConstraintDefinitionSyntax be
cns) =
    [Pair] -> Value
object [ Text
"has-column-constraint" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object [ Text
"table" Text -> QualifiedName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= QualifiedName
tbl, Text
"column" Text -> Text -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= Text
col
                                               , Text
"constraint" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= BeamSqlBackendColumnConstraintDefinitionSyntax be -> Value
forall constraint.
Sql92SerializableConstraintDefinitionSyntax constraint =>
constraint -> Value
serializeConstraint BeamSqlBackendColumnConstraintDefinitionSyntax be
cns ] ]

  predicateCascadesDropOn :: TableColumnHasConstraint be -> p' -> Bool
predicateCascadesDropOn (TableColumnHasConstraint QualifiedName
tblNm Text
colNm BeamSqlBackendColumnConstraintDefinitionSyntax be
_) p'
p'
    | Just (TableExistsPredicate QualifiedName
tblNm') <- p' -> Maybe TableExistsPredicate
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast p'
p' = QualifiedName
tblNm' QualifiedName -> QualifiedName -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName
tblNm
    | Just (TableHasColumn QualifiedName
tblNm' Text
colNm' BeamMigrateSqlBackendDataTypeSyntax be
_ :: TableHasColumn be) <- p' -> Maybe (TableHasColumn be)
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast p'
p' = QualifiedName
tblNm' QualifiedName -> QualifiedName -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName
tblNm Bool -> Bool -> Bool
&& Text
colNm' Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
colNm
    | Bool
otherwise = Bool
False

-- | Asserts that the given table has a primary key made of the given columns.
-- The order of the columns is significant.
data TableHasPrimaryKey
  = TableHasPrimaryKey
  { TableHasPrimaryKey -> QualifiedName
hasPrimaryKey_table :: QualifiedName   {-^ Table name -}
  , TableHasPrimaryKey -> [Text]
hasPrimaryKey_cols  :: [Text] {-^ Column names -}
  } deriving (Int -> TableHasPrimaryKey -> ShowS
[TableHasPrimaryKey] -> ShowS
TableHasPrimaryKey -> String
(Int -> TableHasPrimaryKey -> ShowS)
-> (TableHasPrimaryKey -> String)
-> ([TableHasPrimaryKey] -> ShowS)
-> Show TableHasPrimaryKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TableHasPrimaryKey] -> ShowS
$cshowList :: [TableHasPrimaryKey] -> ShowS
show :: TableHasPrimaryKey -> String
$cshow :: TableHasPrimaryKey -> String
showsPrec :: Int -> TableHasPrimaryKey -> ShowS
$cshowsPrec :: Int -> TableHasPrimaryKey -> ShowS
Show, TableHasPrimaryKey -> TableHasPrimaryKey -> Bool
(TableHasPrimaryKey -> TableHasPrimaryKey -> Bool)
-> (TableHasPrimaryKey -> TableHasPrimaryKey -> Bool)
-> Eq TableHasPrimaryKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TableHasPrimaryKey -> TableHasPrimaryKey -> Bool
$c/= :: TableHasPrimaryKey -> TableHasPrimaryKey -> Bool
== :: TableHasPrimaryKey -> TableHasPrimaryKey -> Bool
$c== :: TableHasPrimaryKey -> TableHasPrimaryKey -> Bool
Eq, (forall x. TableHasPrimaryKey -> Rep TableHasPrimaryKey x)
-> (forall x. Rep TableHasPrimaryKey x -> TableHasPrimaryKey)
-> Generic TableHasPrimaryKey
forall x. Rep TableHasPrimaryKey x -> TableHasPrimaryKey
forall x. TableHasPrimaryKey -> Rep TableHasPrimaryKey x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TableHasPrimaryKey x -> TableHasPrimaryKey
$cfrom :: forall x. TableHasPrimaryKey -> Rep TableHasPrimaryKey x
Generic)
instance Hashable TableHasPrimaryKey
instance DatabasePredicate TableHasPrimaryKey where
  englishDescription :: TableHasPrimaryKey -> String
englishDescription (TableHasPrimaryKey QualifiedName
tblName [Text]
colNames) =
    String
"Table " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> QualifiedName -> String
forall a. Show a => a -> String
show QualifiedName
tblName String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
" has primary key " String -> ShowS
forall a. Semigroup a => a -> a -> a
<> [Text] -> String
forall a. Show a => a -> String
show [Text]
colNames

  predicateSpecificity :: proxy TableHasPrimaryKey -> PredicateSpecificity
predicateSpecificity proxy TableHasPrimaryKey
_ = PredicateSpecificity
PredicateSpecificityAllBackends

  serializePredicate :: TableHasPrimaryKey -> Value
serializePredicate (TableHasPrimaryKey QualifiedName
tbl [Text]
cols) =
    [Pair] -> Value
object [ Text
"has-primary-key" Text -> Value -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Pair] -> Value
object [ Text
"table" Text -> QualifiedName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= QualifiedName
tbl
                                         , Text
"columns" Text -> [Text] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Text -> v -> kv
.= [Text]
cols ] ]

  predicateCascadesDropOn :: TableHasPrimaryKey -> p' -> Bool
predicateCascadesDropOn (TableHasPrimaryKey QualifiedName
tblNm [Text]
_) p'
p'
    | Just (TableExistsPredicate QualifiedName
tblNm') <- p' -> Maybe TableExistsPredicate
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast p'
p' = QualifiedName
tblNm' QualifiedName -> QualifiedName -> Bool
forall a. Eq a => a -> a -> Bool
== QualifiedName
tblNm
    | Bool
otherwise = Bool
False

-- * Deserialization

-- | 'BeamDeserializers' for all the predicates defined in this module
beamCheckDeserializers
  :: forall be
   . ( Typeable be, BeamMigrateOnlySqlBackend be
     , HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be) )
  => BeamDeserializers be
beamCheckDeserializers :: BeamDeserializers be
beamCheckDeserializers = [BeamDeserializers be] -> BeamDeserializers be
forall a. Monoid a => [a] -> a
mconcat
  [ (forall be'.
 BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate)
-> BeamDeserializers be
forall ty be.
Typeable ty =>
(forall be'. BeamDeserializers be' -> Value -> Parser ty)
-> BeamDeserializers be
beamDeserializer ((Value -> Parser SomeDatabasePredicate)
-> BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate
forall a b. a -> b -> a
const Value -> Parser SomeDatabasePredicate
deserializeTableExistsPredicate)
  , (forall be'.
 BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate)
-> BeamDeserializers be
forall ty be.
Typeable ty =>
(forall be'. BeamDeserializers be' -> Value -> Parser ty)
-> BeamDeserializers be
beamDeserializer ((Value -> Parser SomeDatabasePredicate)
-> BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate
forall a b. a -> b -> a
const Value -> Parser SomeDatabasePredicate
deserializeTableHasPrimaryKeyPredicate)
  , (forall be'.
 BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate)
-> BeamDeserializers be
forall ty be.
Typeable ty =>
(forall be'. BeamDeserializers be' -> Value -> Parser ty)
-> BeamDeserializers be
beamDeserializer forall be'.
BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate
deserializeTableHasColumnPredicate
  , (forall be'.
 BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate)
-> BeamDeserializers be
forall ty be.
Typeable ty =>
(forall be'. BeamDeserializers be' -> Value -> Parser ty)
-> BeamDeserializers be
beamDeserializer forall be'.
BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate
deserializeTableColumnHasConstraintPredicate
  ]
  where
    deserializeTableExistsPredicate :: Value -> Parser SomeDatabasePredicate
    deserializeTableExistsPredicate :: Value -> Parser SomeDatabasePredicate
deserializeTableExistsPredicate =
      String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableExistPredicate" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v ->
      TableExistsPredicate -> SomeDatabasePredicate
forall p. DatabasePredicate p => p -> SomeDatabasePredicate
SomeDatabasePredicate (TableExistsPredicate -> SomeDatabasePredicate)
-> Parser TableExistsPredicate -> Parser SomeDatabasePredicate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QualifiedName -> TableExistsPredicate
TableExistsPredicate (QualifiedName -> TableExistsPredicate)
-> Parser QualifiedName -> Parser TableExistsPredicate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v Object -> Text -> Parser QualifiedName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"table-exists")

    deserializeTableHasPrimaryKeyPredicate :: Value -> Parser SomeDatabasePredicate
    deserializeTableHasPrimaryKeyPredicate :: Value -> Parser SomeDatabasePredicate
deserializeTableHasPrimaryKeyPredicate =
      String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableHasPrimaryKey" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v ->
      Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"has-primary-key" Parser Value
-> (Value -> Parser SomeDatabasePredicate)
-> Parser SomeDatabasePredicate
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      (String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableHasPrimaryKey" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v' ->
       TableHasPrimaryKey -> SomeDatabasePredicate
forall p. DatabasePredicate p => p -> SomeDatabasePredicate
SomeDatabasePredicate (TableHasPrimaryKey -> SomeDatabasePredicate)
-> Parser TableHasPrimaryKey -> Parser SomeDatabasePredicate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (QualifiedName -> [Text] -> TableHasPrimaryKey
TableHasPrimaryKey (QualifiedName -> [Text] -> TableHasPrimaryKey)
-> Parser QualifiedName -> Parser ([Text] -> TableHasPrimaryKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v' Object -> Text -> Parser QualifiedName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"table" Parser ([Text] -> TableHasPrimaryKey)
-> Parser [Text] -> Parser TableHasPrimaryKey
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v' Object -> Text -> Parser [Text]
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"columns"))

    deserializeTableHasColumnPredicate :: BeamDeserializers be'
                                       -> Value -> Parser SomeDatabasePredicate
    deserializeTableHasColumnPredicate :: BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate
deserializeTableHasColumnPredicate BeamDeserializers be'
d =
      String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableHasColumn" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v ->
      Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"has-column" Parser Value
-> (Value -> Parser SomeDatabasePredicate)
-> Parser SomeDatabasePredicate
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      (String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableHasColumn" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v' ->
       TableHasColumn be -> SomeDatabasePredicate
forall p. DatabasePredicate p => p -> SomeDatabasePredicate
SomeDatabasePredicate (TableHasColumn be -> SomeDatabasePredicate)
-> Parser (TableHasColumn be) -> Parser SomeDatabasePredicate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
       (TableHasColumn be -> TableHasColumn be)
-> Parser (TableHasColumn be) -> Parser (TableHasColumn be)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TableHasColumn be -> TableHasColumn be
forall a. a -> a
id @(TableHasColumn be))
         (QualifiedName
-> Text
-> Sql92ColumnSchemaColumnTypeSyntax
     (Sql92CreateTableColumnSchemaSyntax
        (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
-> TableHasColumn be
forall be.
HasDataTypeCreatedCheck (BeamMigrateSqlBackendDataTypeSyntax be) =>
QualifiedName
-> Text
-> BeamMigrateSqlBackendDataTypeSyntax be
-> TableHasColumn be
TableHasColumn (QualifiedName
 -> Text
 -> Sql92ColumnSchemaColumnTypeSyntax
      (Sql92CreateTableColumnSchemaSyntax
         (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
 -> TableHasColumn be)
-> Parser QualifiedName
-> Parser
     (Text
      -> Sql92ColumnSchemaColumnTypeSyntax
           (Sql92CreateTableColumnSchemaSyntax
              (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
      -> TableHasColumn be)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v' Object -> Text -> Parser QualifiedName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"table" Parser
  (Text
   -> Sql92ColumnSchemaColumnTypeSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
   -> TableHasColumn be)
-> Parser Text
-> Parser
     (Sql92ColumnSchemaColumnTypeSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
      -> TableHasColumn be)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v' Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"column"
                         Parser
  (Sql92ColumnSchemaColumnTypeSyntax
     (Sql92CreateTableColumnSchemaSyntax
        (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
   -> TableHasColumn be)
-> Parser
     (Sql92ColumnSchemaColumnTypeSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be))))
-> Parser (TableHasColumn be)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (BeamDeserializers be'
-> Value
-> Parser
     (Sql92ColumnSchemaColumnTypeSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be))))
forall a be.
Typeable a =>
BeamDeserializers be -> Value -> Parser a
beamDeserialize BeamDeserializers be'
d (Value
 -> Parser
      (Sql92ColumnSchemaColumnTypeSyntax
         (Sql92CreateTableColumnSchemaSyntax
            (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))))
-> Parser Value
-> Parser
     (Sql92ColumnSchemaColumnTypeSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be))))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v' Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"type")))

    deserializeTableColumnHasConstraintPredicate :: BeamDeserializers be'
                                                 -> Value -> Parser SomeDatabasePredicate
    deserializeTableColumnHasConstraintPredicate :: BeamDeserializers be' -> Value -> Parser SomeDatabasePredicate
deserializeTableColumnHasConstraintPredicate BeamDeserializers be'
d =
      String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableColumnHasConstraint" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v ->
      Object
v Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"has-column-constraint" Parser Value
-> (Value -> Parser SomeDatabasePredicate)
-> Parser SomeDatabasePredicate
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
      (String
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"TableColumnHasConstraint" ((Object -> Parser SomeDatabasePredicate)
 -> Value -> Parser SomeDatabasePredicate)
-> (Object -> Parser SomeDatabasePredicate)
-> Value
-> Parser SomeDatabasePredicate
forall a b. (a -> b) -> a -> b
$ \Object
v' ->
       TableColumnHasConstraint be -> SomeDatabasePredicate
forall p. DatabasePredicate p => p -> SomeDatabasePredicate
SomeDatabasePredicate (TableColumnHasConstraint be -> SomeDatabasePredicate)
-> Parser (TableColumnHasConstraint be)
-> Parser SomeDatabasePredicate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
       (TableColumnHasConstraint be -> TableColumnHasConstraint be)
-> Parser (TableColumnHasConstraint be)
-> Parser (TableColumnHasConstraint be)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TableColumnHasConstraint be -> TableColumnHasConstraint be
forall a. a -> a
id @(TableColumnHasConstraint be))
         (QualifiedName
-> Text
-> Sql92ColumnSchemaColumnConstraintDefinitionSyntax
     (Sql92CreateTableColumnSchemaSyntax
        (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
-> TableColumnHasConstraint be
forall be.
QualifiedName
-> Text
-> BeamSqlBackendColumnConstraintDefinitionSyntax be
-> TableColumnHasConstraint be
TableColumnHasConstraint (QualifiedName
 -> Text
 -> Sql92ColumnSchemaColumnConstraintDefinitionSyntax
      (Sql92CreateTableColumnSchemaSyntax
         (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
 -> TableColumnHasConstraint be)
-> Parser QualifiedName
-> Parser
     (Text
      -> Sql92ColumnSchemaColumnConstraintDefinitionSyntax
           (Sql92CreateTableColumnSchemaSyntax
              (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
      -> TableColumnHasConstraint be)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Object
v' Object -> Text -> Parser QualifiedName
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"table" Parser
  (Text
   -> Sql92ColumnSchemaColumnConstraintDefinitionSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
   -> TableColumnHasConstraint be)
-> Parser Text
-> Parser
     (Sql92ColumnSchemaColumnConstraintDefinitionSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
      -> TableColumnHasConstraint be)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Object
v' Object -> Text -> Parser Text
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"column"
                                   Parser
  (Sql92ColumnSchemaColumnConstraintDefinitionSyntax
     (Sql92CreateTableColumnSchemaSyntax
        (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))
   -> TableColumnHasConstraint be)
-> Parser
     (Sql92ColumnSchemaColumnConstraintDefinitionSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be))))
-> Parser (TableColumnHasConstraint be)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (BeamDeserializers be'
-> Value
-> Parser
     (Sql92ColumnSchemaColumnConstraintDefinitionSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be))))
forall a be.
Typeable a =>
BeamDeserializers be -> Value -> Parser a
beamDeserialize BeamDeserializers be'
d (Value
 -> Parser
      (Sql92ColumnSchemaColumnConstraintDefinitionSyntax
         (Sql92CreateTableColumnSchemaSyntax
            (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be)))))
-> Parser Value
-> Parser
     (Sql92ColumnSchemaColumnConstraintDefinitionSyntax
        (Sql92CreateTableColumnSchemaSyntax
           (Sql92DdlCommandCreateTableSyntax (BeamSqlBackendSyntax be))))
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Object
v' Object -> Text -> Parser Value
forall a. FromJSON a => Object -> Text -> Parser a
.: Text
"constraint")))