DBA Data[Home] [Help]

PACKAGE BODY: APPS.PN_RETRO_ADJUSTMENT_PKG

Source


1 PACKAGE BODY pn_retro_adjustment_pkg AS
2 /* $Header: PNRTADJB.pls 120.5.12010000.2 2009/05/26 07:08:33 rthumma ship $ */
3 
4 ------------------------------ DECLARATIONS ----------------------------------+
5 
6 TYPE item_id_tbl_type IS TABLE OF pn_payment_items.payment_item_id%TYPE INDEX BY BINARY_INTEGER;
7 TYPE sched_id_tbl_type IS TABLE OF pn_payment_schedules.payment_schedule_id%TYPE INDEX BY BINARY_INTEGER;
8 TYPE amt_tbl_type IS TABLE OF pn_payment_items.actual_amount%TYPE INDEX BY BINARY_INTEGER;
9 TYPE date_tbl_type IS TABLE OF pn_payment_items.due_date%TYPE INDEX BY BINARY_INTEGER;
10 
11 bad_input_exception        EXCEPTION;
12 
13 ------------------------------------------------------------------------------+
14 -- PROCEDURE   : create_virtual_schedules
15 -- DESCRIPTION : given a start date, end date, schedule day, amount, freq
16 --               create virtual items with corresponding dates.
17 -- HISTORY     :
18 -- 24-SEP-04 ftanudja o Created.
19 -- 10-AUG-05 piagrawa o Bug 4354810 - Added code to retrive the proper schedule
20 --                      start date
21 -- 05-APR-06 piagrawa o Bug 4354810 - Added handling for terms with start date
22 --                      equal to end date
23 ------------------------------------------------------------------------------+
24 
25 PROCEDURE create_virtual_schedules(
26             p_start_date pn_payment_terms.start_date%TYPE,
27             p_end_date   pn_payment_terms.end_date%TYPE,
28             p_sch_day    pn_payment_terms.schedule_day%TYPE,
29             p_amount     pn_payment_terms.actual_amount%TYPE,
30             p_term_freq  pn_payment_terms.frequency_code%TYPE,
31     	    p_payment_term_id pn_payment_terms_all.payment_term_id%TYPE,
32             x_sched_tbl  OUT NOCOPY payment_item_tbl_type
33          )
34 IS
35   l_current_end_date   pn_payment_terms.end_date%TYPE;
36   l_current_start_date pn_payment_terms.start_date%TYPE;
37   l_current_amount     pn_payment_terms.actual_amount%TYPE;
38   l_dummy_amount       pn_payment_terms.actual_amount%TYPE;
39 
40   l_count              NUMBER;
41   l_freq_num           NUMBER;
42 
43   l_info               VARCHAR2(100);
44   l_desc               VARCHAR2(100) := 'pn_retro_adjustment_pkg.create_virtual_schedules';
45   l_cal_yr_st_dt       pn_leases_all.cal_start%type;
46   l_yr_start_dt        DATE;
47   l_sch_str_dt         DATE := NULL;
48 
49 BEGIN
50 
51   pnp_debug_pkg.log(l_desc ||' (+)');
52 
53   l_info := ' validating input ';
54   pnp_debug_pkg.log(l_info);
55 
56   IF p_start_date IS NULL OR
57      p_end_date IS NULL OR
58      p_sch_day IS NULL OR
59      p_amount IS NULL OR
60      p_term_freq IS NULL OR
61      p_start_date > p_end_date OR
62      p_sch_day < 1 OR
63      p_sch_day > 28
64   THEN
65      raise bad_input_exception;
69   pnp_debug_pkg.log(l_info);
66   END IF;
67 
68   l_info := ' initializing variables ';
70 
71  SELECT cal_start
72  INTO   l_cal_yr_st_dt
73  FROM PN_LEASES_ALL
74  WHERE LEASE_ID = (select distinct lease_id from pn_payment_terms_all where payment_term_id = p_payment_term_id);
75 
76 
77  IF l_cal_yr_st_dt IS NOT NULL THEN
78        l_yr_start_dt := to_date(l_cal_yr_st_dt || '-' || to_char(p_start_date,'YYYY'),'DD-MM-YYYY');
79  END IF;
80 
81  IF l_yr_start_dt IS NOT NULL AND p_term_freq NOT IN ('MON','OT') THEN
82     pn_schedules_items.get_sch_start(p_yr_start_dt => l_yr_start_dt,
83                       p_freq_code => p_term_freq,
84 	              p_term_start_dt => p_start_date,
85                       p_sch_str_dt => l_sch_str_dt);
86  END IF;
87 
88   l_current_start_date := NVL(l_sch_str_dt,p_start_date);
89   l_current_end_date := p_start_date;
90 
91   -- special case for one time payments and terms with start date
92   -- equal to end date
93   IF p_term_freq = 'OT' OR (p_start_date = p_end_Date) THEN
94      l_current_end_date := p_start_date - 1;
95   END IF;
96 
97   l_info := ' creating items ';
98 
99   l_freq_num := pn_schedules_items.get_frequency(p_term_freq);
100 
101   WHILE l_current_end_date < p_end_date LOOP
102 
103      IF p_term_freq = 'MON' THEN
104         l_current_end_date := last_day(l_current_start_date);
105      ELSIF p_term_freq = 'OT' THEN
106         l_current_end_date := l_current_start_date;
107      ELSE
108         l_current_end_date := add_months(l_current_start_date, l_freq_num) - 1;
109      END IF;
110 
111      l_info := ' getting amount for schedule start: '|| l_current_start_date;
112      pnp_debug_pkg.log(l_info);
113 
114      IF p_term_freq = 'OT' THEN
115 
116         l_current_amount := p_amount;
117 
118      ELSE
119 
120         IF p_term_freq IN ('MON') THEN
121 
122            l_current_start_date := pn_schedules_items.First_Day(l_current_start_date);
123 
124         END IF;
125 
126         pn_schedules_items.get_amount(
127             p_sch_str_dt   => l_current_start_date,
128             p_sch_end_dt   => l_current_end_date,
129             p_trm_str_dt   => p_start_date,
130             p_trm_end_dt   => p_end_date,
131             p_act_amt      => p_amount,
132             p_est_amt      => null,
133             p_freq         => l_freq_num,
134             p_cash_act_amt => l_current_amount,
135             p_cash_est_amt => l_dummy_amount);
136 
137      END IF;
138 
139      -- make sure end date does not exceed the term end date
140      -- NOTE: this has to be done AFTER calling pn_schedules_items.get_amount() !!
141      l_current_end_date := LEAST(l_current_end_date, p_end_date);
142 
143      l_count := x_sched_tbl.COUNT;
144      x_sched_tbl(l_count).start_date    := l_current_start_date;
145      x_sched_tbl(l_count).end_date      := l_current_end_date;
146      x_sched_tbl(l_count).schedule_date := last_day(add_months(l_current_start_date, -1)) + p_sch_day;
147      x_sched_tbl(l_count).amount        := l_current_amount;
148 
149      l_current_start_date := l_current_end_date + 1;
150 
151      -- for one time payments, set logic to terminate loop
152      IF p_term_freq = 'OT' THEN l_current_end_date := p_end_date + 1; END IF;
153 
154   END LOOP;
155 
156   pnp_debug_pkg.log(l_desc ||' (-)');
157 
158 EXCEPTION
159   WHEN OTHERS THEN
160      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
161      raise;
162 
163 END create_virtual_schedules;
164 
165 ------------------------------------------------------------------------------+
166 -- PROCEDURE   : get_current_schedules
167 -- DESCRIPTION : given a payment term id, fetch all original and adjustment
168 --               items associated with it.
169 -- NOTES       :
170 -- The program works as follows:
171 -- 1) Fetch all original items into PL/SQL table
172 -- 2) Fetch all adjustment items into PL/SQL table
173 -- 3) Start comparing the two tables with the following rules
174 --    a) If no adjustment exists, return the original items table. No merging
175 --       is required here.
176 --    b) If any of the two tables has 'run out', exit loop and just parse
177 --       the rest of the other table into the output table.
178 --
179 -- HISTORY     :
180 -- 27-SEP-04 ftanudja o Created.
181 -- 15-JUL-05  SatyaDeep o Replaced base views with their _ALL tables
182 ------------------------------------------------------------------------------+
183 PROCEDURE get_current_schedules(
184             p_term_id    pn_payment_terms.payment_term_id%TYPE,
185             x_sched_tbl  OUT NOCOPY payment_item_tbl_type
186 )
187 IS
188   -- NOTE: important that the cursor is ordered by date
189   CURSOR fetch_original_items IS
190    SELECT item.payment_item_id,
191           item.actual_amount,
192           item.payment_schedule_id,
193           schedule.schedule_date,
194           schedule.payment_status_lookup_code
195      FROM pn_payment_items_all item,
196           pn_payment_schedules_all schedule
197     WHERE item.payment_term_id = p_term_id
198       AND item.payment_schedule_id = schedule.payment_schedule_id
199       AND item.payment_item_type_lookup_code = 'CASH'
200       AND item.last_adjustment_type_code IS NULL
201     ORDER BY schedule.schedule_date;
202 
203   -- NOTE: important that the cursor is ordered by date
204   CURSOR fetch_adj_items IS
205    SELECT summary.adjustment_summary_id,
206           summary.adj_schedule_date,
207           summary.sum_adj_amount
208      FROM pn_adjustment_summaries summary
209     WHERE summary.payment_term_id = p_term_id
210     ORDER BY summary.adj_schedule_date;
211 
212   l_orig_item_tbl payment_item_tbl_type;
213   l_adj_item_tbl  payment_item_tbl_type;
214 
215   l_count_adj    NUMBER;
216   l_count_orig   NUMBER;
217   l_count_summ   NUMBER;
218   l_info         VARCHAR2(300);
219   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.get_current_schedules';
220 
221 BEGIN
222 
223   pnp_debug_pkg.log(l_desc ||' (+)');
224 
225   l_info := ' fetching original items data ';
226   pnp_debug_pkg.log(l_info);
227 
228   l_count_orig := l_orig_item_tbl.COUNT;
229 
230   FOR orig_data_rec IN fetch_original_items LOOP
231      l_orig_item_tbl(l_count_orig).item_id        := orig_data_rec.payment_item_id;
232      l_orig_item_tbl(l_count_orig).amount         := orig_data_rec.actual_amount;
233      l_orig_item_tbl(l_count_orig).schedule_id    := orig_data_rec.payment_schedule_id;
234      l_orig_item_tbl(l_count_orig).schedule_date  := orig_data_rec.schedule_date;
235      l_orig_item_tbl(l_count_orig).payment_status := orig_data_rec.payment_status_lookup_code;
236      l_count_orig := l_count_orig + 1;
237   END LOOP;
238 
239   l_info := ' fetching adjustment items data ';
240   pnp_debug_pkg.log(l_info);
241 
242   l_count_adj := l_adj_item_tbl.COUNT;
243 
244   FOR adj_data_rec IN fetch_adj_items LOOP
245      l_adj_item_tbl(l_count_adj).adj_summ_id   := adj_data_rec.adjustment_summary_id;
246      l_adj_item_tbl(l_count_adj).amount        := adj_data_rec.sum_adj_amount;
247      l_adj_item_tbl(l_count_adj).schedule_date := adj_data_rec.adj_schedule_date;
248      l_count_adj := l_count_adj + 1;
249   END LOOP;
250 
251   l_info := ' merging the two tables ';
252   pnp_debug_pkg.log(l_info);
253 
254   IF l_adj_item_tbl.COUNT = 0 THEN
255 
256      -- if no adjustments, then return l_orig_item_tbl
257      x_sched_tbl := l_orig_item_tbl;
258 
259   ELSE
260      l_count_orig := null;
261      l_count_adj  := 0;
262      l_count_summ := 0;
263 
264      FOR i IN 0 .. l_orig_item_tbl.COUNT - 1 LOOP
265 
266         IF l_orig_item_tbl(i).schedule_date = l_adj_item_tbl(l_count_adj).schedule_date THEN
267 
268            l_info := ' (orig = adj): inserting the current item into result table '||
269                      ' orig_item date: '||l_orig_item_tbl(i).schedule_date ||
270                      ' adj_item date: '||l_adj_item_tbl(l_count_adj).schedule_date;
271 
272            pnp_debug_pkg.log(l_info);
273 
274            x_sched_tbl(l_count_summ).item_id        := l_orig_item_tbl(i).item_id;
275            x_sched_tbl(l_count_summ).schedule_id    := l_orig_item_tbl(i).schedule_id;
276            x_sched_tbl(l_count_summ).schedule_date  := l_orig_item_tbl(i).schedule_date;
277            x_sched_tbl(l_count_summ).payment_status := l_orig_item_tbl(i).payment_status;
278            x_sched_tbl(l_count_summ).adj_summ_id    := l_adj_item_tbl(l_count_adj).adj_summ_id;
279            x_sched_tbl(l_count_summ).amount         := l_orig_item_tbl(i).amount +
280                                                        l_adj_item_tbl(l_count_adj).amount;
281 
282            l_count_summ                             := l_count_summ + 1;
283            l_count_adj                              := l_count_adj + 1;
284 
285            IF l_count_adj = l_adj_item_tbl.COUNT THEN
286               l_count_orig := i + 1;
287               exit;
288            END IF;
289 
290         ELSIF l_orig_item_tbl(i).schedule_date < l_adj_item_tbl(l_count_adj).schedule_date THEN
291 
292            l_info := ' (orig < adj): inserting the current item into result table '||
293                      ' orig_item date: '||l_orig_item_tbl(i).schedule_date ||
294                      ' adj_item date: '||l_adj_item_tbl(l_count_adj).schedule_date;
295 
296            pnp_debug_pkg.log(l_info);
297 
298            x_sched_tbl(l_count_summ).item_id        := l_orig_item_tbl(i).item_id;
299            x_sched_tbl(l_count_summ).schedule_id    := l_orig_item_tbl(i).schedule_id;
300            x_sched_tbl(l_count_summ).schedule_date  := l_orig_item_tbl(i).schedule_date;
301            x_sched_tbl(l_count_summ).payment_status := l_orig_item_tbl(i).payment_status;
302            x_sched_tbl(l_count_summ).amount         := l_orig_item_tbl(i).amount;
303            l_count_summ                             := l_count_summ + 1;
304 
305         ELSE
306 
307            l_info := ' (orig > adj): looping through other table until a greater date is found ';
308 
309            pnp_debug_pkg.log(l_info);
310 
311            WHILE (l_count_adj <= l_adj_item_tbl.COUNT - 1) AND
312                  (l_orig_item_tbl(i).schedule_date >
316               l_info := ' inserting the current item into result table '||
313                   l_adj_item_tbl(l_count_adj).schedule_date)
314            LOOP
315 
317                         ' orig_item date: '||l_orig_item_tbl(i).schedule_date ||
318                         ' adj_item date: '||l_adj_item_tbl(l_count_adj).schedule_date;
319 
320               pnp_debug_pkg.log(l_info);
321 
322               IF (l_count_summ <> 0 AND
323                   x_sched_tbl(l_count_summ - 1).schedule_date <>
324                   l_adj_item_tbl(l_count_adj).schedule_date)
325                  OR l_count_summ = 0 THEN
326                  x_sched_tbl(l_count_summ).adj_summ_id   := l_adj_item_tbl(l_count_adj).adj_summ_id;
327                  x_sched_tbl(l_count_summ).schedule_date := l_adj_item_tbl(l_count_adj).schedule_date;
328                  x_sched_tbl(l_count_summ).amount        := l_adj_item_tbl(l_count_adj).amount;
329                  l_count_summ                            := l_count_summ + 1;
330               END IF;
331 
332               l_count_adj                             := l_count_adj + 1;
333 
334            END LOOP;
335 
336            l_info := ' finished finding lesser adj dates, now inserting current orig '||
337                      ' item into result table orig_item date: '|| l_orig_item_tbl(i).schedule_date;
338 
339            pnp_debug_pkg.log(l_info);
340 
341            x_sched_tbl(l_count_summ).item_id        := l_orig_item_tbl(i).item_id;
342            x_sched_tbl(l_count_summ).schedule_id    := l_orig_item_tbl(i).schedule_id;
343            x_sched_tbl(l_count_summ).schedule_date  := l_orig_item_tbl(i).schedule_date;
344            x_sched_tbl(l_count_summ).payment_status := l_orig_item_tbl(i).payment_status;
345            x_sched_tbl(l_count_summ).amount         := l_orig_item_tbl(i).amount;
346 
347            IF (l_count_adj <= l_adj_item_tbl.COUNT - 1) AND
348               (l_orig_item_tbl(i).schedule_date = l_adj_item_tbl(l_count_adj).schedule_date)
349            THEN
350               x_sched_tbl(l_count_summ).adj_summ_id   := l_adj_item_tbl(l_count_adj).adj_summ_id;
351               x_sched_tbl(l_count_summ).amount        := x_sched_tbl(l_count_summ).amount +
352                                                          l_adj_item_tbl(l_count_adj).amount;
353               l_count_adj := l_count_adj + 1;
354            END IF;
355 
356            l_count_summ                             := l_count_summ + 1;
357 
358            IF l_count_adj = l_adj_item_tbl.COUNT THEN
359               l_count_orig := i + 1;
360               exit;
361            END IF;
362 
363         END IF;
364 
365      END LOOP;
366 
367      l_info := ' merging the leftover items from l_orig_item_tbl ';
368      pnp_debug_pkg.log(l_info);
369 
370      IF l_count_orig IS NOT NULL THEN
371         FOR i IN l_count_orig .. l_orig_item_tbl.COUNT - 1 LOOP
372            x_sched_tbl(l_count_summ).item_id        := l_orig_item_tbl(i).item_id;
373            x_sched_tbl(l_count_summ).schedule_id    := l_orig_item_tbl(i).schedule_id;
374            x_sched_tbl(l_count_summ).schedule_date  := l_orig_item_tbl(i).schedule_date;
375            x_sched_tbl(l_count_summ).amount         := l_orig_item_tbl(i).amount;
376            x_sched_tbl(l_count_summ).payment_status := l_orig_item_tbl(i).payment_status;
377            l_count_summ := l_count_summ + 1;
378         END LOOP;
379      END IF;
380 
381      l_info := ' merging the leftover items from l_adj_item_tbl ';
382      pnp_debug_pkg.log(l_info);
383 
384      FOR i IN l_count_adj  .. l_adj_item_tbl.COUNT - 1 LOOP
385         IF (l_count_summ <> 0 AND
386             x_sched_tbl(l_count_summ - 1).schedule_date <>
387             l_adj_item_tbl(i).schedule_date)
388            OR
389            l_count_summ = 0 THEN
390            x_sched_tbl(l_count_summ).adj_summ_id   := l_adj_item_tbl(i).adj_summ_id;
391            x_sched_tbl(l_count_summ).schedule_date := l_adj_item_tbl(i).schedule_date;
392            x_sched_tbl(l_count_summ).amount        := l_adj_item_tbl(i).amount;
393            l_count_summ                            := l_count_summ + 1;
394         END IF;
395      END LOOP;
396   END IF;
397 
398   pnp_debug_pkg.log(l_desc ||' (-)');
399 
400 EXCEPTION
401   WHEN OTHERS THEN
402      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
403      raise;
404 
405 END get_current_schedules;
406 
407 ------------------------------------------------------------------------------+
408 -- PROCEDURE   : merge_schedules
409 -- DESCRIPTION : given two schedules, current and virtual, merge the two
410 --               together
411 -- NOTE        :
412 -- This uses 99% of the logic of get_current_schedules() to merge the tables
413 -- using dates. Only the updated fields are sometimes different. Here the
414 -- value of virtual items is put into the 'new_amount' column.
415 --
416 -- HISTORY     :
417 -- 28-SEP-04 ftanudja o Created.
418 ------------------------------------------------------------------------------+
419 PROCEDURE merge_schedules(
420             p_current_sched payment_item_tbl_type,
421             p_virtual_sched payment_item_tbl_type,
422             x_sched_tbl     OUT NOCOPY payment_item_tbl_type
423 )
424 IS
425   l_count_virtl  NUMBER;
426   l_count_curnt  NUMBER;
427   l_count_merge  NUMBER;
428 
429   l_info         VARCHAR2(200);
430   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.merge_schedules';
431 
432 BEGIN
433 
434   pnp_debug_pkg.log(l_desc ||' (+)');
435 
436   l_info := ' initializing counters ';
437   pnp_debug_pkg.log(l_info);
438 
439   l_count_curnt := null;
440   l_count_virtl := 0;
441   l_count_merge := 0;
442 
443   l_info := ' merging the two tables ';
444   pnp_debug_pkg.log(l_info);
445 
446   FOR i IN 0 .. p_current_sched.COUNT - 1 LOOP
447 
448      IF p_current_sched(i).schedule_date = p_virtual_sched(l_count_virtl).schedule_date THEN
449 
450         l_info := ' (curnt = virtl): inserting item into result table '||
451                   ' curnt_item date: '||p_current_sched(i).schedule_date ||
452                   ' virtl_item date: '||p_virtual_sched(l_count_virtl).schedule_date;
453 
454         pnp_debug_pkg.log(l_info);
455 
456         x_sched_tbl(l_count_merge).item_id        := p_current_sched(i).item_id;
457         x_sched_tbl(l_count_merge).adj_summ_id    := p_current_sched(i).adj_summ_id;
458         x_sched_tbl(l_count_merge).schedule_id    := p_current_sched(i).schedule_id;
459         x_sched_tbl(l_count_merge).schedule_date  := p_current_sched(i).schedule_date;
460         x_sched_tbl(l_count_merge).payment_status := p_current_sched(i).payment_status;
461         x_sched_tbl(l_count_merge).amount         := p_current_sched(i).amount;
462 
463         x_sched_tbl(l_count_merge).new_amount     := p_virtual_sched(l_count_virtl).amount;
464         x_sched_tbl(l_count_merge).start_date     := p_virtual_sched(l_count_virtl).start_date;
465         x_sched_tbl(l_count_merge).end_date       := p_virtual_sched(l_count_virtl).end_date;
466 
467         l_count_merge                             := l_count_merge + 1;
468         l_count_virtl                             := l_count_virtl + 1;
469 
470         IF l_count_virtl = p_virtual_sched.COUNT THEN
471            l_count_curnt := i + 1;
472            exit;
473         END IF;
474 
475      ELSIF p_current_sched(i).schedule_date < p_virtual_sched(l_count_virtl).schedule_date THEN
476 
477         l_info := ' (curnt < virtl): inserting item into result table '||
478                   ' curnt_item date: '||p_current_sched(i).schedule_date ||
479                   ' virtl_item date: '||p_virtual_sched(l_count_virtl).schedule_date;
480 
481         pnp_debug_pkg.log(l_info);
482 
483         x_sched_tbl(l_count_merge).item_id        := p_current_sched(i).item_id;
484         x_sched_tbl(l_count_merge).adj_summ_id    := p_current_sched(i).adj_summ_id;
485         x_sched_tbl(l_count_merge).schedule_id    := p_current_sched(i).schedule_id;
486         x_sched_tbl(l_count_merge).schedule_date  := p_current_sched(i).schedule_date;
487         x_sched_tbl(l_count_merge).payment_status := p_current_sched(i).payment_status;
488         x_sched_tbl(l_count_merge).amount         := p_current_sched(i).amount;
489         l_count_merge                             := l_count_merge + 1;
490 
491      ELSE
492 
493         l_info := ' (curnt > virtl): looping through other table until a greater date is found ';
494 
495         pnp_debug_pkg.log(l_info);
496 
497         WHILE (l_count_virtl <= p_virtual_sched.COUNT - 1) AND
498               (p_current_sched(i).schedule_date >
499                p_virtual_sched(l_count_virtl).schedule_date)
500         LOOP
501 
502            l_info := ' inserting into result table '||
503                      ' curnt_item date: '||p_current_sched(i).schedule_date ||
504                      ' virtl_item date: '||p_virtual_sched(l_count_virtl).schedule_date;
505 
506            pnp_debug_pkg.log(l_info);
507 
508            IF (l_count_merge <> 0 AND
509                x_sched_tbl(l_count_merge - 1).schedule_date <>
510                p_virtual_sched(l_count_virtl).schedule_date)
511               OR l_count_merge = 0 THEN
512               x_sched_tbl(l_count_merge).schedule_date := p_virtual_sched(l_count_virtl).schedule_date;
513               x_sched_tbl(l_count_merge).new_amount    := p_virtual_sched(l_count_virtl).amount;
514               x_sched_tbl(l_count_merge).start_date    := p_virtual_sched(l_count_virtl).start_date;
515               x_sched_tbl(l_count_merge).end_date      := p_virtual_sched(l_count_virtl).end_date;
516 
517               l_count_merge                            := l_count_merge + 1;
518            END IF;
519 
520            l_count_virtl                               := l_count_virtl + 1;
521 
522         END LOOP;
523 
524         l_info := ' finished finding lesser adj dates, now inserting current '||
525                      ' item into result table curnt_item date:'||p_current_sched(i).schedule_date;
526 
527         pnp_debug_pkg.log(l_info);
528 
529         x_sched_tbl(l_count_merge).item_id        := p_current_sched(i).item_id;
530         x_sched_tbl(l_count_merge).adj_summ_id    := p_current_sched(i).adj_summ_id;
531         x_sched_tbl(l_count_merge).schedule_id    := p_current_sched(i).schedule_id;
532         x_sched_tbl(l_count_merge).schedule_date  := p_current_sched(i).schedule_date;
533         x_sched_tbl(l_count_merge).payment_status := p_current_sched(i).payment_status;
534         x_sched_tbl(l_count_merge).amount         := p_current_sched(i).amount;
535 
536         IF (l_count_virtl <= p_virtual_sched.COUNT - 1) AND
537            (p_current_sched(i).schedule_date = p_virtual_sched(l_count_virtl).schedule_date)
538         THEN
539            x_sched_tbl(l_count_merge).new_amount  := p_virtual_sched(l_count_virtl).amount;
540            x_sched_tbl(l_count_merge).start_date  := p_virtual_sched(l_count_virtl).start_date;
541            x_sched_tbl(l_count_merge).end_date    := p_virtual_sched(l_count_virtl).end_date;
542            l_count_virtl                          := l_count_virtl + 1;
543 
544         END IF;
545 
546         l_count_merge                             := l_count_merge + 1;
547 
548         IF l_count_virtl = p_virtual_sched.COUNT THEN
549            l_count_curnt := i + 1;
550            exit;
551         END IF;
552 
553      END IF;
554 
555   END LOOP;
556 
557   l_info := ' merging the leftover items from p_current_sched ';
558   pnp_debug_pkg.log(l_info);
559 
560   IF l_count_curnt IS NOT NULL THEN
561      FOR i IN l_count_curnt .. p_current_sched.COUNT - 1 LOOP
562         x_sched_tbl(l_count_merge).item_id        := p_current_sched(i).item_id;
563         x_sched_tbl(l_count_merge).adj_summ_id    := p_current_sched(i).adj_summ_id;
564         x_sched_tbl(l_count_merge).schedule_id    := p_current_sched(i).schedule_id;
565         x_sched_tbl(l_count_merge).schedule_date  := p_current_sched(i).schedule_date;
566         x_sched_tbl(l_count_merge).amount         := p_current_sched(i).amount;
567         x_sched_tbl(l_count_merge).payment_status := p_current_sched(i).payment_status;
568         l_count_merge := l_count_merge + 1;
569      END LOOP;
570   END IF;
571 
572   l_info := ' merging the leftover items from p_virtual_sched ';
573   pnp_debug_pkg.log(l_info);
574 
575   FOR i IN l_count_virtl  .. p_virtual_sched.COUNT - 1 LOOP
576      IF (l_count_merge <> 0 AND
577          x_sched_tbl(l_count_merge - 1).schedule_date <>
578          p_virtual_sched(i).schedule_date)
579         OR
580         l_count_merge = 0 THEN
581 
582         x_sched_tbl(l_count_merge).schedule_date := p_virtual_sched(i).schedule_date;
583         x_sched_tbl(l_count_merge).new_amount    := p_virtual_sched(i).amount;
584         x_sched_tbl(l_count_merge).start_date    := p_virtual_sched(i).start_date;
585         x_sched_tbl(l_count_merge).end_date      := p_virtual_sched(i).end_date;
586 
587         l_count_merge                            := l_count_merge + 1;
588      END IF;
589   END LOOP;
590 
591   pnp_debug_pkg.log(l_desc ||' (-)');
592 
593 EXCEPTION
594   WHEN OTHERS THEN
595      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
596      raise;
597 
598 END merge_schedules;
599 
600 ------------------------------------------------------------------------------+
601 -- PROCEDURE   : find_start_end_dates
602 -- DESCRIPTION : In case the start and end dates are not found from the pl/sql
603 --               table, determine using term information.
604 -- NOTE        : This is usually called when a new adjustment is needed to
605 --               cancel out an approved item that is outside of the date range
606 --               due to retro adjustment.
607 -- HISTORY     :
608 -- 08-OCT-04 ftanudja o Created.
609 -- 14-JAN-05 atuppad  o removed least of p_term_end_dt for x_end_date
610 ------------------------------------------------------------------------------+
611 PROCEDURE find_start_end_dates(
612             p_term_freq     pn_payment_terms.frequency_code%TYPE,
613             p_term_start_dt pn_payment_terms.start_date%TYPE,
614             p_term_end_dt   pn_payment_terms.end_date%TYPE,
615             p_schedule_dt   pn_payment_schedules.schedule_date%TYPE,
616             x_start_date    OUT NOCOPY pn_payment_items.adj_start_date%TYPE,
617             x_end_date      OUT NOCOPY pn_payment_items.adj_end_date%TYPE
618 )
619 IS
620   l_freq_num     NUMBER;
621   l_start_day    NUMBER;
622   l_info         VARCHAR2(100);
623   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.find_start_end_dates';
624 
625 BEGIN
626 
627   pnp_debug_pkg.log(l_desc ||' (+)');
628 
629   IF p_term_freq = 'MON' THEN
630 
631      x_end_date   := last_day(p_schedule_dt);
632      x_start_date := add_months(x_end_date, -1) + 1;
633      x_end_date   := least(x_end_date, p_term_end_dt);
634 
635   ELSIF p_term_freq = 'QTR' THEN
636 
637      l_freq_num   := pn_schedules_items.get_frequency(p_term_freq);
638      l_start_day  := TO_NUMBER(TO_CHAR(p_term_start_dt,'DD'));
639 
640      x_start_date := last_day(add_months(p_schedule_dt,- 1)) + l_start_day;
641      x_end_date   := add_months(x_start_date, l_freq_num) - 1;
642 
643   END IF;
644 
645   pnp_debug_pkg.log(l_desc ||' (-)');
646 
647 EXCEPTION
648   WHEN OTHERS THEN
649      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
650      raise;
651 
652 END find_start_end_dates;
653 
654 ------------------------------------------------------------------------------+
655 -- PROCEDURE   : create_adjustment_tables
656 -- DESCRIPTION : Given a table of schedules and items, determine what action
657 --               needs to be done. Group items into tables, depending on what
658 --               action needs to be done. All changes to original items go
659 --               to xxx_orig_table; all changes to adjustment items go to
660 --               xxx_adj_table.
661 --
662 -- Program logic as follows
663 --
664 -- IF virtual item exists, and current item doesn't exist THEN
665 --   IF schedule date > last_appr_sch_dt THEN
666 --      create new original item
667 --   ELSE
668 --      create new adjustment item
669 --   END IF
670 -- ELSIF virtual item doesn't exist, and current item exists THEN
671 --   IF payment status = 'DRAFT' THEN
672 --      delete original item
673 ---  ELSE
674 --      update adjustment item
675 --   END IF
676 -- ELSIF virtual item exists, and current item exists, and they're not = THEN
677 --   IF payment status = 'DRAFT' THEN
678 --      update original item
679 --   ELSE
680 --      update adjustment item
681 --   END IF
682 -- END IF
683 --
684 -- HISTORY     :
685 -- 29-SEP-04 ftanudja o Created.
686 -- 14-JAN-04 atuppad  o for the records in x_adj_table, made sure that they
687 --                      start_date and end_date.
688 ------------------------------------------------------------------------------+
689 PROCEDURE create_adjustment_tables (
690             p_sched_table    payment_item_tbl_type,
691             p_last_appr_dt   DATE,
692             p_term_freq      pn_payment_terms.frequency_code%TYPE,
693             p_term_start_dt  pn_payment_terms.start_date%TYPE,
694             p_term_end_dt    pn_payment_terms.end_date%TYPE,
695             x_new_orig_table OUT NOCOPY payment_item_tbl_type,
696             x_upd_orig_table OUT NOCOPY payment_item_tbl_type,
697             x_del_orig_table OUT NOCOPY payment_item_tbl_type,
698             x_adj_table      OUT NOCOPY payment_item_tbl_type
699 )
700 IS
701   l_count_new_orig NUMBER := 0;
702   l_count_upd_orig NUMBER := 0;
703   l_count_del_orig NUMBER := 0;
704   l_count_chg_adj  NUMBER := 0;
705   l_last_appr_dt   DATE;
706 
707   l_start_date   pn_adjustment_details.adj_start_date%TYPE;
708   l_end_date     pn_adjustment_details.adj_end_date%TYPE;
709 
710   l_info         VARCHAR2(100);
711   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.create_adjustment_tables';
712 
713 BEGIN
714 
715   pnp_debug_pkg.log(l_desc ||' (+)');
716 
717   l_info := ' looping through the schedule table ';
718   pnp_debug_pkg.log(l_info);
719 
723 
720   l_last_appr_dt := nvl(p_last_appr_dt, TO_DATE('01/01/0001','DD/MM/YYYY'));
721 
722   FOR i IN 0 .. p_sched_table.COUNT - 1 LOOP
724      IF p_sched_table(i).new_amount IS NOT NULL AND
725         p_sched_table(i).amount IS NULL AND
726         p_sched_table(i).new_amount <> 0
727      THEN
728 
729         IF p_sched_table(i).schedule_date > l_last_appr_dt THEN
730            x_new_orig_table(l_count_new_orig).amount        := p_sched_table(i).new_amount;
731            x_new_orig_table(l_count_new_orig).schedule_date := p_sched_table(i).schedule_date;
732            x_new_orig_table(l_count_new_orig).trx_date      := p_sched_table(i).schedule_date;
733            l_count_new_orig                                 := l_count_new_orig + 1;
734 
735         ELSE
736            x_adj_table(l_count_chg_adj).amount        := p_sched_table(i).new_amount;
737            x_adj_table(l_count_chg_adj).schedule_date := p_sched_table(i).schedule_date;
738            x_adj_table(l_count_chg_adj).start_date    := p_sched_table(i).start_date;
739            x_adj_table(l_count_chg_adj).end_date      := p_sched_table(i).end_date;
740            l_count_chg_adj                            := l_count_chg_adj + 1;
741 
742         END IF;
743 
744      ELSIF p_sched_table(i).new_amount IS NULL AND
745            p_sched_table(i).amount IS NOT NULL
746      THEN
747 
748         IF p_sched_table(i).payment_status = 'DRAFT' THEN
749 
750            x_del_orig_table(l_count_del_orig).item_id       := p_sched_table(i).item_id;
751            x_del_orig_table(l_count_del_orig).schedule_id   := p_sched_table(i).schedule_id;
752            x_del_orig_table(l_count_del_orig).schedule_date := p_sched_table(i).schedule_date;
753            l_count_del_orig                                 := l_count_del_orig + 1;
754 
755         ELSIF p_sched_table(i).amount <> 0 THEN
756 
757            x_adj_table(l_count_chg_adj).amount        := - p_sched_table(i).amount;
758            x_adj_table(l_count_chg_adj).schedule_date := p_sched_table(i).schedule_date;
759            x_adj_table(l_count_chg_adj).start_date    := p_sched_table(i).start_date;
760            x_adj_table(l_count_chg_adj).end_date      := p_sched_table(i).end_date;
761            x_adj_table(l_count_chg_adj).adj_summ_id   := p_sched_table(i).adj_summ_id;
762            l_count_chg_adj                            := l_count_chg_adj + 1;
763 
764         END IF;
765 
766      ELSIF p_sched_table(i).new_amount IS NOT NULL AND
767            p_sched_table(i).amount IS NOT NULL AND
768            p_sched_table(i).amount <> p_sched_table(i).new_amount
769      THEN
770 
771         IF p_sched_table(i).payment_status = 'DRAFT' AND p_sched_table(i).new_amount <> 0 THEN
772 
773            x_upd_orig_table(l_count_upd_orig).item_id       := p_sched_table(i).item_id;
774            x_upd_orig_table(l_count_upd_orig).schedule_date := p_sched_table(i).schedule_date;
775            x_upd_orig_table(l_count_upd_orig).amount        := p_sched_table(i).new_amount;
776 
777            l_count_upd_orig := l_count_upd_orig + 1;
778 
779         -- this case is almost never going to happen
780         ELSIF p_sched_table(i).payment_status = 'DRAFT' AND p_sched_table(i).new_amount = 0 THEN
781 
782            x_del_orig_table(l_count_del_orig).item_id       := p_sched_table(i).item_id;
783            x_del_orig_table(l_count_del_orig).schedule_id   := p_sched_table(i).schedule_id;
784            x_del_orig_table(l_count_del_orig).schedule_date := p_sched_table(i).schedule_date;
785            l_count_del_orig                                 := l_count_del_orig + 1;
786 
787         ELSE
788 
789            x_adj_table(l_count_chg_adj).amount        := p_sched_table(i).new_amount -
790                                                              p_sched_table(i).amount;
791            x_adj_table(l_count_chg_adj).schedule_date := p_sched_table(i).schedule_date;
792            x_adj_table(l_count_chg_adj).start_date    := p_sched_table(i).start_date;
793            x_adj_table(l_count_chg_adj).end_date      := p_sched_table(i).end_date;
794            x_adj_table(l_count_chg_adj).adj_summ_id   := p_sched_table(i).adj_summ_id;
795            l_count_chg_adj                            := l_count_chg_adj + 1;
796 
797         END IF;
798 
799      END IF;
800 
801   END LOOP;
802 
803   /* AMTNEW CHANGES - START */
804   FOR i IN 0 .. x_adj_table.COUNT - 1 LOOP
805 
806      IF x_adj_table(i).start_date IS NULL OR x_adj_table(i).end_date IS NULL THEN
807 
808         l_info := ' now figuring out start and end dates for schedule date:'||
809                     x_adj_table(i).schedule_date;
810         pnp_debug_pkg.log(l_info);
811 
812         find_start_end_dates(
813            p_term_freq     => p_term_freq,
814            p_term_start_dt => p_term_start_dt,
815            p_term_end_dt   => p_term_end_dt,
816            p_schedule_dt   => x_adj_table(i).schedule_date,
817            x_start_date    => l_start_date,
818            x_end_date      => l_end_date
819         );
820         x_adj_table(i).start_date := l_start_date;
821         x_adj_table(i).end_date := l_end_date;
822 
823      END IF;
824 
825   END LOOP;
826   /* AMTNEW CHANGES - END */
827 
828   pnp_debug_pkg.log(l_desc ||' (-)');
829 
830 EXCEPTION
831   WHEN OTHERS THEN
832      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
833      raise;
834 
835 END create_adjustment_tables;
836 
837 ------------------------------------------------------------------------------+
838 -- PROCEDURE   : calculate_adjustment_details
839 -- DESCRIPTION : given a table of adjustments, find all payment items that are
840 --               impacted and separate them into 3 tables: one for updation,
841 --               one for deletion, and one for creation.
842 -- HISTORY     :
843 -- 29-SEP-04 ftanudja o Created.
844 -- 15-JUL-05  SatyaDeep o Replaced base views with their _ALL tables
845 ------------------------------------------------------------------------------+
846 
847 PROCEDURE calculate_adjustment_details(
848              p_adj_table     IN OUT NOCOPY payment_item_tbl_type,
849              p_new_itm_table OUT NOCOPY payment_item_tbl_type,
850              p_upd_itm_table OUT NOCOPY payment_item_tbl_type,
851              p_del_itm_table OUT NOCOPY payment_item_tbl_type
852 )
853 IS
854 
855   CURSOR get_item_details (p_adj_summ_id pn_adjustment_summaries.adjustment_summary_id%TYPE)IS
856      SELECT item.payment_item_id,
857             item.actual_amount amount,
858             schedule.payment_schedule_id,
859             schedule.schedule_date
860        FROM pn_payment_items_all item,
861             pn_payment_schedules_all schedule
862       WHERE schedule.payment_schedule_id = item.payment_schedule_id
863         AND schedule.payment_status_lookup_code = 'DRAFT'
864         AND item.payment_item_id IN
865             (SELECT payment_item_id
866                FROM pn_adjustment_details
867               WHERE adjustment_summary_id = p_adj_summ_id);
868 
869   l_items_table     payment_item_tbl_type;
870 
871   -- for table counters
872   l_count_new_itm   NUMBER;
873   l_count_upd_itm   NUMBER;
874   l_count_del_itm   NUMBER;
875   l_count_items     NUMBER;
876 
877   l_sch_date        DATE;
878   l_temp_amt        NUMBER;
879   l_exist_draft_adj BOOLEAN;
880 
881   l_info            VARCHAR2(100);
882   l_desc            VARCHAR2(100) := 'pn_retro_adjustment_pkg.calculate_adjustment_details';
883 
884 BEGIN
885 
886   pnp_debug_pkg.log(l_desc ||' (+)');
887 
888   l_info := ' initializing counters ';
889   pnp_debug_pkg.log(l_info);
890 
891   l_count_new_itm := 0;
892   l_count_upd_itm := 0;
893   l_count_del_itm := 0;
894   l_count_items   := 0;
895 
896   FOR i IN 0 .. p_adj_table.COUNT - 1 LOOP
897 
898      l_items_table.delete;
899      l_exist_draft_adj := FALSE;
900 
901      IF p_adj_table(i).adj_summ_id IS NOT NULL THEN
902 
903         l_info := ' fetching items for adj summary id: '||p_adj_table(i).adj_summ_id;
904         pnp_debug_pkg.log(l_info);
905 
906         FOR items_rec IN get_item_details (p_adj_table(i).adj_summ_id) LOOP
907 
908            l_exist_draft_adj := TRUE;
909            l_temp_amt := items_rec.amount + p_adj_table(i).amount;
910 
911            -- if new amount is zero, delete, else update
912            IF l_temp_amt = 0 THEN
913 
914               p_del_itm_table(l_count_del_itm).item_id       := items_rec.payment_item_id;
915               p_del_itm_table(l_count_del_itm).schedule_date := items_rec.schedule_date;
916               p_del_itm_table(l_count_del_itm).schedule_id   := items_rec.payment_schedule_id;
917               l_count_del_itm                                := l_count_del_itm + 1;
918 
919            ELSIF l_temp_amt <> 0 THEN
920 
921               p_adj_table(i).item_id                       := items_rec.payment_item_id;
922               p_upd_itm_table(l_count_upd_itm).item_id     := items_rec.payment_item_id;
923               p_upd_itm_table(l_count_upd_itm).amount      := l_temp_amt;
924               l_count_upd_itm                              := l_count_upd_itm + 1;
925 
926            END IF;
927 
928            -- there should be only one draft item, or even if there are multiple,
929            -- only one should be changed
930            exit;
931 
932         END LOOP;
933 
934      END IF;
935 
936      -- if nothing found, create new adjustment
937 
938      IF NOT l_exist_draft_adj THEN
939         p_new_itm_table(l_count_new_itm).amount        := p_adj_table(i).amount;
940         p_new_itm_table(l_count_new_itm).schedule_date := p_adj_table(i).schedule_date;
941         p_new_itm_table(l_count_new_itm).start_date    := p_adj_table(i).start_date;
942         p_new_itm_table(l_count_new_itm).end_date      := p_adj_table(i).end_date;
943         l_count_new_itm                                := l_count_new_itm + 1;
944      END IF;
945 
946   END LOOP;
947 
948   pnp_debug_pkg.log(l_desc ||' (-)');
949 
950 EXCEPTION
951   WHEN OTHERS THEN
952      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
953      raise;
954 
955 END calculate_adjustment_details;
956 
957 
958 ------------------------------------------------------------------------------+
959 -- PROCEDURE   : prepare_new_items_from_adj
960 -- DESCRIPTION : Given a table of adjustments data, creates a table of items
961 --               that needs to be created based on various system options
962 --               values.
963 -- HISTORY     :
964 -- 05-OCT-04 ftanudja o Created.
965 -- 10-AUG-05 piagrawa o Bug#4284035 - Modified the signature to pass org id
966 ------------------------------------------------------------------------------+
967 PROCEDURE prepare_new_items_from_adj (
968             p_sch_day      pn_payment_terms.schedule_day%TYPE,
969             p_item_adj_tbl IN OUT NOCOPY payment_item_tbl_type,
970             p_org_id       NUMBER
971 )
972 IS
973   l_item_dtl_tbl   payment_item_tbl_type;
974 
975   -- for system option values
976   l_consolidate    BOOLEAN;
977   l_use_crnt_month BOOLEAN;
978   l_trx_sysdate    BOOLEAN;
979 
980   l_sch_dt         pn_payment_schedules.schedule_date%TYPE;
981   l_trx_dt         pn_payment_items.due_date%TYPE;
982   l_total_amt      pn_payment_items.actual_amount%TYPE;
983 
984   l_info           VARCHAR2(100);
985   l_desc           VARCHAR2(100) := 'pn_retro_adjustment_pkg.prepare_new_items_from_adj';
986 
987 BEGIN
988 
989   pnp_debug_pkg.log(l_desc ||' (+)');
990 
991   l_info := ' fetching system option values ';
992   pnp_debug_pkg.log(l_info);
993 
994   IF pn_mo_cache_utils.get_profile_value('PN_CONSOLIDATE_ADJ_ITEMS', p_org_id) = 'Y' THEN
995      l_consolidate := TRUE;
996   ELSE
997      l_consolidate := FALSE;
998   END IF;
999 
1000   IF pn_mo_cache_utils.get_profile_value('PN_USE_SYSDATE_FOR_ADJ', p_org_id) = 'Y' THEN
1001      l_use_crnt_month := TRUE;
1002   ELSE
1003      l_use_crnt_month := FALSE;
1004   END IF;
1005 
1006   IF pn_mo_cache_utils.get_profile_value('PN_USE_SYSDATE_AS_TRX_DATE', p_org_id) = 'Y' THEN
1007      l_trx_sysdate := TRUE;
1008   ELSE
1009      l_trx_sysdate := FALSE;
1010   END IF;
1011 
1012   l_total_amt      := 0;
1013 
1014   FOR i IN 0 .. p_item_adj_tbl.COUNT - 1 LOOP
1015 
1016      IF l_consolidate AND l_use_crnt_month THEN
1017         l_total_amt := l_total_amt + p_item_adj_tbl(i).amount;
1018 
1019      ELSIF NOT l_consolidate THEN
1020 
1021         IF l_use_crnt_month THEN
1022            l_sch_dt := last_day(add_months(TRUNC(SYSDATE), -1)) + p_sch_day;
1023 
1024         ELSE
1025            l_sch_dt := p_item_adj_tbl(i).schedule_date;
1026         END IF;
1027 
1028         IF l_trx_sysdate THEN
1029            l_trx_dt := TRUNC(SYSDATE);
1030         ELSE
1031            l_trx_dt := l_sch_dt;
1032         END IF;
1033 
1034         l_item_dtl_tbl(i).schedule_date := l_sch_dt;
1035         l_item_dtl_tbl(i).trx_date      := l_trx_dt;
1036         l_item_dtl_tbl(i).start_date    := p_item_adj_tbl(i).start_date;
1037         l_item_dtl_tbl(i).end_date      := p_item_adj_tbl(i).end_date;
1038         l_item_dtl_tbl(i).amount        := p_item_adj_tbl(i).amount;
1039 
1040      END IF;
1041 
1042   END LOOP;
1043 
1044   IF l_use_crnt_month AND l_consolidate AND l_total_amt <> 0 THEN
1045 
1046      l_item_dtl_tbl(0).schedule_date := last_day(add_months(TRUNC(SYSDATE), -1)) + p_sch_day;
1047      l_item_dtl_tbl(0).start_date    := p_item_adj_tbl(0).start_date;
1048      l_item_dtl_tbl(0).end_date      := p_item_adj_tbl(p_item_adj_tbl.COUNT - 1).end_date;
1049      l_item_dtl_tbl(0).amount        := l_total_amt;
1050 
1051      IF l_trx_sysdate THEN
1052         l_item_dtl_tbl(0).trx_date   := TRUNC(SYSDATE);
1053      ELSE
1054         l_item_dtl_tbl(0).trx_date   := l_item_dtl_tbl(0).schedule_date;
1055      END IF;
1056 
1057   END IF;
1058 
1059   p_item_adj_tbl := l_item_dtl_tbl;
1060 
1061   pnp_debug_pkg.log(l_desc ||' (-)');
1062 
1063 EXCEPTION
1064   WHEN OTHERS THEN
1065      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1066      raise;
1067 
1068 END prepare_new_items_from_adj;
1069 
1070 ------------------------------------------------------------------------------+
1071 -- PROCEDURE   : find_schedule
1072 -- DESCRIPTION : finds a draft schedule for a given schedule date for a lease
1073 --               OR creates a new draft schedule if none is found.
1074 -- HISTORY     :
1075 -- 19-OCT-04  ftanudja  o Created.
1076 -- 15-JUL-05  SatyaDeep o Replaced base views with their _ALL tables
1077 -- 10-AUG-05  piagrawa  o Bug #4284035 - Passed org id of the lease to insert_row
1078 ------------------------------------------------------------------------------+
1079 PROCEDURE find_schedule (
1080             p_lease_id        pn_leases.lease_id%TYPE,
1084             p_schedule_id     OUT NOCOPY pn_payment_schedules.payment_schedule_id%TYPE
1081             p_lease_change_id pn_lease_changes.lease_change_id%TYPE,
1082             p_term_id         pn_payment_terms.payment_term_id%TYPE,
1083             p_schedule_date   pn_payment_schedules.schedule_date%TYPE,
1085 )
1086 IS
1087   CURSOR fetch_schedule IS
1088    SELECT payment_schedule_id
1089      FROM pn_payment_schedules_all
1090     WHERE schedule_date = p_schedule_date
1091       AND lease_id = p_lease_id
1092       AND payment_status_lookup_code = 'DRAFT';
1093 
1094   CURSOR check_if_sch_belong_to_term(p_sch_id pn_payment_schedules.payment_schedule_id%TYPE) IS
1095    SELECT 'Y'
1096      FROM dual
1097     WHERE EXISTS (SELECT NULL
1098                     FROM pn_payment_items_all
1099                    WHERE payment_schedule_id = p_sch_id
1100                      AND payment_term_id = p_term_id);
1101 
1102   CURSOR org_id_cur IS
1103    SELECT org_id
1104    FROM pn_leases_all
1105    WHERE lease_id = p_lease_id;
1106 
1107   l_rowid        VARCHAR2(100);
1108   l_found        BOOLEAN := FALSE;
1109 
1110   l_info         VARCHAR2(100);
1111   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.find_schedule';
1112   l_org_id       NUMBER;
1113 
1114 BEGIN
1115 
1116   pnp_debug_pkg.log(l_desc ||' (+)');
1117 
1118   l_info:= ' finding draft schedules for date: '||p_schedule_date;
1119   pnp_debug_pkg.log(l_info);
1120 
1121   FOR org_id_rec IN org_id_cur LOOP
1122      l_org_id := org_id_rec.org_id;
1123   END LOOP;
1124 
1125   FOR schedule_rec IN fetch_schedule LOOP
1126 
1127      IF l_found = FALSE THEN
1128 
1129         l_found := TRUE;
1130         p_schedule_id := schedule_rec.payment_schedule_id;
1131 
1132         l_info := ' getting draft schedule id: '||p_schedule_id;
1133         pnp_debug_pkg.log(l_info);
1134 
1135      ELSE -- if multiple schedules find
1136 
1137         l_info := ' checking multiple schedules for : '||p_schedule_date;
1138         pnp_debug_pkg.log(l_info);
1139 
1140         FOR get_id_rec IN check_if_sch_belong_to_term(schedule_rec.payment_schedule_id) LOOP
1141            p_schedule_id := schedule_rec.payment_schedule_id;
1142         END LOOP;
1143 
1144      END IF;
1145 
1146   END LOOP;
1147 
1148   IF NOT l_found THEN
1149      l_info:= ' inserting a new draft schedule for date: '||p_schedule_date;
1150      pnp_debug_pkg.log(l_info);
1151 
1152      pnt_payment_schedules_pkg.insert_row(
1153         x_context                     => null,
1154         x_rowid                       => l_rowid,
1155         x_payment_schedule_id         => p_schedule_id,
1156         x_schedule_date               => p_schedule_date,
1157         x_lease_change_id             => p_lease_change_id,
1158         x_lease_id                    => p_lease_id,
1159         x_approved_by_user_id         => null,
1160         x_transferred_by_user_ID      => null,
1161         x_payment_status_lookup_code  => 'DRAFT',
1162         x_approval_date               => null,
1163         x_transfer_date               => null,
1164         x_period_name                 => null,
1165         x_attribute_category          => null,
1166         x_attribute1                  => null,
1167         x_attribute2                  => null,
1168         x_attribute3                  => null,
1169         x_attribute4                  => null,
1170         x_attribute5                  => null,
1171         x_attribute6                  => null,
1172         x_attribute7                  => null,
1173         x_attribute8                  => null,
1174         x_attribute9                  => null,
1175         x_attribute10                 => null,
1176         x_attribute11                 => null,
1177         x_attribute12                 => null,
1178         x_attribute13                 => null,
1179         x_attribute14                 => null,
1180         x_attribute15                 => null,
1181         x_creation_date               => SYSDATE,
1182         x_created_by                  => fnd_global.user_id,
1183         x_last_update_date            => SYSDATE,
1184         x_last_updated_by             => fnd_global.user_id,
1185         x_last_update_login           => fnd_global.login_id,
1186         x_org_id                      => l_org_id
1187      );
1188 
1189   END IF;
1190 
1191   pnp_debug_pkg.log(l_desc ||' (-)');
1192 
1193 EXCEPTION
1194   WHEN OTHERS THEN
1195      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1196      raise;
1197 
1198 END find_schedule;
1199 
1200 ------------------------------------------------------------------------------+
1201 -- PROCEDURE   : get_schedule_id_for_new_items
1202 -- DESCRIPTION : calls pn_schedules_items.create_schedule for every schedule
1203 --               date in the table and returns the schedule id to the same
1204 --               table.
1205 -- NOTE        : This is dependent on pn_schedules_items.create_schedule()
1206 -- HISTORY     :
1207 -- 05-OCT-04 ftanudja o Created.
1208 ------------------------------------------------------------------------------+
1209 PROCEDURE get_schedule_id_for_new_items(
1210             p_lease_id        pn_leases.lease_id%TYPE,
1211             p_term_id         pn_payment_terms.payment_term_id%TYPE,
1212             p_lease_change_id pn_lease_changes.lease_change_id%TYPE,
1213             p_sched_tbl       IN OUT NOCOPY payment_item_tbl_type
1214 )
1215 IS
1216   l_info         VARCHAR2(100);
1217   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.get_schedule_id_for_new_items';
1218 
1219 BEGIN
1220 
1221   pnp_debug_pkg.log(l_desc ||' (+)');
1222 
1223   l_info := ' starting loop ';
1224   pnp_debug_pkg.log(l_info);
1225 
1226   FOR i IN 0 .. p_sched_tbl.COUNT - 1 LOOP
1227 
1228      l_info := ' finding schedule for '||p_sched_tbl(i).schedule_date ;
1229      pnp_debug_pkg.log(l_info);
1230 
1231      find_schedule(
1232         p_lease_id        => p_lease_id,
1233         p_lease_change_id => p_lease_change_id,
1234         p_term_id         => p_term_id,
1235         p_schedule_date   => p_sched_tbl(i).schedule_date,
1236         p_schedule_id     => p_sched_tbl(i).schedule_id
1237      );
1238 
1239   END LOOP;
1240 
1241   pnp_debug_pkg.log(l_desc ||' (-)');
1242 
1243 EXCEPTION
1244   WHEN OTHERS THEN
1245      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1246      raise;
1247 
1248 END get_schedule_id_for_new_items;
1249 
1250 ------------------------------------------------------------------------------+
1251 -- PROCEDURE   : remove_item_reference
1252 -- DESCRIPTION : takes a table containing payment id and remove all reference
1253 --               to it from the pn_adjustment_details table.
1254 -- HISTORY     :
1255 -- 05-OCT-04 ftanudja o Created.
1256 ------------------------------------------------------------------------------+
1257 
1258 PROCEDURE remove_item_reference (
1259             p_item_tbl payment_item_tbl_type
1260 )
1261 IS
1262 
1263   l_payment_id_tbl item_id_tbl_type;
1264 
1265   l_info           VARCHAR2(100);
1266   l_desc           VARCHAR2(100) := 'pn_retro_adjustment_pkg.remove_item_reference';
1267 
1268 BEGIN
1269 
1270   pnp_debug_pkg.log(l_desc ||' (+)');
1271 
1272   l_info := ' preparing for bulk update ';
1273   pnp_debug_pkg.log(l_info);
1274 
1275   FOR i IN 0 .. p_item_tbl.COUNT - 1 LOOP
1276      l_payment_id_tbl(i) := p_item_tbl(i).item_id;
1277   END LOOP;
1278 
1279   l_info := ' performing bulk update ';
1280   pnp_debug_pkg.log(l_info);
1281 
1282   FORALL i IN 0 .. l_payment_id_tbl.COUNT - 1
1283     UPDATE pn_adjustment_details
1284        SET payment_item_id   = null,
1285            last_update_date  = SYSDATE,
1286            last_updated_by   = fnd_global.user_id,
1287            last_update_login = fnd_global.login_id
1288      WHERE payment_item_id = l_payment_id_tbl(i);
1289 
1290   pnp_debug_pkg.log(l_desc ||' (-)');
1291 
1292 EXCEPTION
1293   WHEN OTHERS THEN
1294      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1295      raise;
1296 
1297 END remove_item_reference;
1298 
1299 ------------------------------------------------------------------------------+
1300 -- PROCEDURE   : process_items
1301 -- DESCRIPTION : Takes 3 tables for UPDATE, DELETE, and INSERT operation
1302 --               into the pn_payment_items table. Does BULK operations for
1303 --               efficiency.
1304 -- HISTORY     :
1305 -- 05-OCT-04 ftanudja o Created.
1306 -- 15-JUL-05  SatyaDeep o Replaced base views with their _ALL tables
1307 ------------------------------------------------------------------------------+
1308 PROCEDURE process_items(
1309             p_term_id      pn_payment_terms.payment_term_id%TYPE,
1310             p_adj_type_cd  pn_payment_items.last_adjustment_type_code%TYPE,
1311             p_upd_item_tbl payment_item_tbl_type,
1312             p_del_item_tbl payment_item_tbl_type,
1313             p_new_item_tbl IN OUT NOCOPY payment_item_tbl_type
1314 )
1315 IS
1316 
1317   CURSOR get_term_data IS
1318    SELECT vendor_id,
1319           vendor_site_id,
1320           customer_id,
1321           customer_site_use_id,
1322           cust_ship_site_id,
1323           set_of_books_id,
1324           currency_code,
1325           rate,
1326           estimated_amount,
1327           org_id
1328      FROM pn_payment_terms_all
1329     WHERE payment_term_id = p_term_id;
1330 
1331   l_new_itm_id_tbl        item_id_tbl_type;
1332   l_payment_id_tbl        item_id_tbl_type;
1333   l_sched_id_tbl          sched_id_tbl_type;
1334   l_act_amt_tbl           amt_tbl_type;
1335   l_est_amt_tbl           amt_tbl_type;
1336   l_trx_date_tbl          date_tbl_type;
1337   l_start_date_tbl        date_tbl_type;
1338   l_end_date_tbl          date_tbl_type;
1339 
1340   l_vendor_id             pn_payment_terms.vendor_id%TYPE;
1341   l_vendor_site_id        pn_payment_terms.vendor_site_id%TYPE;
1342   l_customer_id           pn_payment_terms.customer_id%TYPE;
1343   l_customer_site_use_id  pn_payment_terms.customer_site_use_id%TYPE;
1344   l_cust_ship_site_id     pn_payment_terms.cust_ship_site_id%TYPE;
1345   l_set_of_books_id       pn_payment_terms.set_of_books_id%TYPE;
1346   l_currency_code         pn_payment_terms.currency_code%TYPE;
1347   l_rate                  pn_payment_terms.rate%TYPE;
1348 
1349   l_precision             NUMBER;
1350   l_ext_precision         NUMBER;
1351   l_min_acct_unit         NUMBER;
1352 
1353   l_has_est_amt           BOOLEAN;
1354 
1355   l_info                  VARCHAR2(100);
1356   l_desc                  VARCHAR2(100) := 'pn_retro_adjustment_pkg.process_items';
1357   l_org_id                NUMBER;
1358 
1359 BEGIN
1360 
1361   pnp_debug_pkg.log(l_desc ||' (+)');
1362 
1363   l_info := ' updating items ';
1364   pnp_debug_pkg.log(l_info);
1365 
1366   FOR i IN 0 .. p_upd_item_tbl.COUNT - 1 LOOP
1367     l_act_amt_tbl(i)    := p_upd_item_tbl(i).amount;
1368     l_payment_id_tbl(i) := p_upd_item_tbl(i).item_id;
1369     IF l_has_est_amt THEN
1370        l_est_amt_tbl(i) := p_upd_item_tbl(i).amount;
1371     ELSE
1372        l_est_amt_tbl(i) := null;
1373     END IF;
1374   END LOOP;
1375 
1376   l_info := ' preparing for bulk update ';
1377   pnp_debug_pkg.log(l_info);
1378 
1379   FOR term_rec IN get_term_data LOOP
1380 
1381     l_currency_code := term_rec.currency_code;
1382     fnd_currency.get_info(  l_currency_code
1383                           , l_precision
1384                           , l_ext_precision
1385                           , l_min_acct_unit);
1386 
1387     EXIT;
1388   END LOOP;
1389 
1390   FORALL i IN 0 .. l_payment_id_tbl.COUNT - 1
1391     UPDATE pn_payment_items_all
1392        SET actual_amount     = ROUND(l_act_amt_tbl(i), l_precision),
1393            estimated_amount  = ROUND(l_est_amt_tbl(i), l_precision),
1394            last_update_date  = SYSDATE,
1395            last_updated_by   = fnd_global.user_id,
1396            last_update_login = fnd_global.login_id
1397      WHERE payment_item_id   = l_payment_id_tbl(i);
1398 
1399   l_info := ' deleting items ';
1400   pnp_debug_pkg.log(l_info);
1401 
1402   l_payment_id_tbl.delete;
1403 
1404   FOR i IN 0 .. p_del_item_tbl.COUNT - 1 LOOP
1405     l_payment_id_tbl(i)  := p_del_item_tbl(i).item_id;
1406   END LOOP;
1407 
1408   l_info := ' preparing for bulk delete ';
1409   pnp_debug_pkg.log(l_info);
1410 
1411   FORALL i IN 0 .. l_payment_id_tbl.COUNT - 1
1412     DELETE pn_payment_items
1413      WHERE payment_item_id = l_payment_id_tbl(i);
1414 
1415   l_info := ' creating items ';
1416   pnp_debug_pkg.log(l_info);
1417 
1418   l_payment_id_tbl.delete;
1419   l_act_amt_tbl.delete;
1420   l_est_amt_tbl.delete;
1421   l_has_est_amt := FALSE;
1422 
1423   l_info := ' fetching term details ';
1424   pnp_debug_pkg.log(l_info);
1425 
1426   FOR term_rec IN get_term_data LOOP
1427 
1428     l_vendor_id             := term_rec.vendor_id;
1429     l_vendor_site_id        := term_rec.vendor_site_id;
1430     l_customer_id           := term_rec.customer_id;
1431     l_customer_site_use_id  := term_rec.customer_site_use_id;
1432     l_cust_ship_site_id     := term_rec.cust_ship_site_id;
1433     l_set_of_books_id       := term_rec.set_of_books_id;
1434     l_currency_code         := term_rec.currency_code;
1435     l_rate                  := term_rec.rate;
1436     l_org_id                := term_rec.org_id;
1437     IF term_rec.estimated_amount IS NOT NULL THEN
1438        l_has_est_amt        := TRUE;
1439     END IF;
1440 
1441     fnd_currency.get_info(l_currency_code, l_precision, l_ext_precision, l_min_acct_unit);
1442 
1443     EXIT;
1444   END LOOP;
1445 
1446   l_info := ' preparing for bulk insert ';
1447   pnp_debug_pkg.log(l_info);
1448 
1449   FOR i IN 0 .. p_new_item_tbl.COUNT - 1 LOOP
1450      l_sched_id_tbl(i)    := p_new_item_tbl(i).schedule_id;
1451      l_act_amt_tbl(i)     := p_new_item_tbl(i).amount;
1452      l_trx_date_tbl(i)    := p_new_item_tbl(i).trx_date;
1453      l_start_date_tbl(i)  := p_new_item_tbl(i).start_date;
1454      l_end_date_tbl(i)    := p_new_item_tbl(i).end_date;
1455 
1456      IF l_has_est_amt THEN
1457         l_est_amt_tbl(i)  := p_new_item_tbl(i).amount;
1458      ELSE
1459         l_est_amt_tbl(i)  := null;
1460      END IF;
1461 
1462   END LOOP;
1463 
1464   FORALL i IN 0 .. l_sched_id_tbl.COUNT - 1
1465     INSERT INTO pn_payment_items_all
1466     (
1467        payment_item_id,
1468        last_update_date,
1469        last_updated_by,
1470        creation_date,
1471        created_by,
1472        last_update_login,
1473        actual_amount,
1474        estimated_amount,
1475        due_date,
1476        adj_start_date,
1477        adj_end_date,
1478        last_adjustment_type_code,
1479        payment_item_type_lookup_code,
1480        payment_term_id,
1481        payment_schedule_id,
1482        period_fraction,
1483        vendor_id,
1484        customer_id,
1485        vendor_site_id,
1486        customer_site_use_id,
1487        cust_ship_site_id,
1488        set_of_books_id,
1489        currency_code,
1490        export_currency_code,
1491        export_currency_amount,
1492        rate,
1493        org_id
1494     )
1495     VALUES
1496     (
1497        pn_payment_items_s.nextval,
1498        SYSDATE,
1499        fnd_global.user_id,
1500        SYSDATE,
1501        fnd_global.user_id,
1502        fnd_global.login_id,
1503        ROUND(l_act_amt_tbl(i), l_precision),
1504        ROUND(l_est_amt_tbl(i), l_precision),
1505        l_trx_date_tbl(i),
1506        l_start_date_tbl(i),
1507        l_end_date_tbl(i),
1508        p_adj_type_cd,
1509        'CASH',
1510        p_term_id,
1511        l_sched_id_tbl(i),
1512        1,
1513        l_vendor_id,
1514        l_customer_id,
1515        l_vendor_site_id,
1516        l_customer_site_use_id,
1517        l_cust_ship_site_id,
1518        l_set_of_books_id,
1519        l_currency_code,
1520        l_currency_code,
1521        null,
1522        l_rate,
1523        l_org_id
1524      ) RETURNING payment_item_id BULK COLLECT INTO l_new_itm_id_tbl;
1525 
1526   -- NOTE: l_new_itm_id_tbl is populated starting from (1), not (0) --
1527 
1528   l_info := ' updating p_new_item_tbl with newly inserted item id ';
1529   pnp_debug_pkg.log(l_info);
1530 
1531   FOR i IN 0 .. p_new_item_tbl.COUNT - 1 LOOP
1532      p_new_item_tbl(i).item_id := l_new_itm_id_tbl(i + 1);
1533   END LOOP;
1534 
1535   pnp_debug_pkg.log(l_desc ||' (-)');
1536 
1537 EXCEPTION
1538   WHEN OTHERS THEN
1539      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1540      raise;
1541 
1542 END process_items;
1543 
1544 ------------------------------------------------------------------------------+
1545 -- PROCEDURE   : populate_new_item_id
1546 -- DESCRIPTION : puts newly inserted payment item ID's into adjustment table
1547 --               by doing a simple bubble search
1548 -- NOTES       : the procedure assumes both tables are ordered by dates
1549 -- HISTORY     :
1550 -- 07-OCT-04 ftanudja o Created.
1551 ------------------------------------------------------------------------------+
1552 PROCEDURE populate_new_item_id(
1553             p_new_item_tbl payment_item_tbl_type,
1554             p_adj_tbl      IN OUT NOCOPY payment_item_tbl_type
1555 )
1556 IS
1557   l_mark       NUMBER := 0;
1558 
1559   l_info       VARCHAR2(100);
1560   l_desc       VARCHAR2(100) := 'pn_retro_adjustment_pkg.populate_new_item_id';
1561 
1562 BEGIN
1563 
1564   pnp_debug_pkg.log(l_desc ||' (+)');
1565 
1566   l_info := ' starting loop ';
1567   pnp_debug_pkg.log(l_info);
1568 
1569   FOR i IN 0 .. p_adj_tbl.COUNT - 1 LOOP
1570 
1571      IF p_adj_tbl(i).item_id IS NULL THEN
1572 
1573         l_info := ' looping through adjustment table for start date '||p_adj_tbl(i).start_date||
1574                   ' and end date '||p_adj_tbl(i).end_date;
1575         pnp_debug_pkg.log(l_info);
1576 
1577         FOR j IN l_mark .. p_new_item_tbl.COUNT - 1 LOOP
1578 
1579            IF p_new_item_tbl(j).start_date <= p_adj_tbl(i).start_date AND
1580               p_new_item_tbl(j).end_date >= p_adj_tbl(i).end_date
1581            THEN
1582 
1583               l_info := ' found item match with start date '||p_new_item_tbl(j).start_date||
1584                        ' and end date '||p_new_item_tbl(j).end_date;
1585               pnp_debug_pkg.log(l_info);
1586 
1587               p_adj_tbl(i).item_id := p_new_item_tbl(j).item_id;
1588               l_mark := j;
1589               exit;
1590            END IF;
1591 
1592         END LOOP;
1593 
1594      END IF;
1595 
1596   END LOOP;
1597 
1598   pnp_debug_pkg.log(l_desc ||' (-)');
1599 
1600 EXCEPTION
1601   WHEN OTHERS THEN
1602      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1603      raise;
1604 
1605 END populate_new_item_id;
1606 
1607 ------------------------------------------------------------------------------+
1608 -- PROCEDURE   : create_adjustment_entries
1609 -- DESCRIPTION : creates a new batch of adjustment entries for the current
1610 --               term history
1611 -- HISTORY     :
1612 -- 06-OCT-04 ftanudja o Created.
1613 -- 10-AUG-05 piagrawa o Bug#4284035 - Modified the signature to pass org id.
1614 ------------------------------------------------------------------------------+
1615 PROCEDURE create_adjustment_entries(
1616             p_term_id        pn_payment_terms.payment_term_id%TYPE,
1617             p_term_freq      pn_payment_terms.frequency_code%TYPE,
1618             p_term_start_dt  pn_payment_terms.start_date%TYPE,
1619             p_term_end_dt    pn_payment_terms.end_date%TYPE,
1620             p_term_hist_id   pn_payment_terms_history.term_history_id%TYPE,
1621             p_adj_table      payment_item_tbl_type,
1622             p_org_id         NUMBER
1623 )
1624 IS
1625   l_start_date   pn_adjustment_details.adj_start_date%TYPE;
1626   l_end_date     pn_adjustment_details.adj_end_date%TYPE;
1627   l_adj_summ_id  pn_adjustment_summaries.adjustment_summary_id%TYPE;
1628 
1629   l_group_num    NUMBER := 0;
1630   l_consolidate  BOOLEAN;
1631 
1632   l_info         VARCHAR2(100);
1633   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.create_adjustment_entries';
1634 
1635 BEGIN
1636 
1637   pnp_debug_pkg.log(l_desc ||' (+)');
1638 
1639   l_info := ' preparing adjustment data ';
1640   pnp_debug_pkg.log(l_info);
1641 
1642   IF pn_mo_cache_utils.get_profile_value('PN_USE_SYSDATE_FOR_ADJ', p_org_id) = 'Y' AND
1643      pn_mo_cache_utils.get_profile_value('PN_CONSOLIDATE_ADJ_ITEMS', p_org_id) = 'Y' THEN
1644      l_consolidate := TRUE;
1645   ELSE
1646      l_consolidate := FALSE;
1647   END IF;
1648 
1649   FOR i IN 0 .. p_adj_table.COUNT - 1 LOOP
1650 
1651      IF p_adj_table(i).adj_summ_id IS NULL THEN
1652 
1653        l_info := ' inserting into adjustment summary table for schedule date:'||
1654                    p_adj_table(i).schedule_date;
1655        pnp_debug_pkg.log(l_info);
1656 
1657        INSERT INTO pn_adjustment_summaries (
1658           adjustment_summary_id,
1659           adj_schedule_date,
1660           payment_term_id,
1661           sum_adj_amount,
1662           creation_date,
1663           created_by,
1664           last_update_date,
1665           last_updated_by,
1666           last_update_login
1667        ) VALUES (
1668           pn_adjustment_summaries_s.nextval,
1669           p_adj_table(i).schedule_date,
1670           p_term_id,
1671           p_adj_table(i).amount,
1672           SYSDATE,
1673           fnd_global.user_id,
1674           SYSDATE,
1675           fnd_global.user_id,
1676           fnd_global.login_id
1677        ) RETURNING adjustment_summary_id INTO l_adj_summ_id;
1678 
1679      ELSE
1680 
1681         l_adj_summ_id := p_adj_table(i).adj_summ_id;
1682 
1683      END IF;
1684 
1685      IF p_adj_table(i).start_date IS NULL OR p_adj_table(i).end_date IS NULL THEN
1686 
1687         l_info := ' figuring out start and end dates for schedule date:'||
1688                     p_adj_table(i).schedule_date;
1689         pnp_debug_pkg.log(l_info);
1690 
1691         find_start_end_dates(
1692            p_term_freq     => p_term_freq,
1693            p_term_start_dt => p_term_start_dt,
1694            p_term_end_dt   => p_term_end_dt,
1695            p_schedule_dt   => p_adj_table(i).schedule_date,
1696            x_start_date    => l_start_date,
1697            x_end_date      => l_end_date
1698         );
1699      ELSE
1700 
1701         l_start_date := p_adj_table(i).start_date;
1702         l_end_date   := p_adj_table(i).end_date;
1703 
1704      END IF;
1705 
1706      l_info := ' finding system options to determine group num ';
1707      pnp_debug_pkg.log(l_info);
1708 
1709      IF NOT l_consolidate THEN
1710         l_group_num := l_group_num + 1;
1711      END IF;
1712 
1713      l_info := ' inserting new adjustment for schedule date:'||
1714                  p_adj_table(i).schedule_date;
1715      pnp_debug_pkg.log(l_info);
1716 
1717      INSERT INTO pn_adjustment_details (
1718         adjustment_detail_id,
1719         term_history_id,
1720         adjustment_summary_id,
1721         payment_item_id,
1722         adj_start_date,
1723         adj_end_date,
1724         adjustment_amount,
1725         group_num,
1726         creation_date,
1727         created_by,
1728         last_update_date,
1729         last_updated_by,
1730         last_update_login
1731      ) VALUES (
1732         pn_adjustment_details_s.nextval,
1733         p_term_hist_id,
1734         l_adj_summ_id,
1735         p_adj_table(i).item_id,
1736         l_start_date,
1737         l_end_date,
1738         p_adj_table(i).amount,
1739         l_group_num,
1740         SYSDATE,
1741         fnd_global.user_id,
1742         SYSDATE,
1743         fnd_global.user_id,
1744         fnd_global.login_id
1745      );
1746 
1747      IF p_adj_table(i).adj_summ_id IS NOT NULL THEN
1748 
1749         l_info := ' updating adjustment summary id:'||
1750                     p_adj_table(i).adj_summ_id;
1751         pnp_debug_pkg.log(l_info);
1752 
1753         UPDATE pn_adjustment_summaries
1754            SET sum_adj_amount        = sum_adj_amount + p_adj_table(i).amount,
1755                last_update_date      = SYSDATE,
1756                last_updated_by       = fnd_global.user_id,
1757                last_update_login     = fnd_global.login_id
1758          WHERE adjustment_summary_id = p_adj_table(i).adj_summ_id;
1759 
1760      END IF;
1761 
1762   END LOOP;
1763 
1764   pnp_debug_pkg.log(l_desc ||' (-)');
1765 
1766 EXCEPTION
1767   WHEN OTHERS THEN
1768      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
1769      raise;
1770 
1771 END create_adjustment_entries;
1772 
1773 
1774 ------------------------------------------------------------------------------+
1775 -- PROCEDURE     : cleanup_schedules
1776 -- DESCRIPTION   : Given a lease id and lease end date it clean up schedules.
1777 --                 Delete schedules with no items.Also deletes the draft schedules
1778 --                 which lie outside the lease.
1779 --  PURPOSE      :
1780 --  INVOKED FROM : schedules_items.mini_retro_contraction
1781 --  ARGUMENTS    : p_lease_id
1782 --  HISTORY      :
1783 --  08-OCT-04  piagrawa  o Bug 4354810 - Overloaded for mini -retro.
1784 --  04-APR-06  piagrawa  o Bug#5107134 - modified schedules_draft_cur to include
1785 --                          status 'ON_HOLD'
1786 ------------------------------------------------------------------------------+
1787 PROCEDURE cleanup_schedules(p_lease_id        pn_leases_all.lease_id%TYPE)
1788 IS
1789 
1790    CURSOR schedules_draft_cur IS
1791      SELECT payment_schedule_id
1792      FROM pn_payment_schedules_all
1793      WHERE lease_id = p_lease_id
1794      AND payment_status_lookup_code IN ('DRAFT', 'ON_HOLD');
1795 
1796    CURSOR find_payment_items_cur (p_sch_id pn_payment_schedules.payment_schedule_id%TYPE)IS
1797       SELECT payment_item_id
1798       FROM pn_payment_items_all  item
1799       WHERE item.payment_schedule_id = p_sch_id;
1800 
1801   l_found  BOOLEAN;
1802 
1803 BEGIN
1804    pnp_debug_pkg.log('cleanup_schedules   (+)');
1805 
1806    FOR schedules_draft_rec IN schedules_draft_cur LOOP
1807 
1808      l_found := FALSE;
1809 
1810      FOR find_payment_items_rec IN find_payment_items_cur(schedules_draft_rec.payment_schedule_id) LOOP
1811         l_found := TRUE;
1812      END LOOP;
1813 
1814      IF(l_found = FALSE) THEN
1815 
1816         pnp_debug_pkg.log('Deleting schedule id ........'||schedules_draft_rec.payment_schedule_id);
1817 
1818         DELETE pn_payment_schedules_all
1819         WHERE payment_schedule_id = schedules_draft_rec.payment_schedule_id;
1820 
1821      END IF;
1822 
1823    END LOOP;
1824 
1825    pnp_debug_pkg.log('cleanup_schedules   (-)');
1826 
1827 END cleanup_schedules;
1828 
1829 ------------------------------------------------------------------------------+
1830 -- PROCEDURE   : cleanup_schedules
1831 -- DESCRIPTION : Given a list of schedule id's, clean up schedules. Delete
1832 --               schedules with no items. Create 0 cash item for schedules
1833 --               with no cash items.
1834 -- HISTORY     :
1835 -- 08-OCT-04 ftanudja o Created.
1836 -- 15-JUL-05  SatyaDeep o Replaced base views with their _ALL tables
1837 ------------------------------------------------------------------------------+
1838 PROCEDURE cleanup_schedules(
1839             p_term_id       pn_payment_terms.payment_term_id%TYPE,
1840             p_orig_item_tbl payment_item_tbl_type,
1841             p_adj_item_tbl  payment_item_tbl_type
1842 )
1843 IS
1844 
1845   CURSOR find_cash_items (p_sch_id pn_payment_schedules.payment_schedule_id%TYPE)IS
1846    SELECT SUM(DECODE(item.payment_item_type_lookup_code, 'CASH', 1, 0)) num_cash
1847      FROM pn_payment_items_all  item
1848     WHERE item.payment_schedule_id = p_sch_id;
1849 
1850   CURSOR get_term_data IS
1851    SELECT vendor_id,
1852           vendor_site_id,
1853           customer_id,
1854           customer_site_use_id,
1855           cust_ship_site_id,
1856           set_of_books_id,
1857           currency_code,
1858           rate,
1859           estimated_amount,
1860           org_id
1861      FROM pn_payment_terms_all
1862     WHERE payment_term_id = p_term_id;
1863 
1864   l_vendor_id             pn_payment_terms.vendor_id%TYPE;
1865   l_vendor_site_id        pn_payment_terms.vendor_site_id%TYPE;
1866   l_customer_id           pn_payment_terms.customer_id%TYPE;
1867   l_customer_site_use_id  pn_payment_terms.customer_site_use_id%TYPE;
1868   l_cust_ship_site_id     pn_payment_terms.cust_ship_site_id%TYPE;
1869   l_set_of_books_id       pn_payment_terms.set_of_books_id%TYPE;
1870   l_currency_code         pn_payment_terms.currency_code%TYPE;
1871   l_rate                  pn_payment_terms.rate%TYPE;
1872 
1873   l_sched_id_tbl          sched_id_tbl_type;
1874   l_sched_dt_tbl          date_tbl_type;
1875   l_found                 BOOLEAN;
1876   l_num_item              NUMBER;
1877 
1878   l_info                  VARCHAR2(100);
1879   l_desc                  VARCHAR2(100) := 'pn_retro_adjustment_pkg.cleanup_schedules';
1880   l_org_id                NUMBER;
1881 
1882 BEGIN
1883 
1884   pnp_debug_pkg.log(l_desc ||' (+)');
1885 
1886   l_info := ' looping through original items table ';
1887   pnp_debug_pkg.log(l_info);
1888 
1889   FOR i IN 0 .. p_orig_item_tbl.COUNT - 1 LOOP
1890      l_sched_id_tbl(i) := p_orig_item_tbl(i).schedule_id;
1891      l_sched_dt_tbl(i) := p_orig_item_tbl(i).schedule_date;
1892   END LOOP;
1893 
1894   l_info := ' looping through adjustment items table ';
1895   pnp_debug_pkg.log(l_info);
1896 
1897   FOR i IN 0 .. p_adj_item_tbl.COUNT - 1 LOOP
1898 
1899      l_found := FALSE;
1900 
1901      FOR j IN 0 .. l_sched_id_tbl.COUNT - 1 LOOP
1902 
1903         IF l_sched_id_tbl(j) = p_adj_item_tbl(i).schedule_id THEN
1907      END LOOP;
1904            l_found := TRUE;
1905         END IF;
1906 
1908 
1909      IF NOT l_found THEN
1910         l_sched_id_tbl(l_sched_id_tbl.COUNT) := p_adj_item_tbl(i).schedule_id;
1911         l_sched_dt_tbl(l_sched_dt_tbl.COUNT) := p_adj_item_tbl(i).schedule_date;
1912      END IF;
1913 
1914   END LOOP;
1915 
1916   l_info := ' looping through schedule id table ';
1917   pnp_debug_pkg.log(l_info);
1918 
1919   FOR i IN 0 .. l_sched_id_tbl.COUNT - 1 LOOP
1920 
1921      l_found := FALSE;
1922 
1923      l_info := ' looping through schedule id table ';
1924      pnp_debug_pkg.log(l_info);
1925 
1926      FOR items_rec IN find_cash_items(l_sched_id_tbl(i)) LOOP
1927         l_found    := TRUE;
1928         l_num_item := items_rec.num_cash;
1929      END LOOP;
1930 
1931      IF l_found AND l_num_item = 0 THEN
1932 
1933         l_info := ' inserting $0 cash item onto schedule id: '||l_sched_id_tbl(i);
1934 
1935         pnp_debug_pkg.log(l_info);
1936 
1937         FOR term_rec IN get_term_data LOOP
1938 
1939           l_vendor_id             := term_rec.vendor_id;
1940           l_vendor_site_id        := term_rec.vendor_site_id;
1941           l_customer_id           := term_rec.customer_id;
1942           l_customer_site_use_id  := term_rec.customer_site_use_id;
1943           l_cust_ship_site_id     := term_rec.cust_ship_site_id;
1944           l_set_of_books_id       := term_rec.set_of_books_id;
1945           l_currency_code         := term_rec.currency_code;
1946           l_rate                  := term_rec.rate;
1947           l_org_id                := term_rec.org_id;
1948           EXIT;
1949 
1950         END LOOP;
1951 
1952         INSERT INTO pn_payment_items_all
1953         (
1954            payment_item_id,
1955            last_update_date,
1956            last_updated_by,
1957            creation_date,
1958            created_by,
1959            last_update_login,
1960            actual_amount,
1961            estimated_amount,
1962            due_date,
1963            adj_start_date,
1964            adj_end_date,
1965            payment_item_type_lookup_code,
1966            payment_term_id,
1967            payment_schedule_id,
1968            period_fraction,
1969            vendor_id,
1970            customer_id,
1971            vendor_site_id,
1972            customer_site_use_id,
1973            cust_ship_site_id,
1974            set_of_books_id,
1975            currency_code,
1976            export_currency_code,
1977            export_currency_amount,
1978            rate,
1979            org_id
1980         ) VALUES
1981         (
1982            pn_payment_items_s.nextval,
1983            SYSDATE,
1984            fnd_global.user_id,
1985            SYSDATE,
1986            fnd_global.user_id,
1987            fnd_global.login_id,
1988            0,
1989            null,
1990            l_sched_dt_tbl(i),
1991            null,
1992            null,
1993            'CASH',
1994            p_term_id,
1995            l_sched_id_tbl(i),
1996            1,
1997            l_vendor_id,
1998            l_customer_id,
1999            l_vendor_site_id,
2000            l_customer_site_use_id,
2001            l_cust_ship_site_id,
2002            l_set_of_books_id,
2003            l_currency_code,
2004            l_currency_code,
2005            null,
2006            l_rate,
2007            l_org_id
2008         );
2009 
2010      ELSIF NOT l_found THEN
2011 
2012         l_info := ' deleting schedule id : '||l_sched_id_tbl(i);
2013         pnp_debug_pkg.log(l_info);
2014 
2015         DELETE pn_payment_schedules_all
2016          WHERE payment_schedule_id = l_sched_id_tbl(i);
2017 
2018      END IF;
2019   END LOOP;
2020 
2021   pnp_debug_pkg.log(l_desc ||' (-)');
2022 
2023 EXCEPTION
2024   WHEN OTHERS THEN
2025      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
2026      raise;
2027 
2028 END cleanup_schedules;
2029 
2030 ------------------------------------------------------------------------------+
2031 -- PROCEDURE   : update_terms_history
2032 -- DESCRIPTION : updates the term history table with the latest adjustment
2033 --               type code.
2034 -- HISTORY     :
2035 -- 14-OCT-04 ftanudja o Created.
2036 -- 14-JAN-05 atuppad  o Added code to update total_adj_amount
2037 ------------------------------------------------------------------------------+
2038 PROCEDURE update_terms_history(
2039             p_term_hist_id     pn_payment_terms_history.term_history_id%TYPE,
2040             p_adj_type_cd      pn_payment_items.last_adjustment_type_code%TYPE,
2041             p_lease_change_id  pn_lease_changes.lease_change_id%TYPE,
2042             p_term_id          pn_payment_terms.payment_term_id%TYPE
2043 )
2044 IS
2045 
2046   -- Get total adj amount
2047   CURSOR get_total_adj_amt IS
2048     SELECT SUM(pad.adjustment_amount) total_adj_amount
2049     FROM   pn_adjustment_details pad,
2050            pn_payment_terms_history pth
2051     WHERE  pth.payment_term_id = p_term_id
2052     AND    pth.lease_change_id = p_lease_change_id
2053     AND    pad.term_history_id = pth.term_history_id;
2054 
2055   l_info         VARCHAR2(100);
2056   l_desc         VARCHAR2(100) := 'pn_retro_adjustment_pkg.update_terms_history';
2057   l_amount       NUMBER;
2058 
2059 BEGIN
2060 
2061   pnp_debug_pkg.log(l_desc ||' (+)');
2062 
2063   FOR amt_rec IN get_total_adj_amt LOOP
2064     l_amount := amt_rec.total_adj_amount;
2065   END LOOP;
2066 
2070          last_update_date     = SYSDATE,
2067   UPDATE pn_payment_terms_history
2068      SET adjustment_type_code = p_adj_type_cd,
2069          total_adj_amount     = l_amount,
2071          last_update_login    = fnd_global.login_id,
2072          last_updated_by      = fnd_global.user_id
2073    WHERE term_history_id      = p_term_hist_id;
2074 
2075   pnp_debug_pkg.log(l_desc ||' (-)');
2076 
2077 EXCEPTION
2078   WHEN OTHERS THEN
2079      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
2080      raise;
2081 
2082 END update_terms_history;
2083 
2084 ------------------------------------------------------------------------------+
2085 -- PROCEDURE   : create_retro_adjustments
2086 -- DESCRIPTION : This is the main procedure being called for retro adjustment
2087 --               changes.
2088 -- HISTORY     :
2089 -- 04-OCT-04 ftanudja o Created.
2090 -- 14-JAN-05 atuppad  o Changed the signature of below proc
2091 --                      - create_adjustment_tables
2092 --                      - update_terms_history
2093 -- 15-JUL-05  SatyaDeep o Replaced base views with their _ALL tables
2094 -- 10-AUG-05  piagrawa  o Bug #4284035 - Updated the calls to proc
2095 --                        prepare_new_items_from_adj and create_adjustment_entries
2096 --                        to pass org id.
2097 ------------------------------------------------------------------------------+
2098 PROCEDURE create_retro_adjustments(
2099             p_lease_id      pn_payment_terms.lease_id%TYPE,
2100             p_lease_chg_id  pn_lease_changes.lease_change_id%TYPE,
2101             p_term_id       pn_payment_terms.payment_term_id%TYPE,
2102             p_term_start_dt pn_payment_terms.start_date%TYPE,
2103             p_term_end_dt   pn_payment_terms.end_date%TYPE,
2104             p_term_sch_day  pn_payment_terms.schedule_day%TYPE,
2105             p_term_act_amt  pn_payment_terms.actual_amount%TYPE,
2106             p_term_freq     pn_payment_terms.frequency_code%TYPE,
2107             p_term_hist_id  pn_payment_terms_history.term_history_id%TYPE,
2108             p_adj_type_cd   pn_payment_items.last_adjustment_type_code%TYPE
2109 )
2110 IS
2111   CURSOR get_last_appr_sched IS
2112    SELECT max(schedule_date) schedule_date
2113    FROM pn_payment_schedules_all
2114    WHERE lease_id = p_lease_id
2115    AND payment_status_lookup_code = 'APPROVED';
2116 
2117   CURSOR org_id_cur IS
2118    SELECT org_id
2119    FROM pn_leases_all
2120    WHERE lease_id = p_lease_id;
2121 
2122   l_virtual_sched  payment_item_tbl_type;
2123   l_current_sched  payment_item_tbl_type;
2124   l_merged_sched   payment_item_tbl_type;
2125 
2126   l_new_orig_table payment_item_tbl_type;
2127   l_upd_orig_table payment_item_tbl_type;
2128   l_del_orig_table payment_item_tbl_type;
2129 
2130   l_new_itm_table  payment_item_tbl_type;
2131   l_upd_itm_table  payment_item_tbl_type;
2132   l_del_itm_table  payment_item_tbl_type;
2133 
2134   l_adj_table      payment_item_tbl_type;
2135 
2136   l_last_appr_dt   DATE;
2137   l_info           VARCHAR2(100);
2138   l_desc           VARCHAR2(100) := 'pn_retro_adjustment_pkg.create_retro_adjustments';
2139   l_org_id         NUMBER;
2140 
2141 BEGIN
2142 
2143   pnp_debug_pkg.log(l_desc ||' (+)');
2144 
2145   FOR org_id_rec IN org_id_cur LOOP
2146      l_org_id := org_id_rec.org_id;
2147   END LOOP;
2148 
2149   create_virtual_schedules (
2150      p_start_date => p_term_start_dt,
2151      p_end_date   => p_term_end_dt,
2152      p_sch_day    => p_term_sch_day,
2153      p_amount     => p_term_act_amt,
2154      p_term_freq  => p_term_freq,
2155      p_payment_term_id => p_term_id,
2156      x_sched_tbl  => l_virtual_sched
2157   );
2158 
2159   get_current_schedules(
2160      p_term_id    => p_term_id,
2161      x_sched_tbl  => l_current_sched
2162   );
2163 
2164   merge_schedules(
2165      p_current_sched => l_current_sched,
2166      p_virtual_sched => l_virtual_sched,
2167      x_sched_tbl     => l_merged_sched
2168   );
2169 
2170   -- get last approved schedule date
2171   FOR date_rec IN get_last_appr_sched LOOP
2172      l_last_appr_dt := date_rec.schedule_date;
2173      exit;
2174   END LOOP;
2175 
2176   create_adjustment_tables(
2177      p_sched_table    => l_merged_sched,
2178      p_last_appr_dt   => l_last_appr_dt,
2179      p_term_freq      => p_term_freq,
2180      p_term_start_dt  => p_term_start_dt,
2181      p_term_end_dt    => p_term_end_dt,
2182      x_new_orig_table => l_new_orig_table,
2183      x_upd_orig_table => l_upd_orig_table,
2184      x_del_orig_table => l_del_orig_table,
2185      x_adj_table      => l_adj_table
2186   );
2187 
2188   -- for new items, find schedule id
2189   get_schedule_id_for_new_items(
2190      p_lease_id        => p_lease_id,
2191      p_term_id         => p_term_id,
2192      p_lease_change_id => p_lease_chg_id,
2193      p_sched_tbl       => l_new_orig_table
2194   );
2195 
2196   -- process original items
2197   process_items(
2198      p_term_id      => p_term_id,
2199      p_adj_type_cd  => null,
2200      p_upd_item_tbl => l_upd_orig_table,
2201      p_del_item_tbl => l_del_orig_table,
2202      p_new_item_tbl => l_new_orig_table
2203   );
2204 
2205   calculate_adjustment_details(
2206      p_adj_table     => l_adj_table,
2207      p_new_itm_table => l_new_itm_table,
2208      p_upd_itm_table => l_upd_itm_table,
2209      p_del_itm_table => l_del_itm_table
2210   );
2211 
2212   -- before deleting items, remove reference of items to be deleted
2213   -- from the adjustment table
2214   remove_item_reference(
2215      p_item_tbl     => l_del_itm_table
2216   );
2217 
2218   prepare_new_items_from_adj (
2219      p_sch_day      => p_term_sch_day,
2220      p_item_adj_tbl => l_new_itm_table,
2221      p_org_id       => l_org_id
2222   );
2223 
2224   -- for new items, find schedule id
2225   get_schedule_id_for_new_items(
2226      p_lease_id        => p_lease_id,
2227      p_term_id         => p_term_id,
2228      p_lease_change_id => p_lease_chg_id,
2229      p_sched_tbl       => l_new_itm_table
2230   );
2231 
2232   -- process adjustment items
2233   process_items(
2234      p_term_id      => p_term_id,
2235      p_adj_type_cd  => p_adj_type_cd,
2236      p_upd_item_tbl => l_upd_itm_table,
2237      p_del_item_tbl => l_del_itm_table,
2238      p_new_item_tbl => l_new_itm_table
2239   );
2240 
2241   populate_new_item_id(
2242      p_new_item_tbl => l_new_itm_table,
2243      p_adj_tbl      => l_adj_table
2244   );
2245 
2246   create_adjustment_entries(
2247      p_term_id       => p_term_id,
2248      p_term_freq     => p_term_freq,
2249      p_term_start_dt => p_term_start_dt,
2250      p_term_end_dt   => p_term_end_dt,
2251      p_term_hist_id  => p_term_hist_id,
2252      p_adj_table     => l_adj_table,
2253      p_org_id        => l_org_id
2254   );
2255 
2256   -- clean up schedules of deleted items (original and adjustment)
2257   cleanup_schedules(
2258      p_term_id       => p_term_id,
2259      p_orig_item_tbl => l_del_orig_table,
2260      p_adj_item_tbl  => l_del_itm_table
2261   );
2262 
2263   IF l_adj_table.COUNT > 0 THEN
2264 
2265      update_terms_history(
2266         p_term_hist_id    => p_term_hist_id,
2267         p_adj_type_cd     => p_adj_type_cd,
2268         p_lease_change_id => p_lease_chg_id,
2269         p_term_id         => p_term_id
2270      );
2271 
2272   END IF;
2273 
2274   pnp_debug_pkg.log(l_desc ||' (-)');
2275 
2276 EXCEPTION
2277   WHEN OTHERS THEN
2278      pnp_debug_pkg.log(l_desc || ': Error while ' || l_info);
2279      raise;
2280 
2281 END create_retro_adjustments;
2282 
2283 
2284 END pn_retro_adjustment_pkg;