DBA Data[Home] [Help]

PACKAGE BODY: APPS.QA_CHAR_INDEXES_PKG

Source


1 PACKAGE BODY qa_char_indexes_pkg AS
2 /* $Header: qaindexb.pls 120.2 2011/06/13 08:04:42 ntungare noship $ */
3 
4     -- A constant to fool GSCC.  See bug 3554899
5     -- Copied from qltvcreb
6     -- bso Wed Apr  7 22:27:11 PDT 2004
7     g_period CONSTANT VARCHAR2(1) := '.';
8 
9     --
10     -- Apps schema info
11     --
12     g_dummy           BOOLEAN;
13     g_fnd             CONSTANT VARCHAR2(3) := 'FND';
14     g_fnd_schema      VARCHAR2(30);
15     g_qa              CONSTANT VARCHAR2(3) := 'QA';
16     g_qa_schema       VARCHAR2(30);
17     g_status          VARCHAR2(1);
18     g_industry        VARCHAR2(10);
19 
20     --
21     -- Standard who columns.
22     --
23     who_user_id                 CONSTANT NUMBER := fnd_global.conc_login_id;
24     who_request_id              CONSTANT NUMBER := fnd_global.conc_request_id;
25     who_program_id              CONSTANT NUMBER := fnd_global.conc_program_id;
26     who_program_application_id  CONSTANT NUMBER := fnd_global.prog_appl_id;
27 
28 
29     CURSOR c_enabled(p_char_id NUMBER) IS
30         SELECT enabled_flag
31         FROM   qa_char_indexes
32         WHERE  char_id = p_char_id;
33 
34 
35     FUNCTION index_exists(p_char_id NUMBER)
36         RETURN INTEGER IS
37 
38     --
39     -- Return 1 if index exists for p_char_id.  0 otherwise.
40     --
41         l NUMBER;
42 
43     BEGIN
44 
45         OPEN c_enabled(p_char_id);
46         FETCH c_enabled INTO l;
47         IF c_enabled%NOTFOUND THEN
48             CLOSE c_enabled;
49             RETURN 0;
50         END IF;
51 
52         CLOSE c_enabled;
53         RETURN 1;
54 
55     END index_exists;
56 
57 
58     FUNCTION index_exists_and_enabled(p_char_id NUMBER)
59         RETURN INTEGER IS
60 
61     --
62     -- Return 1 if index exists and enabled for p_char_id.  0 otherwise.
63     --
64 
65         l NUMBER;
66 
67     BEGIN
68         OPEN c_enabled(p_char_id);
69         FETCH c_enabled INTO l;
70         IF c_enabled%NOTFOUND THEN
71             CLOSE c_enabled;
72             RETURN 0;
73         END IF;
74 
75         CLOSE c_enabled;
76         IF l = 1 THEN
77             RETURN 1;
78         ELSE
79             RETURN 0;
80         END IF;
81 
82     END index_exists_and_enabled;
83 
84 
85     FUNCTION get_default_result_column(p_char_id NUMBER)
86         RETURN VARCHAR2 IS
87 
88     --
89     -- Return the default result column name of an index (that is
90     -- the final parameter in the decode function.
91     -- If no index exists or the index is disabled, this function
92     -- returns NULL.  Caller can use this function to test for
93     -- the enable/disable status also.  Just test to see if the
94     -- return value is NULL or not.
95     --
96 
97         CURSOR c IS
98             SELECT default_result_column
99             FROM   qa_char_indexes
100             WHERE  char_id = p_char_id AND enabled_flag = 1;
101 
102         l_result_column VARCHAR2(30);
103 
104     BEGIN
105         OPEN c;
106         FETCH c INTO l_result_column;
107         IF c%notfound THEN
108             CLOSE c;
109             RETURN NULL;
110         END IF;
111 
112         CLOSE c;
113         RETURN l_result_column;
114     END get_default_result_column;
115 
116 
117     FUNCTION disable_index(p_char_id NUMBER) RETURN INTEGER IS
118     --
119     -- Disable the index if one exists.  Return 0 if successful;
120     -- a negative error code if not (or if index doesn't exist).
121     -- Does not perform database commit.
122     --
123     BEGIN
124         UPDATE qa_char_indexes
125         SET enabled_flag = 2
126         WHERE char_id = p_char_id;
127 
128         RETURN 0;
129 
130         EXCEPTION
131             WHEN OTHERS THEN
132                 RETURN err_disable_index;
133 
134     END disable_index;
135 
136 
137     FUNCTION create_hardcoded_index(
138         p_char_id NUMBER,
139         p_alias VARCHAR2,
140         p_index_name VARCHAR2,
141         p_additional_parameters VARCHAR2)
142         RETURN INTEGER IS
143     --
144     -- Create the hardcoded index.
145     -- Return 0 if successful, a negative error code if not.
146     --
147     -- FUTURE EXPANSION ONLY.  NOT IN SCOPE.
148     -- bso Sun Nov 21 15:42:23 PST 2004
149     --
150     BEGIN
151         RETURN err_unsupported_element_type;
152     END create_hardcoded_index;
153 
154     --
155     -- bug 12596623
156     -- Added a new parameter p_process_num_decode to ensure that
157     -- while building the predicate for numbers, the DECODE()
158     -- function is not Stripped off
159     --
160     FUNCTION construct_decode_function(
161         p_char_id NUMBER,
162         p_alias VARCHAR2,
163         x_most_common OUT NOCOPY VARCHAR2,
164         x_function OUT NOCOPY dbms_sql.varchar2s,
165         p_process_num_decode IN BOOLEAN DEFAULT FALSE)
166         RETURN INTEGER IS
167 
168     --
169     -- This is an auxiliary function that constructs the decode
170     -- function to be used in the function-based index.  The
171     -- function string is returned in pieces in the x_function
172     -- array (an array of varchar2).  An array is used instead of
173     -- a simple VARCHAR2 because PL/SQL VARCHAR2 can only handle
174     -- 32K while a create index DDL can handle 64K.
175     --
176     -- Make sure the input p_alias is either null or a valid table
177     -- alias with the period, such as 'QR.'
178     --
179     -- Return 0 if successful; a negative error code otherwise.
180     --
181     -- Note: this function was modeled after the global_view
182     -- procedure in qltvcreb and utilized the same dbms_sql.varchar2s
183     -- array.  It can potentially handle more than 32K, but the
184     -- current scope is to handle decode function of 32K or less
185     -- to make other PL/SQL manipulation of this function string
186     -- more manageable.  Expansion to > 32K is non-trivial because
187     -- ordinary PL/SQL VARCHAR2 variables used in many places to
188     -- handle this function string cannot handle > 32K.
189     -- bso Sun Nov 21 14:51:50 PST 2004
190     --
191 
192         --
193         -- This cursor is used to find the most commonly used
194         -- result column name given a char_id.  Ignore template
195         -- plans (i.e., organization_id <> 0)
196         --
197         CURSOR c_most_common(p_char_id NUMBER) IS
198             SELECT qpc.result_column_name
199             FROM   qa_plan_chars qpc, qa_plans qp
200             WHERE  qpc.plan_id = qp.plan_id AND
201                    qpc.char_id = p_char_id AND
202                    qp.organization_id <> 0
203             GROUP BY result_column_name
204             ORDER BY count(result_column_name) desc;
205 
206         l_most_common VARCHAR2(30);
207 
208         --
209         -- This cursor is the main loop to go through each plan
210         -- that is not template plan (i.e., organization_id <> 0).
211         -- Since the most commonly used result column name will be
212         -- appended to the end of the DECODE function as default
213         -- parameter, the plans having this are ignored also.
214         --
215         CURSOR c_result_column(p_char_id NUMBER, p_col VARCHAR2) IS
216             SELECT qpc.plan_id, qpc.result_column_name
217             FROM   qa_plan_chars qpc, qa_plans qp
218             WHERE  qpc.plan_id = qp.plan_id AND
219                    qpc.char_id = p_char_id AND
220                    qp.organization_id <> 0 AND
221                    qpc.result_column_name <> p_col;
222 
223         --
224         -- bug 12596623
225         -- Cursor for the case when the decode is not to be stripped off
226         --
227         CURSOR c2_result_column(p_char_id NUMBER) IS
228             SELECT qpc.plan_id, qpc.result_column_name
229             FROM   qa_plan_chars qpc, qa_plans qp
230             WHERE  qpc.plan_id = qp.plan_id AND
231                    qpc.char_id = p_char_id AND
232                    qp.organization_id <> 0;
233 
234         --
235         -- Bug 1357601.  The decode statement used to "straighten" softcoded
236         -- elements into a single column has a sever limit of 255 parameters.
237         -- These variables are added to resolve the limit.  When the limit is
238         -- up, we use the very last parameter of the decode statement to
239         -- start a new decode, which can have another 255 params.  This is
240         -- repeated as necessary.
241         --
242         -- decode_count keeps the no. of decodes being used so far.
243         -- decode_param keeps the no. of parameters in the current decode.
244         -- decode_limit is the server limit.  This should be updated if
245         --    the server is enhanced in the future.
246         --
247         decode_count NUMBER;
248         decode_param NUMBER;
249         decode_limit CONSTANT NUMBER := 255;
250         i INTEGER;
251 
252     BEGIN
253 
254         OPEN c_most_common(p_char_id);
255         FETCH c_most_common INTO l_most_common;
256         IF c_most_common%notfound THEN
257             CLOSE c_most_common;
258             RETURN err_element_not_in_use;
259         END IF;
260 
261         CLOSE c_most_common;
262         x_most_common := l_most_common;
263 
264         --
265         -- Main loop to go through each plan ID that has p_char_id
266         -- as element (except when the result column name is the
267         -- most common column).  Now construct the decode function.
268         -- For example,
269         --
270         -- decode(qr.plan_id,
271         --     101, qr.character2,
272         --     102, qr.character5,
273         --     103, qr.character14,
274         --     qr.character1)
275         --
276         i := 1;
277         x_function(i) := 'DECODE(' || p_alias || 'PLAN_ID,';
278         decode_count := 1;     -- see comments in variable declaration.
279         decode_param := 1;
280 
281         IF (p_process_num_decode = FALSE) THEN
282             FOR r IN c_result_column(p_char_id, l_most_common) LOOP
283                 i := i + 1;
284 
285                 --
286                 -- If maximum no. of arguments to the "decode" function is
287                 -- close to the server allowed 'decode_limit', then we want
288                 -- to start a new tail-end decode statement.
289                 --
290                 IF decode_param >= (decode_limit - 2) THEN
291                     x_function(i) := 'DECODE(' || p_alias || 'PLAN_ID,';
292                     i := i + 1;
293                     decode_count := decode_count + 1;
294                     decode_param := 1;
295                 END IF;
296 
297                 x_function(i) := r.plan_id || ',' || p_alias ||
298                     r.result_column_name || ',';
299 
300                 decode_param := decode_param + 2;
301             END LOOP;
302         ELSE
303             FOR r IN c2_result_column(p_char_id) LOOP
304                 i := i + 1;
305 
306                 --
307                 -- If maximum no. of arguments to the "decode" function is
308                 -- close to the server allowed 'decode_limit', then we want
309                 -- to start a new tail-end decode statement.
310                 --
311                 IF decode_param >= (decode_limit - 2) THEN
312                     x_function(i) := 'DECODE(' || p_alias || 'PLAN_ID,';
313                     i := i + 1;
314                     decode_count := decode_count + 1;
315                     decode_param := 1;
316                 END IF;
317 
318                 x_function(i) := r.plan_id || ',' || p_alias ||
319                     r.result_column_name || ',';
320 
321                 decode_param := decode_param + 2;
322             END LOOP;
323             x_function(i) := RTRIM(x_function(i),',');
324         END IF;
325 
326         -- bug 12596623
327         IF (i = 1 AND p_process_num_decode = FALSE) THEN
328             --
329             -- In the extremely rare condition where all plans have the
330             -- same result column for this char ID, we need to remove
331             -- the decode function.
332             --
333             x_function(i) := p_alias || l_most_common;
334         ELSE
335             --
336             -- Add the most common column as default parameter and then
337             -- close all decode() parenthesis
338             --
339             --
340             --
341             -- bug 12596623
342             -- if processing for number then the default most common
343             -- result column should not be appended
344             --
345             IF p_process_num_decode = FALSE THEN
346                x_function(i) := x_function(i) || p_alias || l_most_common;
347             END IF;
348 
349             FOR x IN 1 .. decode_count LOOP
350                 x_function(i) := x_function(i) || ')';
351             END LOOP;
352         END IF;
353 
354         RETURN 0;
355 
356     END construct_decode_function;
360         p_function dbms_sql.varchar2s,
357 
358 
359     FUNCTION varchar2s_to_varchar2(
361         x_ddl OUT NOCOPY VARCHAR2)
362         RETURN INTEGER IS
363     --
364     -- A helper function to convert the decode function string from
365     -- dbms_sql.varchar2 format to a simple string.  Return 0 if
366     -- successful; -1 if not.
367     --
368         l_ddl VARCHAR2(32767);
369     BEGIN
370 
371         FOR i IN p_function.FIRST .. p_function.LAST LOOP
372             l_ddl := l_ddl || p_function(i);
373         END LOOP;
374 
375         x_ddl := l_ddl;
376         RETURN 0;
377 
378         EXCEPTION
379             WHEN OTHERS THEN
380                 RETURN err_string_overflow;
381 
382     END varchar2s_to_varchar2;
383 
384     --
385     -- bug 12596623
386     -- New function to return the Case predicate for indices
387     -- on numbers.
388     --
389     FUNCTION get_case_function(p_char_id IN VARCHAR2, p_alias in VARCHAR2, x_case_func OUT NOCOPY VARCHAR2)
390       RETURN INTEGER AS
391         l_case_func VARCHAR2(32767);
392 
393         l_function dbms_sql.varchar2s;
394         l_status INTEGER;
395         l_alias_dot VARCHAR2(50);
396         l_most_common VARCHAR2(30);
397         l_rowid VARCHAR2(50);
398 
399         l_num_index_ddl VARCHAR2(32767);
400         l_num_ddl       VARCHAR2(32767);
401     BEGIN
402         IF p_alias IS NOT NULL THEN
403             l_alias_dot := p_alias || '.';
404         END IF;
405 
406         l_status := construct_decode_function(
407                          p_char_id,
408                          l_alias_dot,
409                          l_most_common,
410                          l_function,
411                          TRUE);
412 
413         IF l_status <> 0 THEN
414            RETURN l_status;
415         END IF;
416 
417         l_status := varchar2s_to_varchar2(l_function, l_num_ddl);
418 
419         IF l_status <> 0 THEN
420            RETURN l_status;
421         END IF;
422 
423         l_case_func :=
424         'CASE WHEN INSTR ('|| l_num_ddl ||', '','') > 0 THEN '||
425         '      to_number( '|| l_num_ddl ||', ''FM99999999999999999999999999999999999999999999999999D999999999999'', ''nls_numeric_characters='''',.'''''') '||
426         ' ELSE to_number( '|| l_num_ddl ||', ''FM99999999999999999999999999999999999999999999999999D999999999999'', ''nls_numeric_characters=''''.,'''''') '||
427         ' END ';
428 
429         x_case_func := l_case_func;
430         RETURN 0;
431 
432         EXCEPTION
433             WHEN OTHERS THEN
434                 RETURN err_string_overflow;
435 
436     END get_case_function;
437 
438     FUNCTION create_softcoded_index(
439         p_char_id NUMBER,
440         p_alias VARCHAR2,
441         p_index_name VARCHAR2,
442         p_additional_parameters VARCHAR2)
443         RETURN INTEGER IS
444     --
445     -- Create the softcoded index.
446     -- Return 0 if successful, a negative error code if not.
447     --
448         l_ddl VARCHAR2(32767); -- current scope supports 32k only
449         l_function dbms_sql.varchar2s;
450         l_status INTEGER;
451         l_alias_dot VARCHAR2(50);
452         l_most_common VARCHAR2(30);
453         l_rowid VARCHAR2(50);
454 
455         l_num_index_ddl VARCHAR2(32767);
456         l_num_ddl       VARCHAR2(32767);
457 
458     BEGIN
459         IF p_alias IS NOT NULL THEN
460             l_alias_dot := p_alias || '.';
461         END IF;
462 
463         l_status := construct_decode_function(
464             p_char_id, l_alias_dot, l_most_common, l_function);
465         IF l_status <> 0 THEN
466             RETURN l_status;
467         END IF;
468 
469         l_status := varchar2s_to_varchar2(l_function, l_ddl);
470         IF l_status <> 0 THEN
471             RETURN l_status;
472         END IF;
473 
474         --
475         -- bug 12596623
476         -- If the element is of the type char, then the where clause
477         -- thats constructed in QWB would contain an UPPER(). Hence
478         -- we have to add the upper function around the DECODE to ensure
479         -- that the search on the element is driven through the index.
480         --
481         IF qa_plan_element_api.get_element_datatype(p_char_id) = 1 THEN
482            l_ddl := 'UPPER('||l_ddl||')';
483 
484         --
485         -- bug 12596623
486         -- If the element is of the type number, then the where clause
487         -- thats constructed in QWB would contain the case function
488         --
489         ELSIF (qa_plan_element_api.get_element_datatype(p_char_id) = 2) THEN
490            l_status := get_case_function(p_char_id,  p_alias, l_num_index_ddl);
491            IF l_status <> 0 THEN
492               RETURN l_status;
493            END IF;
494         END IF;
495 
496         --
497         -- Table operation is performed before DDL by design
498         -- so that the database commit inherent in the DDL
499         -- will commit the data in sync.
500         --
501         insert_row(
502             x_rowid                     => l_rowid,
503             p_created_by                => who_user_id,
504             p_creation_date             => sysdate,
505             p_last_updated_by           => who_user_id,
506             p_last_update_date          => sysdate,
507             p_last_update_login         => who_user_id,
508             p_request_id                => who_request_id,
509             p_program_application_id    => who_program_application_id,
510             p_program_id                => who_program_id,
514             p_index_name                => p_index_name,
511             p_program_update_date       => sysdate,
512             p_char_id                   => p_char_id,
513             p_enabled_flag              => 1,
515             p_default_result_column     => l_most_common,
516             p_text                      => l_ddl,
517             p_additional_parameters     => p_additional_parameters);
518 
519         --
520         -- Here l_ddl contains the actual DECODE function.
521         -- we prepend and append the rest of the actual
522         -- rdbms CREATE INDEX command and pass to ad_ddl.
523         -- String overflow is still possible.
524         --
525         l_ddl := 'CREATE INDEX ' || g_qa_schema || '.' ||
526             '"' || p_index_name || '" ON ' ||
527             g_qa_schema || '.QA_RESULTS ' || p_alias ||
528             '(' || l_alias_dot || 'PLAN_ID, ' || l_ddl || ') ' ||
529             p_additional_parameters;
530 
531         ad_ddl.do_ddl(
532             applsys_schema => g_fnd_schema,
533             application_short_name => g_qa,
534             statement_type => ad_ddl.create_index,
535             statement => l_ddl,
536             object_name => p_index_name);
537 
538         --
539         -- bug 12596623
540         -- Create the Internal index for numbers
541         --
542         IF ((qa_plan_element_api.get_element_datatype(p_char_id) = 2) AND
543              l_num_index_ddl IS NOT NULL) THEN
544                 l_num_index_ddl := 'CREATE INDEX ' || g_qa_schema || '.' ||
545                     '"' || 'QA_'||p_char_id||'_INT' || '" ON ' ||
546                     g_qa_schema || '.QA_RESULTS ' || p_alias ||
547                     '(' || l_alias_dot || 'PLAN_ID, ' || l_num_index_ddl || ') ' ||
548                     p_additional_parameters;
549 
550                 ad_ddl.do_ddl(
551                     applsys_schema => g_fnd_schema,
552                     application_short_name => g_qa,
553                     statement_type => ad_ddl.create_index,
554                     statement => l_num_index_ddl,
555                     object_name => 'QA_'||p_char_id||'_INT');
556         END IF;
557 
558         RETURN 0;
559 
560 
561         EXCEPTION
562             WHEN VALUE_ERROR THEN
563                 RETURN err_string_overflow;
564             WHEN OTHERS THEN
565                 RETURN err_create_index;
566 
567     END create_softcoded_index;
568 
569 
570 
571     PROCEDURE insert_row(
572         x_rowid                     OUT NOCOPY VARCHAR2,
573         p_created_by                NUMBER,
574         p_creation_date             DATE,
575         p_last_updated_by           NUMBER,
576         p_last_update_date          DATE,
577         p_last_update_login         NUMBER,
578         p_request_id                NUMBER,
579         p_program_application_id    NUMBER,
580         p_program_id                NUMBER,
581         p_program_update_date       DATE,
582         p_char_id                   NUMBER,
583         p_enabled_flag              NUMBER,
584         p_index_name                VARCHAR2,
585         p_default_result_column     VARCHAR2,
586         p_text                      VARCHAR2,
587         p_additional_parameters     VARCHAR2) IS
588 
589         CURSOR c IS
590              SELECT rowid
591              FROM   qa_char_indexes
592              WHERE  char_id = p_char_id;
593 
594     BEGIN
595         INSERT INTO qa_char_indexes(
596             created_by,
597             creation_date,
598             last_updated_by,
599             last_update_date,
600             last_update_login,
601             request_id,
602             program_application_id,
603             program_id,
604             program_update_date,
605             char_id,
606             enabled_flag,
607             index_name,
608             default_result_column,
609             text,
610             additional_parameters)
611         VALUES(
612             p_created_by,
613             p_creation_date,
614             p_last_updated_by,
615             p_last_update_date,
616             p_last_update_login,
617             p_request_id,
618             p_program_application_id,
619             p_program_id,
620             p_program_update_date,
621             p_char_id,
622             p_enabled_flag,
623             p_index_name,
624             p_default_result_column,
625             p_text,
626             p_additional_parameters);
627 
628         OPEN c;
629         FETCH c INTO x_rowid;
630         IF SQL%NOTFOUND THEN
631             CLOSE c;
632             RAISE no_data_found;
633         END IF;
634         CLOSE c;
635 
636     END insert_row;
637 
638 
639     PROCEDURE delete_row(p_char_id NUMBER) IS
640     --
641     -- The delete_row handler differs from the normal standard
642     -- a little because this procedure is not designed to be used
643     -- by Forms, so it is more efficient to pass in the primary key
644     -- than to pass in the rowid.
645     -- bso
646     --
647     BEGIN
648 
649         DELETE
650         FROM  qa_char_indexes
651         WHERE char_id = p_char_id;
652 
653         IF SQL%NOTFOUND THEN
654             RAISE no_data_found;
655         END IF;
656 
657     END delete_row;
658 
659 
660     FUNCTION drop_index(p_char_id NUMBER) RETURN INTEGER IS
661     --
662     -- Main function to drop an index.  If successful, the index record in
663     -- qa_char_indexes table is also deleted to register the fact.
664     --
668     -- performed inherently.
665     -- Return 0 if successful, a negative error code if not.
666     --
667     -- Because this is a DDL, by definition a commit is
669     --
670         l_index_name VARCHAR2(30);
671         l_num_int_index VARCHAR2(30);
672 
673         l_ddl VARCHAR2(100);
674         CURSOR c IS
675             SELECT index_name
676             FROM   qa_char_indexes
677             WHERE  char_id = p_char_id;
678 
679         Cursor c_num_idx IS
680         SELECT index_name from all_indexes
681             WHERE TABLE_NAME = 'QA_RESULTS'
682               AND INDEX_NAME = 'QA_'|| p_char_id || '_INT'
683               AND OWNER      = g_qa;
684 
685     BEGIN
686         SAVEPOINT l_drop_index;
687 
688         OPEN c;
689         FETCH c INTO l_index_name;
690         IF c%notfound THEN
691             CLOSE c;
692             RETURN err_drop_index;
693         END IF;
694         CLOSE c;
695 
696         BEGIN
697             --
698             -- Table operation is performed before DDL by design
699             -- so that the database commit inherent in the DDL
700             -- will commit the data in sync.
701             --
702             delete_row(p_char_id);
703 
704             EXCEPTION
705                 WHEN OTHERS THEN
706                     RETURN err_delete_row;
707         END;
708 
709         l_ddl := 'DROP INDEX ' || g_qa_schema || '.' ||
710             '"' || l_index_name || '"';
711 
712         ad_ddl.do_ddl(
713             applsys_schema => g_fnd_schema,
714             application_short_name => g_qa,
715             statement_type => ad_ddl.drop_index,
716             statement => l_ddl,
717             object_name => l_index_name);
718 
719         --
720         -- bug 12596623
721         -- Drop the internal index if it exists for Numeric elements
722         --
723         IF qa_plan_element_api.get_element_datatype(p_char_id) = 2 THEN
724            OPEN c_num_idx;
725            FETCH c_num_idx INTO l_num_int_index;
726            IF c_num_idx%notfound THEN
727              CLOSE c_num_idx;
728            ELSE
729              CLOSE c_num_idx;
730              l_ddl := 'DROP INDEX ' || g_qa_schema || '.' ||
731                       '"' || l_num_int_index || '"';
732 
733              ad_ddl.do_ddl(
734                  applsys_schema => g_fnd_schema,
735                  application_short_name => g_qa,
736                  statement_type => ad_ddl.drop_index,
737                  statement => l_ddl,
738                  object_name => l_num_int_index);
739            END IF;
740         END IF;
741 
742         RETURN 0;
743 
744         EXCEPTION
745             WHEN OTHERS THEN
746                 ROLLBACK TO l_drop_index;
747                 RETURN err_drop_index;
748 
749     END drop_index;
750 
751 
752     FUNCTION create_or_regenerate_index(
753         p_char_id NUMBER,
754         p_index_name VARCHAR2,
755         p_additional_parameters VARCHAR2)
756         RETURN INTEGER IS
757     --
758     -- Main function to create or regenerate index.
759     -- If an index already exists, then it is dropped before
760     -- creating.  If an index is created or regenerated
761     -- successfully, then the qa_char_indexes table is
762     -- updated with that fact.
763     --
764     -- Return 0 if successful, a negative error code if not.
765     --
766     -- Because this is a DDL, by definition a commit is
767     -- performed inherently.
768     --
769         l_status INTEGER;
770 
771     BEGIN
772 
773         SAVEPOINT l_create_index;
774 
775         --
776         -- A safeguard against dropping Quality's own indexes.
777         --
778         IF substr(p_index_name, 1, 3) = 'QA_' THEN
779             RETURN err_index_name;
780         END IF;
781 
782         IF index_exists(p_char_id) = 1 THEN
783             l_status := drop_index(p_char_id);
784             IF l_status <> 0 THEN
785                 RETURN l_status;
786             END IF;
787         END IF;
788 
789         --
790         -- Simple check to make sure p_char_id is a softcoded element.
791         --
792         IF qa_chars_api.hardcoded_column(p_char_id) IS NOT NULL THEN
793             RETURN err_unsupported_element_type;
794         END IF;
795 
796         l_status := create_softcoded_index(
797             p_char_id => p_char_id,
798             p_alias => '',
799             p_index_name => p_index_name,
800             p_additional_parameters => p_additional_parameters);
801         IF l_status <> 0 THEN
802             ROLLBACK TO l_create_index;
803             RETURN l_status;
804         END IF;
805 
806         RETURN 0;
807 
808         EXCEPTION
809             WHEN OTHERS THEN
810                 ROLLBACK TO l_create_index;
811                 RETURN err_insert_row;
812 
813     END create_or_regenerate_index;
814 
815 
816     PROCEDURE get_predicate(
817         p_char_id NUMBER,
818         p_alias VARCHAR2,
819         x_predicate OUT NOCOPY VARCHAR2) IS
820 
821         l_predicate VARCHAR2(32767);
822 
823         -- Bug 4086800. A CLOB value cannot be fetched directly
824         -- into a VARCHAR2 variable prior to 9i. Hence the below
825         -- cursor needs to be modified to be compatible across
826         -- database versions. Used the dbms_lob package routines
827         -- for varchar2 conversions. kabalakr.
828 
829         CURSOR c IS
833 
830             SELECT dbms_lob.substr(text, dbms_lob.getlength(text), 1)
831             FROM   qa_char_indexes
832             WHERE  char_id = p_char_id AND enabled_flag = 1;
834     BEGIN
835         OPEN c;
836         FETCH c INTO l_predicate;
837         IF c%notfound THEN
838             CLOSE c;
839             x_predicate := NULL;
840         ELSE
841             CLOSE c;
842 
843             IF p_alias IS NOT NULL THEN
844                 l_predicate := replace(replace(l_predicate,
845                     'PLAN_ID', p_alias || '.PLAN_ID'),
846                     'CHARACTER', p_alias || '.CHARACTER');
847             END IF;
848 
849             x_predicate := l_predicate;
850         END IF;
851 
852         EXCEPTION
853             WHEN OTHERS THEN
854                 x_predicate := NULL;
855 
856     END get_predicate;
857 
858 
859     PROCEDURE wrapper(
860         errbuf    OUT NOCOPY VARCHAR2,
861         retcode   OUT NOCOPY NUMBER,
862         argument1            VARCHAR2,
863         argument2            VARCHAR2,
864         argument3            VARCHAR2,
865         argument4            VARCHAR2) IS
866 
867     --
868     -- Wrapper procedure to create or drop the index.
869     -- This procedure is the entry point for this package
870     -- through the concurrent program 'Manage Collection
871     -- element indexes'. This wrapper procedure is attached
872     -- to the QAINDEX executable.
873     -- argument1 -> Index Action : 'Create or Regenerate' OR 'Drop'.
874     -- argument2 -> Proposed or New Index name.
875     -- argument3 -> Softcoded Plan element on which Index action
876     --              will be executed.
877     -- argument4 -> Additional Parameters specified by the user
878     --              when creating the index.
879     --
880 
881        l_type_of_action   NUMBER;
882        l_char_id          NUMBER;
883        l_return           NUMBER;
884 
885     BEGIN
886 
887        fnd_file.put_line(fnd_file.log, 'qa_char_indexes_pkg: entered the wrapper');
888 
889        l_type_of_action := to_number(argument1);
890        l_char_id := to_number(argument3);
891 
892        IF l_type_of_action = 1 THEN
893           fnd_file.put_line(fnd_file.log, 'Create or Regnerate the Index');
894 
895           l_return := create_or_regenerate_index(
896              p_char_id                => l_char_id,
897              p_index_name             => argument2,
898              p_additional_parameters  => argument4);
899 
900           IF (l_return = 0) THEN
901              fnd_file.put_line(fnd_file.log, 'Index successfully created');
902              errbuf := '';
903              retcode := 0;
904           ELSE
905              fnd_file.put_line(fnd_file.log, 'Index creation failed. ERROR:'||to_char(l_return));
906              errbuf := 'ERROR:'||to_char(l_return);
907              retcode := 2;
908           END IF;
909 
910 
911        ELSIF (l_type_of_action = 2) THEN
912           fnd_file.put_line(fnd_file.log, 'Drop the Index');
913 
914           l_return := drop_index(
915              p_char_id => l_char_id);
916 
917           IF (l_return = 0) THEN
918              fnd_file.put_line(fnd_file.log, 'Index successfully dropped');
919              errbuf := '';
920              retcode := 0;
921           ELSE
922              fnd_file.put_line(fnd_file.log, 'Index failed to drop. ERROR:'||to_char(l_return));
923              errbuf := 'ERROR:'||to_char(l_return);
924              retcode := 2;
925           END IF;
926        END IF;
927 
928        fnd_file.put_line(fnd_file.log, 'qa_char_indexes_pkg: exiting the wrapper');
929 
930     END wrapper;
931 
932 
933     FUNCTION get_index_predicate(
934         p_char_id NUMBER,
935         p_alias VARCHAR2)
936         RETURN VARCHAR2 IS
937 
938     -- This function acts as a wrapper to the get_predicate procedure.
939     -- The requirement is from QWB Advanced Search, where we need to
940     -- model the VO with the get_predicate().
941 
942         l_predicate VARCHAR2(32767);
943 
944     BEGIN
945 
946         -- This is just a wrapper to get_predicate() procedure.
947         -- No validations in this function.
948 
949         get_predicate(p_char_id   => p_char_id,
950                       p_alias     => p_alias,
951                       x_predicate => l_predicate);
952 
953         RETURN l_predicate;
954 
955     END get_index_predicate;
956 
957 
958     --
959     -- Bug 3930666.  This bug does not impact this
960     -- current package.  But it is most efficient to
961     -- fix it by exposing a new function to the public
962     -- which is a combination of varchar2s_to_varchar2
963     -- and construct_decode_function of this package.
964     -- To be used in qlthrb.plb.
965     -- bso Tue Apr  5 17:24:07 PDT 2005
966     --
967     FUNCTION get_decode_function(
968         p_char_id NUMBER,
969         p_alias VARCHAR2 DEFAULT NULL)
970         RETURN VARCHAR2 IS
971 
972         l_most_common VARCHAR2(30);
973         l_function dbms_sql.varchar2s;
974         l_predicate VARCHAR2(32767);
975         l_status NUMBER;
976 
977     BEGIN
978         l_status := construct_decode_function(p_char_id,
979             p_alias, l_most_common, l_function);
980 
981         IF l_status <> 0 THEN
982             RETURN '';
983         END IF;
984 
985         l_status := varchar2s_to_varchar2(l_function, l_predicate);
986         IF l_status <> 0 THEN
987             RETURN '';
988         END IF;
989 
990         RETURN l_predicate;
991 
992     END get_decode_function;
993 
994 BEGIN
995 
996     g_dummy := fnd_installation.get_app_info(
997         application_short_name => g_fnd,
998         status => g_status,
999         industry => g_industry,
1000         oracle_schema => g_fnd_schema);
1001 
1002     g_dummy := fnd_installation.get_app_info(
1003         application_short_name => g_qa,
1004         status => g_status,
1005         industry => g_industry,
1006         oracle_schema => g_qa_schema);
1007 
1008 END qa_char_indexes_pkg;