DBA Data[Home] [Help]

PACKAGE BODY: SYSTEM.AD_APPS_PRIVATE

Source


1 package body AD_APPS_PRIVATE as
2 /* $Header: adaprb.pls 120.5 2007/02/15 14:54:34 stangutu ship $ */
3 
4   --
5   -- PRIVATE GLOBAL VARIABLES
6   --
7   --Collection type to cache results
8   -- Added the folling for bug# 4583342
9   -- UserName_Cache_Table_TYpe
10   TYPE Un_Cache_Tbl_Type IS TABLE OF VARCHAR2(40) INDEX BY VARCHAR2(10);
11 
12   --Collection variable to cache results
13   g_Un_Cache_Tbl Un_Cache_Tbl_Type;
14   --
15   -- PRIVATE PROCEDURES/FUNCTIONS SPECIFICATIONS
16   --
17 
18 procedure copy_view_internal
19            (view_name   in varchar2,
20             from_schema in varchar2,
21             to_schema   in varchar2);
22 --
23 -- Purpose
24 --   The procedure copies a view from one schema to another.
25 -- Arguments
26 --   view_name View to be copied
27 --   from_schema Schema to copy from
28 --   to_schema Schema to copy to
29 -- Example
30 --   none
31 -- Notes
32 --
33 -- This is the old copy_view routine.
34 -- Renamed it and created a new copy_view that is a wrapper
35 -- It calls this one and tries to handle deadlock errors
36 --
37 
38   --
39   -- PROCEDURES/FUNCTIONS
40   --
41 
42 --
43 -- Procedures dealing with APPS_DDL and APPS_ARRAY_DDL
44 --
45 
46 procedure do_apps_ddl
47            (schema_name in varchar2,
48             ddl_text    in varchar2,
49             abbrev_stmt in varchar2)
50 --
51 --   schema_name The schema in which to run the statement
52 --   ddl_text  The SQL statement to run
53 --   abbrev_stmt Replace ddl_text with '$statement$' in stack trace?
54 --
55 is
56   statement             varchar2(500);
57 begin
58   -- execute statement in specified schema
59 
60   statement:='begin '||schema_name||'.apps_ddl.apps_ddl(:ddl_text); end;';
61 
62   EXECUTE IMMEDIATE statement
63   using ddl_text;
64 
65 exception
66   when others then
67 
68     if abbrev_stmt = 'FALSE' then
69       ad_apps_private.error_buf := 'do_apps_ddl('||schema_name||
70         ','||ddl_text|| '): '||ad_apps_private.error_buf;
71     else
72       ad_apps_private.error_buf := 'do_apps_ddl('||schema_name||
73         ', $statement$): '||ad_apps_private.error_buf;
74     end if;
75 
76     raise;
77 end do_apps_ddl;
78 
79 
80 procedure do_apps_ddl
81            (schema_name in varchar2,
82             ddl_text    in varchar2)
83 is
84 begin
85   do_apps_ddl (schema_name => schema_name,
86                ddl_text    => ddl_text,
87                abbrev_stmt => 'FALSE');
88 end;
89 
90 
91 procedure do_apps_array_ddl
92             (schema_name in varchar2,
93              lb          in integer,
94              ub          in integer,
95              add_newline in varchar2)
96 is
97   statement             varchar2(500);
98 begin
99    -- call the package procedure created earlier in schema username
100 
101    statement:=
102        'begin '||schema_name||
103        '.apps_array_ddl.apps_array_ddl(:lb, :ub, :nlf); end;';
104 
105    EXECUTE IMMEDIATE statement
106    using lb, ub, add_newline;
107 
108 exception
109   when others then
110     ad_apps_private.error_buf := 'do_apps_array_ddl('||schema_name||', '||
111                 lb||', '||ub||', '||add_newline||'): '||
112                 ad_apps_private.error_buf;
113     raise;
114 end do_apps_array_ddl;
115 
116 procedure do_apps_array_ddl
117             (schema_name in varchar2,
118              lb          in integer,
119              ub          in integer)
120 is
121 begin
122   do_apps_array_ddl (schema_name => schema_name,
123                      lb          => lb,
124                      ub          => ub,
125                      add_newline => 'FALSE');
126 end;
127 
128 
129 procedure do_array_assignment
130            (schema_name in varchar2,
131             ddl_text    in varchar2,
132             rowcount    in integer)
133 is
134   statement             varchar2(500);
135 begin
136   -- Do the array assignment to the global variable in schema username
137 
138   statement:=
139     'begin '||schema_name||'.apps_array_ddl.glprogtext(:i) := :ddl_text; end;';
140 
141   EXECUTE IMMEDIATE statement
142   using rowcount, ddl_text;
143 
144 exception
145   when others then
146     ad_apps_private.error_buf := 'do_array_assignment('||schema_name||','||
147         ddl_text||','||rowcount||'): '||ad_apps_private.error_buf;
148     raise;
149 end do_array_assignment;
150 
151 
152 procedure check_for_apps_ddl
153            (schema_name in varchar2)
154 is
155   dummy         number;
156   i             number;
157   found_session boolean := False;
158   pack_stmt     varchar2(1000);
159 begin
160   -- Check to see if apps_ddl and apps_array_ddl exist and are valid
161   -- but only once per session. Not necessary to continue to check
162   for i in 1..schema_check.count loop
163    if upper(schema_name) = schema_check(i)
164    then
165     found_session := True;
166     exit; -- no reason to check further, exit the loop
167    end if;
168   end loop;
169 
170   if NOT found_session
171   then
172     select count(*)
173     into dummy
174     from dba_objects
175     where object_type in ('PACKAGE', 'PACKAGE BODY')
176     and object_name in ('APPS_DDL', 'APPS_ARRAY_DDL')
177     and status = 'VALID'
178     and owner = upper(schema_name);
179 
180     if dummy <> 4 then
181       begin
182 
183         pack_stmt:='alter package '||schema_name||'.APPS_DDL compile';
184         execute immediate pack_stmt;
185 
186         pack_stmt:='alter package '||schema_name||'.APPS_ARRAY_DDL compile';
187         execute immediate pack_stmt;
188 
189       exception
190         when others then
191 
192         raise_application_error(-20000,
193         'APPS_DDL/APPS_ARRAY_DDL package(s) missing or invalid in schema '||
194         upper(schema_name));
195 
196       end;
197 
198     else
199      schema_check(schema_check.count+1) := upper(schema_name);
200     end if;
201   end if;
202   exception
203     when others then
204       ad_apps_private.error_buf := 'check_for_apps_ddl('||schema_name||
205                                    '): '||ad_apps_private.error_buf;
206       raise;
207 end check_for_apps_ddl;
208 
209 --
210 -- Procedures dealing with Oracle Schemas
211 --
212 
213 function check_if_schema_exists (schema_name in varchar2)
214 return boolean is
215   cursor c1 is
216     select name from sys.user$
217     where name = upper(check_if_schema_exists.schema_name);
218 begin
219   for c1rec in c1 loop
220     -- at least one row was returned so the user exists.
221     return TRUE;
222   end loop;
223   -- no rows returned then return false
224   return FALSE;
225 exception
226   when others then
227     ad_apps_private.error_buf := 'check_if_schema_exists('||schema_name||
228                                 '): '||ad_apps_private.error_buf;
229     raise;
230 end check_if_schema_exists;
231 
232 --
233 -- Utility functions
234 --
235 PROCEDURE create_grant
236            (p_grantor_schema_name IN VARCHAR2,
237             p_grantee_schema_name IN VARCHAR2,
238             p_object_name         IN VARCHAR2,
239             p_privileges          IN VARCHAR2,
240             p_with_grant_option   IN BOOLEAN DEFAULT TRUE,
241             p_recursion_depth     IN NUMBER DEFAULT NULL)
242   IS
243      l_statement           VARCHAR2(500);
244      l_owner_schema_name   dba_objects.owner%TYPE;
245      l_object_type         dba_objects.object_type%TYPE;
246      l_recursion_depth     NUMBER;
247      l_exists              NUMBER;
248      l_queue_owner         VARCHAR2(30);
249 
250      no_privileges_to_grant EXCEPTION;
251      PRAGMA EXCEPTION_INIT(no_privileges_to_grant, -1929);
252 
253     no_grant_exist EXCEPTION;
254     PRAGMA EXCEPTION_INIT(no_grant_exist, -1720);
255 
256 BEGIN
257    BEGIN
258       l_statement := ('GRANT ' || p_privileges || ' ON "' ||
259         p_object_name || '" TO ' || p_grantee_schema_name);
260       IF (p_with_grant_option) THEN
261   l_statement := l_statement || ' WITH GRANT OPTION';
262       END IF;
263       ad_apps_private.do_apps_ddl(p_grantor_schema_name, l_statement);
264    EXCEPTION
265       WHEN no_privileges_to_grant THEN
266   --
267   -- In case of APPS1 to APPS2 granting this can happen
268   -- and we need to get grantable grant from the base schema.
269   --
270   --
271   -- Get the object type.
272   --
273   BEGIN
274      SELECT object_type
275        INTO l_object_type
276        FROM dba_objects
277        WHERE owner = p_grantor_schema_name
278        AND object_name = p_object_name;
279   EXCEPTION
280    WHEN OTHERS THEN
281    ad_apps_private.error_buf :=
282    p_object_name || ' does not exist in ' ||
283    p_grantor_schema_name || ad_apps_private.error_buf;
284   RAISE;
285    END;
286 IF (l_object_type = 'SYNONYM') THEN
287      BEGIN
288    SELECT table_owner
289    INTO l_owner_schema_name
290    FROM dba_synonyms
291    WHERE owner = p_grantor_schema_name
292    AND synonym_name = p_object_name;
293      EXCEPTION
294       WHEN OTHERS THEN
295       ad_apps_private.error_buf :=
296       'Synonym ' || p_object_name || ' does not exist in ' ||
297       p_grantor_schema_name || ad_apps_private.error_buf;
298     RAISE;
299      END;
300      --
301      -- Check to recursion depth in case of circular synonyms.
302      --
303      l_recursion_depth := Nvl(p_recursion_depth, 0) + 1;
304      IF (l_recursion_depth < 0 OR
305   l_recursion_depth > 20) THEN
306         ad_apps_private.error_buf :=
307    'Recursion depth exceeded the limit (0-20) : ' ||
308    l_recursion_depth || ad_apps_private.error_buf;
309         RAISE;
310      END IF;
311      --
312      -- Recursively call to get grantable grant.
313      --
314      create_grant(p_grantor_schema_name => l_owner_schema_name,
315     p_grantee_schema_name => p_grantor_schema_name,
316     p_object_name         => p_object_name,
317     p_privileges          => p_privileges,
318     p_with_grant_option   => TRUE,
319     p_recursion_depth     => l_recursion_depth);
320      --
321      -- Now we have the grant from previous owner schema.
322      --
323      ad_apps_private.do_apps_ddl(p_grantor_schema_name, l_statement);
324    ELSE
325       ad_apps_private.error_buf :=
326       'No priv to grant for a non-synonym object. ' ||
327       ad_apps_private.error_buf;
328       RAISE;
329   END IF;
330    END;
331 
332 EXCEPTION
333 /* Added for bug2765486 to trap ORA -1720 */
334 /* BUG 2892989, Since APPLSYS owns WF queues, we don't use the owner condition
335    and use dba_queues that is faster than using dba_objects  */
336 
337  WHEN no_grant_exist THEN
338   BEGIN
339 	SELECT 1, owner into l_exists, l_queue_owner
340         FROM dba_queues where name = p_object_name;
341 
342   EXCEPTION
343      WHEN OTHERS THEN
344       ad_apps_private.error_buf := 'create_grant('||
345       p_object_name || ' does not exist in ' ||
346       l_queue_owner ||'): ' || ad_apps_private.error_buf;
347       RAISE;
348   END;
349 
350   IF l_exists = 1 THEN
351       dbms_aqadm.grant_queue_privilege(privilege  =>'ALL',
352       queue_name =>l_queue_owner||'.'||p_object_name,
353       grantee =>p_grantee_schema_name,grant_option=>TRUE);
354   END IF;
355 
356  WHEN no_privileges_to_grant THEN
357   ad_apps_private.error_buf := null;
358 
359  WHEN OTHERS THEN
360       DECLARE
361   l_with_grant_option_text VARCHAR2(10) := 'FALSE';
362       BEGIN
363   IF (p_with_grant_option) THEN
364      l_with_grant_option_text := 'TRUE';
365   END IF;
366   ad_apps_private.error_buf := 'create_grant('||
367     p_grantor_schema_name || ',' || p_grantee_schema_name || ',' ||
368     p_object_name || ',' || p_privileges || ',' ||
369     l_with_grant_option_text || ',' || p_recursion_depth || '): ' ||
370     ad_apps_private.error_buf;
371       END;
372     RAISE;
373 END create_grant;
374 
375 PROCEDURE create_synonym (p_from_schema_name IN VARCHAR2,
376                           p_from_object_name IN VARCHAR2,
377                           p_to_schema_name   IN VARCHAR2,
378                           p_to_object_name   IN VARCHAR2)
379   IS
380      l_statement           VARCHAR2(500);
381      l_object_type         dba_objects.object_type%TYPE;
382 
383      name_is_already_used  EXCEPTION;
384      PRAGMA EXCEPTION_INIT(name_is_already_used, -955);
385 BEGIN
386    BEGIN
387       l_statement := ('CREATE SYNONYM "' || p_to_object_name || '" FOR ' ||
388         p_from_schema_name || '."' ||
389         p_from_object_name || '"');
390       ad_apps_private.do_apps_ddl(p_to_schema_name, l_statement);
391    EXCEPTION
392       WHEN name_is_already_used THEN
393   BEGIN
394      SELECT object_type
395        INTO l_object_type
396        FROM dba_objects
397        WHERE owner = p_to_schema_name
398        AND object_name = p_to_object_name;
399   EXCEPTION
400      WHEN OTHERS THEN
401         ad_apps_private.error_buf :=
402    p_to_object_name || ' does not exist in ' ||
403    p_to_schema_name || ad_apps_private.error_buf;
404         RAISE;
405   END;
406   IF (l_object_type = 'SYNONYM') THEN
407      --
408      -- Drop the synonym and then re-create.
409      --
410      ad_apps_private.drop_object(p_to_schema_name, p_to_object_name,
411      'SYNONYM');
412      ad_apps_private.do_apps_ddl(p_to_schema_name, l_statement);
413    ELSE
414      RAISE;
415   END IF;
416    END;
417 EXCEPTION
418    WHEN OTHERS THEN
419       ad_apps_private.error_buf := 'create_synonym('||
420  p_from_schema_name || ',' || p_from_object_name || ',' ||
421  p_to_schema_name   || ',' || p_to_object_name   || '): ' ||
422  ad_apps_private.error_buf;
423       RAISE;
424 END create_synonym;
425 
426 procedure create_grants_and_synonyms
427            (install_group_num in number,
428             from_schema       in varchar2,
429             aol_schema        in varchar2,
430             apps_schema       in varchar2,
431             force             in varchar2)
432 is
433 begin
434   -- initialize variables; call init functions
435 
436   ad_apps_private.error_buf := null;
437 
438   ad_apps_private.initialize(aol_schema);
439 
440   ad_apps_private.load_exception_list;
441 
442   -- first make sure that the apps_ddl packages exist
443   -- in all relevent schemas
444 
445   ad_apps_private.check_for_apps_ddl(from_schema);
446   ad_apps_private.check_for_apps_ddl(apps_schema);
447 
448 -- create grants and synonyms from base to apps
449 --
450 -- if force=TRUE, will drop all synonyms in apps schema corresponding
451 -- to objects in this base schema before creating synonyms
452 --
453 -- This is handy for re-synchronizing the MLS schema with the APPS schema
454 -- in the case where the base object grant is manually removed from the
455 -- APPS schema.  Then the MLS grant would be removed via cascade, and we have
456 -- no automated way of fixing the MLS grant (re-running this without FORCE
457 -- will not re-create the MLS grant, because the synonym in APPS will not
458 -- have changed)
459 
460   create_base_gs(from_schema, apps_schema, force);
461 
465       install_group_num||','||from_schema||','||aol_schema||','||
462 exception
463   when others then
464     ad_apps_private.error_buf := 'create_grants_and_synonyms('||
466       apps_schema||'): '||ad_apps_private.error_buf;
467     raise;
468 
469 end create_grants_and_synonyms;
470 
471 procedure create_grants_and_synonyms
472            (install_group_num in number,
473             from_schema       in varchar2,
474             aol_schema        in varchar2,
475             apps_schema       in varchar2)
476 is
477 begin
478 
479 create_grants_and_synonyms
480            (install_group_num => install_group_num,
481             from_schema       => from_schema,
482             aol_schema        => aol_schema,
483             apps_schema       => apps_schema,
484             force             => 'FALSE');
485 end;
486 
487 
488 procedure get_apps_schema_name
489            (ign                in         number,
490             aol_or_apps_schema in         varchar2,
491             apps_schema        out nocopy varchar2,
492             apps_mls_schema    out nocopy varchar2)
493 is
494   c                     integer;
495   rows_processed        integer;
496   l_apps_schema         varchar2(30);
497   l_mls_apps_schema     varchar2(30);
498   c_statement           varchar2(500);
499 begin
500 
501   -- from the IGN get the APPS schema
502   IF ( g_Un_Cache_Tbl.COUNT <> 0 AND g_Un_Cache_Tbl.EXISTS(ign||'_aol') ) THEN
503     l_apps_schema := g_Un_Cache_Tbl(ign||'_aol') ;
504   ELSE -- if cache check
505    BEGIN --Block 1
506     c := dbms_sql.open_cursor;
507     -- select APPS account for given IGN, or if IGN is 0 then the min
508     c_statement:= 'select oracle_username from '||
509                   aol_or_apps_schema||'.fnd_oracle_userid '||
510                   'where (install_group_num = :install_group_num '||
511                   '      or install_group_num = '||
512                   '           (select min(install_group_num) from '||
513                   aol_or_apps_schema||'.fnd_oracle_userid '||
514                   '     where 1 = decode (:install_group_num,0,1,2) '||
515                   '     and read_only_flag = ''U'')) '||
516                   'and read_only_flag = ''U'' ';
517     dbms_sql.parse(c, c_statement, dbms_sql.native);
518     dbms_sql.bind_variable(c,'install_group_num',ign);
519     dbms_sql.define_column(c,1,l_apps_schema,30);
520     rows_processed := dbms_sql.execute(c);
521     if dbms_sql.fetch_rows(c) > 0 then
522       dbms_sql.column_value(c,1,l_apps_schema);
523     else
524       raise no_data_found;
525     end if;
526     dbms_sql.close_cursor(c);
527     --
528     -- Cache the result to the global collection
529     g_Un_Cache_Tbl(ign||'_aol') := l_apps_schema;
530    EXCEPTION
531     when others then
532       dbms_sql.close_cursor(c);
533       ad_apps_private.error_buf := 'c_statement='||c_statement||': '||
534                                    ad_apps_private.error_buf;
535       raise;
536    END ; -- Block 1
537   END IF ; -- Cache check
538 
539 
540   -- from the IGN get the MLS_APPS schema if it exists, otherwise default it
541   -- Only do this if MLS is enabled.
542   if ad_apps_private.is_mls is null then
543     ad_apps_private.initialize(aol_or_apps_schema);
544   end if;
545 
546   if is_mls then
547    IF ( g_Un_Cache_Tbl.COUNT <> 0 AND g_Un_Cache_Tbl.EXISTS (ign||'_mls') ) THEN
548      l_mls_apps_schema := g_Un_Cache_Tbl(ign||'_mls') ;
549    ELSE -- if cache check 2
550     BEGIN --BLock 2
551       c := dbms_sql.open_cursor;
552       c_statement:= 'select oracle_username from '||
553                   aol_or_apps_schema||'.fnd_oracle_userid '||
554                   'where (install_group_num = :install_group_num '||
555                   '      or install_group_num = '||
556                   '           (select min(install_group_num) from '||
557                   aol_or_apps_schema||'.fnd_oracle_userid '||
558                   '     where 1 = decode (:install_group_num,0,1,2) '||
559                   '     and read_only_flag = ''M'')) '||
560                   'and read_only_flag = ''M'' ';
561       dbms_sql.parse(c, c_statement, dbms_sql.native);
562       dbms_sql.bind_variable(c,'install_group_num',ign);
563       dbms_sql.define_column(c,1,l_mls_apps_schema,30);
564       rows_processed := dbms_sql.execute(c);
565       if dbms_sql.fetch_rows(c) > 0 then
566         dbms_sql.column_value(c,1,l_mls_apps_schema);
567       else
568         raise no_data_found;
569       end if;
570       dbms_sql.close_cursor(c);
571       g_Un_Cache_Tbl(ign||'_mls') := l_mls_apps_schema ;
572     EXCEPTION
573       when others then
574         dbms_sql.close_cursor(c);
575         ad_apps_private.error_buf := 'c_statement='||c_statement||': '||
576                                      ad_apps_private.error_buf;
577         raise;
578     END ; -- Block 2
579    END IF ; -- if cache check 2
580   END IF ;
581 
582 apps_schema := l_apps_schema;
583 apps_mls_schema := l_mls_apps_schema;
584 
585 exception
586   when others then
587     ad_apps_private.error_buf := 'get_apps_schema_name('||ign||
588                 ','||aol_or_apps_schema||'): '||ad_apps_private.error_buf;
589     raise;
590 END get_apps_schema_name;
591 
592 procedure drop_object
596 IS
593            (target_schema in varchar2,
594             object_name   in varchar2,
595             object_type   in varchar2)
597   c                     integer;
598   rows_processed        integer;
599   statement             varchar2(1000);
600   object_not_exist      exception;
601   pragma exception_init(object_not_exist, -4043);
602   table_view_not_exist  exception;
603   pragma exception_init(table_view_not_exist, -942);
604   trigger_not_exist     exception;
605   pragma exception_init(trigger_not_exist, -4080);
606   synonym_not_exist     exception;
607   pragma exception_init(synonym_not_exist, -1434);
608   sequence_not_exist     exception;
609   pragma exception_init(sequence_not_exist, -2289);
610 begin
611   -- don't use apps_ddl here because this is called in the
612   -- procedure that creates the apps_ddl code, so apps_ddl cannot be
613   -- called before it is created
614   c := dbms_sql.open_cursor;
615   statement :='drop '||object_type||' '||target_schema||'."'||object_name||'"';
616   dbms_sql.parse(c, statement, dbms_sql.native);
617   rows_processed := dbms_sql.execute(c);
618   dbms_sql.close_cursor(c);
619 exception
620   -- trap ora -4043 (Object xxx does not exist)
621   when object_not_exist then
622     dbms_sql.close_cursor(c);
623     if upper(object_type) = 'PROCEDURE' or
624        upper(object_type) = 'PACKAGE' or
625        upper(object_type) = 'PACKAGE BODY' then
626       null;
627     else
628       ad_apps_private.error_buf := 'drop_object('||target_schema||','||
629                 object_name||
630                 ','||object_type||'): '||ad_apps_private.error_buf;
631       raise;
632     end if;
633   -- trap ora -942 (Table or view xxx does not exist)
634   when table_view_not_exist then
635     dbms_sql.close_cursor(c);
636     if upper(object_type) = 'VIEW' then
637       null;
638     else
639       ad_apps_private.error_buf := 'drop_object('||target_schema||','||
640                 object_name||
641                 ','||object_type||'): '||ad_apps_private.error_buf;
642       raise;
643     end if;
644   -- trap ora -4080 (Trigger does not exist)
645   when trigger_not_exist then
646     dbms_sql.close_cursor(c);
647     if upper(object_type) = 'TRIGGER' then
648       null;
649     else
650       ad_apps_private.error_buf := 'drop_object('||target_schema||','||
651                 object_name||
652                 ','||object_type||'): '||ad_apps_private.error_buf;
653       raise;
654     end if;
655   -- trap ora -1434 (Synonym does not exist)
656   when synonym_not_exist then
657     dbms_sql.close_cursor(c);
658     if upper(object_type) = 'SYNONYM' then
659       null;
660     else
661       ad_apps_private.error_buf := 'drop_object('||target_schema||','||
662                 object_name||','||object_type||'): '||
663                 ad_apps_private.error_buf;
664       raise;
665     end if;
666   -- trap ora -2289 (Sequence does not exist)
667   when sequence_not_exist then
668     dbms_sql.close_cursor(c);
669     if upper(object_type) = 'SEQUENCE' then
670       null;
671     else
672       ad_apps_private.error_buf := 'drop_object('||target_schema||','||
673                 object_name||','||object_type||'): '||
674                 ad_apps_private.error_buf;
675       raise;
676     end if;
677   when others then
678     dbms_sql.close_cursor(c);
679     ad_apps_private.error_buf := 'drop_object('||target_schema||','||
680                 object_name||
681                 ','||object_type||'): '||ad_apps_private.error_buf;
682     raise;
683 end drop_object;
684 
685 
686 procedure copy_view
687            (view_name   in varchar2,
688             from_schema in varchar2,
689             to_schema   in varchar2)
690 is
691   error_comp_or_validate_object exception;
692   PRAGMA EXCEPTION_INIT(error_comp_or_validate_object, -4045);
693   extra_buf varchar2(200);
694 begin
695   extra_buf := null;
696 --
697 -- wrap call to copy_view_internal in a begin/end block to handle
698 -- the exception.  Only try to remedy the exception once, then call
699 -- copy_view_internal again.  If the second call fails, just fail.
700 --
701   begin
702     ad_apps_private.copy_view_internal(view_name, from_schema, to_schema);
703   exception
704     when others then
705       --
706       --
707       -- Put the "Stack Trace" info in the extra_buf string
708 
709       extra_buf := extra_buf ||
710                    ' +++<drop_object('||to_schema||','||view_name||', VIEW)+++';
711       --
712       -- Try dropping the view
713       begin
714          -- dbms_output.put_line('Dropping view '||to_schema||'.'||view_name);
715          drop_object(to_schema, view_name, 'VIEW');
716        exception
717          when others then
718            raise;
719       end;
720 
721       -- try to recompile dependent objects
722       -- Put the "Stack Trace" info in the extra_buf string
723 
724       extra_buf := ' +++(ad_apps_private.recomp_referenced_objs('||view_name||
725                    ',VIEW,'||from_schema||','||to_schema||'))+++ ';
726 
727       begin
728         ad_apps_private.recomp_referenced_objs(view_name, 'VIEW',
729                                                from_schema, to_schema);
730 
734         -- try creating the view again
731         extra_buf := '+++(ad_apps_private.copy_view_internal('||
732                      view_name||','||from_schema||','||to_schema||')+++';
733 
735         ad_apps_private.copy_view_internal(view_name, from_schema, to_schema);
736 
737       exception
738         when others then
739           -- Ignore any compilation errors. If a dependent view is invalid,
740           -- the hope is that by the time we have finished all of the views,
741           -- the dependent view will be valid again. (Bug 2361208)
742           null;
743       end; -- end of second try at copying views.
744       -- in all cases, clear the buffer. We will report any views that didn't
745       -- compile in the calling routine
746 
747       extra_buf := null;
748 
749     end; -- end of first attempt at copying views.
750 exception
751   when others then
752     ad_apps_private.error_buf := 'ad_apps_private.copy_view('||view_name||','
753       ||from_schema||','||to_schema||'): '|| extra_buf ||
754       ad_apps_private.error_buf;
755     raise;
756 end copy_view;
757 
758 
759 procedure copy_view_internal
760            (view_name   in varchar2,
761             from_schema in varchar2,
762             to_schema   in varchar2)
763 is
764   success_with_comp_error exception;
765   PRAGMA EXCEPTION_INIT(success_with_comp_error, -24344);
766   view_text             varchar2(32760);
767   statement             varchar2(32760);
768   view_columns          varchar2(32760);
769   temp_len              pls_integer;
770 begin
771 --
772 -- Outer block to handle huge views
773 --
774   declare
775     numeric_or_value_error exception;
776     pragma exception_init(numeric_or_value_error, -6502);
777     view_size number;
778   begin
779 
780     temp_len := 0;
781 
782     select text into view_text from dba_views
783     where owner = upper(copy_view_internal.from_schema)
784     and   view_name = copy_view_internal.view_name;
785 
786     if view_text is null then
787       raise numeric_or_value_error;
788     end if;
789 
790     ad_apps_private.build_view_columns(copy_view_internal.from_schema,
791                         copy_view_internal.view_name, view_columns);
792 
793     temp_len := length(view_columns) + length(view_text)
794                 + length(copy_view_internal.view_name) + 36;
795 
796     if temp_len > 30000 then
797       raise numeric_or_value_error;
798     end if;
799 
800     statement := 'create or replace force view "'||
801                      copy_view_internal.view_name||'" ' ||
802                      view_columns || ' as '|| view_text;
803 
804 --
805 -- Inner block for normal logic
806 --
807     declare
808       invalid_num_columns     exception;
809       pragma exception_init(invalid_num_columns, -1730);
810       name_already_used exception;
811       pragma exception_init(name_already_used, -955);
812     begin
813 
814       ad_apps_private.do_apps_ddl(copy_view_internal.to_schema,statement);
815 
816     exception
817       when invalid_num_columns then
818         -- trap the error ora-1730 invalid number of columns
819         -- this happens when trying to copy an invalid view that
820         -- was created on an oracle6 database using select *
821         -- syntax.  Now if the underlying table has changed shape
822         -- the number of columns in the view will not match the
823         -- number being selected, thus causing this error.
824         -- We will skip this view as it is inherently invalid,
825         -- and cannot be created even with the force option.
826         -- This happens for some R9 views after an upgrade, and
827         -- may happen for custom views as well.  This is not
828         -- a problem for any views created on oracle7 because
829         -- Oracle7 will convert the select * into the column list.
830         null;
831       when name_already_used then
832         -- first reset error buf
833         ad_apps_private.error_buf := null;
834         -- drop any synonym that may exist by the same name
835         ad_apps_private.drop_object(copy_view_internal.to_schema,
836                 view_name, 'SYNONYM');
837         ad_apps_private.do_apps_ddl(copy_view_internal.to_schema,statement);
838       when others then
839         raise;
840     end;
841 --
842 -- End inner block
843 --
844   exception
845     when numeric_or_value_error then
846       if temp_len > 30000 then
847    -- reset main error buffer
848    ad_apps_private.error_buf := null;
849 
850    -- Call copy_huge_view
851 
852    ad_apps_private.copy_huge_view(copy_view_internal.view_name,
853       copy_view_internal.from_schema, copy_view_internal.to_schema);
854       else
855  --
856  -- handle case where view text > 32 K
857  --
858  select dv.text_length
859  into view_size
860  from dba_views dv
861  where dv.view_name= copy_view_internal.view_name
862  and   dv.owner= upper(copy_view_internal.from_schema);
863 
864  -- Compare against 24000, since the actual 'create view'
865  -- statement will have some column names, etc. added on
866 
867  if view_size < 24000 then
868    raise;
869  else
870    -- reset main error buffer
871    ad_apps_private.error_buf := null;
872 
876       copy_view_internal.from_schema, copy_view_internal.to_schema);
873    -- Call copy_huge_view
874 
875    ad_apps_private.copy_huge_view(copy_view_internal.view_name,
877 
878  end if;
879       end if;
880     when others then
881       raise;
882   end;
883 --
884 -- End outer block
885 --
886 exception
887   when success_with_comp_error then
888 --
889 -- Trap and ignore ORA-24344: success with compilation error
890 -- This only happens on ORACLE 8
891 --
892     -- reset main error buffer
893     ad_apps_private.error_buf := null;
894   when others then
895     ad_apps_private.error_buf := 'ad_apps_private.copy_view_internal('||
896       view_name||','||from_schema||','||to_schema||'): '||
897       ad_apps_private.error_buf;
898     raise;
899 
900 end copy_view_internal;
901 
902 
903 procedure copy_huge_view
904            (view_name  in varchar2,
905             fromschema in varchar2,
906             toschema   in varchar2)
907 is
908   success_with_comp_error exception;
909   PRAGMA EXCEPTION_INIT(success_with_comp_error, -24344);
910   statement             varchar2(256);
911   view_columns          varchar2(32760);
912   row_count             integer;
913   position              number;
914   curr_value            varchar2(256);
915   val_length            number;
916   value_max_size        number;
917   c                     integer;
918   rows_processed        integer;
919 begin
920 --
921 -- We count on the size of each element of a varchar2s table being
922 --   of size 256 per this declaration taken from RDBMS v7.1 pvtsql.sql
923 --
924 -- type varchar2s is table of varchar2(256) index by binary_integer;
925 --
926 
927   value_max_size := 256;
928 
929 --  statement := 'create or replace force view "'||
930 --                   copy_huge_view.view_name||'" ' ||
931 --                     view_columns || ' as '|| view_text;
932 
933 --
934 -- create first line of 'create view' statement
935 --
936 
937   row_count := 1;
938 
939   statement := 'create or replace force view "'||
940     copy_huge_view.view_name||'" ';
941 
942   ad_apps_private.do_array_assignment(copy_huge_view.toschema,
943                 statement, row_count);
944 
945 --
946 -- Add in view columns
947 --
948 
949   ad_apps_private.build_view_columns(copy_huge_view.fromschema,
950                         copy_huge_view.view_name, view_columns);
951 
952 -- for substr, position 1 is first character
953 
954   position := 1;
955   val_length := value_max_size;
956 
957   while val_length = value_max_size loop
958     curr_value := substr(view_columns, position, value_max_size);
959     val_length := length(curr_value);
960 
961     row_count := row_count + 1;
962 
963     ad_apps_private.do_array_assignment(copy_huge_view.toschema,
964                 curr_value, row_count);
965 
966     position := position + val_length;
967   end loop;
968 
969 --
970 -- Add in ' as '
971 --
972 
973   statement := ' as ';
974   row_count := row_count + 1;
975 
976   ad_apps_private.do_array_assignment(copy_huge_view.toschema,
977       statement, row_count);
978 
979 --
980 -- Add in view select text
981 --
982 
983 -- for long column, position zero is first character
984 
985   position := 0;
986   val_length := value_max_size;
987 
988 -- create select statement to get value from dba_views
989 
990   c := sys.dbms_sys_sql.open_cursor;
991   statement := 'select text into :view_text from dba_views '||
992     'where owner='''||copy_huge_view.fromschema||''' '||
993     'and view_name='''||copy_huge_view.view_name||'''';
994 
995   sys.dbms_sys_sql.parse(c, statement, dbms_sql.native);
996   sys.dbms_sys_sql.define_column_long(c,1);
997   rows_processed := sys.dbms_sys_sql.execute(c);
998 
999   if sys.dbms_sys_sql.fetch_rows(c) > 0 then
1000     while val_length = value_max_size loop
1001       sys.dbms_sys_sql.column_value_long(c,1,value_max_size,position,
1002            curr_value,val_length);
1003 
1004       row_count := row_count + 1;
1005 
1006       ad_apps_private.do_array_assignment(copy_huge_view.toschema,
1007         curr_value, row_count);
1008 
1009       position := position + val_length;
1010     end loop;
1011   else
1012     sys.dbms_sys_sql.close_cursor(c);
1013     ad_apps_private.error_buf := 'statement='||statement||
1014        ':'||ad_apps_private.error_buf;
1015     raise no_data_found;
1016   end if;
1017 
1018   sys.dbms_sys_sql.close_cursor(c);
1019 
1020 --
1021 -- Execute create view statement using apps_array_ddl
1022 --
1023 
1024   declare
1025     invalid_num_columns     exception;
1026     pragma exception_init(invalid_num_columns, -1730);
1027     name_already_used exception;
1028     pragma exception_init(name_already_used, -955);
1029   begin
1030     -- execute the array of statement.
1031     ad_apps_private.do_apps_array_ddl(copy_huge_view.toschema, 1, row_count);
1032   exception
1033     when invalid_num_columns then
1037       -- syntax.  Now if the underlying table has changed shape
1034       -- trap the error ora-1730 invalid number of columns
1035       -- this happens when trying to copy an invalid view that
1036       -- was created on an oracle6 database using select *
1038       -- the number of columns in the view will not match the
1039       -- number being selected, thus causing this error.
1040       -- We will skip this view as it is inherently invalid,
1041       -- and cannot be created even with the force option.
1042       -- This happens for some R9 views after an upgrade, and
1043       -- may happen for custom views as well.  This is not
1044       -- a problem for any views created on oracle7 because
1045       -- Oracle7 will convert the select * into the column list.
1046       null;
1047     when name_already_used then
1048       -- first reset error buf
1049       ad_apps_private.error_buf := null;
1050       -- drop any synonym that may exist by the same name
1051       ad_apps_private.drop_object(copy_huge_view.toschema,
1052                 view_name, 'SYNONYM');
1053       ad_apps_private.do_apps_array_ddl(copy_huge_view.toschema, 1, row_count);
1054     when others then
1055       raise;
1056     end;
1057 
1058 exception
1059   when success_with_comp_error then
1060 --
1061 -- Trap and ignore ORA-24344: success with compilation error
1062 -- This only happens on ORACLE 8
1063 --
1064     -- reset main error buffer
1065     ad_apps_private.error_buf := null;
1066   when others then
1067     ad_apps_private.error_buf := 'copy_huge_view('||
1068         view_name||','||fromschema||','||toschema||'): '||
1069          ad_apps_private.error_buf;
1070     raise;
1071 
1072 end copy_huge_view;
1073 
1074 
1075 procedure compare_view_text
1076            (view_name  in         varchar2,
1077             fromschema in         varchar2,
1078             toschema   in         varchar2,
1079             from_len   in         number,
1080             to_len     in         number,
1081             equal      out nocopy varchar2)
1082 is
1083   max_easy_len   number;
1084   local_equal    varchar2(10);
1085   extra_err_info varchar2(100);
1086   src_vw_text    varchar2(32760);
1087   dst_vw_text    varchar2(32760);
1088   c1             integer;
1089   statement1     varchar2(256);
1090   position1       number;
1091   val_length1     number;
1092   c2             integer;
1093   statement2     varchar2(256);
1094   position2       number;
1095   val_length2     number;
1096   rows_processed integer;
1097 begin
1098   -- Initialize variables
1099 
1100   local_equal := 'FALSE';
1101   equal := local_equal;
1102   max_easy_len := 32760; -- must match declarations of (src|dst)_vw_text
1103 
1104   -- Return FALSE if view lengths not equal
1105 
1106   if from_len <> to_len then
1107     return;
1108   end if;
1109 
1110   -- Do a piecewise select from the long column into the
1111   -- local variables in a loop, and keep comparing them until
1112   -- we find a difference or run out of text to compare
1113 
1114   -- Setup select for source view
1115 
1116   -- for long column, position zero is first character
1117 
1118   position1 := 0;
1119   val_length1 := max_easy_len;
1120 
1121   -- create select statement
1122 
1123   c1 := sys.dbms_sys_sql.open_cursor;
1124   statement1 := 'select text into :view_text from dba_views '||
1125   'where owner=upper('''||fromschema||''') '||
1126   'and view_name=upper('''||view_name||''') '||
1127   'and text_length='||from_len;
1128 
1129   sys.dbms_sys_sql.parse(c1, statement1, dbms_sql.native);
1130   sys.dbms_sys_sql.define_column_long(c1,1);
1131   rows_processed := sys.dbms_sys_sql.execute(c1);
1132 
1133   if sys.dbms_sys_sql.fetch_rows(c1) <= 0 then
1134     sys.dbms_sys_sql.close_cursor(c1);
1135     extra_err_info := ' <L SRC> ';
1136     raise no_data_found;
1137   end if;
1138 
1139   -- Setup select for dest view
1140 
1141   position2 := 0;
1142   val_length2 := max_easy_len;
1143 
1144   -- create select statement
1145 
1146   c2 := sys.dbms_sys_sql.open_cursor;
1147   statement2 := 'select text into :view_text from dba_views '||
1148   'where owner=upper('''||toschema||''') '||
1149   'and view_name=upper('''||view_name||''') '||
1150   'and text_length='||to_len;
1151 
1152   sys.dbms_sys_sql.parse(c2, statement2, dbms_sql.native);
1153   sys.dbms_sys_sql.define_column_long(c2,1);
1154   rows_processed := sys.dbms_sys_sql.execute(c2);
1155 
1156   if sys.dbms_sys_sql.fetch_rows(c2) <= 0 then
1157     sys.dbms_sys_sql.close_cursor(c2);
1158     extra_err_info := ' <L DST> ';
1159     raise no_data_found;
1160   end if;
1161 
1162   -- loop through chunks of view text and compare them
1163 
1164   while val_length1 = max_easy_len loop
1165 
1166     -- Get chunk of source view text
1167 
1168     sys.dbms_sys_sql.column_value_long(c1, 1, max_easy_len, position1,
1169          src_vw_text, val_length1);
1170 
1171     position1 := position1 + val_length1;
1172 
1173     -- Get chunk of destination view text
1174 
1175     sys.dbms_sys_sql.column_value_long(c2, 1, max_easy_len, position2,
1176          dst_vw_text, val_length2);
1177 
1181 
1178     position2 := position2 + val_length2;
1179 
1180     -- compare chunks
1182     if src_vw_text <> dst_vw_text then
1183 
1184       -- views not equal
1185 
1186       sys.dbms_sys_sql.close_cursor(c1);
1187       sys.dbms_sys_sql.close_cursor(c2);
1188       return;
1189     end if;
1190 
1191   end loop;
1192 
1193   -- If we got this far, the views are equal
1194 
1195   sys.dbms_sys_sql.close_cursor(c1);
1196   sys.dbms_sys_sql.close_cursor(c2);
1197 
1198   local_equal := 'TRUE';
1199   equal := local_equal;
1200   return;
1201 
1202 exception
1203   when others then
1204     ad_apps_private.error_buf := 'compare_view_text('||
1205         view_name||','||fromschema||','||toschema||
1206         ','||from_len||','||to_len||','||local_equal||')'||
1207         extra_err_info||': '||
1208          ad_apps_private.error_buf;
1209     raise;
1210 
1211 end compare_view_text;
1212 
1213 
1214 procedure copy_code
1215            (object_name in varchar2,
1216             object_type in varchar2,
1217             from_schema in varchar2,
1218             to_schema   in varchar2)
1219 is
1220   success_with_comp_error exception;
1221   PRAGMA EXCEPTION_INIT(success_with_comp_error, -24344);
1222   source_text           varchar2(2000);
1223   row_count             integer;
1224   prog_text             varchar2(32760);
1225   cursor c1 is
1226     select text from dba_source
1227     where owner = upper(copy_code.from_schema)
1228     and name = copy_code.object_name
1229     and type = copy_code.object_type
1230     order by line;
1231   cursor PKG_HEADER (c_owner in varchar2,
1232                      c_name  in varchar2,
1233                      c_type  in varchar2) is
1234     select
1235        substr(s.text, instr(s.text,'$Header'||': '),
1236               ((instr(s.text,' $', instr(s.text,'$Header'||': ')) + 2)
1237                - instr(s.text,'$Header'||': ')))
1238     from dba_source s
1239     where s.owner= upper(c_owner)
1240     and   s.name = upper(c_name)
1241     and   s.type = upper(c_type)
1242     and   s.line between 2 and 5
1243     and   s.text like '%$Header'||': % $%';
1244   header_string         varchar2(500);
1245 begin
1246   -- first get the source text
1247   -- purposely starting counter at 1 as later we add the
1248   -- create or replace at line 1
1249   row_count:=1;
1250   for c1rec in c1 loop
1251     row_count:=row_count+1;
1252 
1253     -- check line length
1254     --
1255     -- If longer than 255 characters, check to see if package contains
1256     --  a Header string.
1257     --   If so, fail
1258     --   If not, skip copying package and return successfully
1259     -- The assumption here is that a package without a Header string is
1260     --   not an Oracle Applications package, so we can safely skip copying
1261     --   the package.
1262 
1263     if length(c1rec.text) > 255 then
1264 
1265       open PKG_HEADER(from_schema, object_name, object_type);
1266 
1267       fetch PKG_HEADER
1268       into header_string;
1269 
1270       if PKG_HEADER%NOTFOUND then
1271         -- no header, so just return without copying PKG
1272 
1273         close PKG_HEADER;
1274         return;
1275 
1276       else
1277         -- has header, so fail
1278 
1279         close PKG_HEADER;
1280         raise_application_error(-20000,
1281           object_type||' '||from_schema||'.'||object_name||
1282           ': Line '||to_char(row_count-1)||' longer than 255 characters.');
1283       end if;
1284 
1285     end if;
1286 
1287     -- build one line of sql statement in the global variable in
1288     -- the global array variable in to schema.
1289 
1290     ad_apps_private.do_array_assignment(copy_code.to_schema,
1291                 c1rec.text, row_count);
1292   end loop;
1293   -- once we have fetched all source
1294   -- then create the object
1295   declare
1296     statement           varchar2(256);
1297     name_already_used   exception;
1298     pragma exception_init(name_already_used, -955);
1299   begin
1300     statement := 'create or replace ';
1301     -- build the first line of the array of sql statement
1302     ad_apps_private.do_array_assignment(copy_code.to_schema, statement, 1);
1303     -- execute the array of statement.
1304     ad_apps_private.do_apps_array_ddl(copy_code.to_schema, 1, row_count);
1305   exception
1306     when name_already_used then
1307       -- first reset error buf
1308       ad_apps_private.error_buf := null;
1309       -- drop any synonym by such name and retry
1310       ad_apps_private.drop_object(copy_code.to_schema,
1311                   copy_code.object_name, 'SYNONYM');
1312       ad_apps_private.do_apps_array_ddl(copy_code.to_schema, 1, row_count);
1313   end;
1314 exception
1315   when success_with_comp_error then
1316 --
1317 -- Trap and ignore ORA-24344: success with compilation error
1318 -- This only happens on ORACLE 8
1319 --
1320     -- reset main error buffer
1321     ad_apps_private.error_buf := null;
1322   when others then
1323     ad_apps_private.error_buf := 'ad_apps_private.copy_code('||object_name||','
1327 
1324         ||object_type||','||from_schema||','||to_schema||'): '
1325         || ad_apps_private.error_buf;
1326     raise;
1328 end copy_code;
1329 
1330 
1331 procedure compare_code
1332            (object_name in         varchar2,
1333             object_type in         varchar2,
1334             from_schema in         varchar2,
1335             to_schema   in         varchar2,
1336             comp_level  in         varchar2,
1337             equal       out nocopy varchar2)
1338 is
1339   cursor LINE_COUNT (c_owner in varchar2,
1340                      c_name  in varchar2,
1341                      c_type  in varchar2) is
1342     select count(*)
1343     from dba_source
1344     where owner = upper(c_owner)
1345     and   name  = upper(c_name)
1346     and   type  = upper(c_type);
1347   cursor LINE_AND_CHAR_COUNT (c_owner in varchar2,
1348                            c_name  in varchar2,
1349                            c_type  in varchar2) is
1350     select count(*), sum(length(text))
1351     from dba_source
1352     where owner = upper(c_owner)
1353     and   name  = upper(c_name)
1354     and   type  = upper(c_type);
1355   cursor SET_DIFFERENCE (s_owner in varchar2,
1356                          d_owner in varchar2,
1357                          c_name  in varchar2,
1358                          c_type  in varchar2) is
1359      SELECT /*+FIRST_ROWS */
1360          'X'
1361      FROM
1362         dba_source ds1,
1363         dba_source ds2
1364      WHERE
1365            ds1.owner = UPPER(s_owner)
1366      AND   ds1.name  = UPPER(c_name )
1367      AND   ds1.type  = UPPER(c_type )
1368      AND   ds2.owner = UPPER(d_owner)
1369      AND   ds2.name  = UPPER(c_name )
1370      AND   ds2.type  = UPPER(c_type )
1371      AND  (ds1.line <> ds2.line
1372      OR    ds1.text <> ds2.text     )
1373      AND   rownum =1;
1374   local_equal    varchar2(10);
1375   dummy_text     varchar2(100);
1376   extra_err_info varchar2(100);
1377   source_num_lines   number;
1378   dest_num_lines     number;
1379   source_num_chars   number;
1380   dest_num_chars     number;
1381 begin
1382   -- Exit immediately if comp_level = 'none'
1383 
1384   if lower(comp_level) = 'none' then
1385     local_equal := 'TRUE';
1386     equal := local_equal;
1387     return;
1388   end if; -- caller doesn't really want comparison
1389 
1390   -- Initialize variables
1391 
1392   local_equal := 'FALSE';
1393   equal := local_equal;
1394 
1395   --
1396   --   comp_level valid values, and what they mean:
1397   --
1398   --     none   : return "equal" without comparing objects
1399   --
1400   --     lines  : compare number of source lines in each object
1401   --              return "equal" if same number of source lines
1402   --
1403   --     chars  : compare number of source lines and number of
1404   --              source chars in each object
1405   --              return "equal" if same number of source lines and chars
1406   --
1407   --     full   : compare number of source lines in each object,
1408   --              then compare actual source text
1409   --              return "equal" only if exactly equal
1410   --
1411 
1412   -- Validate comparison level
1413 
1414   dummy_text := lower(comp_level);
1415 
1416   if dummy_text <> 'none' and
1417      dummy_text <> 'lines' and
1418      dummy_text <> 'chars' and
1419      dummy_text <> 'full' then
1420 
1421     extra_err_info := ' <Invalid comp_level: '''||comp_level||'''> ';
1422     raise no_data_found;
1423   end if; -- validation
1424 
1425   -- If 'lines' or 'full' specified, get number of source lines
1426 
1427   if lower(comp_level) = 'lines' or
1428      lower(comp_level) = 'full' then
1429 
1430     -- Get number of source lines for source object
1431 
1432     open LINE_COUNT(from_schema, object_name, object_type);
1433 
1434     fetch LINE_COUNT
1435     into source_num_lines;
1436 
1437     close LINE_COUNT;
1438 
1439     -- Get number of source lines for destination object
1440 
1441     open LINE_COUNT(to_schema, object_name, object_type);
1442 
1443     fetch LINE_COUNT
1444     into dest_num_lines;
1445 
1446     close LINE_COUNT;
1447 
1448     -- return not equal if number of lines is not the same
1449 
1450     if source_num_lines <> dest_num_lines then
1451       return;
1452     end if;
1453 
1454     -- Exit and claim objects equal if comp_level = 'lines'
1455 
1456     if lower(comp_level) = 'lines' then
1457       local_equal := 'TRUE';
1458       equal := local_equal;
1459       return;
1460     end if; -- comp_level is lines
1461 
1462   end if; -- comp_level is 'lines' or 'full'
1463 
1464   -- compute number of lines and chars at same time if
1465   -- comp_level is chars
1466 
1467   if lower(comp_level) = 'chars' then
1468 
1469     -- Get number of source lines and chars for source object
1470 
1471     open LINE_AND_CHAR_COUNT(from_schema, object_name, object_type);
1472 
1473     fetch LINE_AND_CHAR_COUNT
1474     into source_num_lines, source_num_chars;
1475 
1476     close LINE_AND_CHAR_COUNT;
1477 
1481 
1478     -- Get number of source lines and chars for destination object
1479 
1480     open LINE_AND_CHAR_COUNT(to_schema, object_name, object_type);
1482     fetch LINE_AND_CHAR_COUNT
1483     into dest_num_lines, dest_num_chars;
1484 
1485     close LINE_AND_CHAR_COUNT;
1486 
1487     -- return not equal if number of lines is not the same
1488 
1489     if source_num_lines <> dest_num_lines then
1490       return;
1491     end if;
1492 
1493     -- return not equal if number of chars is not the same
1494 
1495     if source_num_chars <> dest_num_chars then
1496       return;
1497     end if;
1498 
1499     -- Exit success because comp_level = 'chars'
1500 
1501     local_equal := 'TRUE';
1502     equal := local_equal;
1503     return;
1504 
1505   end if; -- comp_level is chars
1506 
1507   -- Do full text compare using set difference
1508 
1509   if lower(comp_level) = 'full' then
1510     -- Open set difference cursor, select from it, and see if
1511     -- any rows are returned
1512 
1513     open SET_DIFFERENCE (from_schema, to_schema, object_name, object_type);
1514 
1515     fetch SET_DIFFERENCE
1516     into dummy_text;
1517 
1518     if SET_DIFFERENCE%NOTFOUND then
1519       -- no rows returned: objects are equal
1520 
1521       close SET_DIFFERENCE;
1522       local_equal := 'TRUE';
1523       equal := local_equal;
1524       return;
1525     else
1526       -- a row was returned: objects not equal
1527 
1528       close SET_DIFFERENCE;
1529       return;
1530     end if;
1531 
1532   end if; -- user specified full compare
1533 
1534   -- If we got this far, we had a logic error somewhere above
1535 
1536   extra_err_info := ' <internal logic error> ';
1537   raise no_data_found;
1538 
1539 exception
1540   when others then
1541     ad_apps_private.error_buf := 'ad_apps_private.compare_code('||
1542       object_name||','||object_type||','||from_schema||','||to_schema||
1543       ','||comp_level||','||local_equal||')'||extra_err_info||': '||
1544       ad_apps_private.error_buf;
1545     raise;
1546 
1547 end compare_code;
1548 
1549 
1550 procedure create_base_gs
1551            (base_schema in varchar2,
1552             apps_schema in varchar2,
1553             force       in varchar2)
1554 is
1555   name_already_used     exception;
1556   pragma exception_init(name_already_used, -955);
1557 
1558   --
1559   -- In 'union all' statements corresponding columns must have
1560   -- the same data type. PL/SQL uses first select to determine the
1561   -- column type. If the other select statements return a different
1562   -- (or in this case longer varchar2) data type it raises
1563   -- 'ORA-06502: PL/SQL: numeric or value' error.
1564   -- Because of that we need to rpad 'TABLE' with extra 3 spaces.
1565   -- Code uses rtrim() to remove them.
1566   -- bug1301043.
1567   --
1568   cursor grants_cursor is
1569     (select table_name object_name, 'TABLE   ' object_type
1570      from dba_tables
1571      where owner= upper(base_schema)
1572      and   iot_name is null
1573      and   table_name not like '%$%'
1574      minus
1575      select queue_table object_name, 'TABLE   ' object_type
1576      from dba_queue_tables
1577      where owner= upper(base_schema)
1578      and   queue_table not like '%$%')
1579     union all
1580     select sequence_name object_name, 'SEQUENCE' object_type
1581     from dba_sequences
1582     where sequence_owner= upper(base_schema)
1583     and sequence_name not like '%$%';
1584 
1585   cursor synonyms_cursor is
1586     (select table_name object_name, 'TABLE   ' object_type
1587      from dba_tables dt
1588      where owner= upper(base_schema)
1589      and   iot_name is null
1590      and   table_name not like '%$%'
1591      minus
1592      select queue_table object_name, 'TABLE   ' object_type
1593      from dba_queue_tables
1594      where owner= upper(base_schema)
1595      and   queue_table not like '%$%')
1596     minus
1597     select ds.synonym_name object_name, 'TABLE   ' object_type
1598     from dba_synonyms ds
1599     where ds.owner = upper(apps_schema)
1600     and   ds.table_owner  = upper(base_schema)
1601     and   ds.synonym_name = ds.table_name
1602     and   ds.table_name not like '%$%'
1603     union all
1604     select sequence_name object_name, 'SEQUENCE' object_type
1605     from dba_sequences seq
1606     where sequence_owner= upper(base_schema)
1607     and sequence_name not like '%$%'
1608     minus
1609     select ds.synonym_name object_name, 'SEQUENCE' object_type
1610     from dba_synonyms ds
1611     where ds.owner = upper(apps_schema)
1612     and   ds.table_owner  = upper(base_schema)
1613     and   ds.synonym_name = ds.table_name
1614     and   ds.table_name not like '%$%';
1615 
1616   statement varchar2(500);
1617   what_part varchar2(30);
1618   found_cust varchar2(10);
1619   cust_correct varchar2(10);
1620   cust_row_index number;
1621 begin
1622   -- Create grants (whether they exist already or not)
1623 
1624   what_part := 'In Grants Loop:';
1625 
1626   for grant_rec in grants_cursor loop
1627      create_grant(p_grantor_schema_name => base_schema,
1628     p_grantee_schema_name => apps_schema,
1632   end loop;
1629     p_object_name         => rtrim(grant_rec.object_name),
1630     p_privileges          => 'ALL',
1631     p_with_grant_option   => TRUE);
1633 
1634   -- Drop synonyms (if force='TRUE')
1635 
1636   what_part := 'In Drop Synonyms Loop:';
1637 
1638   if force = 'TRUE' then
1639     for drop_rec in grants_cursor loop
1640 
1641       -- Check to see if this is an active exception object
1642 
1643       if matching_exception_object(base_schema, rtrim(drop_rec.object_name),
1644                                    rtrim(drop_rec.object_type),
1645                                    'STANDARD_EXCEPTION',
1646                                    apps_schema, found_cust, cust_correct,
1647                                    cust_row_index) then
1648         --
1649         -- Active 'STANDARD_EXCEPTION' exception object
1650         --
1651         -- If customized object in APPS exists and is a synonym, drop it.
1652         -- Otherwise, don't do anything
1653         --
1654         if     found_cust = 'TRUE'
1655            and apps_type(cust_row_index) = 'SYNONYM' then
1656 
1657           ad_apps_private.drop_object(apps_schema, apps_name(cust_row_index),
1658                                       'SYNONYM');
1659         end if;
1660         -- end if customized object exists and is synonym
1661       else
1662         -- Existing object in APPS should be a synonym.  Just drop it.
1663 
1664         ad_apps_private.drop_object(apps_schema, rtrim(drop_rec.object_name),
1665                                     'SYNONYM');
1666       end if;
1667       -- end if active exception object
1668     end loop;
1669   end if;
1670   -- end if force=TRUE
1671 
1672   -- Create synonyms (if not there, or if incorrect)
1673 
1674   what_part := 'In Synonyms Loop:';
1675 
1676   --
1677   -- Note that the query for this loop returns all base schema tables
1678   -- and synonyms for which there is not a synonym with the same name
1679   -- in APPS pointing to the table/synonym.  Because it is possible for
1680   -- the trigger object for an exception to exist and the actual exception
1681   -- object in APPS to not exist, we just skip all active exception objects
1682   -- in this loop, and handle them in another loop after this one.
1683   --
1684   for syn_rec in synonyms_cursor loop
1685 
1686     -- (re)create synonym if not an active exception object
1687 
1688     if not matching_exception_object(base_schema, rtrim(syn_rec.object_name),
1689                                      rtrim(syn_rec.object_type),
1690                                      'STANDARD_EXCEPTION',
1691                                      apps_schema, found_cust, cust_correct,
1692                                      cust_row_index) then
1693        -- not an active exception object.  Create the synonym.
1694        create_synonym(p_from_schema_name => base_schema,
1695         p_from_object_name => rtrim(syn_rec.object_name),
1696         p_to_schema_name   => apps_schema,
1697         p_to_object_name   => rtrim(syn_rec.object_name));
1698     end if;
1699     -- end if not an active exception object
1700   end loop;
1701 
1702 -- Handle active exception objects
1703 
1704   what_part := 'In Exception Objects Loop:';
1705 
1706   for excpt_rec in grants_cursor loop
1707 
1708     -- Check to see if this is an active exception object
1709 
1710     if matching_exception_object(base_schema, rtrim(excpt_rec.object_name),
1711                                  rtrim(excpt_rec.object_type),
1712                                  'STANDARD_EXCEPTION',
1713                                  apps_schema, found_cust, cust_correct,
1714                                  cust_row_index) then
1715       --
1716       -- Active 'STANDARD_EXCEPTION' exception object
1717       --
1718       -- if customized object does not exist
1719       --   if not synonym, fatal error
1720       --   if synonym, create it
1721       --
1722       -- if customized object exists and is not correct
1723       --   if not synonym, fatal error
1724       --   if synonym drop and recreate
1725       --
1726       -- if customized object exists and is correct, don't do anything
1727       --
1728       if found_cust = 'FALSE' then
1729         if apps_type(cust_row_index) <> 'SYNONYM' then
1730 
1731           -- customized object not a synonym and not there.  No way
1732           -- we can repair it in this procedure.  fatal error
1733 
1734           raise_application_error(-20001,
1735             apps_type(cust_row_index)||' '||
1736             apps_schema||'.'||apps_name(cust_row_index)||
1737             ' is missing exception object.');
1738         else
1739 
1740     -- customized object is not there, but it is a synonym
1741     -- create it
1742     DECLARE
1743        l_from_schema_name dba_objects.owner%TYPE;
1744     BEGIN
1745        IF (points_to_schema(cust_row_index) = 'BASE') THEN
1746    l_from_schema_name := base_schema;
1747         ELSE
1748    l_from_schema_name := apps_schema;
1749        END IF;
1750        create_synonym(p_from_schema_name => l_from_schema_name,
1751         p_from_object_name => points_to_name(cust_row_index),
1752         p_to_schema_name   => apps_schema,
1753         p_to_object_name   => apps_name(cust_row_index));
1754     END;
1755         end if;
1756         -- end if missing customized object is not a synonym
1757       else
1761 
1758         -- customized object exists
1759         -- if not correct and not synonym, fatal error
1760         -- if not correct and is synonym, drop and recreate it
1762         if cust_correct = 'FALSE' then
1763           if apps_type(cust_row_index) <> 'SYNONYM' then
1764 
1765             -- customized object not a synonym and not correct.  No way
1766             -- we can repair it in this procedure.  fatal error
1767 
1768             raise_application_error(-20001,
1769               apps_type(cust_row_index)||' '||
1770               apps_schema||'.'||apps_name(cust_row_index)||
1771               ' is incorrect exception object.');
1772           else
1773 
1774             -- customized object is an existing but incorrect synonym
1775             -- drop it and then recreate it
1776 
1777             -- Drop synonym
1778 
1779             ad_apps_private.drop_object(apps_schema,
1780               apps_name(cust_row_index), 'SYNONYM');
1781 
1782             -- Recreate synonym
1783      DECLARE
1784         l_from_schema_name dba_objects.owner%TYPE;
1785      BEGIN
1786         IF (points_to_schema(cust_row_index) = 'BASE') THEN
1787     l_from_schema_name := base_schema;
1788   ELSE
1789     l_from_schema_name := apps_schema;
1790         END IF;
1791         create_synonym(p_from_schema_name => l_from_schema_name,
1792          p_from_object_name => points_to_name(cust_row_index),
1793          p_to_schema_name   => apps_schema,
1794          p_to_object_name   => apps_name(cust_row_index));
1795      END;
1796           end if;
1797           -- end if incorrect customized object is not a synonym
1798         end if;
1799         -- end if customized object exists, but is not correct
1800       end if;
1801       -- end if active customization, but customized object not there
1802     end if;
1803     -- end if active exception object
1804   end loop;
1805   -- end loop to handle exception objects
1806 
1807 exception
1808   when others then
1809     ad_apps_private.error_buf := 'create_base_gs('||base_schema||','||
1810         apps_schema||'): '||what_part||ad_apps_private.error_buf;
1811     raise;
1812 end create_base_gs;
1813 
1814 procedure create_base_gs
1815            (base_schema in varchar2,
1816             apps_schema in varchar2)
1817 is
1818 begin
1819 create_base_gs (base_schema => base_schema,
1820                 apps_schema => apps_schema,
1821                 force       => 'FALSE');
1822 end;
1823 
1824 
1825 procedure create_gs
1826            (object_owner_schema in varchar2,
1827             to_schema           in varchar2,
1828             object_name         in varchar2,
1829             with_option         in boolean,
1830             privs               in varchar2,
1831             grant_from_schema   in varchar2 default null)
1832 is
1833   with_option_print varchar2(10);
1834 begin
1835    -- Perform the grant first so that the last_ddl_time on the base
1836    -- object is less than the synonym.  This facilitates the restart better
1837    -- grant all for each table/sequence
1838    create_grant(p_grantor_schema_name => object_owner_schema,
1839   p_grantee_schema_name => to_schema,
1840   p_object_name         => object_name,
1841   p_privileges          => privs,
1842   p_with_grant_option   => with_option);
1843 
1844    create_synonym(p_from_schema_name => object_owner_schema,
1845     p_from_object_name => object_name,
1846     p_to_schema_name   => to_schema,
1847     p_to_object_name   => object_name);
1848 exception
1849   when others then
1850      if with_option then
1851  with_option_print := 'TRUE';
1852       else
1853  with_option_print := 'FALSE';
1854      end if;
1855 
1856     ad_apps_private.error_buf := 'ad_apps_private.create_gs('||
1857         object_owner_schema||','||to_schema||','||object_name||
1858         ', '||with_option_print||','||privs||','||
1859         grant_from_schema||'): '||ad_apps_private.error_buf;
1860     raise;
1861 end create_gs;
1862 
1863 
1864 --
1865 -- Procedures used to create an APPS/MLS schema
1866 --
1867 
1868 procedure create_synonyms
1869            (from_schema       in varchar2,
1870             to_schema         in varchar2,
1871             grant_from_schema in varchar2 default null)
1872 is
1873   cursor c1 is
1874     select ds.synonym_name
1875     from dba_synonyms ds
1876     where ds.owner = upper(from_schema)
1877     and   ds.synonym_name = ds.table_name -- regular synonyms only
1878     and   ds.synonym_name not like '%$%';
1879   exact_syn_match       boolean;
1880   any_obj_w_this_name   boolean;
1881   type_of_obj           varchar2(200);
1882   extra_err_info        varchar2(100);
1883   name_already_used     exception;
1884   pragma exception_init(name_already_used, -955);
1885 begin
1886   for c1rec in c1 loop
1887     --
1888     -- Check for exact synonym match.  Drop and recreate synonym
1889     -- if not exact synonym match
1890     --
1891     ad_apps_private.exact_synonym_match(to_schema, c1rec.synonym_name,
1892       from_schema, c1rec.synonym_name, exact_syn_match,
1893       any_obj_w_this_name, type_of_obj);
1894 
1895     if not exact_syn_match then
1896 
1897       -- Drop existing object, if any
1898 
1899       if any_obj_w_this_name then
1900 
1901         -- Fail if table
1902         if type_of_obj = 'TABLE' then
1906         end if; -- fail if existing object is a table
1903           extra_err_info := ' <'||to_schema||'.'||c1rec.synonym_name||
1904             ' is a table.> ';
1905           raise name_already_used;
1907 
1908         -- just drop object if not a table
1909 
1910         if    type_of_obj = 'PKG_S_AND_B'
1911            or type_of_obj = 'PACKAGE'
1912            or type_of_obj = 'PACKAGE BODY' then
1913           -- existing object is package
1914           ad_apps_private.drop_object(to_schema, c1rec.synonym_name,
1915                                       'PACKAGE');
1916         else
1917           -- existing object not package
1918           ad_apps_private.drop_object(to_schema, c1rec.synonym_name,
1919                                       type_of_obj);
1920         end if; -- end if existing object is package
1921       end if;  -- end if any existing object with this name in toschema
1922 
1923       -- create grant/synonym
1924       begin
1925         if grant_from_schema is not null then
1926           ad_apps_private.create_gs(from_schema,to_schema,
1927               c1rec.synonym_name,FALSE,'ALL',grant_from_schema);
1928         else
1929           ad_apps_private.create_gs(from_schema,to_schema,
1930               c1rec.synonym_name,TRUE,'ALL');
1931         end if;
1932       exception
1933         when name_already_used then
1934           -- first reset error buf
1935           ad_apps_private.error_buf := null;
1936           -- first drop synonym
1937           ad_apps_private.drop_object(to_schema,c1rec.synonym_name,
1938                                       'SYNONYM');
1939           -- then create the synonym
1940           if grant_from_schema is not null then
1941             ad_apps_private.create_gs(from_schema,to_schema,
1942                 c1rec.synonym_name,FALSE,'ALL',grant_from_schema);
1943           else
1944             ad_apps_private.create_gs(from_schema,to_schema,
1945                 c1rec.synonym_name,TRUE,'ALL');
1946           end if;
1947       end; -- block for creating the grant/synonym
1948     end if; -- not exact synonym match: (re-)create synonym
1949   end loop; -- through all normal synonyms in APPS
1950 
1951 exception
1952   when others then
1953     ad_apps_private.error_buf := 'create_synonyms('||
1954       from_schema||','||to_schema||','||grant_from_schema||')'||
1955       extra_err_info||': '||
1956       ad_apps_private.error_buf;
1957     raise;
1958 end create_synonyms;
1959 
1960 
1961 procedure copy_odd_synonyms
1962            (fromschema in varchar2,
1963             toschema   in varchar2)
1964 is
1965   cursor c1 is
1966     select ds.synonym_name
1967     from dba_synonyms ds
1968     where ds.owner = upper(fromschema)
1969     and   ds.synonym_name <> ds.table_name; -- odd synonyms only
1970   exact_syn_match       boolean;
1971   any_obj_w_this_name   boolean;
1972   type_of_obj           varchar2(200);
1973   extra_err_info        varchar2(100);
1974   name_already_used     exception;
1975   pragma exception_init(name_already_used, -955);
1976 begin
1977   for c1rec in c1 loop
1978     --
1979     -- Check for exact synonym match.  Drop and recreate synonym
1980     -- if not exact synonym match
1981     --
1982     ad_apps_private.exact_synonym_match(toschema, c1rec.synonym_name,
1983       fromschema, c1rec.synonym_name, exact_syn_match,
1984       any_obj_w_this_name, type_of_obj);
1985 
1986     if not exact_syn_match then
1987 
1988       -- Drop existing object, if any
1989 
1990       if any_obj_w_this_name then
1991 
1992         -- Fail if table
1993         if type_of_obj = 'TABLE' then
1994           extra_err_info := ' <'||toschema||'.'||c1rec.synonym_name||
1995             ' is a table.> ';
1996           raise name_already_used;
1997         end if; -- fail if existing object is a table
1998 
1999         -- just drop object if not a table
2000 
2001         if    type_of_obj = 'PKG_S_AND_B'
2002            or type_of_obj = 'PACKAGE'
2003            or type_of_obj = 'PACKAGE BODY' then
2004           -- existing object is package
2005           ad_apps_private.drop_object(toschema, c1rec.synonym_name,
2006                                       'PACKAGE');
2007         else
2008           -- existing object not package
2009           ad_apps_private.drop_object(toschema, c1rec.synonym_name,
2010                                       type_of_obj);
2011         end if; -- end if existing object is package
2012       end if;  -- end if any existing object with this name in toschema
2013 
2014       -- create grant/synonym
2015       begin
2016         ad_apps_private.create_gs(fromschema,toschema,
2017           c1rec.synonym_name,TRUE,'ALL');
2018       exception
2019         when name_already_used then
2020           -- first reset error buf
2021           ad_apps_private.error_buf := null;
2022           -- first drop synonym
2023           ad_apps_private.drop_object(toschema, c1rec.synonym_name,
2024                                       'SYNONYM');
2025           -- then create the synonym
2026           ad_apps_private.create_gs(fromschema,toschema,
2027             c1rec.synonym_name,TRUE,'ALL');
2028       end; -- block for creating the grant/synonym
2029     end if; -- not exact synonym match: (re-)create synonym
2030   end loop; -- through all normal synonyms in APPS
2031 
2032 exception
2033   when others then
2034     ad_apps_private.error_buf := 'copy_odd_synonyms('||
2038 end copy_odd_synonyms;
2035       fromschema||','||toschema||')'||extra_err_info||': '||
2036       ad_apps_private.error_buf;
2037     raise;
2039 
2040 
2041 procedure create_special_views
2042            (install_group_num in number,
2043             aol_schema        in varchar2,
2044             apps_schema       in varchar2,
2045             create_mls_views  in boolean)
2046 is
2047   oracle_id_cursor      integer;
2048   rows_processed        integer;
2049   table_schema          varchar2(30);
2050 
2051   -- select distinct as multiple products can share the same oracleid
2052   -- select only those oracle_ids that belong to the current data
2053   -- group or the 0 datagroup (0 meaning a single install product)
2054   oracle_id_sql constant varchar2(2000) := ign_schema_select_part1||
2055           aol_schema||ign_schema_select_part2||aol_schema||
2056           ign_schema_select_part3||' in (to_char(:install_g_num), 0 )';
2057 begin
2058 
2059   oracle_id_cursor := dbms_sql.open_cursor;
2060   dbms_sql.parse(oracle_id_cursor, oracle_id_sql, dbms_sql.native);
2061   dbms_sql.bind_variable(oracle_id_cursor,'install_g_num',
2062                 create_special_views.install_group_num);
2063   dbms_sql.define_column(oracle_id_cursor,1,table_schema,30);
2064   rows_processed := dbms_sql.execute(oracle_id_cursor);
2065   loop
2066       if dbms_sql.fetch_rows(oracle_id_cursor) > 0 then
2067         dbms_sql.column_value(oracle_id_cursor,1,table_schema);
2068         -- for each schema see if any of the listed tables exist in
2069         -- that schema and create the view in the apps schema
2070         declare
2071           c                     integer;
2072           rows_processed        integer;
2073           l_table_name          varchar2(30);
2074           table_mls             varchar2(1);
2075           statement             varchar2(32000);
2076           view_column_list      varchar2(20000);
2077           select_list           varchar2(20000);
2078           max_trans_date        date;
2079           max_xref_date         date;
2080           trans_record_date     date;
2081           view_date             date;
2082           table_date            date;
2083           view_is_old           boolean;
2084         begin
2085 
2086                 -- Get value for max_trans_date
2087                 declare
2088                   c                     integer;
2089                   rows_processed        integer;
2090                   statement             varchar2(500);
2091                 begin
2092                   c := dbms_sql.open_cursor;
2093                   statement :=
2094                         'select nvl(max(last_update_date),              '||
2095                         '    to_date(''01/01/1970'',''DD/MM/YYYY''))    '||
2096                         '    from '||aol_schema||'.ak_translated_columns';
2097                   dbms_sql.parse(c, statement, dbms_sql.native);
2098                   dbms_sql.define_column(c,1,max_trans_date);
2099                   rows_processed := dbms_sql.execute(c);
2100                   loop
2101                     if dbms_sql.fetch_rows(c) > 0 then
2102                       dbms_sql.column_value(c,1,max_trans_date);
2103                     end if;
2104                     dbms_sql.close_cursor(c);
2105                     exit;
2106                   end loop;
2107                 exception
2108                   when others then
2109                     dbms_sql.close_cursor(c);
2110                     ad_apps_private.error_buf := 'statement='||
2111                                                  statement||':'||
2112                                                  ad_apps_private.error_buf;
2113                     raise;
2114                 end;
2115 
2116 
2117                 -- Get value for max_xref_date
2118                 declare
2119                   c                     integer;
2120                   rows_processed        integer;
2121                   statement             varchar2(500);
2122                 begin
2123                   c := dbms_sql.open_cursor;
2124                   statement :=
2125                         'select nvl(max(last_update_date),              '||
2126                         '   to_date(''01/01/1970'',''DD/MM/YYYY''))     '||
2127                         '   from '||aol_schema||'.ak_language_attribute_xrefs';
2128                   dbms_sql.parse(c, statement, dbms_sql.native);
2129                   dbms_sql.define_column(c,1,max_xref_date);
2130                   rows_processed := dbms_sql.execute(c);
2131                   loop
2132                     if dbms_sql.fetch_rows(c) > 0 then
2133                       dbms_sql.column_value(c,1,max_xref_date);
2134                     end if;
2135                     dbms_sql.close_cursor(c);
2136                     exit;
2137                   end loop;
2138                 exception
2139                   when others then
2140                     dbms_sql.close_cursor(c);
2141                     ad_apps_private.error_buf := 'statement='||
2142                                                  statement||':'||
2143                                                  ad_apps_private.error_buf;
2144                     raise;
2145                 end;
2146 
2147 
2148             c := dbms_sql.open_cursor;
2149 
2150             if create_mls_views then
2151               -- work on tables that are multilingual
2152               statement := 'select distinct upper(atc.table_name)           '||
2156                            'and nvl(atc.enabled_flag,''Y'') = ''Y''         '||
2153                            'from '||aol_schema||'.ak_translated_columns atc,'||
2154                            '     dba_tables dt                              '||
2155                            'where dt.table_name = upper(atc.table_name)     '||
2157                            'and dt.owner = :table_schema                    ';
2158             else
2159               -- therefore there are no special views to be created
2160               statement := 'select null from sys.dual where 1 = 2   '||
2161                            'and :table_schema = ''X''                       ';
2162             end if;
2163 
2164 
2165             dbms_sql.parse(c, statement, dbms_sql.native);
2166             dbms_sql.bind_variable(c,'table_schema',table_schema);
2167             dbms_sql.define_column(c,1,l_table_name,30);
2168             rows_processed := dbms_sql.execute(c);
2169             loop
2170               if dbms_sql.fetch_rows(c) > 0 then
2171                 dbms_sql.column_value(c,1,l_table_name);
2172 
2173                 -- initialize all comparison variables
2174                 view_is_old := FALSE;
2175                 view_date := to_date('01/01/1970','DD/MM/YYYY');
2176                 table_date := to_date('01/01/1970','DD/MM/YYYY');
2177                 trans_record_date := to_date('01/01/1970','DD/MM/YYYY');
2178 
2179                 -- Get view_date
2180                 select nvl(min(last_ddl_time),
2181                         to_date('01/01/1970','DD/MM/YYYY'))
2182                 into view_date
2183                 from dba_objects
2184                 where object_name = upper(l_table_name)
2185                 and object_type = 'VIEW'
2186                 and owner = upper(apps_schema);
2187 
2188                 -- Get table_date
2189                 select nvl(min(decode(last_ddl_time,sysdate,
2190                         to_date('31/12/2199','DD/MM/YYYY'),last_ddl_time)),
2191                         to_date('01/01/1970','DD/MM/YYYY'))
2192                 into table_date
2193                 from dba_objects
2194                 where object_name = upper(l_table_name)
2195                 and object_type = 'TABLE'
2196                 and owner = upper(table_schema);
2197 
2198                 -- Get trans_record_date
2199                 declare
2200                   c                     integer;
2201                   rows_processed        integer;
2202                   statement             varchar2(500);
2203                 begin
2204                   c := dbms_sql.open_cursor;
2205                   statement :=
2206                           'select last_update_date                          '||
2207                           ' from '||aol_schema||'.ak_translated_columns     '||
2208                           ' where upper(table_name) = upper(:table_name)    ';
2209                   dbms_sql.parse(c, statement, dbms_sql.native);
2210                   dbms_sql.bind_variable(c,'table_name',l_table_name);
2211                   dbms_sql.define_column(c,1,trans_record_date);
2212                   rows_processed := dbms_sql.execute(c);
2213                   loop
2214                     if dbms_sql.fetch_rows(c) > 0 then
2215                         dbms_sql.column_value(c,1,trans_record_date);
2216                     end if;
2217                     dbms_sql.close_cursor(c);
2218                     exit;
2219                   end loop;
2220                 exception
2221                   when others then
2222                     dbms_sql.close_cursor(c);
2223                     ad_apps_private.error_buf := 'statement='||
2224                                                  statement||':'||
2225                                                  ad_apps_private.error_buf;
2226                     raise;
2227                 end;
2228 
2229                 -- Only recreate the view if:
2230                 --   last_ddl_time on view is less than the underlying table
2231                 if view_date < table_date then
2232                    view_is_old := TRUE;
2233                 end if;
2234                 --   last_ddl_time on view is less than the record in
2235                 --      ak_translated_columns
2236                 if view_date < trans_record_date then
2237                    view_is_old := TRUE;
2238                 end if;
2239                 --   last_ddl_time on view is less than the max_trans_date
2240                 if view_date < max_trans_date then
2241                    view_is_old := TRUE;
2242                 end if;
2243                 --   last_ddl_time on view is less than the max_xref_date
2244                 if view_date < max_xref_date then
2245                    view_is_old := TRUE;
2246                 end if;
2247                 --   View doesn't exist (i.e. last_update_date
2248                 --      was null '01-JAN-70')
2249                 if view_date = to_date('01/01/1970','DD/MM/YYYY') then
2250                    view_is_old := TRUE;
2251                 end if;
2252 
2253 
2254                 -- Only recreate the view if the existing view is old
2255                 -- otherwise nothing has changed that would require the view to
2256                 -- be recreated.
2257                 if view_is_old = TRUE then
2258      -- for each table create grant
2259      create_grant(p_grantor_schema_name => table_schema,
2260     p_grantee_schema_name => apps_schema,
2261     p_object_name         => l_table_name,
2265                 -- then build column list
2262     p_privileges          => 'ALL',
2263     p_with_grant_option   => TRUE);
2264 
2266                 ad_mls.build_mls_column_list(l_table_name,
2267                                         table_schema,aol_schema,
2268                                         view_column_list,select_list);
2269 
2270                 -- Create the view
2271                 declare
2272                   success_with_comp_error exception;
2273                   PRAGMA EXCEPTION_INIT(success_with_comp_error, -24344);
2274                   statement             varchar2(32000);
2275                 begin
2276                   statement := 'create or replace view "'||l_table_name||
2277                                '" '||view_column_list||
2278                                ' as select ' || select_list || ' from '||
2279                                table_schema||'."'||l_table_name||'"';
2280 
2281                   declare
2282                     name_already_used exception;
2283                     pragma exception_init(name_already_used, -955);
2284                   begin
2285                     ad_apps_private.do_apps_ddl(apps_schema,statement);
2286                   exception
2287                     when name_already_used then
2288                       -- first reset error buf
2289                       ad_apps_private.error_buf := null;
2290                       -- drop synonym and try view create again
2291                         ad_apps_private.drop_object(apps_schema,
2292                                 l_table_name, 'SYNONYM');
2293                         ad_apps_private.do_apps_ddl(apps_schema,statement);
2294                   end;
2295 
2296                 exception
2297                   when success_with_comp_error then
2298 --
2299 -- Trap and ignore ORA-24344: success with compilation error
2300 -- This only happens on ORACLE 8
2301 --
2302                     -- reset main error buffer
2303                     ad_apps_private.error_buf := null;
2304                 end;
2305                 end if;  -- view_is_old
2306               else
2307                 -- no more oracle views to process for this schema
2308                 dbms_sql.close_cursor(c);
2309                 exit;
2310               end if;
2311             end loop;  -- loop over all views
2312 
2313         exception
2314           when others then
2315             dbms_sql.close_cursor(c);
2316             ad_apps_private.error_buf := 'statement='||statement||': '||
2317                                          ad_apps_private.error_buf;
2318             raise;
2319         end;
2320 
2321       else
2322         -- no more rows to process
2323         dbms_sql.close_cursor(oracle_id_cursor);
2324         exit;
2325       end if;
2326   end loop;
2327 exception
2328   when others then
2329     dbms_sql.close_cursor(oracle_id_cursor);
2330     ad_apps_private.error_buf := 'create_special_views('||install_group_num||
2331                 ','||aol_schema||
2332                 ','||apps_schema||',create_mls_views): '||
2333                 ad_apps_private.error_buf;
2334     raise;
2335 end create_special_views;
2336 
2337 
2338 procedure copy_views
2339            (aoluser    in varchar2,
2340             fromschema in varchar2,
2341             toschema   in varchar2)
2342 is
2343   -- Do not copy obsolete views left over by AutoInstall( 'AI9%' or 'AI1%')
2344   cursor view_cur is
2345     select v1.view_name, v1.text_length source_len,
2346            v2.text_length dest_len
2347     from dba_views v1, dba_views v2
2348     where v1.owner = upper(fromschema)
2349     and   v1.view_name not like 'AI9%'
2350     and   v1.view_name not like 'AI1%'
2351     and   v2.owner (+) = upper(toschema)
2352     and   v2.view_name (+) = v1.view_name;
2353   comp_result  varchar2(10);
2354 begin
2355   for v_rec in view_cur loop
2356     --
2357     -- Check if view exists in destination schema,
2358     -- and create it if it's not already there
2359     --
2360     if v_rec.dest_len is null then
2361       ad_apps_private.copy_view(v_rec.view_name, fromschema, toschema);
2362     else
2363       --
2364       -- View exists in both schemas
2365       --
2366       -- Compare view lengths.  Re-create view in dest schema if the
2367       -- two views have different lengths.
2368       --
2369       if v_rec.source_len <> v_rec.dest_len then
2370         ad_apps_private.copy_view(v_rec.view_name, fromschema, toschema);
2371       else
2372         --
2373         -- View lengths equal.  Compare actual view text.
2374         --
2375 
2376         ad_apps_private.compare_view_text(v_rec.view_name, fromschema,
2377           toschema, v_rec.source_len, v_rec.dest_len, comp_result);
2378 
2379         -- Only copy view to destination schema if text not equal
2380 
2381         if comp_result = 'FALSE' then
2382           ad_apps_private.copy_view(v_rec.view_name, fromschema, toschema);
2383         end if;
2384 
2385       end if; -- view lengths equal
2386     end if; -- view exists in dest schema
2387   end loop;
2388 exception
2389   when others then
2390     ad_apps_private.error_buf := 'copy_views('||aoluser||','||fromschema||','||
2391                         toschema||'): '||ad_apps_private.error_buf;
2392     raise;
2393 end copy_views;
2394 
2395 
2396 procedure copy_stored_progs
2400             p_subset      in varchar2,
2397            (fromschema    in varchar2,
2398             toschema      in varchar2,
2399             p_object_type in varchar2,
2401             compare_level in varchar2)
2402 is
2403   -- don't do the apps_ddl procedure, because using it to drop
2404   -- and recreate itself is problematic
2405   cursor src_pls_obj is
2406     select do.object_name, do.object_type, do2.object_name name2
2407     from dba_objects do, dba_objects do2
2408     where do.owner = upper(copy_stored_progs.fromschema)
2409     and   do.object_type in (
2410      decode(copy_stored_progs.p_object_type,
2411                         'B',null,          'P',null,          'F',null,
2412                         'C',null,          'A','PACKAGE',     'S','PACKAGE',
2413                         'PACKAGE'),
2414      decode(copy_stored_progs.p_object_type,
2415                         'B','PACKAGE BODY','P',null,          'F',null,
2416                         'C','PACKAGE BODY','A','PACKAGE BODY','S',null,
2417                         'PACKAGE BODY'),
2418      decode(copy_stored_progs.p_object_type,
2419                         'B',null,          'P',null,          'F','FUNCTION',
2420                         'C','FUNCTION',    'A','FUNCTION',    'S',null,
2421                         'FUNCTION'),
2422      decode(copy_stored_progs.p_object_type,
2423                         'B',null,          'P','PROCEDURE',   'F',null,
2424                         'C','PROCEDURE',   'A','PROCEDURE',   'S',null,
2425                         'PROCEDURE'))
2426     and   do.object_name not in ('APPS_DDL', 'APPS_ARRAY_DDL')
2427     and   do.object_name not like 'FFP%'
2428     and   do.object_name like copy_stored_progs.p_subset || '%'
2429     and   do2.owner (+) = upper(copy_stored_progs.toschema)
2430     and   do2.object_name (+) = do.object_name
2431     and   do2.object_type (+) = do.object_type
2432     order by decode(do.object_type,'PACKAGE',1,2);
2433   cursor PKG_HEADER (c_owner in varchar2,
2434                      c_name  in varchar2,
2435                      c_type  in varchar2) is
2436     select
2437        substr(s.text, instr(s.text,'$Header'||': '),
2438               ((instr(s.text,' $', instr(s.text,'$Header'||': ')) + 2)
2439                - instr(s.text,'$Header'||': ')))
2440     from dba_source s
2441     where s.owner= upper(c_owner)
2442     and   s.name = upper(c_name)
2443     and   s.type = upper(c_type)
2444     and   s.line between 2 and 5
2445     and   s.text like '%$Header'||': % $%';
2446   src_header    varchar2(500);
2447   dst_header    varchar2(500);
2448   objs_equal    varchar2(10);
2449   object_number number;
2450 begin
2451   -- loop through all package/function/procedure/pkg body in source schema
2452 
2453   for src_rec in src_pls_obj loop
2454 
2455     if src_rec.name2 is null then
2456 
2457       -- object not in destination schema, so copy it to destination schema
2458 
2459       ad_apps_private.copy_code(src_rec.object_name, src_rec.object_type,
2460         fromschema, toschema);
2461 
2462     else
2463       -- get header information for object in source schema
2464 
2465       open PKG_HEADER(fromschema, src_rec.object_name, src_rec.object_type);
2466 
2467       fetch PKG_HEADER
2468       into src_header;
2469 
2470       if PKG_HEADER%NOTFOUND then
2471         src_header := null;
2472       end if;
2473 
2474       close PKG_HEADER;
2475 
2476       -- If object in source schema had header information,
2477       -- compare headers (if possible).  Otherwise, have to do full
2478       -- comparison of source and destination objects
2479 
2480       if src_header is not null then
2481 
2482         -- get header information for object in destination schema
2483 
2484         open PKG_HEADER(toschema, src_rec.object_name, src_rec.object_type);
2485 
2486         fetch PKG_HEADER
2487         into dst_header;
2488 
2489         if PKG_HEADER%NOTFOUND then
2490           dst_header := null;
2491         end if;
2492 
2493         close PKG_HEADER;
2494 
2495         -- if no header information in destination object,
2496         -- copy source to destination
2497 
2498         if dst_header is null then
2499 
2500           ad_apps_private.copy_code(src_rec.object_name, src_rec.object_type,
2501             fromschema, toschema);
2502 
2503         else
2504 
2505           -- compare header strings
2506           -- copy source to destination if header strings different
2507           -- possibly do more extensive comparison if header lines same
2508 
2509           if src_header <> dst_header then
2510 
2511             ad_apps_private.copy_code(src_rec.object_name,
2512               src_rec.object_type, fromschema, toschema);
2513 
2514           else
2515 
2516             -- header strings are identical
2517             -- do object comparison according to compare_level
2518 
2519             ad_apps_private.compare_code(src_rec.object_name,
2520               src_rec.object_type, fromschema, toschema,
2521               compare_level, objs_equal);
2522 
2523             -- copy source to dest if not equal
2524 
2525             if objs_equal = 'FALSE' then
2526 
2527               ad_apps_private.copy_code(src_rec.object_name,
2528                 src_rec.object_type, fromschema, toschema);
2532           end if; -- source and destination header not identical
2529 
2530             end if; -- source and destination objects not identical
2531 
2533 
2534         end if; -- destination has header information
2535 
2536       else
2537 
2538         -- no header information in source schema object
2539         -- do full object comparison
2540         -- (even if compare_level <> 'full')
2541 
2542         ad_apps_private.compare_code(src_rec.object_name,
2543           src_rec.object_type, fromschema, toschema,
2544           'full', objs_equal);
2545 
2546         -- copy source to dest if not equal
2547 
2548         if objs_equal = 'FALSE' then
2549 
2550           ad_apps_private.copy_code(src_rec.object_name,
2551             src_rec.object_type, fromschema, toschema);
2552 
2553         end if; -- source and destination objects not identical
2554 
2555       end if; -- source schema object has header information
2556 
2557     end if; -- object not in destination schema
2558   end loop;  -- loop over all stored progs in source schema
2559 
2560 exception
2561   when others then
2562     ad_apps_private.error_buf := 'copy_stored_progs('||fromschema||','||
2563         toschema||','||p_object_type||','||p_subset||','||
2564         compare_level||'): '||ad_apps_private.error_buf;
2565     raise;
2566 end copy_stored_progs;
2567 
2568 
2569 procedure exact_synonym_match
2570            (syn_own_schema  in         varchar2,
2571             syn_name        in         varchar2,
2572             tab_owner       in         varchar2,
2573             tab_name        in         varchar2,
2574             exact_match     out nocopy boolean,
2575             is_obj_w_name   out nocopy boolean,
2576             typ_exist_obj   out nocopy varchar2)
2577 is
2578   found_exact_match boolean;
2579   found_object_with_same_name boolean;
2580 
2581   cursor SYN_MATCH (c_owner          in varchar2,
2582                     c_synonym_name   in varchar2,
2583                     c_table_owner    in varchar2,
2584                     c_table_name     in varchar2) is
2585     select 'X'
2586     from dba_synonyms
2587     where owner = c_owner
2588     and   synonym_name = c_synonym_name
2589     and   table_owner = c_table_owner
2590     and   table_name = c_table_name
2591     and   db_link is null;
2592 
2593   cursor FIND_OBJ (c_owner       in varchar2,
2594                    c_object_name in varchar2) is
2595     select object_type
2596     from dba_objects
2597     where owner = c_owner
2598     and   object_name = c_object_name
2599     order by decode(object_type, 'PACKAGE', 1, 2);
2600 
2601   dummy1 varchar2(10);
2602   obj_type_found varchar2(30);
2603 begin
2604   exact_match := FALSE;
2605   is_obj_w_name := FALSE;
2606   typ_exist_obj := null;
2607 
2608   open SYN_MATCH(syn_own_schema, syn_name, tab_owner, tab_name);
2609 
2610   fetch SYN_MATCH
2611   into dummy1;
2612 
2613   if SYN_MATCH%NOTFOUND then
2614   -- no exact synonym match
2615     close SYN_MATCH;
2616 
2617     open FIND_OBJ(syn_own_schema, syn_name);
2618 
2619     fetch FIND_OBJ
2620     into obj_type_found;
2621 
2622     if FIND_OBJ%NOTFOUND then
2623     -- no object in schema with given name
2624       close FIND_OBJ;
2625 
2626       -- No need to set return variables, since they are already
2627       -- set to indicate "no matching object in schema"
2628     else
2629     -- at least one object in schema with given name
2630 
2631       if obj_type_found = 'PACKAGE' then
2632       -- found existing 'PACKAGE'.  Check for 'PACKAGE BODY' as well
2633         fetch FIND_OBJ
2634         into obj_type_found;
2635 
2636         if FIND_OBJ%NOTFOUND then
2637         -- only 'PACKAGE' found
2638           close FIND_OBJ;
2639 
2640           is_obj_w_name := TRUE;
2641           typ_exist_obj := 'PACKAGE';
2642         else
2643         -- found something besides 'PACKAGE'
2644           close FIND_OBJ;
2645 
2646           if obj_type_found = 'PACKAGE BODY' then
2647           -- end if found package body too
2648             is_obj_w_name := TRUE;
2649             typ_exist_obj := 'PKG_S_AND_B';
2650           else
2651           -- found other object w same name, but not package body
2652           -- this should never happen
2653             raise_application_error(-20000, 'Object '||syn_name||
2654               ' in schema '||syn_own_schema||
2655               ' has type PACKAGE and also type '||obj_type_found);
2656           end if;
2657           -- end if found package body too
2658         end if;
2659         -- end if only 'PACKAGE' found
2660       else
2661       -- found something other than 'PACKAGE'
2662         close FIND_OBJ;
2663 
2664         is_obj_w_name := TRUE;
2665         typ_exist_obj := obj_type_found;
2666       end if;
2667       -- end if found existing 'PACKAGE'
2668 
2669     end if;
2670     -- end if no object in schema with given name
2671   else
2672   -- found exact synonym match
2673     close SYN_MATCH;
2674 
2675     exact_match := TRUE;
2676     is_obj_w_name := TRUE;
2677     typ_exist_obj := 'SYNONYM';
2678   end if;
2682   when others then
2679   -- end if no exact synonym match
2680 
2681 exception
2683     ad_apps_private.error_buf := 'exact_synonym_match('||syn_own_schema||
2684       ','||syn_name||','||tab_owner||','||tab_name||'): '||
2685       ad_apps_private.error_buf;
2686     raise;
2687 end exact_synonym_match;
2688 
2689 
2690 procedure recomp_referenced_objs
2691            (object_name      in varchar2,
2692             object_type      in varchar2,
2693             obj_list_schema  in varchar2,
2694             recompile_schema in varchar2)
2695 is
2696   type NameType is table of varchar2(30)
2697     index by binary_integer;
2698   type NumType is table of binary_integer
2699     index by binary_integer;
2700 
2701   obj_names  NameType;
2702   obj_types  NameType;
2703   obj_levels NumType;
2704   obj_processed NumType;
2705 
2706   num_objs   number;
2707 
2708   cursor GET_DEPS (c_owner in varchar2,
2709                    c_type  in varchar2,
2710                    c_name  in varchar2,
2711                    c_level in number) is
2712     select distinct c_level, referenced_name, referenced_type
2713     from dba_dependencies
2714     where owner = c_owner
2715     and   name  = c_name
2716     and   type  = c_type
2717     and   referenced_owner = owner
2718     and   referenced_type in
2719             ('VIEW', 'PACKAGE', 'PROCDEDURE', 'FUNCTION', 'PACKAGE BODY');
2720 
2721   sel_level  number;
2722   sel_name   varchar2(30);
2723   sel_type   varchar2(30);
2724   done_sel   boolean;
2725   done_sel2  boolean;
2726   add_object boolean;
2727   any_added  boolean;
2728   idx        number;
2729   i          number;
2730   j          number;
2731   start_val  number;
2732   end_val    number;
2733   max_level  number;
2734   dummy      varchar2(30);
2735   statement  varchar2(100);
2736 begin
2737   num_objs := 0;
2738   done_sel := FALSE;
2739   max_level := 0;
2740 
2741   -- open cursor for initial select
2742 
2743   open GET_DEPS(obj_list_schema, object_type, object_name, 1);
2744 
2745   while not done_sel loop
2746 
2747     fetch GET_DEPS
2748     into sel_level, sel_name, sel_type;
2749 
2750     if GET_DEPS%NOTFOUND then
2751       done_sel := TRUE;
2752     else
2753       -- process dependent object
2754 
2755       num_objs := num_objs + 1;
2756 
2757       obj_names(num_objs) := sel_name;
2758       obj_types(num_objs) := sel_type;
2759       obj_levels(num_objs) := sel_level;
2760       obj_processed(num_objs) := 0;
2761 
2762       if sel_level > max_level then
2763         max_level := sel_level;
2764       end if;
2765 
2766 --    dbms_output.put_line('Add: '||sel_level||' '||sel_type||' '||sel_name);
2767     end if;
2768 
2769   end loop;
2770 -- end loop to get first-level dependencies
2771 
2772   close GET_DEPS;
2773   done_sel := FALSE;
2774 
2775   while not done_sel loop
2776     any_added := FALSE;
2777     start_val:= 1;
2778     end_val:= num_objs;
2779 
2780     for i in start_val..end_val loop
2781 
2782       if (obj_processed(i) = 0) then
2783 
2784         open GET_DEPS(obj_list_schema, obj_types(i), obj_names(i),
2785                       obj_levels(i)+1);
2786 
2787         obj_processed(i) := 1;
2788 
2789         done_sel2:= FALSE;
2790 
2791         while not done_sel2 loop
2792 
2793           fetch GET_DEPS
2794           into sel_level, sel_name, sel_type;
2795 
2796           if GET_DEPS%NOTFOUND then
2797             done_sel2:= TRUE;
2798           else
2799             -- check to see if this object is already on the list
2800 
2801             add_object:= TRUE;
2802 
2803             for j in obj_names.first..obj_names.last loop
2804               if sel_name = obj_names(j) and
2805                  sel_type = obj_types(j) then
2806                 add_object := FALSE;
2807 
2808 -- If object is already on list, but listed at a lower level,
2809 -- update object level to the current level.  This way we will list
2810 -- all objects at the level corresponding to the deepest point in the
2811 -- hierarchy at which they are required by another object.
2812 
2813                 if sel_level > obj_levels(j) then
2814                   obj_levels(j) := sel_level;
2815 
2816                  if sel_level > max_level then
2817                    max_level := sel_level;
2818                  end if;
2819 
2820                 end if;
2821 
2822                 exit;
2823               end if;
2824             end loop;
2825 -- end loop to see if object already in list
2826 
2827             if add_object then
2828               num_objs := num_objs + 1;
2829 
2830               obj_names(num_objs) := sel_name;
2831               obj_types(num_objs) := sel_type;
2832               obj_levels(num_objs) := sel_level;
2833               obj_processed(num_objs) := 0;
2834 
2835               if sel_level > max_level then
2836                 max_level := sel_level;
2837               end if;
2838               any_added := TRUE;
2839 
2840 --   dbms_output.put_line('Add: '||sel_level||' '||sel_type||' '||sel_name);
2841 
2845 --  dbms_output.put_line('FYI: '||sel_level||' '||sel_type||' '||sel_name);
2842             end if;
2843 -- end if added object
2844 
2846           end if;
2847 
2848         end loop;
2849 -- end loop to fetch dependent objects for one object at this level
2850 
2851         close GET_DEPS;
2852 
2853       end if;
2854 -- end if didn't already fetch dependent objs for this object
2855     end loop;
2856 -- end loop to fetch dependent objects for this level
2857 
2858     if not any_added then
2859       done_sel := TRUE;
2860     end if;
2861 
2862   end loop;
2863 -- end loop to get all dependent objects
2864 
2865 -- Debugging output: list all dependent objects and their dependency levels
2866 
2867 --  for i in 1..num_objs loop
2868 --    dbms_output.put_line('Fin: '||obj_levels(i)||' '||
2869 --      obj_types(i)||' '||obj_names(i));
2870 --  end loop;
2871 
2872 -- compile objects by dependency order in dest schema
2873 -- go backwards on same dependency level in the hopes that this makes it less
2874 -- likely we'll encounter the same deadlock the RDBMS did earlier
2875 
2876   for idx in reverse 1..max_level loop
2877     for i in reverse 1..num_objs loop
2878       if obj_levels(i) = idx then
2879 
2880         -- check to see if object exists in dest schema
2881 
2882         select object_name
2883         into dummy
2884         from dba_objects
2885         where owner = recompile_schema
2886         and   object_name = obj_names(i)
2887         and   object_type = obj_types(i);
2888 
2889         if not SQL%NOTFOUND then
2890 
2891           -- build compilation statement
2892 
2893           if    obj_types(i) = 'PACKAGE' then
2894             statement := 'ALTER PACKAGE "'|| obj_names(i) ||
2895                          '" COMPILE SPECIFICATION';
2896           elsif obj_types(i) = 'PACKAGE BODY' then
2897             statement := 'ALTER PACKAGE "'|| obj_names(i) ||
2898                          '" COMPILE BODY';
2899           else
2900             statement := 'ALTER '|| obj_types(i) ||' "'||
2901                          obj_names(i) || '" COMPILE';
2902           end if;
2903 
2904           -- execute compilation statement
2905 
2906 --          dbms_output.put_line('('||obj_levels(i)||') '||statement);
2907 
2908           begin
2909             ad_apps_private.do_apps_ddl(recompile_schema, statement);
2910           exception
2911             when others then
2912               ad_apps_private.error_buf := null;
2913           end;
2914 
2915         end if;
2916 -- end if object exists in desc schema
2917 
2918       end if;
2919 -- end if this object is at the current dependency level
2920     end loop;
2921 -- end loop to compile invalid objecs for current level
2922   end loop;
2923 -- end loop to compile invalid objects for all levels
2924 
2925 exception
2926   when others then
2927     ad_apps_private.error_buf := 'recomp_referenced_objs('||object_name||
2928       ','||obj_list_schema||','||recompile_schema||'): '||
2929       ad_apps_private.error_buf;
2930     raise;
2931 end recomp_referenced_objs;
2932 
2933 
2934 --
2935 -- Other Misc procedures
2936 --
2937 
2938 
2939 procedure build_view_columns
2940            (from_schema     in         varchar2,
2941             view_name       in         varchar2,
2942             out_column_text out nocopy varchar2)
2943 is
2944   counter               number := 0;
2945   column_text           varchar2(32760);
2946   cursor c1 is
2947     select column_name from dba_tab_columns
2948     where table_name = build_view_columns.view_name
2949     and   owner = upper(build_view_columns.from_schema)
2950     order by column_id;
2951 begin
2952   for c1rec in c1 loop
2953     if counter = 0 then
2954         column_text := '("' || c1rec.column_name;
2955     else
2956       column_text := column_text || '","' || c1rec.column_name;
2957     end if;
2958     counter := counter + 1;
2959   end loop;
2960   if counter > 0 then
2961     -- at least one column so add closing paren
2962     column_text := column_text || '")';
2963   end if;
2964   out_column_text := column_text;
2965 
2966 exception
2967   when others then
2968   ad_apps_private.error_buf := 'ad_apps_private.build_view_columns('||
2969         from_schema||','||view_name||',out_column_text): '||
2970         ad_apps_private.error_buf;
2971   raise;
2972 end build_view_columns;
2973 
2974 
2975 procedure show_exception_list
2976 is
2977   i number;
2978 begin
2979   -- initialize dbms_output with large buffer size (200,000)
2980   --  default is 20,000   min is 2,000  max is 1,000,000
2981 
2982   dbms_output.enable(200000);
2983 
2984   -- load exception list, if not already loaded
2985 
2986   load_exception_list;
2987 
2988   -- display settings
2989 
2990   dbms_output.put_line('-');
2991   dbms_output.put_line(list_count ||' entries in exception list.');
2992   dbms_output.put_line('-');
2993 
2994   i := 1;
2995   while i <= list_count loop
2996     dbms_output.put_line('['||i||'] Product Short Name: '||
2997       prod_short_name(i));
2998     dbms_output.put_line('['||i||'] Base Schema Name  : '||
3002     dbms_output.put_line('['||i||'] Exception Type    : '||
2999       base_name(i));
3000     dbms_output.put_line('['||i||'] Base Schema Type  : '||
3001       base_type(i));
3003       exception_type(i));
3004     dbms_output.put_line('['||i||'] Trigger Obj Schema: '||
3005       trigger_obj_schema(i));
3006     dbms_output.put_line('['||i||'] Trigger Obj Type  : '||
3007       trigger_obj_type(i));
3008     dbms_output.put_line('['||i||'] Trigger Obj Name  : '||
3009       trigger_obj_name(i));
3010     dbms_output.put_line('['||i||'] APPS Schema Name  : '||
3011       apps_name(i));
3012     dbms_output.put_line('['||i||'] APPS Schema Type  : '||
3013       apps_type(i));
3014     dbms_output.put_line('['||i||'] Points to Schema  : '||
3015       points_to_schema(i));
3016     dbms_output.put_line('['||i||'] Points to Obj Name: '||
3017       points_to_name(i));
3018     dbms_output.put_line('['||i||']');
3019     i := i + 1;
3020   end loop;
3021 
3022   dbms_output.put_line('-');
3023 
3024 exception
3025   when others then
3026     ad_apps_private.error_buf := 'show_exception_list: '||
3027       ad_apps_private.error_buf;
3028     raise;
3029 end show_exception_list;
3030 
3031 
3032 procedure load_exception_list
3033 is
3034   i number;
3035 begin
3036   --
3037   -- The "exception objects" list:
3038   --
3039   -- Lists objects in the base schema which are known to not be
3040   -- represented in the APPS schema by a synonym that points to
3041   -- the base object in some cases.
3042   --
3043   -- We determine whether the exception case should be activated by
3044   -- the presence of another object in either the base or APPS schema
3045   -- (called the "trigger object").
3046   --
3047   -- If the trigger object is present, we expect the synonym for the
3048   -- base object in the APPS schema to be replaced by a "customized object"
3049   -- with a specified name and type.  If the "customized object" is a
3050   -- synonym, we list the schema and name of the object it should point to.
3051   --
3052   -- No column in the exception objects list can be null except
3053   -- for the points_to_schema and points_to_name columns
3054   --
3055   -- Here is what each column means:
3056   --
3057   -- prod_short_name
3058   --
3059   --   The product short name for the product that owns the object in
3060   --   the base schema.
3061   --
3062   -- base_name
3063   --
3064   --   The name of the object in the base schema.
3065   --
3066   -- base_type
3067   --
3068   --   The type of the object in the base schema.
3069   --
3070   -- exception_type
3071   --
3072   --   Type of exception.  One of the following:
3073   --
3074   --     STANDARD_EXCEPTION
3075   --
3076   --       Possibly this is the only exception type we will ever support,
3077   --         but I wanted to leave it open for future expansion
3078   --
3079   --       Right now, only tables that were converted to MultiOrg in
3080   --         a patch will have any exceptions at all.
3081   --
3082   -- trigger_obj_schema
3083   --
3084   --   The schema in which the "trigger object" is located.
3085   --   If trigger object does not exist in trigger schema with the specified
3086   --     name and type, the exception logic will not execute.
3087   --   Valid values are: BASE and APPS
3088   --
3089   -- trigger_obj_type
3090   --
3091   --   The type of the "trigger object"
3092   --   The trigger object cannot be a synonym.
3093   --
3094   -- trigger_obj_name
3095   --
3096   --   The name of the "trigger object"
3097   --   The trigger object cannot have the same schema and name as the
3098   --     customized object in APPS, unless they are identical
3099   --     (same schema, type, and name).
3100   --
3101   -- apps_name
3102   --
3103   --   Name of the "customized object" in the APPS schema.
3104   --   Usually the same name as in the base schema.
3105   --
3106   -- apps_type
3107   --
3108   --   Type of the "customized object" in the APPS schema.
3109   --
3110   -- points_to_schema
3111   --
3112   --   This should be null unless customized object is a synonym.
3113   --   If object in the APPS schema is a synonym, this is the schema in
3114   --     which the object that the synonym should point to is located.
3115   --   Valid values are: BASE and APPS (and null, of course)
3116   --
3117   -- points_to_name
3118   --
3119   --   This should be null unless customized object is a synonym.
3120   --   If object in the APPS schema is a synonym, this is the name of
3121   --     the object that the synonym should point to.
3122   --
3123 
3124   --
3125   -- If counter variable is null, initialize list
3126   -- If counter variable is not null, assume list already initialized
3127   --
3128 
3129   if list_count is null then
3130 
3131     list_count := 0;
3132 
3133     -- Commented-out entries from Rel 11.0
3134     -- Keep them here so we can use them for reference
3135 
3136 --    -- For PER_ASSIGNMENT_BUDGET_VALUES
3137 
3138 --    list_count := list_count + 1;
3139 --    prod_short_name(list_count)     := 'PER';
3140 --    base_name(list_count)           := 'PER_ASSIGNMENT_BUDGET_VALUES';
3144 --    trigger_obj_type(list_count)    := 'VIEW';
3141 --    base_type(list_count)           := 'TABLE';
3142 --    exception_type(list_count)      := 'STANDARD_EXCEPTION';
3143 --    trigger_obj_schema(list_count ) := 'APPS';
3145 --    trigger_obj_name(list_count)    := 'PER_ASG_BUDGET_VALS_INTNL';
3146 --    apps_name(list_count)           := 'PER_ASSIGNMENT_BUDGET_VALUES';
3147 --    apps_type(list_count)           := 'SYNONYM';
3148 --    points_to_schema(list_count)    := 'APPS';
3149 --    points_to_name(list_count)      := 'PER_ASG_BUDGET_VALS_INTNL';
3150 
3151 --    -- For JG_ZZ_VEND_SITE_INFO
3152 
3153 --    list_count := list_count + 1;
3154 --    prod_short_name(list_count)     := 'SQLAP';
3155 --    base_name(list_count)           := 'JG_ZZ_VEND_SITE_INFO';
3156 --    base_type(list_count)           := 'TABLE';
3157 --    exception_type(list_count)      := 'STANDARD_EXCEPTION';
3158 --    trigger_obj_schema(list_count ) := 'APPS';
3159 --    trigger_obj_type(list_count)    := 'VIEW';
3160 --    trigger_obj_name(list_count)    := 'JG_ZZ_VEND_SITE_INFO_V';
3161 --    apps_name(list_count)           := 'JG_ZZ_VEND_SITE_INFO';
3162 --    apps_type(list_count)           := 'SYNONYM';
3163 --    points_to_schema(list_count)    := 'APPS';
3164 --    points_to_name(list_count)      := 'JG_ZZ_VEND_SITE_INFO_V';
3165 
3166     --
3167     -- Entries for Rel 11.5.x
3168     --
3169 
3170     -- For RA_CONTACTS
3171 
3172     list_count := list_count + 1;
3173     prod_short_name(list_count)     := 'AR';
3174     base_name(list_count)           := 'RA_CONTACTS';
3175     base_type(list_count)           := 'TABLE';
3176     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3177     trigger_obj_schema(list_count ) := 'APPS';
3178     trigger_obj_type(list_count)    := 'VIEW';
3179     trigger_obj_name(list_count)    := 'RA_HCONTACTS';
3180     apps_name(list_count)           := 'RA_CONTACTS';
3181     apps_type(list_count)           := 'SYNONYM';
3182     points_to_schema(list_count)    := 'APPS';
3183     points_to_name(list_count)      := 'RA_HCONTACTS';
3184 
3185     -- For AR_CUST_PROF_CLASS_AMOUNTS
3186 
3187     list_count := list_count + 1;
3188     prod_short_name(list_count)     := 'AR';
3189     base_name(list_count)           := 'AR_CUST_PROF_CLASS_AMOUNTS';
3190     base_type(list_count)           := 'TABLE';
3191     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3192     trigger_obj_schema(list_count ) := 'APPS';
3193     trigger_obj_type(list_count)    := 'VIEW';
3194     trigger_obj_name(list_count)    := 'AR_HCUST_PROF_CLASS_AMOUNTS';
3195     apps_name(list_count)           := 'AR_CUST_PROF_CLASS_AMOUNTS';
3196     apps_type(list_count)           := 'SYNONYM';
3197     points_to_schema(list_count)    := 'APPS';
3198     points_to_name(list_count)      := 'AR_HCUST_PROF_CLASS_AMOUNTS';
3199 
3200     -- For AR_CUSTOMER_PROFILES
3201 
3202     list_count := list_count + 1;
3203     prod_short_name(list_count)     := 'AR';
3204     base_name(list_count)           := 'AR_CUSTOMER_PROFILES';
3205     base_type(list_count)           := 'TABLE';
3206     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3207     trigger_obj_schema(list_count ) := 'APPS';
3208     trigger_obj_type(list_count)    := 'VIEW';
3209     trigger_obj_name(list_count)    := 'AR_HCUSTOMER_PROFILES';
3210     apps_name(list_count)           := 'AR_CUSTOMER_PROFILES';
3211     apps_type(list_count)           := 'SYNONYM';
3212     points_to_schema(list_count)    := 'APPS';
3213     points_to_name(list_count)      := 'AR_HCUSTOMER_PROFILES';
3214 
3215     -- For RA_CONTACT_ROLES
3216 
3217     list_count := list_count + 1;
3218     prod_short_name(list_count)     := 'AR';
3219     base_name(list_count)           := 'RA_CONTACT_ROLES';
3220     base_type(list_count)           := 'TABLE';
3221     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3222     trigger_obj_schema(list_count ) := 'APPS';
3223     trigger_obj_type(list_count)    := 'VIEW';
3224     trigger_obj_name(list_count)    := 'RA_HCONTACT_ROLES';
3225     apps_name(list_count)           := 'RA_CONTACT_ROLES';
3226     apps_type(list_count)           := 'SYNONYM';
3227     points_to_schema(list_count)    := 'APPS';
3228     points_to_name(list_count)      := 'RA_HCONTACT_ROLES';
3229 
3230     -- For AR_CUSTOMER_PROFILE_AMOUNTS
3231 
3232     list_count := list_count + 1;
3233     prod_short_name(list_count)     := 'AR';
3234     base_name(list_count)           := 'AR_CUSTOMER_PROFILE_AMOUNTS';
3235     base_type(list_count)           := 'TABLE';
3236     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3237     trigger_obj_schema(list_count ) := 'APPS';
3238     trigger_obj_type(list_count)    := 'VIEW';
3239     trigger_obj_name(list_count)    := 'AR_HCUSTOMER_PROFILE_AMOUNTS';
3240     apps_name(list_count)           := 'AR_CUSTOMER_PROFILE_AMOUNTS';
3241     apps_type(list_count)           := 'SYNONYM';
3242     points_to_schema(list_count)    := 'APPS';
3243     points_to_name(list_count)      := 'AR_HCUSTOMER_PROFILE_AMOUNTS';
3244 
3245     -- For AR_CUSTOMER_PROFILE_CLASSES
3246 
3247     list_count := list_count + 1;
3248     prod_short_name(list_count)     := 'AR';
3249     base_name(list_count)           := 'AR_CUSTOMER_PROFILE_CLASSES';
3250     base_type(list_count)           := 'TABLE';
3251     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3252     trigger_obj_schema(list_count ) := 'APPS';
3253     trigger_obj_type(list_count)    := 'VIEW';
3257     points_to_schema(list_count)    := 'APPS';
3254     trigger_obj_name(list_count)    := 'AR_HCUSTOMER_PROFILE_CLASSES';
3255     apps_name(list_count)           := 'AR_CUSTOMER_PROFILE_CLASSES';
3256     apps_type(list_count)           := 'SYNONYM';
3258     points_to_name(list_count)      := 'AR_HCUSTOMER_PROFILE_CLASSES';
3259 
3260    -- For CZ_LOCALIZED_TEXTS
3261 
3262     list_count := list_count + 1;
3263     prod_short_name(list_count)     := 'CZ';
3264     base_name(list_count)           := 'CZ_INTL_TEXTS';
3265     base_type(list_count)           := 'TABLE';
3266     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3267     trigger_obj_schema(list_count ) := 'APPS';
3268     trigger_obj_type(list_count)    := 'VIEW';
3269     trigger_obj_name(list_count)    := 'CZ_LOCALIZED_TEXTS_VL';
3270     apps_name(list_count)           := 'CZ_INTL_TEXTS';
3271     apps_type(list_count)           := 'SYNONYM';
3272     points_to_schema(list_count)    := 'APPS';
3273     points_to_name(list_count)      := 'CZ_LOCALIZED_TEXTS_VL';
3274 
3275 
3276     -- for HZ_CONTACT_RESTRICTIONS
3277 
3278     list_count := list_count + 1;
3279     prod_short_name(list_count)     := 'AR';
3280     base_name(list_count)           := 'HZ_CONTACT_RESTRICTIONS';
3281     base_type(list_count)           := 'TABLE';
3282     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3283     trigger_obj_schema(list_count ) := 'APPS';
3284     trigger_obj_type(list_count)    := 'VIEW';
3285     trigger_obj_name(list_count)    := 'HZ_CONTACT_RESTRICTIONS';
3286     apps_name(list_count)           := 'HZ_CONTACT_RESTRICTIONS';
3287     apps_type(list_count)           := 'VIEW';
3288     points_to_schema(list_count)    := null;
3289     points_to_name(list_count)      := null;
3290 
3291 
3292     -- for HZ_PARTY_RELATIONSHIPS
3293 
3294     list_count := list_count + 1;
3295     prod_short_name(list_count)     := 'AR';
3296     base_name(list_count)           := 'HZ_PARTY_RELATIONSHIPS';
3297     base_type(list_count)           := 'TABLE';
3298     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3299     trigger_obj_schema(list_count ) := 'APPS';
3300     trigger_obj_type(list_count)    := 'VIEW';
3301     trigger_obj_name(list_count)    := 'HZ_PARTY_RELATIONSHIPS';
3302     apps_name(list_count)           := 'HZ_PARTY_RELATIONSHIPS';
3303     apps_type(list_count)           := 'VIEW';
3304     points_to_schema(list_count)    := null;
3305     points_to_name(list_count)      := null;
3306 
3307 
3308     -- For JTF_TASK_ALL_ASSIGNMENTS
3309 
3310     list_count := list_count + 1;
3311     prod_short_name(list_count)     := 'JTF';
3312     base_name(list_count)           := 'JTF_TASK_ASSIGNMENTS';
3313     base_type(list_count)           := 'TABLE';
3314     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3315     trigger_obj_schema(list_count ) := 'APPS';
3316     trigger_obj_type(list_count)    := 'VIEW';
3317     trigger_obj_name(list_count)    := 'JTF_TASK_ASSIGNMENTS_V';
3318     apps_name(list_count)           := 'JTF_TASK_ASSIGNMENTS';
3319     apps_type(list_count)           := 'SYNONYM';
3320     points_to_schema(list_count)    := 'APPS';
3321     points_to_name(list_count)      := 'JTF_TASK_ASSIGNMENTS_V';
3322 
3323 
3324     -- For JTF_RS_SRP_TERRITORIES
3325 
3326     list_count := list_count + 1;
3327     prod_short_name(list_count)     := 'JTF';
3328     base_name(list_count)           := 'JTF_RS_SRP_TERRITORIES';
3329     base_type(list_count)           := 'TABLE';
3330     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3331     trigger_obj_schema(list_count ) := 'APPS';
3332     trigger_obj_type(list_count)    := 'TABLE';
3333     trigger_obj_name(list_count)    := 'JTF_RS_SRP_TERRITORIES';
3334     apps_name(list_count)           := 'RA_SALESREP_TERRITORIES';
3335     apps_type(list_count)           := 'SYNONYM';
3336     points_to_schema(list_count)    := 'APPS';
3337     points_to_name(list_count)      := 'RA_SALESREP_TERRITORIES';
3338 
3339     -- Bug 5877306 - stangutu - 13 Feb, 2007
3340     -- ADD EXCEPTION FOR SYNONYMS IN LOAD_EXCEPTION_LIST
3341     -- For OE_SYSTEM_PARAMETERS_ALL
3342 
3343     list_count := list_count + 1;
3344     prod_short_name(list_count)     := 'ONT';
3345     base_name(list_count)           := 'OE_SYSTEM_PARAMETERS_ALL';
3346     base_type(list_count)           := 'TABLE';
3347     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3348     trigger_obj_schema(list_count ) := 'APPS';
3349     trigger_obj_type(list_count)    := 'VIEW';
3350     trigger_obj_name(list_count)    := 'OE_SYS_PARAMS_ALL_UPG';
3351     apps_name(list_count)           := 'OE_SYSTEM_PARAMETERS_ALL';
3352     apps_type(list_count)           := 'SYNONYM';
3353     points_to_schema(list_count)    := 'APPS';
3354     points_to_name(list_count)      := 'OE_SYS_PARAMS_ALL_UPG';
3355 
3356     -- For RA_CUSTOMERS
3357 
3358     list_count := list_count + 1;
3359     prod_short_name(list_count)     := 'AR';
3360     base_name(list_count)           := 'RA_CUSTOMERS';
3361     base_type(list_count)           := 'TABLE';
3362     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3363     trigger_obj_schema(list_count ) := 'APPS';
3364     trigger_obj_type(list_count)    := 'VIEW';
3365     trigger_obj_name(list_count)    := 'RA_HCUSTOMERS';
3366     apps_name(list_count)           := 'RA_CUSTOMERS';
3367     apps_type(list_count)           := 'SYNONYM';
3368     points_to_schema(list_count)    := 'APPS';
3372 
3369     points_to_name(list_count)      := 'RA_HCUSTOMERS';
3370 
3371     -- For RA_PHONES
3373     list_count := list_count + 1;
3374     prod_short_name(list_count)     := 'AR';
3375     base_name(list_count)           := 'RA_PHONES';
3376     base_type(list_count)           := 'TABLE';
3377     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3378     trigger_obj_schema(list_count ) := 'APPS';
3379     trigger_obj_type(list_count)    := 'VIEW';
3380     trigger_obj_name(list_count)    := 'RA_HPHONES';
3381     apps_name(list_count)           := 'RA_PHONES';
3382     apps_type(list_count)           := 'SYNONYM';
3383     points_to_schema(list_count)    := 'APPS';
3384     points_to_name(list_count)      := 'RA_HPHONES';
3385 
3386     -- For RA_ADDRESSES_ALL
3387 
3388     list_count := list_count + 1;
3389     prod_short_name(list_count)     := 'AR';
3390     base_name(list_count)           := 'RA_ADDRESSES_ALL';
3391     base_type(list_count)           := 'TABLE';
3392     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3393     trigger_obj_schema(list_count ) := 'APPS';
3394     trigger_obj_type(list_count)    := 'VIEW';
3395     trigger_obj_name(list_count)    := 'RA_ADDRESSES_MORG';
3396     apps_name(list_count)           := 'RA_ADDRESSES_ALL';
3397     apps_type(list_count)           := 'SYNONYM';
3398     points_to_schema(list_count)    := 'APPS';
3399     points_to_name(list_count)      := 'RA_ADDRESSES_MORG';
3400 
3401     -- For RA_CUSTOMER_RELATIONSHIPS_ALL
3402 
3403     list_count := list_count + 1;
3404     prod_short_name(list_count)     := 'AR';
3405     base_name(list_count)           := 'RA_CUSTOMER_RELATIONSHIPS_ALL';
3406     base_type(list_count)           := 'TABLE';
3407     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3408     trigger_obj_schema(list_count ) := 'APPS';
3409     trigger_obj_type(list_count)    := 'VIEW';
3410     trigger_obj_name(list_count)    := 'RA_CUSTOMER_RELATIONSHIPS_MORG';
3411     apps_name(list_count)           := 'RA_CUSTOMER_RELATIONSHIPS_ALL';
3412     apps_type(list_count)           := 'SYNONYM';
3413     points_to_schema(list_count)    := 'APPS';
3414     points_to_name(list_count)      := 'RA_CUSTOMER_RELATIONSHIPS_MORG';
3415 
3416     -- For RA_SITE_USES_ALL
3417 
3418     list_count := list_count + 1;
3419     prod_short_name(list_count)     := 'AR';
3420     base_name(list_count)           := 'RA_SITE_USES_ALL';
3421     base_type(list_count)           := 'TABLE';
3422     exception_type(list_count)      := 'STANDARD_EXCEPTION';
3423     trigger_obj_schema(list_count ) := 'APPS';
3424     trigger_obj_type(list_count)    := 'VIEW';
3425     trigger_obj_name(list_count)    := 'RA_SITE_USES_MORG';
3426     apps_name(list_count)           := 'RA_SITE_USES_ALL';
3427     apps_type(list_count)           := 'SYNONYM';
3428     points_to_schema(list_count)    := 'APPS';
3429     points_to_name(list_count)      := 'RA_SITE_USES_MORG';
3430 
3431     --
3432     -- Validate list entries
3433     --
3434 
3435     for i in 1..list_count loop
3436 
3437       if    prod_short_name(i) is null
3438          or base_name(i) is null
3439          or base_type(i) is null
3440          or exception_type(i) is null
3441          or trigger_obj_schema(i) is null
3442          or trigger_obj_type(i) is null
3443          or trigger_obj_name(i) is null
3444          or apps_name(i) is null
3445          or apps_type(i) is null then
3446         raise_application_error(-20001,
3447           'Exception objects list row '||i||' has an invalid null value.');
3448       end if;
3449       -- end if any mandatory not-null field in the row was null
3450 
3451       if     trigger_obj_schema(i) <> 'BASE'
3452          and trigger_obj_schema(i) <> 'APPS' then
3453         raise_application_error(-20001,
3454           'Invalid trigger_obj_schema value: "'||trigger_obj_schema(i)||
3455           '". ('||i||')');
3456       end if;
3457       -- end if trigger object schema not valid
3458 
3459       if trigger_obj_type(i) = 'SYNONYM' then
3460         raise_application_error(-20001,
3461           'Trigger Object "'||trigger_obj_name(i)||'" cannot be a synonym'||
3462           '. ('||i||')');
3463       end if;
3464       -- end if trigger object is synonym
3465 
3466       if     apps_type(i) = 'SYNONYM'
3467          and (   points_to_schema(i) is null
3468               or points_to_name(i) is null) then
3469         raise_application_error(-20001,
3470           'Synonym "'||apps_name(i)||'" missing schema and/or object name'||
3471           '. ('||i||')');
3472       end if;
3473       -- end if customized object in APPS is a synonym, but either
3474       -- the schema or object name that the synonym is supposed to
3475       -- point to was not specified
3476 
3477       if     points_to_schema(i) <> 'BASE'
3478          and points_to_schema(i) <> 'APPS'
3479          and points_to_schema(i) is not null then
3480         raise_application_error(-20001,
3481           'Invalid points_to_schema value: "'||points_to_schema(i)||
3482           '". ('||i||')');
3483       end if;
3484       -- end if points_to_schema not valid
3485 
3486       if     trigger_obj_schema(i) = 'APPS'
3487          and trigger_obj_name(i) = apps_name(i)
3488          and trigger_obj_type(i) <> apps_type(i) then
3489         raise_application_error(-20001,
3490           'Trigger and customized objs have same name, but not same'||
3491           ' type. ('||i||')');
3495 
3492       end if;
3493       -- end check for trigger and customized object same name,
3494       -- but different types
3496     end loop;
3497     -- end loop to validate list entries
3498 
3499   end if;
3500   -- end if initialize list
3501 
3502 exception
3503   when others then
3504     ad_apps_private.error_buf := 'load_exception_list: '||
3505       ad_apps_private.error_buf;
3506     raise;
3507 end load_exception_list;
3508 
3509 
3510 function matching_exception_object (base_schema_name in  varchar2,
3511                                     base_object_name in  varchar2,
3512                                     base_object_type in  varchar2,
3513                                     except_type      in  varchar2,
3514                                     apps_schema_name in  varchar2,
3515                                     found_cust_obj   out nocopy varchar2,
3516                                     cust_obj_correct out nocopy varchar2,
3517                                     index_to_object  out nocopy number)
3518 return boolean
3519 is
3520   i number;
3521   obj_index number;
3522   found_trigger_obj boolean;
3523   found_customized_object boolean;
3524   custom_object_correct boolean;
3525   matches_exactly boolean;
3526   any_obj_w_this_name boolean;
3527   type_of_existing_obj varchar2(100);
3528   trigger_is_base boolean;
3529   points_to_base boolean;
3530   whereami varchar2(100);
3531 begin
3532   -- set default return value for 'out' variables
3533 
3534   whereami := null;
3535 
3536   found_cust_obj := null;
3537   cust_obj_correct := null;
3538   index_to_object := null;
3539 
3540   -- look for matching object on list
3541 
3542   found_trigger_obj := FALSE;
3543   found_customized_object := FALSE;
3544   custom_object_correct := FALSE;
3545   obj_index := 0;
3546 
3547   whereami := ' Before Loop ';
3548 
3549   if list_count is null then
3550     raise_application_error(-20001,
3551       'Exception Objects list has not been initialized');
3552   end if;
3553 
3554   for i in 1..list_count loop
3555 
3556     whereami := ' Loop Top ';
3557 
3558     if     base_name(i) = base_object_name
3559        and base_type(i) = base_object_type
3560        and exception_type(i) = except_type then
3561 
3562       -- decode data in row for this exception object
3563 
3564       whereami := ' A ';
3565 
3566       if    trigger_obj_schema(i) = 'BASE' then
3567         trigger_is_base := TRUE;
3568       elsif trigger_obj_schema(i) = 'APPS' then
3569         trigger_is_base := FALSE;
3570       else
3571         raise_application_error(-20001,
3572           'Invalid trigger_obj_schema value: "'||trigger_obj_schema(i)||
3573           '". ('||i||')');
3574       end if;
3575       -- end if trigger object schema is base schema
3576 
3577       whereami := ' B ';
3578 
3579       if points_to_schema(i) = 'BASE' then
3580         points_to_base := TRUE;
3581       elsif  points_to_schema(i) = 'APPS' then
3582         points_to_base := FALSE;
3583       elsif points_to_schema(i) is null then
3584         points_to_base := null;
3585       else
3586         raise_application_error(-20001,
3587           'Invalid points_to_schema value: "'||points_to_schema(i)||
3588           '". ('||i||')');
3589       end if;
3590       -- end if points_to schema is base schema
3591 
3592       -- check to see if trigger object exists
3593 
3594       whereami := ' C ';
3595 
3596       if trigger_is_base then
3597         ad_apps_private.exact_synonym_match(base_schema_name,
3598           trigger_obj_name(i), null, null,
3599           matches_exactly, any_obj_w_this_name, type_of_existing_obj);
3600       else
3601         ad_apps_private.exact_synonym_match(apps_schema_name,
3602           trigger_obj_name(i), null, null,
3603           matches_exactly, any_obj_w_this_name, type_of_existing_obj);
3604       end if;
3605 
3606       whereami := ' D ';
3607 
3608       if     any_obj_w_this_name
3609          and type_of_existing_obj = trigger_obj_type(i) then
3610 
3611         -- Trigger object exists.
3612         -- Say "this is an exception object" and set row number,
3613         --   then check to see if object is correct
3614 
3615  found_trigger_obj := TRUE;
3616  obj_index := i;
3617 
3618  -- Now check to see if the customized object exists and is correct
3619 
3620         whereami := ' E ';
3621 
3622  if apps_type(i) = 'SYNONYM' then
3623    if points_to_base then
3624      ad_apps_private.exact_synonym_match(apps_schema_name,apps_name(i),
3625        base_schema_name, points_to_name(i), matches_exactly,
3626        any_obj_w_this_name, type_of_existing_obj);
3627    else
3628      ad_apps_private.exact_synonym_match(apps_schema_name,apps_name(i),
3629        apps_schema_name, points_to_name(i), matches_exactly,
3630        any_obj_w_this_name, type_of_existing_obj);
3631    end if;
3632  else
3633    ad_apps_private.exact_synonym_match(apps_schema_name,apps_name(i),
3634      null, null, matches_exactly, any_obj_w_this_name,
3635      type_of_existing_obj);
3636  end if;
3637 
3638         whereami := ' F ';
3639 
3640         if     any_obj_w_this_name
3644 
3641            and type_of_existing_obj = apps_type(i) then
3642 
3643           found_customized_object := TRUE;
3645           -- decide if object was correct
3646 
3647           if apps_type(i) = 'SYNONYM' then
3648             if matches_exactly then
3649               custom_object_correct := TRUE;
3650             end if;
3651             -- end if synonym that matches exactly
3652           else
3653             -- If we got here for a non-synonym, we say the object is
3654             -- correct, as we really have no farther tests we can apply
3655             custom_object_correct := TRUE;
3656           end if;
3657           -- end if object in APPS is a synonym
3658         end if;
3659         -- end if exists object in APPS with same name
3660         -- and type as customized object
3661 
3662       end if;
3663       -- end if trigger object exists and is correct type
3664 
3665       -- break out of loop
3666 
3667       exit;
3668 
3669     end if;
3670     -- end if object name, object type, and exception type match
3671     -- the current object on the exception objects list
3672   end loop;
3673   -- end loop through exception objects list
3674 
3675   whereami := ' After Loop ';
3676 
3677   -- Set return values and exit
3678 
3679   if found_trigger_obj then
3680 
3681     if found_customized_object then
3682       found_cust_obj := 'TRUE';
3683     else
3684       found_cust_obj := 'FALSE';
3685     end if;
3686     -- end if found customized object
3687 
3688     if custom_object_correct then
3689       cust_obj_correct := 'TRUE';
3690     else
3691       cust_obj_correct := 'FALSE';
3692     end if;
3693     -- end if customized object correct
3694 
3695     index_to_object := obj_index;
3696 
3697     return(TRUE);
3698   else
3699     return(FALSE);
3700   end if;
3701   -- end if base object is active exception object
3702 
3703 exception
3704   when others then
3705     ad_apps_private.error_buf := 'matching_exception_object('||
3706      base_schema_name||','||base_object_name||','||
3707      base_object_type||','||except_type||','||
3708      apps_schema_name||')<'||whereami||'> : '||
3709      ad_apps_private.error_buf;
3710     raise;
3711 end matching_exception_object;
3712 
3713 
3714 procedure initialize
3715            (aol_schema in varchar2)
3716 is
3717   l_mrc_schema_name      varchar2(30);
3718   l_release_name         varchar2(30);
3719   l_statement            varchar2(500);
3720   l_first_space_in_rl    number;
3721   l_rel_comp_result      boolean;
3722   cursor GET_MRC_SCHEMA_NAME is
3723     select oracle_username
3724     from fnd_oracle_userid
3725     where read_only_flag = 'K';
3726 begin
3727   -- only perform the work if the variables are null, meaning that
3728   -- this routine has not been called before
3729   if ad_apps_private.is_mls is null
3730     or ad_apps_private.is_mc is null then
3731     -- get values for is_mc and is_mls
3732     declare
3733       x                 varchar2(30);
3734       y                 varchar2(30);
3735       c                 integer;
3736       rows_processed    integer;
3737       statement         varchar2(500);
3738     begin
3739       c := dbms_sql.open_cursor;
3740       statement := 'select nvl(min(multi_currency_flag),''N''), '||
3741                 'nvl(min(multi_lingual_flag),''N'') '||
3742                 'from '||aol_schema||'.fnd_product_groups';
3743       dbms_sql.parse(c, statement, dbms_sql.native);
3744       dbms_sql.define_column(c,1,x,30);
3745       dbms_sql.define_column(c,2,y,30);
3746       rows_processed := dbms_sql.execute(c);
3747       if dbms_sql.fetch_rows(c) > 0 then
3748         dbms_sql.column_value(c,1,x);
3749         dbms_sql.column_value(c,2,y);
3750 
3751       if x = 'Y' then
3752         -- Fixed bug 3258312 : Although MRC flag is at 'Y', someone
3753         -- may have dropped it or the release might be 11.5.10 or more.
3754         -- In both these cases, we have to set "ad_apps_private.is_mc"
3755         -- to 'FALSE'.
3756 
3757         -- get mrc schema name from FND_ORACLE_USERID
3758 
3759         open GET_MRC_SCHEMA_NAME;
3760 
3761         fetch GET_MRC_SCHEMA_NAME
3762         into l_mrc_schema_name;
3763 
3764         if GET_MRC_SCHEMA_NAME%NOTFOUND then
3765 
3766           -- MRC schema not registered in FND_ORACLE_USERID.
3767           -- Reset MRC flag to FALSE.
3768 
3769           close GET_MRC_SCHEMA_NAME;
3770 
3771           ad_apps_private.is_mc := FALSE;
3772         else
3773 
3774         -- MRC schema registered in FND_ORACLE_USERID, Check in DBA_USERS.
3775 
3776           close GET_MRC_SCHEMA_NAME;
3777 
3778           if ad_apps_private.check_if_schema_exists(l_mrc_schema_name) then
3779 
3780              -- Fixed bug 3353468 to resolve a runtime issue for
3781              -- 11.5.10. Check if the release>=11.5.10. if yes, MRC
3782              -- is not enabled
3783 
3784              -- Get the release name from FND_PRODUCT_GROUPS table.
3785 
3786              begin
3787                 l_statement := 'select release_name from ' || aol_schema ||
3788                                '.fnd_product_groups';
3792                 when others then
3789                 execute immediate l_statement into l_release_name;
3790 
3791              exception
3793                   raise_application_error(-20000,
3794                   'Unable to get the RELEASE_NAME from FND_PRODUCT_GROUPS.');
3795              end;
3796 
3797              -- Trimming copied from FND_RELEASE.get_release()
3798              l_release_name      := rtrim(ltrim(l_release_name, ' '),' ');
3799              l_first_space_in_rl := instr(l_release_name,' ');
3800              if not l_first_space_in_rl = 0 then
3801                 -- There is extra info, remove it
3802                 l_release_name := substr(l_release_name, 1,
3803                                          l_first_space_in_rl - 1);
3804              end if;
3805              -- End of trimming.
3806 
3807              -- Now check for release information,
3808              -- set is_mc flag to TRUE if release is
3809              -- 11.5.9 or lower and FALSE if otherwise
3810 
3811              l_rel_comp_result :=  compare_releases(l_release_name ,
3812                                                     '11.5.9');
3813 
3814              if (l_rel_comp_result = TRUE) then
3815                 ad_apps_private.is_mc := TRUE;
3816              else
3817                 ad_apps_private.is_mc := FALSE;
3818              end if;
3819 
3820             else
3821               -- no MRC schema in DBA_USERS!
3822               ad_apps_private.is_mc := FALSE;
3823            end if;
3824 
3825           end if;
3826           -- end if block for MRC schema registered in FND_ORACLE_USERID
3827 
3828         else -- if not fnd_product_groups.multi_currency_flag
3829 
3830           ad_apps_private.is_mc := FALSE;
3831 
3832         end if;
3833 
3834         if y = 'Y' then
3835           ad_apps_private.is_mls := TRUE;
3836         else
3837           ad_apps_private.is_mls := FALSE;
3838         end if;
3839         dbms_sql.close_cursor(c);
3840       else
3841         raise no_data_found;
3842       end if;
3843     exception
3844       when others then
3845         dbms_sql.close_cursor(c);
3846         ad_apps_private.error_buf := 'statement='||
3847                                      statement||':'||
3848                                      ad_apps_private.error_buf;
3849         raise;
3850     end;
3851 
3852   end if;
3853 
3854 exception
3855   when others then
3856     ad_apps_private.error_buf := 'initialize('||aol_schema||'): '||
3857                 ad_apps_private.error_buf;
3858     raise;
3859 end initialize;
3860 
3861 
3862 --
3863 --
3864 -- Function compare releases. Copied from AD_PATCH.compare_versions()
3865 -- Compare passed release_levels. Returns TRUE if release_1 <= release_2.
3866 --
3867 --
3868 
3869 function compare_releases(release_1 in varchar2,
3870                           release_2 in varchar2)
3871 return boolean
3872 is
3873 
3874   release_1_str  varchar2(132);
3875   release_2_str  varchar2(132);
3876   release_1_ver number;
3877   release_2_ver number;
3878   ret_status boolean           := TRUE;
3879 
3880 begin
3881 
3882   release_1_str   := release_1 || '.';
3883   release_2_str  := release_2 || '.';
3884 
3885   while release_1_str is not null or release_2_str is not null loop
3886 
3887       -- Parse out a version from release_1
3888       if (release_1_str is null) then
3889          release_1_ver := 0;
3890       else
3891          release_1_ver := nvl(to_number(substr(release_1_str,1,
3892                              instr(release_1_str,'.')-1)),-1);
3893          release_1_str := substr(release_1_str,instr(release_1_str,'.')+1);
3894       end if;
3895 
3896       -- Next parse out a version from release_2
3897 
3898       if (release_2_str is null)
3899       then
3900         release_2_ver := 0;
3901       else
3902         release_2_ver := nvl(to_number(substr(release_2_str,1,
3903                              instr(release_2_str,'.')-1)),-1);
3904         release_2_str := substr(release_2_str,instr(release_2_str,'.')+1);
3905       end if;
3906 
3907       if (release_1_ver > release_2_ver)
3908       then
3909         ret_status := FALSE;
3910         exit;
3911       elsif (release_1_ver < release_2_ver)
3912       then
3913         exit;
3914       end if;
3915 
3916       -- Otherwise continue to loop.
3917 
3918   end loop;
3919 
3920   return(ret_status);
3921 
3922 end compare_releases;
3923 
3924 
3925 end ad_apps_private;