DBA Data[Home] [Help]

PACKAGE BODY: APPS.QP_UPDATE_UTIL

Source


1 PACKAGE BODY QP_Update_Util AS
2 /* $Header: QPXQINDB.pls 120.4 2006/08/14 22:36:28 jhkuo noship $ */
3 
4 
5 PROCEDURE Update_Qualification_Ind
6 		  (p_worker            NUMBER,
7                    p_line_type         VARCHAR2,
8                    p_List_Line_Id_Low  NUMBER DEFAULT NULL,
9 		   p_List_Line_Id_High NUMBER DEFAULT NULL,
10                    p_last_proc_line    NUMBER :=  0)
11 IS
12 
13 l_old_header_id     NUMBER := -9999;
14 l_old_header_qual_exists BOOLEAN := FALSE;
15 
16 TYPE Num_Type IS TABLE OF NUMBER INDEX BY BINARY_INTEGER;
17 TYPE Char30_Type IS TABLE OF VARCHAR2(30) INDEX BY BINARY_INTEGER;
18 
19 l_list_line_id_tbl       Num_Type;
20 l_qualification_ind_tbl  Num_Type;
21 l_list_type_code_tbl     Char30_Type;
22 l_list_header_id_tbl     Num_Type;
23 
24 l_count                NUMBER;
25 l_rows                 NATURAL := 5000;
26 l_total_rows           NUMBER := 0;
27 
28 cursor list_lines_cur(a_list_line_id NUMBER,b_list_line_id NUMBER)
29 is
30   select l.list_line_id, l.qualification_ind, h.list_type_code, h.list_header_id
31   from   qp_list_lines l, qp_list_headers_b h
32   where  l.list_header_id = h.list_header_id
33   and    (l.list_line_id between a_list_line_id and b_list_line_id)
34   order by l.list_line_id;
35 
36 l_new_list_line_id_low NUMBER;
37 l_index                NUMBER;
38 
39 BEGIN
40 
41   --Determine the new list_line_id_low for re-runnability.
42   l_new_list_line_id_low := GREATEST(p_last_proc_line + 1, p_list_line_id_low);
43 
44   OPEN list_lines_cur(l_new_list_line_id_low, p_list_line_id_high);
45 
46   LOOP
47     l_list_line_id_tbl.delete;
48     l_list_header_id_tbl.delete;
49     l_qualification_ind_tbl.delete;
50     l_list_type_code_tbl.delete;
51 
52     FETCH list_lines_cur BULK COLLECT INTO l_list_line_id_tbl,
53               l_qualification_ind_tbl, l_list_type_code_tbl,
54               l_list_header_id_tbl LIMIT l_rows;
55 
56     EXIT WHEN l_list_line_id_tbl.COUNT = 0;
57 
58     BEGIN
59 
60       FOR i IN l_list_line_id_tbl.FIRST..l_list_line_id_tbl.LAST
61       LOOP
62         BEGIN
63           --Initialize qualification_ind to 0.
64           l_qualification_ind_tbl(i) := 0;
65 
66           --If line has rltd modifiers, then increment qual_ind by 1.
67           BEGIN
68             select 1
69 	    into   l_count
70 	    from   qp_rltd_modifiers
71 	    where  to_rltd_modifier_id = l_list_line_id_tbl(i)
72 	    and    rltd_modifier_grp_type <> 'COUPON'
73             and    rownum = 1;
74 
75           EXCEPTION
76             WHEN  NO_DATA_FOUND  THEN
77               l_count := 0;
78 	  END;
79 
80           IF l_count > 0 THEN
81             l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 1;
82           END IF;
83 
84           --If line belongs to Price List or Agreement and if the PRL or AGR
85 		--has header-level qualifier other than Primary PL that are
86 		--qualifiers of Secondary PLs, then increment qual_ind by 2.
87           IF l_list_type_code_tbl(i) IN ('AGR', 'PRL') THEN
88 
89 	    IF l_old_header_id <> l_list_header_id_tbl(i) THEN
90 
91 	      l_old_header_id := l_list_header_id_tbl(i);
92 
93               BEGIN
94                 select 1
95 	        into   l_count
96                 from   qp_qualifiers
97 		where  list_header_id = l_list_header_id_tbl(i)
98 		and    NOT (qualifier_context = 'MODLIST' and
99 		 	    qualifier_attribute = 'QUALIFIER_ATTRIBUTE4')
100                 and    rownum = 1;
101 
102               EXCEPTION
103                 WHEN  NO_DATA_FOUND  THEN
104                   l_count := 0;
105 	      END;
106 
107 	      IF l_count > 0 THEN
108                 l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 2;
109 		l_old_header_qual_exists := TRUE;
110 	      ELSE
111 	        l_old_header_qual_exists :=  FALSE;
112 	      END IF;
113 
114             ELSE -- current list_header_id same as old_header_id
115 
116 	      IF l_old_header_qual_exists THEN
117                 l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 2;
118 	      END IF;
119 
120             END IF; -- If current list_header_id different from old_header_id
121 
122 	  --For all other list header types
123 	  ELSE
124 	    --If header-level qualifier exists for the list_header_id then
125 	    --increment qual ind by 2
126             IF l_old_header_id <> l_list_header_id_tbl(i) THEN
127 
128 	      l_old_header_id := l_list_header_id_tbl(i);
129 
130               BEGIN
131                 select 1
132 		into   l_count
133 	    	from   qp_qualifiers
134 		where  list_header_id = l_list_header_id_tbl(i)
135 		and    nvl(list_line_id,-1) = -1
136                 and    rownum = 1;
137 
138               EXCEPTION
139                 WHEN  NO_DATA_FOUND  THEN
140                   l_count := 0;
141 	      END;
142 
143 	      IF l_count > 0 THEN
144                 l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 2;
145 		l_old_header_qual_exists :=  TRUE;
146 	      ELSE
147 		l_old_header_qual_exists :=  FALSE;
148 	      END IF;
149 
150             ELSE -- current list_header_id same as old_header_id
151 
152 	      IF l_old_header_qual_exists THEN
153                 l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 2;
154 	      END IF;
155 
156             END IF; -- If current list_header_id different from old_header_id
157 
158 	    --If line-level qualifier exists for the list_line_id then
159 	    --increment qual ind by 8
160             BEGIN
161               select 1
162 	      into   l_count
163 	      from   qp_qualifiers
164 	      where  list_header_id = l_list_header_id_tbl(i)
165 	      and    list_line_id = l_list_line_id_tbl(i)
166               and    rownum = 1;
167 
168             EXCEPTION
169               WHEN  NO_DATA_FOUND  THEN
170                 l_count := 0;
171 	    END;
172 
173 	    IF l_count > 0 THEN
174               l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 8;
175 	    END IF;
176 
177           END IF;
178 
179           --If line has product attributes, then increment qual_ind by 4.
180           BEGIN
181 	    select 1
182 	    into   l_count
183 	    from   qp_pricing_attributes
184 	    where  list_line_id = l_list_line_id_tbl(i)
185 	    and    excluder_flag = 'N'
186             and    rownum = 1;
187 
188           EXCEPTION
189             WHEN  NO_DATA_FOUND  THEN
190               l_count := 0;
191 	  END;
192 
193 	  IF l_count > 0 THEN
194             l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 4;
195 	  END IF;
196 
197           --If line has pricing attributes, then increment qual_ind by 16.
198           BEGIN
199 	    select 1
200 	    into   l_count
201 	    from   qp_pricing_attributes
202 	    where  list_line_id = l_list_line_id_tbl(i)
203 	    and    pricing_attribute_context is not null
204 	    and    pricing_attribute is not null
205             -- changes made per rchellam's request--spgopal
206 	    and    pricing_attr_value_from IS NOT NULL
207             and    rownum = 1;
208 
209           EXCEPTION
210             WHEN  NO_DATA_FOUND  THEN
211               l_count := 0;
212 	  END;
213 
214 	  IF l_count > 0 THEN
215             l_qualification_ind_tbl(i) := l_qualification_ind_tbl(i) + 16;
216 	  END IF;
217 
218         EXCEPTION
219 	  WHEN OTHERS THEN
220 	    rollback;
221 	    QP_UTIL.Log_Error(
222                       p_id1 => 'Error in list_line_id ' ||
223 		    	to_char(l_list_line_id_tbl(l_list_line_id_tbl.FIRST + SQL%ROWCOUNT)),
224 		      p_id2 => substr(sqlerrm, 1, 30),
225 		      p_error_type => 'UPDATE_QUALIFICATION_IND',
226 		      p_error_desc => 'Error Processing list_line_id '||
227 		        to_char(l_list_line_id_tbl(l_list_line_id_tbl.FIRST + SQL%ROWCOUNT)),
228 		      p_error_module => 'Update_Qualification_Ind');
229 	    raise;
230         END;
231 
232       END LOOP; --End of For Loop
233 
234      FORALL j IN l_list_line_id_tbl.FIRST..l_list_line_id_tbl.LAST
235           UPDATE qp_list_lines
236 		SET    qualification_ind = l_qualification_ind_tbl(j)
237 		WHERE  list_line_id = l_list_line_id_tbl(j);
238 
239       FORALL k IN l_list_line_id_tbl.FIRST..l_list_line_id_tbl.LAST
240           UPDATE qp_pricing_attributes
241 		SET    qualification_ind = l_qualification_ind_tbl(k)
242 		WHERE  list_line_id = l_list_line_id_tbl(k);
243 
244       l_total_rows := l_total_rows + SQL%ROWCOUNT;
245 
246     EXCEPTION
247       WHEN OTHERS THEN
248 	rollback;
249 	QP_UTIL.Log_Error(
250 	    p_id1 => 'Error in list_line_id ' ||
251 	      to_char(l_list_line_id_tbl(l_list_line_id_tbl.FIRST + SQL%ROWCOUNT)),
252             p_id2 => substr(sqlerrm, 1, 30),
253 	    p_error_type => 'UPDATE_QUALIFICATION_IND',
254 	    p_error_desc => 'Error Processing list_line_id '||
255 	      to_char(l_list_line_id_tbl(l_list_line_id_tbl.FIRST + SQL%ROWCOUNT)),
256 	    p_error_module => 'Update_Qualification_Ind');
257 	raise;
258     END;
259 
260     --Fetch the index of the last list_line_id processed successfully.
261     l_index := l_list_line_id_tbl.LAST;
262 
263     --Update the qp_upg_lines_distribution table's record for the current worker and
264     --line_type with the last list_line_id successfully processed.
265     UPDATE qp_upg_lines_distribution
266     SET    last_proc_line = l_list_line_id_tbl(l_index)
267     WHERE  worker = p_worker
268     AND    line_type = p_line_type;
269 
270     COMMIT; --after every 5000(l_rows) lines are processed
271 
272   END LOOP; --End of cursor loop
273 
274   CLOSE list_lines_cur;
275 
276 EXCEPTION
277   WHEN OTHERS THEN
278     CLOSE list_lines_cur;
279     RAISE;
280 
281 END Update_Qualification_ind;
282 
283 
284 PROCEDURE update_pricing_attributes(
285             p_start_rowid  ROWID DEFAULT NULL,
286             p_end_rowid    ROWID DEFAULT NULL)
287 IS
288 canonical_mask VARCHAR2(100) := qp_number.canonical_mask;
289 
290 BEGIN
291   UPDATE
292    (SELECT list_header_id, pricing_phase_id, qualification_ind,
293            list_line_id, pricing_attribute_datatype,
294            pricing_attr_value_from, pricing_attr_value_to,
295            pricing_attr_value_from_number, pricing_attr_value_to_number,
296            CASE
297              WHEN comparison_operator_code = 'BETWEEN'
298                   AND pricing_attr_value_from IS NULL
299                   AND pricing_attr_value_to IS NOT NULL
300              THEN DECODE(pricing_attribute_datatype,
301                          'N', '-9999999999',
302                          'C', '0',
303                          '0001/01/01 00:00:00')
304              ELSE pricing_attr_value_from
305            END new_from,
306            CASE
307              WHEN comparison_operator_code = 'BETWEEN'
308                   AND pricing_attr_value_from IS NOT NULL
309                   AND pricing_attr_value_to IS NULL
310              THEN DECODE(pricing_attribute_datatype,
311                          'N', '9999999999',
312                          'C', 'z',
313                          '9999/01/01 00:00:00')
314              ELSE pricing_attr_value_to
315            END new_to
316     FROM   qp_pricing_attributes
317     WHERE  rowid BETWEEN
318              p_start_rowid AND p_end_rowid) pa
319   SET (list_header_id, pricing_phase_id, qualification_ind) =
320         (SELECT ll.list_header_id, ll.pricing_phase_id, ll.qualification_ind
321          FROM   qp_list_lines ll
322          WHERE  ll.list_line_id = pa.list_line_id),
323         pricing_attr_value_from = new_from,
324         pricing_attr_value_to = new_to,
325         pricing_attr_value_from_number =
326           DECODE(pricing_attribute_datatype, 'N',
327                  DECODE(ltrim(new_from, '0123456789.-'),
328                         null, to_number(new_from, canonical_mask))),
329         pricing_attr_value_to_number =
330           DECODE(pricing_attribute_datatype, 'N',
331                  DECODE(ltrim(new_to, '0123456789.-'),
332                         null, to_number(new_to, canonical_mask)));
333 
334 EXCEPTION
335   WHEN OTHERS THEN
336     ROLLBACK;
337     RAISE;
338 
339 END update_pricing_attributes;
340 
341 procedure  create_parallel_slabs
342        (  l_workers IN number := 5,
343           p_batchsize in number := 5000)
344       is
345       v_type              varchar2(30) := 'UPA'; -- for QPXUPPAB.sql
346 
347       cursor pricing_attributes
348       is
349       select pa.pricing_attribute_id pricing_attribute_id
350              /* Removed hint to tune the sqlstmt */
351       from  qp_pricing_attributes  pa, qp_list_lines ll
352       where pa.list_line_id = ll.list_line_id
353       and   pa.list_header_id is null
354       and   pa.pricing_phase_id is null
355       order by pricing_attribute_id;
356 
357 
358       l_total_lines     number;
359       l_min_line        number;
360       l_max_line        number;
361       l_counter           number;
362       l_gap               number;
363       l_worker_count        number;
364       l_worker_start        number;
365       l_worker_end          number;
366       l_pricing_attribute_id     number;
367       l_start_flag        number;
368       l_total_workers       number;
369 
370    Begin
371 
372       delete from qp_upg_lines_distribution
373       where line_type = v_type;
374 
375       commit;
376 
377       begin
378                 select
379                      count(*),
380                      nvl(min(pricing_attribute_id),0),
381                      nvl(max(pricing_attribute_id),0)
382                 into
383                      l_total_lines,
384                      l_min_line,
385                      l_max_line
386                 from  qp_pricing_attributes  pa, qp_list_lines ll
387                 where pa.list_line_id = ll.list_line_id
388                 and   pa.list_header_id is null
389                 and   pa.pricing_phase_id is null;
390 
391            exception
392                 when others then
393                   null;
394       end;
395 
396          if  l_total_lines < p_batchsize  or l_workers = 1 then
397 
398 
399                 qp_modifier_upgrade_util_pvt.insert_line_distribution
400                 (
401                     l_worker             => 1,
402                     l_start_line  => l_min_line,
403                     l_end_line    => l_max_line,
404                     l_type_var         => 'UPA'
405                 );
406 
407          else
408                 l_max_line  := 0;
409                 l_min_line  := 0;
410                 l_total_workers := l_workers;
411                 l_counter     := 0;
412                 l_start_flag  := 0;
413                 l_worker_count  := 0;
414                 l_gap         := round(l_total_lines / l_total_workers, 0);
415 
416                 for pa_rec in pricing_attributes loop
417 
418                     l_pricing_attribute_id := pa_rec.pricing_attribute_id;
419                     l_counter       := l_counter + 1;
420 
421                     if l_start_flag = 0 then
422                               l_start_flag := 1;
423                               l_min_line := pa_rec.pricing_attribute_id;
424                               l_max_line := NULL;
425                               l_worker_count := l_worker_count + 1;
426                     end if;
427 
428                   if l_counter = l_gap and l_worker_count < l_total_workers
429                   then
430                          l_max_line := pa_rec.pricing_attribute_id;
431 
432                      qp_modifier_upgrade_util_pvt.insert_line_distribution
433                      (
434                        l_worker             => l_worker_count,
435                        l_start_line  => l_min_line,
436                        l_end_line    => l_max_line,
437                        l_type_var         => 'UPA'
438                      );
439 
440                          l_counter    := 0;
441                          l_start_flag := 0;
442 
443                   end if;
444 
445                 end loop;
446 
447                 l_max_line := l_pricing_attribute_id;
448 
449                      qp_modifier_upgrade_util_pvt.insert_line_distribution
450                      (
451                        l_worker             => l_worker_count,
452                        l_start_line  => l_min_line,
453                        l_end_line    => l_max_line,
454                        l_type_var         => 'UPA'
455                      );
456 
457 
458                 commit;
459 	 end if;
460 
461 end create_parallel_slabs;
462 
463 End QP_Update_Util;