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