DBA Data[Home] [Help]

PACKAGE BODY: SYSTEM.AD_APPS_PRIVATE

Source


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