{-# LANGUAGE DeriveGeneric, DerivingVia, DeriveAnyClass #-}
module ProjectM36.SQL.CreateTable where
import ProjectM36.SQL.Select
import Control.DeepSeq
import Codec.Winery
import GHC.Generics
data CreateTable = CreateTable
{ CreateTable -> TableName
target :: TableName,
CreateTable
-> [(UnqualifiedColumnName, ColumnType, PerColumnConstraints)]
targetColumns :: [(UnqualifiedColumnName, ColumnType, PerColumnConstraints)]
}
deriving (Int -> CreateTable -> ShowS
[CreateTable] -> ShowS
CreateTable -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateTable] -> ShowS
$cshowList :: [CreateTable] -> ShowS
show :: CreateTable -> String
$cshow :: CreateTable -> String
showsPrec :: Int -> CreateTable -> ShowS
$cshowsPrec :: Int -> CreateTable -> ShowS
Show, CreateTable -> CreateTable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateTable -> CreateTable -> Bool
$c/= :: CreateTable -> CreateTable -> Bool
== :: CreateTable -> CreateTable -> Bool
$c== :: CreateTable -> CreateTable -> Bool
Eq, forall x. Rep CreateTable x -> CreateTable
forall x. CreateTable -> Rep CreateTable x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateTable x -> CreateTable
$cfrom :: forall x. CreateTable -> Rep CreateTable x
Generic, CreateTable -> ()
forall a. (a -> ()) -> NFData a
rnf :: CreateTable -> ()
$crnf :: CreateTable -> ()
NFData)
deriving Typeable CreateTable
BundleSerialise CreateTable
Extractor CreateTable
Decoder CreateTable
Proxy CreateTable -> SchemaGen Schema
CreateTable -> Builder
forall a.
Typeable a
-> (Proxy a -> SchemaGen Schema)
-> (a -> Builder)
-> Extractor a
-> Decoder a
-> BundleSerialise a
-> Serialise a
bundleSerialise :: BundleSerialise CreateTable
$cbundleSerialise :: BundleSerialise CreateTable
decodeCurrent :: Decoder CreateTable
$cdecodeCurrent :: Decoder CreateTable
extractor :: Extractor CreateTable
$cextractor :: Extractor CreateTable
toBuilder :: CreateTable -> Builder
$ctoBuilder :: CreateTable -> Builder
schemaGen :: Proxy CreateTable -> SchemaGen Schema
$cschemaGen :: Proxy CreateTable -> SchemaGen Schema
Serialise via WineryRecord CreateTable
data ColumnType =
IntegerColumnType |
TextColumnType |
BoolColumnType |
DoubleColumnType |
DateTimeColumnType |
DateColumnType |
ByteaColumnType
deriving (Int -> ColumnType -> ShowS
[ColumnType] -> ShowS
ColumnType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ColumnType] -> ShowS
$cshowList :: [ColumnType] -> ShowS
show :: ColumnType -> String
$cshow :: ColumnType -> String
showsPrec :: Int -> ColumnType -> ShowS
$cshowsPrec :: Int -> ColumnType -> ShowS
Show, ColumnType -> ColumnType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ColumnType -> ColumnType -> Bool
$c/= :: ColumnType -> ColumnType -> Bool
== :: ColumnType -> ColumnType -> Bool
$c== :: ColumnType -> ColumnType -> Bool
Eq, forall x. Rep ColumnType x -> ColumnType
forall x. ColumnType -> Rep ColumnType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ColumnType x -> ColumnType
$cfrom :: forall x. ColumnType -> Rep ColumnType x
Generic, ColumnType -> ()
forall a. (a -> ()) -> NFData a
rnf :: ColumnType -> ()
$crnf :: ColumnType -> ()
NFData)
deriving Typeable ColumnType
BundleSerialise ColumnType
Extractor ColumnType
Decoder ColumnType
Proxy ColumnType -> SchemaGen Schema
ColumnType -> Builder
forall a.
Typeable a
-> (Proxy a -> SchemaGen Schema)
-> (a -> Builder)
-> Extractor a
-> Decoder a
-> BundleSerialise a
-> Serialise a
bundleSerialise :: BundleSerialise ColumnType
$cbundleSerialise :: BundleSerialise ColumnType
decodeCurrent :: Decoder ColumnType
$cdecodeCurrent :: Decoder ColumnType
extractor :: Extractor ColumnType
$cextractor :: Extractor ColumnType
toBuilder :: ColumnType -> Builder
$ctoBuilder :: ColumnType -> Builder
schemaGen :: Proxy ColumnType -> SchemaGen Schema
$cschemaGen :: Proxy ColumnType -> SchemaGen Schema
Serialise via WineryVariant ColumnType
data PerColumnConstraints = PerColumnConstraints {
PerColumnConstraints -> Bool
notNullConstraint :: Bool,
PerColumnConstraints -> Bool
uniquenessConstraint :: Bool,
PerColumnConstraints -> Maybe (TableName, UnqualifiedColumnName)
references :: Maybe (TableName, UnqualifiedColumnName)
}
deriving (Int -> PerColumnConstraints -> ShowS
[PerColumnConstraints] -> ShowS
PerColumnConstraints -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PerColumnConstraints] -> ShowS
$cshowList :: [PerColumnConstraints] -> ShowS
show :: PerColumnConstraints -> String
$cshow :: PerColumnConstraints -> String
showsPrec :: Int -> PerColumnConstraints -> ShowS
$cshowsPrec :: Int -> PerColumnConstraints -> ShowS
Show, PerColumnConstraints -> PerColumnConstraints -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PerColumnConstraints -> PerColumnConstraints -> Bool
$c/= :: PerColumnConstraints -> PerColumnConstraints -> Bool
== :: PerColumnConstraints -> PerColumnConstraints -> Bool
$c== :: PerColumnConstraints -> PerColumnConstraints -> Bool
Eq, forall x. Rep PerColumnConstraints x -> PerColumnConstraints
forall x. PerColumnConstraints -> Rep PerColumnConstraints x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PerColumnConstraints x -> PerColumnConstraints
$cfrom :: forall x. PerColumnConstraints -> Rep PerColumnConstraints x
Generic, PerColumnConstraints -> ()
forall a. (a -> ()) -> NFData a
rnf :: PerColumnConstraints -> ()
$crnf :: PerColumnConstraints -> ()
NFData)
deriving Typeable PerColumnConstraints
BundleSerialise PerColumnConstraints
Extractor PerColumnConstraints
Decoder PerColumnConstraints
Proxy PerColumnConstraints -> SchemaGen Schema
PerColumnConstraints -> Builder
forall a.
Typeable a
-> (Proxy a -> SchemaGen Schema)
-> (a -> Builder)
-> Extractor a
-> Decoder a
-> BundleSerialise a
-> Serialise a
bundleSerialise :: BundleSerialise PerColumnConstraints
$cbundleSerialise :: BundleSerialise PerColumnConstraints
decodeCurrent :: Decoder PerColumnConstraints
$cdecodeCurrent :: Decoder PerColumnConstraints
extractor :: Extractor PerColumnConstraints
$cextractor :: Extractor PerColumnConstraints
toBuilder :: PerColumnConstraints -> Builder
$ctoBuilder :: PerColumnConstraints -> Builder
schemaGen :: Proxy PerColumnConstraints -> SchemaGen Schema
$cschemaGen :: Proxy PerColumnConstraints -> SchemaGen Schema
Serialise via WineryVariant PerColumnConstraints