-- Section 14 in Foundation {-# LANGUAGE OverloadedStrings #-} module Language.SQL.SimpleSQL.SQL2011DataManipulation (sql2011DataManipulationTests) where import Language.SQL.SimpleSQL.TestTypes import Language.SQL.SimpleSQL.Syntax sql2011DataManipulationTests :: TestItem sql2011DataManipulationTests = Group "sql 2011 data manipulation tests" [ {- 14 Data manipulation 14.1 ::= DECLARE FOR 14.2 ::= [ ] [ ] CURSOR [ ] [ ] ::= SENSITIVE | INSENSITIVE | ASENSITIVE ::= SCROLL | NO SCROLL ::= WITH HOLD | WITHOUT HOLD ::= WITH RETURN | WITHOUT RETURN 14.3 ::= [ ] ::= FOR { READ ONLY | UPDATE [ OF ] } 14.4 ::= OPEN 14.5 ::= FETCH [ [ ] FROM ] INTO ::= NEXT | PRIOR | FIRST | LAST | { ABSOLUTE | RELATIVE } ::= [ { }... ] 14.6 ::= CLOSE 14.7 ::= SELECT [ ]
| ONLY
14.9 ::= DELETE FROM [ FOR PORTION OF FROM TO ] [ [ AS ] ] [ WHERE ] -} (TestStatement ansi2011 "delete from t" $ Delete [Name Nothing "t"] Nothing Nothing) ,(TestStatement ansi2011 "delete from t as u" $ Delete [Name Nothing "t"] (Just (Name Nothing "u")) Nothing) ,(TestStatement ansi2011 "delete from t where x = 5" $ Delete [Name Nothing "t"] Nothing (Just $ BinOp (Iden [Name Nothing "x"]) [Name Nothing "="] (NumLit "5"))) ,(TestStatement ansi2011 "delete from t as u where u.x = 5" $ Delete [Name Nothing "t"] (Just (Name Nothing "u")) (Just $ BinOp (Iden [Name Nothing "u", Name Nothing "x"]) [Name Nothing "="] (NumLit "5"))) {- 14.10 ::= TRUNCATE TABLE [ ] ::= CONTINUE IDENTITY | RESTART IDENTITY -} ,(TestStatement ansi2011 "truncate table t" $ Truncate [Name Nothing "t"] DefaultIdentityRestart) ,(TestStatement ansi2011 "truncate table t continue identity" $ Truncate [Name Nothing "t"] ContinueIdentity) ,(TestStatement ansi2011 "truncate table t restart identity" $ Truncate [Name Nothing "t"] RestartIdentity) {- 14.11 ::= INSERT INTO ::=
::= | | ::= [ ] [ ] ::= [ ] [ ] ::= OVERRIDING USER VALUE | OVERRIDING SYSTEM VALUE ::= DEFAULT VALUES ::= -} ,(TestStatement ansi2011 "insert into t select * from u" $ Insert [Name Nothing "t"] Nothing $ InsertQuery $ toQueryExpr $ makeSelect {msSelectList = [(Star, Nothing)] ,msFrom = [TRSimple [Name Nothing "u"]]}) ,(TestStatement ansi2011 "insert into t(a,b,c) select * from u" $ Insert [Name Nothing "t"] (Just [Name Nothing "a", Name Nothing "b", Name Nothing "c"]) $ InsertQuery $ toQueryExpr $ makeSelect {msSelectList = [(Star, Nothing)] ,msFrom = [TRSimple [Name Nothing "u"]]}) ,(TestStatement ansi2011 "insert into t default values" $ Insert [Name Nothing "t"] Nothing DefaultInsertValues) ,(TestStatement ansi2011 "insert into t values(1,2)" $ Insert [Name Nothing "t"] Nothing $ InsertQuery $ Values [[NumLit "1", NumLit "2"]]) ,(TestStatement ansi2011 "insert into t values (1,2),(3,4)" $ Insert [Name Nothing "t"] Nothing $ InsertQuery $ Values [[NumLit "1", NumLit "2"] ,[NumLit "3", NumLit "4"]]) ,(TestStatement ansi2011 "insert into t values (default,null,array[],multiset[])" $ Insert [Name Nothing "t"] Nothing $ InsertQuery $ Values [[Iden [Name Nothing "default"] ,Iden [Name Nothing "null"] ,Array (Iden [Name Nothing "array"]) [] ,MultisetCtor []]]) {- 14.12 ::= MERGE INTO [ [ AS ] ] USING
ON merge into t using t on a = b merge operation specification merge into t as u using (table factor | joined expression) MERGE INTO tablename USING table_reference ON (condition) WHEN MATCHED THEN UPDATE SET column1 = value1 [, column2 = value2 ...] WHEN NOT MATCHED THEN INSERT (column1 [, column2 ...]) VALUES (value1 [, value2 ... merge into t23 using t42 on t42.id = t23.id when matched then update set t23.col1 = t42.col1 when not matched then insert (id, col1) values (t42.id, t42.col1) MERGE INTO TableA u USING (SELECT b.Key1, b.ColB1, c.ColC1 FROM TableB b INNER JOIN TableC c ON c.KeyC1 = b.KeyB1 ) s ON (u.KeyA1 = s.KeyA1) WHEN MATCHED THEN UPDATE SET u.ColA1 = s.ColB1, u.ColA2 = s.ColC1 MERGE INTO Department USING NewDept AS ND ON nd.Department_Number = Department. Department_Number WHEN MATCHED THEN UPDATE SET budget_amount = nd.Budget_Amount WHEN NOT MATCHED THEN INSERT VALUES (nd.Department_Number, nd.Department_ Name, nd.Budget_Amount, nd.Manager_Employee_Number); MERGE INTO Orders2 USING Orders3 ON ORDERS3.Order_Number = Orders2. Order_Number WHEN NOT MATCHED THEN INSERT Orders3.order_number, Orders3. invoice_number, Orders3.customer_number, Orders3. initial_order_date, Orders3.invoice_date, Orders3. invoice_amount); MERGE INTO Orders2 USING Orders3 ON ORDERS3.Order_Number = Orders2. Order_Number AND 1=0 WHEN NOT MATCHED THEN INSERT (Orders3.order_number, Orders3.invoice_number, Orders3.customer_number, Orders3. initial_order_date, Orders3.invoice_date, Orders3. invoice_amount); MERGE INTO Department USING NewDept AS ND ON nd.Department_Number = Department. Department_Number WHEN MATCHED THEN UPDATE SET budget_amount = nd.Budget_Amount LOGGING ALL ERRORS WITH NO LIMIT; MERGE INTO Department USING (SELECT Department_Number, department_name, Budget_Amount, Manager_Employee_Number FROM NewDept WHERE Department_Number IN (SELECT Department_Number FROM Employee)) AS m ON m.Department_Number = Department. Department_Number WHEN MATCHED THEN UPDATE SET budget_amount = m.Budget_Amount WHEN NOT MATCHED THEN INSERT (m.Department_Number, m.Department_ Name, m.Budget_Amount, m.Manager_Employee_Number) LOGGING ALL ERRORS WITH NO LIMIT; MERGE INTO Customers AS c USING Moved AS m ON m.SSN = c.SSN WHEN MATCHED THEN UPDATE SET Street = m.Street, HouseNo = m.HouseNo, City = m.City; MERGE INTO CentralOfficeAccounts AS C -- Target USING BranchOfficeAccounts AS B -- Source ON C.account_nbr = B.account_nbr WHEN MATCHED THEN -- On match update UPDATE SET C.company_name = B.company_name, C.primary_contact = B.primary_contact, C.contact_phone = B.contact_phone WHEN NOT MATCHED THEN -- Add missing INSERT (account_nbr, company_name, primary_contact, contact_phone) VALUES (B.account_nbr, B.company_name, B.primary_contact, B.contact_phone); SELECT account_nbr, company_name, primary_contact, contact_phone FROM CentralOfficeAccounts; MERGE INTO CentralOfficeAccounts AS C -- Target USING BranchOfficeAccounts AS B -- Source ON C.account_nbr = B.account_nbr WHEN MATCHED -- On match update AND (C.company_name <> B.company_name -- Additional search conditions OR C.primary_contact <> B.primary_contact OR C.contact_phone <> B.contact_phone) THEN UPDATE SET C.company_name = B.company_name, C.primary_contact = B.primary_contact, C.contact_phone = B.contact_phone WHEN NOT MATCHED THEN -- Add missing INSERT (account_nbr, company_name, primary_contact, contact_phone) VALUES (B.account_nbr, B.company_name, B.primary_contact, B.contact_phone); MERGE INTO CentralOfficeAccounts AS C -- Target USING BranchOfficeAccounts AS B -- Source ON C.account_nbr = B.account_nbr WHEN MATCHED -- On match update AND (C.company_name <> B.company_name -- Additional search conditions OR C.primary_contact <> B.primary_contact OR C.contact_phone <> B.contact_phone) THEN UPDATE SET C.company_name = B.company_name, C.primary_contact = B.primary_contact, C.contact_phone = B.contact_phone WHEN NOT MATCHED THEN -- Add missing INSERT (account_nbr, company_name, primary_contact, contact_phone) VALUES (B.account_nbr, B.company_name, B.primary_contact, B.contact_phone) WHEN SOURCE NOT MATCHED THEN -- Delete missing from source DELETE; SELECT account_nbr, company_name, primary_contact, contact_phone FROM CentralOfficeAccounts; ::= ::= ... ::= | ::= WHEN MATCHED [ AND ] THEN ::= | ::= WHEN NOT MATCHED [ AND ] THEN ::= UPDATE SET ::= DELETE ::= INSERT [ ] [ ] VALUES ::= [ { }... ] ::= | 14.13 ::= UPDATE [ [ AS ] ] SET WHERE CURRENT OF 14.14 ::= UPDATE [ FOR PORTION OF FROM TO ] [ [ AS ] ] SET [ WHERE ] -} ,(TestStatement ansi2011 "update t set a=b" $ Update [Name Nothing "t"] Nothing [Set [Name Nothing "a"] (Iden [Name Nothing "b"])] Nothing) ,(TestStatement ansi2011 "update t set a=b, c=5" $ Update [Name Nothing "t"] Nothing [Set [Name Nothing "a"] (Iden [Name Nothing "b"]) ,Set [Name Nothing "c"] (NumLit "5")] Nothing) ,(TestStatement ansi2011 "update t set a=b where a>5" $ Update [Name Nothing "t"] Nothing [Set [Name Nothing "a"] (Iden [Name Nothing "b"])] $ Just $ BinOp (Iden [Name Nothing "a"]) [Name Nothing ">"] (NumLit "5")) ,(TestStatement ansi2011 "update t as u set a=b where u.a>5" $ Update [Name Nothing "t"] (Just $ Name Nothing "u") [Set [Name Nothing "a"] (Iden [Name Nothing "b"])] $ Just $ BinOp (Iden [Name Nothing "u",Name Nothing "a"]) [Name Nothing ">"] (NumLit "5")) ,(TestStatement ansi2011 "update t set (a,b)=(3,5)" $ Update [Name Nothing "t"] Nothing [SetMultiple [[Name Nothing "a"],[Name Nothing "b"]] [NumLit "3", NumLit "5"]] Nothing) {- 14.15 ::= [ { }... ] ::= | ::= | ::= ::= [ { }... ] ::= ::= | ::= ::= ::= | ::= | 14.16 ::= DECLARE LOCAL TEMPORARY TABLE
[ ON COMMIT
ROWS ] declare local temporary table t (a int) [on commit {preserve | delete} rows] 14.17 ::= FREE LOCATOR [ { }... ] ::= | | 14.18 ::= HOLD LOCATOR [ { }... ] -} ]