{-# LANGUAGE
AllowAmbiguousTypes
, ConstraintKinds
, DeriveAnyClass
, DeriveGeneric
, DerivingStrategies
, FlexibleContexts
, FlexibleInstances
, GADTs
, LambdaCase
, MultiParamTypeClasses
, OverloadedLabels
, OverloadedStrings
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeInType
, TypeOperators
, UndecidableSuperClasses
#-}
module Squeal.PostgreSQL.Definition.View
(
createView
, createOrReplaceView
, dropView
, dropViewIfExists
, alterViewRename
, alterViewSetSchema
) where
import GHC.TypeLits
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Definition
import Squeal.PostgreSQL.Query
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
createView
:: (Has sch db schema, KnownSymbol vw)
=> QualifiedAlias sch vw
-> Query '[] '[] db '[] view
-> Definition db (Alter sch (Create vw ('View view) schema) db)
createView :: QualifiedAlias sch vw
-> Query '[] '[] db '[] view
-> Definition db (Alter sch (Create vw ('View view) schema) db)
createView QualifiedAlias sch vw
alias Query '[] '[] db '[] view
query = ByteString
-> Definition db (Alter sch (Create vw ('View view) schema) db)
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition (ByteString
-> Definition db (Alter sch (Create vw ('View view) schema) db))
-> ByteString
-> Definition db (Alter sch (Create vw ('View view) schema) db)
forall a b. (a -> b) -> a -> b
$
ByteString
"CREATE" ByteString -> ByteString -> ByteString
<+> ByteString
"VIEW" ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch vw -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch vw
alias ByteString -> ByteString -> ByteString
<+> ByteString
"AS"
ByteString -> ByteString -> ByteString
<+> Query '[] '[] db '[] view -> ByteString
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (row :: RowType).
Query lat with db params row -> ByteString
renderQuery Query '[] '[] db '[] view
query ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
";"
createOrReplaceView
:: (Has sch db schema, KnownSymbol vw)
=> QualifiedAlias sch vw
-> Query '[] '[] db '[] view
-> Definition db (Alter sch (CreateOrReplace vw ('View view) schema) db)
createOrReplaceView :: QualifiedAlias sch vw
-> Query '[] '[] db '[] view
-> Definition
db (Alter sch (CreateOrReplace vw ('View view) schema) db)
createOrReplaceView QualifiedAlias sch vw
alias Query '[] '[] db '[] view
query = ByteString
-> Definition
db (Alter sch (CreateOrReplace vw ('View view) schema) db)
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition (ByteString
-> Definition
db (Alter sch (CreateOrReplace vw ('View view) schema) db))
-> ByteString
-> Definition
db (Alter sch (CreateOrReplace vw ('View view) schema) db)
forall a b. (a -> b) -> a -> b
$
ByteString
"CREATE OR REPLACE VIEW" ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch vw -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch vw
alias ByteString -> ByteString -> ByteString
<+> ByteString
"AS"
ByteString -> ByteString -> ByteString
<+> Query '[] '[] db '[] view -> ByteString
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (row :: RowType).
Query lat with db params row -> ByteString
renderQuery Query '[] '[] db '[] view
query ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
";"
dropView
:: (Has sch db schema, KnownSymbol vw)
=> QualifiedAlias sch vw
-> Definition db (Alter sch (DropSchemum vw 'View schema) db)
dropView :: QualifiedAlias sch vw
-> Definition db (Alter sch (DropSchemum vw 'View schema) db)
dropView QualifiedAlias sch vw
vw = ByteString
-> Definition db (Alter sch (DropSchemum vw 'View schema) db)
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition (ByteString
-> Definition db (Alter sch (DropSchemum vw 'View schema) db))
-> ByteString
-> Definition db (Alter sch (DropSchemum vw 'View schema) db)
forall a b. (a -> b) -> a -> b
$ ByteString
"DROP VIEW" ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch vw -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch vw
vw ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
";"
dropViewIfExists
:: (Has sch db schema, KnownSymbol vw)
=> QualifiedAlias sch vw
-> Definition db (Alter sch (DropIfExists vw schema) db)
dropViewIfExists :: QualifiedAlias sch vw
-> Definition db (Alter sch (DropIfExists vw schema) db)
dropViewIfExists QualifiedAlias sch vw
vw = ByteString -> Definition db (Alter sch (DropIfExists vw schema) db)
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition (ByteString
-> Definition db (Alter sch (DropIfExists vw schema) db))
-> ByteString
-> Definition db (Alter sch (DropIfExists vw schema) db)
forall a b. (a -> b) -> a -> b
$
ByteString
"DROP VIEW IF EXISTS" ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch vw -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch vw
vw ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
";"
alterViewRename
:: ( Has sch db schema
, KnownSymbol ty1
, Has ty0 schema ('View vw))
=> QualifiedAlias sch ty0
-> Alias ty1
-> Definition db (Alter sch (Rename ty0 ty1 schema) db )
alterViewRename :: QualifiedAlias sch ty0
-> Alias ty1
-> Definition db (Alter sch (Rename ty0 ty1 schema) db)
alterViewRename QualifiedAlias sch ty0
vw0 Alias ty1
vw1 = ByteString -> Definition db (Alter sch (Rename ty0 ty1 schema) db)
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition (ByteString
-> Definition db (Alter sch (Rename ty0 ty1 schema) db))
-> ByteString
-> Definition db (Alter sch (Rename ty0 ty1 schema) db)
forall a b. (a -> b) -> a -> b
$
ByteString
"ALTER VIEW" ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch ty0 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch ty0
vw0
ByteString -> ByteString -> ByteString
<+> ByteString
"RENAME TO" ByteString -> ByteString -> ByteString
<+> Alias ty1 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias ty1
vw1 ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
";"
alterViewSetSchema
:: ( Has sch0 db schema0
, Has vw schema0 ('View view)
, Has sch1 db schema1 )
=> QualifiedAlias sch0 vw
-> Alias sch1
-> Definition db (SetSchema sch0 sch1 schema0 schema1 vw 'View view db)
alterViewSetSchema :: QualifiedAlias sch0 vw
-> Alias sch1
-> Definition
db (SetSchema sch0 sch1 schema0 schema1 vw 'View view db)
alterViewSetSchema QualifiedAlias sch0 vw
ty Alias sch1
sch = ByteString
-> Definition
db
(Alter
sch1
(Create vw ('View view) schema1)
(Alter sch0 (DropSchemum vw 'View schema0) db))
forall (db0 :: SchemasType) (db1 :: SchemasType).
ByteString -> Definition db0 db1
UnsafeDefinition (ByteString
-> Definition
db
(Alter
sch1
(Create vw ('View view) schema1)
(Alter sch0 (DropSchemum vw 'View schema0) db)))
-> ByteString
-> Definition
db
(Alter
sch1
(Create vw ('View view) schema1)
(Alter sch0 (DropSchemum vw 'View schema0) db))
forall a b. (a -> b) -> a -> b
$
ByteString
"ALTER VIEW" ByteString -> ByteString -> ByteString
<+> QualifiedAlias sch0 vw -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL QualifiedAlias sch0 vw
ty ByteString -> ByteString -> ByteString
<+> ByteString
"SET SCHEMA" ByteString -> ByteString -> ByteString
<+> Alias sch1 -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias sch1
sch ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
";"