DBA Data[Home] [Help]

PACKAGE BODY: APPS.PO_PDOI_PRICE_DIFF_PROCESS_PVT

Source


1 PACKAGE BODY PO_PDOI_PRICE_DIFF_PROCESS_PVT AS
2 /* $Header: PO_PDOI_PRICE_DIFF_PROCESS_PVT.plb 120.13 2006/09/15 21:44:21 jinwang noship $ */
3 
4 d_pkg_name CONSTANT VARCHAR2(50) :=
5   PO_LOG.get_package_base('PO_PDOI_PRICE_DIFF_PROCESS_PVT');
6 
7 --------------------------------------------------------------------------
8 ---------------------- PRIVATE PROCEDURES PROTOTYPE ----------------------
9 --------------------------------------------------------------------------
10 
11 PROCEDURE populate_error_flag
12 (
13   x_results             IN     po_validation_results_type,
14   x_price_diffs         IN OUT NOCOPY PO_PDOI_TYPES.price_diffs_rec_type
15 );
16 
17 --------------------------------------------------------------------------
18 ---------------------- PUBLIC PROCEDURES ---------------------------------
19 --------------------------------------------------------------------------
20 
21 -----------------------------------------------------------------------
22 --Start of Comments
23 --Name: open_price_diffs
24 --Function:
25 --  Open cursor for query.
26 --  This query retrieves the price differential attributes and related header,
27 --  line and location attributes for processing
28 --Parameters:
29 --IN:
30 --  p_max_intf_price_diff_id
31 --    maximal interface_price_diff_id processed so far
32 --    The query will only retrieve the price_differential records which have
33 --    not been processed
34 --IN OUT:
35 --  x_price_diffs_csr
36 --  cursor variable to hold pointer to current processing row in the result
37 --  set returned by the query
38 --OUT:
39 --End of Comments
40 ------------------------------------------------------------------------
41 PROCEDURE open_price_diffs
42 (
43   p_max_intf_price_diff_id   IN NUMBER,
44   x_price_diffs_csr          OUT NOCOPY PO_PDOI_TYPES.intf_cursor_type
45 ) IS
46 
47   d_api_name CONSTANT VARCHAR2(30) := 'open_price_diffs';
48   d_module   CONSTANT VARCHAR2(255) := d_pkg_name || d_api_name || '.';
49   d_position NUMBER;
50 
51 BEGIN
52   d_position := 0;
53 
54   IF (PO_LOG.d_proc) THEN
55     PO_LOG.proc_begin(d_module, 'p_max_intf_price_diff_id',
56                       p_max_intf_price_diff_id);
57   END IF;
58 
59   OPEN x_price_diffs_csr FOR
60   SELECT intf_price_diffs.price_diff_interface_id,
61          intf_price_diffs.interface_line_id,
62          intf_price_diffs.interface_header_id,
63          intf_price_diffs.price_differential_num,
64          intf_price_diffs.price_type,
65          intf_price_diffs.entity_type,
66          intf_price_diffs.entity_id,
67          intf_price_diffs.multiplier,
68          intf_price_diffs.min_multiplier,
69          intf_price_diffs.max_multiplier,
70 
71          -- attributes read from line location record
72          intf_locs.line_location_id,
73 
74          -- attributes read from line record
75          intf_lines.po_line_id,
76 
77          -- attributes read from header record
78          intf_headers.draft_id,
79          NVL(draft_headers.style_id, txn_headers.style_id),
80 
81          -- set initial value for error_flag
82          FND_API.g_FALSE
83   FROM   PO_PRICE_DIFF_INTERFACE intf_price_diffs,
84          PO_LINE_LOCATIONS_INTERFACE intf_locs,
85          PO_LINES_INTERFACE intf_lines,
86          PO_HEADERS_INTERFACE intf_headers,
87          PO_LINES_DRAFT_ALL draft_lines,
88          PO_HEADERS_DRAFT_ALL draft_headers,
89          PO_HEADERS_ALL txn_headers
90   WHERE  intf_price_diffs.interface_line_id = intf_lines.interface_line_id
91   AND    intf_lines.interface_header_id = intf_headers.interface_header_id
92   AND    intf_lines.po_line_id = draft_lines.po_line_id
93   AND    intf_headers.draft_id = draft_lines.draft_id
94   AND    intf_headers.po_header_id = draft_headers.po_header_id(+)
95   AND    intf_headers.draft_id = draft_headers.draft_id(+)
96   AND    intf_headers.po_header_id = txn_headers.po_header_id(+)
97   AND    draft_lines.order_type_lookup_code = 'RATE'
98   AND    intf_price_diffs.interface_line_location_id = intf_locs.interface_line_location_id(+)
99   AND    intf_price_diffs.processing_id = PO_PDOI_PARAMS.g_processing_id
100   AND    intf_headers.processing_round_num = PO_PDOI_PARAMS.g_current_round_num
101   AND    intf_price_diffs.price_diff_interface_id > p_max_intf_price_diff_id
102   AND    NVL(intf_lines.process_code, PO_PDOI_CONSTANTS.g_PROCESS_CODE_PENDING)
103            <> PO_PDOI_CONSTANTS.g_PROCESS_CODE_NOTIFIED
104   ORDER BY intf_price_diffs.price_diff_interface_id;
105 
106   IF (PO_LOG.d_proc) THEN
107     PO_LOG.proc_end (d_module);
108   END IF;
109 
110 EXCEPTION
111   WHEN OTHERS THEN
112     PO_MESSAGE_S.add_exc_msg
113     (
114       p_pkg_name => d_pkg_name,
115       p_procedure_name => d_api_name || '.' || d_position
116     );
117     RAISE;
118 END open_price_diffs;
119 
120 -----------------------------------------------------------------------
121 --Start of Comments
122 --Name: fetch_price_diffs
123 --Function:
124 --  fetch results in batch
125 --Parameters:
126 --IN:
127 --IN OUT:
128 --x_price_diffs_csr
129 --  cursor variable that hold pointers to currently processing row
130 --x_price_diffs
131 --  record variable to hold price differential info within a batch
132 --OUT:
133 --End of Comments
134 ------------------------------------------------------------------------
135 PROCEDURE fetch_price_diffs
136 (
137   x_price_diffs_csr   IN OUT NOCOPY PO_PDOI_TYPES.intf_cursor_type,
138   x_price_diffs       OUT NOCOPY PO_PDOI_TYPES.price_diffs_rec_type
139 ) IS
140 
141   d_api_name CONSTANT VARCHAR2(30) := 'fetch_price_diffs';
142   d_module   CONSTANT VARCHAR2(255) := d_pkg_name || d_api_name || '.';
143   d_position NUMBER;
144 
145 BEGIN
146   d_position := 0;
147 
148   IF (PO_LOG.d_proc) THEN
149     PO_LOG.proc_begin(d_module);
150   END IF;
151 
152   FETCH x_price_diffs_csr BULK COLLECT INTO
153     x_price_diffs.intf_price_diff_id_tbl,
154     x_price_diffs.intf_line_id_tbl,
155     x_price_diffs.intf_header_id_tbl,
156     x_price_diffs.price_diff_num_tbl,
157     x_price_diffs.price_type_tbl,
158     x_price_diffs.entity_type_tbl,
159     x_price_diffs.entity_id_tbl,
160     x_price_diffs.multiplier_tbl,
161     x_price_diffs.min_multiplier_tbl,
162     x_price_diffs.max_multiplier_tbl,
163 
164     -- attributes read from line location record
165     x_price_diffs.loc_line_loc_id_tbl,
166 
167     -- attributes read from line record
168     x_price_diffs.ln_po_line_id_tbl,
169 
170     -- attributes read from header record
171     x_price_diffs.draft_id_tbl,
172     x_price_diffs.hd_style_id_tbl,
173 
174     -- set initial value for error_flag
175     x_price_diffs.error_flag_tbl
176   LIMIT PO_PDOI_CONSTANTS.g_DEF_BATCH_SIZE;
177 
178   IF (PO_LOG.d_proc) THEN
179     PO_LOG.proc_end (d_module);
180   END IF;
181 
182 EXCEPTION
183   WHEN OTHERS THEN
184     PO_MESSAGE_S.add_exc_msg
185     (
186       p_pkg_name => d_pkg_name,
187       p_procedure_name => d_api_name || '.' || d_position
188     );
189     RAISE;
190 END fetch_price_diffs;
191 
192 -----------------------------------------------------------------------
193 --Start of Comments
194 --Name: default_price_diffs
195 --Function: perform defaulting logic on price diff attributes
196 --Parameters:
197 --IN:
198 --IN OUT:
199 --  x_price_diffs
200 --    record to store all the price diff rows within the batch;
201 --    defaulting are performed for certain attributes only
202 --    if their value is empty.
203 --OUT:
204 --End of Comments
205 ------------------------------------------------------------------------
206 PROCEDURE default_price_diffs
207 (
208   x_price_diffs       IN OUT NOCOPY PO_PDOI_TYPES.price_diffs_rec_type
209 ) IS
210 
211   d_api_name CONSTANT VARCHAR2(30) := 'default_price_diffs';
212   d_module   CONSTANT VARCHAR2(255) := d_pkg_name || d_api_name || '.';
213   d_position NUMBER;
214 BEGIN
215   d_position := 0;
216 
217   IF (PO_LOG.d_proc) THEN
218     PO_LOG.proc_begin(d_module);
219   END IF;
220 
221   PO_TIMING_UTL.start_time(PO_PDOI_CONSTANTS.g_T_PRICE_DIFF_DEFAULT);
222 
223   d_position := 10;
224 
225   FOR i IN 1..x_price_diffs.rec_count
226   LOOP
227     IF (PO_LOG.d_stmt) THEN
228       PO_LOG.stmt(d_module, d_position, 'index', i);
229       PO_LOG.stmt(d_module, d_position, 'line loc id',
230                   x_price_diffs.loc_line_loc_id_tbl(i));
231       PO_LOG.stmt(d_module, d_position, 'po line id',
232                   x_price_diffs.ln_po_line_id_tbl(i));
233       PO_LOG.stmt(d_module, d_position, 'entity type',
234                   x_price_diffs.entity_type_tbl(i));
235       PO_LOG.stmt(d_module, d_position, 'entity id',
236                   x_price_diffs.entity_id_tbl(i));
237     END IF;
238 
239     d_position := 20;
240 
241     -- default entity_type
242     IF (x_price_diffs.entity_type_tbl(i) IS NULL) THEN
243       IF (x_price_diffs.loc_line_loc_id_tbl(i) IS NOT NULL AND
244 	      PO_PDOI_PARAMS.g_request.document_type =
245 		    PO_PDOI_CONSTANTS.g_DOC_TYPE_BLANKET) THEN
246         x_price_diffs.entity_type_tbl(i) := 'PRICE BREAK';
247       ELSE
248         IF (PO_PDOI_PARAMS.g_request.document_type =
249               PO_PDOI_CONSTANTS.g_DOC_TYPE_BLANKET) THEN
250           x_price_diffs.entity_type_tbl(i) := 'BLANKET LINE';
251         ELSE
252           x_price_diffs.entity_type_tbl(i) := 'PO LINE';
253         END IF;
254       END IF;
255     END IF;
256 
257     d_position := 30;
258     -- set entity_id according to the entity_type
259     IF (x_price_diffs.entity_type_tbl(i) = 'PRICE BREAK') THEN
260       x_price_diffs.entity_id_tbl(i) := x_price_diffs.loc_line_loc_id_tbl(i);
261     ELSIF (x_price_diffs.entity_type_tbl(i) IN ('BLANKET LINE', 'PO LINE')) THEN
262       x_price_diffs.entity_id_tbl(i) := x_price_diffs.ln_po_line_id_tbl(i);
263     ELSE
264       NULL; -- invalid entity_type
265     END IF;
266   END LOOP;
267 
268   d_position := 40;
269 
270   -- default price_differential_num if not provided or not unique
271   PO_PDOI_MAINPROC_UTL_PVT.check_price_diff_num_unique
272   (
273     p_entity_type_tbl           => x_price_diffs.entity_type_tbl,
274     p_entity_id_tbl             => x_price_diffs.entity_id_tbl,
275     p_draft_id_tbl              => x_price_diffs.draft_id_tbl,
276     p_intf_price_diff_id_tbl    => x_price_diffs.intf_price_diff_id_tbl,
277     p_price_diff_num_tbl        => x_price_diffs.price_diff_num_tbl,
278     x_price_diff_num_unique_tbl => x_price_diffs.price_diff_num_unique_tbl
279   );
280 
281   d_position := 50;
282 
283   PO_PDOI_MAINPROC_UTL_PVT.calculate_max_price_diff_num
284   (
285     p_entity_type_tbl           => x_price_diffs.entity_type_tbl,
286     p_entity_id_tbl             => x_price_diffs.entity_id_tbl,
287     p_draft_id_tbl              => x_price_diffs.draft_id_tbl,
288     p_price_diff_num_tbl        => x_price_diffs.price_diff_num_tbl
289   );
290 
291   d_position := 60;
292 
293   FOR i IN 1..x_price_diffs.rec_count
294   LOOP
295     IF (x_price_diffs.price_diff_num_tbl(i) IS NULL OR
296         x_price_diffs.price_diff_num_unique_tbl(i) = FND_API.g_FALSE) THEN
297       x_price_diffs.price_diff_num_tbl(i) :=
298         PO_PDOI_MAINPROC_UTL_PVT.get_next_price_diff_num
299         (
300           p_entity_type => x_price_diffs.entity_type_tbl(i),
301           p_entity_id   => x_price_diffs.entity_id_tbl(i)
302         );
303     END IF;
304   END LOOP;
305 
306   PO_TIMING_UTL.stop_time(PO_PDOI_CONSTANTS.g_T_PRICE_DIFF_DEFAULT);
307 
308   IF (PO_LOG.d_proc) THEN
309     PO_LOG.proc_end (d_module);
310   END IF;
311 
312 EXCEPTION
313   WHEN OTHERS THEN
314     PO_MESSAGE_S.add_exc_msg
315     (
316       p_pkg_name => d_pkg_name,
317       p_procedure_name => d_api_name || '.' || d_position
318     );
319     RAISE;
320 END default_price_diffs;
321 
322 -----------------------------------------------------------------------
323 --Start of Comments
324 --Name: validate_price_diffs
325 --Function:
326 --  validate price differential attributes read within a batch
327 --Parameters:
328 --IN:
329 --IN OUT:
330 --x_dists
331 --  The record contains the values to be validated.
332 --  If there is error(s) on any attribute of the price differential row,
333 --  corresponding value in error_flag_tbl will be set with value
334 --  FND_API.G_TRUE.
335 --OUT:
336 --End of Comments
337 ------------------------------------------------------------------------
338 ------------------------------------------------------------------------
339 PROCEDURE validate_price_diffs
340 (
341   x_price_diffs         IN OUT NOCOPY PO_PDOI_TYPES.price_diffs_rec_type
342 ) IS
343 
344   d_api_name CONSTANT VARCHAR2(30) := 'validate_price_diffs';
345   d_module   CONSTANT VARCHAR2(255) := d_pkg_name || d_api_name || '.';
346   d_position NUMBER;
347 
348   l_price_differentials  PO_PRICE_DIFF_VAL_TYPE := PO_PRICE_DIFF_VAL_TYPE();
349   l_parameter_name_tbl   PO_TBL_VARCHAR2000 := PO_TBL_VARCHAR2000();
350   l_parameter_value_tbl  PO_TBL_VARCHAR2000 := PO_TBL_VARCHAR2000();
351   l_result_type          VARCHAR2(30);
352   l_results              po_validation_results_type;
353 
354 BEGIN
355   d_position := 0;
356 
357   IF (PO_LOG.d_proc) THEN
358     PO_LOG.proc_begin(d_module);
359   END IF;
360 
361   PO_TIMING_UTL.start_time(PO_PDOI_CONSTANTS.g_T_PRICE_DIFF_VALIDATE);
362 
363   l_price_differentials.interface_id   := x_price_diffs.intf_price_diff_id_tbl;
364   l_price_differentials.price_type     := x_price_diffs.price_type_tbl;
365   l_price_differentials.entity_type    := x_price_diffs.entity_type_tbl;
366   l_price_differentials.entity_id      := x_price_diffs.entity_id_tbl;
367   l_price_differentials.multiplier     := x_price_diffs.multiplier_tbl;
368   l_price_differentials.min_multiplier := x_price_diffs.min_multiplier_tbl;
369   l_price_differentials.max_multiplier := x_price_diffs.max_multiplier_tbl;
370   l_price_differentials.hdr_style_id   := x_price_diffs.hd_style_id_tbl;
371 
372   d_position := 10;
373 
374   l_parameter_name_tbl.EXTEND(1);
375   l_parameter_value_tbl.EXTEND(1);
376   l_parameter_name_tbl(1)     := 'DOC_TYPE';
377   l_parameter_value_tbl(1)    := PO_PDOI_PARAMS.g_request.document_type;
378 
379   PO_VALIDATIONS.validate_pdoi(p_price_differentials   => l_price_differentials,
380                                p_parameter_name_tbl    => l_parameter_name_tbl,
381                                p_parameter_value_tbl   => l_parameter_value_tbl,
382                                x_result_type           => l_result_type,
383                                x_results               => l_results);
384 
385   d_position := 20;
386 
387   IF (l_result_type = po_validations.c_result_type_failure) THEN
388     IF (PO_LOG.d_stmt) THEN
389       PO_LOG.stmt(d_module, d_position, 'vaidate price diffs return failure');
390     END IF;
391 
392     PO_PDOI_ERR_UTL.process_val_type_errors
393     (
394       x_results   => l_results,
395       p_table_name => 'PO_PRICE_DIFF_INTERFACE',
396       p_price_diffs => x_price_diffs
397     );
398 
399     d_position := 30;
400 
401     populate_error_flag
402     (
403       x_results     => l_results,
404       x_price_diffs => x_price_diffs
405     );
406   END IF;
407 
408   IF l_result_type = po_validations.c_result_type_fatal THEN
409     IF (PO_LOG.d_stmt) THEN
410       PO_LOG.stmt(d_module, d_position, 'vaidate price diffs return fatal');
411     END IF;
412 
413     RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
414   END IF;
415 
416   PO_TIMING_UTL.stop_time(PO_PDOI_CONSTANTS.g_T_PRICE_DIFF_VALIDATE);
417 
418   IF (PO_LOG.d_proc) THEN
419     PO_LOG.proc_end (d_module);
420   END IF;
421 
422 EXCEPTION
423   WHEN OTHERS THEN
424     PO_MESSAGE_S.add_exc_msg
425     (
426       p_pkg_name => d_pkg_name,
427       p_procedure_name => d_api_name || '.' || d_position
428     );
429     RAISE;
430 END validate_price_diffs;
431 
432 -------------------------------------------------------------------------
433 --------------------- PRIVATE PROCEDURES --------------------------------
434 -------------------------------------------------------------------------
435 
436 -----------------------------------------------------------------------
437 --Start of Comments
438 --Name: populate_error_flag
439 --Function:
440 --  corresponding value in error_flag_tbl will be set with value FND_API.G_FALSE.
441 --Parameters:
442 --IN:
443 --p_results
444 --  The validation results that contains the errored line information.
445 --IN OUT:
446 --p_price_diffs
447 --  The record contains the values to be validated.
448 --  If there is error(s) on any attribute of the price differential row,
449 --  corresponding value in error_flag_tbl will be set with value
450 --  FND_API.G_TRUE.
451 --OUT:
452 --End of Comments
453 ------------------------------------------------------------------------
454 PROCEDURE populate_error_flag
455 (
456   x_results             IN     po_validation_results_type,
457   x_price_diffs         IN OUT NOCOPY PO_PDOI_TYPES.price_diffs_rec_type
458 ) IS
459 
460   d_api_name CONSTANT VARCHAR2(30) := 'populate_error_flag';
461   d_module   CONSTANT VARCHAR2(255) := d_pkg_name || d_api_name || '.';
462   d_position NUMBER;
463 
464   l_index_tbl  DBMS_SQL.number_table;
465   l_index      NUMBER;
466   l_remove_err_price_diff_tbl PO_TBL_NUMBER := PO_TBL_NUMBER();
467   l_remove_err_line_tbl       PO_TBL_NUMBER := PO_TBL_NUMBER();
468   l_intf_header_id NUMBER;
469 BEGIN
470   d_position := 0;
471 
472   IF (PO_LOG.d_proc) THEN
473     PO_LOG.proc_begin(d_module);
474   END IF;
475 
476   FOR i IN 1 .. x_price_diffs.intf_price_diff_id_tbl.COUNT LOOP
477       l_index_tbl(x_price_diffs.intf_price_diff_id_tbl(i)) := i;
478   END LOOP;
479 
480   d_position := 10;
481 
482   FOR i IN 1 .. x_results.entity_id.COUNT LOOP
483     l_index := l_index_tbl(x_results.entity_id(i));
484 
485     -- Bug 5215781:
486     -- set error_flag to TRUE for all remaining records if error threshold is
487     -- hit for CATALOG UPLOAD
488     IF (PO_PDOI_PARAMS.g_request.calling_module =
489           PO_PDOI_CONSTANTS.g_call_mod_CATALOG_UPLOAD AND
490         PO_PDOI_PARAMS.g_docs_info(PO_PDOI_PARAMS.g_request.interface_header_id)
491           .err_tolerance_exceeded = FND_API.g_TRUE) THEN
492       d_position := 20;
493 
494       IF (PO_LOG.d_stmt) THEN
495         PO_LOG.stmt(d_module, d_position, 'after error tolerance exceeded, collect error on index', l_index);
496       END IF;
497 
498       -- collect price_diff_interface_ids to remove the errors from error intf table
499       IF (NOT PO_PDOI_PARAMS.g_errored_lines.EXISTS(x_price_diffs.intf_line_id_tbl(l_index))) THEN
500         d_position := 30;
501 
502         l_remove_err_line_tbl.EXTEND;
503         l_remove_err_price_diff_tbl.EXTEND;
504         l_remove_err_line_tbl(l_remove_err_line_tbl.COUNT) := x_price_diffs.intf_line_id_tbl(l_index);
505         l_remove_err_price_diff_tbl(l_remove_err_price_diff_tbl.COUNT) := x_price_diffs.intf_price_diff_id_tbl(l_index);
506       END IF;
507     ELSIF (x_results.result_type(i) = po_validations.c_result_type_failure) THEN
508         d_position := 40;
509 
510         IF (PO_LOG.d_stmt) THEN
511           PO_LOG.stmt(d_module, d_position, 'error on index', l_index);
512         END IF;
513 
514         x_price_diffs.error_flag_tbl(l_index) := FND_API.g_TRUE;
515 
516         -- Bug 5215781:
517         -- price diff level errors will be counted in line errors and threshold will be
518         -- checked; If threshold is hit, reject all price diff records that are processed
519         -- after the current record and remove the errors from interface table for those
520         -- records
521         IF (NOT PO_PDOI_PARAMS.g_errored_lines.EXISTS(x_price_diffs.intf_line_id_tbl(l_index))) THEN
522           d_position := 50;
523 
524           IF (PO_LOG.d_stmt) THEN
525             PO_LOG.stmt(d_module, d_position, 'set error on line',
526                         x_price_diffs.intf_line_id_tbl(l_index));
527           END IF;
528 
529           -- set corresponding line to ERROR
530           PO_PDOI_PARAMS.g_errored_lines(x_price_diffs.intf_line_id_tbl(l_index)) := 'Y';
531 
532           l_intf_header_id := x_price_diffs.intf_header_id_tbl(l_index);
533           PO_PDOI_PARAMS.g_docs_info(l_intf_header_id).number_of_errored_lines
534             := PO_PDOI_PARAMS.g_docs_info(l_intf_header_id).number_of_errored_lines +1;
535 
536           -- check threshold
537           IF (PO_PDOI_PARAMS.g_request.calling_module =
538                 PO_PDOI_CONSTANTS.g_call_mod_CATALOG_UPLOAD AND
539               PO_PDOI_PARAMS.g_docs_info(l_intf_header_id).number_of_errored_lines
540                 = PO_PDOI_PARAMS.g_request.err_lines_tolerance) THEN
541             IF (PO_LOG.d_stmt) THEN
542               PO_LOG.stmt(d_module, d_position, 'threshold hit on line',
543                           x_price_diffs.intf_line_id_tbl(l_index));
544             END IF;
545 
546             PO_PDOI_PARAMS.g_docs_info(l_intf_header_id).err_tolerance_exceeded := FND_API.g_TRUE;
547 
548             -- reject all rows after this row
549             FOR j IN l_index+1..x_price_diffs.rec_count LOOP
550               x_price_diffs.error_flag_tbl(j) := FND_API.g_TRUE;
551             END LOOP;
552           END IF;
553         END IF;
554      END IF;
555   END LOOP;
556 
557   d_position := 60;
558 
559   -- Bug 5215781:
560   -- remove the errors for price diffs from po_interface_errors if those records are supposed to be processed
561   -- after the price diff where we hit the error tolerance; And they do not belong to any line that has been
562   -- counted in g_errored_lines. That means, we want to rollback some changes made on po_interface_errors if
563   -- error tolerance is reached at some point
564   PO_INTERFACE_ERRORS_UTL.flush_errors_tbl;
565 
566   FORALL i IN 1..l_remove_err_price_diff_tbl.COUNT
567     DELETE FROM PO_INTERFACE_ERRORS
568     WHERE price_diff_interface_id = l_remove_err_price_diff_tbl(i)
569     AND   interface_line_id = l_remove_err_line_tbl(i);
570 
571   d_position := 70;
572 
573   IF (PO_LOG.d_proc) THEN
574     PO_LOG.proc_end (d_module);
575   END IF;
576 
577 EXCEPTION
578   WHEN OTHERS THEN
579     PO_MESSAGE_S.add_exc_msg
580     (
581       p_pkg_name => d_pkg_name,
582       p_procedure_name => d_api_name || '.' || d_position
583     );
584     RAISE;
585 END populate_error_flag;
586 
587 END PO_PDOI_PRICE_DIFF_PROCESS_PVT;