DBA Data[Home] [Help]

PACKAGE BODY: APPS.QA_PARENT_CHILD_PKG

Source


1 PACKAGE BODY  QA_PARENT_CHILD_PKG as
2 /* $Header: qapcb.pls 120.34.12020000.5 2012/11/14 09:25:58 ntungare ship $ */
3 
4  --
5  -- bug 7588376
6  -- New collection to store the values corresponding to the
7  -- relationship elements selected from the parent collection
8  -- plan
9  -- skolluku
10  Type parent_plan_vales_tab_typ is table of varchar2(2000) index by varchar2(2000);
11  parent_plan_vales_tab parent_plan_vales_tab_typ;
12 
13 -- Bug 4343758
14 -- R12 OAF Txn Integration Project
15 -- Standard Global variable
16 -- shkalyan 05/07/2005.
17 g_pkg_name      CONSTANT VARCHAR2(30)   := 'QA_PARENT_CHILD_PKG';
18 
19 --
20 -- Through out this package all the functions will return 'T' or 'F'
21 -- instead of 'TRUE' or 'FALSE'. The reason is, we may call this
22 -- serverside functions from Java or by other platforms.
23 --
24 
25  FUNCTION aggregate_functions(p_sql_string IN VARCHAR2,
26                                p_occurrence IN NUMBER,
27                                p_child_plan_id IN NUMBER,
28                                x_value OUT NOCOPY NUMBER) RETURN VARCHAR2 IS
29    l_value NUMBER;
30 
31   BEGIN
32      BEGIN
33          EXECUTE IMMEDIATE p_sql_string INTO l_value USING p_occurrence,p_child_plan_id;
34 
35          -- Bug 2716973
36          -- Even though fix here is not required, but for consistency adding NVL function here.
37          -- rponnusa Sun Jan 12 23:59:07 PST 2003
38 
39          x_value := NVL(l_value,0);
40          RETURN 'T';
41      EXCEPTION
42         WHEN OTHERS THEN
43              RETURN 'F';
44      END;
45 
46  END aggregate_functions;
47 
48  --
49  -- bug 5682448
50  -- added the Txn_header_id parameter
51  -- ntungare Wed Feb 21 07:28:43 PST 2007
52  --
53  FUNCTION aggregate_functions(p_sql_string IN VARCHAR2,
54                               p_occurrence IN NUMBER,
55                               p_child_plan_id IN NUMBER,
56                               p_txn_header_id IN NUMBER,
57                               x_value OUT NOCOPY NUMBER) RETURN VARCHAR2 IS
58    l_value NUMBER;
59 
60   BEGIN
61      BEGIN
62          EXECUTE IMMEDIATE p_sql_string INTO l_value
63            USING p_occurrence,p_child_plan_id,p_txn_header_id;
64 
65          -- Bug 2716973
66          -- Even though fix here is not required, but for consistency adding NVL function here.
67          -- rponnusa Sun Jan 12 23:59:07 PST 2003
68          x_value := NVL(l_value,0);
69          RETURN 'T';
70      EXCEPTION
71         WHEN OTHERS THEN
72              RETURN 'F';
73      END;
74 
75  END aggregate_functions;
76 
77 
78  FUNCTION commit_allowed(p_plan_id NUMBER, p_collection_id NUMBER,
79                          p_occurrence NUMBER ,p_child_plan_ids VARCHAR2)   RETURN VARCHAR2 IS
80   l_incomplete_plan_ids VARCHAR2(10000);
81   BEGIN
82 
83     -- Bug 5161719. SHKALYAN 13-Apr-2006
84     -- Modified to call the new overloaded commit_allowed to avoid
85     -- code duplication
86     RETURN commit_allowed
87            (
88              p_plan_id => p_plan_id,
89              p_collection_id => p_collection_id,
90              p_occurrence => p_occurrence,
91              p_child_plan_ids => p_child_plan_ids,
92              x_incomplete_plan_ids => l_incomplete_plan_ids
93            );
94   END commit_allowed;
95 
96   -- Bug 5161719. SHKALYAN 13-Apr-2006
97   -- Created this overloaded commit_allowed function to pass back to the
98   -- caller a list of incomplete child plan ids in x_incomplete_plan_ids
99   -- This is because in OAF Txn integration project the message is expected
100   -- to have the incomplete child plan information.
101   -- Rest of the logic was moved from the old get_plan_name
102   -- to avoid code duplication.
103   FUNCTION commit_allowed(
104                  p_plan_id                         NUMBER,
105                  p_collection_id                   NUMBER,
106                  p_occurrence                      NUMBER,
107                  p_child_plan_ids                  VARCHAR2,
108                  x_incomplete_plan_ids  OUT NOCOPY VARCHAR2) RETURN VARCHAR2 IS
109 
110 ---
111 --- Simple function which returns True when results are collected for
112 --- immediate child plans else returns False.
113 ---
114 --- Important thing to remember here is  that collection_id for parent
115 --- child plan are same in case of EQR. That is the reason I have included
116 --- one more where condtion in the cursor c2. See the following statement
117 ---          'AND   child_collection_id = p_collection_id '
118 ---
119 --- The parameter 'p_child_plan_ids' will contain all the immediate child plan ids
120 --- separated by comma operator.
121 
122 
123   l_child_id_array       ChildPlanArray;
124   l_child_plan_id        NUMBER;
125   l_total_length         NUMBER;
126   l_result               VARCHAR2(1);
127   separator  CONSTANT    VARCHAR2(1) := ',';
128 
129 -- Bug 2300962. Removed child_collection_id in the where clause
130 -- To check, child is entered or not child plan id is enough.
131 
132   CURSOR c2(c_child_plan_id NUMBER)  IS
133                SELECT 'T' FROM qa_pc_results_relationship
134                WHERE  parent_plan_id = p_plan_id
135                AND    parent_collection_id = p_collection_id
136                AND    parent_occurrence = p_occurrence
137                AND    child_plan_id = c_child_plan_id
138                AND    rownum =1;
139 
140   BEGIN
141    l_result := 'F';
142    l_total_length := LENGTH(p_child_plan_ids);
143 
144    -- We need check for all the child_plan_ids one by one to see whether records are
145    -- entered for the child plan or not.
146 
147   -- anagarwa Mon Apr 15 15:51:58 PDT 2002
148   -- Bug 2320896 was being caused due to error in logic.
149   -- This code is being replaced to avoid character to number conversion
150 
151 
152    parse_list(p_child_plan_ids, l_child_id_array);
153 
154    FOR i IN 1..l_child_id_array.COUNT LOOP
155       l_child_plan_id := l_child_id_array(i);
156       OPEN c2(l_child_plan_id);
157       FETCH c2 INTO l_result;
158       IF (c2%NOTFOUND) THEN
159          l_result := 'F';
160 
161          -- Bug 5161719. SHKALYAN 13-Apr-2006
162          -- In addition to setting result as false form the list of
163          -- incomplete plan ids
164          x_incomplete_plan_ids := x_incomplete_plan_ids || separator || l_child_plan_id;
165          CLOSE c2;
166          EXIT;
167       END IF;
168       CLOSE c2;
169 
170    END LOOP;
171 
172    -- Bug 5161719. SHKALYAN 13-Apr-2006
173    -- Remove the leading comma
174    IF ( x_incomplete_plan_ids IS NOT NULL ) THEN
175      x_incomplete_plan_ids := SUBSTR( x_incomplete_plan_ids, LENGTH(separator) + 1 );
176    END IF;
177 
178    RETURN l_result;
179 
180  END commit_allowed;
181 
182 
183  PROCEDURE enable_and_fire_actions(p_collection_id    NUMBER) IS
184 
185 ---
186 ---  This procedure commits all the records corresponding to one single session with status = 2.
187 ---  This is required since all the child records will be saved with qa_results.status =1
188 ---  When the child record is enabled, status code will be changed to 2. The status of
189 ---  child record is changed to 2 only when Parent record gets committed
190 ---
191 
192   BEGIN
193        qa_results_api.enable_and_fire_action(p_collection_id);
194  END enable_and_fire_actions;
195 
196  FUNCTION get_descendants(
197       p_plan_id         NUMBER,
198       p_collection_id   NUMBER,
199       p_occurrence      NUMBER,
200       x_plan_ids          OUT NOCOPY dbms_sql.number_table,
201       x_collection_ids    OUT NOCOPY dbms_sql.number_table,
202       x_occurrences       OUT NOCOPY dbms_sql.number_table)  RETURN VARCHAR2 IS
203 
204 ---
205 --- Given a parent record (plan/collection/occurrence), this procedure finds all the child and
206 --- grandchildren records (therefore, descendants) of the record.  These are returned in the
207 --- three output PL/SQL tables.  The parent record itself is not included in the output.
208 --- The query technical is called hierarchical subquery.  The final where clause makes
209 --- sure the child record is actually enabled in the  qa_results table.
210 ---
211 
212   BEGIN
213 
214     SELECT      child_plan_id,  child_collection_id,  child_occurrence
215     BULK COLLECT INTO
216                 x_plan_ids,  x_collection_ids,  x_occurrences
217     FROM        qa_pc_results_relationship r
218     WHERE EXISTS (
219                 SELECT 1
220                 FROM qa_results qr
221                 WHERE qr.plan_id = r.child_plan_id AND
222                       qr.collection_id = r.child_collection_id AND
223                       qr.occurrence = r.child_occurrence AND
224                       (qr.status IS NULL or qr.status=2) )
225     START WITH  parent_plan_id = p_plan_id AND
226                 parent_collection_id = p_collection_id AND
227                 parent_occurrence = p_occurrence
228     CONNECT BY  PRIOR child_occurrence = parent_occurrence;
229 
230     IF (SQL%FOUND) THEN
231       RETURN 'T';
232     ELSE
233       RETURN 'F';
234     END IF;
235 
236  END get_descendants;
237 
238 ---------------------------------------------------------------------------
239  FUNCTION evaluate_child_lov_criteria( p_plan_id          IN NUMBER,
240                                         p_criteria_values  IN VARCHAR2,
241                                         x_child_plan_ids  OUT NOCOPY VARCHAR2)
242                                         RETURN VARCHAR2 IS
243 ---
244 --- This function finds all the matching child plan for the current plan.
245 --- First converts the values passed through p_criteria_values
246 --- into array. For each child plan we checking for the criteria values
247 --- by calling another function 'criteria_matched'.
248 --- We will concatenate all the child id into string with separator as ','
249 --- Return true if any matching child availabe with the concatenated
250 --- child plan_id's otherwise return false.
251 ---
252 
253       -- Bug 2448888. when all child plans have effective from and to date range is
254       -- outside the sysdate then, FRM-41084:- Error getting Group Cell raised when
255       -- child button is hit. This is similar to bug Bug 2355817.
256       -- Make a join to qa_plans in cursor C and fetch only effective child plans.
257       -- rponnusa Tue Jul  9 00:25:19 PDT 2002
258 
259       CURSOR c IS SELECT qpr.plan_relationship_id,qpr.child_plan_id
260                   FROM   qa_plans qp,
261                          qa_pc_plan_relationship qpr
262                   WHERE  qpr.parent_plan_id = p_plan_id
263                   AND    qpr.child_plan_id = qp.plan_id
264                   AND    qpr.plan_relationship_type = 1
265                   AND    qpr.data_entry_mode in (1,2,3)
266                   AND ((qp.effective_to IS NULL AND TRUNC(SYSDATE) >= qp.effective_from)
267                        OR (qp.effective_from IS NULL AND TRUNC(SYSDATE) <= qp.effective_to)
268                        OR (qp.effective_from IS NOT NULL AND qp.effective_to IS NOT NULL
269                            AND TRUNC(SYSDATE) BETWEEN qp.effective_from AND qp.effective_to)
270                        OR (qp.effective_from IS NULL AND qp.effective_to IS NULL ));
271 
272      current_child_plan_id  NUMBER;
273      p_plan_relationship_id NUMBER;
274      ret_value              VARCHAR2(1);
275      childexist             BOOLEAN;
276      elements               qa_txn_grp.ElementsArray;
277   BEGIN
278      ret_value := 'F';
279      childexist := FALSE;
280      elements := qa_txn_grp.result_to_array(p_criteria_values);
281      OPEN c;
282      LOOP
283         FETCH c INTO p_plan_relationship_id,current_child_plan_id;
284         IF (c%NOTFOUND) THEN
285           EXIT;
286         END IF;
287 
288         IF( criteria_matched(p_plan_relationship_id,elements) = 'T') THEN
289 
290             IF( childexist) THEN
291                x_child_plan_ids := x_child_plan_ids ||','||current_child_plan_id;
292             ELSE
293                x_child_plan_ids :=current_child_plan_id;
294                childexist := TRUE;
295             END IF;
296         END IF;
297      END LOOP;
298 
299      IF (c%ROWCOUNT = 0) THEN
300         ret_value := 'F';
301      ELSIF (x_child_plan_ids IS NULL) THEN
302         ret_value := 'F';
303      ELSE
304         ret_value := 'T';
305      END IF;
306      CLOSE c;
307 
308      RETURN ret_value;
309  END evaluate_child_lov_criteria;
310 
311 /* following function added to be able to view history records in VQR.
312    The name is eval_updateview_lov_criteria and NOT evaluate_updateview_lov_criteria
313    because there's a character limit for length of function name in package.
314 */
315 
316  FUNCTION eval_updateview_lov_criteria( p_plan_id          IN NUMBER,
317                                         p_criteria_values  IN VARCHAR2,
318                                         x_child_plan_ids  OUT NOCOPY VARCHAR2)
319                                         RETURN VARCHAR2 IS
320 ---
321 --- This function finds all the matching child plan for the current plan.
322 --- First converts the values passed through p_criteria_values
323 --- into array. For each child plan we checking for the criteria values
324 --- by calling another function 'criteria_matched'.
325 --- We will concatenate all the child id into string with separator as ','
326 --- Return true if any matching child availabe with the concatenated
327 --- child plan_id's otherwise return false.
328 ---
329 
330       -- Bug 2448888. when all child plans have effective from and to date range is
331       -- outside the sysdate then, FRM-41084:- Error getting Group Cell raised when
332       -- child button is hit. This is similar to bug Bug 2355817.
333       -- Make a join to qa_plans in cursor C and fetch only effective child plans.
334       -- rponnusa Tue Jul  9 00:25:19 PDT 2002
335 
336       CURSOR c IS SELECT qpr.plan_relationship_id,qpr.child_plan_id
337                   FROM   qa_plans qp,
338                          qa_pc_plan_relationship qpr
339                   WHERE  qpr.parent_plan_id = p_plan_id
340                   AND    qpr.child_plan_id = qp.plan_id
341                   AND    qpr.plan_relationship_type = 1
342                   AND    qpr.data_entry_mode in (1,2,3,4)
343                   AND ((qp.effective_to IS NULL AND TRUNC(SYSDATE) >= qp.effective_from)
344                        OR (qp.effective_from IS NULL AND TRUNC(SYSDATE) <= qp.effective_to)
345                        OR (qp.effective_from IS NOT NULL AND qp.effective_to IS NOT NULL
346                            AND TRUNC(SYSDATE) BETWEEN qp.effective_from AND qp.effective_to)
347                        OR (qp.effective_from IS NULL AND qp.effective_to IS NULL ));
348 
349      current_child_plan_id  NUMBER;
350      p_plan_relationship_id NUMBER;
351      ret_value              VARCHAR2(1);
352      childexist             BOOLEAN;
353      elements               qa_txn_grp.ElementsArray;
354   BEGIN
355      ret_value := 'F';
356      childexist := FALSE;
357      elements := qa_txn_grp.result_to_array(p_criteria_values);
358      OPEN c;
359      LOOP
360         FETCH c INTO p_plan_relationship_id,current_child_plan_id;
361         IF (c%NOTFOUND) THEN
362           EXIT;
363         END IF;
364 
365         IF( criteria_matched(p_plan_relationship_id,elements) = 'T') THEN
366 
367             IF( childexist) THEN
368                x_child_plan_ids := x_child_plan_ids ||','||current_child_plan_id;
369             ELSE
370                x_child_plan_ids :=current_child_plan_id;
371                childexist := TRUE;
372             END IF;
373         END IF;
374      END LOOP;
375 
376      IF (c%ROWCOUNT = 0) THEN
377         ret_value := 'F';
378      ELSIF (x_child_plan_ids IS NULL) THEN
379         ret_value := 'F';
380      ELSE
381         ret_value := 'T';
382      END IF;
383      CLOSE c;
384 
385      RETURN ret_value;
386 
387  END eval_updateview_lov_criteria;
388 
389 -----------------------------------------------------------------------------------------------------
390  FUNCTION criteria_matched(p_plan_relationship_id IN NUMBER,
391                             p_criteria_array qa_txn_grp.ElementsArray)
392                             RETURN VARCHAR2 IS
393 
394 ---
395 --- This function first finds out all the criteria for the parent-child
396 --- relationship through plan_relationship_id in qa_pc_criteria table.
397 --- If no criteria found then return true
398 --- else finds out all the char_id and its associated values
399 --- for the plan_relationship_id.
400 
401 --- Check for each char_id (ie,. element ) to see value available
402 --- in the parent form. We are checking this condition in the
403 --- element array (which contains all the parent-form char_id and
404 --- its associated value). If, not able to find the char_id in the
405 --- element array then return false.
406 
407 --- If there is matching char_id in element array then compare
408 --- the value in the element array with the low_value, high_value.
409 --- If everything is ok then return true, false otherwise.
410 ---
411 
412     l_char_id      NUMBER ;
413     l_operator     NUMBER ;
414     l_low_value    VARCHAR2(150);
415     l_high_value   VARCHAR2(150);
416     l_ret_value    VARCHAR2(1);
417     l_datatype     NUMBER;
418 
419     CURSOR c IS SELECT qpc.char_id,qpc.operator,qpc.low_value,qpc.high_value,qc.datatype
420                 FROM   qa_pc_criteria qpc ,qa_chars qc
421                 WHERE  qpc.plan_relationship_id = p_plan_relationship_id
422                 AND    qpc.char_id = qc.char_id;
423   BEGIN
424 
425     l_ret_value := 'F';
426     OPEN c;
427 
428     -- To launch a single child plan there may be more than one criteria defined.
429     -- Hence going into the loop to match all criteria. In case of more than one
430     -- criteria, all the criteria should match in order to return TRUE
431 
432     LOOP
433        FETCH c INTO l_char_id,  l_operator, l_low_value, l_high_value, l_datatype;
434        IF (c%NOTFOUND) THEN
435           EXIT;
436        END IF;
437 
438       -- There are records for the plan_relationship_id, our next job is to
439       -- check the value entered in the parent plan for the element, matches
440       -- with the criteria  for the same element in qa_pc_criteria
441 
442        IF (p_criteria_array.EXISTS(l_char_id)) THEN
443 
444          IF( QLTCOMPB.compare(p_criteria_array(l_char_id).value,
445                               l_operator,l_low_value,
446                               l_high_value,l_datatype)) THEN
447 
448             l_ret_value := 'T';
449          ELSE
450              -- For example if 3 criteria defined and matching condition
451              -- fails in the first criteria itself then we need not check for
452              -- other criterias, we can simply exit from the loop and
453              -- return FALSE
454 
455             l_ret_value := 'F';
456             EXIT;
457          END IF;
458        ELSE
459           -- This is a worst case. There is no value found in the element array
460           -- for the char_id
461           l_ret_value := 'F';
462        END IF;
463     END LOOP;
464 
465     IF (c%ROWCOUNT = 0) THEN
466         -- No criteria defined for the plan, so simply return TRUE
467         l_ret_value := 'T';
468     END IF;
469     CLOSE c;
470 
471     RETURN l_ret_value;
472   END criteria_matched;
473 
474 ------------------------------------------------------------------------------------------
475   FUNCTION evaluate_criteria(p_plan_id            IN NUMBER,
476                              p_criteria_values    IN VARCHAR2,
477                              p_relationship_type  IN NUMBER,
478                              p_data_entry_mode    IN NUMBER,
479                              x_child_plan_ids     OUT NOCOPY VARCHAR2) RETURN VARCHAR2 IS
480   --
481   -- This function finds out the matching child plan for the given data_entry_mode and
482   -- relationship_type. In case of matching child found returns TRUE with the child
483   -- plan_id in a comma separated string through x_child_plan_ids.
484   -- In case of no match simply returns FALSE
485   --
486 
487     CURSOR c IS SELECT   plan_relationship_id,child_plan_id
488                   FROM   qa_pc_plan_relationship
489                   WHERE  parent_plan_id    = p_plan_id
490                   AND    plan_relationship_type = p_relationship_type
491                   AND    data_entry_mode   = p_data_entry_mode;
492 
493   -- Added the cursor below to check the effectivity of the child plan.
494   -- The Cursor will fetch the child_plan only if it falls in the effective
495   -- data range. Bug 2355817. kabalakr 06 MAY 2002.
496 
497     CURSOR p(l_child_plan_id NUMBER) IS
498        SELECT plan_id
499        FROM qa_plans
500        WHERE plan_id = l_child_plan_id
501        AND ((effective_to IS NULL AND TRUNC(SYSDATE) >= effective_from)
502              OR (effective_from IS NULL AND TRUNC(SYSDATE) <= effective_to)
503              OR (effective_from IS NOT NULL AND effective_to IS NOT NULL
504                  AND TRUNC(SYSDATE) BETWEEN effective_from AND effective_to)
505              OR (effective_from IS NULL AND effective_to IS NULL ));
506 
507 
508      current_child_plan_id  NUMBER ;
509      p_plan_relationship_id NUMBER ;
510      ret_value              VARCHAR2(1);
511      childexist             BOOLEAN;
512      separator  CONSTANT    VARCHAR2(1) := ',';
513 
514      elements               qa_txn_grp.ElementsArray;
515 
516   -- Bug 2355817. kabalakr
517      l_child_pl_id          NUMBER;
518 
519   BEGIN
520      ret_value := 'F';
521      childexist := FALSE;
522      elements := qa_txn_grp.result_to_array(p_criteria_values);
523      OPEN c;
524      -- Get all the child plan id for the parent plan to find out any matching
525      -- childplan is exist or not.
526      LOOP
527 
528         FETCH c INTO p_plan_relationship_id,current_child_plan_id;
529         IF (c%NOTFOUND) THEN
530           EXIT;
531         END IF;
532 
533         -- Open cursor p for the current child_plan_id. Call criteria_matched
534         -- only if the cursor fetches the plan. Bug 2355817.
535         -- kabalakr 06 MAY 2002.
536 
537         OPEN p(current_child_plan_id);
538         FETCH p INTO l_child_pl_id;
539 
540         IF (p%FOUND) THEN
541 
542           IF( criteria_matched(p_plan_relationship_id,elements) = 'T') THEN
543 
544         -- The following 'if' condition is required because we should not return the
545         -- child plan ids with last character as the separator ( comma here)
546 
547              IF( childexist) THEN
548                x_child_plan_ids := x_child_plan_ids || separator ||current_child_plan_id;
549              ELSE
550                x_child_plan_ids :=current_child_plan_id;
551                childexist := TRUE;
552              END IF;
553 
554           END IF;
555         END IF;
556 
557         CLOSE p;
558 
559      END LOOP;
560 
561      IF (c%ROWCOUNT = 0) THEN
562         -- This scanario can happen if the  parent plan dont have child plan associated
563         -- with it.
564         ret_value := 'F';
565 
566      ELSIF (x_child_plan_ids IS NULL) THEN
567         -- This can happen when parent plan have child but the matching criteria to launch the
568         -- child fails
569         ret_value := 'F';
570      ELSE
571         ret_value := 'T';
572      END IF;
573      CLOSE c;
574 
575      RETURN ret_value;
576 
577   END evaluate_criteria;
578 
579     PROCEDURE parse_list(x_result IN VARCHAR2,
580                          x_array OUT NOCOPY ChildPlanArray) IS
581 
582         -- For longcomments enhancement, Bug 2234299
583         -- changed 'value' type from qa_results.character1%TYPE to varchar2(2000)
584         -- rponnusa Thu Mar 14 21:27:04 PST 2002
585 
586         value VARCHAR2(2000);
587         c VARCHAR2(10);
588         separator CONSTANT VARCHAR2(1) := ',';
589         arr_index INTEGER;
590         p INTEGER;
591         n INTEGER;
592 
593     BEGIN
594     --
595     -- Loop until a single ',' is found or x_result is exhausted.
596     --
597         arr_index := 1;
598         p := 1;
599         n := length(x_result);
600         WHILE p <= n LOOP
601             c := substr(x_result, p, 1);
602             p := p + 1;
603             IF (c = separator) THEN
604                x_array(arr_index) := value;
605                arr_index := arr_index + 1;
606                value := '';
607             ELSE
608                value := value || c;
609             END IF;
610 
611         END LOOP;
612         x_array(arr_index) := value;
613     END parse_list;
614 
615 --
616 -- Removed DEFAULT clause for GSCC compliance
617 -- Before removal
618 --     p_txn_header_id IN NUMBER DEFAULT NULL
619 -- After removal
620 --     p_txn_header_id IN NUMBER
621 -- rkunchal
622 --
623 
624 PROCEDURE insert_automatic_records(p_plan_id IN NUMBER,
625                                    p_collection_id IN NUMBER,
626                                    p_occurrence IN NUMBER,
627                                    p_child_plan_ids IN VARCHAR2,
628                                    p_relationship_type IN NUMBER,
629                                    p_data_entry_mode IN NUMBER,
630                                    p_criteria_values IN VARCHAR2,
631                                    p_org_id IN NUMBER,
632                                    p_spec_id IN NUMBER,
633                                    x_status OUT NOCOPY VARCHAR2,
634                                    p_txn_header_id IN NUMBER) IS
635 
636  parent_values_array    qa_txn_grp.ElementsArray;
637  l_child_id_array       ChildPlanArray;
638  l_sysdate              DATE;
639  l_length               INTEGER;
640  l_row_count            INTEGER;
641  l_count                INTEGER;
642  l_child_char_id        INTEGER;
643  l_parent_char_id       INTEGER;
644  l_p                    INTEGER;
645  l_return_int           INTEGER;
646  l_occurrence           NUMBER;
647  l_child_plan_id        NUMBER;
648  l_child_element_values VARCHAR2(32000);
649  l_messages             VARCHAR2(32000);
650  l_rowid                VARCHAR2(1000);
651 
652  --
653  -- Bug 9015927
654  -- Added the following variables/types for fetching
655  -- the default values for elements and store them in
656  -- an array.
657  -- skolluku
658  --
659  TYPE def_arr_typ IS TABLE OF QA_PLAN_CHARS.DEFAULT_VALUE%TYPE INDEX BY BINARY_INTEGER;
660  def_arr def_arr_typ;
661  cntr NUMBER;
662  CURSOR def_cur(c_child_plan_id NUMBER) IS
663    SELECT
664        qpc.char_id,
665        qpc.default_value
666    FROM qa_plan_chars qpc,
667         qa_plans qp
668    WHERE qp.plan_id = qpc.plan_id
669      AND qpc.default_value IS NOT NULL
670      AND qpc.enabled_flag=1
671      AND qp.plan_id = c_child_plan_id;
672 
673  CURSOR row_num_cur(c_child_plan_id NUMBER) IS
674       SELECT auto_row_count
675       FROM   qa_pc_plan_relationship
676       WHERE  parent_plan_id = p_plan_id
677       AND    child_plan_id = c_child_plan_id;
678 
679 
680  -- anagarwa Mon Dec 16 16:55:09 PST 2002
681  -- Bug 2701777
682  -- if parent or child elements are disabled and the parent child relationship
683  -- still exists for them then insert API  qa_mqa_results.post_result raises
684  -- returns an error and prevents the history as well as automatic results
685  -- from being saved. It causes a ON-INSERT trigger being raised on forms
686  -- and even the parent results cannot be saved.
687  -- To fix the problem, qa_pc_result_column_v is being modified to have parent
688  -- and child char's enabled flags which are checked to be 1 before the values
689  -- are copied.
690 
691  CURSOR char_id_cur(c_child_plan_id NUMBER) IS
692       SELECT parent_char_id, child_char_id
693       FROM   qa_pc_result_columns_v
694       WHERE  parent_plan_id = p_plan_id
695       AND    child_plan_id = c_child_plan_id
696       AND    parent_enabled_flag = 1
697       AND    child_enabled_flag = 1;
698 
699  -- Bug 3678910. In Automatic data collection, sequence generation should be
700  -- enabled for Sequence type elements. The below cursor will fetch all the
701  -- sequence element char_ids which is not a target for Copy Element relation.
702  -- If there exist any copy relation with sequence element as target, the value
703  -- will be copied from the parent plan. Sequence will not get generated in that
704  -- case. kabalakr.
705 
706  -- Bug 4958734.  SQL Repository Fix SQL ID: 15007931
707  CURSOR child_seq_char_ids(c_child_plan_id NUMBER) IS
708     SELECT qc.char_id
709       FROM qa_plan_chars qpc, qa_chars qc
710       WHERE qpc.plan_id = c_child_plan_id
711         AND qpc.char_id = qc.char_id
712         AND qpc.enabled_flag = 1
713         AND qc.datatype = 5
714     MINUS
715       SELECT child_char_id
716       FROM qa_pc_result_columns_v
717       WHERE parent_plan_id = p_plan_id
718         AND child_plan_id = c_child_plan_id
719         AND parent_enabled_flag = 1
720         AND child_enabled_flag = 1;
721 /*
722       SELECT qc.char_id
723       FROM   qa_plan_chars qpc,
724              qa_chars qc
725       WHERE  qpc.plan_id = c_child_plan_id
726       AND    qpc.char_id = qc.char_id
727       AND    qpc.enabled_flag = 1
728       AND    qc.datatype = 5
729       AND    qc.char_id NOT IN
730                 (SELECT child_char_id
731                  FROM   qa_pc_result_columns_v
732                  WHERE  parent_plan_id = p_plan_id
733                  AND    child_plan_id = c_child_plan_id
734                  AND    parent_enabled_flag = 1
735                  AND    child_enabled_flag = 1);
736 */
737 
738  l_seq_default_str VARCHAR(30);
739 
740  --
741  -- Bug 5383667
742  -- String to hold the Id values
743  -- ntungare
744  --
745  l_char_id_val  VARCHAR2(2000);
746  l_id_str       VARCHAR2(2000);
747 
748  --
749  -- bug 6086385
750  -- New variable to catch the status returned
751  -- by the insert_history_auto_rec_QWB proc
752  -- called for the subsequent child records
753  -- ntungare Thu Jul  5 06:50:27 PDT 2007
754  --
755  auto_hist_proc_stat varchar2(2000);
756 
757  --
758  -- bug 6086385
759  -- New variable to read the occurrence of
760  -- the Child plan record enetred
761  -- ntungare Thu Jul  5 06:50:27 PDT 2007
762  --
763  l_child_occurrence    NUMBER;
764 
765  --
766  -- Bug 9015927
767  --
768  flag boolean;
769  BEGIN
770      l_length := length(p_child_plan_ids);
771      l_count  := 1;
772      l_sysdate := sysdate;
773 
774      -- flatten the p_criteria_values string into an array
775      parent_values_array := qa_txn_grp.result_to_array(p_criteria_values);
776 
777      --parse p_child_plan_ids to get child plan ids in an array
778      IF p_child_plan_ids IS NOT NULL THEN
779          l_p := 0;
780          parse_list(p_child_plan_ids, l_child_id_array);
781      END IF;
782      --for each child plan insert automatic rows as follows
783      FOR i IN 1..l_child_id_array.COUNT LOOP
784 
785          l_child_plan_id := l_child_id_array(i);
786          --
787          -- Bug 9015927
788          -- Initialize the default values array for
789          -- the current child plan.
790          -- skolluku
791          --
792          def_arr.delete();
793          FOR def_rec IN def_cur(l_child_plan_id) LOOP
794              def_arr(def_rec.char_id) := def_rec.default_value;
795          END LOOP;
796 
797          --if p_relationship_type=1 and p_data_entry_mode=4, it means we are
798          --entering rows for History plan. The number of rows to be entered
799          -- in this case is always 1. ELSE get the number of rows to be entered.
800          IF(p_relationship_type=1 AND p_data_entry_mode=4) THEN
801              l_row_count := 1;
802          ELSE
803              OPEN row_num_cur(l_child_id_array(i));
804              fetch row_num_cur into l_row_count;
805              CLOSE row_num_cur;
806          END IF;
807          --for row_count
808          WHILE l_count <= l_row_count LOOP
809              --OPEN cursor of parent_char_id and child_char_id from
810              -- QA_PC_RESULTS_COLUMN_V for p_plan_id and current child plan id
811              --for each cursor row
812              l_child_element_values := '';
813              FOR char_id_record IN char_id_cur(l_child_id_array(i)) LOOP
814                  l_parent_char_id := char_id_record.parent_char_id;
815                  l_child_char_id := char_id_record.child_char_id;
816                  --
817                  -- Bug 9015927
818                  -- Remove the element getting its value from Parent
819                  -- plan, from the default array so that the copied value
820                  -- is not overwritten by the default value.
821                  -- skolluku
822                  --
823                  def_arr.delete(l_child_char_id);
824 
825                  -- Bug 2403395
826                  -- Added 'replace' command to doubly encode ''@' character
827                  -- if the l_parent_char_id.value contains '@' character.
828                  -- rponnusa Wed Jun  5 00:49:14 PDT 2002
829                  l_child_element_values := l_child_element_values || '@' ||
830                        l_child_char_id || '=' ||
831                        replace(parent_values_array(l_parent_char_id).value,'@','@@');
832 
833                  --
834                  -- Bug 5383667
835                  -- Constructing the Id str
836                  -- The id string has to be built of the format
837                  -- charid=value@charid=value.
838                  -- ntungare
839                  --
840                  l_char_id_val := qa_plan_element_api.get_id_val
841                                         (l_child_char_id,
842                                          p_plan_id,
843                                          p_collection_id,
844                                          p_occurrence);
845 
846                  If l_char_id_val IS NOT NULL THEN
847                     l_id_str := l_id_str || '@' || l_child_char_id || '='|| l_char_id_val;
848                  End If;
849 
850              END LOOP; -- for all columns to be copied
851              --
852              -- Bug 9015927
853              -- Add the default values for the elements that are not
854              -- copied from the Parent plan.
855              -- skolluku
856              --
857              cntr := def_arr.first;
858              WHILE cntr <= def_arr.last LOOP
859                 l_child_element_values := l_child_element_values || '@' ||
860                     cntr || '=' ||
861                     replace(def_arr(cntr),'@','@@');
862                 cntr := def_arr.next(cntr);
863              END LOOP;
864 
865              -- Bug 3678910. Now, check whether we are inserting records for
866              -- data entry mode - Automatic. If yes, we should make sure to generate
867              -- sequence numbers (assign the string 'Automatic') for sequence type
868              -- elements that are not copy targets. kabalakr.
869 
870              IF(p_relationship_type=1 AND p_data_entry_mode=2) THEN
871 
872                fnd_message.set_name('QA','QA_SEQ_DEFAULT');
873                l_seq_default_str := fnd_message.get;
874 
875                FOR seq_char_id_record IN child_seq_char_ids(l_child_id_array(i))
876                LOOP
877                   l_child_element_values := l_child_element_values || '@' ||
878                                             seq_char_id_record.char_id || '=' ||
879                                             l_seq_default_str;
880                END LOOP;
881 
882              END IF; -- If Automatic. End of bug 3678910.
883 
884              --
885              -- Bug 5383667
886              -- Removing the extra @ appended at the start
887              -- ntungare
888              --
889              If l_id_str IS NOT NULL THEN
890                 l_id_str := SUBSTR(l_id_str, 2);
891              END If;
892 
893              IF (l_child_element_values IS NOT NULL) THEN
894                  l_child_element_values := substr(l_child_element_values,2);
895                  l_p :=1;
896 
897                  --
898                  -- bug 5682448
899                  -- modified the call to the proc to send the commit
900                  -- flag as no (0)
901                  -- ntungare Wed Feb 21 07:31:00 PST 2007
902                  --
903 
904                  -- Bug 2290747.Added parameter p_txn_header_id to enable
905                  -- history plan record when parent plan gets updated
906                  -- rponnusa Mon Apr  1 22:25:49 PST 2002
907 
908                  -- anagarwa Thu Dec 19 15:43:27 PST 2002
909                  -- Bug 2701777
910                  -- post_result_with_no_validation inserts records into
911                  -- qa_results without any validations. This prevents any
912                  -- errors if user changes element values in parent plan
913                  -- but not the History plan
914 
915                  --
916                  -- bug 5383667
917                  -- Passing the Id string as well
918                  -- ntungare
919                  --
920                  l_return_int:= qa_mqa_results.post_result_with_no_validation(
921                                             l_occurrence,
922                                             p_org_id,
923                                             l_child_plan_id, p_spec_id,
924                                             p_collection_id,
925                                             l_child_element_values,
926                                             l_id_str, '', l_p, 0, l_messages,
927                                             p_txn_header_id);
928 
929                  --ilawler - bug #2648137 - Fri Mar 19 09:50:07 2004
930                  --added post_result return check
931                  IF l_return_int = -1 THEN
932                     x_status := 'F';
933                     RETURN;
934                  END IF;
935 
936                  -- anagarwa Fri Aug 30 13:07:05 PDT 2002
937                  -- Bug 2517932
938                  -- following added to copy attachments to History records.
939 
940                  IF p_data_entry_mode = 4 THEN
941                      FND_ATTACHED_DOCUMENTS2_PKG.copy_attachments(
942                                X_from_entity_name => 'QA_RESULTS',
943                                X_from_pk1_value   => to_char(p_occurrence),
944                                X_from_pk2_value   => to_char(p_collection_id),
945                                X_from_pk3_value   => to_char(p_plan_id),
946                                X_to_entity_name   => 'QA_RESULTS',
947                                X_to_pk1_value     => to_char(l_occurrence),
948                                X_to_pk2_value     => to_char(p_collection_id),
949                                X_to_pk3_value     => to_char(l_child_plan_id));
950                  END IF;
951 
952                  -- insert the relationships
953                  -- Gapless Sequence Proj. rponnusa Wed Jul 30 04:52:45 PDT 2003
954                  -- passing child_txn_header_id
955                  QA_PC_RESULTS_REL_PKG.Insert_Row(
956                        X_Rowid                   => l_rowid,
957                        X_Parent_Plan_Id          => p_plan_id,
958                        X_Parent_Collection_Id    => p_collection_id,
959                        X_Parent_Occurrence       => p_occurrence,
960                        X_Child_Plan_Id           => l_child_plan_id,
961                        X_Child_Collection_Id     => p_collection_id,
962                        X_Child_Occurrence        => l_occurrence,
963                        X_Enabled_Flag            => 1,
964                        X_Last_Update_Date        => l_sysdate,
965                        X_Last_Updated_By         => fnd_global.user_id,
966                        X_Creation_Date           => l_sysdate,
967                        X_Created_By              => fnd_global.user_id,
968                        X_Last_Update_Login       => fnd_global.user_id,
969                        X_Child_Txn_Header_Id     => p_txn_header_id);
970 
971              END IF;
972              l_count := l_count + 1;
973              --
974              -- Bug 9015927
975              -- Added following call to the actions processor to fire actions only
976              -- for automatic child records.
977              -- skolluku
978              --
979              flag := QLTDACTB.DO_ACTIONS(p_collection_id,  1, NULL,  NULL,
980                                     TRUE , FALSE, 'BACKGROUND_ASSIGN_VALUE' , 'COLLECTION_ID',
981                                     l_occurrence,l_child_plan_id,'COLLECTION_ID');
982 
983              --
984              -- Bug 5383667
985              -- Resetting the Id string for the next row being
986              -- processed
987              -- ntungare
988              l_id_str :=  NULL;
989 
990              --
991              -- bug 6086385
992              -- Getting the Occurrence of the Child record that has been
993              -- inserted
994              -- nutngare Thu Jul  5 05:21:16 PDT 2007
995              --
996              SELECT MAX(occurrence)
997                into l_child_occurrence
998                 FROM   qa_results
999               WHERE  plan_id = l_child_plan_id and
1000                      collection_id = p_collection_id and
1001                      organization_id = p_org_id and
1002                      txn_header_id = p_txn_header_id;
1003 
1004              --
1005              -- bug 6086385
1006              -- Processing the Subsequent Automatic Child plans
1007              -- Using the insert_history_auto_rec_QWB instead of
1008              -- insert_history_auto_rec to make sure that the Txn_header_id
1009              -- is not incremented
1010              -- ntungare Thu Jul  5 05:15:29 PDT 2007
1011              --
1012              insert_history_auto_rec_QWB(p_plan_id           => l_child_plan_id,
1013                                          p_collection_id     => p_collection_id,
1014                                          p_occurrence        => l_child_occurrence,
1015                                          p_organization_id   => p_org_id,
1016                                          p_txn_header_id     => p_txn_header_id,
1017                                          p_relationship_type => 1,
1018                                          p_data_entry_mode   => 2 ,
1019                                          x_status            => auto_hist_proc_stat);
1020 
1021              --
1022              -- bug 6086385
1023              -- Processing the History Child plans
1024              -- Using the insert_history_auto_rec_QWB instead of
1025              -- insert_history_auto_rec to make sure that the Txn_header_id
1026              -- is not incremented
1027              -- ntungare Thu Jul  5 05:15:29 PDT 2007
1028              --
1029              insert_history_auto_rec_QWB(p_plan_id           => l_child_plan_id,
1030                                          p_collection_id     => p_collection_id,
1031                                          p_occurrence        => l_child_occurrence,
1032                                          p_organization_id   => p_org_id,
1033                                          p_txn_header_id     => p_txn_header_id,
1034                                          p_relationship_type => 1,
1035                                          p_data_entry_mode   => 4 ,
1036                                          x_status            => auto_hist_proc_stat);
1037 
1038          END LOOP; --for number of rows
1039 
1040  /* Bug 3223081 : Added the following statement to reset the l_count to 1 after all the rows are inserted for one child plan
1041                         l_count :=1;
1042     - akbhatia
1043  */
1044            l_count :=1;
1045         -- i := i + 1;
1046      END LOOP; --outer for loop for child plans
1047      x_status := 'T';
1048  END;
1049 
1050 
1051 
1052 
1053 FUNCTION descendants_exist(p_plan_id NUMBER,
1054                            p_collection_id NUMBER,
1055                            p_occurrence NUMBER)
1056          RETURN VARCHAR2 IS
1057 ---
1058 --- This function takes in plan_id, collection_id and occurrence and returns a 'T'
1059 --- if it finds any child record for this record. Otherwise it returns 'F'.
1060 ---
1061 
1062 --l_exists INTEGER;
1063   l_exists VARCHAR2(1);
1064 
1065     CURSOR descendant_cur IS
1066            SELECT  'T'
1067            FROM  qa_pc_results_relationship
1068            WHERE parent_occurrence = p_occurrence
1069            AND   rownum = 1;
1070 
1071 
1072  BEGIN
1073     l_exists := 'F';
1074     OPEN descendant_cur;
1075     FETCH descendant_cur INTO l_exists;
1076     IF (descendant_cur%NOTFOUND) THEN
1077        l_exists := 'F';
1078     END IF;
1079 
1080     CLOSE descendant_cur;
1081     RETURN l_exists;
1082 
1083  END;
1084 
1085 FUNCTION get_disabled_descendants(p_plan_id NUMBER,
1086                              p_collection_id NUMBER,
1087                              p_occurrence NUMBER,
1088                              --p_enabled    NUMBER,
1089                              x_plan_ids OUT NOCOPY dbms_sql.number_table,
1090                              x_collection_ids OUT NOCOPY dbms_sql.number_table,
1091                              x_occurrences OUT NOCOPY dbms_sql.number_table)
1092          RETURN VARCHAR2 IS
1093 ---
1094 --- This function is similar to get_descendants above with one difference
1095 --- it looks for all disabled records .
1096 ---
1097 
1098  BEGIN
1099 
1100   BEGIN
1101     SELECT     child_plan_id, child_collection_id, child_occurrence
1102     BULK COLLECT INTO
1103            x_plan_ids, x_collection_ids, x_occurrences
1104     FROM       qa_pc_results_relationship r
1105     WHERE EXISTS (
1106                SELECT 1
1107                FROM  qa_results qr
1108                WHERE qr.plan_id = r.child_plan_id AND
1109                      qr.collection_id = r.child_collection_id AND
1110                      qr.occurrence = r.child_occurrence AND
1111                     qr.status = 1 )
1112     START WITH parent_plan_id = p_plan_id AND
1113            parent_collection_id = p_collection_id AND
1114            parent_occurrence = p_occurrence
1115     CONNECT BY PRIOR child_occurrence = parent_occurrence;
1116   EXCEPTION
1117     WHEN NO_DATA_FOUND THEN
1118          RETURN 'F';
1119   END;
1120 
1121   IF SQL%FOUND THEN
1122      RETURN 'T';
1123   ELSE
1124      RETURN 'F';
1125   END IF;
1126 
1127  END;
1128 
1129 PROCEDURE delete_child_rows(p_plan_ids IN dbms_sql.number_table,
1130                             p_collection_ids IN dbms_sql.number_table,
1131                             p_occurrences IN dbms_sql.number_table,
1132                             p_parent_plan_id       NUMBER ,
1133                             p_parent_collection_id NUMBER ,
1134                             p_parent_occurrence    NUMBER ,
1135                             p_enabled_flag         VARCHAR2)
1136 
1137           IS
1138 ---
1139 --- The following procedure takes in plan_id, collection id and occurrece and
1140 --- deletes these rows from QA_RESULTS. It also deletes entry for these rows
1141 --- from relationships tables.
1142 ---
1143 --- p_enabled_flag holds    'T'  => delete only enabled child records
1144 ---                         'F'  => delete only disabled child records
1145 
1146   i INTEGER ;
1147 
1148  BEGIN
1149 
1150     i := 0;
1151 
1152     -- Gapless Sequence Proj. rponnusa Wed Jul 30 04:52:45 PDT 2003
1153     -- Call the sequence api to capture audit information for the child/grand
1154     -- child record records. Audit info. for toplevel parent is not
1155     -- collected here.
1156 
1157     -- capture audit only when enabled child records (status NULL or 2)
1158     -- are deleted
1159     IF p_enabled_flag = 'T' THEN
1160 
1161        QA_SEQUENCE_API.audit_sequence_values(
1162                                 p_plan_ids,
1163                                 p_collection_ids,
1164                                 p_occurrences,
1165                                 p_parent_plan_id,
1166                                 p_parent_collection_id,
1167                                 p_parent_occurrence);
1168     END IF;
1169 
1170     FORALL i IN p_occurrences.FIRST .. p_occurrences.LAST
1171        DELETE from QA_RESULTS
1172        WHERE  plan_id       = p_plan_ids(i)
1173        AND    collection_id = p_collection_ids(i)
1174        AND    occurrence    = p_occurrences(i);
1175 
1176    FORALL i IN p_occurrences.FIRST .. p_occurrences.LAST
1177        DELETE from QA_PC_RESULTS_RELATIONSHIP
1178        WHERE  child_occurrence =  p_occurrences(i);
1179  END delete_child_rows;
1180 
1181 
1182  PROCEDURE enable_fire_for_txn_hdr_id(p_txn_header_id IN NUMBER) IS
1183  flag BOOLEAN ;
1184 
1185  BEGIN
1186 
1187      IF p_txn_header_id is not null THEN
1188         UPDATE qa_results
1189         SET status = 2
1190         WHERE txn_header_id = p_txn_header_id;
1191 
1192         flag := QLTDACTB.DO_ACTIONS(p_txn_header_id,  1, NULL,  NULL,
1193                                     FALSE , FALSE, 'DEFERRED' , 'TXN_HEADER_ID');
1194      END IF;
1195  END;
1196 
1197  --
1198  -- bug 5682448
1199  -- New proc to enable the records and fire
1200  -- the actions for all those enabled records
1201  -- ntungare Wed Feb 21 07:34:11 PST 2007
1202  --
1203  PROCEDURE enable_fire_for_coll_id(p_txn_header_id IN NUMBER) IS
1204     flag BOOLEAN ;
1205 
1206     Type num_tab_typ is table of number index by binary_integer;
1207 
1208     plan_id_tab        num_tab_typ;
1209     collection_id_tab  num_tab_typ;
1210     occurrence_tab     num_tab_typ;
1211 
1212  BEGIN
1213      IF p_txn_header_id is not null THEN
1214 
1215         -- Updating the rows in the QA_RESULTS which are currently
1216         -- invalid
1217         --
1218         UPDATE qa_results
1219         SET status = 2
1220         WHERE txn_header_id = p_txn_header_id
1221           and status =1
1222         RETURNING plan_id, collection_id, occurrence
1223           BULK COLLECT INTO plan_id_tab, collection_id_tab, occurrence_tab;
1224 
1225         -- Looping through all the updated records and firing
1226         -- actions for them
1227         --
1228         For Cntr in 1..plan_id_tab.COUNT
1229              LOOP
1230                 -- Calling the do_actions for the plan_id, collection_id,
1231                 -- Occurrence combination
1232                 --
1233                 flag := QLTDACTB.DO_ACTIONS
1234                           (X_TXN_HEADER_ID         => collection_id_tab(cntr),
1235                            X_CONCURRENT            => 1,
1236                            X_PO_TXN_PROCESSOR_MODE => NULL,
1237                            X_GROUP_ID              => NULL,
1238                            X_BACKGROUND            => FALSE ,
1239                            X_DEBUG                 => FALSE,
1240                            X_ACTION_TYPE           => 'DEFERRED' ,
1241                            X_PASSED_ID_NAME        => 'COLLECTION_ID',
1242                            P_OCCURRENCE            => occurrence_tab(cntr),
1243                            P_PLAN_ID               => plan_id_tab(cntr));
1244              END LOOP;
1245      END IF; --p_txn_header_id is not null
1246  END enable_fire_for_coll_id;
1247 
1248 
1249  -- Bug 4270911. CU2 SQL Literal fix. TD #18
1250  -- Uses FND_DSQL package for the case of unknown number of binds.
1251  -- srhariha. Fri Apr 15 06:40:15 PDT 2005.
1252 
1253 FUNCTION find_parent(p_child_plan_id IN NUMBER,
1254                      p_child_collection_id IN NUMBER,
1255                      p_child_occurrence IN NUMBER,
1256                      x_parent_plan_id OUT NOCOPY NUMBER,
1257                      x_parent_collection_id OUT NOCOPY NUMBER,
1258                      x_parent_occurrence OUT NOCOPY NUMBER)
1259                      RETURN VARCHAR2 IS
1260 
1261 --
1262 -- This function intelligently finding out parent plan record when child plan record information
1263 -- is passed. First find out parent_plan_id from qa_pc_plan_relationship. Then findout all
1264 -- element ids with which parent and child plans are related. Take only those elements which have
1265 -- link_flag = 1 in qa_pc_element_relationship table.
1266 
1267 -- Find the values of the elements from qa_results for the child plan.  Then find the first record
1268 -- for the parent plan which has all the elements (only those related in the qa_pc_element_relation)
1269 -- same value for those of child plan. Return the parent record information.
1270 
1271  l_plan_relationship_id NUMBER;
1272  l_parent_plan_id       NUMBER;
1273  l_temp_var             NUMBER;
1274  l_res_col              VARCHAR2(150);                 -- stores result column name in qa_results
1275  l_res_value            VARCHAR2(150);                 -- stores result column value in qa_results
1276 
1277  query_clause VARCHAR2(32000):= NULL;
1278  select_clause VARCHAR2(80)  := NULL;
1279  from_clause CONSTANT VARCHAR2(80)    := ' FROM QA_RESULTS ';
1280  where_clause VARCHAR2(5000) := NULL;
1281  parent_where_clause VARCHAR2(5000):= NULL;
1282 
1283 
1284  Type resCurTyp IS REF CURSOR; --define weak REF CURSOR type
1285  res_cur resCurTyp; --define cursor variable
1286 
1287  CURSOR plan_cursor(p_child_plan_id NUMBER) IS
1288    SELECT plan_relationship_id,parent_plan_id
1289    FROM   qa_pc_plan_relationship
1290    WHERE  child_plan_id = p_child_plan_id
1291    AND    rownum = 1;
1292 
1293 -- Bug 2357067. Modified the element_cursor so that all parent,child columns
1294 -- can be fetched once.
1295 
1296 CURSOR element_cursor(p_relationship_id NUMBER) IS
1297 select pe.parent_char_id,
1298        qpc1.result_column_name parent_database_column,
1299        pe.child_char_id,
1300        qpc2.result_column_name child_database_column
1301 from
1302        qa_pc_plan_relationship pr,
1303        qa_pc_element_relationship pe,
1304        qa_plan_chars qpc1,
1305        qa_plan_chars qpc2
1306 where
1307        pr.plan_relationship_id = pe.plan_relationship_id and
1308        pr.parent_plan_id = qpc1.plan_id and
1309        pe.parent_char_id = qpc1.char_id and
1310        pr.child_plan_id = qpc2.plan_id and
1311        pe.child_char_id = qpc2.char_id and
1312        pe.plan_relationship_id = p_relationship_id and
1313        pe.element_relationship_type = 1 and
1314        pe.link_flag = 1;
1315 
1316 -- Bug 4270911. CU2 SQL Literal fix.
1317 -- New cursor handler.
1318 cursor_handle NUMBER;
1319 no_of_rows NUMBER;
1320 BEGIN
1321    l_temp_var := -99;
1322    -- Bug 4270911. CU2 SQL Literal fix.
1323    -- Use bind variables.
1324    -- srhariha. Fri Apr 15 06:22:04 PDT 2005.
1325 
1326    where_clause := ' WHERE plan_id = :p_child_plan_id' ||
1327                    ' AND collection_id = :p_child_collection_id' ||
1328                    ' AND occurrence = :p_child_occurrence';
1329 
1330    -- get the parent_plan_id for the child plan
1331    OPEN plan_cursor(p_child_plan_id);
1332    FETCH plan_cursor INTO l_plan_relationship_id,l_parent_plan_id;
1333    IF (plan_cursor%NOTFOUND) THEN
1334       CLOSE plan_cursor;
1335       RETURN 'F';
1336    END IF;
1337 
1338    CLOSE plan_cursor;
1339 
1340   -- Bug 4270911. CU2 SQL Literal fix.
1341    -- Use fnd_dsql package.
1342    -- srhariha. Fri Apr 15 06:22:04 PDT 2005.
1343 
1344   select_clause := ' SELECT 1, plan_id, collection_id, occurrence ';
1345   fnd_dsql.init;
1346   fnd_dsql.add_text(select_clause || from_clause || ' ');
1347   fnd_dsql.add_text(' WHERE plan_id =');
1348   fnd_dsql.add_bind(l_parent_plan_id);
1349   fnd_dsql.add_text(' ');
1350 
1351    --  parent_where_clause := ' WHERE plan_id = ' || parent_plan_id ;
1352 
1353    -- get all the child plan elements which has relationship
1354    -- and link_flag = 1. This flag is specifically used for flow workstation integration.
1355 
1356    FOR ele_rec IN element_cursor(l_plan_relationship_id) LOOP
1357 
1358       select_clause := ' SELECT ' ||  ele_rec.child_database_column;
1359       query_clause := select_clause || from_clause || where_clause;
1360 
1361      -- Bug 4270911. CU2 SQL Literal fix.
1362      -- Use bind variables.
1363      -- srhariha. Fri Apr 15 06:22:04 PDT 2005.
1364 
1365 
1366       OPEN res_cur FOR query_clause USING p_child_plan_id, p_child_collection_id, p_child_occurrence;
1367       FETCH res_cur INTO l_res_value;
1368       CLOSE res_cur;
1369 
1370       -- If the copy element in child record is null, then build the query accordingly
1371 
1372       IF l_res_value IS NULL THEN
1373         --parent_where_clause := parent_where_clause || ' AND ' ||
1374         --                     ele_rec.parent_database_column || ' IS NULL';
1375         fnd_dsql.add_text(' AND ' || ele_rec.parent_database_column || ' IS NULL ');
1376       ELSE
1377 /* rkaza 06/04/2002. Bug 2302554. Enclosing l_res_value with single quotes. */
1378 --        parent_where_clause := parent_where_clause || ' AND ' ||
1379 --                               ele_rec.parent_database_column || ' = ' || '''' || qa_core_pkg.dequote(l_res_value) || '''';
1380 
1381         fnd_dsql.add_text(' AND ' || ele_rec.parent_database_column || ' = ');
1382         fnd_dsql.add_bind(l_res_value);
1383         fnd_dsql.add_text(' ');
1384       END IF;
1385 
1386    END LOOP;
1387 
1388    --Necessary to say rownum=1 to avoid multiple rows
1389 --   parent_where_clause := parent_where_clause || ' AND ROWNUM = 1 ';
1390    fnd_dsql.add_text(' AND ROWNUM = 1 ');
1391 
1392 --   query_clause := select_clause || from_clause || parent_where_clause;
1393 
1394 --   OPEN res_cur FOR query_clause USING l_parent_plan_id;
1395 --   FETCH res_cur INTO l_temp_var, x_parent_plan_id,
1396 --                      x_parent_collection_id, x_parent_occurrence;
1397 --   CLOSE res_cur;
1398 
1399 
1400     cursor_handle := dbms_sql.open_cursor;
1401     fnd_dsql.set_cursor(cursor_handle);
1402 
1403     query_clause := fnd_dsql.get_text;
1404     dbms_sql.parse(cursor_handle,query_clause,dbms_sql.NATIVE);
1405     fnd_dsql.do_binds;
1406 
1407     dbms_sql.define_column(cursor_handle,1,l_temp_var);
1408     dbms_sql.define_column(cursor_handle,2,x_parent_plan_id);
1409     dbms_sql.define_column(cursor_handle,3,x_parent_collection_id);
1410     dbms_sql.define_column(cursor_handle,4,x_parent_occurrence);
1411 
1412     no_of_rows := dbms_sql.execute(cursor_handle);
1413 
1414     no_of_rows := dbms_sql.fetch_rows(cursor_handle);
1415 
1416     l_temp_var := 0;
1417     IF (no_of_rows > 0) THEN
1418        dbms_sql.column_value(cursor_handle,1,l_temp_var);
1419        dbms_sql.column_value(cursor_handle,2,x_parent_plan_id);
1420        dbms_sql.column_value(cursor_handle,3,x_parent_collection_id);
1421        dbms_sql.column_value(cursor_handle,4,x_parent_occurrence);
1422 
1423 
1424     END IF;
1425 
1426    dbms_sql.close_cursor(cursor_handle);
1427 
1428    IF (l_temp_var = 1) THEN
1429         RETURN 'T';
1430    ELSE
1431         RETURN 'F';
1432    END IF;
1433 
1434 END find_parent;
1435 
1436  -- 12. QWB Usability Improvements
1437  -- added 2 new prameters to return a comma separated list
1438  -- of Parent plan elements for which the aggregation is done
1439  -- and the list of the aggregated values
1440  --
1441  --
1442  -- bug 7046071
1443  -- Added the parameter p_ssqr_operation parameter to check if the
1444  -- call is done from the OAF application or from Forms
1445  -- In case of the OAF application, the COMMIT that is
1446  -- executed in the aggregate_parent must not be called
1447  -- ntungare
1448  --
1449  PROCEDURE relate(p_parent_plan_id IN NUMBER,
1450                   p_parent_collection_id IN NUMBER,
1451                   p_parent_occurrence IN NUMBER,
1452                   p_child_plan_id IN NUMBER,
1453                   p_child_collection_id IN NUMBER,
1454                   p_child_occurrence IN NUMBER,
1455                   p_child_txn_header_id IN NUMBER,
1456                   x_agg_elements OUT NOCOPY VARCHAR2,
1457                   x_agg_val OUT NOCOPY VARCHAR2,
1458                   p_ssqr_operation IN NUMBER DEFAULT NULL) IS
1459 
1460  l_date     DATE;
1461  l_user_id  NUMBER;
1462  l_login_id NUMBER;
1463  l_rowid    VARCHAR2(18) := null;
1464 
1465  l_ret_value VARCHAR2(1);
1466  -- Gapless Sequence Proj. rponnusa Wed Jul 30 04:52:45 PDT 2003
1467  -- Added following cursor.
1468 
1469  l_child_txn_header_id NUMBER;
1470 
1471  CURSOR c IS
1472    SELECT txn_header_id FROM qa_results
1473    WHERE  plan_id       = p_child_plan_id AND
1474           collection_id = p_child_collection_id AND
1475           occurrence    = p_child_occurrence;
1476 
1477    -- 12.1 QWB Usability Improvements
1478    --
1479    agg_elements VARCHAR2(4000);
1480    agg_val      VARCHAR2(4000);
1481  BEGIN
1482 
1483    --anagarwa Fri Jun 11 15:08:03 PDT 2004
1484    -- bug 3678910
1485    -- If parent or child key is invalid then no need to create a relationship
1486    IF  p_parent_occurrence < 0 OR  p_parent_collection_id < 0 OR
1487        p_parent_plan_id < 0 OR  p_child_plan_id < 0 OR
1488        p_child_collection_id < 0 OR  p_child_occurrence < 0  THEN
1489 
1490       RETURN;
1491    END IF;
1492 
1493    l_user_id  := fnd_global.user_id;
1494    l_login_id := fnd_global.login_id;
1495    l_date := sysdate;
1496 
1497    -- Gapless Sequence Proj. rponnusa Wed Jul 30 04:52:45 PDT 2003
1498    -- Findout txn header ID for the child record
1499 
1500    IF p_child_txn_header_id IS NULL THEN
1501       OPEN c;
1502       FETCH c INTO l_child_txn_header_id;
1503       CLOSE c;
1504    ELSE
1505       l_child_txn_header_id := p_child_txn_header_id;
1506    END IF;
1507 
1508  -- Gapless Sequence Proj passing child_txn_header_id
1509  QA_PC_RESULTS_REL_PKG.Insert_Row(
1510       X_Rowid                   => l_rowid,
1511       X_Parent_Plan_Id          => p_parent_plan_id,
1512       X_Parent_Collection_Id    => p_parent_collection_id,
1513       X_Parent_Occurrence       => p_parent_occurrence,
1514       X_Child_Plan_Id           => p_child_plan_id,
1515       X_Child_Collection_Id     => p_child_collection_id,
1516       X_Child_Occurrence        => p_child_occurrence,
1517       X_Enabled_Flag            => 1,
1518       X_Last_Update_Date        => l_date,
1519       X_Last_Updated_By         => l_user_id,
1520       X_Creation_Date           => l_date,
1521       X_Created_By              => l_user_id,
1522       X_Last_Update_Login       => l_login_id,
1523       X_Child_Txn_Header_Id     => l_child_txn_header_id);
1524 
1525  -- Bug 2302554
1526  -- once the parent and child are related, parent record
1527  -- should be updated with child element values(if any aggregate
1528  -- relationship defined) and child record should be updated
1529  -- with parent plan values (if copy relation defined with
1530  -- link_flag = 2)
1531  -- 12.1 QWB Usabiltity improvements
1532  -- added 2 new parameters to get the parent element which
1533  -- is to have the aggregated value and to get the aggregated
1534  -- value
1535  --
1536  --
1537  -- bug 7046071
1538  -- Passing the parameter p_ssqr_operation parameter to check if the
1539  -- call is done from the OAF application or from Forms
1540  -- In case of the OAF application, the COMMIT that is
1541  -- executed in the aggregate_parent must not be called
1542  -- ntungare
1543  --
1544  l_ret_value := QA_PARENT_CHILD_PKG.update_parent(p_parent_plan_id ,
1545                   p_parent_collection_id ,
1546                   p_parent_occurrence,
1547                   p_child_plan_id,
1548                   p_child_collection_id ,
1549                   p_child_occurrence,
1550                   agg_elements,
1551                   agg_val,
1552                   p_ssqr_operation);
1553 
1554  -- 12.1 QWB Usability Improvements
1555  --
1556  x_agg_elements := agg_elements;
1557  x_agg_val      := agg_val;
1558 
1559  --
1560  -- bug 7588376
1561  -- Starting with a fresh copy of the collection
1562  -- that stores the values of the relactionship elements
1563  -- in the parent plan
1564  --
1565  parent_plan_vales_tab.delete;
1566  l_ret_value:= QA_PARENT_CHILD_PKG.update_child(p_parent_plan_id ,
1567                   p_parent_collection_id ,
1568                   p_parent_occurrence,
1569                   p_child_plan_id,
1570                   p_child_collection_id ,
1571                   p_child_occurrence );
1572  --
1573  -- bug 7588376
1574  -- resetting the collection
1575  --
1576  parent_plan_vales_tab.delete;
1577 
1578 END relate;
1579 
1580 FUNCTION get_plan_name(p_plan_ids IN VARCHAR2 , x_plan_name OUT NOCOPY VARCHAR2) return VARCHAR2 IS
1581 
1582 -- This functions returns the name of the plan when plan_id is passed.
1583 -- This can take the plan_id in the comma separated string like '501,502,503'
1584 -- and returns all the plan_name in the comma separated string.
1585 
1586 -- This function is useful when we need to display the message to user about the
1587 -- childplan name or parent plan name.
1588 
1589   l_child_id_array       ChildPlanArray;
1590   l_total_length NUMBER;
1591   l_plan_name VARCHAR2(10000) := NULL;
1592   l_name      VARCHAR2(30);
1593   l_plan_id   NUMBER;
1594   l_str_from  NUMBER := 1;
1595   l_str_to    NUMBER;
1596   l_separator CONSTANT VARCHAR2(1) := ',';
1597 
1598   CURSOR plan_cursor(c_plan_id NUMBER) IS
1599     SELECT name
1600     FROM qa_plans
1601     WHERE plan_id = c_plan_id;
1602 
1603  BEGIN
1604   l_total_length := LENGTH(p_plan_ids);
1605 
1606    -- We need check for all the child_plan_ids one by one or parent_plan_id to
1607    -- to get plan name
1608 
1609   -- anagarwa Mon Apr 15 15:51:58 PDT 2002
1610   -- Bug 2320896 was being caused due to error in logic.
1611   -- This code is being replaced to avoid character to number conversion
1612 
1613 /*
1614 
1615    LOOP
1616         l_str_to := instr(p_plan_ids,l_separator,l_str_from);
1617         IF (l_str_to = 0) THEN
1618             -- we are here if only one plan id is passed or we are in the
1619             -- last child plan id
1620 
1621             l_plan_id := to_number(substr(p_plan_ids,  l_str_from, l_total_length));
1622         ELSE
1623             l_plan_id := to_number(substr(p_plan_ids, l_str_from, l_str_to -1 ));
1624 
1625             -- Adding +1 with the l_str_to to make l_str_from variable pointing to first
1626             -- character after the comma separator
1627 
1628             l_str_from := l_str_to +1;
1629         END IF;
1630 
1631        OPEN plan_cursor;
1632        FETCH plan_cursor INTO l_name;
1633        IF (plan_cursor%NOTFOUND) THEN
1634           CLOSE plan_cursor;
1635           RETURN 'F';
1636        END IF;
1637 
1638        IF l_plan_name IS NULL THEN
1639            l_plan_name := l_name;
1640        ELSE
1641            l_plan_name := l_plan_name || l_separator || l_name;
1642        END IF;
1643        CLOSE plan_cursor;
1644 
1645        IF (l_str_to = 0 ) THEN
1646            -- We parsed all the child plan ids.
1647            EXIT;
1648        END IF;
1649    END LOOP;
1650 */
1651 
1652    parse_list(p_plan_ids, l_child_id_array);
1653 
1654    FOR i IN 1..l_child_id_array.COUNT LOOP
1655       l_plan_id := l_child_id_array(i);
1656       OPEN plan_cursor(l_plan_id);
1657       FETCH plan_cursor INTO l_name;
1658       IF (plan_cursor%NOTFOUND) THEN
1659          CLOSE plan_cursor;
1660          RETURN 'F';
1661       END IF;
1662 
1663       IF l_plan_name IS NULL THEN
1664           l_plan_name := l_name;
1665       ELSE
1666           l_plan_name := l_plan_name || l_separator || l_name;
1667       END IF;
1668       CLOSE plan_cursor;
1669 
1670    END LOOP;
1671    x_plan_name := l_plan_name;
1672 
1673    RETURN 'T';
1674  END get_plan_name;
1675 
1676  FUNCTION should_parent_spec_be_copied(p_parent_plan_id NUMBER, p_child_plan_id NUMBER)
1677         RETURN VARCHAR2 IS
1678 
1679   -- This function returns true if parent plan specification_id can be copied to child
1680   -- else return false.
1681 
1682   l_default_parent NUMBER := -99;
1683 
1684   CURSOR default_cursor IS
1685         SELECT default_parent_spec
1686         FROM   qa_pc_plan_relationship
1687         WHERE  parent_plan_id = p_parent_plan_id
1688         AND    child_plan_id = p_child_plan_id;
1689 
1690 
1691  BEGIN
1692 
1693     -- As of now just return true. To implement this function we should have a new field
1694     -- default_parent_spec column in table qa_pc_plan_relationship.
1695     -- Hence i am commenting out the actual implementation of this function.
1696 
1697  --   RETURN 'T';
1698 
1699     OPEN default_cursor;
1700     FETCH default_cursor INTO l_default_parent;
1701     IF (default_cursor%NOTFOUND) THEN
1702       l_default_parent := -99;
1703     END IF;
1704     CLOSE default_cursor;
1705     IF l_default_parent = 1 THEN
1706         RETURN 'T';
1707     ELSE
1708         RETURN 'F';
1709     END IF;
1710 
1711  END should_parent_spec_be_copied;
1712 
1713  FUNCTION is_parent_child_plan(p_plan_id NUMBER) RETURN VARCHAR2 IS
1714  -- this functions return 'T' if the plan is parent-child relationship
1715  -- plan. ie pc relationship is defined for this plan.
1716 
1717  l_is_parent_plan VARCHAR2(1);
1718 
1719  CURSOR plan_cursor(p_plan_id NUMBER) IS
1720    SELECT 'T'
1721    FROM   qa_pc_plan_relationship
1722    WHERE  parent_plan_id = p_plan_id
1723    OR     child_plan_id = p_plan_id
1724    AND    rownum = 1;
1725  BEGIN
1726     l_is_parent_plan := 'F';
1727     OPEN plan_cursor(p_plan_id);
1728     FETCH plan_cursor INTO l_is_parent_plan;
1729     IF( plan_cursor%NOTFOUND) THEN
1730         l_is_parent_plan := 'F';
1731     END IF;
1732     CLOSE plan_cursor;
1733     RETURN l_is_parent_plan;
1734  END is_parent_child_plan;
1735 
1736   -- Bug 4343758
1737   -- R12 OAF Txn Integration Project
1738   -- Added p_commit parameter to the existing update_parent function
1739   -- and renamed it as aggregate_parent since we do not want
1740   -- the explicit commit for OAF Txn Delete Flows
1741   -- shkalyan 05/13/2005.
1742  --
1743  -- 12.1 QWB Usability Improvements
1744  -- added 2 new parameters to get the list of the
1745  -- aggregated elements and the aggregated values.
1746  --
1747  FUNCTION aggregate_parent(p_parent_plan_id IN NUMBER,
1748                            p_parent_collection_id IN NUMBER,
1749                            p_parent_occurrence IN NUMBER,
1750                            p_child_plan_id IN NUMBER,
1751                            p_child_collection_id IN NUMBER,
1752                            p_child_occurrence IN NUMBER,
1753                            p_commit IN VARCHAR2,
1754                            x_agg_elements OUT NOCOPY VARCHAR2,
1755                            x_agg_val OUT NOCOPY VARCHAR2)
1756         RETURN VARCHAR2 IS
1757 
1758  l_sql_string VARCHAR2(32000);
1759  l_update_parent_sql VARCHAR2(32000);
1760  l_value NUMBER;
1761 
1762  --
1763  -- Bug 6450756
1764  -- Declaration of variables needed for
1765  -- locking the row that needs to be
1766  -- updated with the aggregating values.
1767  -- bhsankar  Sun Sep 30 23:38:58 PDT 2007
1768  --
1769  l_parent_db_col  VARCHAR2(30);
1770  l_select_sql     VARCHAR2(32000);
1771 
1772  -- anagarwa Mon Dec 16 16:55:09 PST 2002
1773  -- Bug 2701777
1774  -- added parent_enabled_flag and child_enabled_flag to where clause
1775  -- to limit working on onlly those elements that are enabled.
1776  CURSOR element_cursor IS
1777     SELECT parent_database_column,
1778            child_database_column,
1779            element_relationship_type,
1780            parent_char_id
1781     FROM   qa_pc_result_columns_v
1782     WHERE  parent_plan_id = p_parent_plan_id
1783     AND    child_plan_id = p_child_plan_id
1784     AND    element_relationship_type in (2,3,4,5,6,7,8)
1785     AND    parent_enabled_flag = 1
1786     AND    child_enabled_flag = 1;
1787 
1788  --
1789  -- Bug 6450756
1790  -- User Defined exception for handling row locks
1791  -- in scenarios U->V->U or U->V->E
1792  -- where aggegating into top most parent will
1793  -- result in a lock.
1794  -- bhsankar  Sun Sep 30 23:38:58 PDT 2007
1795  --
1796  ROW_LOCK_FAILED EXCEPTION;
1797  PRAGMA EXCEPTION_INIT(ROW_LOCK_FAILED, -54);
1798 
1799 
1800  BEGIN
1801 
1802   FOR cur_rec IN element_cursor LOOP
1803 
1804       -- build the required sql string
1805 
1806       l_sql_string := 'FROM qa_results qr, qa_pc_results_relationship pc'
1807                     || ' WHERE qr.plan_id=pc.child_plan_id'
1808                     || ' AND qr.collection_id=pc.child_collection_id'
1809                     || ' AND qr.occurrence=pc.child_occurrence'
1810                     || ' AND pc.parent_occurrence= :p_parent_occurrence'
1811                     || ' AND pc.child_plan_id= :p_child_plan_id'
1812                     --
1813                     -- bug 5682448
1814                     -- Added the extra condititon to aggregate only the
1815                     -- enabled records in stauts 2 or NULL
1816                     -- ntungare Wed Feb 21 07:38:04 PST 2007
1817                     --
1818                     || ' AND (qr.status = 2 OR qr.status IS NULL)';
1819 
1820       -- Bug 2427337. Fix here is not related this bug. To use aggregate functions
1821       -- on a element which is stored in character col in qa_results table, we need
1822       -- to use to_number function, or else, unwanted value will be returned.
1823       -- rponnusa Tue Jun 25 06:15:48 PDT 2002
1824 
1825       IF (cur_rec.element_relationship_type = 2  ) THEN  -- sum
1826          l_sql_string := 'SELECT SUM(to_number(qr.'||cur_rec.child_database_column||')) ' || l_sql_string;
1827       ELSIF (cur_rec.element_relationship_type = 3 ) THEN  -- average or Mean
1828          l_sql_string := 'SELECT AVG(to_number(qr.'||cur_rec.child_database_column||')) ' || l_sql_string;
1829       ELSIF (cur_rec.element_relationship_type = 4 ) THEN -- std. deviation
1830          l_sql_string := 'SELECT STDDEV(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
1831 
1832       ELSIF (cur_rec.element_relationship_type = 5 ) THEN -- min
1833          l_sql_string := 'SELECT MIN(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
1834       ELSIF (cur_rec.element_relationship_type = 6 ) THEN -- max
1835          l_sql_string := 'SELECT MAX(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
1836       ELSIF (cur_rec.element_relationship_type = 7 ) THEN -- variance
1837          l_sql_string := 'SELECT VARIANCE(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
1838       ELSIF (cur_rec.element_relationship_type = 8 ) THEN -- count
1839          -- anagarwa  Tue Feb 18 11:13:20 PST 2003
1840          -- Bug 2789847
1841          -- Count may be done on non numeric elements like Sequence Numbers and
1842          -- even Nonconformance Status, Source etc.
1843          -- A to_number will cause an exception in such a case and is hence
1844          -- removed from sql statement.
1845          l_sql_string := 'SELECT COUNT(qr.'|| cur_rec.child_database_column||') ' || l_sql_string;
1846       END IF;
1847       -- find out the aggregate value for the element in child plan.
1848       BEGIN
1849          EXECUTE IMMEDIATE l_sql_string INTO l_value
1850                  USING p_parent_occurrence,p_child_plan_id;
1851       EXCEPTION
1852         WHEN OTHERS THEN raise;
1853 
1854       END;
1855 
1856       -- Bug 2716973
1857       -- When the child aggregate relationship element value is updated to parent record,
1858       -- Post-Forms-Commit Trigger error raised if child element contain null value.
1859       -- rponnusa Sun Jan 12 23:59:07 PST 2003
1860 
1861       l_value := NVL(l_value,0);
1862 
1863       -- See 2624112
1864       -- The maximum allowed precision is now expanded to 12.
1865       -- Rounding to 12...
1866       -- rkunchal Thu Oct 17 22:51:45 PDT 2002
1867 
1868       -- rounding off to 6 digits is required since, for a number field, the maximum allowd
1869       -- decimal places is 6.
1870 
1871       -- l_value := round(l_value,6);
1872       l_value := round(l_value,12);
1873       --
1874       -- Bug 6450756
1875       -- Lock the row in the parent so that the
1876       -- values can be aggregated from the child
1877       -- If the row is not getting locked, then
1878       -- it might be because of the following flow
1879       -- U->V->U or U->V->E. Catch the exception and
1880       -- dont take any action since the aggregations
1881       -- would anyway fire at the parent level.
1882       -- bhsankar  Sun Sep 30 23:38:58 PDT 2007
1883       --
1884       l_select_sql := 'SELECT '
1885                       || cur_rec.parent_database_column
1886                       || ' FROM qa_results WHERE  plan_id = :p_parent_plan_id'
1887                       || ' AND collection_id= :p_parent_collection_id'
1888                       || ' AND occurrence= :p_parent_occurrence FOR UPDATE NOWAIT';
1889 
1890       BEGIN
1891          EXECUTE IMMEDIATE l_select_sql INTO l_parent_db_col
1892                  USING p_parent_plan_id,p_parent_collection_id,p_parent_occurrence;
1893 
1894          -- now we need to update the parent record. Build the sql here.
1895 
1896          l_update_parent_sql := 'UPDATE qa_results  SET '
1897                             || cur_rec.parent_database_column || ' = :l_value'
1898                             || ' WHERE plan_id= :p_parent_plan_id'
1899                             || ' AND collection_id= :p_parent_collection_id'
1900                             || ' AND occurrence= :p_parent_occurrence';
1901               BEGIN
1902                  EXECUTE IMMEDIATE l_update_parent_sql
1903                          USING l_value,p_parent_plan_id,p_parent_collection_id,p_parent_occurrence;
1904 
1905                 -- 12.1 QWB Usability improvements
1906                 -- Building a list of the Aggregated parent plan elements
1907                 --
1908                 x_agg_elements := x_agg_elements ||','||
1909                                   qa_ak_mapping_api.get_vo_attribute_name(cur_rec.parent_char_id, p_parent_plan_id);
1910                 -- 12.1 QWB Usability improvements
1911                 -- Building a list of the Aggregated values
1912                 --
1913                 x_agg_val := x_agg_val ||','|| l_value;
1914 
1915               EXCEPTION
1916                 WHEN OTHERS THEN raise;
1917               END;
1918 
1919       EXCEPTION
1920          WHEN ROW_LOCK_FAILED THEN NULL;
1921          WHEN OTHERS THEN RAISE;
1922       END;
1923 
1924   END LOOP;
1925   -- we are returning true when the parent record is updated or
1926   -- there is no aggregate relationship defined for the parent,child plans.
1927 
1928   -- Bug 4343758
1929   -- R12 OAF Txn Integration Project
1930   -- Added check based on p_commit parameter since we do not want to commit
1931   -- by default if invoked from OAF Pages.
1932   -- shkalyan 05/13/2005.
1933 
1934   -- bug 15858247
1935   -- If ERES is enabled, then the commit should not be issued since this would
1936   -- be done by the EDR library.
1937   -- In all other cases, it is OK to issue the commit since the data would be
1938   -- committed on the child plan form before navigating back to the parent.
1939   --
1940   IF (( p_commit = 'T' ) AND (NVL(FND_PROFILE.VALUE('EDR_ERES_ENABLED'),'N')='N')) THEN
1941     -- Bug 2300962. Needs explicit commit, if called from post-database-commit trigger
1942     COMMIT;
1943   END IF;
1944 
1945   RETURN 'T';
1946 
1947  END aggregate_parent;
1948 
1949  FUNCTION update_parent(p_parent_plan_id IN NUMBER,
1950                        p_parent_collection_id IN NUMBER,
1951                        p_parent_occurrence IN NUMBER,
1952                        p_child_plan_id IN NUMBER,
1953                        p_child_collection_id IN NUMBER,
1954                        p_child_occurrence IN NUMBER)
1955         RETURN VARCHAR2 IS
1956 
1957    -- 12.1 QWB Usability Improvements
1958    agg_elements VARCHAR2(4000);
1959    agg_val      VARCHAR2(4000);
1960 BEGIN
1961    -- 12.1 QWB Usability Improvements
1962    return update_parent(p_parent_plan_id,
1963                        p_parent_collection_id,
1964                        p_parent_occurrence,
1965                        p_child_plan_id,
1966                        p_child_collection_id,
1967                        p_child_occurrence,
1968                        agg_elements,
1969                        agg_val);
1970 END;
1971 
1972  -- 12.1 QWB Usability Improvements
1973  -- Overloaded method that has 2 additional parameters
1974  -- that return a list of Aggregated elements and
1975  -- their values
1976  --
1977  -- bug 7046071
1978  -- Passing the parameter p_ssqr_operation parameter to check if the
1979  -- call is done from the OAF application or from Forms
1980  -- In case of the OAF application, the COMMIT that is
1981  -- executed in the aggregate_parent must not be called
1982  -- ntungare
1983  --
1984  FUNCTION update_parent(p_parent_plan_id IN NUMBER,
1985                        p_parent_collection_id IN NUMBER,
1986                        p_parent_occurrence IN NUMBER,
1987                        p_child_plan_id IN NUMBER,
1988                        p_child_collection_id IN NUMBER,
1989                        p_child_occurrence IN NUMBER,
1990                        x_agg_elements OUT NOCOPY VARCHAR2,
1991                        x_agg_val OUT NOCOPY VARCHAR2,
1992 		       p_ssqr_operation IN NUMBER DEFAULT NULL)
1993         RETURN VARCHAR2 IS
1994    l_return_status VARCHAR2(1);
1995 
1996    agg_elements VARCHAR2(4000);
1997    agg_val      VARCHAR2(4000);
1998 
1999    -- bug 7046071
2000    l_commit     VARCHAR2(1) := 'T';
2001  BEGIN
2002   -- Bug 4343758
2003   -- R12 OAF Txn Integration Project
2004   -- Moved the entire code to aggregate_parent function because
2005   -- this function was committing by default. Since we do not want
2006   -- the explicit commit for OAF Txn Delete Flows we have introduced this
2007   -- new procedure which accepts the commit flag as input.
2008 
2009    --
2010    -- bug 7046071
2011    -- If this processing is initiated from the OAF application
2012    -- either standalone or through OAF txn then the commit must
2013    -- not be done since this would taken care by the framework
2014    -- so setting the commit flag as 'F'
2015    -- ntungare
2016    --
2017    IF (p_ssqr_operation IN (1,2)) THEN
2018         l_commit := 'F';
2019    END IF;
2020 
2021    -- 12.1 QWB Usabitlity Improvements.
2022    -- Passing parameters for the aggregated elements
2023    --
2024    -- bug 7046071
2025    -- Passing the derived value for the commit flag
2026    -- ntungare
2027    --
2028    l_return_status :=
2029    aggregate_parent
2030    (
2031         p_parent_plan_id       => p_parent_plan_id,
2032         p_parent_collection_id => p_parent_collection_id,
2033         p_parent_occurrence    => p_parent_occurrence,
2034         p_child_plan_id        => p_child_plan_id,
2035         p_child_collection_id  => p_child_collection_id,
2036         p_child_occurrence     => p_child_occurrence,
2037         p_commit               => l_commit,
2038         x_agg_elements         => agg_elements,
2039         x_agg_val              => agg_val
2040    );
2041 
2042    x_agg_elements := agg_elements;
2043    x_agg_val      := agg_val;
2044 
2045    -- Bug 4343758. OA Framework Integration project.
2046    -- Function should return the status back to caller.
2047    -- srhariha. Tue May 24 22:56:13 PDT 2005.
2048    RETURN l_return_status;
2049  END update_parent;
2050 
2051  --
2052  -- bug 6266439
2053  -- New procedure to peform the date conversions while
2054  -- selecting and updating the data in the QA_RESULTS
2055  -- table, while peforming a Child record update.
2056  -- ntungare Thu Aug  2 03:32:32 PDT 2007
2057  --
2058  PROCEDURE DATE_SELECT_UPDATE(p_parent_result_column  IN     VARCHAR2,
2059                               p_child_result_column   IN     VARCHAR2,
2060                               p_parent_plan_id        IN     NUMBER,
2061                               p_child_plan_id         IN     NUMBER,
2062                               p_var                   IN     NUMBER,
2063                               p_select_column     OUT NOCOPY VARCHAR2,
2064                               p_update_column     OUT NOCOPY VARCHAR2)
2065       IS
2066 
2067    -- Cursor to check if the resultcolumn is
2068    -- of the DateTime/Date type and whether its a Hardcoded
2069    -- element
2070    -- Bug 8546279.Changed cursor query to inclide date type elements too
2071    -- collecting datatype too for datatype 3,date and 6,datetime.pdube
2072    Cursor cur (p_plan_id in NUMBER, p_res_col in VARCHAR2) is
2073      Select 1, qc.hardcoded_column, qc.datatype
2074        from qa_plan_chars qpc, qa_chars qc
2075      where qpc.plan_id = p_plan_id
2076        and qpc.char_id = qc.char_id
2077        and qpc.result_column_name = p_res_col
2078        and qc.datatype in (3,6);
2079 
2080    data_found       PLS_INTEGER := 0;
2081    hardcoded_column QA_CHARS.HARDCODED_COLUMN%TYPE := NULL;
2082    -- Bug 8546279 FP of 8446050.Added variables.pdube
2083    datatype         NUMBER;
2084    child_is_datetime       BOOLEAN := FALSE;
2085    datetimetype            CONSTANT NUMBER := 6;
2086    datetype                CONSTANT NUMBER := 3;
2087 
2088    parent_is_date          BOOLEAN := FALSE;
2089    child_is_date           BOOLEAN := FALSE;
2090    parent_hardcoded_column BOOLEAN := FALSE;
2091    child_hardcoded_column  BOOLEAN := FALSE;
2092  BEGIN
2093    -- Checking if the Parent element is a date element
2094    Open cur (p_parent_plan_id, p_parent_result_column);
2095    -- Bug 8546279.FP 8446050.fetching the datatype too.pdube
2096    -- Fetch cur into data_found, hardcoded_column;
2097    fetch cur into data_found, hardcoded_column, datatype;
2098    Close cur;
2099 
2100    If data_found =1 Then
2101      parent_is_date := TRUE;
2102      data_found :=0;
2103      -- Bug 8546279.FP for pdube
2104      datatype   := NULL;
2105 
2106      -- Checking if the Parent element is a HC date
2107      If hardcoded_column IS NOT NULL THEN
2108        parent_hardcoded_column := TRUE;
2109        hardcoded_column := NULL;
2110      END If;
2111    End If;
2112 
2113    -- This processing is to be performed only if the
2114    -- elements are dates. If the parent element is not a date
2115    -- then the child element too won't be of the date type since
2116    -- relationship with any other datatype cannot be established
2117    -- in which case, the processing can be terminated.
2118    --
2119    If parent_is_date <> TRUE THEN
2120      RETURN;
2121    ELSE
2122      -- Checking if the Child element is a date element
2123      Open cur (p_child_plan_id, p_child_result_column);
2124      -- Bug 8546279.FP 8446050.fetching the datatype too.pdube
2125      -- fetch cur into data_found, hardcoded_column;
2126      fetch cur into data_found, hardcoded_column, datatype;
2127      Close cur;
2128 
2129      If data_found =1 Then
2130        -- Bug 8546279.FP for 8446050.Added this if else ladder to set
2131        -- the boolean variables for checking date/datetime elements.pdube
2132        -- child_is_date := TRUE;
2133        IF (datatype = datetimetype) THEN
2134            child_is_datetime := TRUE;
2135 	   datatype          := NULL;
2136        ELSE
2137            child_is_date := TRUE;
2138 	   datatype          := NULL;
2139        END IF;
2140        data_found :=0;
2141        -- Checking if the Child element is a HC date
2142        If hardcoded_column IS NOT NULL THEN
2143          child_hardcoded_column := TRUE;
2144          hardcoded_column := NULL;
2145        END If;
2146      End If;
2147 
2148 
2149      -- Bug 8546279.FP for 8446050.
2150      -- If the parent element is a HC date then we have to convert it to the
2151      -- Canonical format while selecting. If the Parent element is a SC date
2152      -- then since the data is fetched from the Deref view which anyways converts
2153      -- the character string to the date format, we have to get the dereferenced
2154      -- name of the element and then convert it to the canonical character format.
2155      -- For the target elements in the update clause, if the target element is HC
2156      -- date then we have to convert the data which is selected as string in the
2157      -- canonical format into a date. For SC target elements, since the data is
2158      -- already in the canonical format, we can update it directly.Made changes to
2159      -- handle the date and datetime elements.pdube
2160      If (parent_is_date) AND (parent_hardcoded_column) THEN
2161          --HC-> HC
2162          --  If (child_is_date) AND (child_hardcoded_column) THEN
2163          --    p_select_column := 'to_char('||p_parent_result_column||',''DD-MON-YYYY HH24:MI:SS'') ';
2164          --    p_update_column := 'to_date(:'||to_char(p_var)||',''DD-MON-YYYY HH24:MI:SS'') ';
2165          IF (child_is_datetime OR child_is_date) AND (child_hardcoded_column) THEN
2166              p_select_column := 'to_char('||p_parent_result_column||',''YYYY/MM/DD HH24:MI:SS'') ';
2167              p_update_column := 'to_date(:'||to_char(p_var)||',''YYYY/MM/DD HH24:MI:SS'') ';
2168 
2169          --HC-> SC datetime
2170          ELSIF (child_is_datetime) AND (child_hardcoded_column = FALSE) THEN
2171              p_select_column := 'to_char('||p_parent_result_column||',''YYYY/MM/DD HH24:MI:SS'') ';
2172              p_update_column := ':'||to_char(p_var);
2173 
2174          --HC-> SC date
2175          ELSIF (child_is_date) AND (child_hardcoded_column = FALSE) THEN
2176              -- p_select_column := 'QLTDATE.date_to_canon_dt('||p_parent_result_column||') ';
2177              p_select_column := 'to_char('||p_parent_result_column||',''YYYY/MM/DD'') ';
2178              p_update_column := ':'||to_char(p_var);
2179          END IF;
2180      ELSIF (parent_is_date) AND (parent_hardcoded_column = FALSE) THEN
2181          --SC-> HC
2182          -- If (child_is_date) AND (child_hardcoded_column) THEN
2183          --    p_select_column := p_parent_result_column;
2184          --    p_update_column := 'qltdate.canon_to_date(:'||to_char(p_var)||') ';
2185          If (child_is_datetime) AND (child_hardcoded_column) THEN
2186              get_deref_column(p_parent_result_column => p_parent_result_column,
2187                                     p_parent_plan_id       => p_parent_plan_id,
2188                                     x_select_column        => p_select_column);
2189              p_select_column := 'to_char('||p_select_column||',''YYYY/MM/DD HH24:MI:SS'') ';
2190              p_update_column := 'to_date(:'||to_char(p_var)||',''YYYY/MM/DD HH24:MI:SS'') ';
2191 
2192          --SC-> SC Date
2193          ELSIF (child_is_date) AND (child_hardcoded_column = FALSE) THEN
2194              -- p_select_column := p_parent_result_column;
2195              -- p_update_column := ':'||to_char(p_var);
2196              get_deref_column(p_parent_result_column => p_parent_result_column,
2197                                     p_parent_plan_id       => p_parent_plan_id,
2198                                     x_select_column        => p_select_column);
2199              p_select_column := 'to_char('||p_select_column||',''YYYY/MM/DD'') ';
2200              p_update_column := ':'||to_char(p_var);
2201 
2202 	 --SC-> SC Date time
2203          ELSIF (child_is_datetime) AND (child_hardcoded_column = FALSE) THEN
2204              get_deref_column(p_parent_result_column => p_parent_result_column,
2205                                     p_parent_plan_id       => p_parent_plan_id,
2206                                     x_select_column        => p_select_column);
2207              p_select_column := 'to_char('||p_select_column||',''YYYY/MM/DD HH24:MI:SS'') ';
2208              p_update_column := ':'||to_char(p_var);
2209 	 END If;
2210      END If;
2211      -- End of bug 8546279.FP for 8446050.pdube
2212    END If;
2213  END DATE_SELECT_UPDATE;
2214 
2215  --
2216  -- bug 9831189
2217  -- New function to check if the child element
2218  -- is a HC element that doesnt have a foreign
2219  -- key reference in which case the char name of the
2220  -- corresponding parent element is to be chosen
2221  -- instead of the standard HC result column name
2222  --
2223  FUNCTION IS_SPECIAL_HC_ELEM ( p_child_result_column VARCHAR2,
2224                                p_child_plan_id       NUMBER) return BOOLEAN AS
2225      CURSOR p_cur IS
2226          SELECT   1
2227          FROM     qa_chars qc,
2228                   qa_plan_chars qpc
2229          WHERE    qc.char_id = qpc.char_id
2230          AND      qpc.plan_id = p_child_plan_id
2231          AND      qpc.result_column_name = p_child_result_column
2232          AND      qc.hardcoded_column IS NOT NULL -- HC element
2233          AND      (qc.FK_TABLE_NAME IS NULL -- HC element without Foreign Key
2234                     OR
2235                    qc.FK_TABLE_NAME IS NOT NULL AND qc.fk_lookup_type not in (0,1));
2236      ret_val NUMBER := NULL;
2237 
2238  BEGIN
2239      OPEN p_cur;
2240      FETCH p_cur into ret_val;
2241      CLOSE p_cur;
2242 
2243      IF ret_val IS NOT NULL THEN
2244        RETURN TRUE;
2245      ELSE
2246        RETURN FALSE;
2247      END IF;
2248  END IS_SPECIAL_HC_ELEM;
2249 
2250  --
2251  -- bug 7588376
2252  -- New procedure to select the dereferenced column for
2253  -- a hardcoded column, if its value is being copied to
2254  -- a softcoded element in the child plan.
2255  -- skolluku
2256  --
2257  PROCEDURE get_deref_column(p_parent_result_column IN     VARCHAR2,
2258                             p_parent_plan_id       IN     NUMBER,
2259                             x_select_column        OUT NOCOPY VARCHAR2)
2260       IS
2261 
2262    -- of a Hardcoded element and also to fetch its
2263    -- dereferenced column.
2264    Cursor cur (p_plan_id in NUMBER, p_res_col in VARCHAR2) is
2265      Select UPPER(TRANSLATE(qc.name,   ' ''*{}',   '_____')) name, qc.hardcoded_column
2266        from qa_plan_chars qpc, qa_chars qc
2267      where qpc.plan_id = p_plan_id
2268        and qpc.char_id = qc.char_id
2269        and qpc.result_column_name = p_res_col;
2270 
2271    parent_element_name       varchar2(2000):= NULL;
2272    hardcoded_column QA_CHARS.HARDCODED_COLUMN%TYPE := NULL;
2273 
2274  BEGIN
2275    -- init the select column to null.
2276    x_select_column := NULL;
2277 
2278    -- Checking if the Parent element is a hardcoded element
2279    Open cur (p_parent_plan_id, p_parent_result_column);
2280    fetch cur into parent_element_name, hardcoded_column;
2281    Close cur;
2282 
2283    -- Assign the dereferenced column to copy to SC child element.
2284    x_select_column := parent_element_name;
2285  END get_deref_column;
2286 
2287 -- 5114865
2288 -- Function to perform the Updation of the Child
2289 -- Plan Columns those which have been identified
2290 -- as having a Copy Relationship with the corresponding
2291 -- Parent Plans
2292 -- This section of code was earlier a part of
2293 -- update_child Function and was extraced so that
2294 -- it can be used in common by function
2295 -- update_sequence_Child
2296 -- nutngare Wed Mar  8 09:00:46 PST 2006
2297 --
2298 FUNCTION perform_child_update(p_parentchild_element_tab IN QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type,
2299                               p_parent_plan_id IN NUMBER,
2300                               p_parent_collection_id IN NUMBER,
2301                               p_parent_occurrence IN NUMBER,
2302                               p_child_plan_id IN NUMBER,
2303                               p_child_collection_id IN NUMBER,
2304                               p_child_occurrence IN NUMBER)
2305         RETURN VARCHAR2 IS
2306 
2307  l_sql_string VARCHAR2(32000) := NULL;
2308  l_update_clause VARCHAR2(32000) := NULL;
2309  -- bug 6266477
2310  -- Increased the width to 32000 from 2000 for l_value
2311  -- skolluku Sun Oct 14 03:26:31 PDT 2007
2312  l_value VARCHAR2(32000);
2313  l_append BOOLEAN := FALSE;
2314  l_comma  CONSTANT VARCHAR2(3) := ' , ';
2315 
2316 
2317  c1         NUMBER;
2318  ignore     NUMBER;
2319  l_var      NUMBER := 1;
2320  -- bug 6266477
2321  -- Commented the bindTab array since the elementsarray would
2322  -- be used to build the array out of the string of values.
2323  -- l_bind_var would be declared as an object of ElementsArray
2324  -- skolluku Sun Oct 14 03:26:31 PDT 2007
2325  --
2326  -- TYPE bindTab IS TABLE OF l_value%TYPE INDEX BY BINARY_INTEGER;
2327  -- l_bind_var bindTab;
2328  l_bind_var   qa_txn_grp.ElementsArray;
2329 
2330  --
2331  -- bug 6266439
2332  -- New variable to hold the name of the column
2333  -- to be selected from the QA_RESULTS table
2334  -- ntungare Thu Aug  2 03:40:42 PDT 2007
2335  --
2336  select_column varchar2(2000);
2337 
2338  -- New variable to hold the bind variable
2339  -- to be updated in the QA_RESULTS table
2340  update_column varchar2(2000);
2341  --
2342  -- Bug 7588376
2343  -- A new variable to get the plan view naem for
2344  -- parent plan.
2345  -- skolluku
2346  --
2347  l_plan_view_name varchar2(1000);
2348 
2349  l_seq_flag BOOLEAN := FALSE;
2350 BEGIN
2351     For element_cntr in 1..p_parentchild_element_tab.count
2352        LOOP
2353          --
2354          -- bug 14134055
2355          If (Substr(UPPER(p_parentchild_element_tab(element_cntr).parent_database_column),1,8) = 'SEQUENCE') THEN
2356             l_seq_flag := TRUE;
2357          END IF;
2358          --
2359          -- Bug 6266477
2360          -- Moved the if block below for better framing.
2361          -- skolluku Sun Oct 14 03:26:31 PDT 2007
2362          --
2363          -- IF(l_append) THEN
2364          --    l_update_clause := l_update_clause  || l_comma;
2365          -- END IF;
2366 
2367          --
2368          -- bug 6266439
2369          -- If the result column names are not of the sequenceXX or CommentsXX
2370          -- type, then they can be of the HC or SC date Type.
2371          -- So make a call to the new proc to get the appropriate Select
2372          -- and update columns
2373          -- ntungare Thu Aug  2 03:42:18 PDT 2007
2374          --
2375          If ((Substr(UPPER(p_parentchild_element_tab(element_cntr).parent_database_column),1,8) <> 'SEQUENCE')  AND
2376              (Substr(UPPER(p_parentchild_element_tab(element_cntr).parent_database_column),1,7) <> 'COMMENT')) THEN
2377 
2378             DATE_SELECT_UPDATE(p_parent_result_column => UPPER(p_parentchild_element_tab(element_cntr).parent_database_column),
2379                                p_child_result_column  => UPPER(p_parentchild_element_tab(element_cntr).child_database_column),
2380                                p_parent_plan_id       => p_parent_plan_id,
2381                                p_child_plan_id        => p_child_plan_id,
2382                                p_var                  => l_var,
2383                                p_select_column        => select_column,
2384                                p_update_column        => update_column);
2385 
2386 
2387          End If;
2388          --
2389          -- Bug 7588376
2390          -- Check if the child is a softcoded element. If it is, call the new procedure get_deref_column
2391          -- which returns the dereferenced column if the child is a SC element. This will help in copying the
2392          -- dereferenced value to the child instead of the ID.
2393          -- skolluku
2394          --
2395          --
2396 	 --  Bug 8546279.FP for 8446050.extended to SEQUENCE and COMMENT element support.pdube
2397 	 --
2398  	 -- bug 9831189
2399  	 -- New function to check if the child element
2400  	 -- is a HC element that doesnt have a foreign
2401  	 -- key reference in which case the char name of the
2402  	 -- corresponding parent element is to be chosen
2403  	 -- instead of the standard HC result column name
2404  	 --
2405 	 If ((Substr(UPPER(p_parentchild_element_tab(element_cntr).child_database_column),1,9) = 'CHARACTER' OR
2406 	      Substr(UPPER(p_parentchild_element_tab(element_cntr).child_database_column),1,8) = 'SEQUENCE'  OR
2407 	      Substr(UPPER(p_parentchild_element_tab(element_cntr).child_database_column),1,7) = 'COMMENT'   OR
2408               IS_SPECIAL_HC_ELEM (
2409  	          p_child_result_column => UPPER(p_parentchild_element_tab(element_cntr).child_database_column),
2410  	          p_child_plan_id       => p_child_plan_id)
2411  	      ) AND
2412               select_column IS NULL ) THEN --AND
2413  	      -- NOT parent_plan_vales_tab.exists(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence)) THEN
2414 
2415                  get_deref_column(p_parent_result_column => UPPER(p_parentchild_element_tab(element_cntr).parent_database_column),
2416                             p_parent_plan_id       => p_parent_plan_id,
2417                             x_select_column        => select_column);
2418 
2419          End If;
2420          -- bug 6266477
2421          -- Moved if block below for easier framing of
2422          -- the select clause.
2423          -- skolluku Sun Oct 14 03:26:31 PDT 2007
2424          --
2425          IF(l_append) THEN
2426             l_update_clause := l_update_clause  || l_comma;
2427             --
2428             -- bug 6266477
2429             -- Added the following to execute the query
2430             -- to fetch all the parent result column values
2431             -- in a single hit to qa_results table
2432             -- The string is built as 1=<result_column_value1>@2=result_column_value2>
2433             -- so that the result_to_array can be reused to collect into an array.
2434             -- skolluku Sun Oct 14 03:26:31 PDT 2007
2435             --
2436             l_sql_string := l_sql_string || ' || ''@';
2437             l_sql_string := l_sql_string || element_cntr || '='' || '
2438                             || 'replace(' || NVL(select_column, p_parentchild_element_tab(element_cntr).parent_database_column) || ', ''@'', ''@@'')';
2439          ELSE
2440             l_sql_string := l_sql_string || '''' || element_cntr || '='' || '
2441                             || 'replace(' || NVL(select_column,  p_parentchild_element_tab(element_cntr).parent_database_column) || ', ''@'', ''@@'')';
2442          END IF;
2443 
2444          --
2445          -- bug 6266439
2446          -- Making use of the select columns string
2447          -- ntungare Thu Aug  2 03:42:18 PDT 2007
2448          --
2449          /*
2450          l_sql_string := 'SELECT ' || p_parentchild_element_tab(element_cntr).parent_database_column
2451            || ' FROM qa_results '
2452            || ' WHERE plan_id= :p_parent_plan_id'
2453            || ' AND collection_id= :p_parent_collection_id'
2454            || ' AND occurrence= :p_parent_occurrence';
2455          */
2456           --
2457           -- bug 626477
2458           -- Commented out the execution of the built string,
2459           -- since this query needs to be executed
2460           -- only once to better performance.
2461           -- skolluku Sun Oct 14 03:26:31 PDT 2007
2462           --
2463           /*
2464          l_sql_string := 'SELECT ' || NVL(select_column, p_parentchild_element_tab(element_cntr).parent_database_column)
2465               || ' FROM qa_results '
2466               || ' WHERE plan_id= :p_parent_plan_id'
2467               || ' AND collection_id= :p_parent_collection_id'
2468               || ' AND occurrence= :p_parent_occurrence';
2469 
2470          BEGIN
2471             EXECUTE IMMEDIATE l_sql_string INTO l_value
2472                USING p_parent_plan_id,p_parent_collection_id,p_parent_occurrence;
2473          EXCEPTION
2474             WHEN OTHERS THEN RETURN 'F';
2475          END;
2476          */
2477          -- anagarwa Fri May 24 11:09:43 PDT 2002
2478          -- bug 2388986. Though not directly related to this bug, it was found
2479          -- during the analysis/review. If there's a single quote in value then
2480          -- this whole thing will fail. adding dequote prevents such catastrophic
2481          -- scenarios.
2482 
2483          -- Bug 2976810. Instead of the literal value concatenation and execution using
2484          -- EXECUTE IMMEDIATE, we'll pack these values into an array, bind them and
2485          -- and execute using DBMS_SQL.execute. kabalakr
2486 
2487          -- l_update_clause := l_update_clause || cur_rec.child_database_column ||
2488          --                    ' = ' || ''''||qa_core_pkg.dequote(l_value) ||'''';
2489 
2490          --
2491          -- bug 6266439
2492          -- Making use of the update columns string
2493          -- ntungare Thu Aug  2 03:45:10 PDT 2007
2494          --
2495          /*
2496          l_update_clause := l_update_clause ||
2497                             p_parentchild_element_tab(element_cntr).child_database_column ||
2498                             ' = :'||to_char(l_var);
2499          */
2500          l_update_clause := l_update_clause ||
2501                             p_parentchild_element_tab(element_cntr).child_database_column ||
2502                             ' = '||NVL(update_column, ':'||to_char(l_var));
2503          --
2504          -- bug 6266477
2505          -- Commented the below assignment
2506          -- since it will happen after statement execution
2507          -- outside the loop.
2508          -- skolluku Sun Oct 14 03:26:31 PDT 2007
2509          --
2510          -- l_bind_var(l_var) := l_value;
2511          l_var := l_var + 1;
2512 
2513          l_append := TRUE;
2514 
2515          -- Bug 8546279.FP for 8446050.pdube
2516          -- Reinitializing the select and update column variables for next
2517          -- collection element.
2518          select_column := NULL;
2519          update_column := NULL;
2520        END LOOP;
2521 
2522     IF( l_update_clause IS NULL) THEN
2523         -- this will happen only if the element_cursor does not fetch any records.
2524         RETURN 'T';
2525     END IF;
2526     --
2527     -- Bug 7588376
2528     -- Fetch the plan view name for the parent plan. The deref view
2529     -- will be used instead of QA_RESULTS table to copy the values
2530     -- from parent to child because QA_RESULTS does not contain the
2531     -- dereferenced values for hardcoded elements. If the parent
2532     -- element is HC and child is SC, the value, instead of the ID,
2533     -- should be copied, and using QA_RESULTS will not accomplish that.
2534     -- The value will be picked from the deref_view only if the value
2535     -- is not cached in the collection
2536     -- skolluku
2537     --
2538     --
2539     --  Bug 8546279.FP for 8446050.pdube
2540     -- IF NOT parent_plan_vales_tab.exists(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence) THEN
2541     -- Bug 14134055
2542     --
2543     --IF NOT parent_plan_vales_tab.exists(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence||'*'||p_child_plan_id) THEN
2544     IF (NOT parent_plan_vales_tab.exists(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence||'*'||p_child_plan_id) OR
2545         l_seq_flag = TRUE) THEN
2546        SELECT deref_view_name INTO l_plan_view_name
2547         FROM qa_plans
2548         WHERE plan_id = p_parent_plan_id;
2549 
2550     --
2551     -- Bug 7588376
2552     -- Replace QA_RESULTS with the l_plan_view_name for the reason explained above.
2553     -- skolluku
2554     --
2555     --
2556     --
2557     -- bug 6266477
2558     -- Execute the select statement here to hit the table
2559     -- QA_RESULTS only once to improve performance and get
2560     -- the values into anl_bind_var array.
2561     -- skolluku Sun Oct 14 03:26:31 PDT 2007
2562     --
2563     l_sql_string := 'Select ' || l_sql_string
2564                            -- || ' FROM qa_results '
2565                            || ' FROM ' || l_plan_view_name
2566                            || ' WHERE plan_id= :p_parent_plan_id'
2567                            || ' AND collection_id= :p_parent_collection_id'
2568                            || ' AND occurrence= :p_parent_occurrence';
2569     BEGIN
2570        EXECUTE IMMEDIATE l_sql_string INTO l_value
2571          USING p_parent_plan_id,p_parent_collection_id,p_parent_occurrence;
2572        -- Bug 8546279.FP for 8446050.Introduced child_plan_id to uniquely identify the record.pdube
2573        -- parent_plan_vales_tab(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence) := l_value;
2574        parent_plan_vales_tab(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence||'*'||p_child_plan_id) := l_value;
2575     EXCEPTION
2576        WHEN OTHERS THEN RETURN 'F';
2577     END;
2578     -- Picking the cached value
2579     ELSE
2580        -- Bug 8546279.FP for 8446050.pdube
2581        -- l_value := parent_plan_vales_tab(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence);
2582        l_value := parent_plan_vales_tab(p_parent_plan_id ||'*'||p_parent_collection_id||'*'||p_parent_occurrence||'*'||p_child_plan_id);
2583     END IF;
2584 
2585     l_bind_var := qa_txn_grp.result_to_array(l_value);
2586 
2587     l_update_clause := 'UPDATE qa_results  SET ' || l_update_clause
2588          || ' WHERE plan_id= :p_child_plan_id'
2589          || ' AND collection_id= :p_child_collection_id'
2590          || ' AND occurrence= :p_child_occurrence';
2591 
2592     BEGIN
2593 
2594         c1 := dbms_sql.open_cursor;
2595         dbms_sql.parse(c1, l_update_clause, dbms_sql.native);
2596 
2597         l_var := l_bind_var.FIRST;
2598 
2599         WHILE (l_var IS NOT NULL) LOOP
2600            --
2601            -- bug 6266477
2602            -- Replaced bind statement since, l_bind_val is
2603            -- an object of qa_txn_grp.ElementsArray which
2604            -- will have 2 fields and we are interested
2605            -- only in the value field.
2606            -- skolluku Sun Oct 14 03:26:31 PDT 2007
2607            --
2608            -- dbms_sql.bind_variable(c1, ':' || to_char(l_var), l_bind_var(l_var));
2609            dbms_sql.bind_variable(c1, ':' || to_char(l_var), l_bind_var(l_var).value);
2610 	   l_var := l_bind_var.NEXT(l_var);
2611         END LOOP;
2612 
2613         dbms_sql.bind_variable(c1, ':p_child_plan_id', p_child_plan_id);
2614         dbms_sql.bind_variable(c1, ':p_child_collection_id', p_child_collection_id);
2615         dbms_sql.bind_variable(c1, ':p_child_occurrence', p_child_occurrence);
2616 
2617         ignore := dbms_sql.execute(c1);
2618 
2619         --bug# 5510747 shkalyan. Added close cursor
2620 	dbms_sql.close_cursor(c1);
2621 
2622     EXCEPTION
2623        WHEN OTHERS THEN
2624         --
2625         -- Bug 4675642.
2626         -- The cursor c1 was not being closed in case of error during processing the records. Doing
2627         -- that now.
2628         -- ntungare Sun Oct 16 21:38:29 PDT 2005
2629         --
2630            IF dbms_sql.is_open(c1)
2631              THEN
2632                dbms_sql.close_cursor(c1);
2633            END IF;
2634            RETURN 'F';
2635     END;
2636     Return 'T';
2637 END perform_child_update;
2638 
2639 FUNCTION update_child(p_parent_plan_id IN NUMBER,
2640                        p_parent_collection_id IN NUMBER,
2641                        p_parent_occurrence IN NUMBER,
2642                        p_child_plan_id IN NUMBER,
2643                        p_child_collection_id IN NUMBER,
2644                        p_child_occurrence IN NUMBER)
2645         RETURN VARCHAR2 IS
2646 
2647  -- the following cursor contains sql text used for the view
2648  -- qa_pc_result_columns_v. I added link_flag in where clause.
2649 
2650  -- anagarwa Mon Dec 16 16:55:09 PST 2002
2651  -- Bug 2701777
2652  -- added parent_enabled_flag and child_enabled_flag to where clause
2653  -- to limit working on onlly those elements that are enabled.
2654 
2655  CURSOR element_cursor IS
2656    SELECT qprc.parent_database_column,
2657           qprc.child_database_column
2658    FROM
2659        qa_pc_result_columns_v qprc
2660   WHERE
2661        qprc.parent_plan_id = p_parent_plan_id and
2662        qprc.child_plan_id = p_child_plan_id and
2663        qprc.element_relationship_type = 1 and
2664        parent_enabled_flag = 1 and
2665        child_enabled_flag = 1;
2666 
2667  -- suramasw.Bug 3561911.
2668 
2669  -- The following cursor was added to generate sequence numbers
2670  -- for sequence elements in child plan which donot have copy
2671  -- relation from the parent plan in date entry mode 'Automatic'.
2672 
2673  -- The cursor does the following(starting from the inner join)
2674  -- 1.get the child plan collection elements char_id's which have
2675  --   copy relation with the parent plan and when the date entry
2676  --   mode is 'Automatic'.
2677  -- 2.get the child plan collection elements char_ids which are
2678  --   of datatype sequence and which donot belong to the set of
2679  --   values fetched in step 1 mentioned above.
2680  -- 3.get the result_column_name(SEQUENCE1, SEQUENCE2, ......)
2681  --   for the values fetched in step 2 mentioned above.
2682 
2683 /* Bug 3678910. Commenting out the changes done for bug 3561911.
2684    Please see the bug for more info. kabalakr.
2685 
2686  CURSOR seq_cursor is
2687     SELECT qpc.char_id,
2688            qpc.result_column_name
2689     FROM   qa_chars qc,
2690            qa_plan_chars qpc
2691     WHERE  qpc.plan_id = p_child_plan_id
2692     AND qpc.char_id NOT IN
2693         (SELECT child_char_id
2694          FROM qa_pc_element_relationship qper,
2695               qa_pc_plan_relationship qppr
2696          WHERE qper.plan_relationship_id  = qppr.plan_relationship_id
2697          AND qppr.parent_plan_id = p_parent_plan_id
2698          AND qppr.child_plan_id = p_child_plan_id
2699          AND qppr.data_entry_mode = 2)
2700     AND qpc.char_id = qc.char_id
2701     AND qc.datatype =5;
2702 
2703  l_seq VARCHAR2(2000);
2704 
2705 */
2706 
2707 
2708   -- 5114865
2709   -- Collection to hold the PC relationship elements
2710   l_element_cursor_tab QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type;
2711 
2712   -- Counter for the PC elements
2713   l_element_cntr  PLS_INTEGER := 1;
2714 
2715   l_ret_val  VARCHAR2(10);
2716 
2717 BEGIN
2718   -- Bug 5114865
2719   -- Collecting the child plan elements which are
2720   -- to be updated into a collection that would be
2721   -- passed to perform_child_update to processing
2722   -- ntungare Wed Mar  8 09:04:26 PST 2006
2723   --
2724   FOR cur_rec IN element_cursor LOOP
2725      l_element_cursor_tab(l_element_cntr).parent_database_column:= cur_rec.parent_database_column;
2726      l_element_cursor_tab(l_element_cntr).child_database_column := cur_rec.child_database_column;
2727      l_element_cntr := l_element_cntr + 1;
2728   END LOOP;
2729 
2730    -- Bug 5114865
2731    -- Calling the proedure to perform the update
2732    -- ntungare Wed Mar  8 09:04:26 PST 2006
2733    --
2734    l_ret_val := perform_child_update
2735                        (p_parentchild_element_tab => l_element_cursor_tab,
2736                         p_parent_plan_id          => p_parent_plan_id ,
2737                         p_parent_collection_id    => p_parent_collection_id,
2738                         p_parent_occurrence       => p_parent_occurrence,
2739                         p_child_plan_id           => p_child_plan_id ,
2740                         p_child_collection_id     => p_child_collection_id,
2741                         p_child_occurrence        => p_child_occurrence);
2742 
2743    If l_ret_val = 'F'
2744      THEN RETURN 'F';
2745    END IF;
2746 
2747  RETURN 'T';
2748 END update_child;
2749 
2750 -- bug 5114865
2751 -- New Function to get a list of all the elements
2752 -- in the Child Plan that get the value from a seq
2753 -- type element in the Parent plan or from a char
2754 -- element having a sequence Ancestor
2755 -- ntungare Wed Mar 22 01:13:53 PST 2006
2756 --
2757 FUNCTION get_seq_rel_elements (p_parent_plan_id      IN NUMBER,
2758                                p_child_plan_id       IN NUMBER,
2759                                p_topmostRel_flag     IN BOOLEAN,
2760                                p_parent_elements_tab IN QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type,
2761                                p_elements_tab       OUT NOCOPY QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type)
2762 
2763        RETURN BOOLEAN AS
2764 
2765    l_parent_datatype      NUMBER;
2766    l_childdbcolname       VARCHAR2(1000);
2767    l_prev_parentdbcolname VARCHAR2(1000);
2768 
2769    -- Cursor to fetch the Char elements in the child plan
2770    -- having sequence ancestor but not a direct Seq-char
2771    -- relation
2772    Cursor element_cur(p_parentdbcol VARCHAR2) IS
2773    SELECT qprc.parent_database_column parent_database_column,
2774            qprc.child_database_column  child_database_column
2775     FROM
2776         qa_pc_result_columns_v qprc
2777    WHERE
2778         qprc.parent_plan_id = p_parent_plan_id and
2779         qprc.child_plan_id = p_child_plan_id and
2780         qprc.element_relationship_type = 1 and
2781         parent_enabled_flag = 1 and
2782         child_dataType <> 5 and
2783         child_enabled_flag = 1 and
2784         parent_database_column = p_parentdbcol ;
2785 
2786    elements_tab_count PLS_INTEGER;
2787 BEGIN
2788    -- Fetching the Sequence to Char Relation Elements
2789    SELECT qprc.parent_database_column parent_database_column,
2790            qprc.child_database_column  child_database_column
2791       BULK COLLECT INTO  p_elements_tab
2792     FROM
2793         qa_pc_result_columns_v qprc
2794    WHERE
2795         qprc.parent_plan_id = p_parent_plan_id and
2796         qprc.child_plan_id = p_child_plan_id and
2797         qprc.element_relationship_type = 1 and
2798         parent_enabled_flag = 1 and
2799         child_dataType <> 5 and
2800         child_enabled_flag = 1 and
2801         parent_dataType = 5 ;
2802 
2803     -- A topmost plan-child combination will only have
2804     -- Seq-Char copy relation. However, further down the
2805     -- hierarchy the copy relationship can be between
2806     -- two char elements, the one on the parent having a
2807     -- Sequence Ancestor. The following section of code
2808     -- fetches these relations
2809     -- ntungare
2810     If p_topmostRel_flag = FALSE THEN
2811        elements_tab_count := NVL(p_elements_tab.LAST,0);
2812 
2813        -- Looping through the elements that have been copied onto the
2814        -- Current parent plan, when it was processed as a child, and
2815        -- Checking if any of these have to be futher copied down on to
2816        -- the Current Child plan.
2817        FOR cntr in 1..p_parent_elements_tab.COUNT
2818           LOOP
2819              -- Fetching the values from the Cursor defined above
2820              -- passing the Parent and Child Plan Id and the Parent
2821              -- DB columns and setting the Child DB column where they need
2822              -- to be copied .
2823              FOR elem in element_cur(p_parent_elements_tab(cntr).child_database_column)
2824                LOOP
2825                   elements_tab_count := elements_tab_count +1;
2826                   p_elements_tab(elements_tab_count).parent_database_column := elem.parent_database_column;
2827                   p_elements_tab(elements_tab_count).child_database_column := elem.child_database_column;
2828                END LOOP;
2829           END LOOP;
2830     END IF;
2831 
2832     -- Checking if any P-C relations exist
2833     -- If they do then the function return
2834     -- TRUE after wich furhter processing can
2835     -- be done.
2836     IF p_elements_tab.COUNT <> 0 THEN
2837        RETURN TRUE;
2838     ELSE RETURN FALSE;
2839     END IF;
2840 END get_seq_rel_elements;
2841 
2842 -- Bug 5114865
2843 -- New Procedure to get a list of the elements that
2844 -- have been copied onto the plan Id passed when it
2845 -- is processed as a child plan.
2846 -- The elements those have been copied at every level
2847 -- are stored in the Collection nested in p_parentchild_Tab
2848 -- ntungare Wed Mar 22 01:14:24 PST 2006
2849 --
2850 PROCEDURE get_parent_elementscopied(p_parentchild_Tab     IN QA_PARENT_CHILD_PKG.ParentChildTabTyp,
2851                                     p_current_plan_id     IN NUMBER,
2852                                     p_parent_elements_tab OUT NOCOPY QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type)
2853   AS
2854 BEGIN
2855   -- Looping through all the P-C relations
2856   -- Till we reach a level where the Plan Id passed
2857   -- has been a child plan
2858   For cntr in 1..p_parentchild_Tab.COUNT
2859     LOOP
2860        If p_current_plan_id = p_parentchild_Tab(cntr).child_plan_id
2861          THEN
2862             -- If the level if found then the elements
2863             -- those have been copied in it when it was a child
2864             -- are returned in a collection.
2865             -- These are the only elements whose values may or
2866             -- maynot have to be propagated further to the
2867             -- subsequent Children, if such a relationship exists
2868             p_parent_elements_tab := p_parentchild_Tab(cntr).parentelement_tab;
2869             EXIT;
2870        END IF;
2871     END LOOP;
2872 END get_parent_elementscopied;
2873 
2874 
2875 -- Bug 5114865
2876 -- Function to copy the values from the Parent to the Child plans
2877 -- only when the source element in the Parent plan is of the
2878 -- Sequence Type and that in the child is of the Char Type
2879 -- ntungare Wed Mar 22 01:15:26 PST 2006
2880 --
2881 FUNCTION update_sequence_child(p_ParentChild_Tab IN QA_PARENT_CHILD_PKG.ParentChildTabTyp)
2882        RETURN VARCHAR2 IS
2883 
2884 Type Num_tab_Typ is table of NUMBER INDEX BY BINARY_INTEGER;
2885 parentCol_DataType_Tab Num_tab_Typ;
2886 parentwithSeq_flag BOOLEAN;
2887 
2888 l_ParentChild_Tab         QA_PARENT_CHILD_PKG.ParentChildTabTyp;
2889 l_elements_toprocess_tab  QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type;
2890 l_parent_elements_tab     QA_PARENT_CHILD_PKG.g_parentchild_elementtab_type;
2891 
2892 l_ret_val VARCHAR2(10);
2893 
2894 l_element_cntr  PLS_INTEGER := 1;
2895 
2896 l_topmostRel_flag BOOLEAN;
2897 l_topmost_plan_id NUMBER;
2898 
2899 BEGIN
2900      l_ParentChild_Tab := p_ParentChild_Tab;
2901      parentwithSeq_flag := FALSE;
2902      l_topmostRel_flag := TRUE;
2903 
2904      --Getting the Topmost Plan Id
2905      l_topmost_plan_id := l_ParentChild_Tab(1).parent_plan_id;
2906 
2907      -- Looping through the P-C plan combinations to be processed
2908      For cntr in 1..l_ParentChild_Tab.COUNT
2909        LOOP
2910           -- If the current Parent Plan Id is the same as the
2911           -- Topmost plan id then setting the flag accordingly
2912           -- This flag would determine if we need to look at what
2913           -- elements have been copied to the Current Parent plan
2914           -- when it was processed as a child, or not, as it would
2915           -- have no meaning for the Topmost level Plan.
2916           If l_ParentChild_Tab(cntr).parent_plan_id = l_topmost_plan_id
2917             THEN l_topmostRel_flag := TRUE;
2918             ELSE l_topmostRel_flag := FALSE;
2919           END IF;
2920 
2921           -- Getting the elements copied to the current Parent Plan
2922           -- during its processing as a child Plan.
2923           -- For the Topmost level plan, this would be of no meaning
2924           IF l_topmostRel_flag = FALSE THEN
2925              get_parent_elementscopied(p_ParentChild_Tab     => l_ParentChild_Tab,
2926                                        p_current_plan_id     => l_ParentChild_Tab(cntr).parent_plan_id,
2927                                        p_parent_elements_tab => l_parent_elements_tab);
2928           END IF;
2929 
2930           -- Getting a list of the the elements in the child plan
2931           -- that either get the value from a sequence element in
2932           -- the parent plan or a Char element which is turn may
2933           -- have received the data from a sequence element
2934           --
2935           parentwithSeq_flag := get_seq_rel_elements
2936                                         (p_parent_plan_id      => l_ParentChild_Tab(cntr).parent_plan_id,
2937                                          p_child_plan_id       => l_ParentChild_Tab(cntr).child_plan_id,
2938                                          p_topmostRel_flag     => l_topmostRel_flag,
2939                                          p_parent_elements_tab => l_parent_elements_tab,
2940                                          p_elements_tab        => l_elements_toprocess_tab);
2941 
2942           -- Processing the list of elements obtained from above
2943           -- and captured in l_pc_elementstoprocess_tab
2944           -- The parentwithSeq_flag would be TRUE only if any of
2945           -- the elements of the Child Plan have copy relations
2946           -- with Seq Type elements or with Char elements with Seq
2947           -- Type ancestors, in the parent plan
2948           --
2949           IF parentwithSeq_flag THEN
2950              l_ret_val := perform_child_update
2951                                  (p_parentchild_element_tab => l_elements_toprocess_tab,
2952                                   p_parent_plan_id          => l_ParentChild_Tab(cntr).parent_plan_id,
2953                                   p_parent_collection_id    => l_ParentChild_Tab(cntr).parent_collection_id,
2954                                   p_parent_occurrence       => l_ParentChild_Tab(cntr).parent_occurrence,
2955                                   p_child_plan_id           => l_ParentChild_Tab(cntr).child_plan_id,
2956                                   p_child_collection_id     => l_ParentChild_Tab(cntr).child_collection_id,
2957                                   p_child_occurrence        => l_ParentChild_Tab(cntr).child_occurrence);
2958 
2959              If l_ret_val = 'F'
2960                 THEN RETURN 'F';
2961              END IF;
2962 
2963              -- Resetting the flag value
2964              parentwithSeq_flag := FALSE;
2965 
2966              -- Copying the list of the elements copied to the
2967              -- Child plan into the nested collection in l_ParentChild_Tab
2968              -- as this would be looked up when the Current Child plan is
2969              -- processed as a Parent Plan
2970              --
2971              l_ParentChild_Tab(cntr).parentelement_tab:= l_elements_toprocess_tab;
2972 
2973              -- Emptying the elements collection
2974              l_elements_toprocess_tab.DELETE;
2975           END IF;
2976         END LOOP;
2977    RETURN 'T';
2978 END update_sequence_child;
2979 
2980 PROCEDURE get_criteria_values(p_parent_plan_id IN NUMBER,
2981                               p_parent_collection_id IN NUMBER,
2982                               p_parent_occurrence IN NUMBER,
2983                               p_organization_id IN NUMBER,
2984                               x_criteria_values OUT NOCOPY VARCHAR2) IS
2985 
2986 
2987 CURSOR parent_cur IS
2988    /*
2989      anagarwa Tue Jul 16 18:36:52 PDT 2002
2990      Bug 2465920 reports that when hardcoded elements have to be copied to
2991      history or automatic plans in collection imports, it (histor/automatic
2992      functionality) fails.
2993      By selecting form_field instead of database_column we can fix it.
2994      However, item, comp_item, locator and  comp_locator don't exist in
2995      QA_RESULTS_V. So we add special handling for these later.
2996   */
2997    --SELECT char_id,database_column
2998    SELECT char_id, replace(form_field, 'DISPLAY' , 'CHARACTER') database_column,
2999         datatype
3000    FROM qa_pc_plan_columns_v
3001    WHERE plan_id = p_parent_plan_id;
3002 
3003  --
3004  -- bug 6266477
3005  -- Increased the width of the variables
3006  -- l_res_value, select_clause to 32000
3007  -- skolluku Mon Oct 15 02:57:40 PDT 2007
3008  --
3009  l_res_value  VARCHAR2(32000);
3010  l_string     VARCHAR2(32000);
3011  l_append     BOOLEAN;
3012 
3013  select_clause VARCHAR2(32000);
3014  from_clause CONSTANT VARCHAR2(80)    := ' FROM QA_RESULTS_V ';
3015  where_clause VARCHAR2(5000);
3016  query_clause VARCHAR2(32000);
3017  -- anagarwa Tue Jul 16 18:36:52 PDT 2002
3018  -- Bug 2465920: new variable to handle  item, comp_item, locator and
3019  -- comp_locator
3020  column_name  VARCHAR2(150);
3021 
3022 
3023  -- Bug 3776542. Performance issue due to use of literals in the SQL to fetch
3024  -- criteria value from QA_RESULTS_V. Earlier we were using reference cursor to
3025  -- fetch the value with a SQL that had literals. After fix, we are using EXECUTE_IMMEDIATE
3026  -- with SQL containing bind variables. This ref cursor is needed no more, hence commenting
3027  -- it out.Thu Jul 29 02:02:03 PDT 2004.
3028  -- srhariha.
3029 
3030 -- Type resCurTyp IS REF CURSOR; --define weak REF CURSOR type
3031 -- res_cur resCurTyp; --define cursor variable
3032 
3033 BEGIN
3034 
3035   -- Bug 3776542. Performance issue due to use of literals in the SQL. Modified the
3036   -- string to include bind variables.
3037   -- srhariha.Thu Jul 29 02:02:03 PDT 2004.
3038   l_append := FALSE;
3039   where_clause := ' WHERE plan_id = ' || ':p_parent_plan_id' ||
3040                    ' AND collection_id = ' ||':p_parent_collection_id' ||
3041                    ' AND occurrence = ' || ':p_parent_occurrence';
3042 
3043   -- finding out the values for each element of parent record
3044   FOR parent_rec IN parent_cur LOOP
3045       -- anagarwa Tue Jul 16 18:36:52 PDT 2002
3046       -- Bug 2465920: item, comp_item, locator and comp_locator don't exist in
3047       -- QA_REULTS_V so we select id's instead.
3048       column_name := parent_rec.database_column;
3049       IF column_name = 'ITEM' THEN
3050           column_name := 'ITEM_ID';
3051 
3052       ELSIF column_name = 'COMP_ITEM' THEN
3053           column_name := 'COMP_ITEM_ID';
3054 
3055       ELSIF column_name = 'LOCATOR' THEN
3056           column_name := 'LOCATOR_ID';
3057 
3058       ELSIF column_name = 'COMP_LOCATOR' THEN
3059           column_name := 'COMP_LOCATOR_ID';
3060 
3061       -- Bug 2694385. Added bill_reference,routing_reference,to_locator since
3062       -- these elements will not present in qa_results_v.
3063       -- rponnusa Wed Dec 18 05:38:40 PST 2002
3064 
3065       ELSIF column_name = 'BILL_REFERENCE' THEN
3066           column_name  := 'BILL_REFERENCE_ID';
3067 
3068       ELSIF column_name = 'ROUTING_REFERENCE' THEN
3069           column_name  := 'ROUTING_REFERENCE_ID';
3070 
3071       ELSIF column_name = 'TO_LOCATOR' THEN
3072           column_name  := 'TO_LOCATOR_ID';
3073 
3074       -- Bug 3424886 ksoh Mon Feb  9 13:39:41 PST 2004
3075       -- need to convert hardcoded dates to canonical string
3076       ELSIF (substr(column_name, 1, 9) <> 'CHARACTER') AND
3077             (parent_rec.datatype = qa_ss_const.datetime_datatype) THEN
3078           column_name  := 'FND_DATE.DATE_TO_CANONICAL(' || column_name || ')';
3079       END IF;
3080       --
3081       -- bug 6266477
3082       -- Commenting the below code since the handling is done
3083       -- differently to avoid multiple hits to QA_RESULTS_V
3084       -- skolluku Mon Oct 15 02:57:40 PDT 2007
3085       --
3086       /*select_clause := 'SELECT ' || column_name;
3087       query_clause := select_clause || from_clause || where_clause;
3088 
3089       -- Bug 3776542. Performance issue due to use of literals in the SQL to fetch
3090       -- criteria value from QA_RESULTS_V. Earlier we were using reference cursor to
3091       -- fetch the value with a SQL that had literals. After fix, we are using EXECUTE_IMMEDIATE
3092       -- with SQL containing bind variables. This ref cursor is needed no more, hence commenting
3093       -- it out.
3094       -- srhariha.Thu Jul 29 02:02:03 PDT 2004
3095 
3096       --OPEN res_cur FOR query_clause ;
3097       --FETCH res_cur INTO l_res_value;
3098       --CLOSE res_cur;
3099       EXECUTE IMMEDIATE query_clause
3100               INTO      l_res_value
3101               USING     p_parent_plan_id,
3102                         p_parent_collection_id,
3103                         p_parent_occurrence;
3104 
3105       IF (l_append) THEN
3106            l_string    := l_string || '@';
3107       END IF;
3108       */
3109 
3110 
3111       -- Bug 2694385. Commented existing IF condition and added following code with
3112       -- bill_reference,routing_reference,to_locator
3113       -- rponnusa Wed Dec 18 05:38:40 PST 2002
3114 
3115     /*
3116       IF ((parent_rec.char_id = 10) or  parent_rec.char_id = 60) then
3117               l_res_value := qa_flex_util.item(p_organization_id , l_res_value);
3118       ELSIF ((parent_rec.char_id = 15) or (parent_rec.char_id = 65)) then
3119               l_res_value := qa_flex_util.locator(p_organization_id, l_res_value);
3120       END IF;
3121     */
3122       -- Bug 6266477
3123       -- Commented below code.
3124       -- skollluku Mon Oct 15 02:57:40 PDT 2007
3125       /*IF parent_rec.char_id IN (qa_ss_const.item, qa_ss_const.comp_item,
3126                                 qa_ss_const.routing_reference, qa_ss_const.bill_reference) THEN
3127             l_res_value := qa_flex_util.item(p_organization_id , l_res_value);
3128 
3129       ELSIF parent_rec.char_id IN (qa_ss_const.locator, qa_ss_const.comp_locator,
3130                                    qa_ss_const.to_locator) THEN
3131             l_res_value := qa_flex_util.locator(p_organization_id, l_res_value);
3132       END IF;
3133 
3134       -- Bug 2403395
3135       -- If the l_res_value contains '@' character then doubly encode it.
3136       -- rponnusa Wed Jun  5 00:49:14 PDT 2002
3137       l_res_value := replace(l_res_value,'@','@@');
3138 
3139       l_string := l_string || parent_rec.char_id || '=' || l_res_value;
3140       */
3141       --
3142       -- bug 6266477
3143       -- Added the below code to enhance performance
3144       -- by hitting the view QA_RESULTS_V just once
3145       -- skolluku Mon Oct 15 02:57:40 PDT 2007
3146       --
3147       IF parent_rec.char_id IN (qa_ss_const.item, qa_ss_const.comp_item,
3148                                 qa_ss_const.routing_reference, qa_ss_const.bill_reference) THEN
3149             column_name := 'qa_flex_util.item(' || p_organization_id || ', ' || column_name || ')';
3150 
3151       ELSIF parent_rec.char_id IN (qa_ss_const.locator, qa_ss_const.comp_locator,
3152                                    qa_ss_const.to_locator) THEN
3153             column_name := 'qa_flex_util.locator(' || p_organization_id || ', ' || column_name || ')';
3154       END IF;
3155 
3156       column_name := 'replace(' || column_name || ', ''@'', ''@@'')';
3157       if (l_append) then
3158          l_string    := l_string || ' || ''@';
3159          l_string := l_string || parent_rec.char_id || '='' || ' || column_name;
3160       else
3161          l_string := l_string || '''' || parent_rec.char_id || '='' || ' || column_name;
3162       end if;
3163 
3164       l_append := TRUE;
3165 
3166   END LOOP;
3167   --
3168   -- bug 6266477
3169   -- Executing the statement outside the loop
3170   -- to improve performance.
3171   -- skolluku Mon Oct 15 02:57:40 PDT 2007
3172   --
3173   select_clause := 'SELECT ' || l_string;
3174   query_clause := select_clause || from_clause || where_clause;
3175   EXECUTE IMMEDIATE query_clause
3176           INTO      l_res_value
3177           USING     p_parent_plan_id,
3178                     p_parent_collection_id,
3179                     p_parent_occurrence;
3180   --
3181   -- bug 6266477
3182   -- Modified since l_res_value needs be
3183   -- assigned to x_criteria_values
3184   -- skolluku Mon Oct 15 02:57:40 PDT 2007
3185   --
3186   -- x_criteria_values := l_string;
3187   x_criteria_values := l_res_value;
3188 
3189 END get_criteria_values;
3190 
3191 
3192 
3193 PROCEDURE insert_history_auto_rec(p_parent_plan_id IN NUMBER,
3194                                   p_txn_header_id IN NUMBER,
3195                                   p_relationship_type IN NUMBER,
3196                                   p_data_entry_mode IN NUMBER) IS
3197 
3198  CURSOR plan_cur IS
3199   SELECT 1
3200   FROM qa_pc_plan_relationship
3201   WHERE parent_plan_id = p_parent_plan_id
3202   AND plan_relationship_type = p_relationship_type
3203   AND data_entry_mode = p_data_entry_mode;
3204 
3205  CURSOR res_cur IS
3206   SELECT collection_id,occurrence,organization_id
3207   FROM qa_results
3208   WHERE plan_id = p_parent_plan_id
3209   AND txn_header_id = p_txn_header_id;
3210 
3211 
3212 l_dummy   NUMBER := -99;
3213 l_spec_id NUMBER;
3214 x_status  VARCHAR2(1);
3215 l_status  VARCHAR2(1);
3216 
3217 l_criteria_values VARCHAR2(32000);
3218 l_child_plan_ids  VARCHAR2(10000);
3219 
3220 -- variables declared for bug 2302539
3221 l_child_txn_header_id NUMBER;
3222 l_fire_action         BOOLEAN := FALSE;
3223 
3224 BEGIN
3225   IF(QA_PARENT_CHILD_PKG.is_parent_child_plan(p_parent_plan_id ) = 'F') THEN
3226       -- don't do anything
3227      RETURN;
3228   END IF;
3229   OPEN plan_cur;
3230   FETCH plan_cur INTO l_dummy;
3231   CLOSE plan_cur;
3232 
3233   IF(l_dummy <> 1) THEN
3234     -- no history or automatic child plans
3235     RETURN;
3236   END IF;
3237 
3238   -- Bug 2302539
3239   -- Parent and child records txn_header_id should be different in order to fire
3240   -- actions for the child plans, since action firing for the parent record
3241   -- was taken care in collection import code. We just needs to fire actions
3242   -- for the child records.
3243   -- rponnusa Tue May 28 01:52:47 PDT 2002
3244   FOR c1 in (SELECT mtl_material_transactions_s.nextval txn_header_id FROM DUAL) LOOP
3245 
3246       l_child_txn_header_id := c1.txn_header_id;
3247       EXIT;
3248   END LOOP;
3249 
3250   FOR import_rec IN res_cur LOOP
3251      get_criteria_values(p_parent_plan_id,
3252                          import_rec.collection_id,
3253                          import_rec.occurrence,
3254                          import_rec.organization_id,
3255                          l_criteria_values);
3256      l_status := evaluate_criteria(p_parent_plan_id,
3257                                    l_criteria_values,
3258                                    p_relationship_type,
3259                                    p_data_entry_mode,
3260                                    l_child_plan_ids);
3261 
3262      IF(l_status = 'T') THEN
3263 
3264         insert_automatic_records(p_parent_plan_id,
3265                                  import_rec.collection_id,
3266                                  import_rec.occurrence,
3267                                  l_child_plan_ids,
3268                                  p_relationship_type,
3269                                  p_data_entry_mode,
3270                                  l_criteria_values,
3271                                  import_rec.organization_id,
3272                                  l_spec_id,
3273                                  x_status,
3274                                  l_child_txn_header_id);
3275         l_fire_action := TRUE;
3276      END IF;
3277 
3278 
3279   END LOOP;
3280 
3281   -- Bug 2302539
3282   -- enable and fire actions only if atleast one history/automatic record is inserted.
3283   -- Passing child_txn_header_id to fire actions for the child plans.
3284   -- rponnusa Tue May 28 01:52:47 PDT 2002
3285 
3286   IF l_fire_action THEN
3287     enable_fire_for_txn_hdr_id(l_child_txn_header_id);
3288   END IF;
3289 
3290 END insert_history_auto_rec;
3291 
3292 FUNCTION is_parent_saved(p_plan_id  IN NUMBER,
3293                           p_collection_id IN NUMBER,
3294                           p_occurrence IN NUMBER)
3295         RETURN VARCHAR2 IS
3296 
3297  -- Return true if the given parent record is saved in enable status
3298 
3299  CURSOR c IS
3300     SELECT 1
3301     FROM qa_results
3302     WHERE plan_id = p_plan_id
3303     AND collection_id = p_collection_id
3304     AND occurrence = p_occurrence
3305     AND status = 2;
3306 
3307  l_status NUMBER := -99;
3308 BEGIN
3309   OPEN c;
3310   FETCH c INTO  l_status;
3311   CLOSE c;
3312   IF (l_status = 1) THEN
3313      RETURN 'T';
3314   ELSE
3315      RETURN 'F';
3316   END IF;
3317 
3318 END is_parent_saved;
3319 
3320 FUNCTION update_all_children(p_parent_plan_id IN NUMBER,
3321                        p_parent_collection_id IN NUMBER,
3322                        p_parent_occurrence IN NUMBER)
3323         RETURN VARCHAR2 IS
3324 
3325   l_return_value  VARCHAR2(1);
3326   l_dummy VARCHAR2(1);
3327 
3328   -- anagarwa Fri May 24 09:57:43 PDT 2002
3329   -- bug 2388986
3330   -- the cursor was incorrect because it was updating all children including
3331   -- history records. this is incorrect as instead of just inserting a new
3332   --  record for history, all previour records are updated with new data.
3333   -- This in turn causes the audit trail to be lost thereby defeating the
3334   -- whole purpose of having history plans!
3335   -- I've added a new join with qa_pc_plan_relationship to ensure this does
3336   -- NOT happen for history plans.
3337   -- IT IS EXTREMELY IMPORTANT TO ENSURE THAT A SINGLE PAIR OF PARENT CHILD
3338   -- PLANS FORM A SINGLE RELATIONSHIP. IF NOT THAT THIS JOIN WILL FAIL !
3339   CURSOR children_cur IS
3340         select qprr.child_plan_id,
3341                qprr.child_collection_id,
3342                qprr.child_occurrence
3343         from   qa_pc_results_relationship qprr,
3344                qa_pc_plan_relationship    qpr
3345         where  qprr.parent_occurrence = p_parent_occurrence
3346         and    qprr.parent_plan_id = p_parent_plan_id
3347         and    qprr.parent_collection_id = p_parent_collection_id
3348         and    qpr.parent_plan_id = qprr.parent_plan_id
3349         and    qpr.child_plan_id = qprr.child_plan_id
3350         and    qpr.data_entry_mode <> 4;
3351 
3352 BEGIN
3353     l_return_value := 'T';
3354     l_dummy := 'T';
3355     --
3356     -- bug 7588376
3357     -- Starting with a fresh copy of the collection
3358     -- that stores the values of the relactionship elements
3359     -- in the parent plan
3360     --
3361     parent_plan_vales_tab.delete;
3362 
3363         FOR children_rec IN children_cur
3364         LOOP
3365                 l_return_value :=
3366                         update_child (  p_parent_plan_id,
3367                                 p_parent_collection_id,
3368                                 p_parent_occurrence,
3369                                 children_rec.child_plan_id,
3370                                 children_rec.child_collection_id,
3371                                 children_rec.child_occurrence);
3372 
3373                 --check if the fetched child has any children
3374                 IF (descendants_exist(children_rec.child_plan_id,
3375                                 children_rec.child_collection_id,
3376                                 children_rec.child_occurrence) = 'T')
3377                 THEN
3378                         --Recursive call
3379                    l_dummy :=
3380                       update_all_children(children_rec.child_plan_id,
3381                                 children_rec.child_collection_id,
3382                                 children_rec.child_occurrence);
3383                 END IF;
3384         END LOOP;
3385         --
3386         -- bug 7588376
3387         -- resetting the collection
3388         --
3389         parent_plan_vales_tab.delete;
3390         RETURN l_return_value;
3391 
3392 END update_all_children;
3393 
3394 
3395  FUNCTION applicable_child_plans_eqr( p_plan_id          IN NUMBER ,
3396                                         p_criteria_values  IN VARCHAR2)
3397                                         RETURN VARCHAR2 IS
3398 
3399  ret_flag VARCHAR2(10);
3400  child_plan_list VARCHAR2(1000);
3401 
3402  BEGIN
3403 
3404     ret_flag := evaluate_child_lov_criteria (p_plan_id, p_criteria_values,
3405                                              child_plan_list);
3406 
3407    RETURN child_plan_list;
3408 
3409 
3410  END applicable_child_plans_eqr;
3411 
3412  FUNCTION applicable_child_plans(p_plan_id            IN NUMBER,
3413                                    p_criteria_values    IN VARCHAR2)
3414       RETURN VARCHAR2
3415    IS
3416    --similar to evaluate_child_lov_criteria except no data_entry_mode
3417    -- restriction
3418       CURSOR c IS
3419           SELECT qpr.plan_relationship_id,
3420                  qpr.child_plan_id,
3421                  qpr.data_entry_mode
3422           FROM   qa_plans qp,
3423                  qa_pc_plan_relationship qpr
3424           WHERE  qpr.parent_plan_id = p_plan_id
3425           AND    qpr.child_plan_id = qp.plan_id
3426           AND    qpr.plan_relationship_type = 1
3427           AND ((qp.effective_to IS NULL AND TRUNC(SYSDATE) >= qp.effective_from)
3428                 OR (qp.effective_from IS NULL AND TRUNC(SYSDATE) <= qp.effective_to)
3429                 OR (qp.effective_from IS NOT NULL AND qp.effective_to IS NOT NULL
3430                     AND TRUNC(SYSDATE) BETWEEN qp.effective_from AND qp.effective_to)
3431                 OR (qp.effective_from IS NULL AND qp.effective_to IS NULL));
3432      l_separator             CONSTANT VARCHAR2(1) := '@';
3433      l_subseparator          CONSTANT VARCHAR2(1) := '=';
3434      l_child_plan_id         NUMBER;
3435      l_data_entry_mode       NUMBER;
3436      l_plan_relationship_id  NUMBER;
3437      l_childexist            BOOLEAN;
3438      l_return_string         VARCHAR2(4000);
3439      l_elements              qa_txn_grp.ElementsArray;
3440    BEGIN
3441       l_childexist := FALSE;
3442 
3443       l_elements := qa_txn_grp.result_to_array(p_criteria_values);
3444       OPEN c;
3445       LOOP
3446          FETCH c INTO l_plan_relationship_id, l_child_plan_id, l_data_entry_mode;
3447          IF (c%NOTFOUND) THEN
3448             EXIT;
3449          END IF;
3450 
3451          IF (qa_parent_child_pkg.criteria_matched(l_plan_relationship_id,
3452                                                   l_elements) = 'T') THEN
3453             IF (l_childexist) THEN
3454                l_return_string := l_return_string || l_separator
3455                                   || l_child_plan_id || l_subseparator
3456                                   || l_data_entry_mode;
3457             ELSE
3458                l_return_string := l_child_plan_id || l_subseparator
3459                                   || l_data_entry_mode;
3460                l_childexist := TRUE;
3461             END IF;
3462          END IF;
3463       END LOOP;
3464 
3465       CLOSE c;
3466       RETURN l_return_string;
3467    END;
3468 
3469 
3470 
3471  --anagarwa
3472  -- Bug 3195431
3473  -- only copy elements are context elements. So
3474  -- element_relationship type added to the cursor
3475  FUNCTION is_context_element( p_plan_id IN NUMBER ,
3476                               p_char_id IN NUMBER,
3477                               p_parent_plan_id IN NUMBER,
3478                               p_txn_or_child_flag IN NUMBER)
3479                                         RETURN VARCHAR2 IS
3480 
3481  CURSOR c IS SELECT 1
3482    FROM qa_pc_result_columns_v
3483    WHERE child_plan_id  = p_plan_id and
3484          child_char_id  = p_char_id and
3485          parent_plan_id = p_parent_plan_id and
3486          ELEMENT_RELATIONSHIP_TYPE = 1;
3487 
3488 
3489  l_context VARCHAR2(1);
3490  ret_val NUMBER;
3491 
3492 
3493  BEGIN
3494        l_context := 'N';
3495 
3496        OPEN c;
3497        FETCH c INTO ret_val;
3498        IF(c%NOTFOUND) THEN
3499          l_context := 'N';
3500        ELSIF ret_val = 1 THEN
3501          l_context := 'Y';
3502        END IF;
3503        CLOSE c;
3504 
3505        RETURN l_context;
3506 
3507  END is_context_element;
3508 
3509 
3510 
3511  FUNCTION get_parent_vo_attribute_name(p_child_char_id IN NUMBER,
3512                                        p_plan_id IN NUMBER)
3513                                         RETURN VARCHAR2 IS
3514 
3515  CURSOR c IS SELECT parent_char_id
3516    FROM qa_pc_result_columns_v
3517    WHERE parent_plan_id  = p_plan_id and
3518          child_char_id  = p_child_char_id and
3519          element_relationship_type = 1;
3520 
3521  l_parent_char_id NUMBER;
3522 
3523 
3524  BEGIN
3525 
3526        OPEN c;
3527        FETCH c INTO l_parent_char_id;
3528        IF(c%NOTFOUND) THEN
3529          CLOSE c;
3530          RETURN NULL;
3531        END IF;
3532        CLOSE c;
3533 
3534        RETURN qa_ak_mapping_api.get_vo_attribute_name(l_parent_char_id,
3535                                                       p_plan_id);
3536 
3537  END get_parent_vo_attribute_name;
3538 
3539  --
3540  -- bug 8417775
3541  -- overloaded the function to read the child plan id
3542  -- ntungare
3543  --
3544  FUNCTION get_parent_vo_attribute_name(p_child_char_id IN NUMBER,
3545                                        p_plan_id IN NUMBER,
3546                                        p_child_plan_id IN NUMBER)
3547                                         RETURN VARCHAR2 IS
3548 
3549  CURSOR c IS SELECT parent_char_id
3550    FROM qa_pc_result_columns_v
3551    WHERE parent_plan_id  = p_plan_id and
3552          child_plan_id   = p_child_plan_id and
3553          child_char_id  = p_child_char_id and
3554          element_relationship_type = 1;
3555 
3556  l_parent_char_id NUMBER;
3557 
3558 
3559  BEGIN
3560 
3561        OPEN c;
3562        FETCH c INTO l_parent_char_id;
3563        IF(c%NOTFOUND) THEN
3564          CLOSE c;
3565          RETURN NULL;
3566        END IF;
3567        CLOSE c;
3568 
3569        RETURN qa_ak_mapping_api.get_vo_attribute_name(l_parent_char_id,
3570                                                       p_plan_id);
3571 
3572  END get_parent_vo_attribute_name;
3573 
3574 
3575  FUNCTION get_layout_mode (p_parent_plan_id IN NUMBER,
3576                            p_child_plan_id IN NUMBER)
3577                         RETURN NUMBER IS
3578  CURSOR c is
3579         SELECT layout_mode
3580         FROM   qa_pc_plan_relationship
3581         WHERE  parent_plan_id = p_parent_plan_id
3582         AND    child_plan_id = p_child_plan_id;
3583 
3584  l_layout_mode NUMBER := 0;
3585 
3586  BEGIN
3587 
3588       OPEN c;
3589       FETCH c INTO l_layout_mode;
3590       IF(c%NOTFOUND) THEN
3591          CLOSE c;
3592          RETURN -1;
3593       END IF;
3594       CLOSE c;
3595       RETURN l_layout_mode;
3596 
3597  END get_layout_mode;
3598 
3599  FUNCTION ssqr_post_actions(p_txn_hdr_id IN NUMBER,
3600                             p_plan_id IN NUMBER,
3601                             p_transaction_number IN NUMBER,
3602                             x_sequence_string OUT NOCOPY VARCHAR2)
3603                            RETURN VARCHAR2 IS
3604 
3605  x_status VARCHAR2(10) ;
3606 
3607  BEGIN
3608 
3609      --initialize the sequence string to empty value
3610      x_sequence_string := '';
3611      x_status := '';
3612 
3613      QA_SEQUENCE_API.generate_seq_for_DDE(p_txn_hdr_id, p_plan_id,
3614                                           x_status, x_sequence_string);
3615 
3616 
3617      -- generate sequences
3618 
3619      -- call enable and fire actions
3620 
3621      IF p_transaction_number > 0 THEN
3622          -- do nothing in case of transaction.
3623         RETURN x_status;
3624      ELSE
3625          enable_fire_for_txn_hdr_id(p_txn_hdr_id);
3626          RETURN x_status;
3627      END IF;
3628 
3629  END;
3630  FUNCTION count_updated(p_plan_id IN NUMBER,
3631                         p_txn_header_id IN NUMBER) RETURN NUMBER IS
3632 ---
3633 --- Bug 3095436: Self Service Quality project
3634 --- Simple function to count the number of rows updated in a plan
3635 --- with a particular txn_header_id
3636 --- Used by the Plan Search VO
3637 ---
3638   cnt NUMBER;
3639 
3640   cursor c is
3641     select count(plan_id)
3642     from qa_results
3643     where plan_id = p_plan_id
3644     and txn_header_id = p_txn_header_id;
3645 
3646   BEGIN
3647     open c;
3648     fetch c into cnt;
3649     if (c%notfound) then
3650         return 0;
3651     else
3652         return cnt;
3653     end if;
3654     close c;
3655 
3656   END count_updated;
3657 
3658 FUNCTION get_vud_allowed ( p_plan_id IN NUMBER)
3659     RETURN VARCHAR2 IS
3660 ---
3661 --- Bug 3095436: Self Service Quality project
3662 --- Simple function to tell if the current user has privilege to
3663 --- view, update or delete results in a particular plan
3664 --- Used by the Plan Search VO
3665 ---
3666 
3667 BEGIN
3668 
3669     IF (qa_web_txn_api.allowed_for_plan('QA_RESULTS_VIEW', p_plan_id) = 'T') or
3670        (qa_web_txn_api.allowed_for_plan('QA_RESULTS_DELETE', p_plan_id) = 'T') or
3671        (qa_web_txn_api.allowed_for_plan('QA_RESULTS_UPDATE', p_plan_id) = 'T') THEN
3672       RETURN 'T';
3673     ELSE
3674       RETURN 'F';
3675     END IF;
3676 
3677 END get_vud_allowed;
3678 
3679  --12.1 QWB Usaibilty Improvements
3680  -- Overloaded this function so as to cause minimum
3681  -- impact to the existing code
3682  FUNCTION update_parent(p_parent_plan_id       IN NUMBER,
3683                         p_parent_collection_id IN NUMBER,
3684                         p_parent_occurrence    IN NUMBER,
3685                         p_child_plan_id        IN NUMBER,
3686                         p_child_collection_id  IN NUMBER,
3687                         p_child_occurrence     IN NUMBER,
3688                         p_child_txn_hdr_id     IN NUMBER)
3689         RETURN VARCHAR2 IS
3690     agg_elements VARCHAR2(4000);
3691     agg_val      VARCHAR2(4000);
3692  BEGIN
3693     return update_parent(
3694                        p_parent_plan_id,
3695                        p_parent_collection_id,
3696                        p_parent_occurrence,
3697                        p_child_plan_id,
3698                        p_child_collection_id,
3699                        p_child_occurrence,
3700                        p_child_txn_hdr_id,
3701                        agg_elements,
3702                        agg_val);
3703  END update_parent;
3704 
3705  -- anagarwa Fri Jan 23 12:10:04 PST 2004
3706  -- Bug 3384986 Actions for CAR master not fired when child is updated
3707  -- This is a copy of update_parent above with one extra param, txn_header_id
3708  -- In SSQR when we update the child record, then we call this to update parent
3709  -- and since now we would ike to fire background actions of parent, we update the
3710  -- txn_header_id too.
3711  -- NOTE: I did not modify the existing update_parent but duplicated the code
3712  -- because changing the parameters of existing procedure/function is strongly
3713  -- discouraged per Safe Spec Guide located at
3714  -- http://www-apps.us.oracle.com/%7Epwallack/SafeSpecs.htm
3715 
3716   -- Bug 4343758
3717   -- R12 OAF Txn Integration Project
3718   -- Added p_commit parameter since we do not want to commit by default
3719   -- If invoked from OAF Pages.
3720   -- shkalyan 05/13/2005.
3721  FUNCTION update_parent(p_parent_plan_id IN NUMBER,
3722                        p_parent_collection_id IN NUMBER,
3723                        p_parent_occurrence IN NUMBER,
3724                        p_child_plan_id IN NUMBER,
3725                        p_child_collection_id IN NUMBER,
3726                        p_child_occurrence IN NUMBER,
3727                        p_child_txn_hdr_id IN NUMBER,
3728                        x_agg_elements OUT NOCOPY VARCHAR2,
3729                        x_agg_val OUT NOCOPY VARCHAR2)
3730         RETURN VARCHAR2 IS
3731 
3732  l_sql_string VARCHAR2(32000);
3733  l_update_parent_sql VARCHAR2(32000);
3734  l_value NUMBER;
3735 
3736  -- anagarwa Mon Dec 16 16:55:09 PST 2002
3737  -- Bug 2701777
3738  -- added parent_enabled_flag and child_enabled_flag to where clause
3739  -- to limit working on onlly those elements that are enabled.
3740  CURSOR element_cursor IS
3741     SELECT parent_database_column,
3742            child_database_column,
3743            element_relationship_type,
3744            parent_char_id
3745     FROM   qa_pc_result_columns_v
3746     WHERE  parent_plan_id = p_parent_plan_id
3747     AND    child_plan_id = p_child_plan_id
3748     AND    element_relationship_type in (2,3,4,5,6,7,8)
3749     AND    parent_enabled_flag = 1
3750     AND    child_enabled_flag = 1;
3751 
3752 
3753  BEGIN
3754 
3755   FOR cur_rec IN element_cursor LOOP
3756 
3757       -- build the required sql string
3758 
3759       l_sql_string := 'FROM qa_results qr, qa_pc_results_relationship pc'
3760                     || ' WHERE qr.plan_id=pc.child_plan_id'
3761                     || ' AND qr.collection_id=pc.child_collection_id'
3762                     || ' AND qr.occurrence=pc.child_occurrence'
3763                     || ' AND pc.parent_occurrence= :p_parent_occurrence'
3764                     || ' AND pc.child_plan_id= :p_child_plan_id'
3765                     --
3766                     -- bug 5682448
3767                     -- Added the extra condititon to aggregate only the
3768                     -- enabled records in stauts 2 or NULL
3769                     -- ntungare Wed Feb 21 07:36:09 PST 2007
3770                     --
3771                     || ' AND (qr.status = 2 OR qr.status IS NULL)';
3772 
3773       -- Bug 2427337. Fix here is not related this bug. To use aggregate functions
3774       -- on a element which is stored in character col in qa_results table, we need
3775       -- to use to_number function, or else, unwanted value will be returned.
3776       -- rponnusa Tue Jun 25 06:15:48 PDT 2002
3777 
3778       IF (cur_rec.element_relationship_type = 2  ) THEN  -- sum
3779          l_sql_string := 'SELECT SUM(to_number(qr.'||cur_rec.child_database_column||')) ' || l_sql_string;
3780       ELSIF (cur_rec.element_relationship_type = 3 ) THEN  -- average or Mean
3781          l_sql_string := 'SELECT AVG(to_number(qr.'||cur_rec.child_database_column||')) ' || l_sql_string;
3782       ELSIF (cur_rec.element_relationship_type = 4 ) THEN -- std. deviation
3783          l_sql_string := 'SELECT STDDEV(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
3784 
3785       ELSIF (cur_rec.element_relationship_type = 5 ) THEN -- min
3786          l_sql_string := 'SELECT MIN(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
3787       ELSIF (cur_rec.element_relationship_type = 6 ) THEN -- max
3788          l_sql_string := 'SELECT MAX(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
3789       ELSIF (cur_rec.element_relationship_type = 7 ) THEN -- variance
3790          l_sql_string := 'SELECT VARIANCE(to_number(qr.'|| cur_rec.child_database_column||')) ' || l_sql_string;
3791       ELSIF (cur_rec.element_relationship_type = 8 ) THEN -- count
3792          -- anagarwa  Tue Feb 18 11:13:20 PST 2003
3793          -- Bug 2789847
3794          -- Count may be done on non numeric elements like Sequence Numbers and
3795          -- even Nonconformance Status, Source etc.
3796          -- A to_number will cause an exception in such a case and is hence
3797          -- removed from sql statement.
3798          l_sql_string := 'SELECT COUNT(qr.'|| cur_rec.child_database_column||') ' || l_sql_string;
3799       END IF;
3800       -- find out the aggregate value for the element in child plan.
3801       BEGIN
3802          EXECUTE IMMEDIATE l_sql_string INTO l_value
3803                  USING p_parent_occurrence,p_child_plan_id;
3804       EXCEPTION
3805         WHEN OTHERS THEN raise;
3806 
3807       END;
3808 
3809       -- Bug 2716973
3810       -- When the child aggregate relationship element value is updated to parent record,
3811       -- Post-Forms-Commit Trigger error raised if child element contain null value.
3812       -- rponnusa Sun Jan 12 23:59:07 PST 2003
3813 
3814       l_value := NVL(l_value,0);
3815 
3816       -- See 2624112
3817       -- The maximum allowed precision is now expanded to 12.
3818       -- Rounding to 12...
3819       -- rkunchal Thu Oct 17 22:51:45 PDT 2002
3820 
3821       -- rounding off to 6 digits is required since, for a number field, the maximum allowd
3822       -- decimal places is 6.
3823 
3824       -- l_value := round(l_value,6);
3825       l_value := round(l_value,12);
3826 
3827       -- now we need to update the parent record. Build the sql here.
3828 
3829       -- Bug 4270911. CU2 SQL Literal fix.TD #19
3830       -- Use bind variable for child txn hdr id.
3831       -- srhariha. Fri Apr 15 05:55:04 PDT 2005.
3832 
3833       l_update_parent_sql := 'UPDATE qa_results  SET '
3834                             || cur_rec.parent_database_column || ' = :l_value'
3835                             || ' ,txn_header_id = :p_child_txn_hdr_id'
3836                             || ' WHERE plan_id= :p_parent_plan_id'
3837                             || ' AND collection_id= :p_parent_collection_id'
3838                             || ' AND occurrence= :p_parent_occurrence';
3839       BEGIN
3840          EXECUTE IMMEDIATE l_update_parent_sql
3841                  USING l_value,p_child_txn_hdr_id,p_parent_plan_id,p_parent_collection_id,p_parent_occurrence;
3842 
3843          -- 12.1 QWB Usability improvements
3844          -- Building a list of the Aggregated parent plan elements
3845          --
3846          x_agg_elements := x_agg_elements ||','||
3847                            qa_ak_mapping_api.get_vo_attribute_name(cur_rec.parent_char_id, p_parent_plan_id);
3848          -- 12.1 QWB Usability improvements
3849          -- Building a list of the Aggregated values
3850          --
3851          x_agg_val := x_agg_val ||','|| l_value;
3852       EXCEPTION
3853         WHEN OTHERS THEN raise;
3854       END;
3855 
3856 
3857   END LOOP;
3858   -- we are returning true when the parent record is updated or
3859   -- there is no aggregate relationship defined for the parent,child plans.
3860 
3861   -- Bug 2300962. Needs explicit commit, if called from post-database-commit trigger
3862   -- bug 5306909
3863   -- Commenting this COMMIT as this Update_parent function
3864   -- with the Txn_header_id is called from QWB
3865   -- wherein the Commits are appropriately handled
3866   --  ntungare
3867   --
3868   -- COMMIT;
3869 
3870   RETURN 'T';
3871 
3872  END update_parent;
3873 
3874   -- Bug 3536025. Adding a new procedure insert_history_auto_rec_QWB,which will be
3875   -- called from qltssreb.pls (Quality Workbench). This procedure is very much
3876   -- similar to insert_history_auto_rec ,except this procedure doesnot changes
3877   -- the child plan's txn_header_id and doesnot fire actions for child plans.
3878   -- srhariha. Wed May 26 22:31:28 PDT 2004
3879 
3880 -- Bug 3681815.
3881 -- Removing the old procedure insert_history_auto_rec_QWB with the new code
3882 -- saugupta Tue, 15 Jun 2004 05:23:07 -0700 PDT
3883 --This procedure is similar to the insert_history_auto_rec but is
3884 --simplified for the needs of the SSQR post/update results processing.
3885 --The primary differences are that this procedure is limited to a single
3886 --parent row, the children have the same txn_header_id as the parent, and
3887 --the results are not enabled/don't have actions fired.  This
3888 --enabling/action firing is deferred to the ssqr_post_actions() method.
3889 --Instead, this procedure checks for children using the criteria and then
3890 --passes off to insert_automatic_records to actually create the child
3891 --result rows and relationship rows.
3892 --ilawler Thu Jun 10 17:24:08 2004
3893 
3894 PROCEDURE insert_history_auto_rec_QWB(p_plan_id           IN NUMBER,
3895                                       p_collection_id     IN NUMBER,
3896                                       p_occurrence        IN NUMBER,
3897                                       p_organization_id   IN NUMBER,
3898                                       p_txn_header_id     IN NUMBER,
3899                                       p_relationship_type IN NUMBER,
3900                                       p_data_entry_mode   IN NUMBER,
3901                                       x_status       OUT NOCOPY VARCHAR2) IS
3902 
3903 CURSOR child_check_cur(c_plan_id NUMBER) IS
3904        SELECT 'T'
3905        FROM qa_pc_plan_relationship
3906        WHERE parent_plan_id = c_plan_id
3907        AND plan_relationship_type = p_relationship_type
3908        AND data_entry_mode = p_data_entry_mode;
3909 
3910 l_status          VARCHAR2(1);
3911 l_criteria_values VARCHAR2(32000);
3912 l_child_plan_ids  VARCHAR2(10000);
3913 
3914 BEGIN
3915 --sanity check, make sure this plan has relevant children
3916 BEGIN
3917     OPEN child_check_cur(p_plan_id);
3918     FETCH child_check_cur INTO l_status;
3919     CLOSE child_check_cur;
3920 EXCEPTION
3921     WHEN OTHERS THEN
3922     l_status := 'F';
3923 END;
3924 
3925 IF (l_status <> 'T' OR l_status is NULL) THEN
3926   -- no child plans with type and entry mode provided
3927   RETURN;
3928 END IF;
3929 
3930 --check plan's values against child plans' criteria to get a list of
3931 --applicable children in l_child_plan_ids
3932 get_criteria_values(p_parent_plan_id       => p_plan_id,
3933                     p_parent_collection_id => p_collection_id,
3934                     p_parent_occurrence    => p_occurrence,
3935                     p_organization_id      => p_organization_id,
3936                     x_criteria_values      => l_criteria_values);
3937 
3938 l_status := evaluate_criteria(p_plan_id       => p_plan_id,
3939                               p_criteria_values   => l_criteria_values,
3940                               p_relationship_type => p_relationship_type,
3941                               p_data_entry_mode   => p_data_entry_mode,
3942                               x_child_plan_ids    => l_child_plan_ids);
3943 
3944 IF (l_status = 'T') THEN
3945 
3946   --when evaluate_criteria returns T, we have children that need to be
3947   --created so call insert_automatic_records to do the grunt child row
3948   --creation.
3949   insert_automatic_records(p_plan_id           => p_plan_id,
3950                            p_collection_id      => p_collection_id,
3951                            p_occurrence         => p_occurrence,
3952                            p_child_plan_ids     => l_child_plan_ids,
3953                            p_relationship_type  => p_relationship_type,
3954                            p_data_entry_mode    => p_data_entry_mode,
3955                            p_criteria_values    => l_criteria_values,
3956                            p_org_id             => p_organization_id,
3957                            p_spec_id            => null,
3958                            x_status             => l_status,
3959                            p_txn_header_id      => p_txn_header_id);
3960 
3961   --make sure the insert_automatic succeeded
3962   IF (l_status <> 'T') THEN
3963     x_status := l_status;
3964     RETURN;
3965   END IF;
3966 END IF;
3967 
3968 --don't worry about firing actions, this is handled in
3969 --ssqr_post_actions
3970 
3971 x_status := 'T';
3972 RETURN;
3973 
3974 END insert_history_auto_rec_QWB;
3975 
3976 -- The following procedure was added to remove the entry
3977 -- from QA_PC_RESULTS_RELATIONSHIP table when the user
3978 -- deletes the record from the child plan and saves the
3979 -- child plan. This procedure is called from procedure
3980 -- key_delete_dependent_rows in QLTRES.pld.
3981 -- Bug 3646166.suramasw.
3982 
3983 PROCEDURE DELETE_RELATIONSHIP_ROW(p_child_plan_id IN NUMBER,
3984                                   p_child_occurrence IN NUMBER) IS
3985 
3986 BEGIN
3987 
3988       DELETE FROM  qa_pc_results_relationship
3989              WHERE child_plan_id = p_child_plan_id
3990              AND   child_occurrence = p_child_occurrence;
3991 
3992 END;
3993 
3994   -- Bug 4343758
3995   -- R12 OAF Txn Integration Project
3996   -- Function to delete a Result Row and and it's parent child relationship
3997   -- shkalyan 05/13/2005.
3998   FUNCTION delete_row(
3999       p_plan_id          IN         NUMBER,
4000       p_collection_id    IN         NUMBER,
4001       p_occurrence       IN         NUMBER,
4002       p_enabled          IN         NUMBER := NULL) RETURN VARCHAR2
4003   IS
4004 
4005     l_api_name        CONSTANT VARCHAR2(30)   := 'DELETE_ROW';
4006     l_parent_plan_id           NUMBER;
4007     l_parent_collection_id     NUMBER;
4008     l_parent_occurrence        NUMBER;
4009 
4010     l_return_status            VARCHAR2(1);
4011 
4012   -- Bug 4343758. OA Framework Integration project.
4013   -- Cursor to fetch relationship details.
4014   -- srhariha. Tue May 24 22:56:13 PDT 2005.
4015 
4016   CURSOR c1 IS
4017        SELECT  parent_plan_id,
4018                parent_collection_id,
4019                parent_occurrence
4020        FROM    QA_PC_RESULTS_RELATIONSHIP
4021        WHERE   child_plan_id = p_plan_id
4022        AND     child_collection_id = p_collection_id
4023        AND     child_occurrence = p_occurrence;
4024 
4025     agg_elements VARCHAR2(4000);
4026     agg_val     VARCHAR2(4000);
4027 
4028   BEGIN
4029 
4030     IF ( FND_LOG.level_procedure >= FND_LOG.g_current_runtime_level ) THEN
4031        FND_LOG.string
4032        (
4033           FND_LOG.level_procedure,
4034           g_pkg_name || '.' || l_api_name,
4035           'ENTERING PROCEDURE: P_PLAN_ID: ' || p_plan_id || ' P_COLLECTION_ID: ' || p_collection_id || ' P_OCCURRENCE: ' || p_occurrence || ' P_ENABLED: ' || p_enabled
4036        );
4037     END IF;
4038 
4039     DELETE QA_RESULTS
4040     WHERE  occurrence = p_occurrence
4041     AND    plan_id = p_plan_id
4042     AND    collection_id = p_collection_id;
4043 
4044     IF ( FND_LOG.level_statement >= FND_LOG.g_current_runtime_level ) THEN
4045         FND_LOG.string
4046         (
4047           FND_LOG.level_statement,
4048           g_pkg_name || '.' || l_api_name,
4049           'DELETED ROW IN QA RESULTS. GETTING PARENT'
4050         );
4051     END IF;
4052 
4053     -- Bug 4343758. Oa Framework Integration project.
4054     -- Use cursor to fetch relationship details.
4055     -- srhariha. Tue May 24 22:56:13 PDT 2005.
4056     l_parent_plan_id := null;
4057 
4058     OPEN C1;
4059     FETCH C1 INTO l_parent_plan_id,l_parent_collection_id,l_parent_occurrence;
4060     CLOSE C1;
4061 
4062     IF ( l_parent_plan_id IS NOT NULL ) THEN
4063       IF ( FND_LOG.level_statement >= FND_LOG.g_current_runtime_level ) THEN
4064         FND_LOG.string
4065         (
4066           FND_LOG.level_statement,
4067           g_pkg_name || '.' || l_api_name,
4068           'BEFORE DELETING RELATIONSHIP ROW FOR CHILD'
4069         );
4070       END IF;
4071 
4072       delete_relationship_row
4073       (
4074         p_child_plan_id     => p_plan_id,
4075         p_child_occurrence  => p_occurrence
4076       );
4077 
4078       IF ( FND_LOG.level_statement >= FND_LOG.g_current_runtime_level ) THEN
4079         FND_LOG.string
4080         (
4081           FND_LOG.level_statement,
4082           g_pkg_name || '.' || l_api_name,
4083           'BEFORE UPDATING PARENT FOR AGGREGATION PLAN_ID: ' || l_parent_plan_id || ' COLLECTION_ID: ' || l_parent_collection_id || ' OCCURRENCE: ' || l_parent_occurrence || ' FOR AGGREGATION '
4084         );
4085       END IF;
4086 
4087       -- 12.1 QWB Usability Improvements
4088       -- Added 2 new parameters to get a list of Aggregated elements
4089       -- and their values
4090       --
4091       l_return_status :=
4092       aggregate_parent
4093       (
4094         p_parent_plan_id       => l_parent_plan_id,
4095         p_parent_collection_id => l_parent_collection_id,
4096         p_parent_occurrence    => l_parent_occurrence,
4097         p_child_plan_id        => p_plan_id,
4098         p_child_collection_id  => TO_NUMBER( NULL ),
4099         p_child_occurrence     => TO_NUMBER( NULL ),
4100         p_commit               => 'F',
4101         x_agg_elements         => agg_elements,
4102         x_agg_val              => agg_val
4103       );
4104     END IF;
4105 
4106     IF ( FND_LOG.level_procedure >= FND_LOG.g_current_runtime_level ) THEN
4107        FND_LOG.string
4108        (
4109           FND_LOG.level_procedure,
4110           g_pkg_name || '.' || l_api_name,
4111           'EXITING PROCEDURE: SUCCESS'
4112        );
4113     END IF;
4114 
4115     RETURN 'T';
4116 
4117   END delete_row;
4118 
4119 
4120    -- Bug 4345779. Audits Copy UI project.
4121    -- Code Review feedback incorporation. CR Ref 4.9.5, 4.9.6 and 4.9.7
4122    -- Modularization. Parent child API's must be defined in parent pkg.
4123    -- srhariha. Tue Jul 12 02:12:17 PDT 2005.
4124 
4125    --
4126    -- Parent-Child collections API. Operaters on collection of records.
4127    --
4128 
4129 
4130    -- Bug 4345779. Audits Copy UI project.
4131    -- Code Review feedback incorporation. CR Ref 4.10.1
4132    -- Using static SQL.
4133    -- srhariha. Thu Sep 29 00:09:40 PDT 2005.
4134 
4135 PROCEDURE create_relationship_for_coll
4136                              ( p_parent_plan_id NUMBER,
4137                                p_parent_collection_id NUMBER,
4138                                p_parent_occurrence NUMBER,
4139                                p_child_plan_id NUMBER,
4140                                p_child_collection_id NUMBER,
4141                                p_org_id NUMBER) IS
4142 
4143  l_sql_string VARCHAR2(1000);
4144 
4145    -- Bug 4345779. Audits Copy UI project.
4146    -- Code Review feedback incorporation. CR Ref 4.9.1
4147    -- l_api_name must be declared as constant.
4148    -- srhariha. Tue Jul 12 02:12:17 PDT 2005.
4149 
4150   l_api_name CONSTANT VARCHAR2(40) := 'CREATE_RELATIONSHIP ()';
4151 
4152 BEGIN
4153  INSERT INTO QA_PC_RESULTS_RELATIONSHIP (PARENT_PLAN_ID,
4154                                          PARENT_COLLECTION_ID,
4155                                          PARENT_OCCURRENCE,
4156                                          CHILD_PLAN_ID,
4157                                          CHILD_COLLECTION_ID,
4158                                          CHILD_OCCURRENCE,
4159                                          ENABLED_FLAG,
4160                                          LAST_UPDATE_DATE,
4161                                          LAST_UPDATED_BY,
4162                                          CREATION_DATE,
4163                                          CREATED_BY,
4164                                          LAST_UPDATE_LOGIN,
4165                                          CHILD_TXN_HEADER_ID)
4166                                   SELECT  p_parent_plan_id,
4167                                           p_parent_collection_id,
4168                                           p_parent_occurrence,
4169                                           QR.PLAN_ID,
4170                                           QR.COLLECTION_ID,
4171                                           QR.OCCURRENCE,
4172                                           2,
4173                                           SYSDATE,
4174                                           FND_GLOBAL.USER_ID,
4175                                           SYSDATE,
4176                                           FND_GLOBAL.USER_ID,
4177                                           FND_GLOBAL.USER_ID,
4178                                           QR.TXN_HEADER_ID
4179                                      FROM QA_RESULTS QR
4180                                     WHERE QR.PLAN_ID = p_child_plan_id
4181                                       AND QR.COLLECTION_ID = p_child_collection_id
4182                                       AND QR.ORGANIZATION_ID = p_org_id;
4183 
4184 
4185    EXCEPTION
4186 
4187       WHEN OTHERS THEN
4188        IF ( FND_MSG_PUB.Check_Msg_Level( FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR ) ) THEN
4189           FND_MSG_PUB.Add_Exc_Msg
4190           (
4191             p_pkg_name       => g_pkg_name,
4192             p_procedure_name => l_api_name,
4193             p_error_text     => SUBSTR(SQLERRM,1,240)
4194           );
4195         END IF;
4196 
4197         IF ( FND_LOG.level_procedure >= FND_LOG.g_current_runtime_level ) THEN
4198           FND_LOG.string
4199           (
4200             FND_LOG.level_procedure,
4201             g_pkg_name || '.' || l_api_name,
4202             'EXITING PROCEDURE: ERROR'
4203           );
4204         END IF;
4205 
4206         RAISE;
4207 
4208 END create_relationship_for_coll;
4209 
4210 
4211 PROCEDURE get_copy_result_cols(p_parent_plan_id NUMBER,
4212                                p_child_plan_id NUMBER,
4213                                x_parent_rc_str OUT NOCOPY VARCHAR2,
4214                                x_child_rc_str OUT NOCOPY VARCHAR2 ) IS
4215 
4216   CURSOR C IS
4217    SELECT qprc.parent_database_column,
4218           qprc.child_database_column
4219    FROM   qa_pc_result_columns_v qprc
4220   WHERE   qprc.parent_plan_id = p_parent_plan_id and
4221           qprc.child_plan_id = p_child_plan_id and
4222           qprc.element_relationship_type = 1 and
4223           parent_enabled_flag = 1 and
4224           child_enabled_flag = 1;
4225 
4226   p_rc DBMS_SQL.VARCHAR2_TABLE;
4227   c_rc DBMS_SQL.VARCHAR2_TABLE;
4228 
4229 
4230 BEGIN
4231 
4232    OPEN C;
4233    FETCH C BULK COLLECT INTO p_rc,c_rc;
4234    CLOSE C;
4235 
4236    if(p_rc is null OR c_rc is null) then
4237     return;
4238    end if;
4239 
4240 
4241    FOR i IN p_rc.FIRST .. p_rc.LAST LOOP
4242      x_parent_rc_str := x_parent_rc_str || p_rc(i);
4243      x_child_rc_str :=  x_child_rc_str || c_rc(i);
4244 
4245      IF (i <> p_rc.LAST) THEN
4246        x_parent_rc_str := x_parent_rc_str || ', ';
4247        x_child_rc_str :=  x_child_rc_str || ', ';
4248      END IF;
4249 
4250 
4251    END LOOP;
4252 
4253 
4254 
4255 END get_copy_result_cols;
4256 
4257 PROCEDURE copy_from_parent_for_coll
4258                            (p_parent_plan_id NUMBER,
4259                             p_parent_collection_id NUMBER,
4260                             p_parent_occurrence NUMBER,
4261                             p_child_plan_id NUMBER,
4262                             p_child_collection_id NUMBER,
4263                             p_org_id NUMBER) IS
4264 
4265  l_sql_string VARCHAR2(32000);
4266  l_src_string VARCHAR2(32000);
4267  l_dest_string VARCHAR2(32000);
4268    -- Bug 4345779. Audits Copy UI project.
4269    -- Code Review feedback incorporation. CR Ref 4.9.1
4270    -- l_api_name must be declared as constant.
4271    -- srhariha. Tue Jul 12 02:12:17 PDT 2005.
4272 
4273  l_api_name CONSTANT VARCHAR2(40) := 'COPY_FROM_PARENT_FOR_COLL';
4274 BEGIN
4275 
4276   -- get parent and child result column names
4277   get_copy_result_cols(p_parent_plan_id => p_parent_plan_id,
4278                        p_child_plan_id => p_child_plan_id,
4279                        x_parent_rc_str => l_src_string,
4280                        x_child_rc_str => l_dest_string);
4281 
4282   l_sql_string := ' UPDATE QA_RESULTS   '  ||
4283                   '  SET (  ' || l_dest_string || ' ) = ' ||
4284                  ' ( SELECT ' || l_src_string || ' ' ||
4285                   '  FROM QA_RESULTS QR1       ' ||
4286                   '  WHERE QR1.PLAN_ID = :1    ' ||
4287                   '  AND QR1.COLLECTION_ID = :2' ||
4288                   '  AND QR1.OCCURRENCE = :3)  ' ||
4289                 ' WHERE PLAN_ID = :4 '       ||
4290                 ' AND COLLECTION_ID = :5  ';
4291 
4292   EXECUTE IMMEDIATE l_sql_string USING p_parent_plan_id,
4293                                        p_parent_collection_id,
4294                                        p_parent_occurrence,
4295                                        p_child_plan_id,
4296                                        p_child_collection_id;
4297 
4298    EXCEPTION
4299 
4300       WHEN OTHERS THEN
4301        IF ( FND_MSG_PUB.Check_Msg_Level( FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR ) ) THEN
4302           FND_MSG_PUB.Add_Exc_Msg
4303           (
4304             p_pkg_name       => g_pkg_name,
4305             p_procedure_name => l_api_name,
4306             p_error_text     => SUBSTR(SQLERRM,1,240)
4307           );
4308         END IF;
4309 
4310         IF ( FND_LOG.level_procedure >= FND_LOG.g_current_runtime_level ) THEN
4311           FND_LOG.string
4312           (
4313             FND_LOG.level_procedure,
4314             g_pkg_name || '.' || l_api_name,
4315             'EXITING PROCEDURE: ERROR'
4316           );
4317         END IF;
4318 
4319         RAISE;
4320 END copy_from_parent_for_coll;
4321 
4322    -- Bug 4345779. Audits Copy UI project.
4323    -- Code Review feedback incorporation. CR Ref 4.10.2
4324    -- Rewriting the logic based on new interesting algo
4325    -- suggested by Bryan.
4326    -- srhariha. Thu Sep 29 00:09:40 PDT 2005.
4327 
4328  PROCEDURE create_history_for_coll (
4329              p_plan_id NUMBER,
4330              p_collection_id NUMBER,
4331              p_org_id NUMBER,
4332              p_txn_header_id NUMBER) IS
4333 
4334  l_sql_string VARCHAR2(32000);
4335 
4336 
4337  CURSOR c(x_plan_id NUMBER) IS
4338    SELECT child_plan_id
4339    FROM qa_pc_plan_relationship
4340    WHERE parent_plan_id = x_plan_id
4341    AND data_entry_mode = 4;
4342 
4343  l_src_string VARCHAR2(32000);
4344  l_dest_string VARCHAR2(32000);
4345    -- Bug 4345779. Audits Copy UI project.
4346    -- Code Review feedback incorporation. CR Ref 4.9.1
4347    -- l_api_name must be declared as constant.
4348    -- srhariha. Tue Jul 12 02:12:17 PDT 2005.
4349 
4350  l_api_name CONSTANT VARCHAR2(40) := 'CREATE_HISTORY';
4351 
4352  BEGIN
4353 
4354     -- get history plan id
4355 
4356     FOR hst_rec IN c(p_plan_id) LOOP
4357 
4358       INSERT INTO QA_PC_RESULTS_RELATIONSHIP (
4359                      PARENT_PLAN_ID,
4360                      PARENT_COLLECTION_ID,
4361                      PARENT_OCCURRENCE,
4362                      CHILD_PLAN_ID ,
4363                      CHILD_COLLECTION_ID,
4364                      CHILD_OCCURRENCE,
4365                      ENABLED_FLAG,
4366                      LAST_UPDATE_DATE,
4367                      LAST_UPDATED_BY,
4368                      CREATION_DATE,
4369                      CREATED_BY ,
4370                      LAST_UPDATE_LOGIN,
4371                      CHILD_TXN_HEADER_ID)
4372               SELECT QR.PLAN_ID,
4373                      QR.COLLECTION_ID,
4374                      QR.OCCURRENCE,
4375                      hst_rec.child_plan_id,
4376                      p_collection_id,
4377                      QA_OCCURRENCE_S.NEXTVAL,
4378                      2,
4379                      SYSDATE,
4380                      FND_GLOBAL.USER_ID,
4381                      SYSDATE,
4382                      FND_GLOBAL.USER_ID,
4383                      FND_GLOBAL.USER_ID,
4384                      p_txn_header_id
4385                 FROM QA_RESULTS QR
4386                WHERE QR.PLAN_ID = p_plan_id
4387                  AND QR.COLLECTION_ID = p_collection_id
4388                  AND QR.ORGANIZATION_ID = p_org_id;
4389 
4390 
4391 
4392       -- get parent and child result column names
4393       get_copy_result_cols(p_parent_plan_id => p_plan_id,
4394                            p_child_plan_id => hst_rec.child_plan_id,
4395                            x_parent_rc_str => l_src_string,
4396                            x_child_rc_str => l_dest_string);
4397 
4398 
4399     l_sql_string := ' INSERT INTO qa_results (     collection_id, ' ||
4400                                                 '  occurrence,  ' ||
4401                                                 '  last_update_date, ' ||
4402                                                 '  qa_last_update_date, '||
4403                                                 '  last_updated_by, ' ||
4404                                                 '  qa_last_updated_by, ' ||
4405                                                 '  creation_date,  ' ||
4406                                                 '  qa_creation_date, ' ||
4407                                                 '  created_by, ' ||
4408                                                 '  last_update_login, ' ||
4409                                                 '  qa_created_by, ' ||
4410                                                 '  status, ' ||
4411                                                 '  transaction_number, ' ||
4412                                                 '  organization_id, ' ||
4413                                                 '  plan_id, ' ||
4414                                                 '  txn_header_id, ' ||
4415                                                 l_dest_string || ')' ||
4416                                         ' SELECT   QPRR.CHILD_COLLECTION_ID,  ' ||
4417                                              '     QPRR.CHILD_OCCURRENCE, ' ||
4418                                              '     sysdate, ' ||
4419                                              '     sysdate, ' ||
4420                                              '     fnd_global.user_id, ' ||
4421                                              '     fnd_global.user_id, ' ||
4422                                              '     sysdate, ' ||
4423                                              '     sysdate, ' ||
4424                                              '     fnd_global.user_id, ' ||
4425                                              '     fnd_global.user_id, ' ||
4426                                              '     fnd_global.user_id, ' ||
4427                                              '     2, ' ||
4428                                              '     -1, ' ||
4429                                              '     QR.ORGANIZATION_ID, ' ||
4430                                              '     QPRR.CHILD_PLAN_ID, ' ||
4431                                              '     QPRR.CHILD_TXN_HEADER_ID,  ' ||
4432                                              l_src_string || ' ' ||
4433                                        ' FROM  QA_RESULTS QR, QA_PC_RESULTS_RELATIONSHIP QPRR ' ||
4434                                        ' WHERE QPRR.CHILD_PLAN_ID = :1 ' ||
4435                                        ' AND QPRR.CHILD_COLLECTION_ID = :2 ' ||
4436                                        ' AND QPRR.PARENT_PLAN_ID = :3 ' ||
4437                                        ' AND QPRR.PARENT_COLLECTION_ID = :4 ' ||
4438                                        ' AND QPRR.PARENT_OCCURRENCE = QR.OCCURRENCE ';
4439 
4440     EXECUTE IMMEDIATE l_sql_string USING hst_rec.child_plan_id,
4441                                          p_collection_id,
4442                                          p_plan_id,
4443                                          p_collection_id;
4444 
4445 
4446 
4447   END LOOP; -- hst_rec
4448 
4449      EXCEPTION
4450 
4451       WHEN OTHERS THEN
4452        IF ( FND_MSG_PUB.Check_Msg_Level( FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR ) ) THEN
4453           FND_MSG_PUB.Add_Exc_Msg
4454           (
4455             p_pkg_name       => g_pkg_name,
4456             p_procedure_name => l_api_name,
4457             p_error_text     => SUBSTR(SQLERRM,1,240)
4458           );
4459         END IF;
4460 
4461         IF ( FND_LOG.level_procedure >= FND_LOG.g_current_runtime_level ) THEN
4462           FND_LOG.string
4463           (
4464             FND_LOG.level_procedure,
4465             g_pkg_name || '.' || l_api_name,
4466             'EXITING PROCEDURE: ERROR'
4467           );
4468         END IF;
4469 
4470         RAISE;
4471 
4472 
4473  END create_history_for_coll;
4474 
4475 
4476  -- Bug 4502450. R12 Esig Status support in Multirow UQR
4477  -- saugupta Wed, 24 Aug 2005 08:40:56 -0700 PDT
4478 
4479  -- Function returns only all ancestors i.e parent and grandparent plan rows
4480  -- for a given child plan and does not retrun child itself.
4481  FUNCTION get_ancestors( p_child_plan_id IN NUMBER,
4482                           p_child_occurrence IN NUMBER,
4483                           p_child_collection_id IN NUMBER,
4484                           x_parent_plan_ids          OUT NOCOPY dbms_sql.number_table,
4485                           x_parent_collection_ids    OUT NOCOPY dbms_sql.number_table,
4486                           x_parent_occurrences       OUT NOCOPY dbms_sql.number_table)
4487  RETURN VARCHAR2
4488  IS
4489 
4490  BEGIN
4491       -- check for NULL values
4492       IF( p_child_plan_id IS NULL OR
4493           p_child_occurrence IS NULL OR
4494           p_child_collection_id IS NULL) THEN
4495           -- return False
4496           RETURN 'F';
4497       END IF;
4498 
4499       -- Given a child occurrence this query finds all the parents
4500       -- and grandparent records, therefore ancestors, of the child record.
4501       -- These are returned in the three output PL/SQL tables.
4502       -- The child record itself is not included in the output.
4503       SELECT parent_plan_id, parent_collection_id, parent_occurrence
4504       BULK COLLECT INTO x_parent_plan_ids, x_parent_collection_ids, x_parent_occurrences
4505       FROM qa_pc_results_relationship
4506       START WITH child_plan_id = p_child_plan_id
4507             AND child_occurrence = p_child_occurrence
4508             AND child_collection_id = p_child_collection_id
4509       CONNECT BY PRIOR  parent_occurrence = child_occurrence;
4510 
4511       IF (SQL%FOUND) THEN
4512         RETURN 'T';
4513       ELSE
4514         RETURN 'F';
4515       END IF;
4516 
4517 
4518  END get_ancestors;
4519 
4520  --
4521  -- Bug 5435657
4522  -- New procedure to update the Aggregate values on
4523  -- all the ancestors of the plan_id passed, in case
4524  -- such a P-C relationship exists
4525  -- ntungare Wed Aug  2 20:53:40 PDT 2006
4526  --
4527  PROCEDURE update_all_ancestors(p_parent_plan_id       IN NUMBER,
4528                                 p_parent_collection_id IN NUMBER,
4529                                 p_parent_occurrence    IN NUMBER) IS
4530 
4531      l_parent_plan_id_tab       DBMS_SQL.NUMBER_TABLE;
4532      l_parent_collection_id_tab DBMS_SQL.NUMBER_TABLE;
4533      l_parent_occurrence_tab    DBMS_SQL.NUMBER_TABLE;
4534 
4535      l_current_child_planid   NUMBER;
4536      l_current_child_collid   NUMBER;
4537      l_current_child_occrid   NUMBER;
4538      l_current_parent_planid  NUMBER;
4539      l_current_parent_collid  NUMBER;
4540      l_current_parent_occrid  NUMBER;
4541 
4542  BEGIN
4543      -- Calling the function get_ancestors to get a
4544      -- List of the Ancestors if they exist
4545      IF ( QA_PARENT_CHILD_PKG.get_ancestors(
4546              p_parent_plan_id,
4547              p_parent_occurrence,
4548              p_parent_collection_id,
4549              l_parent_plan_id_tab,
4550              l_parent_collection_id_tab,
4551              l_parent_occurrence_tab) = 'T') THEN
4552 
4553        l_current_child_planid := p_parent_plan_id;
4554        l_current_child_collid := p_parent_collection_id;
4555        l_current_child_occrid := p_parent_occurrence;
4556 
4557        -- Ancestors exist for the plan_id passed so
4558        -- Need to check if an aggregate P-C relationship
4559        -- exists and do the aggregation
4560        -- Looping through all the ancestors
4561        For ancestors_cntr in 1..l_parent_plan_id_tab.COUNT
4562          LOOP
4563             l_current_parent_planid := l_parent_plan_id_tab(ancestors_cntr);
4564             l_current_parent_collid := l_parent_collection_id_tab(ancestors_cntr);
4565             l_current_parent_occrid := l_parent_occurrence_tab(ancestors_cntr);
4566 
4567             -- Calling the procedure to check for aggregate relationships
4568             -- and do the agrregation
4569             IF(QA_PARENT_CHILD_PKG.update_parent
4570                             (l_current_parent_planid,
4571                              l_current_parent_collid,
4572                              l_current_parent_occrid,
4573                              l_current_child_planid,
4574                              l_current_child_collid,
4575                              l_current_child_occrid)='T')
4576             THEN
4577                NULL;
4578             END IF;
4579 
4580             -- Assigning the Current Parrent plan Id, Collection Id
4581             -- and the occurrences as the Child plan Plan id,
4582             -- Collcetion Id and occurrences, for the next round of
4583             -- processing of the ancestors collection
4584             --
4585             l_current_child_planid := l_current_parent_planid;
4586             l_current_child_collid := l_current_parent_collid;
4587             l_current_child_occrid := l_current_parent_occrid;
4588          END LOOP; -- End of Ancestors Loop
4589 
4590      END If; -- End of If ancestors Found
4591  END update_all_ancestors;
4592 
4593  --
4594  -- bug 6134920
4595  -- Added a new procedure to delete all the status
4596  -- 1 invalid child records, generated during an
4597  -- incomplete txn
4598  -- ntungare Tue Jul 10 23:08:22 PDT 2007
4599  --
4600  PROCEDURE delete_invalid_children(p_txn_header_id IN NUMBER) IS
4601      PRAGMA AUTONOMOUS_TRANSACTION;
4602 
4603      TYPE child_plan_id_tab_typ IS TABLE OF qa_pc_results_relationship.child_plan_id%TYPE
4604                                                                  INDEX BY BINARY_INTEGER;
4605      TYPE child_collection_id_tab_typ IS TABLE OF qa_pc_results_relationship.child_collection_id%TYPE
4606                                                                  INDEX BY BINARY_INTEGER;
4607      TYPE child_occurrence_tab_typ IS TABLE OF qa_pc_results_relationship.child_occurrence%TYPE
4608                                                                  INDEX BY BINARY_INTEGER;
4609 
4610      child_plan_id_tab       child_plan_id_tab_typ;
4611      child_collection_id_tab child_collection_id_tab_typ;
4612      child_occurrence_tab    child_occurrence_tab_typ;
4613 
4614  BEGIN
4615      DELETE FROM qa_results
4616        WHERE txn_header_id = p_txn_header_id
4617          AND status        = 1
4618      RETURNING plan_id, collection_id, occurrence
4619        BULK COLLECT INTO child_plan_id_tab,
4620                          child_collection_id_tab,
4621                          child_occurrence_tab;
4622 
4623      FORALL cntr in 1..child_plan_id_tab.COUNT
4624        DELETE from qa_pc_results_relationship
4625          WHERE child_txn_header_id = p_txn_header_id
4626            AND child_plan_id       = child_plan_id_tab(cntr)
4627            AND child_collection_id = child_collection_id_tab(cntr)
4628            AND child_occurrence    = child_occurrence_tab(cntr);
4629 
4630      COMMIT;
4631  END delete_invalid_children;
4632 
4633 -- 12.1 QWB Usability Improvements
4634 -- New method to check if a Parent Plan record
4635 -- has any applicable child plan into which data can be
4636 -- entered.
4637 --
4638 FUNCTION has_enterable_child(p_plan_id in number,
4639                              p_collection_id in number,
4640                              p_occurrence in number)
4641  RETURN varchar2 as
4642    TYPE plan_det IS RECORD (char_id      varchar2(200),
4643                             res_col_name varchar2(200)) ;
4644 
4645    TYPE res_col_tab_typ IS TABLE OF plan_det INDEX BY binary_integer;
4646    res_col_tab res_col_tab_typ;
4647    str varchar2(32767);
4648    result_string varchar2(32767);
4649    -- Bug 9382356
4650    -- New variable to hold the result string for Comments type elements.
4651    -- skolluku
4652    comments_result_string varchar2(4000);
4653    plans qa_txn_grp.ElementsArray;
4654 
4655    cntr NUMBER;
4656 BEGIN
4657    -- Getting the list of the result_column_names from the
4658    -- qa_plan_chars table
4659    SELECT char_id, result_column_name
4660     BULK COLLECT INTO res_col_tab
4661    FROM qa_plan_chars
4662     WHERE plan_id = p_plan_id;
4663 
4664    -- building the select query
4665    FOR cntr in 1..res_col_tab.count
4666      LOOP
4667        -- Bug 9382356
4668        -- Do this loop only for Non-Comments type elements. Comments processing comes later.
4669        -- skolluku
4670        IF res_col_tab(cntr).res_col_name NOT LIKE 'COMMENT%' THEN
4671         str := res_col_tab(cntr).char_id ||
4672 	       '=''||REPLACE('||res_col_tab(cntr).res_col_name||
4673                ',''@'',''@@'')||''@'||str;
4674        END IF;
4675      END LOOP;
4676    str := rtrim(str, '||''@');
4677 
4678    -- Use the columns list built above to query
4679    -- qa_results table, to build the result_string
4680    -- Bug 9382356
4681    -- Added NULL check as this would error out in case there
4682    -- is only COMMENTS element in the plan.
4683    -- skolluku
4684    IF str IS NOT NULL THEN
4685    EXECUTE IMMEDIATE
4686    'Select '''||str||
4687    ' from qa_results where plan_id = :plan_id  and
4688           collection_id = :collection_id and
4689           occurrence = :occurrence'
4690      INTO result_string USING p_plan_id,
4691                               p_collection_id ,
4692                               p_occurrence;
4693     END IF;
4694     -- Bug 9382356
4695     -- Iterating through the loop again. This time only Comments elements will be picked.
4696     -- If present, the result string for the Comments element is created and appended to
4697     -- the existing result string. This had to be done, as if the result string is greater
4698     -- than 4000 in case there are Comments elements, the Execute Immediate fails, due to
4699     -- SQL limitation.
4700     -- skolluku
4701     FOR cntr in 1..res_col_tab.count
4702      LOOP
4703        IF res_col_tab(cntr).res_col_name LIKE 'COMMENT%' THEN
4704            str := res_col_tab(cntr).char_id ||
4705 	              '=''||REPLACE('||res_col_tab(cntr).res_col_name||
4706                   ',''@'',''@@'')';
4707            EXECUTE IMMEDIATE
4708                'Select '''||str||
4709                ' from qa_results where plan_id = :plan_id  and
4710                  collection_id = :collection_id and
4711                  occurrence = :occurrence'
4712            INTO comments_result_string USING p_plan_id,
4713                                              p_collection_id ,
4714                                              p_occurrence;
4715            IF result_string IS NOT NULL THEN
4716               result_string := result_string || '@' || comments_result_string;
4717            ELSE
4718               result_string := comments_result_string;
4719            END IF;
4720        END IF;
4721     END LOOP;
4722 
4723    -- Pass the result string to the applicable_child_plans
4724    -- to get a list of applicable Child plans for the entered data
4725    -- and convert the list of plans returned as a string
4726    -- into an array
4727    plans :=  qa_txn_grp.result_to_array(
4728                 qa_parent_child_pkg.applicable_child_plans(p_plan_id,
4729                                                            result_string));
4730 
4731    cntr := plans.first;
4732 
4733    -- looping through the child plans list to check
4734    -- if there is any non History child plan
4735    WHILE cntr <= plans.LAST
4736     LOOP
4737       IF plans(cntr).VALUE <>4 THEN
4738         -- bug 14773742
4739         -- Check if child plan has security access
4740         --
4741         IF  QA_WEB_TXN_API.ALLOWED_FOR_PLAN('QA_RESULTS_ENTER', cntr) <> 'F' THEN
4742             RETURN 'CHILD_Y';
4743         END IF;
4744       END IF;
4745       cntr := plans.next(cntr);
4746     END LOOP;
4747     RETURN 'CHILD_N';
4748 END has_enterable_child;
4749 
4750 -- 12.1 QWB Usability Improvements
4751 -- New method to check if there aare any updatable child records
4752 --
4753 FUNCTION child_exists_for_update(p_plan_id       IN NUMBER,
4754                                  p_collection_id IN NUMBER,
4755                                  p_occurrence    IN NUMBER)
4756   RETURN VARCHAR2 AS
4757   --
4758   -- removed the Immediate plans check
4759   -- ntungare
4760   --
4761   CURSOR cur is
4762      select 'UPDATE_CHILD_Y'
4763        from qa_pc_results_relationship qpc,
4764             qa_results qr,
4765             qa_pc_plan_relationship qpr
4766        where qpc.parent_plan_id = p_plan_id             and
4767              qpc.parent_collection_id = p_collection_id and
4768              qpc.parent_occurrence  = p_occurrence      and
4769              qpc.child_plan_id = qr.plan_id             and
4770              qpc.child_collection_id = qr.collection_id and
4771              qpc.child_occurrence = qr.occurrence       and
4772              (qr.status = 2 or qr.status is NULL)       and
4773              qpr.parent_plan_id = p_plan_id             and
4774              qpr.child_plan_id = qpc.child_plan_id      and
4775              qpr.data_entry_mode  <> 4                  and
4776              qa_web_txn_api.allowed_for_plan('QA_RESULTS_UPDATE', qpc.child_plan_id) = 'T';
4777              --rownum =1;
4778 
4779   has_child VARCHAR2(100) :='UPDATE_CHILD_N';
4780 BEGIN
4781   /*
4782     This procedure has a bit of a complexity in the form that if the
4783     Criteria defined for the P-C relationship is changed later, then
4784     the child data that has already been collected would be no longer
4785     be applicable, in which case the child records though present in
4786     the relationship table should be ignored. For this we need to
4787     make a call to the "has_enterable" procedure to check for the
4788     applicable children, which would be a severe overhead. A better
4789     way is to prevent the user from changing the criteria if Child
4790     records that match the criteria have already been collected.
4791   */
4792   OPEN cur;
4793   FETCH cur INTO has_child;
4794   CLOSE cur;
4795 
4796   RETURN has_child;
4797 END child_exists_for_update;
4798 
4799 -- 12.1 QWB usability Improvements
4800 -- New method to get a count of child records
4801 -- present for any parent plan record
4802 --
4803 FUNCTION getChildCount(p_plan_id       IN NUMBER,
4804                        p_collection_id IN NUMBER,
4805                        p_occurrence    IN NUMBER)
4806   RETURN NUMBER AS
4807 
4808   childCount NUMBER := 0;
4809 BEGIN
4810   SELECT count(*) INTO childCount
4811    FROM qa_pc_results_relationship qpc,
4812         qa_results qr
4813    WHERE qpc.parent_plan_id = p_plan_id             and
4814          qpc.parent_collection_id = p_collection_id and
4815          qpc.parent_occurrence  = p_occurrence      and
4816          qpc.child_plan_id = qr.plan_id             and
4817          qpc.child_collection_id = qr.collection_id and
4818          qpc.child_occurrence = qr.occurrence       and
4819         (qr.status = 2 or qr.status is NULL);
4820 
4821   RETURN childCount;
4822 end getChildCount;
4823 
4824 -- 12.1 Quality Inline Transaction INtegration
4825 -- New method to identify whether a plan has
4826 -- child plans associated with it or not
4827 --
4828 FUNCTION has_child(p_plan_id IN NUMBER)
4829   RETURN INTEGER AS
4830 
4831   childCount NUMBER;
4832 BEGIN
4833   SELECT count(*) INTO childCount
4834    FROM qa_pc_plan_relationship
4835    WHERE parent_plan_id=p_plan_id;
4836   IF childCount > 0 THEN
4837     RETURN 1;
4838   ELSE
4839     RETURN 2;
4840   END IF;
4841 END has_child;
4842 
4843 -- 12.1 QWB Usability Improvements project
4844 -- Function to update all the History
4845 -- Child records corresponding to a parent record
4846 FUNCTION update_hist_children(p_parent_plan_id IN NUMBER,
4847                        p_parent_collection_id IN NUMBER,
4848                        p_parent_occurrence IN NUMBER)
4849         RETURN VARCHAR2 IS
4850 
4851   l_return_value  VARCHAR2(1);
4852   l_dummy VARCHAR2(1);
4853 
4854   CURSOR children_cur IS
4855         select qprr.child_plan_id,
4856                qprr.child_collection_id,
4857                qprr.child_occurrence
4858         from   qa_pc_results_relationship qprr,
4859                qa_pc_plan_relationship    qpr
4860         where  qprr.parent_occurrence = p_parent_occurrence
4861         and    qprr.parent_plan_id = p_parent_plan_id
4862         and    qprr.parent_collection_id = p_parent_collection_id
4863         and    qpr.parent_plan_id = qprr.parent_plan_id
4864         and    qpr.child_plan_id = qprr.child_plan_id
4865         and    qpr.data_entry_mode = 4;
4866 
4867 BEGIN
4868     l_return_value := 'T';
4869     l_dummy := 'T';
4870 
4871         FOR children_rec IN children_cur
4872         LOOP
4873            l_return_value :=
4874                   update_child (  p_parent_plan_id,
4875                           p_parent_collection_id,
4876                           p_parent_occurrence,
4877                           children_rec.child_plan_id,
4878                           children_rec.child_collection_id,
4879                           children_rec.child_occurrence);
4880         END LOOP;
4881 
4882         RETURN l_return_value;
4883 END update_hist_children;
4884 
4885 -- Bug 7436465.FP for Bug 7035041.pdube Fri Sep 26 03:46:20 PDT 2008
4886 -- Inroduced this procedure to check if any child record exists for parent record.
4887 FUNCTION IF_CHILD_RECORD_EXISTS( p_plan_id IN NUMBER,
4888                                  p_collection_id IN NUMBER,
4889                                  p_occurrence IN NUMBER) RETURN result_column_name_tab_typ IS
4890   result_column_name_tab result_column_name_tab_typ;
4891 BEGIN
4892   SELECT REPLACE(DECODE(QC.HARDCODED_COLUMN, NULL ,QAPC.RESULT_COLUMN_NAME,QC.DEVELOPER_NAME),
4893                         'CHARACTER','DISPLAY') FORM_FIELD
4894        BULK COLLECT INTO  result_column_name_tab
4895   FROM qa_pc_plan_relationship qppr,
4896        qa_pc_criteria qpc,
4897        qa_results qr,
4898        qa_plan_chars qapc,
4899        qa_chars qc
4900   WHERE qpc.plan_relationship_id = qppr.plan_relationship_id
4901   AND   qapc.char_id = qpc.char_id
4902   AND   qapc.char_id = qc.char_id
4903   AND   qr.occurrence =  p_occurrence
4904   AND   qr.collection_id = p_collection_id
4905   AND   qr.plan_id = p_plan_id
4906   AND   qr.plan_id = qapc.plan_id
4907   AND   qppr.parent_plan_id = qr.plan_id
4908   AND EXISTS
4909  (SELECT 1 FROM
4910    qa_pc_results_relationship qprr
4911    WHERE qppr.child_plan_id = qprr.child_plan_id
4912    AND   qppr.parent_plan_id = qprr.parent_plan_id
4913    AND   qppr.child_plan_id = qprr.child_plan_id
4914    AND  qprr.parent_plan_id = qr.plan_id
4915    AND  qprr.parent_collection_id = p_collection_id
4916    AND  qprr.parent_occurrence = p_occurrence
4917    AND  qprr.parent_plan_id = p_plan_id
4918    AND  ROWNUM = 1);
4919 
4920    RETURN result_column_name_tab;
4921  EXCEPTION
4922     WHEN OTHERS THEN
4923     RAISE;
4924     RETURN result_column_name_tab;
4925  END IF_CHILD_RECORD_EXISTS;
4926 
4927  --
4928  -- Bug 13970715
4929  -- add new function to get hardcoded column of parent element
4930  -- based on child element to which parent value is being copied.
4931  -- hmakam
4932  --
4933 
4934  FUNCTION get_parent_hardcoded_column(p_child_char_id IN NUMBER,
4935                                        p_plan_id IN NUMBER,
4936                                        p_child_plan_id IN NUMBER)
4937                                         RETURN VARCHAR2 IS
4938 
4939  CURSOR c IS SELECT parent_database_column
4940    FROM qa_pc_result_columns_v
4941    WHERE parent_plan_id  = p_plan_id and
4942          child_plan_id   = p_child_plan_id and
4943          child_char_id  = p_child_char_id and
4944          element_relationship_type = 1;
4945 
4946  l_parent_database_column VARCHAR2(300);
4947 
4948 
4949  BEGIN
4950 
4951        OPEN c;
4952        FETCH c INTO l_parent_database_column;
4953        IF(c%NOTFOUND) THEN
4954          CLOSE c;
4955          RETURN NULL;
4956        END IF;
4957        CLOSE c;
4958 
4959        RETURN l_parent_database_column;
4960 
4961  END get_parent_hardcoded_column;
4962 
4963 END  QA_PARENT_CHILD_PKG;