DBA Data[Home] [Help]

PACKAGE BODY: APPS.AP_PURGE_PKG

Source


1 PACKAGE BODY AP_PURGE_PKG AS
2 /* $Header: appurgeb.pls 120.22.12020000.5 2012/09/17 12:22:52 rnimmaka ship $ */
3 --bug5052748
4 --This bug mainly solves most of the performance related issues reported
5 --in SQLREP.
6 --There are two kinds of fixes.
7 --NO_UNNEST is used in the inner query to prevent FTS on large tables.
8 --Introduction of AP_INVOICES_ALL,AP_SYSTEM_PARAMETERS_ALL to force an
9 --access path.
10 -- Private Variables
11 -- Declaring the global variables
12 g_debug_switch         VARCHAR2(1) := 'N';
13 
14 g_purge_name           VARCHAR2(15);
15 g_chv_status           VARCHAR2(1) := 'N';
16 g_payables_status      VARCHAR2(1) := 'N';
17 g_purchasing_status    VARCHAR2(1) := 'N';
18 g_pa_status            VARCHAR2(1) := 'N';
19 g_assets_status        VARCHAR2(1) := 'N';
20 g_edi_status           VARCHAR2(1) := 'N';
21 g_mrp_status           VARCHAR2(1) := 'N';
22 g_activity_date        DATE;
23 g_category             VARCHAR2(30);
24 g_organization_id      NUMBER;
25 g_range_size           NUMBER;
26 
27 -- Bug 8913560 : Added the following two procedures
28 PROCEDURE Submit_Multiple_Requests ( p_purge_name IN         VARCHAR2,
29                                      p_success   OUT NOCOPY BOOLEAN  ) ; -- Bug 9268290
30 Procedure Update_Financials_Purges ( p_check_rows             IN NUMBER DEFAULT 0,
31                                      p_invoice_payment_rows   IN NUMBER DEFAULT 0,
32                                      p_invoice_rows           IN NUMBER DEFAULT 0,
33                                      p_ae_line_rows	      IN NUMBER DEFAULT 0,
34                                      p_ae_header_rows	      IN NUMBER DEFAULT 0,
35                                      p_accounting_event_rows  IN NUMBER DEFAULT 0,
36                                      p_invoice_lines_rows     IN NUMBER DEFAULT 0,               --bug 11829621
37                                      p_invoice_distributions_rows IN NUMBER DEFAULT 0,           --bug 11829621
38 				     p_purge_name             IN VARCHAR2         );
39 
40 ------------------------------------------------------------------
41 -- Procedure: Print
42 -- This is a print procedure to split a message string into 132
43 -- character strings.
44 ------------------------------------------------------------------
45 PROCEDURE Print
46         (P_string                IN      VARCHAR2) IS
47 
48   stemp    VARCHAR2(80);
49   nlength  NUMBER := 1;
50 
51 BEGIN
52 
53    WHILE(length(P_string) >= nlength)
54    LOOP
55 
56         stemp := substrb(P_string, nlength, 80);
57         fnd_file.put_line(FND_FILE.LOG, stemp);
58         nlength := (nlength + 80);
59 
60    END LOOP;
61 
62 EXCEPTION
63   WHEN OTHERS THEN
64 
65     IF (SQLCODE <> -20001) THEN
66       FND_MESSAGE.SET_NAME('SQLAP','AP_DEBUG');
67       FND_MESSAGE.SET_TOKEN('ERROR',SQLERRM);
68     END IF;
69     APP_EXCEPTION.RAISE_EXCEPTION;
70 
71 END Print;
72 
73 
74 ------------------------------------------------------------------
75 -- Procedure: Set_Purge_Status
76 -- This procedure is used to set the status of the purge process
77 ------------------------------------------------------------------
78 FUNCTION Set_Purge_Status
79          (P_Status           IN  VARCHAR2,
80           P_Purge_Name       IN  VARCHAR2,
81           P_Debug_Switch     IN  VARCHAR2,
82           P_Calling_Sequence IN VARCHAR2)
83 RETURN BOOLEAN IS
84 
85 debug_info                      VARCHAR2(200);
86 current_calling_sequence        VARCHAR2(2000);
87 
88 BEGIN
89   -- Update the calling sequence
90   --
91    current_calling_sequence :=
92    'Set_purge_status<-'||P_calling_sequence;
93   --
94    debug_info := 'Starting Set_purge_status';
95    IF (p_debug_switch in ('y','Y')) THEN
96       Print('(Updating table financials_purges)'||debug_info);
97    END IF;
98 
99    UPDATE financials_purges
100    SET status = P_Status
101    WHERE purge_name = P_Purge_Name;
102   --
103    debug_info := 'End Set_purge_status';
104    IF (g_debug_switch in ('y','Y')) THEN
105       Print('(Done updating table financials_purges)'||debug_info);
106    END IF;
107    RETURN(TRUE);
108 
109 RETURN NULL;
110 
111 EXCEPTION
112    WHEN OTHERS THEN
113           IF (SQLCODE < 0 ) then
114              Print(SQLERRM);
115           END IF;
116           RETURN(FALSE);
117 
118 END;
119 
120 
121 ------------------------------------------------------------------
122 -- Procedure: Get_Accounting_Method
123 -- This routine gets the accounting method options
124 ------------------------------------------------------------------
125 
126 FUNCTION Get_Accounting_Method
127          (P_Recon_Acctg_Flag      OUT NOCOPY VARCHAR2,
128           P_Using_Accrual_Basis   OUT NOCOPY VARCHAR2,
129           P_Using_Cash_Basis      OUT NOCOPY VARCHAR2,
130           P_Calling_Sequence      IN  VARCHAR2)
131 
132 RETURN BOOLEAN IS
133 
134 debug_info   		  	VARCHAR2(200);
135 current_calling_sequence  	VARCHAR2(2000);
136 
137 BEGIN
138   -- Update the calling sequence
139   --
140   current_calling_sequence :=
141   'Get_accounting_method<-'||P_calling_sequence;
142   --
143   debug_info := 'Starting Get_Accounting_Method';
144   IF g_debug_switch in ('y','Y') THEN
145      Print('(Get_Accounting_Method)' ||debug_info);
146   END IF;
147 
148       /* Bug#2274656 Selecting Recon Accounting Flag also in this program unit */
149   SELECT DECODE(ASP.accounting_method_option, 'Accrual',                     'Y',
150          DECODE(ASP.secondary_accounting_method,
151                    'Accrual', 'Y', 'N')),
152          DECODE(ASP.accounting_method_option,'Cash','Y',
153          DECODE(ASP.secondary_accounting_method,
154                    'Cash',    'Y', 'N')),
155          nvl(ASP.RECON_ACCOUNTING_FLAG,'N')
156   INTO   p_using_accrual_basis,
157          p_using_cash_basis,
158          p_recon_acctg_flag
159   FROM   ap_system_parameters ASP;
160 
161   --
162   debug_info := 'End Get_Accounting_Method';
163   IF g_debug_switch in ('y','Y') THEN
164      Print('(Get_Accounting_Method)' ||debug_info);
165   END IF;
166 
167   RETURN (TRUE);
168   RETURN NULL;
169 
170 EXCEPTION
171 
172   WHEN   OTHERS  THEN
173      IF (SQLCODE < 0 ) then
174          Print(SQLERRM);
175      END IF;
176      RETURN (FALSE);
177 
178 END Get_Accounting_Method;
179 
180 
181 ------------------------------------------------------------------
182 -- Procedure: Check_no_purge_in_process
183 -- This process checks if any purge is in process
184 ------------------------------------------------------------------
185 FUNCTION Check_no_purge_in_process
186          (P_Purge_Name          IN  VARCHAR2,
187           P_Debug_Switch        IN  VARCHAR2,
188           P_Calling_Sequence    IN  VARCHAR2)
189 RETURN  BOOLEAN IS
190 
191 debug_info   		  	VARCHAR2(200);
192 current_calling_sequence  	VARCHAR2(2000);
193 invoice_count                   NUMBER;
194 po_count                        NUMBER;
195 req_count                       NUMBER;
196 vendor_count                    NUMBER;
197 
198 l_status                        VARCHAR2(30);
199 
200 BEGIN
201   -- Update the calling sequence
202   --
203   current_calling_sequence :=
204   'Check_no_purge_in_process<-'||P_calling_sequence;
205 
206   debug_info := 'Starting Check_no_purge_in_process';
207   IF p_debug_switch in ('y','Y') THEN
208      Print('(Check_no_purge_in_process)' ||debug_info);
209   END IF;
210 
211   -- count_invs
212   select count(1)
213   into invoice_count
214   from ap_purge_invoice_list
215   where double_check_flag = 'Y';
216 
217   if (invoice_count = 0) then
218 
219      -- count_pos
220      select count(1)
221      into po_count
222      from po_purge_po_list
223      where double_check_flag = 'Y';
224 
225      if (po_count = 0) then
226 
227         -- count_reqs
228         select count(1)
229         into req_count
230         from po_purge_req_list
231         where double_check_flag = 'Y';
232 
233         if (req_count = 0) then
234 
235             -- count_vendors
236             select count(1)
237             into vendor_count
238             from po_purge_vendor_list
239             where double_check_flag = 'Y';
240 
241             if (vendor_count = 0) then
242 
243                null;
244             else
245 
246                debug_info := 'The PO_PURGE_VENDOR_LIST table contains records. ';
247                Print('(Check_no_purge_in_process)' || debug_info);
248                Print(' Please make sure no purges are running and clear');
249 	       Print(' this table. Process terminating.');
250 
251                l_status := 'COMPLETED-ABORTED';
252 	       if (Set_Purge_Status (
253                              l_status,
254                              p_purge_name,
255                              p_debug_switch,
256                              'Check_no_purge_in_process') <> TRUE) then
257 		  Print(' Set_purge_status failed');
258                   Return (FALSE);
259                end if;
260 
261             end if;
262 
263         else -- req_count <> 0
264 
265 	     debug_info := 'The PO_PURGE_REQ_LIST table contains records. ';
266 	     Print('Check_no_purge_in_process' || debug_info);
267              Print('Please make sure no purges are running and clear');
268 	     Print(' this table. Process terminating.');
269 
270              l_status := 'COMPLETED-ABORTED';
271 	     if (Set_Purge_Status
272                         (l_status,
273                          p_purge_name,
274                          p_debug_switch,
275                          'Check_no_purge_in_process') <> TRUE) then
276 		  Print(' Set_purge_status failed');
277                   Return (FALSE);
278              end if;
279 
280         end if ; -- req_count
281 
282      else
283 
284         debug_info := 'The PO_PURGE_PO_LIST table contains records. ';
285 	Print('Check_no_purge_in_process' || debug_info);
286         Print('Please make sure no purges are running and clear');
287 	Print(' this table. Process terminating.');
288 
289         l_status := 'COMPLETED-ABORTED';
290 	if (Set_Purge_Status
291                      (l_status,
292                       p_purge_name,
293                       p_debug_switch,
294                       'Check_no_purge_in_process') <> TRUE) then
295            Print(' Set_purge_status failed');
296            Return (FALSE);
297         end if;
298 
299      end if;  -- po_count
300 
301   else -- invoice_count
302 
303       debug_info := 'THe AP_PURGE_INVOICE_LIST table contains records. ';
304       Print('Check_no_purge_in_process' || debug_info);
305       Print('Please make sure no purges are running and clear');
306       Print(' this table. Process terminating.');
307 
308       l_status := 'COMPLETED-ABORTED';
309       if (Set_Purge_Status
310                   (l_status,
311                    p_purge_name,
312                    p_debug_switch,
313                    'Check_no_purge_in_process') <> TRUE) then
314            Print(' Set_purge_status failed');
315            Return (FALSE);
316       end if;
317 
318   end if; -- invoice_count
319 
320   COMMIT;
321   RETURN (TRUE);
322 
323 RETURN NULL; EXCEPTION
324   WHEN OTHERS then
325     IF (SQLCODE < 0 ) then
326        Print(SQLERRM);
327     END IF;
328     RETURN (FALSE);
329 
330 END Check_no_purge_in_process;
331 
332 
333 ------------------------------------------------------------------
334 -- Procedure: Check_Chv_In_Cum
335 --
336 ------------------------------------------------------------------
337 FUNCTION Check_chv_in_cum
338          (P_Calling_Sequence  IN  VARCHAR2)
339 RETURN BOOLEAN IS
340 
341 debug_info   		  	VARCHAR2(200);
342 current_calling_sequence  	VARCHAR2(2000);
343 
344 BEGIN
345   -- Update the calling sequence
346   --
347   current_calling_sequence := 'check_chv_in_cum<-'||P_calling_sequence;
348 
349   debug_info := 'Starting check_chv_in_cum';
350   IF g_debug_switch in ('y','Y') THEN
351      Print('(Check_chv_in_cum)' ||debug_info);
352   END IF;
353 
354   --
355   --   test_chv_in_cum
356 
357   delete from chv_purge_schedule_list cpsl
358   where exists (select null
359                 from chv_cum_periods ccp,
360                      chv_schedule_items csi,
361                      chv_schedule_headers csh,
362                      chv_org_options coo
363                 where ccp.organization_id  = g_organization_id
364                 and   sysdate between ccp.cum_period_start_date and
365                                       NVL(ccp.cum_period_end_date,sysdate + 1)
366                 and  coo.organization_id = ccp.organization_id
367                 and  coo.enable_cum_flag = 'Y'
368                 and  csh.schedule_id = csi.schedule_id
369                 and  csh.schedule_horizon_start >= ccp.cum_period_start_date
370                 and  csi.schedule_item_id = cpsl.schedule_item_id);
371 
372   RETURN (TRUE);
373   RETURN NULL;
374 
375 EXCEPTION
376   WHEN OTHERS THEN
377        IF (SQLCODE < 0 ) THEN
378      	   Print(SQLERRM);
379        END IF;
380        RETURN (FALSE);
381 END Check_chv_in_cum;
382 
383 
384 ------------------------------------------------------------------
385 -- Procedure: Check_Chv_In_EDI
386 --
387 ------------------------------------------------------------------
388 FUNCTION Check_chv_in_edi
389          (P_Calling_Sequence  IN VARCHAR2)
390 RETURN BOOLEAN IS
391 
392 debug_info   		  	VARCHAR2(200);
393 current_calling_sequence  	VARCHAR2(2000);
394 
395 BEGIN
396   -- Update the calling sequence
397   --
398   current_calling_sequence := 'check_chv_in_edi<-'||P_calling_sequence;
399 
400   debug_info := 'Starting check_chv_in_edi';
401   IF g_debug_switch in ('y','Y') THEN
402      Print('(Check_chv_in_edi)' ||debug_info);
403   END IF;
404 
405   --
406   --	test_chv_in_edi
407 
408   delete from chv_purge_schedule_list cpsl
409   where exists (select null
410                 from   chv_schedule_items csi,
411                        ece_spso_items esi
412                 where  csi.schedule_item_id = cpsl.schedule_item_id
413                 and    csi.schedule_id = esi.schedule_id);
414 
415   RETURN (TRUE);
416   RETURN NULL;
417 
418 EXCEPTION
419   WHEN OTHERS THEN
420        IF (SQLCODE < 0 ) THEN
421      	   Print(SQLERRM);
422        END IF;
423        RETURN (FALSE);
424 END Check_chv_in_edi;
425 
426 
427 ------------------------------------------------------------------
428 -- Procedure: Do_Dependent_Inv_Checks
429 --
430 ------------------------------------------------------------------
431 FUNCTION DO_DEPENDENT_INV_CHECKS
432          (P_Calling_Sequence  IN VARCHAR2)
433 RETURN BOOLEAN IS
434 
435   /* bug2918268 : Created this function instead of do_dependent_inv_checks function.
436      Because performance of delete stmt in do_dependent_inv_checks was very poor.
437      This function does same check with the delete stmt.
438   */
439 
440  TYPE tab_status_type IS TABLE OF VARCHAR2(1) INDEX BY BINARY_INTEGER;
441  tab_inv tab_status_type;
442  tab_check tab_status_type;
443  tab_clear tab_status_type;
444 
445  -- Bug 8942883 Begin
446  TYPE tab_status_type_vc2 IS TABLE OF VARCHAR2(1) INDEX BY VARCHAR2(30) ;
447  tab_inv_vc2   tab_status_type_vc2 ;
448  tab_check_vc2 tab_status_type_vc2 ;
449  use_vc2    BOOLEAN ;
450  max_inv_id NUMBER ;
451  max_chk_id NUMBER ;
452  p_id_vc2   VARCHAR2(30) ;
453  -- Bug 8942883 End
454 
455  /* bug3136911 added ap_invoice_payments table join in order to check only
456                invoices which are related to payment.
457   */
458  CURSOR c_main IS
459   select pl.invoice_id
460     from ap_purge_invoice_list pl,
461          ap_invoice_payments ip
462    where pl.invoice_id = ip.invoice_id;
463 
464  CURSOR c_main_check(l_invoice_id NUMBER) IS
465   select invoice_id
466     from ap_purge_invoice_list
467    where invoice_id = l_invoice_id
468      and double_check_flag = 'Y';
469 
470   p_count   integer;
471   p_id   integer;
472 
473   l_cnt integer;
474   debug_info                      VARCHAR2(200);
475   current_calling_sequence  	VARCHAR2(2000);
476   l_invoice BOOLEAN ;
477   l_dummy NUMBER ;
478   l_sch_name VARCHAR2(2) := 'A' || 'P' ; -- Bug 8913560
479 
480   Function Check_check(l_invoice_id IN NUMBER ) RETURN BOOLEAN;
481 
482 /* Get related invoice_id from check_id and check if the invoice_id is
483    in purge list. If there is, call check_check to get check_id which
484    is related to the invoice_id */
485   Function Check_inv(l_check_id IN NUMBER) RETURN BOOLEAN IS
486 
487  CURSOR c_inv IS
488   select pil.invoice_id
489     from ap_invoice_payments ip,
490          ap_purge_invoice_list pil
491    where ip.check_id = l_check_id
492      and ip.invoice_id = pil.invoice_id (+) ;
493 
494  l_flag BOOLEAN := FALSE;
495  l_inv_id ap_purge_invoice_list.invoice_id%TYPE;
496 
497 BEGIN
498 
499   OPEN c_inv ;
500   LOOP
501 
502     FETCH c_inv into l_inv_id ;
503     EXIT WHEN c_inv%NOTFOUND ;
504 
505     /* if related invoice id is not in purge list */
506     IF l_inv_id is null THEN
507       l_flag := FALSE ;
508     ELSE
509 
510       /* if the invocie_id is already checked */
511       IF use_vc2 THEN                                     -- Bug 8942883
512          IF tab_inv_vc2.exists(l_inv_id) THEN
513            l_flag := TRUE ;
514          ELSE
515            tab_inv_vc2(l_inv_id) := 'X' ;
516            l_flag := check_check(l_inv_id) ;
517          END IF;
518       ELSE
519          IF tab_inv.exists(l_inv_id) THEN
520            l_flag := TRUE ;
521          ELSE
522            tab_inv(l_inv_id) := 'X' ;
523            l_flag := check_check(l_inv_id) ;
524          END IF;
525       END IF;
526     END IF;
527 
528     EXIT WHEN (not l_flag) ;
529 
530   END LOOP;
531 
532   CLOSE C_inv;
533   RETURN(l_flag) ;
534 
535 END ;
536 
537 /* Get related check_id from invoice_id and call check_invoice
538    to check if the invoice is in purge list. */
539 Function Check_check(l_invoice_id IN NUMBER ) RETURN BOOLEAN IS
540 
541  CURSOR c_check IS
542   select check_id
543     from ap_invoice_payments
544    where invoice_id = l_invoice_id ;
545 
546   l_flag BOOLEAN := FALSE;
547   l_check_id number;
548 
549 BEGIN
550 
551   OPEN c_check ;
552   LOOP
553 
554     FETCH c_check into l_check_id ;
555     EXIT WHEN c_check%NOTFOUND ;
556 
557     /* if the check_id is already checked */
558     IF use_vc2 THEN                                         -- Bug 8942883
559        IF tab_check_vc2.exists(l_check_id) THEN
560          l_flag := TRUE ;
561        ELSE
562          tab_check_vc2(l_check_id) := 'X' ;
563          l_flag := check_inv(l_check_id) ;
564        END IF;
565     ELSE
566        IF tab_check.exists(l_check_id) THEN
567          l_flag := TRUE ;
568        ELSE
569          tab_check(l_check_id) := 'X' ;
570          l_flag := check_inv(l_check_id) ;
571        END IF;
572     END IF ;
573 
574     EXIT WHEN (not l_flag) ;
575 
576   END LOOP;
577 
578   CLOSE C_check;
579   RETURN(l_flag) ;
580 
581 END ;
582 
583 /* main process */
584 BEGIN
585   -- Update the calling sequence
586   --
587    current_calling_sequence :=
588    'Do_dependent_inv_checks<-'||P_calling_sequence;
589   --
590 
591   debug_info := 'Starting series of debug invoice validations';
592   IF g_debug_switch in ('y','Y') THEN
593      Print('(do_dependent_inv_checks)' ||debug_info);
594   END IF;
595 
596   /* Bug 8913560
597   -- Bug 8942883 Begin
598   SELECT MAX( invoice_id )
599   INTO   max_inv_id
600   FROM   ap_invoices ;
601 
602   SELECT MAX( check_id )
603   INTO   max_chk_id
604   FROM   ap_invoice_payments ; */
605   SELECT last_number
606   INTO   max_inv_id
607   FROM   all_sequences
608   WHERE  sequence_owner = l_sch_name
609   AND    sequence_name  = 'AP_INVOICES_S' ;
610 
611   SELECT last_number
612   INTO   max_chk_id
613   FROM   all_sequences
614   WHERE  sequence_owner = l_sch_name
615   AND    sequence_name  = 'AP_CHECKS_S' ;
616 
617   IF ( max_inv_id > 2147483647 OR
618        max_chk_id > 2147483647 )
619   THEN
620      use_vc2 := TRUE ;
621   ELSE
622      use_vc2 := FALSE ;
623   END IF ;
624   -- Bug 8942883 End
625 
626   FOR l_main IN c_main
627   LOOP
628 
629     /* initialization */
630     tab_inv := tab_clear ;
631     tab_check := tab_clear;
632     tab_inv_vc2.DELETE ;     -- Bug 8942883
633     tab_check_vc2.DELETE ;   -- Bug 8942883
634 
635     /* check if this invoice is not checked yet */
636     OPEN c_main_check(l_main.invoice_id) ;
637     FETCH c_main_check into l_dummy ;
638     l_invoice := c_main_check%FOUND ;
639     CLOSE c_main_check ;
640 
641     /* if this invoice is not checked yet */
642     IF (l_invoice) THEN
643 
644        IF use_vc2 THEN					-- Bug 8942883
645           tab_inv_vc2(l_main.invoice_id) := 'X' ;
646        ELSE
647           tab_inv(l_main.invoice_id) := 'X' ;
648        END IF ;
649 
650       IF check_check(l_main.invoice_id) THEN
651 
652         /* if this chain is purgeable,set flag 'S' for all invoices in this chain */
653 	IF use_vc2 THEN					-- Bug 8942883
654 	   p_count := tab_inv_vc2.count;
655 	ELSE
656            p_count := tab_inv.count;
657 	END IF ;
658         IF p_count <> 0 THEN
659           p_id := 0 ;
660 	  p_id_vc2 := 0 ;
661 
662           FOR y IN 1..p_count LOOP
663 	    IF use_vc2 THEN				-- Bug 8942883
664 	       p_id_vc2 := tab_inv_vc2.next(p_id_vc2) ;
665                UPDATE ap_purge_invoice_list
666                   SET double_check_flag = 'S'
667                 WHERE invoice_id = p_id_vc2 ;
668 	    ELSE
669                p_id := tab_inv.next(p_id) ;
670                UPDATE ap_purge_invoice_list
671                   SET double_check_flag = 'S'
672                 WHERE invoice_id = p_id ;
673 	    END IF ;
674           END LOOP;
675 
676         END IF;
677       ELSE
678 
679         /* if this chain is not purgeable, delete selected invoice from purge list */
680 	IF use_vc2 THEN					-- Bug 8942883
681 	   p_count := tab_inv_vc2.count;
682 	ELSE
683            p_count := tab_inv.count;
684 	END IF ;
685         IF p_count <> 0 THEN
686           p_id := 0 ;
687           p_id_vc2 := 0 ;
688 
689           FOR y IN 1..p_count LOOP
690 	    IF use_vc2 THEN				-- Bug 8942883
691 	       p_id_vc2 := tab_inv_vc2.next(p_id_vc2) ;
692                DELETE FROM ap_purge_invoice_list
693                  WHERE invoice_id = p_id_vc2 ;
694 	    ELSE
695                p_id := tab_inv.next(p_id) ;
696                DELETE FROM ap_purge_invoice_list
697                  WHERE invoice_id = p_id ;
698 	    END IF ;
699           END LOOP;
700         end if;
701 
702         /* delete unpurgeable list beforehand for performance */
703 	IF use_vc2 THEN					-- Bug 8942883
704 	   p_count := tab_check_vc2.count;
705 	ELSE
706            p_count := tab_check.count;
707 	END IF ;
708 
709         IF p_count <> 0 THEN
710           p_id := 0 ;
711 	  p_id_vc2 := 0 ;
712 
713           FOR y IN 1..p_count LOOP
714 	    IF use_vc2 THEN				-- Bug 8942883
715 	       p_id_vc2 := tab_check_vc2.next(p_id_vc2) ;
716                DELETE FROM ap_purge_invoice_list
717                WHERE invoice_id in ( select invoice_id
718                    from ap_invoice_payments
719                    where check_id = p_id_vc2);
720 	    ELSE
721                p_id := tab_check.next(p_id) ;
722                DELETE FROM ap_purge_invoice_list
723                WHERE invoice_id in ( select invoice_id
724                    from ap_invoice_payments
725                    where check_id = p_id);
726 	    END IF ;
727           END LOOP;
728         END IF;
729 
730      END IF;
731 
732     END IF;
733 
734   END LOOP;
735 
736   /* Set flag 'Y' back */
737   update ap_purge_invoice_list
738     set double_check_flag = 'Y'
739    where double_check_flag = 'S' ;
740 
741   debug_info := 'End Of Invoice Validations';
742   IF g_debug_switch in ('y','Y') THEN
743      Print('(do_dependent_inv_checks)' ||debug_info);
744   END IF;
745 
746   commit;
747   return(TRUE) ;
748 
749 RETURN NULL;
750 
751 EXCEPTION
752    WHEN OTHERS THEN
753        IF (SQLCODE < 0 ) then
754          Print(SQLERRM);
755       END IF;
756       RETURN(FALSE);
757 END ;
758 
759 ------------------------------------------------------------------
760 -- Procedure: Do_Independent_Inv_Checks
761 --
762 ------------------------------------------------------------------
763 FUNCTION Do_independent_inv_checks
764          (P_Using_Accrual_Basis  IN  VARCHAR2,
765           P_Using_Cash_Basis     IN  VARCHAR2,
766           P_Recon_Acctg_Flag     IN  VARCHAR2,
767           P_Calling_Sequence     IN  VARCHAR2)
768 RETURN BOOLEAN IS
769 
770 /* bug 11722321 incorporating changes of bug 8842960 and 8979828 in R12 start */
771 CURSOR pa_related_invoices IS
772   SELECT invoice_id
773     FROM ap_purge_invoice_list PL
774    WHERE EXISTS
775         (SELECT 'project-related vendor invoices'
776 		FROM	ap_invoice_distributions d
777 		WHERE	d.invoice_id = pl.invoice_id
778     	        AND d.pa_addition_flag in ('Y','T'))
779         OR EXISTS
780 	   (SELECT 'project-related expense report'
781 	    FROM   ap_invoices i
782 	    WHERE  i.invoice_id = pl.invoice_id
783 	    AND	   i.source = 'Oracle Project Accounting');
784 
785 l_invoice_id            NUMBER;
786 
787 /* bug 11722321 incorporating changes of  bug 8842960 and 8979828 in R12 end */
788 
789 debug_info   		  	VARCHAR2(200);
790 current_calling_sequence  	VARCHAR2(2000);
791 l_list_count number;
792 
793 BEGIN
794   -- Update the calling sequence
795   --
796    current_calling_sequence :=
797    'Do_independent_inv_checks<-'||P_calling_sequence;
798 
799 
800    debug_info :=
801    'Starting independent invoice validations -- Payment Schedules';
802    IF g_debug_switch in ('y','Y') THEN
803      Print('(Do_independent_inv_checks)' ||debug_info);
804    END IF;
805 
806    --
807    -- Test Payment Schedules
808   /*bug9944247-modified the sql to improve the performance*/
809 
810   DELETE /*+ PARALLEL(pl) ROWID(pl) */
811     FROM ap_purge_invoice_list pl
812    WHERE pl.rowid IN
813         (SELECT /*+ ORDERED PARALLEL(pl1) FULL(pl1) USE_NL(i,ps)
814                     INDEX(i AP_INVOICES_U1) INDEX(ps AP_PAYMENT_SCHEDULES_U1) */
815                 pl1.rowid
816            FROM ap_purge_invoice_list pl1,
817                 ap_invoices i,
818                 ap_payment_schedules ps
819           WHERE i.invoice_id = pl1.invoice_id
820             AND ps.invoice_id = i.invoice_id
821             AND ((ps.payment_status_flag <> 'Y' AND i.cancelled_date IS NULL)
822                   OR ps.last_update_date > g_activity_date));
823 
824    /*bug9944247-end*/
825 
826    IF g_pa_status = 'Y' then
827      debug_info := 'Test PA Invoices';
828      IF g_debug_switch in ('y','Y') THEN
829        Print('(Do_independent_inv_checks)' ||debug_info);
830      END IF;
831      --
832      -- Test PA Invoices
833 
834 /* bug 11722321 incorporating changes of bug 8842960 and 8979828 in R12 start */
835 
836    DELETE
837    FROM ap_purge_invoice_list PL
838    WHERE EXISTS (
839         SELECT 'Invoices are not transfered to PA'
840         FROM ap_invoices I,
841              ap_invoice_distributions D
842         WHERE I.invoice_id = PL.invoice_id
843           AND I.invoice_id = D.invoice_id
844           AND I.source = 'Oracle Project Accounting'
845           AND D.pa_addition_flag not in ('Y','T','E','Z') );
846 
847     /*   DELETE
848      FROM ap_purge_invoice_list PL
849      WHERE EXISTS
850 	(SELECT 'project-related vendor invoices'
851 	FROM	ap_invoice_distributions d
852 	WHERE	d.invoice_id = pl.invoice_id
853 	AND	d.project_id is not null)   -- bug1746226
854         OR EXISTS
855 	   (SELECT 'project-related expense report'
856 	    FROM   ap_invoices i
857 	    WHERE  i.invoice_id = pl.invoice_id
858 	    AND	   i.source = 'Oracle Project Accounting'); */
859 
860    OPEN pa_related_invoices;
861    LOOP
862      FETCH pa_related_invoices INTO l_invoice_id;
863      EXIT WHEN pa_related_invoices%NOTFOUND OR pa_related_invoices%NOTFOUND IS NULL;
864 
865     -- Call PA to verify whether we can purge this PA related invoice.  That is,
866     -- are there any open transactions for the particular project?
867     -- If PA does not allow purging of the invoice, then, remove, invoice
868     -- from purge list.
869 
870     if (PA_AP_TRX_PURGE.INVOICE_PURGEABLE(l_invoice_id) ) then
871       --allow purge
872        null;
873     else
874       DELETE
875       FROM ap_purge_invoice_list
876       WHERE invoice_id = l_invoice_id;
877     end if;
878    END LOOP;
879    CLOSE pa_related_invoices;
880 
881 /* bug 11722321 incorporating changes of  bug 8842960 and 8979828 in R12 end */
882 
883    END IF;
884 
885 
886 
887    --
888    debug_info := 'Test Distributions';
889    IF g_debug_switch in ('y','Y') THEN
890      Print('(Do_independent_inv_checks)' ||debug_info);
891    END IF;
892 
893 /*
894 1897941 fbreslin: If an invoice is cancelled, the ASSETS_ADDTION_FLAG is
895                   set to "U" so Mass Additions does not include the
896                   distribution.  We are alos not supposed to purge
897                   invoices if any of the distributions have ben passed to
898                   FA. Adding a check to see if the invoice is cancelled
899                   before we remove an invoice with ASSETS_ADDTION_FLAG = U
900                   from the purge list.
901 */
902 
903    IF g_category = 'SIMPLE INVOICES' THEN
904 
905       Print('Test Simple Invoice Distributions');
906       -- Test Simple Invoice Distributions
907 
908       /*bug9944247-modified the sql to improve the performance*/
909 
910       DELETE /*+ PARALLEL(pl) ROWID(pl) */
911         FROM ap_purge_invoice_list pl
912        WHERE pl.rowid IN
913              (SELECT /*+ ORDERED PARALLEL(pl1) FULL(pl1) USE_NL(i,d)
914                          INDEX(i AP_INVOICES_U1) INDEX(d AP_INVOICE_DISTRIBUTIONS_U1) */
915                      pl1.rowid
916                 FROM ap_purge_invoice_list pl1,
917                      ap_invoices i,
918                      ap_invoice_distributions d
919                WHERE i.invoice_id = pl1.invoice_id
920                  AND i.invoice_id = d.invoice_id
921                  AND (d.last_update_date > g_activity_date
922                       OR d.posted_flag <> 'Y'
923                       OR d.accrual_posted_flag = decode(p_using_accrual_basis,'Y','N','Z')
924                       OR d.cash_posted_flag = decode(p_using_cash_basis,'Y',decode(d.cash_posted_flag,'N','N','P','P','Z'),'Z')
925                       OR d.po_distribution_id IS NOT NULL
926                       OR (d.assets_tracking_flag = 'Y' /* bug 11707744 */
927                           AND d.assets_addition_flag || '' = decode(g_assets_status,'Y','U','cantequalme')
928                           AND i.cancelled_date IS NULL)));
929 
930       /*bug9944247-end*/
931 
932    ELSE
933      Print('Test All Invoice Distributions');
934      -- Test All Invoice Distributions
935      DELETE
936      FROM ap_purge_invoice_list PL
937      WHERE EXISTS
938               (SELECT /*+ no_unnest */ 'distributions not purgeable' -- 7759218
939 	 	 FROM ap_invoice_distributions D, ap_invoices I
940 	 	WHERE I.invoice_id = D.invoice_id
941                   AND PL.invoice_id = D.invoice_id
942          	  AND (   D.last_update_date > g_activity_date
943               	       OR D.posted_flag <> 'Y'
944                        OR D.accrual_posted_flag =
945             	          DECODE(p_using_accrual_basis,
946                                  'Y', 'N',
947                                  'Z')
948               	       OR D.cash_posted_flag =
949               	          DECODE(p_using_cash_basis,
950                                  'Y', DECODE(D.cash_posted_flag,
951                                             'N', 'N',
952 		                            'P', 'P',
953                                             'Z'),
954                                  'Z')
955                        OR (    D.assets_tracking_flag = 'Y'   /* bug 11707744 */
956                            AND D.assets_addition_flag||'' =
957        	                       DECODE(g_assets_status,
958                                       'Y', 'U',
959 		                      'cantequalme')
960                            AND I.cancelled_date IS NULL)));
961    END IF;
962 
963 
964 
965    debug_info := 'Test Payments';
966    IF g_debug_switch in ('y','Y') THEN
967      Print('(Do_independent_inv_checks)' ||debug_info);
968    END IF;
969 
970   -- Test Payments
971   -- Perf bug 5052674 -- go to base table AP_INVOICE_PAYMENTS_ALL for
972   -- main SELECT query and base table CE_STATEMENT_RECONCILS_ALL for sub-query
973   /*bug9944247-The sql has been split into two statements so that the SQL does not have
974     to be transformed by the CBO and to avoid the risk of OR clause and sub-query
975     on ce_statement_reconciliations being applied as a filter.
976     It also allows more control using hints. */
977 
978   DELETE /*+ PARALLEL(pl) ROWID(pl) */
979     FROM ap_purge_invoice_list pl
980    WHERE pl.rowid IN
981          (SELECT /*+ ORDERED PARALLEL(pl1) FULL(pl1) USE_NL(p,c)
982                      INDEX(p AP_INVOICE_PAYMENTS_N1) INDEX(c AP_CHECKS_U1) */
983                  pl1.rowid
984             FROM ap_purge_invoice_list pl1,
985                  ap_invoice_payments p,
986                  ap_checks c
987            WHERE p.invoice_id = pl1.invoice_id
988              AND p.check_id = c.check_id
989              AND ((p.posted_flag <> 'Y'
990                    OR p.accrual_posted_flag = decode(p_using_accrual_basis,'Y','N','Z')
991                    OR p.cash_posted_flag = decode(p_using_cash_basis,'Y',decode(p.cash_posted_flag,'N','N','P','P','Z'), 'Z')
992                    OR p.last_update_date > g_activity_date
993                    OR c.last_update_date > g_activity_date
994                    OR (c.future_pay_due_date IS NOT NULL AND c.status_lookup_code = 'ISSUED')
995                    OR decode(p_recon_acctg_flag, 'Y', nvl(c.cleared_date,
996                           nvl(c.void_date, to_date('12/31/2999' ,'MM/DD/YYYY')))) > g_activity_date))
997           );
998 
999    DELETE /*+ PARALLEL(pl) ROWID(pl) */
1000      FROM ap_purge_invoice_list pl
1001     WHERE pl.rowid IN
1002           (SELECT /*+ ORDERED PARALLEL(pl1) FULL(pl1) USE_NL(p, sr)
1003                       INDEX(p AP_INVOICE_PAYMENTS_N1) INDEX(sr CE_STATEMENT_RECONS_N2) */
1004          DISTINCT pl1.rowid
1005              FROM ap_purge_invoice_list pl1,
1006                   ap_invoice_payments p,
1007                   ce_statement_reconciliations sr
1008             WHERE p.invoice_id = pl1.invoice_id
1009               AND p.check_id = sr.reference_id
1010               AND sr.reference_type = 'PAYMENT'
1011           );
1012    /*bug9944247-end*/
1013 
1014   --
1015   debug_info := 'Test Prepayments';
1016   IF g_debug_switch in ('y','Y') THEN
1017      Print('(Do_independent_inv_checks)' ||debug_info);
1018   END IF;
1019 
1020   --  	Delete Inoivces that have applied Prepayments
1021   --    Keep this Statement for Invoices upgrated  from 11.0
1022 
1023    	DELETE
1024    	FROM ap_purge_invoice_list PL
1025    	WHERE EXISTS
1026 	       (SELECT  /*+ no_unnest */ 'related to prepayment' -- 7759218
1027 		FROM    ap_invoice_prepays IP
1028 		WHERE	PL.invoice_id = IP.invoice_id
1029 		OR	PL.invoice_id = IP.prepay_id);
1030 
1031   --    Bug 2153132 by ISartawi add the Delete Statement to exclude
1032   --    invoices with applied Prepayments
1033 
1034         DELETE
1035         FROM ap_purge_invoice_list PL
1036         WHERE EXISTS
1037                (SELECT  'X'
1038                 FROM    ap_invoice_distributions ID
1039                 WHERE   PL.invoice_id = ID.invoice_id
1040                 AND     ID.line_type_lookup_code   = 'PREPAY'
1041                 AND     ID.prepay_distribution_id  IS NOT NULL);
1042 
1043    /* Testing of Payment History moved to this location while fixing bug#2274656
1044       This doesn't make any difference but testing transaction before transfer
1045       will reduce number of records tested for Transfer from Acctg tables */
1046 
1047   debug_info := 'Test Payment History';
1048   IF g_debug_switch in ('y','Y') THEN
1049      Print('(Do_independent_inv_checks)' ||debug_info);
1050   END IF;
1051 
1052   DELETE FROM ap_purge_invoice_list PL
1053   where EXISTS(
1054           select 'history not purgeable'
1055           from ap_invoice_payments aip
1056           ,       ap_payment_history aph
1057           where aip.invoice_id = PL.invoice_id
1058           and aip.check_id = aph.check_id
1059           -- To check for posted_flag added for bug#2274656
1060           and nvl(aph.posted_flag,'N') <> 'Y'
1061           --Bug 1579474
1062           --and aph.last_update_date >= g_activity_date);
1063           and aph.last_update_date > g_activity_date);
1064 
1065   debug_info := 'Test Accounting';
1066   IF g_debug_switch in ('y','Y') THEN
1067      Print('(Do_independent_inv_checks)' ||debug_info);
1068   END IF;
1069 
1070 
1071 -- Fix for bug 2652768 made changes to below DELETE statement
1072 -- Fix for bug 2963666 Added condition to check description is not MRC upgrade
1073   DELETE /*+ PARALLEL(pl) ROWID(pl) */
1074    FROM ap_purge_invoice_list PL
1075   WHERE pl.rowid IN (
1076           Select /*+ ORDERED PARALLEL(pl1) FULL(pl1) */
1077                 pl1.rowid -- 7759218
1078           from  ap_purge_invoice_list pl1,
1079                 ap_invoices_all ai,
1080                 xla_events xe, --Bug 4588031
1081                 xla_transaction_entities xte, --Bug 4588031
1082                 xla_ae_headers xeh, --Bug 4588031
1083                 ap_system_parameters_all asp--bug5052748
1084           where xte.entity_code = 'AP_INVOICES'
1085           and NVL(XTE.SOURCE_ID_INT_1,-99) = PL1.invoice_id    --11059839
1086           AND pl1.invoice_id=ai.invoice_id
1087           AND ai.org_id=asp.org_id
1088           AND asp.set_of_books_id=xte.ledger_id
1089           and xte.entity_id = xe.entity_id
1090           and xe.event_id = xeh.event_id --Bug6318079
1091           and xe.application_id = 200
1092           and xeh.application_id = 200
1093           and xte.application_id = 200
1094           and (xeh.gl_transfer_status_code = 'N'
1095                   OR ( xeh.last_update_date > g_activity_date ))
1096           UNION
1097           Select /*+ ORDERED PARALLEL(pl1) FULL(pl1) */
1098                 pl1.rowid -- 7759218
1099           from  ap_purge_invoice_list pl1,
1100                 xla_events xe, --Bug 4588031
1101                 xla_transaction_entities xte, --Bug 4588031
1102                 ap_invoice_payments aip,
1103                 ap_system_parameters_all asp,--bug5052478
1104                 xla_ae_headers xeh --Bug 4588031
1105           where xte.entity_code = 'AP_PAYMENTS'
1106           and   NVL(XTE.SOURCE_ID_INT_1,-99) = aip.check_id          --11059839
1107           and   xte.entity_id = xe.entity_id
1108           AND   asp.set_of_books_id=xte.ledger_id
1109           AND   aip.org_id=asp.org_id
1110           and   PL1.invoice_id = aip.invoice_id
1111           and   xe.event_id = xeh.event_id
1112           and   xe.application_id = 200
1113           and   xeh.application_id = 200
1114           and   xte.application_id = 200
1115           and   (xeh.gl_transfer_status_code = 'N'
1116                   OR ( xeh.last_update_date > g_activity_date))
1117                   );
1118 
1119    /*bug9944247-end*/
1120 
1121   debug_info := 'Test Invoce matching to receipts';
1122    IF g_debug_switch in ('y','Y') THEN
1123      Print('(Do_independent_inv_checks)' ||debug_info);
1124    END IF;
1125 
1126    DELETE FROM ap_purge_invoice_list PL
1127    WHERE EXISTS (
1128           select 'matched'
1129           from ap_invoice_distributions aid, rcv_transactions rcv
1130           where aid.invoice_id = PL.invoice_id
1131           and aid.rcv_transaction_id = rcv.transaction_id
1132           and rcv.last_update_date > g_activity_date);
1133 
1134   DELETE FROM ap_purge_invoice_list PL
1135   WHERE EXISTS
1136                 (select null
1137                  from  ap_invoice_distributions ad
1138                  where ad.invoice_id = PL.invoice_id
1139                  and   ad.rcv_transaction_id is not null
1140                  and exists (
1141                  select 'matching'  from  ap_invoice_distributions ad2
1142                  where ad2.rcv_transaction_id =  ad.rcv_transaction_id
1143                  and ad2.invoice_id NOT IN (
1144                         select invoice_id
1145 			from  ap_purge_invoice_list
1146 			where double_check_flag = 'Y')));
1147 
1148   -- debug info....
1149   SELECT count(*) INTO l_list_count FROM ap_purge_invoice_list;
1150   Print(to_char(l_list_count)||' records in ap_purge_invoice_list table');
1151 
1152 
1153   RETURN (TRUE);
1154   RETURN NULL;
1155 
1156 EXCEPTION
1157   WHEN OTHERS THEN
1158       IF (SQLCODE < 0 ) then
1159          Print(SQLERRM);
1160       END IF;
1161       RETURN(FALSE);
1162 
1163 END Do_independent_inv_checks;
1164 
1165 
1166 ------------------------------------------------------------------
1167 -- Procedure: Match_pos_to_invoices_ctrl
1168 --
1169 ------------------------------------------------------------------
1170 FUNCTION Match_pos_to_invoices_ctrl
1171          (P_Purge_Name        IN  VARCHAR2,
1172           P_Purge_Status      IN  VARCHAR2,
1173           P_Calling_Sequence  IN  VARCHAR2)
1174 RETURN BOOLEAN IS
1175 
1176 debug_info   		  	VARCHAR2(200);
1177 current_calling_sequence  	VARCHAR2(2000);
1178 po_count                        NUMBER;
1179 invoice_count                   NUMBER;
1180 invs_before_po_match            NUMBER;
1181 pos_before_inv_match            NUMBER;
1182 pos_before_dependents           NUMBER;
1183 invs_before_dependents		NUMBER;
1184 start_list_count		NUMBER;
1185 list_count			NUMBER;
1186 
1187 l_first_iteration               BOOLEAN;
1188 l_po_docs_filtered_flag         BOOLEAN;
1189 
1190 l_po_return_status              VARCHAR2(1);
1191 l_po_msg                        VARCHAR2(2000);
1192 l_po_records_filtered_tmp       VARCHAR2(1);
1193 
1194 
1195 BEGIN
1196 -- Update the calling sequence
1197 --
1198 current_calling_sequence :=
1199 'Match_pos_to_reqs_ctrl<-'||P_calling_sequence;
1200 
1201 debug_info := 'Starting Match_pos_to_invoices_ctrl';
1202 IF g_debug_switch in ('y','Y') THEN
1203    Print('(Match_pos_to_invoices_ctrl)' ||debug_info);
1204 END IF;
1205 
1206 
1207 -- count_invs
1208 select count(1)
1209 into invoice_count
1210 from ap_purge_invoice_list
1211 where double_check_flag = 'Y';
1212 
1213 l_first_iteration := TRUE;
1214 
1215 LOOP   -- <loop 1>
1216 
1217   l_po_docs_filtered_flag := FALSE;
1218 
1219   LOOP   -- <loop 2>
1220 
1221         --
1222 	debug_info := 'LOOP Match_pos_to_invoices_ctrl';
1223         IF g_debug_switch in ('y','Y') THEN
1224            Print('(Match_pos_to_invoices_ctrl)' ||debug_info);
1225         END IF;
1226 
1227 	invs_before_po_match := invoice_count;
1228 
1229 	debug_info := 'LOOP match_pos_to_invoices';
1230         IF g_debug_switch in ('y','Y') THEN
1231            Print('(Match_pos_to_invoices_ctrl)' ||debug_info);
1232         END IF;
1233 
1234 	-- match_pos_to_invoices
1235 
1236         PO_AP_PURGE_GRP.filter_records
1237         (  p_api_version => 1.0,
1238            p_init_msg_list => 'T',
1239            p_commit => 'F',
1240            x_return_status => l_po_return_status,
1241            x_msg_data => l_po_msg,
1242            p_purge_status => p_purge_status,
1243            p_purge_name => p_purge_name,
1244            p_purge_category => g_category,
1245            p_action => 'FILTER DEPENDENT PO AND AP',
1246            x_po_records_filtered => l_po_records_filtered_tmp
1247          );
1248 
1249         IF (l_po_return_status <> 'S') THEN
1250             Print(l_po_msg);
1251             RETURN FALSE;
1252         END IF;
1253 
1254         IF (l_po_records_filtered_tmp = 'T') THEN
1255           l_po_docs_filtered_flag := TRUE;
1256         END IF;
1257 
1258 
1259 	-- match_invoices_to_pos
1260         IF p_purge_status = 'INITIATING' THEN
1261            delete from ap_purge_invoice_list apl
1262 	   where exists
1263 	        (select /*+ no_unnest */ null -- 7759218
1264 	         from  ap_invoice_distributions ad
1265 	         where ad.invoice_id = apl.invoice_id
1266                  and   ad.po_distribution_id is not null
1267 	         and not exists (select null
1268        		   	         from  po_purge_po_list ppl,
1269 				       po_distributions pd
1270                   	         where ppl.po_header_id =
1271 				       pd.po_header_id
1272                   	         and   pd.po_distribution_id =
1273                                        ad.po_distribution_id));
1274         ELSE
1275           --bug5052748
1276           -- re_match_invoices_to_pos
1277            update ap_purge_invoice_list apl
1278            set double_check_flag = 'N'
1279            where double_check_flag = 'Y'
1280            and   exists (select /*+NO_UNNEST*/ null
1281                          from  ap_invoice_distributions ad,po_distributions pd
1282                          where ad.invoice_id = apl.invoice_id
1283                          AND   pd.po_distribution_id=ad.po_distribution_id
1284                          and   ad.po_distribution_id is not null
1285                          and not exists (SELECT null
1286                                          FROM  po_purge_po_list ppl
1287                                          WHERE ppl.double_check_flag = 'Y'
1288                                          AND   ppl.po_header_id =pd.po_header_id));
1289 
1290         END IF;
1291 
1292 	COMMIT;
1293 
1294 	-- count invs
1295 	select count(1)
1296 	into invoice_count
1297 	from ap_purge_invoice_list
1298 	where double_check_flag = 'Y';
1299 
1300        IF (invoice_count = invs_before_po_match AND
1301            l_po_records_filtered_tmp <> 'T') THEN
1302 
1303           EXIT;
1304        END IF;
1305 
1306       if (invoice_count < invs_before_po_match) then
1307 
1308          invs_before_dependents := invoice_count;
1309 
1310          debug_info := 'Starting series of dependent invoice validations';
1311          IF g_debug_switch in ('y','Y') THEN
1312             Print('(Match_pos_to_invoices_ctrl)' ||debug_info);
1313          END IF;
1314 
1315 
1316          -- do_dependent_inv_checks
1317 
1318          LOOP  -- <loop3>
1319 
1320            -- Get invoice list count
1321            SELECT count(*)
1322            INTO   start_list_count
1323            FROM   ap_purge_invoice_list
1324            WHERE  double_check_flag = DECODE(p_purge_status, 'INITIATING', 'Y',
1325                                                    double_check_flag);
1326 
1327            IF p_purge_status = 'INITIATING' THEN
1328               -- Test Check Relationships
1329               DELETE
1330               FROM ap_purge_invoice_list PL
1331               WHERE EXISTS (
1332                          SELECT 'relational problem'
1333                          FROM ap_invoice_payments IP1,
1334                               ap_invoice_payments IP2
1335                          WHERE PL.invoice_id = IP1.invoice_id
1336                          AND   IP1.check_id = IP2.check_id
1337                          AND   IP2.invoice_id NOT IN (
1338                                  SELECT PL2.invoice_id
1339                                  FROM ap_purge_invoice_list PL2
1340                                  WHERE PL2.invoice_id =
1341                                           IP2.invoice_id)
1342                           );
1343 
1344            ELSE
1345              --bug5052748
1346               -- retest_check_relationships
1347               UPDATE ap_purge_invoice_list PL
1348               SET PL.double_check_flag = 'N'
1349               WHERE PL.double_check_flag = 'Y'
1350               AND EXISTS (
1351                       SELECT /*+NO_UNNEST*/'relational problem'
1352                       FROM ap_invoice_payments IP1, ap_invoice_payments IP2
1353                       WHERE PL.invoice_id = IP1.invoice_id
1354                       AND   IP1.check_id = IP2.check_id
1355                       AND   IP2.invoice_id NOT IN (
1356                               SELECT PL2.invoice_id
1357                               FROM ap_purge_invoice_list PL2
1358                               WHERE PL2.invoice_id = IP2.invoice_id
1359                               AND PL2.double_check_flag ='Y'));
1360 
1361            END IF;
1362 
1363            -- get invoice list count
1364            SELECT count(*)
1365            INTO list_count
1366            FROM ap_purge_invoice_list
1367            WHERE  double_check_flag = DECODE(p_purge_status, 'INITIATING', 'Y',
1368                                                    double_check_flag);
1369 
1370            if start_list_count = list_count then
1371                invoice_count := list_count;
1372                EXIT;
1373            end if;
1374          END LOOP;   -- end <loop 3>
1375          COMMIT;
1376        END IF;  -- invoice count < inv_before_po_match
1377   END LOOP;   -- end <loop 2>
1378 
1379   IF (l_first_iteration OR
1380       l_po_docs_filtered_flag) THEN
1381 
1382      PO_AP_PURGE_GRP.filter_records
1383      (  p_api_version => 1.0,
1384         p_init_msg_list => 'T',
1385         p_commit => 'F',
1386         x_return_status => l_po_return_status,
1387         x_msg_data => l_po_msg,
1388         p_purge_status => p_purge_status,
1389         p_purge_name => p_purge_name,
1390         p_purge_category => g_category,
1391         p_action => 'FILTER DEPENDENT PO AND REQ',
1392         x_po_records_filtered => l_po_records_filtered_tmp
1393       );
1394 
1395      IF (l_po_return_status <> 'S') THEN
1396          Print(l_po_msg);
1397          RETURN FALSE;
1398      END IF;
1399      IF (l_po_records_filtered_tmp <> 'T') THEN
1400          l_po_docs_filtered_flag := FALSE;
1401      END IF;
1402   END IF;
1403 
1404   l_first_iteration := FALSE;
1405 
1406   EXIT WHEN NOT l_po_docs_filtered_flag;
1407 
1408 END LOOP;
1409 
1410 debug_info := 'End Match_pos_to_invoices_ctrl';
1411 IF g_debug_switch in ('y','Y') THEN
1412    Print('(Match_pos_to_invoices_ctrl)' ||debug_info);
1413 END IF;
1414 
1415 RETURN (TRUE);
1416 
1417 RETURN NULL; EXCEPTION
1418  WHEN OTHERS then
1419    IF (SQLCODE < 0 ) then
1420      Print(SQLERRM);
1421    END IF;
1422      RETURN (FALSE);
1423 END Match_pos_to_invoices_ctrl;
1424 
1425 
1426 ------------------------------------------------------------------
1427 -- Procedure: Seed_Chv_By_Cum
1428 --
1429 ------------------------------------------------------------------
1430 FUNCTION Seed_chv_by_cum
1431          (P_Purge_Name         IN  VARCHAR2,
1432           P_Calling_Sequence   IN  VARCHAR2)
1433 RETURN BOOLEAN IS
1434 
1435 debug_info   		  	VARCHAR2(200);
1436 current_calling_sequence  	VARCHAR2(2000);
1437 
1438 BEGIN
1439   -- Update the calling sequence
1440   --
1441   current_calling_sequence := 'seed_chv_by_cum<-'||P_calling_sequence;
1442 
1443   debug_info := 'Starting seed_chv_by_cum';
1444   IF g_debug_switch in ('y','Y') THEN
1445      Print('(seed_chv_by_cum)' ||debug_info);
1446   END IF;
1447 
1448   --
1449   insert into chv_purge_cum_list
1450        	 (cum_period_id,
1451           purge_name,
1452           double_check_flag)
1453   select  ccp.cum_period_id,
1454           p_purge_name,
1455           'Y'
1456   from    chv_cum_periods ccp
1457   where   ccp.organization_id = g_organization_id
1458   and     NVL(ccp.cum_period_end_date, sysdate + 1) <= g_activity_date
1459   and     NVL(ccp.cum_period_end_date,sysdate + 1) < sysdate;
1460 
1461   debug_info := 'Starting seeding items in CUM';
1462   IF g_debug_switch in ('y','Y') THEN
1463      Print('(seed_chv_by_cum)' ||debug_info);
1464   END IF;
1465 
1466   insert into chv_purge_schedule_list
1467   	 (schedule_item_id,
1468           purge_name,
1469           double_check_flag)
1470   select  csi.schedule_item_id,
1471           p_purge_name,
1472           'Y'
1473   from    chv_schedule_items csi,
1474           chv_schedule_headers csh,
1475           chv_purge_cum_list cpcl,
1476 	  chv_cum_periods ccp
1477   where   csh.schedule_id = csi.schedule_id
1478   and     csh.schedule_horizon_start between ccp.cum_period_start_date
1479 				       and ccp.cum_period_end_date
1480   and     ccp.cum_period_id = cpcl.cum_period_id
1481   and     csi.organization_id = g_organization_id;
1482 
1483   RETURN (TRUE);
1484 
1485 RETURN NULL;
1486 
1487 EXCEPTION
1488   WHEN OTHERS THEN
1489        IF (SQLCODE < 0 ) THEN
1490     	   Print(SQLERRM);
1491       END IF;
1492    RETURN (FALSE);
1493 END Seed_chv_by_cum;
1494 
1495 
1496 ------------------------------------------------------------------
1497 -- Procedure: Seed_Chv_By_Org
1498 --
1499 ------------------------------------------------------------------
1500 FUNCTION Seed_chv_by_org
1501          (P_Purge_Name           IN  VARCHAR2,
1502           P_Calling_Sequence     IN  VARCHAR2)
1503 RETURN BOOLEAN IS
1504 
1505 debug_info   		  	VARCHAR2(200);
1506 current_calling_sequence  	VARCHAR2(2000);
1507 
1508 BEGIN
1509   -- Update the calling sequence
1510   --
1511   current_calling_sequence := 'seed_chv_by_org<-'||P_calling_sequence;
1512 
1513   debug_info := 'Starting seed_chv_by_org';
1514   IF g_debug_switch in ('y','Y') THEN
1515      Print('(seed_chv_by_org)' ||debug_info);
1516   END IF;
1517 
1518    --
1519   insert into chv_purge_schedule_list
1520    	 (schedule_item_id,
1521        	  purge_name,
1522           double_check_flag)
1523   select  csi.schedule_item_id,
1524           p_purge_name,
1525           'Y'
1526   from    chv_schedule_items csi,
1527           chv_schedule_headers csh
1528   where   csh.schedule_id = csi.schedule_id
1529   and     csh.last_update_date <= g_activity_date
1530   and     NVL(csi.item_purge_status,'N') <> 'PURGED'
1531   and     csi.organization_id = g_organization_id;
1532 
1533   RETURN (TRUE);
1534   RETURN NULL;
1535 
1536 EXCEPTION
1537 	WHEN OTHERS THEN
1538 	   IF (SQLCODE < 0 ) THEN
1539      	      Print(SQLERRM);
1540    	   END IF;
1541      	   RETURN (FALSE);
1542 END seed_chv_by_org;
1543 
1544 
1545 ------------------------------------------------------------------
1546 -- Procedure: Seed_Invoices
1547 --
1548 ------------------------------------------------------------------
1549 FUNCTION Seed_Invoices
1550 	 (P_Purge_Name            IN  VARCHAR2,
1551           P_Using_Accrual_Basis   IN  VARCHAR2,
1552           P_Using_Cash_Basis      IN  VARCHAR2,
1553           P_Calling_Sequence      IN  VARCHAR2)
1554 RETURN BOOLEAN IS
1555 
1556 debug_info   		  	VARCHAR2(200);
1557 current_calling_sequence  	VARCHAR2(2000);
1558 temp number;
1559 l_approx_rows                    NUMBER ;     -- Bug 9268290
1560 l_pay_alone                     VARCHAR2(1) ; -- Bug 9268290
1561 BEGIN
1562   -- Update the calling sequence
1563   --
1564    current_calling_sequence :=
1565    'Seed_invoices<-'||P_calling_sequence;
1566   --
1567    debug_info := 'Starting Seed_invoices';
1568    IF g_debug_switch in ('y','Y') THEN
1569       Print('(Inserting into ap_purge_invoice_list)' ||debug_info);
1570       Print('P_Purge_Name:'||p_purge_name);
1571       Print('P_Using_Accrual_Basis:'||p_using_accrual_basis);
1572       Print('P_Using_Cash_Basis:'||p_using_cash_basis);
1573       Print('g_activity_date:'||g_activity_date);
1574    END IF;
1575 
1576    -- Bug 9268290 Begin
1577    --9481539
1578    SELECT NVL( approx_rows, 0 ),
1579           NVL(pay_alone,'A')
1580    INTO   l_approx_rows,
1581           l_pay_alone
1582    FROM   financials_purges
1583    WHERE  purge_name = p_purge_name ;
1584 
1585    IF g_debug_switch in ('y','Y') THEN
1586       Print(' approx_rows: ' ||l_approx_rows|| ' pay_alone: ' || l_pay_alone );
1587    END IF ;
1588    -- Bug 9268290 End
1589    -- 9481539 modified the decode statement.
1590    -- 9531253 added parallel hint.
1591 
1592         /*bug9944247- modified the sql for to use OPQ hints for better perfomance */
1593 
1594         EXECUTE IMMEDIATE 'ALTER SESSION FORCE PARALLEL QUERY';
1595 
1596         -- modified the below query for bug13799066
1597         /* Bug 10391241 added join for ap_invoice_lines_all */
1598         INSERT INTO ap_purge_invoice_list pl
1599           (
1600             invoice_id,
1601             purge_name,
1602             double_check_flag
1603           )
1604         WITH purge_inv AS
1605           (SELECT /*+ MATERIALIZE INDEX(i AP_INVOICES_N5) */ rowid inv_rowid
1606              FROM ap_invoices i
1607             WHERE i.invoice_date <= g_activity_date
1608           ) ,
1609           purge_zero_inv AS
1610           (SELECT /*+ MATERIALIZE INDEX(i AP_INVOICES_N4)*/ rowid inv_rowid
1611              FROM ap_invoices i
1612             WHERE i.invoice_amount = 0
1613           )
1614         SELECT invoice_id, p_purge_name purge_name, 'Y' double_check_flag
1615           FROM
1616           (SELECT invoice_id, check_id
1617              FROM
1618             (SELECT /*+ ORDERED PARALLEL(PI) FULL(pi) USE_NL(i,p,c,d,l)
1619                     INDEX(p AP_INVOICE_PAYMENTS_N1) INDEX(c AP_CHECKS_U1) INDEX(d
1620                     AP_INVOICE_DISTRIBUTIONS_U1) INDEX(l AP_INVOICE_LINES_U1) */
1621               i.invoice_id, MIN(c.check_id) check_id
1622             FROM purge_inv pi,
1623               ap_invoices i,
1624               ap_invoice_payments p,
1625               ap_checks c,
1626               ap_invoice_distributions d,
1627               ap_invoice_lines l
1628             WHERE i.rowid    = pi.inv_rowid
1629             AND i.invoice_id = l.invoice_id
1630             AND i.invoice_id = d.invoice_id
1631             AND l.line_number = d.invoice_line_number -- bug14237038
1632             AND i.payment_status_flag||'' = 'Y'
1633             AND i.invoice_type_lookup_code <> 'PREPAYMENT'
1634             AND d.posted_flag||'' = 'Y'
1635             AND(d.accrual_posted_flag = DECODE(p_using_accrual_basis, 'Y', 'Y', d.accrual_posted_flag)
1636             OR d.cash_posted_flag = DECODE(p_using_cash_basis, 'Y', 'Y', d.cash_posted_flag))
1637             AND d.last_update_date <= g_activity_date
1638             AND	l.last_update_date <= g_activity_date
1639             AND i.last_update_date <= g_activity_date
1640             AND p.invoice_id = i.invoice_id
1641             AND p.check_id = c.check_id
1642             AND p.last_update_date <= g_activity_date
1643             AND c.last_update_date <= g_activity_date
1644             AND NVL(i.exclusive_payment_flag, 'N') = DECODE(l_pay_alone, 'N', 'N', 'A',
1645                                                 NVL(i.exclusive_payment_flag, 'N'), 'Y')
1646             GROUP BY i.invoice_id
1647             UNION
1648             SELECT /*+ ORDERED PARALLEL(pzi) FULL(pzi) USE_NL(i,p,d)
1649                        INDEX(p AP_INVOICE_PAYMENTS_N1) INDEX(d AP_INVOICE_DISTRIBUTIONS_U1) */
1650                i.invoice_id, NULL check_id
1651               FROM purge_zero_inv pzi,
1652                    ap_invoices i,
1653                    ap_invoice_payments p,
1654                    ap_invoice_distributions d
1655             WHERE i.rowid                   = pzi.inv_rowid
1656               AND p.invoice_id (+)            = i.invoice_id
1657               AND i.invoice_id                = d.invoice_id(+)
1658               AND i.last_update_date         <= g_activity_date
1659               AND i.invoice_date             <= g_activity_date
1660               AND i.invoice_type_lookup_code <> 'PREPAYMENT'
1661               AND p.check_id                 IS NULL
1662             GROUP BY i.invoice_id
1663             HAVING SUM(NVL(d.amount, 0)) = 0
1664             )
1665           ORDER BY DECODE(l_pay_alone, 'Y', invoice_id, 'N', check_id, check_id),
1666             DECODE(l_pay_alone, 'Y', check_id, 'N', invoice_id, invoice_id)
1667           )
1668         WHERE(l_approx_rows = 0 OR rownum <= l_approx_rows) ;
1669 
1670 	EXECUTE IMMEDIATE 'ALTER SESSION ENABLE PARALLEL QUERY';
1671 
1672         /*bug9944247-end*/
1673 
1674         -- Bug 9268290 select count(*) into temp from ap_purge_invoice_list;
1675         temp := SQL%ROWCOUNT ;
1676 
1677         Print(to_char(temp)||' records in ap_purge_invoice list table');
1678 
1679         debug_info := 'End Seed_invoices';
1680         IF g_debug_switch in ('y','Y') THEN
1681            Print('(Done inserting into ap_purge_invoice_list)' ||debug_info);
1682         END IF;
1683 
1684         RETURN(TRUE);
1685         RETURN NULL;
1686 
1687 EXCEPTION
1688         WHEN OTHERS THEN
1689           IF (SQLCODE < 0 ) then
1690              Print(SQLERRM);
1691           END IF;
1692           RETURN(FALSE);
1693 END Seed_invoices;
1694 
1695 
1696 ------------------------------------------------------------------
1697 -- Procedure: Select_Seed_Vendors
1698 --
1699 ------------------------------------------------------------------
1700 FUNCTION Seed_Vendors
1701          (P_Purge_Name           IN  VARCHAR2,
1702           P_Calling_Sequence     IN  VARCHAR2)
1703 RETURN BOOLEAN IS
1704 
1705 debug_info   		  	VARCHAR2(200);
1706 current_calling_sequence  	VARCHAR2(2000);
1707 
1708 BEGIN
1709   -- Update the calling sequence
1710   --
1711 	current_calling_sequence :=
1712  	'Seed_Vendors<-'||P_calling_sequence;
1713 
1714 	debug_info := 'Starting Seed_Vendors';
1715         IF g_debug_switch in ('y','Y') THEN
1716            Print('(Seed_Vendors)' ||debug_info);
1717         END IF;
1718 
1719    --
1720 	insert into po_purge_vendor_list
1721        		(vendor_id,
1722 		purge_name,
1723 		double_check_flag)
1724 	select  vnd.vendor_id,
1725 		p_purge_name,
1726 		'Y'
1727 	from 	ap_suppliers vnd
1728 	where   vnd.end_date_active <= g_activity_date
1729 	and not exists (select 'vnd.vendor is a parent of
1730 			another vendor'
1731                 	from ap_suppliers v
1732                 	where v.parent_vendor_id =
1733 			      vnd.vendor_id)
1734         --Bug 2653578
1735         and PO_THIRD_PARTY_STOCK_GRP.validate_supplier_purge(
1736                                                 vnd.vendor_id) = 'TRUE';
1737 
1738 	-- test vendors
1739 	if g_payables_status = 'Y' then
1740 	   if g_assets_status = 'Y' then
1741               debug_info := 'test_fa_vendors';
1742               IF g_debug_switch in ('y','Y') THEN
1743                  Print('(Seed_Vendors)' ||debug_info);
1744               END IF;
1745 
1746 
1747 	      -- test fa vendors
1748  	      delete from po_purge_vendor_list pvl
1749 	      where exists
1750 	             (select null
1751 		      from  fa_mass_additions fma
1752 		      where fma.po_vendor_id = pvl.vendor_id)
1753 		      or    exists
1754 				(select null
1755 				from  fa_asset_invoices fai
1756 				where fai.po_vendor_id = pvl.vendor_id);
1757             end if;
1758 
1759             debug_info := 'test_ap_vendors';
1760             IF g_debug_switch in ('y','Y') THEN
1761                Print('(Seed_Vendors)' ||debug_info);
1762             END IF;
1763 
1764 
1765 		-- test ap vendors
1766 		delete from po_purge_vendor_list pvl
1767 		where exists
1768 			(select null
1769 			from  ap_invoices_all ai
1770 			where ai.vendor_id = pvl.vendor_id)
1771 		or    exists
1772 			(select null
1773 			from ap_selected_invoices_all asi,
1774                      	     ap_supplier_sites_all pvs
1775 			where asi.vendor_site_id =
1776 		 	      pvs.vendor_site_id
1777                 and   pvs.vendor_id      = pvl.vendor_id)
1778 		or    exists
1779 			(select null
1780 			from ap_recurring_payments_all arp
1781 			where arp.vendor_id = pvl.vendor_id);
1782 	end if;
1783 
1784 	if g_purchasing_status = 'Y' then
1785 
1786            debug_info := 'test_po_vendors';
1787            IF g_debug_switch in ('y','Y') THEN
1788               Print('(Seed_Vendors)' ||debug_info);
1789            END IF;
1790 
1791 
1792 		-- test_po_vendors
1793 		delete from po_purge_vendor_list pvl
1794 		where exists   (select null
1795 				from po_headers_all ph
1796 				where ph.vendor_id =
1797 				      pvl.vendor_id)
1798 		or  exists     (select null
1799 				from rcv_shipment_headers
1800 		        	rcvsh
1801 				where rcvsh.vendor_id =
1802 				      pvl.vendor_id)
1803 		or  exists     (select null
1804 				from po_rfq_vendors rfq
1805 				where rfq.vendor_id =
1806 		 		      pvl.vendor_id);
1807 	end if;
1808 
1809 	COMMIT;
1810 	debug_info := 'End Seed_vendors';
1811         IF g_debug_switch in ('y','Y') THEN
1812            Print('(Seed_Vendors)' ||debug_info);
1813         END IF;
1814 
1815 	RETURN (TRUE);
1816 
1817 RETURN NULL; EXCEPTION
1818 	WHEN OTHERS THEN
1819 	   IF (SQLCODE < 0 ) THEN
1820      	      Print(SQLERRM);
1821    	   END IF;
1822      	   RETURN (FALSE);
1823 END Seed_vendors;
1824 
1825 
1826 ------------------------------------------------------------------
1827 -- Procedure: Test_Vendors
1828 --
1829 ------------------------------------------------------------------
1830 FUNCTION Test_Vendors
1831 	 (P_calling_sequence     IN  VARCHAR2)
1832 RETURN BOOLEAN IS
1833 
1834 debug_info   		  	VARCHAR2(200);
1835 current_calling_sequence  	VARCHAR2(2000);
1836 
1837 BEGIN
1838   -- Update the calling sequence
1839   --
1840   current_calling_sequence :=
1841   'Test_vendors<-'||P_calling_sequence;
1842 
1843   debug_info := 'Starting Test_vendors';
1844   IF g_debug_switch in ('y','Y') THEN
1845      Print('(Test_Vendors)' ||debug_info);
1846   END IF;
1847 
1848 
1849   if (g_payables_status = 'Y') then
1850 
1851      if (g_assets_status = 'Y') then
1852 
1853         debug_info := 'test_fa_vendors';
1854         IF g_debug_switch in ('y','Y') THEN
1855            Print('(Test_Vendors)' ||debug_info);
1856         END IF;
1857 
1858 	-- test_fa_vendors
1859 	delete from po_purge_vendor_list pvl
1860 	where exists   (select null
1861 	        	from  fa_mass_additions fma
1862 		        where fma.po_vendor_id =
1863                               pvl.vendor_id)
1864         or    exists   (select null
1865 		        from  fa_asset_invoices fai
1866 		        where fai.po_vendor_id =
1867                               pvl.vendor_id);
1868      end if;
1869 
1870      -- test_ap_vendors
1871 
1872 
1873      delete from po_purge_vendor_list pvl
1874      where exists   (select null
1875 		     from  ap_invoices_all ai
1876 		     where ai.vendor_id = pvl.vendor_id)
1877      or    exists   (select null
1878 		     from ap_selected_invoices_all asi,
1879                      ap_supplier_sites_all pvs
1880 		     where asi.vendor_site_id =
1881                            pvs.vendor_site_id
1882                      and   pvs.vendor_id  =  pvl.vendor_id)
1883      or    exists   (select null
1884 		     from ap_recurring_payments_all arp
1885 		     where arp.vendor_id = pvl.vendor_id);
1886   end if;
1887 
1888   -- check_po_status
1889 
1890   if (g_purchasing_status = 'Y') then
1891 
1892      debug_info := 'check_po_status';
1893      IF g_debug_switch in ('y','Y') THEN
1894         Print('(Test_Vendors)' ||debug_info);
1895      END IF;
1896 
1897      delete from po_purge_vendor_list pvl
1898      where exists   (select null
1899 		     from po_headers_all ph
1900 		     where ph.vendor_id = pvl.vendor_id)
1901      or  exists     (select null
1902 		     from rcv_shipment_headers rcvsh
1903 		     where rcvsh.vendor_id = pvl.vendor_id)
1904      or  exists     (select null
1905 		     from po_rfq_vendors rfq
1906 		     where rfq.vendor_id = pvl.vendor_id)
1907      or  exists     (select null
1908                      from rcv_headers_interface rhi
1909                      where rhi.vendor_id = pvl.vendor_id)
1910      or  exists     (select null
1911                      from rcv_transactions_interface rti
1912                      where rti.vendor_id = pvl.vendor_id);
1913 
1914 
1915   end if;
1916 
1917   -- check_vendors_in_chv
1918 
1919   if (g_chv_status = 'Y') then
1920      debug_info := 'Check_chv_status';
1921      IF g_debug_switch in ('y','Y') THEN
1922         Print('(Test_Vendors)' ||debug_info);
1923      END IF;
1924 
1925      delete from po_purge_vendor_list pvl
1926      where exists   (select null
1927         from chv_schedule_headers csh
1928         where csh.vendor_id = pvl.vendor_id);
1929   end if;
1930 
1931   -- check_vendors_in_edi
1932 
1933   if (g_edi_status = 'Y') then
1934      debug_info := 'Check_edi_status';
1935      IF g_debug_switch in ('y','Y') THEN
1936         Print('(Test_Vendors)' ||debug_info);
1937      END IF;
1938 
1939      delete from po_purge_vendor_list pvl
1940      where exists   (select null
1941                 from  ece_tp_details etd,
1942                       ap_supplier_sites_all pvs
1943                 where etd.tp_header_id = pvs.tp_header_id
1944                 and pvs.vendor_id = pvl.vendor_id
1945                 and etd.last_update_date > g_activity_date);
1946 --Bug 1781451 Remove from purge list all vendors with last_update_date
1947 --greater than last activity date in Concurrent request parameters
1948 --                and etd.last_update_date <= g_activity_date);
1949 
1950   end if;
1951 
1952 
1953   -- check_vendors_in_sourcing_rules
1954 
1955   if (g_mrp_status = 'Y') then
1956      debug_info := 'Check_vendors_in_sourcing_rules';
1957      IF g_debug_switch in ('y','Y') THEN
1958         Print('(Test_Vendors)' ||debug_info);
1959      END IF;
1960 
1961 --1700943, removing the code below that checks for activity
1962 --dates of the sourcing rules.  we should not purge the
1963 --vendor if it is tied to an inactive rule
1964 
1965      delete from po_purge_vendor_list pvl
1966      where exists   (select null
1967                      from  mrp_sr_source_org msso
1968                      where msso.vendor_id = pvl.vendor_id);
1969 
1970   end if;
1971 
1972   COMMIT;
1973 
1974   debug_info := 'End Test_Vendors';
1975   IF g_debug_switch in ('y','Y') THEN
1976      Print('(Test_Vendors)' ||debug_info);
1977   END IF;
1978 
1979   RETURN (TRUE);
1980 
1981 RETURN NULL;
1982 
1983 EXCEPTION
1984   WHEN OTHERS then
1985     IF (SQLCODE < 0 ) then
1986       Print(SQLERRM);
1987     END IF;
1988     RETURN (FALSE);
1989 
1990 END Test_Vendors;
1991 
1992 
1993 ------------------------------------------------------------------
1994 -- Procedure: Seed_Purge_Tables
1995 -- This procedure is used to select the data to be purged and
1996 -- insert into purge tables.
1997 ------------------------------------------------------------------
1998 FUNCTION Seed_purge_tables
1999 	 (P_Category          IN  VARCHAR2,
2000           P_Purge_Name        IN  VARCHAR2,
2001           P_Activity_Date     IN  DATE,
2002           P_Organization_ID   IN  NUMBER,
2003           P_PA_Status         IN  VARCHAR2,
2004           P_Purchasing_Status IN  VARCHAR2,
2005           P_Payables_Status   IN  VARCHAR2,
2006           P_Assets_Status     IN  VARCHAR2,
2007           P_Chv_Status        IN  VARCHAR2,
2008           P_EDI_Status        IN  VARCHAR2,
2009           P_MRP_Status        IN  VARCHAR2,
2010           P_Debug_Switch      IN  VARCHAR2,
2011           P_calling_sequence  IN  VARCHAR2)
2012 RETURN BOOLEAN IS
2013 
2014 debug_info   		  	VARCHAR2(200);
2015 current_calling_sequence  	VARCHAR2(2000);
2016 l_status                        VARCHAR2(30);
2017 
2018 l_recon_acctg_flag              VARCHAR2(1);
2019 l_using_accrual_basis           VARCHAR2(1);
2020 l_using_cash_basis              VARCHAR2(1);
2021 
2022 l_po_return_status              VARCHAR2(1);
2023 l_po_msg                        VARCHAR2(2000);
2024 l_po_records_filtered           VARCHAR2(1);
2025 l_purge_without_rev             varchar2(10);
2026 l_pay_alone                     varchar2(1);
2027 
2028 BEGIN
2029 
2030   g_debug_switch := p_debug_switch;
2031 
2032   g_activity_date := P_Activity_Date;
2033   g_organization_id := P_Organization_ID;
2034   g_category := P_Category;
2035   g_pa_status := P_PA_Status;
2036   g_purchasing_Status := P_Purchasing_Status;
2037   g_payables_status := P_Payables_Status;
2038   g_assets_status := P_Assets_Status;
2039   g_chv_status := P_Chv_Status;
2040   g_edi_status := P_EDI_Status;
2041   g_mrp_status := P_MRP_Status;
2042 
2043   -- Update the calling sequence
2044   --
2045   current_calling_sequence :=
2046   'Seed_purge_tables<-'||P_calling_sequence;
2047 
2048 
2049   debug_info := 'Get Accounting Methods';
2050   IF g_debug_switch in ('y','Y') THEN
2051      Print('(Seed_purge_tables)'||debug_info);
2052   END IF;
2053 
2054   IF (Get_Accounting_Method(
2055                   l_recon_acctg_flag,
2056                   l_using_accrual_basis,
2057                   l_using_cash_basis,
2058                   'Get Accounting Method') <> TRUE) THEN
2059       Print('Seed_simple_invoices failed');
2060       Return(FALSE);
2061   END IF;
2062 
2063 
2064   debug_info := 'Starting Seed_purge_tables';
2065   IF g_debug_switch in ('y','Y') THEN
2066      Print('(Seed_purge_tables)'||debug_info);
2067   END IF;
2068 
2069     --9481539
2070   select nvl(pay_alone,'A')
2071     into l_pay_alone
2072     from financials_purges
2073    where purge_name =  P_Purge_Name ;
2074 
2075   -- Simple Invoices
2076   if (p_category = 'SIMPLE INVOICES') then
2077 
2078      debug_info := 'Simple Invoices';
2079      IF g_debug_switch in ('y','Y') THEN
2080         Print('(Seed_purge_tables)' ||debug_info);
2081      END IF;
2082 
2083      if (Seed_Invoices(
2084                  p_purge_name,
2085                  l_using_accrual_basis,
2086                  l_using_cash_basis,
2087                  'Seed_purge_tables') <> TRUE) then
2088 	Print('Seed_simple_invoices failed');
2089 	Return(FALSE);
2090      end if;
2091 
2092      if (Do_Independent_Inv_Checks(
2093                        l_using_accrual_basis,
2094                        l_using_cash_basis,
2095                        l_recon_acctg_flag,
2096                        'Seed_purge_tables') <> TRUE) then
2097 	Print('Do_independent_inv_checks failed');
2098 	Return(FALSE);
2099      end if;
2100 
2101      --9481539 bypassing this call for pay alone invoices
2102      if(l_pay_alone <>'Y') then
2103        if (Do_Dependent_inv_checks('Seed_purge_tables')<>
2104 	   TRUE) then
2105 	   Print('Do_dependent_inv_checks failed');
2106 	   Return(FALSE);
2107        end if;
2108      end if ;
2109 
2110   elsif (p_category IN ('SIMPLE REQUISITIONS', 'SIMPLE POS')) then
2111 
2112      debug_info := 'Call PO Purge API';
2113      IF g_debug_switch in ('y','Y') THEN
2114         Print('(Seed_purge_tables)' ||debug_info);
2115      END IF;
2116 
2117      PO_AP_PURGE_GRP.seed_records
2118      (  p_api_version => 1.0,
2119         p_init_msg_list => 'T',
2120         p_commit => 'F',
2121         x_return_status => l_po_return_status,
2122         x_msg_data => l_po_msg,
2123         p_purge_name => p_purge_name,
2124         p_purge_category => p_category,
2125         p_last_activity_date => p_activity_date
2126      );
2127 
2128      IF (l_po_return_status <> 'S') THEN
2129          Print(l_po_msg);
2130          RETURN FALSE;
2131      END IF;
2132 
2133      PO_AP_PURGE_GRP.filter_records
2134      (  p_api_version => 1.0,
2135         p_init_msg_list => 'T',
2136         p_commit => 'F',
2137         x_return_status => l_po_return_status,
2138         x_msg_data => l_po_msg,
2139         p_purge_status => 'INITIATING',
2140         p_purge_name => p_purge_name,
2141         p_purge_category => p_category,
2142         p_action => NULL,
2143         x_po_records_filtered => l_po_records_filtered
2144       );
2145 
2146      IF (l_po_return_status <> 'S') THEN
2147          Print(l_po_msg);
2148          RETURN FALSE;
2149      END IF;
2150 
2151   elsif (p_category = 'MATCHED POS AND INVOICES') then
2152      debug_info := 'Invoices';
2153      IF g_debug_switch in ('y','Y') THEN
2154         Print('(Seed_purge_tables)' ||debug_info);
2155      END IF;
2156 
2157      if (Seed_Invoices(
2158                  p_purge_name,
2159                  l_using_accrual_basis,
2160                  l_using_cash_basis,
2161                  'Seed_purge_tables') <> TRUE) then
2162 	Print('Seed_invoices failed');
2163 	Return(FALSE);
2164      end if;
2165 
2166      debug_info := 'Purchase Orders';
2167      IF g_debug_switch in ('y','Y') THEN
2168         Print('(Seed_purge_tables)' ||debug_info);
2169      END IF;
2170 
2171 
2172      PO_AP_PURGE_GRP.seed_records
2173      (  p_api_version => 1.0,
2174         p_init_msg_list => 'T',
2175         p_commit => 'F',
2176         x_return_status => l_po_return_status,
2177         x_msg_data => l_po_msg,
2178         p_purge_name => p_purge_name,
2179         p_purge_category => p_category,
2180         p_last_activity_date => p_activity_date
2181      );
2182 
2183      IF (l_po_return_status <> 'S') THEN
2184          Print(l_po_msg);
2185          RETURN FALSE;
2186      END IF;
2187 
2188 
2189      PO_AP_PURGE_GRP.filter_records
2190      (  p_api_version => 1.0,
2191         p_init_msg_list => 'T',
2192         p_commit => 'F',
2193         x_return_status => l_po_return_status,
2194         x_msg_data => l_po_msg,
2195         p_purge_status => 'INITIATING',
2196         p_purge_name => p_purge_name,
2197         p_purge_category => p_category,
2198         p_action => 'FILTER REF PO AND REQ',
2199         x_po_records_filtered => l_po_records_filtered
2200       );
2201 
2202      IF (l_po_return_status <> 'S') THEN
2203          Print(l_po_msg);
2204          RETURN FALSE;
2205      END IF;
2206 
2207      if (Do_Independent_Inv_Checks(
2208                        l_using_accrual_basis,
2209                        l_using_cash_basis,
2210                        l_recon_acctg_flag,
2211                        'Seed_purge_tables') <> TRUE) then
2212 	Print('Do_independent_inv_checks failed');
2213 	Return(FALSE);
2214      end if;
2215 
2216      --9481539 bypassing this call for pay alone invoices
2217      if(l_pay_alone <>'Y') then
2218         if (Do_Dependent_Inv_Checks('Seed_purge_tables') <> TRUE) then
2219 	   Print('Do_dependent_inv_checks failed');
2220 	   Return(FALSE);
2221         end if;
2222      end if;
2223 
2224      debug_info := 'Matching POs to Invoices';
2225      IF g_debug_switch in ('y','Y') THEN
2226         Print('(Seed_purge_tables)' ||debug_info);
2227      END IF;
2228 
2229 
2230      if (Match_Pos_To_Invoices_ctrl(
2231                        P_Purge_Name,
2232                        'INITIATING',
2233                        'Seed_purge_tables') <> TRUE) then
2234 	Print('Match_pos_to_Invoices_ctrl failed');
2235 	Return(FALSE);
2236      end if;
2237 
2238   elsif (p_category = 'VENDORS') then
2239 
2240      debug_info := 'Vendors';
2241      IF g_debug_switch in ('y','Y') THEN
2242         Print('(Seed_purge_tables)' ||debug_info);
2243      END IF;
2244 
2245      if (Seed_Vendors(
2246                        P_Purge_Name,
2247                        'Seed_purge_tables') <> TRUE) then
2248 	Print('Seed_Vendors failed');
2249 	Return(FALSE);
2250      end if;
2251 
2252      if (Test_Vendors('Seed_purge_tables') <> TRUE) then
2253 	Print('Test_Vendors failed');
2254 	Return(FALSE);
2255      end if;
2256 
2257   elsif (p_category = 'SCHEDULES BY ORGANIZATION') then
2258 
2259      debug_info := 'Schedules by Org';
2260      IF g_debug_switch in ('y','Y') THEN
2261         Print('(Seed_purge_tables)' ||debug_info);
2262      END IF;
2263 
2264      if (Seed_Chv_By_Org(
2265                         p_purge_name,
2266                         'Seed_purge_tables') <> TRUE) then
2267          Print('Seed_chv_by_org failed');
2268 	 Return(FALSE);
2269      end if;
2270 
2271      if (Check_Chv_In_Cum('Seed_purge_tables') <> TRUE) then
2272          Print('check_chv_in_cum failed');
2273 	 Return(FALSE);
2274      end if;
2275 
2276      if (Check_Chv_In_Edi('Seed_purge_tables') <> TRUE) then
2277          Print('check_chv_in_edi failed');
2278 	 Return(FALSE);
2279      end if;
2280 
2281   elsif (p_category = 'SCHEDULES BY CUM PERIODS') then
2282 
2283      debug_info := 'Schedules by CUM Periods';
2284      IF g_debug_switch in ('y','Y') THEN
2285         Print('(Seed_purge_tables)' ||debug_info);
2286      END IF;
2287 
2288      if (Seed_Chv_By_Cum(
2289                       p_purge_name,
2290                       'Seed_purge_tables') <> TRUE) then
2291          Print('Seed_chv_by_cum failed');
2292 	 Return(FALSE);
2293      end if;
2294 
2295   else
2296 
2297      debug_info := 'An invalid purge category was entered.';
2298      Print('(Seed_purge_tables)'||debug_info);
2299      Print(' Valid Categories are : SIMPLE INVOICES, SIMPLE REQUISITIONS ,');
2300      Print('SIMPLE POS, MATCHED POS AND INVOICES ,');
2301      Print('SCHEDULES BY ORGANIZATION and SCHEDULES BY CUM PERIODS');
2302 
2303      l_status := 'COMPLETED-ABORTED';
2304 
2305      if (Set_Purge_Status(l_status,
2306                           p_purge_name,
2307                           p_debug_switch,
2308                           'Seed_Purge_Tables') <> TRUE) then
2309         Print(' Set_Purge_Status failed.');
2310         Return(FALSE);
2311      end if;
2312 
2313      RETURN(TRUE);
2314   end if;
2315 
2316 RETURN NULL; EXCEPTION
2317   WHEN OTHERS then
2318     IF (SQLCODE < 0 ) then
2319        Print(SQLERRM);
2320     END IF;
2321     RETURN (FALSE);
2322 
2323 END Seed_purge_tables;
2324 
2325 
2326 /*==========================================================================
2327   Function: Invoice_Summary
2328 
2329  *==========================================================================*/
2330 FUNCTION Invoice_Summary( p_inv_lower_limit  IN NUMBER,
2331                           p_inv_upper_limit  IN NUMBER,
2332                           p_purge_name       IN VARCHAR2,
2333                           p_calling_sequence  IN VARCHAR2) RETURN BOOLEAN IS
2334 
2335 debug_info                      VARCHAR2(200);
2336 current_calling_sequence        VARCHAR2(2000);
2337 
2338 range_low       NUMBER;
2339 range_high      NUMBER;
2340 range_inserted  VARCHAR2(1);
2341 range_size      NUMBER:=10000;
2342 
2343 BEGIN
2344   -- Update the calling sequence
2345   --
2346      current_calling_sequence := 'Invoice_Summary<-'||P_calling_sequence;
2347   --
2348   debug_info := 'Starting Invoice_Summary';
2349   IF g_debug_switch in ('y','Y') THEN
2350      Print('(Invoice_Summary)'||debug_info);
2351   END IF;
2352 
2353 
2354   /**** Invoice Loop ****/
2355   range_size := g_range_size;
2356   range_high := 0;
2357   range_low := p_inv_lower_limit;
2358   range_high := range_low + range_size;
2359 
2360   LOOP
2361         range_inserted := 'N';
2362 
2363         -- Check_invoice_Summary
2364        BEGIN
2365         select 'Y'
2366         into   range_inserted
2367         from   sys.dual
2368         where  exists (select null
2369                        from   ap_history_invoices
2370                        where  purge_name = p_purge_name
2371                         and    invoice_id between range_low and range_high);
2372 
2373       EXCEPTION
2374       WHEN NO_DATA_FOUND THEN
2375         range_inserted := 'N';
2376       END;
2377 
2378         if (range_inserted <> 'Y') then
2379           --
2380           debug_info := 'Summerizing sub-group from Oracle Purchasing -- Invoices';
2381           IF g_debug_switch in ('y','Y') THEN
2382              Print('(Invoice_Summary)'||debug_info);
2383           END IF;
2384            -- summarize_invoices
2385 	   -- bug5487843, added org_id and changed to _ALL
2386           INSERT INTO ap_history_invoices_all
2387                   (invoice_id, vendor_id, vendor_site_code, invoice_num, invoice_date,
2388                    invoice_amount, batch_name, purge_name, doc_sequence_id,
2389                    doc_sequence_value,org_id)
2390           SELECT  i.invoice_id, i.vendor_id, v.vendor_site_code, i.invoice_num,
2391                   i.invoice_date, i.invoice_amount, b.batch_name, p_purge_name,
2392                   i.doc_sequence_id, i.doc_sequence_value,i.org_id
2393           FROM    ap_invoices_all i, ap_supplier_sites_all v, ap_batches_all b
2394           WHERE   i.vendor_site_id = v.vendor_site_id
2395           AND     i.batch_id = b.batch_id (+)
2396           AND     i.invoice_id IN (SELECT PL.invoice_id
2397                                    FROM  ap_purge_invoice_list PL
2398                                    WHERE PL.double_check_flag = 'Y'
2399                                    AND   PL.invoice_id BETWEEN range_low AND
2400                                                            range_high);
2401 
2402           --
2403           debug_info := '    -- Checks';
2404           IF g_debug_switch in ('y','Y') THEN
2405              Print('(Invoice_Summary)'||debug_info);
2406           END IF;
2407 
2408           --5007666, added payment_id
2409 	  -- bug5487843, added org_id and changed to _ALL
2410           -- summarize_checks
2411           INSERT INTO ap_history_checks_all
2412           (check_id, bank_account_id, check_number, check_date, amount,
2413           currency_code, void_flag, purge_name, doc_sequence_id,
2414           doc_sequence_value, payment_id,org_id)
2415           SELECT
2416           ac.check_id, ac.bank_account_id, ac.check_number, ac.check_date,
2417           ac.amount, ac.currency_code, DECODE(void_date, null, null, 'Y'),
2418           p_purge_name, ac.doc_sequence_id, ac.doc_sequence_value, ac.payment_id,
2419 	  ac.org_id
2420           FROM ap_checks_all AC,
2421                ap_invoice_payments_all IP,
2422                ap_purge_invoice_list PL
2423           WHERE PL.invoice_id        = IP.invoice_id
2424           AND   IP.check_id          = AC.check_id
2425           AND   PL.double_check_flag = 'Y'
2426           AND   PL.invoice_id BETWEEN range_low AND range_high
2427           AND NOT EXISTS (SELECT null
2428                           FROM   ap_history_checks_all hc
2429                           WHERE  hc.check_id = AC.check_id)
2430           GROUP BY ac.check_id, ac.bank_account_id, ac.check_number,
2431                    ac.check_date, ac.amount, ac.currency_code,
2432                    DECODE(void_date, null, null, 'Y'), purge_name,
2433                    ac.doc_sequence_id, ac.doc_sequence_value, ac.payment_id,
2434 		   ac.org_id; --Bug 6277474 added the org_id in group by clause.
2435 
2436           --
2437           debug_info := '    -- Invoices Payments';
2438           IF g_debug_switch in ('y','Y') THEN
2439              Print('(Invoice_Summary)'||debug_info);
2440           END IF;
2441 
2442           -- summarize_invoice_payments
2443 	  -- bug5487843, added org_id and changed to _ALL
2444           INSERT INTO ap_history_inv_payments_all
2445           (invoice_id, check_id, amount,org_id)
2446           SELECT
2447           IP.invoice_id, IP.check_id, SUM(IP.amount),IP.org_id
2448           FROM  ap_invoice_payments_all IP, ap_purge_invoice_list PL
2449           WHERE IP.invoice_id = PL.invoice_id
2450           AND   PL.double_check_flag = 'Y'
2451           AND   PL.invoice_id BETWEEN range_low AND range_high
2452           GROUP BY IP.invoice_id, IP.check_id,
2453 		   IP.org_id; --Bug 6277474 added the org_id in group by clause.
2454 
2455           COMMIT;
2456         end if;
2457 
2458         range_low := range_high + 1;
2459         range_high := range_high + range_size;
2460 
2461         if (range_low > p_inv_upper_limit) then
2462                 EXIT;
2463         end if;
2464   END LOOP;
2465   --
2466   debug_info := 'End Invoice_Summary';
2467   IF g_debug_switch in ('y','Y') THEN
2468      Print('(Invoice_Summary)'||debug_info);
2469   END IF;
2470 
2471   RETURN (TRUE);
2472 
2473 RETURN NULL; EXCEPTION
2474  WHEN OTHERS then
2475    IF (SQLCODE < 0 ) then
2476      Print(SQLERRM);
2477    END IF;
2478      RETURN (FALSE);
2479 
2480 END Invoice_Summary;
2481 
2482 /*==========================================================================
2483   Function: Vendor_Summary
2484 
2485  *==========================================================================*/
2486 FUNCTION Vendor_Summary(  p_purge_name          IN VARCHAR2,
2487                           p_calling_sequence  IN        VARCHAR2) RETURN BOOLEAN IS
2488 
2489 debug_info                      VARCHAR2(200);
2490 current_calling_sequence        VARCHAR2(2000);
2491 
2492 range_low       NUMBER;
2493 range_high      NUMBER;
2494 range_inserted  VARCHAR2(1);
2495 range_size      NUMBER:=10000;
2496 
2497 BEGIN
2498   -- Update the calling sequence
2499   --
2500      current_calling_sequence := 'Vendor_Summary<-'||P_calling_sequence;
2501   --
2502   debug_info := 'Starting Vendor_Summary';
2503   IF g_debug_switch in ('y','Y') THEN
2504      Print('(Vendor_Summary)'||debug_info);
2505   END IF;
2506 
2507 
2508   range_inserted := 'N';
2509 
2510   -- Check_vendor_Summary
2511 
2512   BEGIN
2513 
2514   select 'Y'
2515   into   range_inserted
2516   from   sys.dual
2517   where  exists (select null
2518                  from   po_history_vendors vnd
2519                  where  vnd.purge_name = p_purge_name);
2520 
2521   EXCEPTION
2522   WHEN NO_DATA_FOUND THEN
2523       range_inserted := 'N';
2524   END;
2525 
2526   if (range_inserted <> 'Y') then
2527   --
2528           debug_info := 'Vendors';
2529           IF g_debug_switch in ('y','Y') THEN
2530              Print('(Vendor_Summary)'||debug_info);
2531           END IF;
2532 
2533           -- summarize_Vendor
2534           insert into po_history_vendors
2535                (vendor_id,
2536                 vendor_name,
2537                 segment1,
2538                 vendor_type_lookup_code,
2539                 purge_name)
2540           select  vnd.vendor_id,
2541                 vnd.vendor_name,
2542                 vnd.segment1,
2543                 vnd.vendor_type_lookup_code,
2544                 p_purge_name
2545           from  po_purge_vendor_list pvl,
2546                 ap_suppliers vnd
2547           where pvl.vendor_id = vnd.vendor_id
2548           and   pvl.double_check_flag = 'Y';
2549 
2550           COMMIT;
2551   end if;
2552 
2553   --
2554   debug_info := 'End Vendor_Summary';
2555   IF g_debug_switch in ('y','Y') THEN
2556      Print('(Vendor_Summary)'||debug_info);
2557   END IF;
2558 
2559   RETURN (TRUE);
2560 
2561 RETURN NULL; EXCEPTION
2562  WHEN OTHERS then
2563    IF (SQLCODE < 0 ) then
2564        Print(SQLERRM);
2565    END IF;
2566      RETURN (FALSE);
2567 
2568 END Vendor_Summary;
2569 
2570 /*==========================================================================
2571   Function: Schedule_Org_Summary
2572 
2573  *==========================================================================*/
2574 FUNCTION Schedule_Org_Summary(
2575                      p_chv_lower_limit    IN NUMBER,
2576                      p_chv_upper_limit    IN NUMBER,
2577                      p_purge_name         IN VARCHAR2,
2578                      p_category           IN VARCHAR2,
2579                      p_calling_sequence   IN VARCHAR2) RETURN BOOLEAN IS
2580 
2581 debug_info                      VARCHAR2(200);
2582 current_calling_sequence        VARCHAR2(2000);
2583 range_low       NUMBER;
2584 range_high      NUMBER;
2585 range_inserted  VARCHAR2(1);
2586 range_size      NUMBER;
2587 
2588 BEGIN
2589   -- Update the calling sequence
2590   --
2591      current_calling_sequence := 'Schedule_Org_Summary<-'||P_calling_sequence;
2592   --
2593   debug_info := 'Starting Schedule_Org_Summary';
2594   IF g_debug_switch in ('y','Y') THEN
2595      Print('(Schedule_Org_Summary)'||debug_info);
2596   END IF;
2597 
2598 
2599   /**** Schedule Loop ****/
2600   range_size :=  g_range_size;
2601   range_high := 0;
2602   range_low := p_chv_lower_limit;
2603   range_high := range_low + range_size;
2604   Print('(Schedule_Org_Summary-Range Size) '||to_char (range_size));
2605   Print('(Schedule_Org_Summary-Range Low) '||to_char (range_low));
2606   Print('(Schedule_Org_Summary-Range High) '||to_char (range_high));
2607 
2608   LOOP
2609         range_inserted := 'N';
2610 
2611         -- Check_Chv_Summary
2612         select MAX('Y')
2613         into   range_inserted
2614         from   sys.dual
2615         where  exists (select null
2616                        from   chv_schedule_items csi,
2617 			      chv_schedule_headers csh,
2618                               chv_history_schedules chs
2619                        where  csi.item_id         = chs.item_id
2620                        and    csi.schedule_id     = chs.schedule_id
2621 		       and    csh.schedule_id     = chs.schedule_id
2622 		       and    csh.vendor_id       = chs.vendor_id
2623 		       and    csh.vendor_site_id  = chs.vendor_site_id
2624 		       and    csi.organization_id = chs.organization_id
2625                        and    chs.purge_name      = p_purge_name
2626                        and    csi.schedule_item_id between range_low
2627                                                and range_high);
2628 
2629         Print('(Range Inserted) ' || range_inserted);
2630         if (NVL(range_inserted,'N') <> 'Y') then
2631           --
2632           debug_info := 'Summerizing sub-group from Oracle Supplier Scheduling';
2633           IF g_debug_switch in ('y','Y') THEN
2634              Print('(Schedule_Org_Summary)'||debug_info);
2635           END IF;
2636 
2637           -- summarize_schedules_by_org
2638           insert into chv_history_schedules
2639                 (schedule_id,
2640                  vendor_id,
2641                  vendor_site_id,
2642                  schedule_type,
2643                  schedule_subtype,
2644 		 schedule_horizon_start,
2645 		 bucket_pattern_id,
2646 		 creation_date,
2647 		 schedule_num,
2648 		 schedule_revision,
2649 		 schedule_status,
2650 		 item_id,
2651 		 organization_id,
2652                  purge_name
2653                  )
2654           select  csh.schedule_id,
2655                   csh.vendor_id,
2656                   csh.vendor_site_id,
2657                   csh.schedule_type,
2658                   csh.schedule_subtype,
2659 		  csh.schedule_horizon_start,
2660 		  csh.bucket_pattern_id,
2661 		  csh.creation_date,
2662 		  csh.schedule_num,
2663 		  csh.schedule_revision,
2664 		  csh.schedule_status,
2665 		  csi.item_id,
2666 		  csi.organization_id,
2667                   p_purge_name
2668           from  chv_purge_schedule_list cpsl,
2669                 chv_schedule_headers csh,
2670                 chv_schedule_items csi
2671           where   cpsl.schedule_item_id = csi.schedule_item_id
2672 	  and     csi.schedule_id = csh.schedule_id
2673           and     cpsl.double_check_flag     = 'Y'
2674           and     cpsl.schedule_item_id between range_low and range_high;
2675 
2676           COMMIT;
2677         end if;
2678 
2679         range_low := range_high + 1;
2680         range_high := range_high + range_size;
2681 
2682         if (range_low >= p_chv_upper_limit) then
2683                 EXIT;
2684         end if;
2685   END LOOP;
2686 
2687   range_inserted := 'N';
2688 
2689   -- Check_Chv_Summary_for_CUMs
2690   select MAX('Y')
2691   into   range_inserted
2692   from   sys.dual
2693   where  exists (select null
2694                  from   chv_cum_periods ccp,
2695                         chv_history_cum_periods chcp
2696 		 where  ccp.cum_period_id   = chcp.cum_period_id
2697                  and    chcp.purge_name     = p_purge_name);
2698 
2699 -- 1783982 fbreslin: Compare using :p_catagory rather than p_purge_name
2700 
2701   if (p_category = 'SCHEDULES BY CUM PERIODS' AND
2702       NVL(range_inserted,'N') <> 'Y') then
2703       -- summarize_schedules_by_org
2704           insert into chv_history_cum_periods
2705                 (cum_period_id,
2706 		 cum_period_name,
2707 		 cum_period_start_date,
2708 		 cum_period_end_date,
2709 		 creation_date,
2710                  purge_name
2711                  )
2712           select  ccp.cum_period_id,
2713        		  ccp.cum_period_name,
2714 		  ccp.cum_period_start_date,
2715 		  ccp.cum_period_end_date,
2716 		  ccp.creation_date,
2717                   p_purge_name
2718           from  chv_purge_cum_list cpcl,
2719                 chv_cum_periods ccp
2720           where   cpcl.cum_period_id = ccp.cum_period_id
2721           and     cpcl.double_check_flag     = 'Y';
2722           COMMIT;
2723   end if;
2724   --
2725   debug_info := 'End schedule_org_summary';
2726   IF g_debug_switch in ('y','Y') THEN
2727      Print('(Schedule_Org_Summary)'||debug_info);
2728   END IF;
2729 
2730   RETURN (TRUE);
2731 
2732 RETURN NULL; EXCEPTION
2733  WHEN OTHERS then
2734    IF (SQLCODE < 0 ) then
2735       Print(SQLERRM);
2736    END IF;
2737      RETURN (FALSE);
2738 
2739 END schedule_org_summary;
2740 
2741 
2742 /*==========================================================================
2743   Function: Get_Ranges
2744 
2745  *==========================================================================*/
2746 FUNCTION Get_Ranges( p_inv_lower_limit   OUT NOCOPY NUMBER,
2747                      p_inv_upper_limit   OUT NOCOPY NUMBER,
2748                      p_req_lower_limit   OUT NOCOPY NUMBER,
2749                      p_req_upper_limit   OUT NOCOPY NUMBER,
2750                      p_po_lower_limit    OUT NOCOPY NUMBER,
2751                      p_po_upper_limit    OUT NOCOPY NUMBER,
2752                      p_chv_lower_limit   OUT NOCOPY NUMBER,
2753 		     p_chv_upper_limit   OUT NOCOPY NUMBER,
2754                      p_calling_sequence  IN         VARCHAR2) RETURN BOOLEAN IS
2755 
2756 debug_info                      VARCHAR2(200);
2757 current_calling_sequence        VARCHAR2(2000);
2758 
2759 BEGIN
2760   -- Update the calling sequence
2761   --
2762      current_calling_sequence := 'Get_Ranges<-'||P_calling_sequence;
2763   --
2764   debug_info := 'Starting Get_Ranges';
2765   IF g_debug_switch in ('y','Y') THEN
2766      Print('(Get_Ranges)'||debug_info);
2767   END IF;
2768 
2769   -- get_ap_range
2770   select nvl(min(invoice_id),-1),
2771          nvl(max(invoice_id),-1)
2772   into   p_inv_lower_limit, p_inv_upper_limit
2773   from   ap_purge_invoice_list
2774   where  double_check_flag = 'Y';
2775 
2776   -- get_po_range
2777   select nvl(min(po_header_id),-1),
2778          nvl(max(po_header_id),-1)
2779   into   p_po_lower_limit, p_po_upper_limit
2780   from   po_purge_po_list
2781   where  double_check_flag = 'Y';
2782 
2783   -- get_req_range
2784   select nvl(min(requisition_header_id),-1),
2785          nvl(max(requisition_header_id),-1)
2786   into   p_req_lower_limit, p_req_upper_limit
2787   from   po_purge_req_list
2788   where  double_check_flag = 'Y';
2789 
2790   -- get_chv_range
2791   select nvl(min(schedule_item_id),-1),
2792          nvl(max(schedule_item_id),-1)
2793   into   p_chv_lower_limit, p_chv_upper_limit
2794   from   chv_purge_schedule_list
2795   where  double_check_flag = 'Y';
2796 
2797   --
2798   debug_info := 'End Get_Ranges';
2799   IF g_debug_switch in ('y','Y') THEN
2800      Print('(Get_Ranges)'||debug_info);
2801   END IF;
2802 
2803   RETURN (TRUE);
2804 
2805 RETURN NULL; EXCEPTION
2806  WHEN OTHERS then
2807    IF (SQLCODE < 0 ) then
2808      Print(SQLERRM);
2809    END IF;
2810      RETURN (FALSE);
2811 
2812 END Get_Ranges;
2813 
2814 /*==========================================================================
2815   Function: Create_Summary_Records
2816 
2817  *==========================================================================*/
2818 FUNCTION Create_Summary_Records(p_purge_name       IN VARCHAR2,
2819                                 p_category         IN VARCHAR2,
2820                                 p_range_size       IN NUMBER,
2821                                 p_debug_switch     IN VARCHAR2,
2822                                 p_calling_sequence IN VARCHAR2) RETURN BOOLEAN IS
2823 
2824 debug_info                      VARCHAR2(200);
2825 current_calling_sequence        VARCHAR2(2000);
2826 
2827 inv_lower_limit		NUMBER;
2828 inv_upper_limit		NUMBER;
2829 req_lower_limit		NUMBER;
2830 req_upper_limit		NUMBER;
2831 po_lower_limit		NUMBER;
2832 po_upper_limit		NUMBER;
2833 chv_lower_limit         NUMBER;
2834 chv_upper_limit		NUMBER;
2835 
2836 l_po_return_status VARCHAR2(1);
2837 l_po_msg VARCHAR2(2000);
2838 
2839 
2840 BEGIN
2841   -- Update the calling sequence
2842   --
2843      current_calling_sequence := 'Create_Summary_Records<-'||P_calling_sequence;
2844   --
2845   debug_info := 'Starting Create_Summary_Records';
2846   IF g_debug_switch in ('y','Y') THEN
2847      Print('(Create_Summary_Records)'||debug_info);
2848   END IF;
2849 
2850   g_debug_switch := p_debug_switch;
2851   g_range_size   := p_range_size;
2852 
2853   --
2854   if (Get_Ranges( inv_lower_limit,
2855                   inv_upper_limit,
2856                   req_lower_limit,
2857                   req_upper_limit,
2858                   po_lower_limit,
2859                   po_upper_limit,
2860                   chv_lower_limit,
2861 		  chv_upper_limit,
2862                   'Create_Summary_Records') <> TRUE) then
2863 	Print('Get_Ranges failed.');
2864         return(FALSE);
2865   end if;
2866 
2867   --
2868   debug_info := 'Inserting summary records into history tables';
2869   IF g_debug_switch in ('y','Y') THEN
2870      Print('(Create_Summary_Records)'||debug_info);
2871   END IF;
2872 
2873   if (p_category in ( 'SIMPLE INVOICES', 'MATCHED POS AND INVOICES')) then
2874 
2875         if (invoice_summary(inv_lower_limit,
2876                             inv_upper_limit,
2877 		            p_purge_name,
2878                             'Create_Summary_Records') <> TRUE) then
2879                 Print('Invoice_Summary failed.');
2880  		return(FALSE);
2881         end if;
2882 
2883         if (p_category = 'MATCHED POS AND INVOICES') then
2884 
2885             PO_AP_PURGE_GRP.summarize_records
2886             (  p_api_version => 1.0,
2887                p_init_msg_list => 'T',
2888                p_commit => 'T',
2889                x_return_status => l_po_return_status,
2890                x_msg_data => l_po_msg,
2891                p_purge_name => p_purge_name,
2892                p_purge_category => p_category,
2893                p_range_size => p_range_size
2894             );
2895 
2896             IF (l_po_return_status <> 'S') THEN
2897                 Print(l_po_msg);
2898                 RETURN FALSE;
2899             END IF;
2900         end if;
2901 
2902   elsif (p_category IN ('SIMPLE REQUISITIONS', 'SIMPLE POS')) THEN
2903 
2904             PO_AP_PURGE_GRP.summarize_records
2905             (  p_api_version => 1.0,
2906                p_init_msg_list => 'T',
2907                p_commit => 'T',
2908                x_return_status => l_po_return_status,
2909                x_msg_data => l_po_msg,
2910                p_purge_name => p_purge_name,
2911                p_purge_category => p_category,
2912                p_range_size => p_range_size
2913             );
2914 
2915             IF (l_po_return_status <> 'S') THEN
2916                 Print(l_po_msg);
2917                 RETURN FALSE;
2918             END IF;
2919          --
2920 
2921   elsif (p_category = 'VENDORS') then
2922 
2923         if (vendor_summary(p_purge_name,
2924                        'Create_Summary_Records') <> TRUE) then
2925                 Print('Vendor_Summary failed.');
2926 		return(FALSE);
2927         end if;
2928   elsif (p_category IN  ('SCHEDULES BY ORGANIZATION' ,
2929          'SCHEDULES BY CUM PERIODS')) then
2930 
2931         if (schedule_org_summary(chv_lower_limit,
2932 			chv_upper_limit,
2933 		        p_purge_name,
2934                         p_category,
2935                        'Create_Summary_Records') <> TRUE) then
2936                 Print('Schedule_Org_Summary failed.');
2937 		return(FALSE);
2938         end if;
2939 
2940   end if;
2941   --
2942   debug_info := 'End Create_Summary_Records';
2943   IF g_debug_switch in ('y','Y') THEN
2944      Print('(Create_Summary_Records)'||debug_info);
2945   END IF;
2946 
2947 
2948   RETURN (TRUE);
2949 
2950 RETURN NULL; EXCEPTION
2951  WHEN OTHERS then
2952    IF (SQLCODE < 0 ) then
2953      Print(SQLERRM);
2954    END IF;
2955      RETURN (FALSE);
2956 
2957 END Create_Summary_Records;
2958 
2959 
2960 
2961 /*==========================================================================
2962  Function: Retest_Invoice_Independents
2963 
2964  *==========================================================================*/
2965 FUNCTION  Retest_Invoice_Independents(
2966                          P_Calling_Sequence     VARCHAR2) RETURN BOOLEAN IS
2967 
2968 debug_info   		  	VARCHAR2(200);
2969 current_calling_sequence  	VARCHAR2(2000);
2970 
2971 /* bug 11722321 incorporating changes of  bug8842960 in R12 start */
2972 CURSOR pa_related_invoices IS
2973   SELECT invoice_id
2974     FROM ap_purge_invoice_list PL
2975    WHERE EXISTS
2976         (SELECT 'project-related vendor invoices'
2977 		FROM	ap_invoice_distributions d
2978 		WHERE	d.invoice_id = pl.invoice_id
2979 		        AND d.pa_addition_flag in ('Y','T'))
2980         OR EXISTS
2981 	   (SELECT 'project-related expense report'
2982 	    FROM   ap_invoices i
2983 	    WHERE  i.invoice_id = pl.invoice_id
2984 	    AND	   i.source = 'Oracle Project Accounting');
2985 
2986 l_invoice_id            NUMBER;
2987 
2988 /* bug 11722321 incorporating changes of bug8842960 in R12 end */
2989 
2990 BEGIN
2991   -- Update the calling sequence
2992   --
2993      current_calling_sequence := 'Retest_Invoice_Independents<-'||P_calling_sequence;
2994 
2995   --
2996   debug_info := 'Reaffirming invoice candidate listing -- Retest Invoices';
2997   IF g_debug_switch in ('y','Y') THEN
2998      Print('(Retest Invoice Independents)'||debug_info);
2999   END IF;
3000 
3001   --
3002 
3003   -- Retest invoices
3004   UPDATE ap_purge_invoice_list PL
3005   SET PL.double_check_flag = 'N'
3006   WHERE PL.double_check_flag = 'Y'
3007   AND EXISTS(
3008                 SELECT 'invoice no longer purgeable'
3009                 FROM ap_invoices I
3010                 WHERE PL.invoice_id = I.invoice_id
3011                 AND ((  I.payment_status_flag <> 'Y'
3012                         AND
3013                         I.invoice_amount <> 0)
3014                      OR I.last_update_date > g_activity_date
3015                      OR I.invoice_date > g_activity_date));
3016 
3017 
3018   /* bug 10391241 */
3019   debug_info := 'Lines';
3020   IF g_debug_switch in ('y','Y') THEN
3021      Print('(Retest Invoice Independents)'||debug_info);
3022   END IF;
3023 
3024   -- Retest invoice lines
3025   UPDATE ap_purge_invoice_list PL
3026   SET PL.double_check_flag = 'N'
3027   WHERE PL.double_check_flag = 'Y'
3028   AND EXISTS(
3029                 SELECT 'lines no longer purgeable'
3030                 FROM ap_invoice_lines IL
3031                 WHERE PL.invoice_id = IL.invoice_id
3032                 AND IL.last_update_date > g_activity_date );
3033 
3034    /* bug 10391241 */
3035   --
3036 
3037   if g_pa_status = 'Y' then
3038        debug_info := 'Test PA Invoices';
3039        Print('(Retest_Invoice_Independens) '||debug_info);
3040 
3041 
3042      -- Retest PA Invoices
3043 /* bug 11722321 incorporating changes of bug 8842960 and 8979828 in R12 start */
3044      UPDATE ap_purge_invoice_list PL
3045      SET PL.double_check_flag = 'N'
3046      WHERE PL.double_check_flag = 'Y'
3047      AND EXISTS (
3048         SELECT 'Invoices are not transfered to PA'
3049         FROM ap_invoices I,
3050              ap_invoice_distributions D
3051         WHERE I.invoice_id = PL.invoice_id
3052           AND I.invoice_id = D.invoice_id
3053           AND I.source <> 'Oracle Project Accounting'
3054           AND D.pa_addition_flag not in ('Y','T','E','Z') );
3055 
3056            /* UPDATE ap_purge_invoice_list PL
3057      SET PL.double_check_flag = 'N'
3058      WHERE PL.double_check_flag = 'Y'
3059      AND (EXISTS
3060                 (SELECT 'project-related vendor invoices'
3061                 FROM    ap_invoice_distributions d
3062                 WHERE   d.invoice_id = pl.invoice_id
3063                 AND     d.project_id is not null   -- bug1746226
3064                 )
3065      OR EXISTS
3066                 (SELECT 'project-related expense report'
3067                 FROM    ap_invoices i
3068                 WHERE   i.invoice_id = pl.invoice_id
3069                 AND     i.source = 'Oracle Project Accounting'
3070                 )); */
3071 
3072 
3073 
3074      OPEN pa_related_invoices;
3075   	 LOOP
3076    	  FETCH pa_related_invoices INTO l_invoice_id;
3077     	  EXIT WHEN pa_related_invoices%NOTFOUND OR pa_related_invoices%NOTFOUND IS NULL;
3078 
3079     	-- Call PA to verify whether we can purge this PA related invoice.  That is,
3080    	-- are there any open transactions for the particular project?
3081     	-- If PA does not allow purging of the invoice, then, remove, invoice
3082     	-- from purge list.
3083 
3084    	 if (PA_AP_TRX_PURGE.INVOICE_PURGEABLE(l_invoice_id) ) then
3085            -- allow purge
3086            null ;
3087 
3088          else
3089      	  UPDATE ap_purge_invoice_list PL
3090      	  SET PL.double_check_flag = 'N'
3091           WHERE PL.double_check_flag = 'Y'
3092       	  AND invoice_id = l_invoice_id;
3093 
3094          end if;
3095 
3096        END LOOP;
3097       CLOSE pa_related_invoices;
3098 
3099 
3100    /* bug 11722321 incorporating changes of bug 8842960 and 8979828 in R12 end */
3101   end if;
3102 
3103   --
3104   debug_info := 'Payment Schedules';
3105   IF g_debug_switch in ('y','Y') THEN
3106      Print('(Retest Invoice Independents)'||debug_info);
3107   END IF;
3108 
3109   --
3110 
3111   -- Retest Payment Schedules
3112 --bug5052748
3113   UPDATE ap_purge_invoice_list PL
3114   SET PL.double_check_flag = 'N'
3115   WHERE PL.double_check_flag = 'Y'
3116   AND EXISTS (
3117                 SELECT /*+NO_UNNEST*/ 'payment schedule no longer purgeable'
3118                 FROM ap_payment_schedules PS,
3119                      ap_invoices I
3120                 WHERE PS.invoice_id = PL.invoice_id
3121                 AND   PS.invoice_id = I.invoice_id
3122                 AND ((PS.payment_status_flag <> 'Y'
3123                       AND  I.cancelled_date is null)
3124                      OR PS.last_update_date > g_activity_date)
3125                 );
3126 
3127   --
3128   debug_info := 'Distributions';
3129   IF g_debug_switch in ('y','Y') THEN
3130      Print('(Retest Invoice Independents)'||debug_info);
3131   END IF;
3132 
3133 /*
3134 1897941 fbreslin: If an invoice is cancelled, the ASSETS_ADDTION_FLAG is
3135                   set to "U" so Mass Additions does not include the
3136                   distribution.  We are alos not supposed to purge
3137                   invoices if any of the distributions have ben passed to
3138                   FA. Adding a check to see if the invoice is cancelled
3139                   before we remove an invoice with ASSETS_ADDTION_FLAG = U
3140                   from the purge list.
3141 */
3142   if g_category = 'SIMPLE INVOICES' then
3143 --bug5052748
3144    -- Retest simple Invoice Distributions
3145         UPDATE ap_purge_invoice_list PL
3146         SET PL.double_check_flag = 'N'
3147         WHERE PL.double_check_flag = 'Y'
3148         AND EXISTS
3149             (SELECT /*+NO_UNNEST*/ 'distribution no longer purgeable'
3150                FROM ap_invoice_distributions D, ap_invoices I
3151               WHERE I.invoice_id = D.invoice_id
3152                 AND PL.invoice_id = D.invoice_id
3153                 AND (   D.last_update_date > g_activity_date
3154                      OR D.posted_flag <> 'Y'
3155                      OR D.po_distribution_id IS NOT NULL
3156                      OR (    D.assets_tracking_flag = 'Y' /* bug 11707744 */
3157                          AND D.assets_addition_flag||'' =
3158                              Decode(g_Assets_Status,
3159                                     'Y', 'U',
3160                                     'cantequalme')
3161                          AND I.cancelled_date IS NULL)));
3162   else
3163 --bug5052748
3164   -- Retest all Invoice Distributions
3165         UPDATE ap_purge_invoice_list PL
3166         SET PL.double_check_flag = 'N'
3167         WHERE PL.double_check_flag = 'Y'
3168         AND EXISTS
3169             (SELECT /*+NO_UNNEST*/'distribution no longer purgeable'
3170                FROM ap_invoice_distributions D, ap_invoices I
3171               WHERE I.invoice_id = D.invoice_id
3172                 AND PL.invoice_id = D.invoice_id
3173                 AND (   D.last_update_date > g_activity_date
3174                      OR D.posted_flag <> 'Y'
3175                      OR (    D.assets_tracking_flag = 'Y' /* bug 11707744 */
3176                          AND D.assets_addition_flag||'' =
3177                              Decode(g_Assets_Status,
3178                                     'Y', 'U',
3179                                     'cantequalme')
3180                          AND I.cancelled_date IS NULL)));
3181   end if;
3182 
3183   --
3184   debug_info := 'Payment Dates';
3185   IF g_debug_switch in ('y','Y') THEN
3186      Print('(Retest Invoice Independents)'||debug_info);
3187   END IF;
3188 
3189   --
3190 --bug5052748
3191   -- Retest Payments
3192         UPDATE ap_purge_invoice_list PL
3193         SET PL.double_check_flag = 'N'
3194         WHERE PL.double_check_flag = 'Y'
3195         AND EXISTS (
3196                 SELECT /*+NO_UNNEST*/'payment no longer purgeable'
3197                 FROM ap_invoice_payments P, ap_checks C
3198                 WHERE P.invoice_id = PL.invoice_id
3199                 AND P.check_id = C.check_id
3200                 AND     (P.posted_flag <> 'Y'
3201                         OR P.last_update_date > g_activity_date
3202                         OR C.last_update_date > g_activity_date
3203                         OR (NVL(C.cleared_date, C.void_date) > g_activity_date
3204 			    AND nvl(C.cleared_date, C.void_date) is not NULL)
3205 		));
3206 
3207   --
3208   debug_info := 'Prepayments';
3209   IF g_debug_switch in ('y','Y') THEN
3210      Print('(Retest Invoice Independents)'||debug_info);
3211   END IF;
3212 
3213   --
3214 
3215         UPDATE ap_purge_invoice_list PL
3216         SET PL.double_check_flag = 'N'
3217         WHERE PL.double_check_flag = 'Y'
3218         AND EXISTS (
3219                 SELECT 'recently related to prepayment'
3220                 FROM ap_invoice_prepays IP
3221                 WHERE   PL.invoice_id = IP.invoice_id
3222                         OR PL.invoice_id = IP.prepay_id);
3223 
3224   --
3225   debug_info := 'Matched';
3226   IF g_debug_switch in ('y','Y') THEN
3227      Print('(Retest Invoice Independents)'||debug_info);
3228   END IF;
3229   --
3230 
3231         UPDATE ap_purge_invoice_list PL
3232         SET PL.double_check_flag = 'N'
3233         WHERE EXISTS (
3234                  SELECT 'matched'
3235                  FROM  ap_invoice_distributions aid
3236                  ,      rcv_transactions rcv
3237                  WHERE aid.invoice_id = PL.invoice_id
3238                  and  aid.rcv_transaction_id = rcv.transaction_id
3239                  --Bug 1579474
3240                  and  rcv.last_update_date > g_activity_date
3241                  );
3242 
3243   --
3244   debug_info := 'Matching Invoices to Receipts';
3245   IF g_debug_switch in ('y','Y') THEN
3246      Print('(Retest Invoice Independents)'||debug_info);
3247   END IF;
3248   --
3249 
3250         UPDATE ap_purge_invoice_list PL
3251 	SET double_check_flag = 'N'
3252 	WHERE EXISTS (
3253 		SELECT null
3254 		FROM ap_invoice_distributions ad
3255 		WHERE ad.invoice_id = PL.invoice_id
3256 		and ad.rcv_transaction_id IS NOT NULL
3257 		and EXISTS (
3258 			SELECT 'matching'
3259 			FROM ap_invoice_distributions ad2
3260 			where ad2.rcv_transaction_id = ad.rcv_transaction_id
3261 			and ad2.invoice_id NOT IN (
3262 				SELECT invoice_id
3263 				FROM ap_purge_invoice_list
3264 				WHERE double_check_flag = 'Y')));
3265 
3266 
3267   --
3268   debug_info := 'Invoice accounting not purgeable';
3269   IF g_debug_switch in ('y','Y') THEN
3270      Print('(Retest Invoice Independents)'||debug_info);
3271   END IF;
3272   -- RETURN (TRUE);
3273   --
3274 -- Fix for bug 2652768 made changes to below UPDATE statement
3275 -- Fix for bug 2963666 added an check for MRC upgraded data
3276    UPDATE ap_purge_invoice_list PL
3277    SET PL.double_check_flag = 'N'
3278    WHERE EXISTS (
3279                  SELECT 'invoice accounting not purgeable'
3280                  FROM   xla_events xe,
3281                         xla_ae_headers xeh,
3282                         xla_transaction_entities xte,
3283                         ap_invoices_all ai,
3284                         ap_system_parameters_all asp --bug5052748
3285                  where xte.entity_code = 'AP_INVOICES'
3286                  and   xte.entity_id = xe.entity_id
3287                  and NVL(XTE.SOURCE_ID_INT_1,-99) = PL.invoice_id    /* Bug#12615876 */
3288                  AND ai.invoice_id=pl.invoice_id
3289                  AND ai.org_id=asp.org_id
3290                  AND asp.set_of_books_id=xte.ledger_id
3291                  and   xe.event_id = xeh.event_id
3292                  and   xe.application_id = 200
3293                  and   xeh.application_id = 200
3294                  and   xte.application_id = 200
3295                  and   (xeh.gl_transfer_status_code = 'N'
3296                         OR ( xeh.last_update_date > g_activity_date)))
3297    OR EXISTS (
3298    /* Changed the subquery - bug 12955426. Now the delete stmt (in Do_independent_inv_checks())
3299       and update stmt (in Retest_Invoice_Independents()) has same queries. */
3300                  Select 'payment accounting not purgeable' -- 7759218
3301           from  xla_events xe, --Bug 4588031
3302                 xla_transaction_entities xte, --Bug 4588031
3303                 ap_invoice_payments aip,
3304                 ap_system_parameters_all asp,--bug5052478
3305                 xla_ae_headers xeh --Bug 4588031
3306           where xte.entity_code = 'AP_PAYMENTS'
3307           and   NVL(XTE.SOURCE_ID_INT_1,-99) = aip.check_id          --11059839
3308           and   xte.entity_id = xe.entity_id
3309           AND   asp.set_of_books_id=xte.ledger_id
3310           AND   aip.org_id=asp.org_id
3311           and   PL.invoice_id = aip.invoice_id
3312           and   xe.event_id = xeh.event_id
3313           and   xe.application_id = 200
3314           and   xeh.application_id = 200
3315           and   xte.application_id = 200
3316           and   (xeh.gl_transfer_status_code = 'N'
3317                   OR ( xeh.last_update_date > g_activity_date)));
3318 /*Commented the subquery - bug 12955426 */
3319 /*
3320 		 SELECT 'payment accounting not purgeable'
3321                  FROM xla_events xe
3322                  ,    ap_invoice_payments aip
3323                  ,    ap_checks apc
3324                  ,    xla_ae_headers xeh
3325                  ,    xla_transaction_entities xte
3326                  WHERE xte.entity_code = 'AP_CHECKS'
3327                  and  NVL(XTE.SOURCE_ID_INT_1,-99) = apc.check_id --Bug#12615876
3328                  and PL.invoice_id = aip.invoice_id
3329                  and aip.check_id = apc.check_id
3330                  and xe.event_id = xeh.event_id
3331                  and xe.application_id = 200
3332                  and xeh.application_id = 200
3333                  and xte.application_id = 200
3334                  and xe.event_id = xeh.event_id
3335                  and (xeh.gl_transfer_status_code = 'N'
3336                       OR ( xeh.last_update_date > g_activity_date)));
3337 */
3338   --
3339   debug_info := 'End Retest_Invoice_Independents';
3340   IF g_debug_switch in ('y','Y') THEN
3341      Print('(Retest Invoice Independents)'||debug_info);
3342   END IF;
3343   RETURN (TRUE);
3344   --
3345 
3346 RETURN NULL; EXCEPTION
3347  WHEN OTHERS then
3348    IF (SQLCODE < 0 ) then
3349      Print(SQLERRM);
3350    END IF;
3351      RETURN (FALSE);
3352 
3353 END Retest_Invoice_Independents;
3354 
3355 
3356 
3357 
3358 /*==========================================================================
3359  Private Function: Redo_Dependent_inv_checks
3360 
3361  *==========================================================================*/
3362 
3363 FUNCTION REDO_DEPENDENT_INV_CHECKS
3364          (P_Calling_Sequence  IN VARCHAR2)
3365 RETURN BOOLEAN IS
3366 
3367 /* bug3057900 : Created this function instead of do_dependent_inv_checks function.
3368    Because performance of delete stmt in do_dependent_inv_checks was very poor.
3369    This function does same check with the delete stmt.
3370 */
3371 
3372  TYPE tab_status_type IS TABLE OF VARCHAR2(1) INDEX BY BINARY_INTEGER;
3373  tab_inv tab_status_type;
3374  tab_check tab_status_type;
3375  tab_clear tab_status_type;
3376 
3377   -- Bug 8942883 Begin
3378  TYPE tab_status_type_vc2 IS TABLE OF VARCHAR2(1) INDEX BY VARCHAR2(30) ;
3379  tab_inv_vc2   tab_status_type_vc2 ;
3380  tab_check_vc2 tab_status_type_vc2 ;
3381  use_vc2    BOOLEAN ;
3382  max_inv_id NUMBER ;
3383  max_chk_id NUMBER ;
3384  p_id_vc2   VARCHAR2(30) ;
3385  -- Bug 8942883 End
3386 
3387  CURSOR c_main IS
3388   select pl.invoice_id
3389     from ap_purge_invoice_list pl,
3390          ap_invoice_payments ip
3391    where pl.invoice_id = ip.invoice_id;
3392 
3393  CURSOR c_main_check(l_invoice_id NUMBER) IS
3394   select invoice_id
3395     from ap_purge_invoice_list
3396    where invoice_id = l_invoice_id
3397      and double_check_flag = 'Y';
3398 
3399   p_count   integer;
3400   p_id   integer;
3401 
3402   l_cnt integer;
3403   debug_info                      VARCHAR2(200);
3404   current_calling_sequence  	VARCHAR2(2000);
3405   l_invoice BOOLEAN ;
3406   l_dummy NUMBER ;
3407   l_sch_name VARCHAR2(2) := 'A' || 'P' ; -- Bug 8913560
3408 
3409 Function Check_check(l_invoice_id IN NUMBER ) RETURN BOOLEAN;
3410 
3411 /* Get related invoice_id from check_id and check if the invoice_id is
3412    in purge list. If there is, call check_check to get check_id which
3413    is related to the invoice_id */
3414 Function Check_inv(l_check_id IN NUMBER) RETURN BOOLEAN IS
3415 
3416  CURSOR c_inv IS
3417   select pil.invoice_id
3418     from ap_invoice_payments ip,
3419          ap_purge_invoice_list pil
3420    where ip.check_id = l_check_id
3421      and ip.invoice_id = pil.invoice_id (+)
3422      and pil.double_check_flag = 'Y';
3423 
3424  l_flag BOOLEAN := FALSE;
3425  l_inv_id ap_purge_invoice_list.invoice_id%TYPE;
3426 
3427 BEGIN
3428 
3429   OPEN c_inv ;
3430   LOOP
3431 
3432     FETCH c_inv into l_inv_id ;
3433     EXIT WHEN c_inv%NOTFOUND ;
3434 
3435     /* if related invoice id is not in purge list */
3436     IF l_inv_id is null THEN
3437       l_flag := FALSE ;
3438     ELSE
3439 
3440       /* if the invocie_id is already checked */
3441       IF use_vc2 THEN                                     -- Bug 8942883
3442          IF tab_inv_vc2.exists(l_inv_id) THEN
3443            l_flag := TRUE ;
3444          ELSE
3445            tab_inv_vc2(l_inv_id) := 'X' ;
3446            l_flag := check_check(l_inv_id) ;
3447          END IF;
3448       ELSE
3449          IF tab_inv.exists(l_inv_id) THEN
3450            l_flag := TRUE ;
3451          ELSE
3452            tab_inv(l_inv_id) := 'X' ;
3453            l_flag := check_check(l_inv_id) ;
3454          END IF;
3455       END IF ;
3456 
3457     END IF;
3458 
3459     EXIT WHEN (not l_flag) ;
3460 
3461   END LOOP;
3462 
3463   CLOSE C_inv;
3464   RETURN(l_flag) ;
3465 
3466 END ;
3467 
3468 /* Get related check_id from invoice_id and call check_invoice
3469    to check if the invoice is in purge list. */
3470 Function Check_check(l_invoice_id IN NUMBER ) RETURN BOOLEAN IS
3471 
3472  CURSOR c_check IS
3473   select check_id
3474     from ap_invoice_payments
3475    where invoice_id = l_invoice_id ;
3476 
3477   l_flag BOOLEAN := FALSE;
3478   l_check_id number;
3479 
3480 BEGIN
3481 
3482   OPEN c_check ;
3483   LOOP
3484 
3485     FETCH c_check into l_check_id ;
3486     EXIT WHEN c_check%NOTFOUND ;
3487 
3488     /* if the check_id is already checked */
3489     IF use_vc2 THEN                                         -- Bug 8942883
3490        IF tab_check_vc2.exists(l_check_id) THEN
3491          l_flag := TRUE ;
3492        ELSE
3493          tab_check_vc2(l_check_id) := 'X' ;
3494          l_flag := check_inv(l_check_id) ;
3495        END IF;
3496     ELSE
3497        IF tab_check.exists(l_check_id) THEN
3498          l_flag := TRUE ;
3499        ELSE
3500          tab_check(l_check_id) := 'X' ;
3501          l_flag := check_inv(l_check_id) ;
3502        END IF;
3503     END IF ;
3504 
3505     EXIT WHEN (not l_flag) ;
3506 
3507   END LOOP;
3508 
3509   CLOSE C_check;
3510   RETURN(l_flag) ;
3511 
3512 END ;
3513 
3514 /* main process */
3515 BEGIN
3516   -- Update the calling sequence
3517   --
3518    current_calling_sequence :=
3519    'ReDo_Dependent_Inv_Checks<-'||P_calling_sequence;
3520   --
3521 
3522   debug_info := 'Starting series of dependent invoice validations';
3523   IF g_debug_switch in ('y','Y') THEN
3524      Print('(Redo_Dependent_Inv_Checks)'||debug_info);
3525   END IF;
3526     /*
3527              In the procedure  REDO_DEPENDENT_INV_CHECKS we
3528              are checking for the dependent invoices in the confirm
3529              Purge state.
3530              Dependent Invoices Means
3531              ~~~~~~~~~~~~~~~~~~~~~~~~
3532 
3533              I- Invoices, C- Check
3534                Pay Through     Pays      Pay Through          Pays
3535 
3536              I1 ----------> C1|-----> I2 ----------> C2-----.-------->I5
3537                               |-----> I3 ----------> C3---, |-------->I6
3538                               |-----> I4 ----------> C4   | '-------->I7
3539                                                           |
3540                                                           |---------->I8
3541                                                           '---------->I9
3542              Now the purge list must contains the invoices:
3543              I1, I2, I3, I4, I5, I6, I7, I8, I9. If any of the invoices
3544              are missing then we remove all the invoices I1-I9 in the
3545              purge list.
3546      */
3547 
3548 -- Bug 6082252 --
3549    l_dummy := 0;
3550   SELECT COUNT(*) into l_dummy
3551 FROM ap_invoice_payments_all aip
3552 WHERE check_id IN
3553   (SELECT DISTINCT check_id
3554    FROM ap_invoice_payments_all
3555    WHERE invoice_id IN
3556     (SELECT invoice_id
3557      FROM ap_purge_invoice_list
3558      WHERE double_check_flag = 'Y') )
3559 AND NOT EXISTS
3560   (SELECT 'CHECK'
3561    FROM ap_purge_invoice_list pil
3562    WHERE pil.invoice_id = aip.invoice_id)
3563 AND ROWNUM =1;
3564 
3565    IF (l_dummy = 0) Then
3566    Return(TRUE);
3567    End IF;
3568 -- Bug 6082252 ends;
3569   /* Bug 8913560
3570   -- Bug 8942883 Begins
3571   SELECT MAX( invoice_id )
3572   INTO   max_inv_id
3573   FROM   ap_invoices ;
3574 
3575   SELECT MAX( check_id )
3576   INTO   max_chk_id
3577   FROM   ap_invoice_payments ; */
3578   SELECT last_number
3579   INTO   max_inv_id
3580   FROM   all_sequences
3581   WHERE  sequence_owner = l_sch_name
3582   AND    sequence_name  = 'AP_INVOICES_S' ;
3583 
3584   SELECT last_number
3585   INTO   max_chk_id
3586   FROM   all_sequences
3587   WHERE  sequence_owner = l_sch_name
3588   AND    sequence_name  = 'AP_CHECKS_S' ;
3589 
3590   IF ( max_inv_id > 2147483647 OR
3591        max_chk_id > 2147483647 )
3592   THEN
3593      use_vc2 := TRUE ;
3594   ELSE
3595      use_vc2 := FALSE ;
3596   END IF ;
3597   -- Bug 8942883 Ends
3598 
3599   FOR l_main IN c_main
3600   LOOP
3601 
3602     /* initialization */
3603     tab_inv := tab_clear ;
3604     tab_check := tab_clear;
3605     tab_inv_vc2.DELETE   ; -- Bug 8942883
3606     tab_check_vc2.DELETE ; -- Bug 8942883
3607 
3608     /* check if this invoice is not checked yet */
3609     OPEN c_main_check(l_main.invoice_id) ;
3610     FETCH c_main_check into l_dummy ;
3611     l_invoice := c_main_check%FOUND ;
3612     CLOSE c_main_check ;
3613 
3614     /* if this invoice is not checked yet */
3615     IF (l_invoice) THEN
3616 
3617       IF use_vc2 THEN					-- Bug 8942883
3618          tab_inv_vc2(l_main.invoice_id) := 'X' ;
3619       ELSE
3620          tab_inv(l_main.invoice_id) := 'X' ;
3621       END IF ;
3622 
3623       IF check_check(l_main.invoice_id) THEN
3624 
3625         /* if this chain is purgeable,set flag 'S' for all invoices in this chain */
3626 	IF use_vc2 THEN					-- Bug 8942883
3627 	   p_count := tab_inv_vc2.count;
3628 	ELSE
3629            p_count := tab_inv.count;
3630 	END IF ;
3631         IF p_count <> 0 THEN
3632           p_id := 0 ;
3633 	  p_id_vc2 := 0 ;
3634 
3635           FOR y IN 1..p_count LOOP
3636 	    IF use_vc2 THEN				-- Bug 8942883
3637                p_id_vc2 := tab_inv_vc2.next(p_id_vc2) ;
3638                UPDATE ap_purge_invoice_list
3639                   SET double_check_flag = 'S'
3640                 WHERE invoice_id = p_id_vc2 ;
3641 	    ELSE
3642                p_id := tab_inv.next(p_id) ;
3643                UPDATE ap_purge_invoice_list
3644                   SET double_check_flag = 'S'
3645                 WHERE invoice_id = p_id ;
3646 	    END IF ;
3647           END LOOP;
3648 
3649         END IF;
3650       ELSE
3651 
3652         /* if this chain is not purgeable, delete selected invoice from purge list */
3653         IF use_vc2 THEN					-- Bug 8942883
3654 	   p_count := tab_inv_vc2.count;
3655 	ELSE
3656            p_count := tab_inv.count;
3657 	END IF ;
3658         IF p_count <> 0 THEN
3659           p_id := 0 ;
3660 	  p_id_vc2 := 0 ;
3661 
3662           FOR y IN 1..p_count LOOP
3663             IF use_vc2 THEN				-- Bug 8942883
3664 	       p_id_vc2 := tab_inv_vc2.next(p_id_vc2) ;
3665                UPDATE ap_purge_invoice_list
3666                   SET double_check_flag = 'N'
3667                 WHERE invoice_id = p_id_vc2 ;
3668 	    ELSE
3669                p_id := tab_inv.next(p_id) ;
3670                UPDATE ap_purge_invoice_list
3671                   SET double_check_flag = 'N'
3672                 WHERE invoice_id = p_id ;
3673 	    END IF ;
3674           END LOOP;
3675         end if;
3676 
3677         /* delete unpurgeable list beforehand for performance */
3678 	IF use_vc2 THEN					-- Bug 8942883
3679 	   p_count := tab_check_vc2.count;
3680 	ELSE
3681            p_count := tab_check.count;
3682 	END IF ;
3683 
3684         IF p_count <> 0 THEN
3685           p_id := 0 ;
3686 	  p_id_vc2 := 0 ;
3687 
3688           FOR y IN 1..p_count LOOP
3689 	    IF use_vc2 THEN				-- Bug 8942883
3690                p_id_vc2 := tab_check_vc2.next(p_id_vc2) ;
3691                UPDATE ap_purge_invoice_list
3692                   SET double_check_flag = 'N'
3693                WHERE invoice_id in ( select invoice_id
3694                    from ap_invoice_payments
3695                    where check_id = p_id_vc2);
3696 	    ELSE
3697 	       p_id := tab_check.next(p_id) ;
3698                UPDATE ap_purge_invoice_list
3699                   SET double_check_flag = 'N'
3700                WHERE invoice_id in ( select invoice_id
3701                    from ap_invoice_payments
3702                    where check_id = p_id);
3703 	    END IF ;
3704           END LOOP;
3705         END IF;
3706 
3707      END IF;
3708 
3709     END IF;
3710 
3711   END LOOP;
3712 
3713   /* Set flag 'Y' back */
3714   update ap_purge_invoice_list
3715     set double_check_flag = 'Y'
3716    where double_check_flag = 'S' ;
3717 
3718   debug_info := 'End of Invoice Validations';
3719   IF g_debug_switch in ('y','Y') THEN
3720      Print('(Redo_Dependent_Inv_Checks)'||debug_info);
3721   END IF;
3722 
3723   commit;
3724   return(TRUE) ;
3725 
3726 RETURN NULL;
3727 
3728 EXCEPTION
3729    WHEN OTHERS THEN
3730       IF (SQLCODE < 0 ) then
3731          Print(SQLERRM);
3732       END IF;
3733       RETURN(FALSE);
3734 END ;
3735 
3736 /*==========================================================================
3737  Private Function: Count_Ap_Rows
3738 
3739  *==========================================================================*/
3740 
3741 FUNCTION Count_Ap_Rows(FP_Check_Rows           OUT NOCOPY NUMBER,
3742                        FP_Invoice_Payment_Rows OUT NOCOPY NUMBER,
3743                        FP_Invoice_Rows         OUT NOCOPY NUMBER,
3744                        P_Calling_Sequence      VARCHAR2) RETURN BOOLEAN IS
3745 
3746 debug_info   		  	VARCHAR2(200);
3747 current_calling_sequence  	VARCHAR2(2000);
3748 
3749 
3750 BEGIN
3751   -- Update the calling sequence
3752   --
3753      current_calling_sequence := 'Count_AP_Rows<-'||P_calling_sequence;
3754 
3755   --
3756 
3757   debug_info := 'ap_checks';
3758   IF g_debug_switch in ('y','Y') THEN
3759      Print('(Count_Ap_Rows)'||debug_info);
3760   END IF;
3761 
3762 
3763 
3764   --
3765   SELECT count(*)
3766   INTO   fp_check_rows
3767   FROM   ap_checks;
3768 
3769   --
3770   debug_info := 'ap_invoice_payments';
3771   IF g_debug_switch in ('y','Y') THEN
3772      Print('(Count_Ap_Rows)'||debug_info);
3773   END IF;
3774 
3775   --
3776   SELECT count(*)
3777   INTO   fp_invoice_payment_rows
3778   FROM   ap_invoice_payments;
3779 
3780   --
3781   debug_info := 'ap_invoices';
3782   IF g_debug_switch in ('y','Y') THEN
3783      Print('(Count_Ap_Rows)'||debug_info);
3784   END IF;
3785 
3786   --
3787   SELECT count(*)
3788   INTO   fp_invoice_rows
3789   FROM ap_invoices;
3790 
3791   RETURN (TRUE);
3792 
3793 RETURN NULL; EXCEPTION
3794  WHEN OTHERS then
3795    IF (SQLCODE < 0 ) then
3796      Print(SQLERRM);
3797    END IF;
3798      RETURN (FALSE);
3799 
3800 END Count_Ap_Rows;
3801 
3802 /*==========================================================================
3803  Private Function: Count_Accounting_Rows
3804 
3805  *==========================================================================*/
3806 
3807 FUNCTION Count_Accounting_Rows(FP_Ae_Line_Rows              OUT NOCOPY NUMBER,
3808                        	       FP_Ae_Header_Rows            OUT NOCOPY NUMBER,
3809                       	       FP_Accounting_Event_Rows     OUT NOCOPY NUMBER,
3810                                FP_Chrg_Allocation_Rows      OUT NOCOPY NUMBER,
3811                                FP_Payment_History_Rows      OUT NOCOPY NUMBER,
3812                                FP_Encumbrance_line_Rows     OUT NOCOPY NUMBER,
3813                                FP_Rcv_Subledger_Detail_Rows OUT NOCOPY NUMBER,
3814                        	       P_Calling_Sequence VARCHAR2) RETURN BOOLEAN IS
3815 
3816 debug_info   		  	VARCHAR2(200);
3817 current_calling_sequence  	VARCHAR2(2000);
3818 
3819 
3820 BEGIN
3821   -- Update the calling sequence
3822   --
3823      current_calling_sequence := 'Count_Accounting_Rows<-'||P_calling_sequence;
3824 
3825   -- Removing references to AP tables for bug 4588031
3826 
3827   -- debug_info := 'ap_ae_lines';
3828   -- IF g_debug_switch in ('y','Y') THEN
3829   --    Print('(Count_Accounting_Rows)'||debug_info);
3830   -- END IF;
3831 
3832 
3833   -- Removing references to AP tables for bug 4588031
3834   -- SELECT count(*)
3835   -- INTO   fp_ae_line_rows
3836   -- FROM   ap_ae_lines;
3837 
3838   --  Removing references to AP tables for bug 4588031
3839   -- debug_info := 'ap_ae_headers';
3840   -- IF g_debug_switch in ('y','Y') THEN
3841   --    Print('(Count_Accounting_Rows)'||debug_info);
3842   -- END IF;
3843 
3844   -- Removing references to AP tables for bug 4588031
3845   -- SELECT count(*)
3846   -- INTO   fp_ae_header_rows
3847   -- FROM   ap_ae_headers;
3848 
3849   -- Removing references to AP tables for bug 4588031
3850   -- debug_info := 'ap_accounting_events';
3851   -- IF g_debug_switch in ('y','Y') THEN
3852   --    Print('(Count_Accounting_Rows)'||debug_info);
3853   -- END IF;
3854 
3855   -- Removing references to AP tables for bug 4588031
3856   -- SELECT count(*)
3857   -- INTO   fp_accounting_event_rows
3858   -- FROM   ap_accounting_events;
3859 
3860   debug_info := 'ap_chrg_allocations';
3861   IF g_debug_switch in ('y','Y') THEN
3862      Print('(Count_Accounting_Rows)'||debug_info);
3863   END IF;
3864 
3865   -- Bug 5118119 -- removed rendundant code as ap_chrg_allocations is obsolete in R12
3866   --
3867   -- SELECT count(*)
3868   -- INTO   fp_chrg_allocation_rows
3869   -- FROM   ap_chrg_allocations;
3870 
3871   --
3872   debug_info := 'ap_payment_history';
3873   IF g_debug_switch in ('y','Y') THEN
3874      Print('(Count_Accounting_Rows)'||debug_info);
3875   END IF;
3876 
3877   --
3878   SELECT count(*)
3879   INTO   fp_payment_history_rows
3880   FROM   ap_payment_history;
3881 
3882   --
3883   debug_info := 'ap_encumbrance_lines';
3884   IF g_debug_switch in ('y','Y') THEN
3885      Print('(Count_Accounting_Rows)'||debug_info);
3886   END IF;
3887 
3888   --
3889   SELECT count(*)
3890   INTO   fp_encumbrance_line_rows
3891   FROM   ap_encumbrance_lines;
3892 
3893   --
3894   debug_info := 'rcv_subledger_details';
3895   IF g_debug_switch in ('y','Y') THEN
3896      Print('(Count_Accounting_Rows)'||debug_info);
3897   END IF;
3898 
3899   --
3900   SELECT count(*)
3901   INTO   fp_rcv_subledger_detail_rows
3902   FROM   rcv_sub_ledger_details;
3903 
3904 
3905   RETURN (TRUE);
3906 
3907 
3908 RETURN NULL; EXCEPTION
3909  WHEN OTHERS then
3910    IF (SQLCODE < 0 ) then
3911      Print(SQLERRM);
3912    END IF;
3913      RETURN (FALSE);
3914 
3915 END Count_Accounting_Rows;
3916 
3917 
3918 
3919 /*==========================================================================
3920   Function: Retest_Seeded_Vendors
3921 
3922  *==========================================================================*/
3923 FUNCTION Retest_Seeded_Vendors(
3924          p_calling_sequence  IN VARCHAR2) RETURN BOOLEAN IS
3925 
3926 debug_info                      VARCHAR2(200);
3927 current_calling_sequence        VARCHAR2(2000);
3928 
3929 BEGIN
3930   -- Update the calling sequence
3931   --
3932   current_calling_sequence := 'Retest_Seeded_Vendors<-'||P_calling_sequence;
3933   --
3934   debug_info := 'Starting Retest_Seeded_Vendors';
3935   IF g_debug_switch in ('y','Y') THEN
3936      Print('(Retest_Seeded_Vendors)'||debug_info);
3937   END IF;
3938 
3939   update po_purge_vendor_list pvl
3940   set double_check_flag = 'N'
3941   where pvl.double_check_flag = 'Y'
3942   and   not exists (select null
3943                     from    ap_suppliers vnd
3944                     where   vnd.vendor_id = pvl.vendor_id
3945                     --and   nvl(vnd.vendor_type_lookup_code, 'VENDOR') <> 'EMPLOYEE'
3946                     and     nvl(vnd.end_date_active,sysdate) <=
3947                                 g_activity_date);
3948 
3949   --
3950   debug_info := 'End Retest_Seeded_Vendors';
3951   IF g_debug_switch in ('y','Y') THEN
3952      Print('(Retest_Seeded_Vendors)'||debug_info);
3953   END IF;
3954 
3955   RETURN (TRUE);
3956 
3957 RETURN NULL; EXCEPTION
3958  WHEN OTHERS then
3959    IF (SQLCODE < 0 ) then
3960      Print(SQLERRM);
3961    END IF;
3962      RETURN (FALSE);
3963 
3964 END Retest_Seeded_Vendors;
3965 
3966 
3967 
3968 /*==========================================================================
3969   Function: Retest_Vendors
3970 
3971  *==========================================================================*/
3972 FUNCTION Retest_Vendors(
3973          p_calling_sequence  IN VARCHAR2) RETURN BOOLEAN IS
3974 
3975 debug_info                      VARCHAR2(200);
3976 current_calling_sequence        VARCHAR2(2000);
3977 
3978 BEGIN
3979   -- Update the calling sequence
3980   --
3981      current_calling_sequence := 'Retest_Vendors<-'||P_calling_sequence;
3982   --
3983   debug_info := 'Starting Retest_Vendors';
3984   IF g_debug_switch in ('y','Y') THEN
3985      Print('(Retest_Vendors)'||debug_info);
3986   END IF;
3987 
3988   if (g_payables_status = 'Y') then
3989      if (g_assets_status = 'Y') then
3990 
3991         debug_info := 'retest_fa_vendors';
3992         IF g_debug_switch in ('y','Y') THEN
3993            Print('(Retest_Vendors)'||debug_info);
3994         END IF;
3995 
3996         -- retest_fa_vendors
3997         update po_purge_vendor_list pvl
3998         set double_check_flag = 'N'
3999         where pvl.double_check_flag = 'Y'
4000         and (exists    (select null
4001                         from fa_mass_additions fma
4002                         where fma.po_vendor_id = pvl.vendor_id)
4003              or
4004              exists    (select null
4005                         from fa_asset_invoices fai
4006                         where fai.po_vendor_id = pvl.vendor_id));
4007      end if;
4008 
4009      debug_info := 'retest_ap_vendors';
4010      IF g_debug_switch in ('y','Y') THEN
4011         Print('(Retest_Vendors)'||debug_info);
4012      END IF;
4013 
4014      -- retest_ap_vendors
4015      update po_purge_vendor_list pvl
4016      set double_check_flag = 'N'
4017      where pvl.double_check_flag = 'Y'
4018      and  (exists   (select null
4019                      from ap_invoices_all ai
4020                      where ai.vendor_id = pvl.vendor_id)
4021            or
4022            exists   (select null
4023                      from ap_selected_invoices_all asi,
4024                           ap_supplier_sites_all pvs
4025                      where asi.vendor_site_id = pvs.vendor_site_id
4026                     and   pvs.vendor_id      = pvl.vendor_id)
4027            or
4028            exists   (select null
4029                      from ap_recurring_payments_all arp
4030                      where arp.vendor_id = pvl.vendor_id));
4031   end if;
4032 
4033   if (g_purchasing_status = 'Y') then
4034 
4035      debug_info := 'retest_po_vendors';
4036      IF g_debug_switch in ('y','Y') THEN
4037         Print('(Retest_Vendors)'||debug_info);
4038      END IF;
4039 
4040 
4041      -- retest_po_vendors
4042      update po_purge_vendor_list pvl
4043      set double_check_flag = 'N'
4044      where pvl.double_check_flag = 'Y'
4045      and (exists   (select null
4046                     from po_headers_all ph
4047                      where ph.vendor_id = pvl.vendor_id)
4048           or
4049           exists    (select null
4050                      from po_rfq_vendors rfq
4051                      where rfq.vendor_id = pvl.vendor_id)
4052           or
4053           exists    (select null
4054                      from rcv_shipment_headers rcvsh
4055                      where rcvsh.vendor_id = pvl.vendor_id)
4056           or
4057           exists    (select null
4058                      from rcv_headers_interface rhi
4059                      where rhi.vendor_id = pvl.vendor_id)
4060           or
4061           exists    (select null
4062                      from rcv_transactions_interface rti
4063                      where rti.vendor_id = pvl.vendor_id));
4064   end if;
4065 
4066   if (g_chv_status = 'Y') then
4067 
4068      debug_info := 'retest_chv_vendors';
4069      IF g_debug_switch in ('y','Y') THEN
4070         Print('(Retest_Vendors)'||debug_info);
4071      END IF;
4072 
4073 
4074      -- retest_chv_vendors
4075 
4076      update po_purge_vendor_list pvl
4077      set double_check_flag = 'N'
4078      where pvl.double_check_flag = 'Y'
4079      and   (exists   (select null
4080                 from chv_schedule_headers csh
4081                 where csh.vendor_id = pvl.vendor_id));
4082 
4083   end if;
4084 
4085 
4086   if (g_mrp_status = 'Y') then
4087 
4088      debug_info := 'retest_mrp_vendors';
4089      IF g_debug_switch in ('y','Y') THEN
4090         Print('(Retest_Vendors)'||debug_info);
4091      END IF;
4092 
4093      -- retest_mrp_vendors
4094 
4095      --1796376, removed check for inactivity dates on sql below
4096 
4097      update po_purge_vendor_list pvl
4098      set double_check_flag = 'N'
4099      where pvl.double_check_flag = 'Y'
4100      and   (exists   (select null
4101                 from  mrp_sr_source_org msso
4102                 where msso.vendor_id = pvl.vendor_id));
4103 
4104   end if;
4105 
4106 
4107   if (g_edi_status = 'Y') then
4108 
4109      debug_info := 'retest_edi_vendors';
4110      IF g_debug_switch in ('y','Y') THEN
4111         Print('(Retest_Vendors)'||debug_info);
4112      END IF;
4113 
4114 
4115      -- retest_edi_vendors
4116 
4117      update po_purge_vendor_list pvl
4118      set double_check_flag = 'N'
4119      where pvl.double_check_flag = 'Y'
4120      and   (exists   (select null
4121                 from  ece_tp_details etd,
4122                       ap_supplier_sites_all pvs
4123                 where etd.tp_header_id = pvs.tp_header_id
4124                 and pvs.vendor_id = pvl.vendor_id
4125                 and etd.last_update_date > g_activity_date));
4126 --Bug 1781451 Update purge list to include only vendors with last_update_date
4127 -- less than last activity date in concurrent request parameters
4128 --              and etd.last_update_date <= g_activity_date));
4129 
4130   end if;
4131 
4132 
4133   COMMIT;
4134 
4135   debug_info := 'End Retest_Vendors';
4136   IF g_debug_switch in ('y','Y') THEN
4137      Print('(Retest_Vendors)'||debug_info);
4138   END IF;
4139 
4140   RETURN (TRUE);
4141 
4142 RETURN NULL; EXCEPTION
4143  WHEN OTHERS then
4144    IF (SQLCODE < 0 ) then
4145      Print(SQLERRM);
4146    END IF;
4147      RETURN (FALSE);
4148 
4149 END Retest_Vendors;
4150 
4151 
4152 
4153 /*==========================================================================
4154   Function: Retest_Seeded_Chv_by_Org
4155 
4156  *==========================================================================*/
4157 
4158 FUNCTION Retest_Seeded_Chv_by_Org(P_Calling_Sequence VARCHAR2) RETURN BOOLEAN IS
4159 
4160 debug_info   		  	VARCHAR2(200);
4161 current_calling_sequence  	VARCHAR2(2000);
4162 
4163 BEGIN
4164   -- Update the calling sequence
4165   --
4166      current_calling_sequence := 'Retest_Seeded_Chv_by_Org<-'||P_calling_sequence;
4167 
4168   --
4169 
4170   debug_info := 'Starting Retest Schedules by Org';
4171   IF g_debug_switch in ('y','Y') THEN
4172      Print('(Retest_Seeded_Chv_by_Org)'||debug_info);
4173   END IF;
4174 
4175   --
4176 
4177   update chv_purge_schedule_list cpsl
4178   set double_check_flag = 'N'
4179   where cpsl.double_check_flag = 'Y'
4180   and  not exists (select 'schedule not purgeable' from chv_schedule_items csi,
4181                              chv_schedule_headers csh
4182             where   csh.schedule_id = csi.schedule_id
4183             and     csh.last_update_date <= g_activity_date
4184             and     csi.organization_id = g_organization_id
4185             and     csi.schedule_item_id = cpsl.schedule_item_id);
4186 
4187   RETURN (TRUE);
4188 
4189 RETURN NULL; EXCEPTION
4190  WHEN OTHERS then
4191    IF (SQLCODE < 0 ) then
4192      Print(SQLERRM);
4193    END IF;
4194      RETURN (FALSE);
4195 
4196 END Retest_Seeded_Chv_by_Org;
4197 
4198 /*==========================================================================
4199   Function: Retest_Seeded_Chv_by_CUM
4200 
4201  *==========================================================================*/
4202 
4203 FUNCTION Retest_Seeded_Chv_by_Cum(P_Calling_Sequence VARCHAR2) RETURN BOOLEAN IS
4204 
4205 debug_info   		  	VARCHAR2(200);
4206 current_calling_sequence  	VARCHAR2(2000);
4207 
4208 BEGIN
4209   -- Update the calling sequence
4210   --
4211      current_calling_sequence := 'Retest_Seeded_Chv_by_Cum<-'||P_calling_sequence;
4212 
4213   --
4214 
4215   debug_info := 'Starting Retest Schedules by CUM';
4216   IF g_debug_switch in ('y','Y') THEN
4217      Print('(Retest_Seeded_Chv_by_CUM)'||debug_info);
4218   END IF;
4219 
4220   --
4221 
4222   update chv_purge_cum_list cpcl
4223   set double_check_flag = 'N'
4224   where cpcl.double_check_flag = 'Y'
4225   and not exists (select  null from chv_cum_periods ccp
4226             where   ccp.organization_id = g_organization_id
4227             and     NVL(ccp.cum_period_end_date, sysdate + 1) <= g_activity_date
4228             and     NVL(ccp.cum_period_end_date,sysdate + 1) < sysdate
4229             and     ccp.cum_period_id = cpcl.cum_period_id);
4230 
4231   debug_info := 'Eliminate Items in CUM';
4232   IF g_debug_switch in ('y','Y') THEN
4233      Print('(Retest_Seeded_Chv_by_CUM)'||debug_info);
4234   END IF;
4235 
4236   --
4237 
4238   update chv_purge_schedule_list cpsl
4239   set double_check_flag = 'N'
4240   where cpsl.double_check_flag = 'Y'
4241   and not exists (select null from chv_schedule_items csi,
4242                              chv_schedule_headers csh,
4243 			     chv_cum_periods ccp,
4244 			     chv_purge_cum_list cpcl
4245             where   csh.schedule_id = csi.schedule_id
4246 	    and     csh.schedule_horizon_start between ccp.cum_period_start_date
4247 						   and ccp.cum_period_end_date
4248 	    and     ccp.cum_period_id = cpcl.cum_period_id
4249             and     csi.organization_id = g_organization_id
4250             and     csi.schedule_item_id = cpsl.schedule_item_id);
4251 
4252 
4253   RETURN (TRUE);
4254 
4255 RETURN NULL; EXCEPTION
4256  WHEN OTHERS then
4257    IF (SQLCODE < 0 ) then
4258      Print(SQLERRM);
4259    END IF;
4260      RETURN (FALSE);
4261 
4262 END Retest_Seeded_Chv_by_Cum;
4263 
4264 /*==========================================================================
4265   Function: Retest_Chv_in_Cum
4266 
4267  *==========================================================================*/
4268 
4269 FUNCTION Retest_Chv_in_Cum(P_Calling_Sequence VARCHAR2) RETURN BOOLEAN IS
4270 
4271 debug_info   		  	VARCHAR2(200);
4272 current_calling_sequence  	VARCHAR2(2000);
4273 
4274 BEGIN
4275   -- Update the calling sequence
4276   --
4277      current_calling_sequence := 'Retest_Chv_in_Cum<-'||P_calling_sequence;
4278 
4279   --
4280 
4281   debug_info := 'Eliminate Schedules in CUM';
4282   IF g_debug_switch in ('y','Y') THEN
4283      Print('(Retest_Chv_in_Cum)'||debug_info);
4284   END IF;
4285 
4286   --
4287   update chv_purge_schedule_list cpsl
4288   set double_check_flag = 'N'
4289   where cpsl.double_check_flag = 'Y'
4290   and exists   (select null
4291               from chv_cum_periods ccp,
4292                    chv_schedule_items csi,
4293                    chv_schedule_headers csh,
4294                    chv_org_options coo
4295               where ccp.organization_id  = g_organization_id
4296               and   sysdate between ccp.cum_period_start_date and
4297                                     NVL(ccp.cum_period_end_date,sysdate + 1)
4298               and  coo.organization_id = ccp.organization_id
4299               and  coo.enable_cum_flag = 'Y'
4300               and  csh.schedule_id = csi.schedule_id
4301               and  csh.schedule_horizon_start >= ccp.cum_period_start_date
4302               and  csi.schedule_item_id = cpsl.schedule_item_id);
4303 
4304 
4305   RETURN (TRUE);
4306 
4307 RETURN NULL; EXCEPTION
4308  WHEN OTHERS then
4309    IF (SQLCODE < 0 ) then
4310       Print(SQLERRM);
4311    END IF;
4312      RETURN (FALSE);
4313 
4314 END Retest_Chv_in_Cum;
4315 
4316 /*==========================================================================
4317   Function: Retest_Chv_in_Edi
4318 
4319  *==========================================================================*/
4320 
4321 FUNCTION Retest_Chv_in_Edi(P_Calling_Sequence VARCHAR2) RETURN BOOLEAN IS
4322 
4323 debug_info   		  	VARCHAR2(200);
4324 current_calling_sequence  	VARCHAR2(2000);
4325 
4326 BEGIN
4327   -- Update the calling sequence
4328   --
4329      current_calling_sequence := 'Retest_Chv_in_Edi<-'||P_calling_sequence;
4330 
4331   --
4332 
4333   debug_info := 'Eliminate Schedules in EDI';
4334   IF g_debug_switch in ('y','Y') THEN
4335      Print('(Retest_Chv_in_edi)'||debug_info);
4336   END IF;
4337 
4338   --
4339   update chv_purge_schedule_list cpsl
4340   set double_check_flag = 'N'
4341   where cpsl.double_check_flag = 'Y'
4342   and exists  (select null
4343               from chv_schedule_items csi,
4344               ece_spso_items esi
4345               where csi.schedule_item_id = cpsl.schedule_item_id
4346               and csi.schedule_id = esi.schedule_id);
4347 
4348 
4349   RETURN (TRUE);
4350 
4351 RETURN NULL; EXCEPTION
4352  WHEN OTHERS then
4353    IF (SQLCODE < 0 ) then
4354       Print(SQLERRM);
4355    END IF;
4356      RETURN (FALSE);
4357 
4358 END Retest_Chv_in_Edi;
4359 
4360 /*==========================================================================
4361   Function: Count_Chv_Rows
4362 
4363  *==========================================================================*/
4364 FUNCTION Count_Chv_Rows
4365         (chv_auth_rows    OUT NOCOPY NUMBER,
4366          chv_cum_adj_rows OUT NOCOPY NUMBER,
4367          chv_cum_rows     OUT NOCOPY NUMBER,
4368          chv_hor_rows     OUT NOCOPY NUMBER,
4369          chv_ord_rows     OUT NOCOPY NUMBER,
4370          chv_head_rows    OUT NOCOPY NUMBER,
4371          chv_item_rows    OUT NOCOPY NUMBER,
4372 	 P_Calling_Sequence   VARCHAR2)
4373 RETURN BOOLEAN IS
4374 
4375 debug_info   		  	VARCHAR2(200);
4376 current_calling_sequence  	VARCHAR2(2000);
4377 
4378 
4379 BEGIN
4380   -- Update the calling sequence
4381   --
4382      current_calling_sequence := 'Count_Chv_Rows<-'||P_calling_sequence;
4383 
4384   debug_info := 'Count Rows in tables affecting Supplier Scheduling';
4385   IF g_debug_switch in ('y','Y') THEN
4386      Print('(Count_Chv_Rows)'||debug_info);
4387   END IF;
4388 
4389   --
4390 
4391   debug_info := 'chv_auth';
4392   IF g_debug_switch in ('y','Y') THEN
4393      Print('(Count_Chv_Rows)'||debug_info);
4394   END IF;
4395 
4396   --
4397   SELECT count(*)
4398   INTO   chv_auth_rows
4399   FROM   chv_authorizations;
4400 
4401   --
4402 
4403   debug_info := 'chv_cum_adj';
4404   IF g_debug_switch in ('y','Y') THEN
4405      Print('(Count_Chv_Rows)'||debug_info);
4406   END IF;
4407 
4408   --
4409   SELECT count(*)
4410   INTO   chv_cum_adj_rows
4411   FROM   chv_cum_adjustments;
4412 
4413   --
4414 
4415   debug_info := 'chv_cum';
4416   IF g_debug_switch in ('y','Y') THEN
4417      Print('(Count_Chv_Rows)'||debug_info);
4418   END IF;
4419 
4420   --
4421   SELECT count(*)
4422   INTO   chv_cum_rows
4423   FROM   chv_cum_periods;
4424   --
4425 
4426   debug_info := 'chv_hor';
4427   IF g_debug_switch in ('y','Y') THEN
4428      Print('(Count_Chv_Rows)'||debug_info);
4429   end iF;
4430 
4431   --
4432   SELECT count(*)
4433   INTO   chv_hor_rows
4434   FROM   chv_horizontal_schedules;
4435   --
4436 
4437   debug_info := 'chv_ord';
4438   IF g_debug_switch in ('y','Y') THEN
4439      Print('(Count_Chv_Rows)'||debug_info);
4440   END IF;
4441 
4442   --
4443   SELECT count(*)
4444   INTO   chv_ord_rows
4445   FROM   chv_item_orders;
4446   --
4447 
4448   debug_info := 'chv_head';
4449   IF g_debug_switch in ('y','Y') THEN
4450      Print('(Count_Chv_Rows)'||debug_info);
4451   END IF;
4452 
4453   --
4454   SELECT count(*)
4455   INTO   chv_head_rows
4456   FROM   chv_schedule_headers;
4457   --
4458 
4459   debug_info := 'chv_item';
4460   IF g_debug_switch in ('y','Y') THEN
4461      Print('(Count_Chv_Rows)'||debug_info);
4462   END IF;
4463 
4464   --
4465   SELECT count(*)
4466   INTO   chv_item_rows
4467   FROM   chv_schedule_items
4468   WHERE  NVL(item_purge_status,'N') <> 'PURGED';
4469 
4470   RETURN (TRUE);
4471 
4472 RETURN NULL; EXCEPTION
4473  WHEN OTHERS then
4474    IF (SQLCODE < 0 ) then
4475       Print(SQLERRM);
4476    END IF;
4477      RETURN (FALSE);
4478 
4479 END Count_Chv_Rows;
4480 
4481 
4482 /*==========================================================================
4483   Function: Record_Initial_Statistics
4484 
4485  *==========================================================================*/
4486 FUNCTION Record_Initial_Statistics(fp_check_rows                IN NUMBER,
4487                                    fp_invoice_payment_rows      IN NUMBER,
4488                                    fp_invoice_rows              IN NUMBER,
4489                                    fp_po_header_rows            IN NUMBER,
4490                                    fp_receipt_line_rows         IN NUMBER,
4491                                    fp_req_header_rows           IN NUMBER,
4492                                    fp_vendor_rows               IN NUMBER,
4493                                    fp_po_asl_rows		IN NUMBER,
4494 				   fp_po_asl_attr_rows	 	IN NUMBER,
4495 				   fp_po_asl_doc_rows		IN NUMBER,
4496 				   fp_chv_auth_rows		IN NUMBER,
4497 				   fp_chv_cum_adj_rows	 	IN NUMBER,
4498 				   fp_chv_cum_rows		IN NUMBER,
4499 				   fp_chv_hor_rows		IN NUMBER,
4500 				   fp_chv_ord_rows		IN NUMBER,
4501 				   fp_chv_head_rows		IN NUMBER,
4502      				   fp_chv_item_rows		IN NUMBER,
4503 				   fp_ae_line_rows		IN NUMBER,
4504                                    fp_ae_header_rows            IN NUMBER,
4505                                    fp_accounting_event_rows	IN NUMBER,
4506                                    fp_chrg_allocation_rows      IN NUMBER,
4507 				   fp_payment_history_rows      IN NUMBER,
4508                                    fp_encumbrance_line_rows     IN NUMBER,
4509                                    fp_rcv_subledger_detail_rows IN NUMBER,
4510                                    fp_purge_name                IN VARCHAR2,
4511          			   p_calling_sequence  IN VARCHAR2) RETURN BOOLEAN IS
4512 
4513 debug_info                      VARCHAR2(200);
4514 current_calling_sequence        VARCHAR2(2000);
4515 
4516 
4517 BEGIN
4518 
4519   -- Update the calling sequence
4520   --
4521      current_calling_sequence := 'Record_Initial_Statistics<-'||P_calling_sequence;
4522   --
4523   debug_info := 'Starting Record_Initial_Statistics';
4524   IF g_debug_switch in ('y','Y') THEN
4525      Print('(Record_Initial_Statistics)'||debug_info);
4526   END IF;
4527 
4528 
4529   UPDATE financials_purges
4530   SET
4531   ap_checks                = fp_check_rows,
4532   ap_invoice_payments      = fp_invoice_payment_rows,
4533   ap_invoices              = fp_invoice_rows,
4534   po_headers               = fp_po_header_rows ,
4535   po_receipts              = fp_receipt_line_rows,
4536   po_requisition_headers   = fp_req_header_rows,
4537   po_vendors               = fp_vendor_rows,
4538   po_approved_supplier_list = fp_po_asl_rows,
4539   po_asl_attributes 	   = fp_po_asl_attr_rows,
4540   po_asl_documents 	   = fp_po_asl_doc_rows,
4541   chv_authorizations 	   = fp_chv_auth_rows,
4542   chv_cum_adjustments 	   = fp_chv_cum_adj_rows,
4543   chv_cum_periods 	   = fp_chv_cum_rows,
4544   chv_horizontal_schedules = fp_chv_hor_rows,
4545   chv_item_orders	   = fp_chv_ord_rows,
4546   chv_schedule_headers 	   = fp_chv_head_rows,
4547   chv_schedule_items 	   = fp_chv_item_rows,
4548   ap_ae_lines              = fp_ae_line_rows,
4549   ap_ae_headers		   = fp_ae_header_rows,
4550   ap_accounting_events	   = fp_accounting_event_rows,
4551   ap_chrg_allocations      = fp_chrg_allocation_rows,
4552   ap_payment_history       = fp_payment_history_rows,
4553   ap_encumbrance_lines     = fp_encumbrance_line_rows,
4554   rcv_subledger_details    = fp_rcv_subledger_detail_rows
4555   WHERE purge_name 	   = fp_purge_name ;
4556 
4557   --
4558   debug_info := 'Starting Record_Initial_Statistics';
4559   IF g_debug_switch in ('y','Y') THEN
4560      Print('(Record_Initial_Statistics)'||debug_info);
4561   END IF;
4562 
4563   --
4564 
4565    UPDATE ap_purge_invoice_list PL
4566    SET PL.double_check_flag = 'N'
4567    WHERE EXISTS (
4568                SELECT 'history not purgeable'
4569                FROM ap_invoice_payments aip
4570                ,    ap_payment_history aph
4571                WHERE aip.invoice_id = PL.invoice_id
4572                and aip.check_id = aph.check_id
4573                and aph.last_update_date > g_activity_date);
4574 
4575   --
4576   debug_info := 'End Record_Initial_Statistics';
4577   IF g_debug_switch in ('y','Y') THEN
4578      Print('(Record_Initial_Statistics)'||debug_info);
4579   END IF;
4580 
4581   --
4582   RETURN (TRUE);
4583 
4584 RETURN NULL; EXCEPTION
4585  WHEN OTHERS then
4586    IF (SQLCODE < 0 ) then
4587      Print(SQLERRM);
4588    END IF;
4589    RETURN (FALSE);
4590 
4591 END Record_Initial_Statistics;
4592 
4593 
4594 /*==========================================================================
4595   Function: Confirm_Seeded_Data
4596 
4597  *==========================================================================*/
4598 FUNCTION Confirm_Seeded_Data(P_Status            IN  VARCHAR2,
4599                              P_Category          IN  VARCHAR2,
4600                              P_Purge_Name        IN  VARCHAR2,
4601                              P_Activity_Date     IN  DATE,
4602                              P_Organization_ID   IN  NUMBER,
4603                              P_PA_Status         IN  VARCHAR2,
4604                              P_Purchasing_Status IN  VARCHAR2,
4605                              P_Payables_Status   IN  VARCHAR2,
4606                              P_Assets_Status     IN  VARCHAR2,
4607                              P_Chv_Status        IN  VARCHAR2,
4608                              P_EDI_Status        IN  VARCHAR2,
4609                              P_MRP_Status        IN  VARCHAR2,
4610                              P_Debug_Switch      IN  VARCHAR2,
4611                              p_calling_sequence  IN  VARCHAR2) RETURN BOOLEAN IS
4612 
4613 debug_info                      VARCHAR2(200);
4614 current_calling_sequence        VARCHAR2(2000);
4615 
4616 check_rows              	NUMBER;
4617 invoice_payment_rows    	NUMBER;
4618 invoice_rows            	NUMBER;
4619 po_header_rows          	NUMBER;
4620 receipt_line_rows       	NUMBER;
4621 req_header_rows         	NUMBER;
4622 vendor_rows              	NUMBER;
4623 po_asl_rows		 	NUMBER;
4624 po_asl_attr_rows	 	NUMBER;
4625 po_asl_doc_rows		 	NUMBER;
4626 chv_auth_rows		 	NUMBER;
4627 chv_cum_adj_rows		NUMBER;
4628 chv_cum_rows			NUMBER;
4629 chv_hor_rows			NUMBER;
4630 chv_ord_rows			NUMBER;
4631 chv_head_rows		        NUMBER;
4632 chv_item_rows			NUMBER;
4633 ae_line_rows		 	NUMBER;
4634 ae_header_rows		 	NUMBER;
4635 accounting_event_rows		NUMBER;
4636 chrg_allocation_rows            NUMBER;
4637 payment_history_rows            NUMBER;
4638 encumbrance_line_rows           NUMBER;
4639 rcv_subledger_detail_rows       NUMBER;
4640 
4641 l_po_return_status              VARCHAR2(1);
4642 l_po_msg                        VARCHAR2(2000);
4643 l_po_records_filtered           VARCHAR2(1);
4644 
4645 l_status                        VARCHAR2(30);
4646 
4647 BEGIN
4648 
4649   g_debug_switch := p_debug_switch;
4650 
4651   g_activity_date := P_Activity_Date;
4652   g_organization_id := P_Organization_ID;
4653   g_category := P_Category;
4654   g_pa_status := P_PA_Status;
4655   g_purchasing_Status := P_Purchasing_Status;
4656   g_payables_status := P_Payables_Status;
4657   g_assets_status := P_Assets_Status;
4658   g_chv_status := P_Chv_Status;
4659   g_edi_status := P_EDI_Status;
4660   g_mrp_status := P_MRP_Status;
4661 
4662   -- Update the calling sequence
4663   --
4664      current_calling_sequence := 'Confirm_Seeded_Data<-'||P_calling_sequence;
4665   --
4666   debug_info := 'Starting Confirm_Seeded_Data';
4667   IF g_debug_switch in ('y','Y') THEN
4668      Print('(Confirm_Seeded_Data)'||debug_info);
4669   END IF;
4670 
4671   -- reset_row_counts
4672   check_rows            := 0;
4673   invoice_payment_rows  := 0;
4674   invoice_rows          := 0;
4675   po_header_rows        := 0;
4676   receipt_line_rows     := 0;
4677   req_header_rows       := 0;
4678   vendor_rows		:= 0;
4679   po_asl_rows		:= 0;
4680   po_asl_attr_rows	:= 0;
4681   po_asl_doc_rows	:= 0;
4682   chv_auth_rows		:= 0;
4683   chv_cum_adj_rows	:= 0;
4684   chv_cum_rows		:= 0;
4685   chv_hor_rows		:= 0;
4686   chv_ord_rows		:= 0;
4687   chv_head_rows		:= 0;
4688   chv_item_rows		:= 0;
4689   ae_line_rows          := 0;
4690   ae_header_rows        := 0;
4691   accounting_event_rows := 0;
4692   chrg_allocation_rows  := 0;
4693   payment_history_rows  := 0;
4694   encumbrance_line_rows := 0;
4695   rcv_subledger_detail_rows := 0;
4696 
4697 
4698   --
4699   debug_info := 'Re-validating candidates';
4700   IF g_debug_switch in ('y','Y') THEN
4701      Print('(Confirm_Seeded_Data)'||debug_info);
4702   END IF;
4703 
4704   if (p_category = 'SIMPLE INVOICES') then
4705 
4706      --
4707      debug_info := '  Invoices';
4708      IF g_debug_switch in ('y','Y') THEN
4709         Print('(Confirm_Seeded_Data)'||debug_info);
4710      END IF;
4711 
4712      if (retest_invoice_independents('Confirm_Seeded_Data') <> TRUE) then
4713         Print('retest_invoice_independents failed.');
4714         return(FALSE);
4715      end if;
4716 
4717      if (redo_dependent_inv_checks('Confirm_Seeded_Data') <> TRUE) then
4718         Print('redo_dependent_inv_checks failed.' );
4719         return(FALSE);
4720      end if;
4721 
4722      --
4723      debug_info := 'Computing initial table size statistics for Payables';
4724      IF g_debug_switch in ('y','Y') THEN
4725         Print('(Confirm_Seeded_Data)'||debug_info);
4726      END IF;
4727 
4728      if (count_ap_rows(check_rows,
4729                        invoice_payment_rows,
4730                        invoice_rows,
4731                        'Confirm_Seeded_Data') <> TRUE) then
4732         Print('count_ap_row failed.' );
4733         return(FALSE);
4734      end if;
4735 
4736       --
4737      debug_info := 'Computing initial table size statistics for Accounting';
4738      IF g_debug_switch in ('y','Y') THEN
4739         Print('(Confirm_Seeded_Data)'||debug_info);
4740      END IF;
4741 
4742      if (count_accounting_rows(ae_line_rows,
4743                                ae_header_rows,
4744                                accounting_event_rows,
4745                                chrg_allocation_rows,
4746                                payment_history_rows,
4747                                encumbrance_line_rows,
4748                                rcv_subledger_detail_rows,
4749                                'Confirm_Seeded_Data') <> TRUE) then
4750         Print('count_accounting_rows failed.' );
4751         return(FALSE);
4752      end if;
4753 
4754 
4755   ELSIF (p_category IN ('SIMPLE REQUISITIONS', 'SIMPLE POS')) THEN
4756 
4757      debug_info := ' Call PO Purge API';
4758      IF g_debug_switch in ('y','Y') THEN
4759         Print('(Confirm_Seeded_Data)'||debug_info);
4760      END IF;
4761 
4762      PO_AP_PURGE_GRP.confirm_records
4763      (  p_api_version => 1.0,
4764         p_init_msg_list => 'T',
4765         p_commit => 'F',
4766         x_return_status => l_po_return_status,
4767         x_msg_data => l_po_msg,
4768         p_purge_name => p_purge_name,
4769         p_purge_category => p_category,
4770         p_last_activity_date => p_activity_date
4771      );
4772 
4773      IF (l_po_return_status <> 'S') THEN
4774          Print(l_po_msg);
4775          RETURN FALSE;
4776      END IF;
4777 
4778      PO_AP_PURGE_GRP.filter_records
4779      (  p_api_version => 1.0,
4780         p_init_msg_list => 'T',
4781         p_commit => 'F',
4782         x_return_status => l_po_return_status,
4783         x_msg_data => l_po_msg,
4784         p_purge_status => 'REVALIDATING',
4785         p_purge_name => p_purge_name,
4786         p_purge_category => p_category,
4787         p_action => NULL,
4788         x_po_records_filtered => l_po_records_filtered
4789       );
4790 
4791      IF (l_po_return_status <> 'S') THEN
4792          Print(l_po_msg);
4793          RETURN FALSE;
4794      END IF;
4795 
4796      debug_info := 'Computing initial table size statistics for Purchasing';
4797      IF g_debug_switch in ('y','Y') THEN
4798         Print('(Confirm_Seeded_Data)'||debug_info);
4799      END IF;
4800 
4801      PO_AP_PURGE_GRP.count_po_rows
4802      ( p_api_version => 1.0,
4803        p_init_msg_list => 'T',
4804        x_return_status => l_po_return_status,
4805        x_msg_data => l_po_msg,
4806        x_po_hdr_count => po_header_rows,
4807        x_rcv_line_count => receipt_line_rows,
4808        x_req_hdr_count => req_header_rows,
4809        x_vendor_count => vendor_rows,
4810        x_asl_count => po_asl_rows,
4811        x_asl_attr_count => po_asl_attr_rows,
4812        x_asl_doc_count => po_asl_doc_rows
4813      );
4814 
4815      IF (l_po_return_status <> 'S') THEN
4816         Print(l_po_msg);
4817         RETURN FALSE;
4818      END IF;
4819 
4820   elsif (p_category = 'MATCHED POS AND INVOICES') then
4821 
4822      --
4823      debug_info := '  Invoices';
4824      IF g_debug_switch in ('y','Y') THEN
4825         Print('(Confirm_Seeded_Data)'||debug_info);
4826      END IF;
4827 
4828      if (retest_invoice_independents('Confirm_Seeded_Data') <> TRUE) then
4829         Print('retest_invoice_independents failed.' );
4830          return(FALSE);
4831      end if;
4832 
4833      if (redo_dependent_inv_checks('Confirm_Seeded_Data') <> TRUE) then
4834         Print('redo_dependent_inv_checks failed.');
4835         return(FALSE);
4836      end if;
4837 
4838      --
4839      debug_info := '  Purchase Orders';
4840      IF g_debug_switch in ('y','Y') THEN
4841         Print('(Confirm_Seeded_Data)'||debug_info);
4842      END IF;
4843 
4844      PO_AP_PURGE_GRP.confirm_records
4845      (  p_api_version => 1.0,
4846         p_init_msg_list => 'T',
4847         p_commit => 'F',
4848         x_return_status => l_po_return_status,
4849         x_msg_data => l_po_msg,
4850         p_purge_name => p_purge_name,
4851         p_purge_category => p_category,
4852         p_last_activity_date => p_activity_date
4853      );
4854 
4855      IF (l_po_return_status <> 'S') THEN
4856          Print(l_po_msg);
4857          RETURN FALSE;
4858      END IF;
4859 
4860      PO_AP_PURGE_GRP.filter_records
4861      (  p_api_version => 1.0,
4862         p_init_msg_list => 'T',
4863         p_commit => 'F',
4864         x_return_status => l_po_return_status,
4865         x_msg_data => l_po_msg,
4866         p_purge_status => 'REVALIDATING',
4867         p_purge_name => p_purge_name,
4868         p_purge_category => p_category,
4869         p_action => 'FILTER REF PO AND REQ',
4870         x_po_records_filtered => l_po_records_filtered
4871       );
4872 
4873      IF (l_po_return_status <> 'S') THEN
4874          Print(l_po_msg);
4875          RETURN FALSE;
4876      END IF;
4877 
4878      --
4879      debug_info := 'Re-matching purchase orders and invoices';
4880      IF g_debug_switch in ('y','Y') THEN
4881         Print('(Confirm_Seeded_Data)'||debug_info);
4882      END IF;
4883 
4884      if (match_pos_to_invoices_ctrl(
4885                        P_Purge_Name,
4886                        'REVALIDATING',
4887                        'Confirm_Seeded_Data') <> TRUE) then
4888         Print('match_pos_to_invoices_ctrl failed.' );
4889         return(FALSE);
4890      end if;
4891 
4892      --
4893      debug_info := 'Computing initial table size statistics for Payables';
4894      IF g_debug_switch in ('y','Y') THEN
4895         Print('(Confirm_Seeded_Data)'||debug_info);
4896      END IF;
4897 
4898      if (count_ap_rows(check_rows,
4899                        invoice_payment_rows,
4900                        invoice_rows,
4901                        'Confirm_Seeded_Data') <> TRUE) then
4902         Print('count_ap_rows failed.' );
4903         return(FALSE);
4904      end if;
4905 
4906      --
4907      debug_info := 'Computing initial table size statistics for Purchasing';
4908      IF g_debug_switch in ('y','Y') THEN
4909         Print('(Confirm_Seeded_Data)'||debug_info);
4910      END IF;
4911 
4912      PO_AP_PURGE_GRP.count_po_rows
4913      ( p_api_version => 1.0,
4914        p_init_msg_list => 'T',
4915        x_return_status => l_po_return_status,
4916        x_msg_data => l_po_msg,
4917        x_po_hdr_count => po_header_rows,
4918        x_rcv_line_count => receipt_line_rows,
4919        x_req_hdr_count => req_header_rows,
4920        x_vendor_count => vendor_rows,
4921        x_asl_count => po_asl_rows,
4922        x_asl_attr_count => po_asl_attr_rows,
4923        x_asl_doc_count => po_asl_doc_rows
4924      );
4925 
4926      IF (l_po_return_status <> 'S') THEN
4927         Print(l_po_msg);
4928         RETURN FALSE;
4929      END IF;
4930 
4931       --
4932      debug_info := 'Computing initial table size statistics for Accounting';
4933      IF g_debug_switch in ('y','Y') THEN
4934         Print('(Confirm_Seeded_Data)'||debug_info);
4935      END IF;
4936 
4937      if (count_accounting_rows(ae_line_rows,
4938                                ae_header_rows,
4939                                accounting_event_rows,
4940                                chrg_allocation_rows,
4941                                payment_history_rows,
4942                                encumbrance_line_rows,
4943                                rcv_subledger_detail_rows,
4944                                'Confirm_Seeded_Data') <> TRUE) then
4945         Print('count_accounting_rows failed.' );
4946         return(FALSE);
4947      end if;
4948 
4949 
4950   elsif (p_category = 'VENDORS') then
4951      --
4952      debug_info := '  Vendors';
4953      IF g_debug_switch in ('y','Y') THEN
4954         Print('(Confirm_Seeded_Data)'||debug_info);
4955      END IF;
4956 
4957      if (retest_seeded_vendors('Confirm_Seeded_Data') <> TRUE) then
4958         Print(' retest_seeded_vendors failed.');
4959         return(FALSE);
4960      end if;
4961 
4962      --
4963      debug_info := 'retest_vendors';
4964      IF g_debug_switch in ('y','Y') THEN
4965         Print('(Confirm_Seeded_Data)'||debug_info);
4966      END IF;
4967 
4968      if (retest_vendors('Confirm_Seeded_Data') <> TRUE) then
4969         Print('retest_vendors failed.' );
4970         return(FALSE);
4971      end if;
4972 
4973      --
4974      debug_info := 'Computing initial table size statistics for Purchasing';
4975      IF g_debug_switch in ('y','Y') THEN
4976         Print('(Confirm_Seeded_Data)'||debug_info);
4977      END IF;
4978 
4979      PO_AP_PURGE_GRP.count_po_rows
4980      ( p_api_version => 1.0,
4981        p_init_msg_list => 'T',
4982        x_return_status => l_po_return_status,
4983        x_msg_data => l_po_msg,
4984        x_po_hdr_count => po_header_rows,
4985        x_rcv_line_count => receipt_line_rows,
4986        x_req_hdr_count => req_header_rows,
4987        x_vendor_count => vendor_rows,
4988        x_asl_count => po_asl_rows,
4989        x_asl_attr_count => po_asl_attr_rows,
4990        x_asl_doc_count => po_asl_doc_rows
4991      );
4992 
4993      IF (l_po_return_status <> 'S') THEN
4994         Print(l_po_msg);
4995         RETURN FALSE;
4996      END IF;
4997 
4998 
4999   elsif (p_category = 'SCHEDULES BY ORGANIZATION') then
5000      --
5001      debug_info := '  Schedules';
5002      IF g_debug_switch in ('y','Y') THEN
5003         Print('(Confirm_Seeded_Data)'||debug_info);
5004      END IF;
5005 
5006      if (retest_seeded_chv_by_org('Confirm_Seeded_Data') <> TRUE) then
5007         Print('retest_seeded_chv_by_org failed.');
5008         return(FALSE);
5009      end if;
5010 
5011      --
5012      debug_info := 'Excluding schedules in cum';
5013      IF g_debug_switch in ('y','Y') THEN
5014         Print('(Confirm_Seeded_Data)'||debug_info);
5015      END IF;
5016 
5017      if (retest_chv_in_cum('Confirm_Seeded_Data') <> TRUE) then
5018         Print('Schedules.retest_chv_in_cum failed.' );
5019         return(FALSE);
5020      end if;
5021 
5022      --
5023 
5024      debug_info := 'Excluding schedules in edi';
5025      IF g_debug_switch in ('y','Y') THEN
5026         Print('(Confirm_Seeded_Data)'||debug_info);
5027      END IF;
5028 
5029      if (retest_chv_in_edi('Confirm_Seeded_Data') <> TRUE) then
5030         Print('Schedules.retest_chv_in_edi failed.' );
5031         return(FALSE);
5032      end if;
5033 
5034      --
5035 
5036      debug_info := 'Computing initial table size statistics for Supplier Scheduling';
5037      IF g_debug_switch in ('y','Y') THEN
5038         Print('(Confirm_Seeded_Data)'||debug_info);
5039      END IF;
5040 
5041      -- count_chv_rows
5042      if (count_chv_rows(chv_auth_rows,
5043                         chv_cum_adj_rows,
5044                         chv_cum_rows,
5045                         chv_hor_rows,
5046                         chv_ord_rows,
5047                         chv_head_rows,
5048                         chv_item_rows,
5049 		        'Delete Seeded Data') <> TRUE) then
5050           Print('purge_schedules_by_cum failed!');
5051           RETURN(FALSE);
5052      end if;
5053 
5054   elsif (p_category = 'SCHEDULES BY CUM PERIODS') then
5055 
5056      --
5057 
5058      debug_info := '  Schedules in CUM Periods';
5059      IF g_debug_switch in ('y','Y') THEN
5060         Print('(Confirm_Seeded_Data)'||debug_info);
5061      END IF;
5062 
5063      if (retest_seeded_chv_by_cum('Confirm_Seeded_Data') <> TRUE) then
5064         Print(' Schedules.retest_seeded_chv_by_cum failed.');
5065         return(FALSE);
5066      end if;
5067 
5068      --
5069 
5070      debug_info := 'Computing initial table size statistics for Supplier Scheduling';
5071      IF g_debug_switch in ('y','Y') THEN
5072         Print('(Confirm_Seeded_Data)'||debug_info);
5073      END IF;
5074 
5075     -- count_chv_rows
5076     if (count_chv_rows(chv_auth_rows,
5077                        chv_cum_adj_rows,
5078                        chv_cum_rows,
5079                        chv_hor_rows,
5080                        chv_ord_rows,
5081                        chv_head_rows,
5082                        chv_item_rows,
5083 	  	      'Delete Seeded Data') <> TRUE) then
5084          Print('purge_schedules_by_cum failed!');
5085          RETURN(FALSE);
5086     end if;
5087 
5088 
5089   else
5090      --
5091      debug_info := 'An invalid purge category was entered';
5092      Print('(Confirm_Seeded_Data) '||debug_info);
5093      Print('Valid categories are : SIMPLE INVOICES, SIMPLE REQUISITIONS,');
5094      Print('SIMPLE POS, MATCHED POS AND INVOICES,VENDORS,');
5095      Print('SCHEDULES BY ORGANIZATION and SCHEDULES BY CUM PERIODS');
5096 
5097      l_status := 'COMPLETED-ABORTED';
5098 
5099      if (Set_Purge_Status(l_status,
5100                           p_purge_name,
5101                           p_debug_switch,
5102                           'Confirm_Seeded_Data') <> TRUE) then
5103         Print(' Set_Purge_Status failed.');
5104         return(FALSE);
5105      end if;
5106 
5107      RETURN(TRUE);
5108   end if;
5109 
5110   --
5111   debug_info := 'record_initial_statistics';
5112 
5113   Print('(Confirm_Seeded_Data) '||debug_info);
5114 
5115 
5116   if (record_initial_statistics(check_rows,
5117                                 invoice_payment_rows,
5118                                 invoice_rows,
5119                                 po_header_rows,
5120                                 receipt_line_rows,
5121                                 req_header_rows,
5122                                 vendor_rows,
5123                                 po_asl_rows,
5124 	          		po_asl_attr_rows,
5125 	     			po_asl_doc_rows,
5126 				chv_auth_rows,
5127 	     		     	chv_cum_adj_rows,
5128 				chv_cum_rows,
5129 				chv_hor_rows,
5130 				chv_ord_rows,
5131 				chv_head_rows,
5132      	 			chv_item_rows,
5133 				ae_line_rows,
5134 				ae_header_rows,
5135 				accounting_event_rows,
5136                                 chrg_allocation_rows,
5137                                 payment_history_rows,
5138                                 encumbrance_line_rows,
5139                                 rcv_subledger_detail_rows,
5140                                 p_purge_name,
5141                                 'Confirm_Seeded_Data') <> TRUE) then
5142         Print('Confirm_Purge.record_initial_statistics failed.' );
5143         return(FALSE);
5144   end if;
5145 
5146   l_status := 'DELETING';
5147 
5148   if (Set_Purge_Status(l_status,
5149                        p_purge_name,
5150                        p_debug_switch,
5151                        'Confirm_Seeded_Data') <> TRUE) then
5152         Print('Set_Purge_Status failed.');
5153         return(FALSE);
5154   end if;
5155 
5156   RETURN (TRUE);
5157 
5158 RETURN NULL; EXCEPTION
5159  WHEN OTHERS then
5160    IF (SQLCODE < 0 ) then
5161      Print(SQLERRM);
5162    END IF;
5163      RETURN (FALSE);
5164 
5165 END Confirm_Seeded_Data;
5166 
5167 
5168 /*==========================================================================
5169   Function: Overflow
5170   Bug 13799066 : Deleted the debug messages from the function
5171  *==========================================================================*/
5172 FUNCTION Overflow
5173          (Overflow_Exist      OUT NOCOPY VARCHAR2,
5174           p_start_rowid       IN  ROWID   ,  -- Bug 8913560 range_low           IN  NUMBER,
5175           p_end_rowid         IN  ROWID  ,   -- Bug 8913560 range_high          IN  NUMBER,
5176 	  p_purge_name        IN  VARCHAR2,  -- Bug 8913560
5177           P_Calling_Sequence  IN  VARCHAR2)
5178 RETURN BOOLEAN IS
5179 
5180 CURSOR overflow_select is
5181 SELECT C.check_stock_id,C.check_number
5182 FROM ap_invoice_payments P, ap_purge_invoice_list PL,
5183      ap_checks C
5184 WHERE P.invoice_id = PL.invoice_id
5185 AND P.check_id = C.check_id
5186 AND PL.double_check_flag = 'Y'
5187 AND -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5188     PL.rowid BETWEEN p_start_rowid AND p_end_rowid;
5189 
5190 debug_info                      VARCHAR2(200);
5191 current_calling_sequence        VARCHAR2(2000);
5192 overflow_check_stock_id         NUMBER;
5193 to_be_deleted_check_number      NUMBER;
5194 overflow_check_number           NUMBER;
5195 l_check_rows                    NUMBER ;  -- Bug 8913560
5196 
5197 BEGIN
5198 
5199 
5200   -- Update the calling sequence
5201   --
5202 
5203   current_calling_sequence := 'Overflow<-'||P_Calling_Sequence;
5204   --
5205   debug_info := 'Starting Overflow';
5206   IF g_debug_switch in ('y','Y') THEN
5207      Print('(Overflow)'||debug_info);
5208   END IF;
5209 
5210   OPEN overflow_select;
5211 
5212   LOOP
5213 
5214     FETCH overflow_select into overflow_check_stock_id,
5215                                to_be_deleted_check_number;
5216     --
5217     EXIT WHEN overflow_select%NOTFOUND OR overflow_select%NOTFOUND IS NULL;
5218 
5219     overflow_check_number := to_be_deleted_check_number - 1;
5220 
5221     -- Need to have a Begin - End construct so that we still enter the loop and
5222     -- exit gracefully, if the select does not return any rows.
5223 
5224     Begin
5225       SELECT 'exist'
5226       INTO  overflow_exist
5227       FROM  ap_checks C
5228       WHERE C.check_stock_id = overflow_check_stock_id
5229       AND   C.check_number = overflow_check_number
5230       AND   C.status_lookup_code = 'OVERFLOW';
5231     Exception
5232        WHEN NO_DATA_FOUND THEN
5233        overflow_exist :='does not exist';
5234          Null;
5235     End;
5236 
5237 
5238     LOOP
5239 
5240       if (overflow_exist = 'exist') then
5241 
5242           -- delete_overflow
5243 
5244           DELETE FROM ap_checks C
5245           WHERE C.check_stock_id     = overflow_check_stock_id
5246           AND   C.check_number       = overflow_check_number
5247           AND   C.status_lookup_code = 'OVERFLOW';
5248 
5249           l_check_rows := SQL%ROWCOUNT ; -- Bug 8913560
5250           Update_Financials_Purges ( p_check_rows => l_check_rows ,
5251 	                             p_purge_name => p_purge_name ) ;
5252 
5253           overflow_check_number := overflow_check_number - 1;
5254 
5255           -- Need to have a Begin - End construct so that we exit gracefully
5256           -- once we are done deleting all the overflow checks i.e when
5257           -- the select does not return any rows.
5258 
5259           Begin
5260             SELECT 'exist'
5261             INTO  overflow_exist
5262             FROM  ap_checks C
5263             WHERE C.check_stock_id = overflow_check_stock_id
5264             AND   C.check_number = overflow_check_number
5265             AND   C.status_lookup_code = 'OVERFLOW';
5266           Exception
5267             When NO_DATA_FOUND then
5268                 overflow_exist := 'does not exist';
5269              Null;
5270           End;
5271       else
5272           EXIT;
5273       end if;
5274     END LOOP;
5275   END LOOP;
5276 
5277   CLOSE overflow_select;
5278 
5279   RETURN(TRUE);
5280 
5281 EXCEPTION
5282   WHEN OTHERS THEN
5283     IF (SQLCODE < 0 ) then
5284        Print(SQLERRM);
5285     END IF;
5286     RETURN (FALSE);
5287 
5288 END Overflow;
5289 
5290 
5291 /*==========================================================================
5292   Function: Setup_Spoil
5293 
5294  *==========================================================================*/
5295 FUNCTION Setup_Spoil
5296          (P_Calling_Sequence   IN  VARCHAR2)
5297 RETURN BOOLEAN IS
5298 
5299 CURSOR setup_spoil_select is
5300 SELECT distinct C.checkrun_name
5301 FROM   ap_checks C, ap_invoice_selection_criteria D
5302 WHERE  D.LAST_UPDATE_DATE <= g_activity_date
5303 AND  C.checkrun_name NOT IN
5304      (SELECT distinct b.checkrun_name
5305       FROM   ap_checks a,
5306              ap_invoice_selection_criteria b
5307       WHERE  a.checkrun_name = b.checkrun_name
5308       AND    a.status_lookup_code not in
5309              ('SET UP', 'SPOILED'))
5310 AND  C.checkrun_name = D.checkrun_name
5311 AND  C.last_update_date <= g_activity_date;
5312 
5313 
5314 debug_info                      VARCHAR2(200);
5315 current_calling_sequence        VARCHAR2(2000);
5316 selected_checkrun               ap_invoice_selection_criteria.checkrun_name%TYPE;
5317 
5318 BEGIN
5319 
5320   -- Update the calling sequence
5321   --
5322 
5323   current_calling_sequence := 'Setup_Spoil<-'||P_Calling_Sequence;
5324 
5325   --
5326 
5327   debug_info := 'Starting Setup_Spoil';
5328   IF g_debug_switch in ('y','Y') THEN
5329      Print('(Setup_Spoil)'||debug_info);
5330   END IF;
5331 
5332   OPEN setup_spoil_select;
5333 
5334   LOOP
5335 
5336     debug_info := 'Fetch setup_spoil_select  Cursor';
5337     IF g_debug_switch in ('y','Y') THEN
5338        Print('(Setup_Spoil)'||debug_info);
5339     END IF;
5340 
5341     FETCH setup_spoil_select into selected_checkrun;
5342     --
5343     EXIT WHEN setup_spoil_select%NOTFOUND OR setup_spoil_select%NOTFOUND IS NULL;
5344 
5345     IF g_debug_switch in ('y','Y') THEN
5346        Print('(Setup_Spoil)'||debug_info);
5347     END IF;
5348 
5349     -- delete_setup_spoil
5350 
5351     debug_info := 'delete_setup_spoil';
5352     IF g_debug_switch in ('y','Y') THEN
5353        Print('(Setup_Spoil)'||debug_info);
5354     END IF;
5355 
5356     DELETE FROM ap_checks C
5357     WHERE  C.checkrun_name = selected_checkrun
5358     AND    C.status_lookup_code in ('SET UP','SPOILED')
5359     AND    C.last_update_date <= g_activity_date;
5360 
5361     -- delete_invoice_selection
5362 
5363     debug_info := 'delete_invoice_selection';
5364     IF g_debug_switch in ('y','Y') THEN
5365        Print('(Setup_Spoil)'||debug_info);
5366     END IF;
5367 
5368     DELETE FROM ap_invoice_selection_criteria C
5369     WHERE  C.checkrun_name = selected_checkrun
5370     AND    C.last_update_date <= g_activity_date;
5371 
5372   END LOOP;
5373 
5374   debug_info := 'End Setup_Spoil';
5375   IF g_debug_switch in ('y','Y') THEN
5376      Print('(Setup_Spoil)'||debug_info);
5377   END IF;
5378 
5379   RETURN (TRUE);
5380 
5381   RETURN NULL;
5382 
5383 EXCEPTION
5384 
5385     WHEN OTHERS THEN
5386     IF (SQLCODE < 0 ) then
5387        Print(SQLERRM);
5388     END IF;
5389     RETURN (FALSE);
5390 
5391 END Setup_Spoil;
5392 
5393 
5394 /*==========================================================================
5395   Function: Delete_AP_Tables
5396 
5397  *==========================================================================*/
5398 FUNCTION Delete_AP_Tables
5399          (P_Calling_Sequence   IN  VARCHAR2,
5400           p_start_rowid        IN  ROWID   ,  -- Bug 8913560
5401           p_end_rowid          IN  ROWID   ,  -- Bug 8913560
5402 	  p_purge_name         IN  VARCHAR2,  -- Bug 8913560
5403 	  P_rows_processed     OUT NOCOPY NUMBER)    -- Bug 9481539
5404 RETURN BOOLEAN IS
5405 
5406 debug_info                   	VARCHAR2(200);
5407 current_calling_sequence     	VARCHAR2(2000);
5408 range_high		     	NUMBER;
5409 range_low		     	NUMBER;
5410 range_size		     	NUMBER;
5411 inv_lower_limit		    	NUMBER;
5412 inv_upper_limit		     	NUMBER;
5413 overflow_exist                  VARCHAR2(200);
5414 overflow_check_stock_id		NUMBER;
5415 to_be_deleted_check_number	NUMBER;
5416 l_key_value_list1               gl_ca_utility_pkg.r_key_value_arr;
5417 l_key_value_list2               gl_ca_utility_pkg.r_key_value_arr;
5418 
5419 
5420 
5421 l_count number := 0;
5422 
5423 /* Bug 8913560
5424  CURSOR range (low_inv_id IN NUMBER) IS
5425     SELECT invoice_id
5426     FROM ap_purge_invoice_list
5427     WHERE double_check_flag = 'Y'
5428     and invoice_id > low_inv_id
5429     ORDER BY invoice_id asc;
5430 */
5431 
5432  CURSOR ap_invoice_cur ( p_start_rowid ROWID, -- Bug 8913560 low_inv_id IN NUMBER,
5433                          p_end_rowid   ROWID  /* Bug 8913560 high_inv_id IN NUMBER*/ ) IS
5434         SELECT PL.invoice_id
5435         FROM ap_purge_invoice_list PL
5436         WHERE PL.double_check_flag = 'Y'
5437         AND   -- Bug 8913560 PL.invoice_id BETWEEN low_inv_id AND high_inv_id
5438 	      PL.rowid BETWEEN p_start_rowid AND p_end_rowid ;
5439 
5440  l_invoice_id           ap_invoices.invoice_id%TYPE;
5441  l_invoice_dist_id      ap_invoice_distributions.invoice_distribution_id%TYPE;
5442  l_check_id             ap_checks.check_id%TYPE;
5443  l_payment_history_id   ap_payment_history.payment_history_id%TYPE;
5444  l_invoice_payment_id   ap_invoice_payments.invoice_payment_id%TYPE;
5445 
5446  -- Bug 8913560 : Added the 3 variables given below
5447  l_check_rows                NUMBER ;
5448  l_invoice_payment_rows      NUMBER ;
5449  l_invoice_rows              NUMBER ;
5450 
5451  /*bug 11829621: added the following two columns */
5452  l_invoice_lines_rows        NUMBER ;
5453  l_invoice_distributions_rows NUMBER;
5454 
5455 BEGIN
5456 
5457   -- Update the calling sequence
5458   --
5459 
5460   current_calling_sequence := 'Delete_AP_Tables<-'||P_Calling_Sequence;
5461 
5462   debug_info := 'Starting Delete_AP_Tables';
5463   IF g_debug_switch in ('y','Y') THEN
5464      Print('(Delete_AP_Tables)'||debug_info);
5465   END IF;
5466 
5467   /* Bug 8913560
5468   --
5469   range_high := 0;
5470   range_size := g_range_size;
5471 
5472   -- get_ap_range
5473 
5474   select nvl(min(invoice_id),-1)
5475   ,      nvl(max(invoice_id),-1)
5476   into range_low, range_high
5477   from ap_purge_invoice_list
5478   where double_check_flag = 'Y';
5479 
5480  --Bug2382623 Changed the paramter to range_low
5481  OPEN  range(range_low);
5482  WHILE l_count < g_range_size
5483    LOOP
5484      FETCH range INTO range_high;
5485      EXIT WHEN range%NOTFOUND;
5486      l_count := l_count + 1;
5487    END LOOP;
5488    CLOSE RANGE;
5489 
5490   LOOP
5491 */
5492      debug_info := 'Deleting one subgroup of Invoices';
5493      IF g_debug_switch in ('y','Y') THEN
5494         Print('(Delete_AP_Tables)'||debug_info);
5495         Print('ap_doc_sequence_audit, Checks');
5496      END IF;
5497 
5498 /*  Bug 5052709 - removal of obsolete SQL
5499      -- Move the deletion of ap_chrg_allocations from purge_pos to here.
5500      -- Since this is now in the loop with range_low and range_high defined,
5501      -- purge this tables in multiple runs, with each run bounded by range_low
5502      -- and range_high of invoice_id
5503 
5504      delete from ap_chrg_allocations aca
5505      where exists (
5506 		select 'allocations'
5507 		from ap_invoice_distributions aid
5508 		,    ap_purge_invoice_list    pil
5509 		where aca.item_dist_id      = aid.invoice_distribution_id
5510 		and   pil.invoice_id        = aid.invoice_id
5511               and   pil.invoice_id BETWEEN range_low and range_high
5512 		and   pil.double_check_flag = 'Y');
5513 */
5514      -- delete_check_sequence_audit
5515 
5516      /* bug3068811 : Changed from EXISTS to IN for performance */
5517      DELETE FROM ap_doc_sequence_audit AUD
5518      WHERE (AUD.doc_sequence_id , AUD.doc_sequence_value)
5519             IN (SELECT C.doc_sequence_id , C.doc_sequence_value
5520                   FROM ap_purge_invoice_list PL,
5521                        ap_checks C,
5522                        ap_invoice_payments IP
5523                   WHERE PL.double_check_flag = 'Y'
5524                   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5525 		        PL.rowid BETWEEN p_start_rowid AND p_end_rowid
5526                   AND   PL.invoice_id = IP.invoice_id
5527                   AND   IP.check_id = C.check_id ) ;
5528 
5529      -- overflow
5530 
5531      debug_info := 'ap_checks';
5532      IF g_debug_switch in ('y','Y') THEN
5533         Print('(Delete_AP_Tables)'||debug_info);
5534      END IF;
5535 
5536      if (Overflow(Overflow_Exist,
5537                   p_start_rowid, -- Bug 8913560 range_low,
5538                   p_end_rowid  , -- Bug 8913560 range_high,
5539 		  p_purge_name , -- Bug 8913560
5540                   'delete_ap_tables') <> TRUE) then
5541          Print( 'Overflow failed!');
5542          RETURN(FALSE);
5543      end if;
5544 
5545      debug_info := 'delete_checks';
5546      IF g_debug_switch in ('y','Y') THEN
5547         Print('(Delete_AP_Tables)'||debug_info);
5548      END IF;
5549 
5550 
5551      -- delete_checks
5552      -- bug 5052764 - go to base table ap_checks_all to remove FTS
5553      DELETE FROM ap_checks_all C
5554      WHERE C.check_id IN (
5555 	   SELECT P.check_id
5556 	   FROM ap_invoice_payments P, ap_purge_invoice_list PL
5557 	   WHERE P.invoice_id = PL.invoice_id
5558 	   AND PL.double_check_flag = 'Y'
5559 	   AND -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5560 	       PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5561 
5562      l_check_rows := SQL%ROWCOUNT ; -- Bug 8913560
5563 
5564      debug_info := 'setup_spoil';
5565      IF g_debug_switch in ('y','Y') THEN
5566         Print('(Delete_AP_Tables)'||debug_info);
5567      END IF;
5568 
5569 
5570      -- setup_spoil
5571 
5572      if (Setup_Spoil('delete_ap_tables') <> TRUE) then
5573          Print('Setup_Spoil failed!');
5574          RETURN(FALSE);
5575      end if;
5576 
5577      debug_info := 'ap_payment_history';
5578      IF g_debug_switch in ('y','Y') THEN
5579         Print('(Delete_AP_Tables)'||debug_info);
5580      END IF;
5581 
5582 
5583      DELETE FROM ap_payment_history aph
5584      WHERE EXISTS (
5585 	SELECT 'history purgeable'
5586 	FROM ap_invoice_payments aip
5587 	,    ap_purge_invoice_list PL
5588 	WHERE aip.invoice_id = PL.invoice_id
5589 	and aip.check_id     = aph.check_id
5590 	and PL.double_check_flag = 'Y'
5591         and PL.rowid BETWEEN p_start_rowid AND p_end_rowid); --9481539
5592 
5593      debug_info := 'ap_invoice_payments';
5594      IF g_debug_switch in ('y','Y') THEN
5595         Print('(Delete_AP_Tables)'||debug_info);
5596      END IF;
5597 
5598 
5599      -- delete_invoice_payments
5600 
5601      DELETE FROM ap_invoice_payments
5602      WHERE invoice_id IN (
5603 	   SELECT PL.invoice_id
5604 	   FROM ap_purge_invoice_list PL
5605 	   WHERE PL.double_check_flag = 'Y'
5606 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5607 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid);
5608 
5609      l_invoice_payment_rows := SQL%ROWCOUNT ; -- Bug 8913560
5610 
5611      debug_info := 'ap_payment_schedules';
5612      IF g_debug_switch in ('y','Y') THEN
5613         Print('(Delete_AP_Tables)'||debug_info);
5614      END IF;
5615 
5616 
5617      -- delete_payment_schedules
5618 
5619      DELETE FROM ap_payment_schedules
5620      WHERE invoice_id IN (
5621 	   SELECT PL.invoice_id
5622 	   FROM ap_purge_invoice_list PL
5623 	   WHERE PL.double_check_flag = 'Y'
5624 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5625 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5626 
5627     debug_info := 'ap_trial_balance';
5628      IF g_debug_switch in ('y','Y') THEN
5629         Print('(Delete_AP_Tables)'||debug_info);
5630      END IF;
5631 
5632 
5633      -- delete_trial_balance
5634 
5635      DELETE FROM ap_trial_balance
5636      WHERE invoice_id IN (
5637 	   SELECT PL.invoice_id
5638 	   FROM ap_purge_invoice_list PL
5639 	   WHERE PL.double_check_flag = 'Y'
5640 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5641 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5642 
5643      debug_info := 'ap_holds';
5644      IF g_debug_switch in ('y','Y') THEN
5645         Print('(Delete_AP_Tables)'||debug_info);
5646      END IF;
5647 
5648 
5649      -- delete_holds
5650 
5651      DELETE FROM ap_holds
5652      WHERE invoice_id IN (
5653 	   SELECT PL.invoice_id
5654 	   FROM ap_purge_invoice_list PL
5655 	   WHERE PL.double_check_flag = 'Y'
5656 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5657 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5658 
5659      debug_info := 'ap_inv_aprvl_hist';
5660      IF g_debug_switch in ('y','Y') THEN
5661         Print('(Delete_AP_Tables)'||debug_info);
5662      END IF;
5663 
5664 
5665      -- delete approval history
5666 
5667      DELETE FROM ap_inv_aprvl_hist
5668      WHERE invoice_id IN (
5669 	   SELECT PL.invoice_id
5670 	   FROM ap_purge_invoice_list PL
5671 	   WHERE PL.double_check_flag = 'Y'
5672 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5673 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5674 
5675 
5676      debug_info := 'ap_invoice_distributions';
5677      IF g_debug_switch in ('y','Y') THEN
5678         Print('(Delete_AP_Tables)'||debug_info);
5679      END IF;
5680 
5681 
5682      DELETE FROM ap_invoice_distributions
5683      WHERE invoice_id IN (
5684 	   SELECT PL.invoice_id
5685 	   FROM ap_purge_invoice_list PL
5686 	   WHERE PL.double_check_flag = 'Y'
5687 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5688 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5689 
5690         l_invoice_distributions_rows := SQL%ROWCOUNT; /*bug 11829621*/
5691 
5692         /* bug 10391241 */
5693      debug_info := 'ap_invoice_lines';
5694      IF g_debug_switch in ('y','Y') THEN
5695         Print('(Delete_AP_Tables)'||debug_info);
5696      END IF;
5697 
5698 
5699      DELETE FROM ap_invoice_lines
5700      WHERE invoice_id IN (
5701 	   SELECT PL.invoice_id
5702 	   FROM ap_purge_invoice_list PL
5703 	   WHERE PL.double_check_flag = 'Y'
5704 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5705 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5706 
5707          l_invoice_lines_rows := SQL%ROWCOUNT; /*bug 11829621*/
5708 
5709       /* bug 10391241 */
5710 
5711      debug_info := 'ap_doc_sequence_audit, Invoices';
5712      IF g_debug_switch in ('y','Y') THEN
5713         Print('(Delete_AP_Tables)'||debug_info);
5714      END IF;
5715 
5716      -- delete_inv_seq_audit
5717 
5718      /* bug3284915 : Changed from EXISTS to IN for performance */
5719      DELETE FROM ap_doc_sequence_audit AUD
5720      WHERE (AUD.doc_sequence_id , AUD.doc_sequence_value)
5721             IN (SELECT I.doc_sequence_id , I.doc_sequence_value
5722                    FROM ap_purge_invoice_list PL,
5723                         ap_invoices I
5724                    WHERE PL.double_check_flag = 'Y'
5725                    AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5726     		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid
5727                    AND   PL.invoice_id = I.invoice_id);
5728 
5729      OPEN ap_invoice_cur(p_start_rowid, p_end_rowid ); -- Bug 8913560 range_low, range_high);
5730      LOOP
5731 
5732      FETCH ap_invoice_cur
5733      INTO l_invoice_id;
5734      EXIT WHEN ap_invoice_cur%NOTFOUND;
5735 
5736 	--Bug 2840203 DBI logging
5737 	--We are only logging the invoice deletion, as the summary code knows to
5738 	--delete all related transactions: dists, holds, payment shedules, payments
5739         AP_DBI_PKG.Maintain_DBI_Summary
5740               (p_table_name => 'AP_INVOICES',
5741                p_operation => 'D',
5742                p_key_value1 => l_invoice_id,
5743                 p_calling_sequence => current_calling_sequence);
5744 
5745      END LOOP;
5746      CLOSE ap_invoice_cur;
5747 
5748      debug_info := 'ap_invoices';
5749      IF g_debug_switch in ('y','Y') THEN
5750         Print('(Delete_AP_Tables)'||debug_info);
5751      END IF;
5752 
5753 
5754      -- delete_invoices
5755 
5756      DELETE FROM ap_invoices
5757      WHERE invoice_id IN (
5758 	   SELECT PL.invoice_id
5759 	   FROM ap_purge_invoice_list PL
5760 	   WHERE PL.double_check_flag = 'Y'
5761 	   AND   -- Bug 8913560 PL.invoice_id BETWEEN range_low AND range_high
5762 		 PL.rowid BETWEEN p_start_rowid AND p_end_rowid );
5763 
5764      l_invoice_rows := SQL%ROWCOUNT ; -- Bug 8913560
5765      P_rows_processed := l_invoice_rows ; -- 9481539
5766 
5767      Update_Financials_Purges ( p_check_rows             => l_check_rows          ,
5768                                 p_invoice_payment_rows   => l_invoice_payment_rows,
5769                                 p_invoice_rows           => l_invoice_rows        ,
5770                                 p_invoice_lines_rows     => l_invoice_lines_rows  ,                --bug 11829621
5771                                 p_invoice_distributions_rows => l_invoice_distributions_rows,      --bug 11829621
5772                                 p_purge_name             => g_purge_name          ) ;
5773 
5774     -- 9481539 assigned the g_purge_name to p_purge_name
5775 /* Bug 8913560
5776      COMMIT;
5777 
5778      l_count :=0;
5779 
5780      range_low := range_high +1;
5781 
5782      OPEN  range(range_low);     --Bug2711759
5783      WHILE l_count < g_range_size
5784      LOOP
5785        FETCH range INTO range_high;
5786        EXIT WHEN range%NOTFOUND;
5787        l_count := l_count + 1;
5788      END LOOP;
5789      CLOSE RANGE;
5790 
5791      if range_low > range_high then
5792 	EXIT;
5793      end if;
5794 
5795   END LOOP; */
5796 
5797   /* 9481539, moving this delete statement to parent process delete_seeded_data
5798   debug_info := 'deleting from ap_batches';
5799   IF g_debug_switch in ('y','Y') THEN
5800      Print('(Delete_AP_Tables)'||debug_info);
5801   END IF;
5802 
5803 
5804   -- delete_batches
5805 
5806   DELETE FROM ap_batches B
5807   WHERE B.last_update_date <= g_activity_date
5808   AND NOT EXISTS (
5809 	  SELECT null
5810 	  FROM ap_invoices I
5811 	  WHERE I.batch_id = B.batch_id); */
5812 
5813     -- Bug 8913560   COMMIT;
5814 
5815   debug_info := 'Completed deleteing from Oracle Payables';
5816   IF g_debug_switch in ('y','Y') THEN
5817      Print('(Delete_AP_Tables)'||debug_info);
5818   END IF;
5819 
5820   RETURN (TRUE);
5821 
5822 RETURN NULL; EXCEPTION
5823 
5824   WHEN OTHERS THEN
5825     IF (SQLCODE < 0 ) then
5826        Print(SQLERRM);
5827     END IF;
5828     RETURN (FALSE);
5829 
5830 END Delete_AP_Tables;
5831 
5832 
5833 /*==========================================================================
5834   Function: PURGE_ACCOUNTING
5835 
5836  *==========================================================================*/
5837 FUNCTION PURGE_ACCOUNTING
5838 
5839     (P_Calling_Sequence   IN  VARCHAR2,
5840      p_start_rowid        IN  ROWID   ,  -- Bug 8913560
5841      p_end_rowid          IN  ROWID   ,  -- Bug 8913560
5842      p_purge_name         IN  VARCHAR2 ) -- Bug 8913560
5843 RETURN BOOLEAN IS
5844 
5845 debug_info                   	VARCHAR2(200);
5846 current_calling_sequence     	VARCHAR2(2000);
5847 range_high		     	NUMBER;
5848 range_low		     	NUMBER;
5849 range_size		     	NUMBER;
5850 inv_lower_limit		    	NUMBER;
5851 inv_upper_limit		     	NUMBER;
5852 overflow_exist                  VARCHAR2(200);
5853 overflow_check_stock_id		NUMBER;
5854 to_be_deleted_check_number	NUMBER;
5855 
5856 
5857 l_count number := 0;
5858 /* Bug 8913560
5859  CURSOR range (low_inv_id IN NUMBER) IS
5860     SELECT invoice_id
5861     FROM ap_purge_invoice_list
5862     WHERE double_check_flag = 'Y'
5863     and invoice_id > low_inv_id
5864     ORDER BY invoice_id asc; */
5865  -- Bug 8913560 : Added the 3 variables given below
5866 l_ae_line_rows	         NUMBER ;
5867 l_ae_header_rows	 NUMBER ;
5868 l_accounting_event_rows  NUMBER ;
5869 
5870 BEGIN
5871 /* Bug 8913560
5872   range_high := 0;
5873   range_size := g_range_size;
5874 
5875   -- get_ap_range
5876 
5877   SELECT nvl(min(invoice_id),-1)
5878   ,      nvl(max(invoice_id),-1)
5879   into range_low, range_high
5880   FROM   ap_purge_invoice_list
5881   WHERE  double_check_flag = 'Y';
5882 
5883      OPEN  range(range_low);   --Bug2711759
5884  WHILE l_count < g_range_size
5885     LOOP
5886        FETCH range INTO range_high;
5887       EXIT WHEN range%NOTFOUND;
5888       l_count := l_count + 1;
5889     END LOOP;
5890     CLOSE RANGE;
5891 
5892 
5893  LOOP
5894 */
5895   -- Update calling sequence
5896 
5897   current_calling_sequence := 'Purge Accounting<-'||P_Calling_Sequence;
5898 
5899   --
5900 
5901   debug_info := 'Starting Purge Accounting';
5902   IF g_debug_switch in ('y','Y') THEN
5903      Print('(Purge_Accounting)'||debug_info);
5904   END IF;
5905 
5906   -- Bug 2463233
5907   -- Code Added by MSWAMINA
5908   -- Added logic to purge the ap_liability_balance
5909   --
5910   debug_info := 'ap_liability_balance';
5911   IF g_debug_switch in ('y','Y') THEN
5912      Print('(Purge_Accounting)'||debug_info);
5913   END IF;
5914 
5915   DELETE   FROM   ap_liability_balance alb
5916   WHERE  EXISTS   (
5917          SELECT   'records exist'
5918            FROM   ap_purge_invoice_list   pil
5919 	  WHERE   alb.invoice_id          = pil.invoice_id
5920             AND   pil.double_check_flag   = 'Y'
5921             AND   /*  Bug 8913560 pil.invoice_id BETWEEN  range_low AND  range_high */
5922 		  pil.rowid BETWEEN p_start_rowid AND p_end_rowid )
5923   AND             journal_sequence_id IS NULL;
5924 
5925 
5926 -- Bug 4588031 - Removing code as AP accoutning tables will not be used in R12
5927 /*
5928  -- Wrote the below 2 delete statements as a fix for bug 2866997
5929  DELETE FROM ap_ae_lines ael
5930   WHERE ael.ae_header_id in
5931       ( SELECT aeh.ae_header_id
5932           FROM ap_ae_headers          aeh
5933               ,ap_accounting_events   aae
5934               ,ap_purge_invoice_list  pil
5935           WHERE aae.source_id              = pil.invoice_id
5936            and aae.source_table            = 'AP_INVOICES'
5937            and aae.accounting_event_id     = aeh.accounting_event_id
5938            and pil.double_check_flag       = 'Y'
5939            and pil.invoice_id BETWEEN range_low AND range_high) ;
5940 
5941  DELETE FROM ap_ae_lines ael
5942   WHERE ael.ae_header_id in
5943         ( SELECT aeh.ae_header_id
5944             FROM ap_ae_headers        aeh  -- bug 2153117 added
5945               ,ap_accounting_events   aae
5946               ,ap_invoice_payments    aip
5947               ,ap_purge_invoice_list  pil
5948         WHERE aae.source_id              = aip.check_id
5949               and aae.source_table        = 'AP_CHECKS'
5950               and pil.double_check_flag  = 'Y'
5951               and aae.accounting_event_id = aeh.accounting_event_id
5952               and aip.invoice_id          = pil.invoice_id
5953               and pil.invoice_id BETWEEN range_low AND range_high);
5954 
5955   debug_info := 'ap_ae_headers';
5956   IF g_debug_switch in ('y','Y') THEN
5957      Print('(Purge_Accounting)'||debug_info);
5958   END IF;
5959 
5960 
5961   DELETE FROM ap_ae_headers aeh
5962   WHERE aeh.accounting_event_id IN
5963       ( SELECT  aae.accounting_event_id
5964 	FROM  ap_accounting_events     aae
5965         ,     ap_purge_invoice_list    pil
5966 	WHERE aae.source_id           = pil.invoice_id
5967 	and   aae.source_table        = 'AP_INVOICES'
5968 	and   pil.double_check_flag   = 'Y'
5969         -- Commented the below line as a fix for bug 2880690
5970         -- and   aae.accounting_event_id = aeh.accounting_event_id
5971         and   pil.invoice_id BETWEEN range_low AND range_high
5972        ) ;
5973 
5974 
5975   DELETE FROM ap_ae_headers aeh
5976   WHERE  aeh.accounting_event_id in
5977       ( SELECT aae.accounting_event_id
5978 	FROM  ap_accounting_events   aae
5979         ,     ap_invoice_payments    aip
5980  	,     ap_purge_invoice_list  pil
5981 	-- bug2153117 removed
5982         -- ,     ap_ae_headers          aeh
5983 	WHERE aae.source_id           = aip.check_id
5984 	and   aae.source_table        = 'AP_CHECKS'
5985 	and   pil.double_check_flag   = 'Y'
5986         -- Commented the below line as a fix for bug 2880690
5987         -- and   aae.accounting_event_id = aeh.accounting_event_id
5988  	and   aip.invoice_id          = pil.invoice_id
5989         and   pil.invoice_id BETWEEN range_low AND range_high) ;
5990 
5991 */ --Bug 4588031
5992 
5993   debug_info := 'ap_encumbrance_lines';
5994   IF g_debug_switch in ('y','Y') THEN
5995      Print('(Purge_Accounting)'||debug_info);
5996   END IF;
5997 
5998   DELETE FROM ap_encumbrance_lines aen
5999   WHERE EXISTS (
6000 	SELECT 'dist'
6001 	FROM  ap_purge_invoice_list    pil
6002 	,     ap_invoice_distributions aid
6003 	WHERE aen.invoice_distribution_id  = aid.invoice_distribution_id
6004 	and   aid.invoice_id               = pil.invoice_id
6005         and   pil.double_check_flag        = 'Y'
6006         and   /*  Bug 8913560 pil.invoice_id BETWEEN  range_low AND  range_high */
6007 	      pil.rowid BETWEEN p_start_rowid AND p_end_rowid);
6008 
6009  -- Bug 4588031 - Removing code as AP accounting tables will not be used in R12
6010 /*  -- delete_ap_accounting_events
6011     -- Fix for bug 2545172 , commented above delete statement and wrote
6012     -- below 3 delete statement
6013 
6014   DELETE FROM AP_ACCOUNTING_EVENTS AAE
6015   WHERE aae.source_id in (SELECT PIL.INVOICE_ID
6016                             FROM AP_PURGE_INVOICE_LIST PIL
6017                           WHERE  PIL.DOUBLE_CHECK_FLAG = 'Y'
6018                           AND PIL.INVOICE_ID BETWEEN range_low AND range_high )
6019         AND AAE.SOURCE_TABLE = 'AP_INVOICES'
6020         ;
6021 
6022   DELETE FROM AP_ACCOUNTING_EVENTS AAE  WHERE
6023             aae.source_id in ( SELECT APC.CHECK_ID
6024                                 FROM AP_PURGE_INVOICE_LIST PIL,
6025                                       AP_CHECKS APC,
6026                                       AP_INVOICE_PAYMENTS AIP
6027                                 WHERE PIL.DOUBLE_CHECK_FLAG = 'Y'
6028                                       AND APC.CHECK_ID = AIP.CHECK_ID
6029                                       AND AIP.INVOICE_ID = PIL.INVOICE_ID
6030                                       AND PIL.INVOICE_ID BETWEEN range_low
6031                                           AND range_high )
6032             AND AAE.SOURCE_TABLE = 'AP_CHECKS' ;
6033 
6034 
6035   DELETE FROM AP_ACCOUNTING_EVENTS AAE  WHERE
6036             AAE.source_id IN ( SELECT APH.CHECK_ID
6037                                FROM AP_PURGE_INVOICE_LIST PIL,
6038                                     AP_INVOICE_PAYMENTS AIP,
6039                                     AP_PAYMENT_HISTORY APH
6040                               WHERE PIL.DOUBLE_CHECK_FLAG = 'Y'
6041                                     AND APH.CHECK_ID = AIP.CHECK_ID
6042                                     AND AIP.INVOICE_ID = PIL.INVOICE_ID
6043                                     AND PIL.INVOICE_ID BETWEEN range_low
6044                                         AND range_high )
6045             and AAE.SOURCE_TABLE = 'AP_PAYMENT_HISTORY'  ;
6046 */--Bug 4588031
6047 /* Bug 8913560
6048   COMMIT;
6049 
6050      l_count :=0;
6051 
6052      range_low := range_high +1;
6053 
6054        OPEN  range(range_low);  --Bug2711759
6055      WHILE l_count < g_range_size
6056      LOOP
6057        FETCH range INTO range_high;
6058        EXIT WHEN range%NOTFOUND;
6059        l_count := l_count + 1;
6060      END LOOP;
6061        CLOSE RANGE;
6062 
6063      if range_low > range_high then
6064 	EXIT;
6065      end if;
6066 
6067  END LOOP;
6068  */
6069 
6070  RETURN NULL; EXCEPTION
6071 
6072   WHEN OTHERS THEN
6073     IF (SQLCODE < 0 ) then
6074        Print(SQLERRM);
6075     END IF;
6076     RETURN (FALSE);
6077 
6078 
6079 END;
6080 
6081 
6082 /*==========================================================================
6083   Function: Purge_Schedules_by_Cum
6084 
6085  *==========================================================================*/
6086 FUNCTION Purge_Schedules_by_Cum
6087          (P_Calling_Sequence     IN   VARCHAR2)
6088 RETURN BOOLEAN IS
6089 
6090 debug_info                      VARCHAR2(200);
6091 current_calling_sequence        VARCHAR2(2000);
6092 chv_lower_limit                 NUMBER;
6093 chv_upper_limit                 NUMBER;
6094 range_high			NUMBER;
6095 range_low			NUMBER;
6096 range_size			NUMBER;
6097 
6098 l_count number := 0;
6099 
6100  CURSOR range (low_chv_id IN NUMBER) IS
6101     SELECT schedule_item_id
6102     FROM chv_purge_schedule_list
6103     WHERE double_check_flag = 'Y'
6104     and schedule_item_id > low_chv_id
6105     ORDER BY schedule_item_id asc;
6106 
6107 
6108 BEGIN
6109 
6110    --  Update the calling sequence
6111    --
6112 
6113    current_calling_sequence := 'Purge_Schedules_by_Cum<-'||P_Calling_Sequence;
6114 
6115    --
6116    debug_info := 'Starting Purge_Schedules_by_Cum';
6117    IF g_debug_switch in ('y','Y') THEN
6118       Print('(Purge_Schedules_by_Cum)'||debug_info);
6119    END IF;
6120 
6121    range_size := g_range_size;
6122 
6123 
6124    range_high := 0;
6125 
6126    debug_info := 'get_chv_range';
6127    IF g_debug_switch in ('y','Y') THEN
6128       Print('(Purge_Schedules_by_Cum)'||debug_info);
6129    END IF;
6130 
6131    -- get_chv_range
6132 
6133   select nvl(min(schedule_item_id),-1)
6134   ,      nvl(max(schedule_item_id),-1)
6135   into range_low, range_high
6136   from chv_purge_schedule_list
6137   where double_check_flag = 'Y';
6138 
6139 
6140   OPEN  range(range_low);  --Bug2711759
6141   WHILE l_count < g_range_size
6142     LOOP
6143       FETCH range INTO range_high;
6144       EXIT WHEN range%NOTFOUND;
6145       l_count := l_count + 1;
6146    END LOOP;
6147    CLOSE RANGE;
6148 
6149 
6150  -----new code ends-----------
6151    LOOP
6152       debug_info := 'Updating a subgroup of Supplier Schedule Items';
6153       IF g_debug_switch in ('y','Y') THEN
6154          Print('(Purge_Schedules_by_Cum)'||debug_info);
6155       END IF;
6156 
6157       -- Update chv_schedule_items
6158 
6159       update chv_schedule_items csi
6160       set csi.item_purge_status = 'PURGED'
6161       where exists
6162           (select null
6163            from  chv_purge_schedule_list cpsl
6164            where cpsl.schedule_item_id = csi.schedule_item_id
6165            and   cpsl.double_check_flag = 'Y'
6166            and   cpsl.schedule_item_id between range_low and range_high);
6167 
6168       debug_info := 'chv_item_orders';
6169       IF g_debug_switch in ('y','Y') THEN
6170          Print('(Purge_Schedules_by_Cum)'||debug_info);
6171       END IF;
6172 
6173       -- delete_chv_item_orders
6174 
6175       delete from chv_item_orders cio
6176       where exists
6177           (select null
6178            from  chv_purge_schedule_list cpsl
6179            where cpsl.schedule_item_id = cio.schedule_item_id
6180            and   cpsl.double_check_flag = 'Y'
6181            and   cpsl.schedule_item_id between range_low and range_high);
6182 
6183       debug_info := 'po_lines';
6184       IF g_debug_switch in ('y','Y') THEN
6185          Print('(Purge_Schedules_by_Cum)'||debug_info);
6186       END IF;
6187 
6188       -- delete_chv_horizontal_schedules
6189 
6190       delete from chv_horizontal_Schedules chs
6191       where exists
6192           (select null
6193            from  chv_purge_schedule_list cpsl
6194            where cpsl.schedule_item_id = chs.schedule_item_id
6195            and   cpsl.double_check_flag = 'Y'
6196            and   cpsl.schedule_item_id between range_low and range_high);
6197 
6198      debug_info := 'chv_authorizations';
6199      IF g_debug_switch in ('y','Y') THEN
6200         Print('(Purge_Schedules_by_Cum)'||debug_info);
6201      END IF;
6202 
6203      -- delete_chv_authorizations
6204 
6205      delete from chv_authorizations ca
6206      where exists
6207           (select null
6208            from  chv_purge_schedule_list cpsl
6209            where cpsl.schedule_item_id = ca.reference_id
6210            and   ca.reference_type = 'SCHEDULE_ITEMS'
6211            and   cpsl.double_check_flag = 'Y'
6212            and   cpsl.schedule_item_id between range_low and range_high);
6213 
6214      COMMIT;
6215 
6216      l_count :=0;
6217 
6218      range_low := range_high +1;
6219 
6220        OPEN  range(range_low);       --Bug2711759
6221      WHILE l_count < g_range_size
6222      LOOP
6223        FETCH range INTO range_high;
6224        EXIT WHEN range%NOTFOUND;
6225        l_count := l_count + 1;
6226      END LOOP;
6227        CLOSE RANGE;
6228 
6229     if range_low > range_high then
6230         EXIT;
6231     end if;
6232 
6233    END LOOP;
6234 
6235    debug_info := 'chv_auth_cum_periods';
6236    IF g_debug_switch in ('y','Y') THEN
6237       Print('(Purge_Schedules_by_Cum)'||debug_info);
6238    END IF;
6239 
6240    -- delete_chv_authorizations
6241 
6242    delete from chv_authorizations ca
6243    where exists
6244         (select null
6245          from  chv_purge_cum_list cpcl
6246          where cpcl.cum_period_id = ca.reference_id
6247          and   cpcl.double_check_flag = 'Y'
6248 	 and   ca.reference_type = 'CUM_PERIODS');
6249 
6250    debug_info := 'chv_cum_adjustments';
6251    IF g_debug_switch in ('y','Y') THEN
6252       Print('(Purge_Schedules_by_Cum)'||debug_info);
6253    END IF;
6254 
6255    -- delete_chv_cum_adjustments
6256 
6257    delete from chv_cum_adjustments cca
6258    where exists
6259         (select null
6260          from  chv_purge_cum_list cpcl
6261          where cpcl.cum_period_id = cca.cum_period_id
6262          and   cpcl.double_check_flag = 'Y');
6263 
6264    debug_info := 'chv_cum_periods';
6265    IF g_debug_switch in ('y','Y') THEN
6266       Print('(Purge_Schedules_by_Cum)'||debug_info);
6267    END IF;
6268 
6269    -- delete_chv_cum_periods
6270 
6271    delete from chv_cum_periods ccp
6272    where exists
6273         (select null
6274          from  chv_purge_cum_list cpcl
6275          where cpcl.cum_period_id = ccp.cum_period_id
6276          and   cpcl.double_check_flag = 'Y');
6277 
6278    debug_info := 'chv_schedule_items';
6279    IF g_debug_switch in ('y','Y') THEN
6280       Print('(Purge_Schedules_by_Cum)'||debug_info);
6281    END IF;
6282 
6283    -- delete_chv_schedule_items
6284 
6285 /* bug2067536 Performance Bug
6286 */
6287    delete from   chv_schedule_items csi
6288    where not exists (select null
6289                        from chv_schedule_items cs
6290                       where csi.schedule_id = cs.schedule_id
6291                         and nvl(cs.item_purge_status,'ACTIVE') <> 'PURGED');
6292 
6293    debug_info := 'chv_schedule_headers';
6294    IF g_debug_switch in ('y','Y') THEN
6295       Print('(Purge_Schedules_by_Cum)'||debug_info);
6296    END IF;
6297 
6298    -- delete_chv_schedule_headers
6299 
6300 /* bug2067536 Performance Bug
6301 */
6302    delete from chv_schedule_headers csh
6303    where not exists (select null
6304                        from chv_schedule_items csi
6305                       where csh.schedule_id = csi.schedule_id );
6306 
6307    COMMIT;
6308 
6309    debug_info := 'End Purge_Schedules_by_Org';
6310    IF g_debug_switch in ('y','Y') THEN
6311       Print('(Purge_Schedules_by_Cum)'||debug_info);
6312    END IF;
6313    RETURN (TRUE);
6314 
6315 RETURN NULL; EXCEPTION
6316     WHEN OTHERS THEN
6317      IF (SQLCODE < 0 ) THEN
6318          Print(SQLERRM);
6319      END IF;
6320      RETURN (FALSE);
6321 END Purge_Schedules_by_Cum;
6322 
6323 
6324 /*==========================================================================
6325   Function: Purge_Schedules_by_Org
6326 
6327  *==========================================================================*/
6328 FUNCTION Purge_Schedules_by_Org
6329          (P_Calling_Sequence     IN   VARCHAR2)
6330 RETURN BOOLEAN IS
6331 
6332 debug_info                      VARCHAR2(200);
6333 current_calling_sequence        VARCHAR2(2000);
6334 chv_lower_limit                  NUMBER;
6335 chv_upper_limit                  NUMBER;
6336 range_high			NUMBER;
6337 range_low			NUMBER;
6338 range_size			NUMBER;
6339 
6340 l_count number := 0;
6341 
6342  CURSOR range (low_chv_id IN NUMBER) IS
6343     SELECT schedule_item_id
6344     FROM chv_purge_schedule_list
6345     WHERE double_check_flag = 'Y'
6346     and schedule_item_id > low_chv_id
6347     ORDER BY schedule_item_id asc;
6348 
6349 
6350 BEGIN
6351 
6352    --  Update the calling sequence
6353    --
6354 
6355    current_calling_sequence := 'Purge_Schedules_by_Org<-'||P_Calling_Sequence;
6356 
6357    --
6358    debug_info := 'Starting Purge_Schedules_by_Org';
6359    IF g_debug_switch in ('y','Y') THEN
6360       Print('(Purge_Schedules_by_Org)'||debug_info);
6361    END IF;
6362 
6363    range_size := g_range_size;
6364 
6365 
6366    range_high := 0;
6367 
6368    debug_info := 'get_chv_range';
6369    IF g_debug_switch in ('y','Y') THEN
6370       Print('(Purge_Schedules_by_Org)'||debug_info);
6371    END IF;
6372 
6373    -- get_chv_range
6374 
6375   select nvl(min(schedule_item_id),-1)
6376   ,      nvl(max(schedule_item_id),-1)
6377   into range_low, range_high
6378   from chv_purge_schedule_list
6379   where double_check_flag = 'Y';
6380 
6381        OPEN  range(range_low);  --Bug2711759
6382    WHILE l_count < g_range_size
6383      LOOP
6384        FETCH range INTO range_high;
6385        EXIT WHEN range%NOTFOUND;
6386        l_count := l_count + 1;
6387      END LOOP;
6388        CLOSE RANGE;
6389 
6390    LOOP
6391       debug_info := 'Updating a subgroup of Supplier Schedule Items';
6392       IF g_debug_switch in ('y','Y') THEN
6393          Print('(Purge_Schedules_by_Org)'||debug_info);
6394       END IF;
6395 
6396       -- Update chv_schedule_items
6397 
6398       update chv_schedule_items csi
6399       set csi.item_purge_status = 'PURGED'
6400       where exists
6401           (select null
6402            from  chv_purge_schedule_list cpsl
6403            where cpsl.schedule_item_id = csi.schedule_item_id
6404            and   cpsl.double_check_flag = 'Y'
6405            and   cpsl.schedule_item_id between range_low and range_high);
6406 
6407       debug_info := 'chv_item_orders';
6408       IF g_debug_switch in ('y','Y') THEN
6409          Print('(Purge_Schedules_by_Org)'||debug_info);
6410       END IF;
6411 
6412       -- delete_chv_item_orders
6413 
6414       delete from chv_item_orders cio
6415       where exists
6416           (select null
6417            from  chv_purge_schedule_list cpsl
6418            where cpsl.schedule_item_id = cio.schedule_item_id
6419            and   cpsl.double_check_flag = 'Y'
6420            and   cpsl.schedule_item_id between range_low and range_high);
6421 
6422       debug_info := 'po_lines';
6423       IF g_debug_switch in ('y','Y') THEN
6424          Print('(Purge_Schedules_by_Org)'||debug_info);
6425       END IF;
6426 
6427       -- delete_chv_horizontal_schedules
6428 
6429       delete from chv_horizontal_Schedules chs
6430       where exists
6431           (select null
6432            from  chv_purge_schedule_list cpsl
6433            where cpsl.schedule_item_id = chs.schedule_item_id
6434            and   cpsl.double_check_flag = 'Y'
6435            and   cpsl.schedule_item_id between range_low and range_high);
6436 
6437      debug_info := 'chv_authorizations';
6438      IF g_debug_switch in ('y','Y') THEN
6439         Print('(Purge_Schedules_by_Org)'||debug_info);
6440      END IF;
6441 
6442      -- delete_chv_authorizations
6443 
6444      delete from chv_authorizations ca
6445      where exists
6446           (select null
6447            from  chv_purge_schedule_list cpsl
6448            where cpsl.schedule_item_id = ca.reference_id
6449            and   ca.reference_type = 'SCHEDULE_ITEMS'
6450            and   cpsl.double_check_flag = 'Y'
6451            and   cpsl.schedule_item_id between range_low and range_high);
6452 
6453      COMMIT;
6454 
6455      l_count :=0;
6456 
6457      range_low := range_high +1;
6458 
6459        OPEN  range(range_low);  --Bug2711759
6460      WHILE l_count < g_range_size
6461      LOOP
6462        FETCH range INTO range_high;
6463        EXIT WHEN range%NOTFOUND;
6464        l_count := l_count + 1;
6465      END LOOP;
6466        CLOSE RANGE;
6467 
6468     if range_low > range_high then
6469         EXIT;
6470     end if;
6471 
6472    END LOOP;
6473 
6474    COMMIT;
6475 
6476 /*  bug2067536 Performance Bug
6477 */
6478 
6479    delete from   chv_schedule_items csi
6480    where not exists (select null
6481                        from chv_schedule_items cs
6482                       where csi.schedule_id = cs.schedule_id
6483                         and nvl(cs.item_purge_status,'ACTIVE') <> 'PURGED');
6484 
6485 /*  bug2067536 Performance Bug
6486 */
6487 
6488    delete from chv_schedule_headers csh
6489    where not exists (select null
6490                        from chv_schedule_items csi
6491                       where csh.schedule_id = csi.schedule_id );
6492 
6493    COMMIT;
6494 
6495    debug_info := 'End Purge_Schedules_by_Org';
6496    IF g_debug_switch in ('y','Y') THEN
6497       Print('(Purge_Schedules_by_Org)'||debug_info);
6498    END IF;
6499    RETURN (TRUE);
6500 
6501 RETURN NULL; EXCEPTION
6502     WHEN OTHERS THEN
6503      IF (SQLCODE < 0 ) THEN
6504          Print(SQLERRM);
6505      END IF;
6506      RETURN (FALSE);
6507 END Purge_Schedules_by_Org;
6508 
6509 
6510 
6511 /*==========================================================================
6512   Function: Purge_Vendors
6513 
6514  *==========================================================================*/
6515 FUNCTION Purge_Vendors
6516 	 (P_Calling_Sequence   IN  VARCHAR2)
6517 RETURN BOOLEAN IS
6518 
6519 debug_info                   	VARCHAR2(2000);
6520 current_calling_sequence     	VARCHAR2(2000);
6521 l_pos_dynamic_call              VARCHAR2(2000);
6522 l_po_return_status              VARCHAR2(1);
6523 
6524 cursor c_purge_vendors IS
6525 select vendor_id
6526 from  po_purge_vendor_list pvl
6527 where  pvl.double_check_flag = 'Y';
6528 
6529 cursor c_purge_vendor_sites IS
6530 select vendor_id,
6531        vendor_site_id
6532 from   po_vendor_sites_all
6533 where  vendor_id in (select vendor_id
6534                      from   po_purge_vendor_list pvl
6535                      where  pvl.double_check_flag = 'Y');
6536 
6537 BEGIN
6538 
6539   -- Update the calling sequence
6540   --
6541 
6542   current_calling_sequence := 'Purge_Vendors<-'||P_Calling_Sequence;
6543 
6544   --
6545 
6546   debug_info := 'ap_suppliers';
6547   IF g_debug_switch in ('y','Y') THEN
6548      Print('(Purge_Vendors)'||debug_info);
6549   END IF;
6550 
6551   -- delete_ap_suppliers
6552   delete from ap_suppliers vnd
6553   where exists
6554         (select null
6555 	 from po_purge_vendor_list pvl
6556 	 where pvl.vendor_id = vnd.vendor_id
6557 	 and   pvl.double_check_flag = 'Y');
6558 
6559 /* Bug 4602105: Commented out the call to etax preupgrade control packages
6560   -- Bug 3070584. Added the call to API for etax preupgrade control.
6561   FOR purge_vendors_rec IN c_purge_vendors
6562   LOOP
6563 
6564       ZX_UPGRADE_CONTROL_PKG.Sync_Suppliers
6565               (P_Dml_Type  => 'D',
6566                P_Vendor_ID => purge_vendors_rec.vendor_id);
6567 
6568   END LOOP;
6569 
6570   debug_info := 'ap_supplier_sites';
6571   IF g_debug_switch in ('y','Y') THEN
6572      Print('(Purge_Vendors)'||debug_info);
6573   END IF;
6574 
6575   -- Bug 3070584. Added the call to API for etax preupgrade control.
6576   FOR purge_sites_rec IN c_purge_vendor_sites
6577   LOOP
6578 
6579       ZX_UPGRADE_CONTROL_PKG.Sync_Supplier_Sites
6580               (P_Dml_Type       => 'D',
6581                P_Vendor_Site_ID => purge_sites_rec.vendor_site_id,
6582                P_Vendor_ID      => purge_sites_rec.vendor_id);
6583 
6584   END LOOP;
6585 */
6586 
6587 
6588   /* Added for bug#9645593 Start */
6589   DELETE
6590     FROM ap_supplier_contacts pc
6591    WHERE pc.org_party_site_id IN
6592          ( SELECT vnd.party_site_id
6593              FROM ap_supplier_sites_all vnd
6594                 , po_purge_vendor_list pvl
6595 	   WHERE pvl.vendor_id = vnd.vendor_id
6596              AND pvl.double_check_flag = 'Y'
6597          );
6598   /* Commented for bug#9645593 End */
6599 
6600   -- delete_ap_supplier_sites
6601   delete from ap_supplier_sites_all vnd
6602   where exists
6603         (select null
6604 	 from po_purge_vendor_list pvl
6605 	 where pvl.vendor_id = vnd.vendor_id
6606 	 and   pvl.double_check_flag = 'Y');
6607 
6608   debug_info := 'ap_supplier_contacts';
6609   IF g_debug_switch in ('y','Y') THEN
6610      Print('(Purge_Vendors)'||debug_info);
6611   END IF;
6612 
6613   /* Commented for bug#9645593 Start
6614   Moved the below code before deleting the supplier site
6615   -- delete_ap_supplier_contacts
6616   delete from ap_supplier_contacts pc
6617   where not exists
6618             (select null
6619 	     from ap_supplier_sites_all ps
6620 	     where ps.vendor_site_id = pc.vendor_site_id);
6621   Commented for bug#9645593 End */
6622 
6623   -- bug 5008627. ap_bank_account_uses is obsolete
6624  /*
6625   debug_info := 'ap_bank_account_uses_all';
6626   IF g_debug_switch in ('y','Y') THEN
6627      Print('(Purge_Vendors)'||debug_info);
6628   END IF;
6629 
6630   delete from ap_bank_account_uses_all abau
6631   where exists
6632         (select null
6633 	 from po_purge_vendor_list pvl
6634 	 where pvl.vendor_id = abau.vendor_id
6635 	 and   pvl.double_check_flag = 'Y');
6636   */
6637   COMMIT;
6638 
6639   IF g_purchasing_status = 'Y' THEN
6640 
6641       debug_info := 'po_vendor_list_entries';
6642       IF g_debug_switch in ('y','Y') THEN
6643          Print('(Purge_Vendors)'||debug_info);
6644       END IF;
6645 
6646       delete from po_vendor_list_entries pvle
6647       where not exists
6648             (select null
6649 	     from ap_suppliers vnd
6650 	     where vnd.vendor_id = pvle.vendor_id);
6651 
6652       debug_info := 'po_vendor_list_headers';
6653       IF g_debug_switch in ('y','Y') THEN
6654          Print('(Purge_Vendors)'||debug_info);
6655       END IF;
6656 
6657       delete from po_vendor_list_headers h
6658       where not exists
6659             (select null
6660 	     from po_vendor_list_entries e
6661 	     where e.vendor_list_header_id =
6662                    h.vendor_list_header_id);
6663 
6664       debug_info := 'po_asl_attributes';
6665       IF g_debug_switch in ('y','Y') THEN
6666          Print('(Purge_Vendors)'||debug_info);
6667       END IF;
6668 
6669       -- delete po_asl_docments
6670 
6671       delete from po_asl_documents pad where
6672       exists (select null from po_asl_attributes paa,
6673                           po_purge_vendor_list pvl
6674 	 where pvl.vendor_id = paa.vendor_id
6675 	 and   pvl.double_check_flag = 'Y'
6676          and   paa.using_organization_id = pad.using_organization_id
6677          and   paa.asl_id = pad.asl_id);
6678 
6679       -- delete_po_asl_attributes
6680 
6681       delete from po_asl_attributes paa
6682       where exists
6683         (select null
6684 	 from po_purge_vendor_list pvl
6685 	 where pvl.vendor_id = paa.vendor_id
6686 	 and   pvl.double_check_flag = 'Y');
6687 
6688       debug_info := 'po_approved_supplier_list';
6689       IF g_debug_switch in ('y','Y') THEN
6690          Print('(Purge_Vendors)'||debug_info);
6691       END IF;
6692 
6693       -- delete_po_approved_supplier_list
6694 
6695       delete from po_approved_supplier_list pasl
6696       where exists
6697         (select null
6698 	 from po_purge_vendor_list pvl
6699 	 where pvl.vendor_id = pasl.vendor_id
6700 	 and   pvl.double_check_flag = 'Y');
6701 
6702 
6703       COMMIT;
6704   END IF;
6705 
6706   -- Bug 3603357. Added POS API call to handle purge
6707   debug_info := 'Call to POS_SUP_PROF_PRG_GRP.handle_purge';
6708   IF g_debug_switch in ('y','Y') THEN
6709      Print('(Purge_Vendors)'||debug_info);
6710   END IF;
6711 
6712   l_pos_dynamic_call :=
6713      'BEGIN
6714          POS_SUP_PROF_PRG_GRP.handle_purge (:l_return_status);
6715       END;';
6716 
6717   BEGIN
6718       EXECUTE IMMEDIATE l_pos_dynamic_call
6719       USING  OUT      l_po_return_status;
6720 
6721   debug_info := 'After call to POS handle_purge';
6722   IF g_debug_switch in ('y','Y') THEN
6723      Print('(Purge_Vendors)');
6724   END IF;
6725 
6726   EXCEPTION
6727   WHEN OTHERS THEN
6728        IF (SQLCODE = -6550) THEN
6729            debug_info := 'Ignore exception from POS call. SQLERRM: '|| SQLERRM;
6730            IF g_debug_switch in ('y','Y') THEN
6731               Print('(Purge_Vendors)'||debug_info);
6732            END IF;
6733        ELSE
6734            RAISE;
6735        END IF;
6736   END;
6737 
6738 
6739   IF g_mrp_status = 'Y' THEN
6740       update mrp_sourcing_rules msr
6741       set planning_active = 2
6742       where exists (select null
6743                     from po_purge_vendor_list pvl,
6744                     mrp_sr_source_org msso,
6745                     mrp_sr_receipt_org msro
6746                     where pvl.vendor_id = msso.vendor_id
6747                     and msso.sr_receipt_id = msro.sr_receipt_id
6748                     and msro.sourcing_rule_id = msr.sourcing_rule_id
6749                     and   pvl.double_check_flag = 'Y');
6750 
6751      update mrp_recommendations mr
6752      set source_vendor_id = null, source_vendor_site_id = null
6753      where exists (select null
6754                    from po_purge_vendor_list pvl
6755                    where pvl.vendor_id = mr.source_vendor_id
6756                    and   pvl.double_check_flag = 'Y');
6757 
6758      delete from mrp_sr_source_org msso
6759      where exists (select null
6760                    from po_purge_vendor_list pvl
6761                    where pvl.vendor_id = msso.vendor_id
6762                    and   pvl.double_check_flag = 'Y');
6763 
6764      delete from mrp_item_sourcing mis
6765      where exists (select null
6766                    from po_purge_vendor_list pvl
6767                    where pvl.vendor_id = mis.vendor_id
6768                    and   pvl.double_check_flag = 'Y');
6769 
6770      COMMIT;
6771   END IF;
6772 
6773   debug_info := 'End Purge_Vendors';
6774   IF g_debug_switch in ('y','Y') THEN
6775      Print('(Purge_Vendors)'||debug_info);
6776   END IF;
6777   RETURN(TRUE);
6778 
6779 RETURN NULL; EXCEPTION
6780   WHEN OTHERS THEN
6781     IF (SQLCODE < 0 ) then
6782        Print(SQLERRM);
6783     END IF;
6784     RETURN (FALSE);
6785 END Purge_vendors;
6786 
6787 
6788 /*==========================================================================
6789   Function: Delete_Seeded_Data
6790 
6791  *==========================================================================*/
6792 FUNCTION Delete_Seeded_Data
6793 	 (P_Purge_Name          IN  VARCHAR2,
6794           P_Category            IN  VARCHAR2,
6795           P_activity_Date       IN  DATE,
6796           P_Range_Size          IN  NUMBER,
6797           P_Purchasing_Status   IN  VARCHAR2,
6798           P_MRP_Status          IN  VARCHAR2,
6799           P_Debug_Switch        IN  VARCHAR2,
6800           P_Calling_Sequence    IN  VARCHAR2)
6801 RETURN BOOLEAN IS
6802 
6803 debug_info                   	VARCHAR2(200);
6804 current_calling_sequence     	VARCHAR2(2000);
6805 check_rows                      NUMBER;
6806 invoice_payment_rows            NUMBER;
6807 invoice_rows                    NUMBER;
6808 po_header_rows                  NUMBER;
6809 shipment_line_rows              NUMBER;
6810 req_header_rows                 NUMBER;
6811 vendor_rows                     NUMBER;
6812 po_asl_rows			NUMBER;
6813 po_asl_attr_rows		NUMBER;
6814 po_asl_doc_rows			NUMBER;
6815 chv_auth_rows			NUMBER;
6816 chv_cum_adj_rows		NUMBER;
6817 chv_cum_rows			NUMBER;
6818 chv_hor_rows			NUMBER;
6819 chv_ord_rows			NUMBER;
6820 chv_head_rows			NUMBER;
6821 chv_item_rows			NUMBER;
6822 ae_line_rows			NUMBER;
6823 ae_header_rows			NUMBER;
6824 accounting_event_rows		NUMBER;
6825 chrg_allocation_rows            NUMBER;
6826 payment_history_rows            NUMBER;
6827 encumbrance_line_rows           NUMBER;
6828 rcv_subledger_detail_rows       NUMBER;
6829 
6830 
6831 l_status                        VARCHAR2(30);
6832 l_po_return_status              VARCHAR2(1);
6833 l_po_msg                        VARCHAR2(2000);
6834 l_purge_without_review          VARCHAR2(10);
6835 l_success                       BOOLEAN ; -- Bug 9268290
6836 l_sql_stmt                      LONG; -- 9481539
6837 BEGIN
6838 
6839   -- Update the calling sequence
6840   --
6841 
6842   g_debug_switch := p_debug_switch;
6843   g_activity_date := p_activity_date;
6844   g_range_size := p_range_size;
6845   g_purchasing_status := p_purchasing_status;
6846   g_mrp_status := p_mrp_status;
6847 
6848 
6849   current_calling_sequence := 'Delete_Seeded_Data<-'||P_Calling_Sequence;
6850 
6851   --
6852 
6853   debug_info := 'Starting Delete_Seeded_Data';
6854   IF g_debug_switch in ('y','Y') THEN
6855      Print('(Delete_Seeded_Data)'||debug_info);
6856   END IF;
6857 
6858   l_purge_without_review := NVL( FND_PROFILE.VALUE( 'AP_PURGE_WITHOUT_REVIEW' ), 'N' );
6859 
6860   debug_info := 'Purge Without Review : ' || l_purge_without_review ;
6861   IF g_debug_switch in ('y','Y') THEN
6862      Print('(Delete_Seeded_Data)'||debug_info);
6863   END IF;
6864 
6865   IF p_category = 'SIMPLE INVOICES' then
6866 -- Bug 8913560
6867      /* Bug 9268290
6868      IF l_purge_without_review = 'Y' THEN
6869         SELECT count(*)
6870         INTO   ae_line_rows
6871         FROM   ap_ae_lines;
6872 
6873         SELECT count(*)
6874         INTO   ae_header_rows
6875         FROM   ap_ae_headers;
6876 
6877         SELECT count(*)
6878         INTO   accounting_event_rows
6879         FROM   ap_accounting_events;
6880 
6881         if (count_ap_rows(check_rows,
6882                           invoice_payment_rows,
6883                           invoice_rows,
6884                           'Confirm_Seeded_Data') <> TRUE) then
6885            Print('count_ap_row failed.' );
6886            return(FALSE);
6887         end if;
6888 
6889 	UPDATE financials_purges
6890         SET
6891         ap_checks                = check_rows,
6892         ap_invoice_payments      = invoice_payment_rows,
6893         ap_invoices              = invoice_rows,
6894         ap_ae_lines		 = ae_line_rows,
6895         ap_ae_headers		 = ae_header_rows,
6896         ap_accounting_events 	 = accounting_event_rows
6897         WHERE purge_name = p_purge_name;
6898 
6899 	COMMIT ;
6900      ELSE  */
6901      IF l_purge_without_review <> 'Y' THEN
6902         SELECT NVL( ap_checks, 0 )           ,
6903 	       NVL( ap_invoice_payments, 0 ) ,
6904                NVL( ap_invoices, 0 )         ,
6905                NVL( ap_ae_lines, 0 )         ,
6906                NVL( ap_ae_headers, 0 )       ,
6907                NVL( ap_accounting_events, 0 )
6908 	INTO   check_rows,
6909 	       invoice_payment_rows,
6910 	       invoice_rows,
6911 	       ae_line_rows,
6912 	       ae_header_rows,
6913 	       accounting_event_rows
6914         FROM   financials_purges
6915 	WHERE  purge_name = p_purge_name;
6916      END IF ;
6917 
6918      debug_info := 'Submitting Multiple Requests';
6919      IF g_debug_switch in ('y','Y') THEN
6920         Print('(Delete_Seeded_Data)'||debug_info);
6921      END IF;
6922 
6923      AP_PURGE_PKG.Submit_Multiple_Requests( p_purge_name, l_success ); -- Bug 9268290
6924 
6925      IF NOT l_success THEN -- Bug 9268290
6926        Print('Submit_Multiple_Requests failed!');
6927        RETURN(FALSE);
6928      END IF ;
6929 
6930      debug_info := 'Control returned from Multiple Requests';
6931      IF g_debug_switch in ('y','Y') THEN
6932         Print('(Delete_Seeded_Data)'||debug_info);
6933      END IF;
6934    /* Bug 8913560
6935     -- delete_ap_tables
6936 
6937      if (delete_ap_tables('Delete_Seeded_Data') <> TRUE) then
6938         Print('delete_ap_tables failed!');
6939         RETURN(FALSE);
6940      end if;
6941 
6942      -- count_ap_rows
6943      if (count_ap_rows(check_rows,
6944                        invoice_payment_rows,
6945                        invoice_rows,
6946                        'Confirm_Seeded_Data') <> TRUE) then
6947         Print('count_ap_row failed.' );
6948         return(FALSE);
6949      end if;
6950 
6951    -- purge_accounting
6952    if (purge_accounting('Delete_Seeded_Data') <> TRUE) then
6953         Print('purge_accounting failed!');
6954         RETURN(FALSE);
6955    end if;
6956 
6957    -- count_accounting_rows
6958 
6959    if (count_accounting_rows(ae_line_rows,
6960                              ae_header_rows,
6961                              accounting_event_rows,
6962                              chrg_allocation_rows,
6963                              payment_history_rows,
6964                              encumbrance_line_rows,
6965                              rcv_subledger_detail_rows,
6966                              'Confirm_Seeded_Data') <> TRUE) then
6967        Print('count_accounting_rows failed.' );
6968        return(FALSE);
6969    end if; */
6970 
6971   ELSIF p_category IN ('SIMPLE REQUISITIONS',
6972                        'SIMPLE POS') then
6973 
6974      PO_AP_PURGE_GRP.delete_records
6975      ( p_api_version => 1.0,
6976        p_init_msg_list => 'T',
6977        p_commit => 'T',
6978        x_return_status => l_po_return_status,
6979        x_msg_data => l_po_msg,
6980        p_purge_name => p_purge_name,
6981        p_purge_category => p_category,
6982        p_range_size => p_range_size);
6983 
6984      IF (l_po_return_status <> 'S') THEN
6985          Print(l_po_msg);
6986          RETURN(FALSE);
6987      END IF;
6988 
6989      PO_AP_PURGE_GRP.count_po_rows
6990      ( p_api_version => 1.0,
6991        p_init_msg_list => 'T',
6992        x_return_status => l_po_return_status,
6993        x_msg_data => l_po_msg,
6994        x_po_hdr_count => po_header_rows,
6995        x_rcv_line_count => shipment_line_rows,
6996        x_req_hdr_count => req_header_rows,
6997        x_vendor_count => vendor_rows,
6998        x_asl_count => po_asl_rows,
6999        x_asl_attr_count => po_asl_attr_rows,
7000        x_asl_doc_count => po_asl_doc_rows
7001      );
7002 
7003      IF (l_po_return_status <> 'S') THEN
7004         Print(l_po_msg);
7005         RETURN FALSE;
7006      END IF;
7007 
7008   ELSIF p_category = 'MATCHED POS AND INVOICES' then
7009 
7010   /* Bug 8913560
7011    -- delete_ap_tables
7012    if (delete_ap_tables('Delete_Seeded_Data') <> TRUE) then
7013         Print('delete_ap_tables failed!');
7014         RETURN(FALSE);
7015    end if;
7016    */
7017    -- Bug 8913560 Start
7018    SELECT NVL( ap_checks, 0 )           ,
7019           NVL( ap_invoice_payments, 0 ) ,
7020           NVL( ap_invoices, 0 )         ,
7021           NVL( ap_ae_lines, 0 )         ,
7022           NVL( ap_ae_headers, 0 )       ,
7023           NVL( ap_accounting_events, 0 )
7024    INTO   check_rows,
7025           invoice_payment_rows,
7026           invoice_rows,
7027           ae_line_rows,
7028           ae_header_rows,
7029           accounting_event_rows
7030    FROM   financials_purges
7031    WHERE  purge_name = p_purge_name;
7032 
7033    debug_info := 'Submitting Multiple Requests';
7034    IF g_debug_switch in ('y','Y') THEN
7035       Print('(Delete_Seeded_Data)'||debug_info);
7036    END IF;
7037 
7038    AP_PURGE_PKG.Submit_Multiple_Requests( p_purge_name, l_success ); -- Bug 9268290
7039 
7040    IF NOT l_success THEN  -- Bug 9268290
7041      Print('Submit_Multiple_Requests failed!');
7042      RETURN(FALSE);
7043    END IF ;
7044 
7045    debug_info := 'Control returned from Multiple Requests';
7046    IF g_debug_switch in ('y','Y') THEN
7047       Print('(Delete_Seeded_Data)'||debug_info);
7048    END IF;
7049    -- Bug 8913560 End
7050 
7051    PO_AP_PURGE_GRP.delete_records
7052      ( p_api_version => 1.0,
7053        p_init_msg_list => 'T',
7054        p_commit => 'T',
7055        x_return_status => l_po_return_status,
7056        x_msg_data => l_po_msg,
7057        p_purge_name => p_purge_name,
7058        p_purge_category => p_category,
7059        p_range_size => p_range_size);
7060 
7061      IF (l_po_return_status <> 'S') THEN
7062          Print(l_po_msg);
7063          RETURN(FALSE);
7064      END IF;
7065    /* Bug 8913560
7066    if (count_ap_rows(check_rows,
7067                      invoice_payment_rows,
7068                      invoice_rows,
7069                      'Confirm_Seeded_Data') <> TRUE) then
7070       Print('count_ap_row failed.' );
7071       return(FALSE);
7072    end if;
7073 
7074    -- purge_accounting
7075    if (purge_accounting('Delete_Seeded_Data') <> TRUE) then
7076         Print('purge_accounting failed!');
7077         RETURN(FALSE);
7078    end if;
7079 
7080   -- count_accounting_rows
7081    if (count_accounting_rows(ae_line_rows,
7082                              ae_header_rows,
7083                              accounting_event_rows,
7084                              chrg_allocation_rows,
7085                              payment_history_rows,
7086                              encumbrance_line_rows,
7087                              rcv_subledger_detail_rows,
7088                              'Confirm_Seeded_Data') <> TRUE) then
7089       Print('count_accounting_rows failed.' );
7090       return(FALSE);
7091    end if; */
7092 
7093 
7094     PO_AP_PURGE_GRP.count_po_rows
7095      ( p_api_version => 1.0,
7096        p_init_msg_list => 'T',
7097        x_return_status => l_po_return_status,
7098        x_msg_data => l_po_msg,
7099        x_po_hdr_count => po_header_rows,
7100        x_rcv_line_count => shipment_line_rows,
7101        x_req_hdr_count => req_header_rows,
7102        x_vendor_count => vendor_rows,
7103        x_asl_count => po_asl_rows,
7104        x_asl_attr_count => po_asl_attr_rows,
7105        x_asl_doc_count => po_asl_doc_rows
7106      );
7107 
7108    IF (l_po_return_status <> 'S') THEN
7109       Print(l_po_msg);
7110       RETURN FALSE;
7111    END IF;
7112 
7113   ELSIF p_category = 'VENDORS' then
7114 
7115    -- purge_vendors
7116    if (purge_vendors('Delete_Seeded_Data') <> TRUE) then
7117         Print('purge_vendors failed!');
7118         RETURN(FALSE);
7119    end if;
7120 
7121 
7122     PO_AP_PURGE_GRP.count_po_rows
7123      ( p_api_version => 1.0,
7124        p_init_msg_list => 'T',
7125        x_return_status => l_po_return_status,
7126        x_msg_data => l_po_msg,
7127        x_po_hdr_count => po_header_rows,
7128        x_rcv_line_count => shipment_line_rows,
7129        x_req_hdr_count => req_header_rows,
7130        x_vendor_count => vendor_rows,
7131        x_asl_count => po_asl_rows,
7132        x_asl_attr_count => po_asl_attr_rows,
7133        x_asl_doc_count => po_asl_doc_rows
7134      );
7135 
7136    IF (l_po_return_status <> 'S') THEN
7137       Print(l_po_msg);
7138       RETURN FALSE;
7139    END IF;
7140 
7141   ELSIF p_category = 'SCHEDULES BY ORGANIZATION' then
7142 
7143    -- purge_schedules
7144 
7145    if (purge_schedules_by_org('Delete_Seeded_Data') <> TRUE) then
7146         Print('purge_schedules_by_org failed!');
7147         RETURN(FALSE);
7148    end if;
7149 
7150    -- count_chv_rows
7151    if (count_chv_rows(chv_auth_rows,
7152                       chv_cum_adj_rows,
7153                       chv_cum_rows,
7154                       chv_hor_rows,
7155                       chv_ord_rows,
7156                       chv_head_rows,
7157                       chv_item_rows,
7158 		      'Delete Seeded Data')
7159         <> TRUE) then
7160         Print('purge_schedules_by_org failed!');
7161         RETURN(FALSE);
7162    end if;
7163 
7164   ELSIF p_category = 'SCHEDULES BY CUM PERIODS' then
7165 
7166   -- purge schedules
7167 
7168   if (purge_schedules_by_cum('Delete_Seeded_Data') <> TRUE) then
7169        Print('purge_schedules_by_cum failed!');
7170        RETURN(FALSE);
7171   end if;
7172 
7173 
7174    -- count_chv_rows
7175    if (count_chv_rows(chv_auth_rows,
7176                       chv_cum_adj_rows,
7177                       chv_cum_rows,
7178                       chv_hor_rows,
7179                       chv_ord_rows,
7180                       chv_head_rows,
7181                       chv_item_rows,
7182 		      'Delete Seeded Data')
7183         <> TRUE) then
7184         Print('purge_schedules_by_cum failed!');
7185         RETURN(FALSE);
7186    end if;
7187   END IF;
7188 
7189   IF ( l_purge_without_review <> 'Y' OR     -- Bug 9268290
7190        p_category <> 'SIMPLE INVOICES'  ) THEN
7191   -- record_final_statistics
7192   	UPDATE financials_purges
7193   	SET
7194   	ap_checks              = nvl(ap_checks, 0) - check_rows,
7195   	ap_invoice_payments    = nvl(ap_invoice_payments, 0) - invoice_payment_rows,
7196   	ap_invoices            = nvl(ap_invoices, 0) - invoice_rows,
7197  	po_headers             = nvl(po_headers, 0) - po_header_rows,
7198   	po_requisition_headers = nvl(po_requisition_headers, 0) - req_header_rows,
7199   	po_vendors             = nvl(po_vendors, 0) - vendor_rows,
7200   	po_receipts            = nvl(po_receipts, 0) - shipment_line_rows,
7201   	po_approved_supplier_list = nvl(po_approved_supplier_list,0) - po_asl_rows,
7202   	po_asl_attributes      = nvl(po_asl_attributes,0) - po_asl_attr_rows,
7203   	po_asl_documents       = nvl(po_asl_documents,0) - po_asl_doc_rows,
7204   	chv_authorizations     = nvl(chv_authorizations,0) - chv_auth_rows,
7205   	chv_cum_adjustments    = nvl(chv_cum_adjustments,0) - chv_cum_adj_rows,
7206   	chv_cum_periods	 = nvl(chv_cum_periods,0) - chv_cum_rows,
7207   	chv_horizontal_Schedules = nvl(chv_horizontal_schedules,0) - chv_hor_rows,
7208   	chv_item_orders        = nvl(chv_item_orders,0) - chv_ord_rows,
7209   	chv_schedule_headers   = nvl(chv_schedule_headers,0) - chv_head_rows,
7210  	chv_schedule_items     = nvl(chv_schedule_items,0) - chv_item_rows,
7211   	ap_ae_lines		 = nvl(ap_ae_lines,0) - ae_line_rows,
7212  	ap_ae_headers		 = nvl(ap_ae_headers,0) - ae_header_rows,
7213   	ap_accounting_events 	 = nvl(ap_accounting_events,0) - accounting_event_rows
7214   	WHERE purge_name = p_purge_name;
7215   END IF ;
7216   -- reset_row_counts
7217   check_rows 	       := 0;
7218   invoice_payment_rows := 0;
7219   invoice_rows	       := 0;
7220   req_header_rows      := 0;
7221   po_header_rows       := 0;
7222   vendor_rows          := 0;
7223   shipment_line_rows   := 0;
7224   po_asl_rows	       := 0;
7225   po_asl_attr_rows     := 0;
7226   po_asl_doc_rows      := 0;
7227   chv_auth_rows	       := 0;
7228   chv_cum_adj_rows     := 0;
7229   chv_cum_rows	       := 0;
7230   chv_hor_rows	       := 0;
7231   chv_ord_rows         := 0;
7232   chv_head_rows	       := 0;
7233   chv_item_rows        := 0;
7234   ae_line_rows 	       := 0;
7235   ae_header_rows       := 0;
7236   accounting_event_rows:= 0;
7237 
7238    -- delete_batches
7239   --9481539
7240   DELETE FROM ap_batches B
7241   WHERE B.last_update_date <= g_activity_date
7242   AND NOT EXISTS (
7243           SELECT null
7244           FROM ap_invoices_all I --bug13799066
7245           WHERE I.batch_id = B.batch_id);
7246 
7247   -- clear_invoice_purge_list
7248   -- 9481539
7249   /*  delete from ap_purge_invoice_list; */
7250    BEGIN
7251      l_sql_stmt :='T'||'RUNCATE '||'TABLE a'||'p.ap_purge_invoice_list';
7252      EXECUTE IMMEDIATE l_sql_stmt;
7253    EXCEPTION
7254      WHEN OTHERS THEN
7255       Print('purge of ap_purge_invoice_list failed!'||sqlerrm);
7256    END;
7257 
7258   PO_AP_PURGE_GRP.delete_purge_lists
7259   (  p_api_version => 1.0,
7260      p_init_msg_list => 'T',
7261      p_commit => 'F',
7262      x_return_status => l_po_return_status,
7263      x_msg_data => l_po_msg,
7264      p_purge_name => p_purge_name);
7265 
7266   -- clear_vendor_purge_list
7267   delete from po_purge_vendor_list;
7268 
7269   -- clear_schedule_list
7270   delete from chv_purge_schedule_list;
7271 
7272   -- clear_cum_list
7273   delete from chv_purge_cum_list;
7274 
7275   l_status := 'COMPLETED-PURGED';
7276 
7277   -- set_purge_status
7278   if (set_purge_status(l_status,
7279                        p_purge_name,
7280                        p_debug_switch,
7281                        'Delete_Seeded_Data')
7282          <> TRUE) then
7283         Print('set_purge_status failed!');
7284         RETURN(FALSE);
7285   end if;
7286   COMMIT;
7287   RETURN(TRUE);
7288 
7289 RETURN NULL; EXCEPTION
7290   WHEN OTHERS THEN
7291     IF (SQLCODE < 0 ) then
7292        Print(SQLERRM);
7293     END IF;
7294     RETURN (FALSE);
7295 
7296 END Delete_Seeded_Data;
7297 
7298 
7299 /*==========================================================================
7300   Function: clear_check_history
7301 
7302  *==========================================================================*/
7303 FUNCTION  clear_check_history RETURN BOOLEAN IS
7304 
7305 BEGIN
7306 
7307  delete from ap_history_checks
7308  where purge_name = g_purge_name;
7309 
7310  RETURN (TRUE);
7311 
7312 RETURN NULL; EXCEPTION
7313 
7314   WHEN   OTHERS  THEN
7315     RETURN (FALSE);
7316 
7317 END;
7318 
7319 
7320 /*==========================================================================
7321   Function: CLEAR_CHV_CUM_HISTORY
7322 
7323  *==========================================================================*/
7324 FUNCTION CLEAR_CHV_CUM_HISTORY RETURN BOOLEAN IS
7325 BEGIN
7326   delete from chv_history_schedules
7327   where purge_name = g_purge_name;
7328 
7329   delete from chv_history_cum_periods
7330   where purge_name = g_purge_name;
7331 
7332   RETURN (TRUE);
7333 
7334 RETURN NULL; EXCEPTION
7335 
7336   WHEN   OTHERS  THEN
7337     RETURN (FALSE);
7338 
7339 END;
7340 
7341 
7342 /*==========================================================================
7343   Function: CLEAR_CHV_CUM_LIST
7344 
7345  *==========================================================================*/
7346 FUNCTION CLEAR_CHV_CUM_LIST RETURN BOOLEAN IS
7347 BEGIN
7348 
7349   delete from chv_purge_schedule_list;
7350   delete from chv_purge_cum_list;
7351 
7352   RETURN (TRUE);
7353 
7354 RETURN NULL; EXCEPTION
7355 
7356   WHEN   OTHERS  THEN
7357     RETURN (FALSE);
7358 
7359 END;
7360 
7361 
7362 /*==========================================================================
7363   Function: CLEAR_CHV_SCHED_HISTORY
7364 
7365  *==========================================================================*/
7366 FUNCTION CLEAR_CHV_SCHED_HISTORY RETURN BOOLEAN IS
7367 BEGIN
7368 
7369   delete from chv_history_schedules
7370   where purge_name = g_purge_name;
7371 
7372   RETURN (TRUE);
7373 
7374 RETURN NULL; EXCEPTION
7375 
7376   WHEN   OTHERS  THEN
7377     RETURN (FALSE);
7378 
7379 END;
7380 
7381 
7382 /*==========================================================================
7383   Function: clear_chv_sched_list
7384 
7385  *==========================================================================*/
7386 FUNCTION  clear_chv_sched_list RETURN BOOLEAN IS
7387 
7388 BEGIN
7389 
7390   delete from chv_purge_schedule_list;
7391 
7392   RETURN (TRUE);
7393 
7394 RETURN NULL; EXCEPTION
7395 
7396   WHEN   OTHERS  THEN
7397     RETURN (FALSE);
7398 
7399 END;
7400 
7401 
7402 /*==========================================================================
7403   Function: clear_invoice_history
7404 
7405  *==========================================================================*/
7406 FUNCTION  clear_invoice_history RETURN BOOLEAN IS
7407 
7408 BEGIN
7409 
7410   delete from ap_history_invoices
7411   where purge_name = g_purge_name;
7412 
7413   RETURN (TRUE);
7414 
7415 RETURN NULL; EXCEPTION
7416 
7417   WHEN   OTHERS  THEN
7418     RETURN (FALSE);
7419 
7420 END;
7421 
7422 
7423 /*==========================================================================
7424   Function: clear_invoice_purge_list
7425 
7426  *==========================================================================*/
7427 FUNCTION  clear_invoice_purge_list RETURN BOOLEAN IS
7428 
7429 BEGIN
7430 
7431   delete from ap_purge_invoice_list;
7432 
7433   RETURN (TRUE);
7434 
7435 RETURN NULL; EXCEPTION
7436 
7437   WHEN   OTHERS  THEN
7438     RETURN (FALSE);
7439 
7440 END;
7441 
7442 
7443 /*==========================================================================
7444   Function: clear_payment_history
7445 
7446  *==========================================================================*/
7447 FUNCTION  clear_payment_history RETURN BOOLEAN IS
7448 
7449 BEGIN
7450 
7451   delete from ap_history_invoice_payments ahp
7452   where not exists (select null
7453                   from ap_history_invoices ahi
7454                   where ahi.invoice_id = ahp.invoice_id);
7455 
7456   RETURN (TRUE);
7457 
7458 RETURN NULL; EXCEPTION
7459 
7460   WHEN   OTHERS  THEN
7461     RETURN (FALSE);
7462 
7463 END;
7464 
7465 
7466 /*==========================================================================
7467   Function: clear_vendor_history
7468 
7469  *==========================================================================*/
7470 FUNCTION  clear_vendor_history RETURN BOOLEAN IS
7471 
7472 BEGIN
7473 
7474   delete from po_history_vendors
7475   where purge_name = g_purge_name;
7476 
7477   RETURN (TRUE);
7478 
7479 RETURN NULL; EXCEPTION
7480 
7481   WHEN   OTHERS  THEN
7482     RETURN (FALSE);
7483 
7484 END;
7485 
7486 
7487 /*==========================================================================
7488   Function: clear_vendor_purge_list
7489 
7490  *==========================================================================*/
7491 FUNCTION  clear_vendor_purge_list RETURN BOOLEAN IS
7492 
7493 BEGIN
7494 
7495   delete from po_purge_vendor_list;
7496 
7497   RETURN (TRUE);
7498 
7499 RETURN NULL; EXCEPTION
7500 
7501   WHEN   OTHERS  THEN
7502     RETURN (FALSE);
7503 
7504 END;
7505 
7506 
7507 /*==========================================================================
7508   Function: Abort_Purge
7509 
7510  *==========================================================================*/
7511 FUNCTION Abort_Purge
7512          (P_Purge_Name          IN  VARCHAR2,
7513           P_Original_Status     IN  VARCHAR2,
7514           P_Debug_Switch        IN  VARCHAR2,
7515           P_Calling_Sequence    IN  VARCHAR2)
7516 RETURN BOOLEAN IS
7517 
7518 debug_info                      VARCHAR2(200);
7519 current_calling_sequence        VARCHAR2(2000);
7520 
7521 l_status                        VARCHAR2(30);
7522 l_po_return_status              VARCHAR2(1);
7523 l_po_msg                        VARCHAR2(2000);
7524 
7525 BEGIN
7526 
7527    -- Update the calling sequence
7528    --
7529 
7530    current_calling_sequence := 'Abort_Purge<-'||P_Calling_Sequence;
7531 
7532    g_debug_switch := p_debug_switch;
7533    g_purge_name := p_purge_name;
7534 
7535    --
7536    debug_info := 'Starting Abort_Purge';
7537    IF g_debug_switch in ('y','Y') THEN
7538       Print('(Abort_Purge)'||debug_info);
7539    END IF;
7540 
7541 
7542    IF(clear_invoice_purge_list <> TRUE) THEN
7543      RETURN (FALSE);
7544    END IF;
7545    COMMIT;
7546 
7547    IF g_debug_switch in ('y','Y') THEN
7548       Print('(Abort_Purge)'||debug_info);
7549    END IF;
7550 
7551    PO_AP_PURGE_GRP.delete_purge_lists
7552    (  p_api_version => 1.0,
7553       p_init_msg_list => 'T',
7554       p_commit => 'T',
7555       x_return_status => l_po_return_status,
7556       x_msg_data => l_po_msg,
7557       p_purge_name => p_purge_name);
7558 
7559    IF (l_po_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
7560      RETURN (FALSE);
7561    END IF;
7562 
7563 
7564    IF(clear_vendor_purge_list <> TRUE) THEN
7565      RETURN (FALSE);
7566    END IF;
7567    COMMIT;
7568 
7569    IF g_debug_switch in ('y','Y') THEN
7570       Print('(Abort_Purge)'||debug_info);
7571    END IF;
7572 
7573    IF(clear_chv_sched_list <> TRUE) THEN
7574      RETURN (FALSE);
7575    END IF;
7576    COMMIT;
7577    IF g_debug_switch in ('y','Y') THEN
7578       Print('(Abort_Purge)'||debug_info);
7579    END IF;
7580 
7581 
7582    IF(clear_chv_cum_list <> TRUE) THEN
7583      RETURN (FALSE);
7584    END IF;
7585    COMMIT;
7586 
7587    IF g_debug_switch in ('y','Y') THEN
7588       Print('(Abort_Purge)'||debug_info);
7589    END IF;
7590 
7591    IF (p_original_status = 'SUMMARIZING' OR
7592        p_original_status = 'SUMMARIZED') THEN
7593 
7594      PO_AP_PURGE_GRP.delete_history_tables
7595      (  p_api_version => 1.0,
7596         p_init_msg_list => 'T',
7597         p_commit => 'T',
7598         x_return_status => l_po_return_status,
7599         x_msg_data => l_po_msg,
7600         p_purge_name => p_purge_name);
7601 
7602      IF (l_po_return_status <> FND_API.G_RET_STS_SUCCESS) THEN
7603        RETURN (FALSE);
7604      END IF;
7605 
7606      IF(clear_vendor_history <> TRUE) THEN
7607         RETURN (FALSE);
7608      END IF;
7609      COMMIT;
7610 
7611      IF g_debug_switch in ('y','Y') THEN
7612         Print('(Abort_Purge)'||debug_info);
7613      END IF;
7614 
7615      IF(clear_invoice_history <> TRUE) THEN
7616         RETURN (FALSE);
7617      END IF;
7618      COMMIT;
7619 
7620      IF g_debug_switch in ('y','Y') THEN
7621         Print('(Abort_Purge)'||debug_info);
7622      END IF;
7623 
7624      IF(clear_check_history <> TRUE) THEN
7625         RETURN (FALSE);
7626      END IF;
7627      COMMIT;
7628      IF g_debug_switch in ('y','Y') THEN
7629         Print('(Abort_Purge)'||debug_info);
7630      END IF;
7631 
7632      IF(clear_payment_history <> TRUE) THEN
7633         RETURN (FALSE);
7634      END IF;
7635      COMMIT;
7636      IF g_debug_switch in ('y','Y') THEN
7637         Print('(Abort_Purge)'||debug_info);
7638      END IF;
7639 
7640      IF(clear_chv_sched_history <> TRUE) THEN
7641         RETURN (FALSE);
7642      END IF;
7643      COMMIT;
7644      IF g_debug_switch in ('y','Y') THEN
7645         Print('(Abort_Purge)'||debug_info);
7646      END IF;
7647 
7648      IF(clear_chv_cum_history <> TRUE) THEN
7649         RETURN (FALSE);
7650      END IF;
7651      COMMIT;
7652      IF g_debug_switch in ('y','Y') THEN
7653         Print('(Abort_Purge)'||debug_info);
7654      END IF;
7655 
7656 
7657    END IF;
7658 
7659    l_status := 'COMPLETED-ABORTED';
7660    IF(set_purge_status(l_status,
7661                        p_purge_name,
7662                        p_debug_switch,
7663                        'Abort_Purge') <> TRUE) THEN
7664       RETURN (FALSE);
7665    END IF;
7666    COMMIT;
7667    IF g_debug_switch in ('y','Y') THEN
7668       Print('(Abort_Purge)'||debug_info);
7669    END IF;
7670    Print('ABORT process commenced');
7671 
7672   RETURN(TRUE);
7673 
7674 RETURN NULL; EXCEPTION
7675   WHEN OTHERS THEN
7676     IF (SQLCODE < 0 ) then
7677        Print(SQLERRM);
7678     END IF;
7679     RETURN (FALSE);
7680 
7681 END Abort_Purge;
7682 
7683 /*==========================================================================
7684   Bug  8913560
7685   Procedure :
7686 
7687   Purpose   : This is called for Delete_Seeded_Data() and in turn, it spawns
7688               multiple child requests to delete Payables and Accounting data
7689  *==========================================================================*/
7690 PROCEDURE Submit_Multiple_Requests ( p_purge_name IN         VARCHAR2 ,
7691                                      p_success    OUT NOCOPY BOOLEAN  ) IS  -- Bug 9268290
7692   l_debug_info                VARCHAR2(2000);
7693   TYPE WorkerList IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
7694   l_worker                    WorkerList;
7695   l_phase                     VARCHAR2(500) := NULL;
7696   l_req_status                VARCHAR2(500) := NULL;
7697   l_devphase                  VARCHAR2(500) := NULL;
7698   l_devstatus                 VARCHAR2(500) := NULL;
7699   l_message                   VARCHAR2(500) := NULL;
7700   l_child_notcomplete         BOOLEAN := TRUE;
7701   l_child_success             VARCHAR2(1);
7702   l_batch_size                NUMBER ;
7703   l_total_recs                NUMBER ;
7704   l_request_id                NUMBER;
7705   l_num_workers               NUMBER;
7706   l_child_failed              EXCEPTION;
7707   l_script_id                 NUMBER;
7708   l_script_name               VARCHAR2(50) ;
7709 BEGIN
7710 
7711   l_num_workers := NVL( FND_PROFILE.VALUE( 'AP_PURGE_WORKER_COUNT' ), 8 ) ;
7712   l_batch_size  := FND_PROFILE.VALUE( 'AP_PURGE_BATCH_SIZE' ) ;
7713   l_script_name := p_purge_name || to_char(SYSDATE, 'DDMMRRRRHH24MISS' ); -- Bug 9268290
7714   --9732780,limiting script name to 30 characters
7715 
7716   IF l_batch_size IS NULL THEN
7717     SELECT COUNT(0)
7718     INTO   l_total_recs
7719     FROM   ap_purge_invoice_list
7720     WHERE  double_check_flag = 'Y';
7721 
7722     l_batch_size := l_total_recs / ( 8 * l_num_workers ) ;
7723   END IF ;
7724 
7725   l_debug_info := 'Workers = ' || l_num_workers || ', Batch Size = ' || l_batch_size ;
7726   IF g_debug_switch in ('y','Y') THEN
7727      Print('(Submit_Multiple_Requests)'||l_debug_info);
7728   END IF;
7729 
7730   FOR i in 1..l_num_workers
7731   LOOP
7732     l_debug_info := 'Submitting concurrent request for worker ' || i;
7733     IF g_debug_switch in ('y','Y') THEN
7734        Print('(Submit_Multiple_Requests)'||l_debug_info);
7735     END IF;
7736 
7737     BEGIN
7738       l_worker(i) := FND_REQUEST.SUBMIT_REQUEST
7739                            ('SQLAP',
7740                             'APXP7PRL',
7741                             'Parallel Purge',
7742                             NULL,
7743                             FALSE,
7744                             l_batch_size,
7745                             i ,
7746                             l_num_workers,
7747 			    l_script_name,
7748 			    g_debug_switch,
7749 			    p_purge_name);
7750      --9481539
7751      --added p_purge_name and g_debug_switch to above function call
7752 
7753       -- This is the concurrent executable of the subworker.
7754       IF (l_worker(i) = 0) THEN  --9531253 replaced l_request_id with l_worker(i)
7755           rollback;
7756           l_debug_info := 'Error in Procedure: Submit_Multiple_Requests.' ||
7757                           'Message: '||fnd_message.get;
7758 	  IF g_debug_switch in ('y','Y') THEN
7759               Print('(Submit_Multiple_Requests)'||l_debug_info);
7760           END IF;
7761           p_success := FALSE ; -- Bug 9268290
7762 	  RETURN ; --Bug 9531253 to return control to calling proc
7763 	           --with out submission of concurrent requests
7764       END IF;
7765 
7766     EXCEPTION
7767       WHEN OTHERS THEN
7768         IF (SQLCODE < 0 ) then
7769            Print(SQLERRM);
7770         END IF;
7771     END ;
7772 
7773   END LOOP;
7774 
7775   COMMIT;
7776 
7777   WHILE l_child_notcomplete LOOP
7778 
7779      dbms_lock.sleep(100);
7780 
7781      l_child_notcomplete := FALSE;
7782 
7783      FOR i in 1..l_num_workers
7784      LOOP
7785 
7786        IF (FND_CONCURRENT.GET_REQUEST_STATUS
7787                                  (l_worker(i),
7788                                   NULL,
7789                                   NULL,
7790                                   l_phase,
7791                                   l_req_status,
7792                                   l_devphase,
7793                                   l_devstatus,
7794                                   l_message)) THEN
7795          NULL;
7796        END IF;
7797 
7798        IF l_devphase <> 'COMPLETE'  Then
7799           l_child_notcomplete := TRUE;
7800        END IF;
7801 
7802        IF l_devphase = 'COMPLETE' AND l_devstatus NOT IN ('NORMAL','WARNING') THEN
7803        	  IF g_debug_switch in ('y','Y') THEN
7804               Print('(Submit_Multiple_Requests)'||'Error ' || l_message || 'occurred in child ' || i ); -- Bug 9268290
7805           END IF;
7806           l_child_success := 'N';
7807        END IF;
7808 
7809      END LOOP;
7810   END LOOP;
7811 
7812   /* If any subworkers have failed then raise an error */
7813   IF l_child_success = 'N' THEN
7814      RAISE l_child_failed;
7815   END IF ;
7816 
7817   COMMIT;
7818   p_success := TRUE ;  -- Bug 9268290
7819 EXCEPTION
7820 
7821   WHEN L_CHILD_FAILED THEN
7822     l_debug_info := 'Error or Warning in one of the subworkers';
7823     Print('(Submit_Multiple_Requests)'||l_debug_info);
7824     p_success := FALSE ;    -- Bug 9268290
7825   WHEN OTHERS THEN
7826     IF (SQLCODE < 0 ) then
7827        Print(SQLERRM);
7828        p_success := FALSE ; -- Bug 9268290
7829     END IF;
7830 END  Submit_Multiple_Requests ;
7831 
7832 /*=========================================================================
7833   Bug  8913560
7834   Procedure : Purge_acctg_and_ap_table
7835   Purpose   : This is called from the child requests spawned by the procedure
7836               Submit_Multiple_Requests().
7837               It uses the AD Parallel architecture to divide the table
7838               AP_PURGE_INVOICE_LIST and uses the row_id range to call the
7839               purge_accounting() and delete_ap_tables() for deleting records
7840  *==========================================================================*/
7841 PROCEDURE Purge_acctg_and_ap_table
7842                (errbuf                  IN OUT NOCOPY VARCHAR2,
7843                 retcode                 IN OUT NOCOPY VARCHAR2,
7844 	        P_batch_size            IN            VARCHAR2,
7845                 P_Worker_Id             IN            NUMBER,
7846                 P_Num_Workers           IN            NUMBER,
7847 		P_Script_Name           IN            VARCHAR2,
7848 		P_Debug_Switch          IN            VARCHAR2 DEFAULT NULL,
7849 		p_purge_name            IN            VARCHAR2 DEFAULT NULL)
7850   IS
7851   l_debug_info                VARCHAR2(2000);
7852   l_table_owner               VARCHAR2(30) ; -- 13105127 - removed the hard coded schema name for gscc
7853   l_any_rows_to_process       BOOLEAN;
7854   l_table_name                VARCHAR2(30);
7855   l_id_column                 VARCHAR2(30);
7856   l_sql_stmt                  VARCHAR2(5000);
7857   l_start_rowid               rowid;
7858   l_end_rowid                 rowid;
7859   l_rows_processed            NUMBER;
7860   l_rows_to_process           NUMBER;
7861   l_restarted_ledgers         NUMBER;
7862   l_return_status             VARCHAR2(1);
7863   l_msg_count                 NUMBER;
7864   l_msg_data                  VARCHAR2(2000);
7865   l_ledger_id                 NUMBER;
7866   l_mode                      VARCHAR2(30) := 'UPDATE';
7867   l_final_count               NUMBER;
7868 
7869   -- 13105127 - gscc
7870   l_status                    VARCHAR2(30);
7871   l_industry                  VARCHAR2(30);
7872 
7873 BEGIN
7874 
7875   l_table_name := 'AP_PURGE_INVOICE_LIST';
7876   l_final_count := 0;
7877 
7878   --9481539 assigned the values to below global variables
7879   g_debug_switch := P_Debug_Switch ;
7880   g_purge_name := p_purge_name ;
7881 
7882 
7883   IF g_debug_switch in ('y','Y') THEN
7884     Print('(Purge_acctg_and_ap_table) Start for '|| p_worker_id );
7885   END IF ;
7886 
7887   -- 13105127 -- added below api to get the table owner
7888   IF (FND_INSTALLATION.GET_APP_INFO('SQLAP', l_status, l_industry, l_table_owner)) THEN
7889      NULL;
7890   END IF;
7891 
7892   ad_parallel_updates_pkg.initialize_rowid_range(
7893            ad_parallel_updates_pkg.ROWID_RANGE,
7894            l_table_owner,
7895            l_table_name,
7896            p_script_name,
7897            p_worker_id,
7898            p_num_workers,
7899            p_batch_size,
7900 	   0);
7901 
7902 
7903   ad_parallel_updates_pkg.get_rowid_range(
7904            l_start_rowid,
7905            l_end_rowid,
7906            l_any_rows_to_process,
7907            p_batch_size,
7908            TRUE);
7909 
7910   IF g_debug_switch in ('y','Y') THEN
7911     IF   l_any_rows_to_process THEN
7912        Print('(Purge_acctg_and_ap_table) Rows to process from ' || l_start_rowid || ' to ' || l_end_rowid );
7913     ELSE
7914        Print('(Purge_acctg_and_ap_table) No Rows to process' );
7915     END IF ;
7916   END IF ;
7917 
7918   WHILE (l_any_rows_to_process = TRUE) LOOP
7919 
7920 	 if (purge_accounting('Purge_acctg_and_ap_table', l_start_rowid, l_end_rowid, p_script_name ) <> TRUE) then
7921 	    Print('purge_accounting failed!');
7922 	    retcode := 2 ;
7923 	    RETURN ;
7924 	 end if;
7925 
7926          if (delete_ap_tables('Purge_acctg_and_ap_table', l_start_rowid, l_end_rowid, p_script_name,l_rows_processed ) <> TRUE) then
7927             Print('delete_ap_tables failed!');
7928 	    retcode := 2 ;
7929             RETURN ;
7930          end if;
7931 
7932 	-- l_rows_processed := SQL%ROWCOUNT; 9481539
7933 	  Print('Invoices deleted -> '||to_char(l_rows_processed));
7934 	  l_final_count := l_final_count + nvl(l_rows_processed,0) ;
7935 
7936          ad_parallel_updates_pkg.processed_rowid_range( l_rows_processed,
7937 						        l_end_rowid);
7938          COMMIT;
7939 
7940          --
7941          -- get new range of rowids
7942          --
7943          ad_parallel_updates_pkg.get_rowid_range(l_start_rowid,
7944 	 				         l_end_rowid,
7945 					         l_any_rows_to_process,
7946 					         p_batch_size,
7947 					         FALSE);
7948 
7949          l_debug_info := 'Worker '|| p_worker_id || '  l_start_rowid = ' || l_start_rowid ||
7950                          ' And l_end_rowid = ' || l_end_rowid   ;
7951          IF g_debug_switch in ('y','Y') THEN
7952             Print('(Purge_acctg_and_ap_table)'||l_debug_info);
7953          END IF;
7954   END LOOP;
7955    Print('Total invoices deleted in this worker -> '||to_char(l_final_count));
7956 
7957 EXCEPTION
7958   WHEN OTHERS THEN
7959     IF (SQLCODE < 0 ) then
7960        errbuf  := FND_MESSAGE.get ;
7961        retcode := 2 ;
7962        Print(SQLERRM);
7963     END IF;
7964 END Purge_acctg_and_ap_table;
7965 
7966 /*==========================================================================
7967   Bug  8913560
7968   Procedure : Update_Financials_Purges
7969   Purpose   : Updates the financilas_purges table during the delete process of
7970               accounting and ap tables that is done using multiple child requests
7971  *==========================================================================*/
7972 Procedure Update_Financials_Purges ( p_check_rows             IN NUMBER DEFAULT 0,
7973                                      p_invoice_payment_rows   IN NUMBER DEFAULT 0,
7974                                      p_invoice_rows           IN NUMBER DEFAULT 0,
7975                                      p_ae_line_rows	      IN NUMBER DEFAULT 0,
7976                                      p_ae_header_rows	      IN NUMBER DEFAULT 0,
7977                                      p_accounting_event_rows  IN NUMBER DEFAULT 0,
7978                                      p_invoice_lines_rows     IN NUMBER DEFAULT 0, --bug 11829621
7979                                      p_invoice_distributions_rows IN NUMBER DEFAULT 0, --bug 11829621
7980 				     p_purge_name             IN VARCHAR2         )
7981 IS
7982     PRAGMA AUTONOMOUS_TRANSACTION ;
7983 BEGIN
7984     UPDATE financials_purges
7985     SET    ap_checks             = NVL(ap_checks           , 0 ) + p_check_rows,
7986            ap_invoice_payments   = NVL(ap_invoice_payments , 0 ) + p_invoice_payment_rows,
7987            ap_invoices           = NVL(ap_invoices         , 0 ) + p_invoice_rows,
7988            ap_invoice_lines      = NVL(ap_invoice_lines    , 0 ) + p_invoice_lines_rows,                        --bug 11829621
7989            ap_invoice_distributions = NVL(ap_invoice_distributions , 0 ) + p_invoice_distributions_rows,        --bug 11829621
7990            ap_ae_lines		 = NVL(ap_ae_lines         , 0 ) + p_ae_line_rows,
7991            ap_ae_headers	 = NVL(ap_ae_headers       , 0 ) + p_ae_header_rows,
7992            ap_accounting_events  = NVL(ap_accounting_events, 0 ) + p_accounting_event_rows
7993     WHERE  purge_name            = p_purge_name;
7994     COMMIT ;
7995 END;
7996 END AP_Purge_PKG;