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