DBA Data[Home] [Help]

PACKAGE BODY: SYSTEM.AD_CLONE_UTILS

Source


1 package body AD_CLONE_UTILS as
2 -- $Header: adclutlb.pls 120.0 2005/05/25 11:48:46 appldev noship $
3 
4   g_db_version            varchar2(40) := NULL;
5   native_clone_supported  boolean      := FALSE;
6   dbms_metadata_supported boolean      := FALSE;
7   g_seq_no                number       := 0;
8 
9 
10   MAX_LOGSTR_SIZE CONSTANT number      := 80;    -- maximum size of log message
11                                                  -- line
12   DQT             CONSTANT varchar2(5) := '"';   -- double quotes
13   QT              CONSTANT varchar2(5) := '''';  -- quotes
14   CCT             CONSTANT varchar2(5) := '||';
15 
16   G_CLONE_SCHEMA_NAME CONSTANT varchar2(30) := 'APPSCLONE';
17   G_SPEC_SCHEMA_NAME  CONSTANT varchar2(30) := 'APPSSPEC';
18 
19 
20   function get_db_version return varchar2 is
21     l_version  varchar2(40);
22   begin
23 
24     if (g_db_version is null) then
25       select version
26       into   g_db_version
27       from   v$instance
28       where  rownum = 1;
29     end if;
30 
31     return(g_db_version);
32   end;
33 
34   function get_schema_info(X_schema_name in varchar2) return varchar2
35   is
36     l_read_only_flag  varchar2(10);
37   begin
38 
39     EXECUTE IMMEDIATE
40        ' SELECT read_only_flag'||
41        ' FROM FND_ORACLE_USERID u'||
42        ' WHERE oracle_username = upper(:b)'
43     INTO l_read_only_flag USING X_schema_name;
44 
45     return(l_read_only_flag);
46 
47   exception
48     when no_data_found then
49        return(null);
50   end;
51 
52   procedure println(X_msg          in varchar2)
53   is
54     i      integer := 1;
55     maxlen integer;
56   begin
57     maxlen := length(X_msg);
58     while (i < maxlen+1) loop
59       g_seq_no := g_seq_no + 1;
60 
61       INSERT INTO AD_GENERIC_TEMP(line_sequence, contents)
62       VALUES (g_seq_no, substr(X_msg, i, MAX_LOGSTR_SIZE));
63 
64       i := i + MAX_LOGSTR_SIZE;
65     end loop;
66 
67   end;
68 
69   procedure print_timestamp(X_msg          in varchar2)
70   is
71   begin
72        println(X_msg||' '||to_char(sysdate, 'YYYY/MM/DD HH24:MI:SS'));
73   end;
74 
75   procedure validate_schema(X_schema_name in varchar2,
76                             X_schema_type in varchar2)
77   is
78     l_schema_info varchar2(10);
79   begin
80 
81      if (X_schema_type not in (SOURCE_SCHEMA_TYPE,
82                                CLONE_SCHEMA_TYPE,
83                                SPEC_SCHEMA_TYPE)) then
84          raise_application_error(-20001,
85            'Invalid schema type : '||X_schema_type);
86      end if;
87 
88      l_schema_info := get_schema_info(X_schema_name);
89 
90      --
91      -- clone snd spec chema should not be a registered schema
92      --
93      if (X_schema_type in (CLONE_SCHEMA_TYPE, SPEC_SCHEMA_TYPE)) then
94         if (l_schema_info is not null) then
95            raise_application_error(-20001,
96                'Schema "'||X_schema_name||'" is a registered schema '||
97                'and cannot be used for Clone operations.');
98         end if;
99 
100         --
101         -- In 11i, the clone schema and spec schema are hard-coded to APPSCLONE
102         -- Make sure no other schema is specified
103         --
104         if (X_schema_type in (CLONE_SCHEMA_TYPE) and
105             X_schema_name <> G_CLONE_SCHEMA_NAME)
106         then
107            raise_application_error(-20001,
108                'Invalid name for clone schema : '||X_schema_name);
109         end if;
110 
111         if (X_schema_type in (SPEC_SCHEMA_TYPE) and
112             X_schema_name <> G_SPEC_SCHEMA_NAME)
113         then
114            raise_application_error(-20001,
115                'Invalid name for specifications schema : '||X_schema_name);
116         end if;
117 
118      end if;
119 
120      --
121      -- the source schema must be a universal schema
122      --
123      if (X_schema_type in (SOURCE_SCHEMA_TYPE)) then
124         if (nvl(l_schema_info, '~') <> 'U') then
125            raise_application_error(-20001,
126              'Schema "'||X_schema_name||'" is not a registered APPS schema '||
127              'and cannot be used as the source for Clone operations.');
128         end if;
129      end if;
130 
131   end;
132 
133   procedure validate_schemas(X_source_schema in varchar2,
134                              X_clone_schema  in varchar2,
135                              X_spec_schema   in varchar2)
136   is
137   begin
138       validate_schema(X_source_schema, SOURCE_SCHEMA_TYPE);
139       validate_schema(X_clone_schema,  CLONE_SCHEMA_TYPE);
140       validate_schema(X_spec_schema,   SPEC_SCHEMA_TYPE);
141   end;
142 
143   procedure get_column_list(X_table_owner         in varchar2,
144                             X_table_name          in varchar2,
145                             X_from_APPS_schema    in varchar2,
146                             X_col_list           out nocopy varchar2,
147                             X_long_column_exists out nocopy boolean,
148                             X_type_column_exists out nocopy boolean,
149                             X_APPS_type_column_exists out nocopy boolean)
150   is
151     cursor c_col is
152        select column_name, data_type, data_type_owner
153        from  dba_tab_columns
154        where owner = X_table_owner
155        and   table_name = X_table_name;
156   begin
157 
158     X_col_list := null;
159     X_long_column_exists := FALSE;
160     X_type_column_exists := FALSE;
161     X_APPS_type_column_exists := FALSE;
162 
163     for crec in c_col loop
164 
165       if (crec.data_type like 'LONG%') then
166          X_long_column_exists := TRUE;
167       elsif ((crec.data_type_owner is not null) and
168             (crec.data_type_owner = X_from_APPS_schema)) then
169          X_type_column_exists := TRUE;
170          X_APPS_type_column_exists := TRUE;
171       else
172 
173          if (crec.data_type_owner is not null) then
174            X_type_column_exists := TRUE;
175          end if;
176 
177          if (X_col_list is not null) then
178             X_col_list := X_col_list ||', '||crec.column_name;
179          else
180             X_col_list := crec.column_name;
181          end if;
182        end if;
183     end loop;
184 
185   end;
186 
187   procedure check_for_special_columns(X_table_name            in varchar2,
188                                       X_from_schema           in varchar2,
189                                       X_long_column_exists    out NOCOPY boolean,
190                                       X_type_column_exists    out NOCOPY boolean)
191   is
192 
193     cursor c_col is
194        select column_name, data_type, data_type_owner
195        from  dba_tab_columns
196        where owner = X_from_schema
197        and   table_name = X_table_name
198        and (data_type  in ('LONG', 'LONG RAW')
199             or
200             (data_type_owner is not null
201              and
202              data_type_owner not in ('SYSTEM', 'MDSYS', X_from_schema)));
203 
204   begin
205     for crec in c_col loop
206 
207       if (crec.data_type like 'LONG%') then
208          X_long_column_exists := TRUE;
209       end if;
210 
211       if (crec.data_type_owner is not null) then
212          X_type_column_exists := TRUE;
213       end if;
214 
215     end loop;
216   end;
217 
218   procedure grant_on_type(X_type_name           in varchar2,
219                           X_type_owner          in varchar2,
220                           X_grant_to_schema     in varchar2,
221                           X_type_exists         out NOCOPY boolean)
222   is
223     l_type_exists varchar2(1);
224   begin
225 
226     begin
227       select 'x'
228       into   l_type_exists
229       from   dba_types
230       where type_name = X_type_name
231       and   owner = X_type_owner;
232 
233       X_type_exists := TRUE;
234     exception
235      when NO_DATA_FOUND then
236        X_type_exists := FALSE;
237        return;
238     end;
239 
240     ad_inst.do_apps_ddl(X_type_owner,
241                         'GRANT ALL ON '||
242                         X_type_owner||'.'||X_type_name||
243                         ' TO '|| X_grant_to_schema|| ' WITH GRANT OPTION');
244   end;
245 
246   procedure copy_table_definition(
247                         X_table_name               in varchar2,
248                         X_base_schema              in varchar2,
249                         X_spec_schema              in varchar2,
250                         X_copy_pk_cons             in boolean  default FALSE,
251                         X_preserve_partitions      in boolean  default FALSE,
252                         X_data_tablespace          in varchar2 default NULL,
253                         X_index_tablespace         in varchar2 default NULL,
254                         X_from_objtyp_schema       in varchar2,
255                         X_to_objtyp_schema         in varchar2,
256                         X_overwrite                in boolean  default FALSE)
257   is
258     l_overwrite varchar2(1);
259   begin
260 
261     if (X_overwrite = TRUE) then
262       l_overwrite := 'Y';
263     else
264       l_overwrite := 'N';
265     end if;
266 
267     EXECUTE IMMEDIATE
268        'declare '||
269        '  ddl_stmt CLOB; '||
270        '  c1       integer; '||
271        '  lb       number; '||
272        '  ub       number; '||
273        '  offset   integer := 1; '||
274        '  ddllen   integer; '||
275        '  MAXSIZE  integer := 32000; '||
276        '  ddl_tab  dbms_sql.varchar2a; '||
277        ''||
278        'begin '||
279        '  dbms_metadata.set_transform_param( '||
280        '     dbms_metadata.SESSION_TRANSFORM, '||
281        '     ''PRETTY'', FALSE); '||
282        ''||
283        '  dbms_metadata.set_transform_param( '||
284        '      dbms_metadata.SESSION_TRANSFORM, '||
285        '      ''SEGMENT_ATTRIBUTES'', FALSE); '||
286 
287        '  dbms_metadata.set_transform_param( '||
288        '      dbms_metadata.SESSION_TRANSFORM, '||
289        '      ''REF_CONSTRAINTS'', FALSE); '||
290        ''||
291        'ddl_stmt := dbms_metadata.get_ddl('||QT||'TABLE'||QT||', '||
292                                              QT||X_table_name||QT||', '||
293                                              QT||X_base_schema||QT||'); '||
294        ''||
295        'ddl_stmt := replace(ddl_stmt, '||
296                        QT||' TABLE '||DQT||X_base_schema||DQT||'.'||QT||
297                   ','||QT||' TABLE '||DQT||X_spec_schema||DQT||'.'||QT||
298                                     '); '||
299        ''||
300        'ddl_stmt := replace(ddl_stmt, '||
301                        QT||DQT||X_from_objtyp_schema||DQT||'.'||QT||
302                   ','||QT||DQT||X_to_objtyp_schema||DQT||'.'||QT||
303                                     '); '||
304        ''||
305        'ddl_stmt := replace(ddl_stmt, '||QT||'USAGE_QUEUE'||QT||
306                                     ','||QT||' '||QT||
307                                     '); '||
308        ''||
309        'offset := 1; '||
310        'lb := 1; '||
311        'ub := 0; '||
312        'ddllen := dbms_lob.getlength(ddl_stmt); '||
313        ''||
314        'while (offset <= ddllen) '||
315        'loop '||
316        '  ub := ub + 1; '||
317        '  ddl_tab(ub) := dbms_lob.substr(ddl_stmt, MAXSIZE, offset); '||
318        '  offset := offset + length(ddl_tab(ub)); '||
319        'end loop; '||
320        ''||
321        'c1 := dbms_sql.open_cursor; '||
322        ''||
323        'begin'||
324        '   dbms_sql.parse(c1, ddl_tab, lb, ub, FALSE, dbms_sql.native); '||
325        'exception '||
326        '  when others then '||
327        '    if (sqlcode = -955) then '||
328        '      if (:l_overwrite = ''Y'') then '||
329        ''||
330        '        EXECUTE IMMEDIATE ''DROP TABLE '||X_spec_schema||'.'||
331                                               '"'||X_table_name||'"''; '||
332        '        dbms_sql.parse(c1, ddl_tab, lb, ub, FALSE, dbms_sql.native); '||
333        '      end if;'||
334        '    else '||
335        '       raise; '||
336        '    end if;'||
337        'end;'||
338        ''||
339        'dbms_sql.close_cursor(c1); '||
340        ''||
341        'end; ' USING l_overwrite;
342   end;
343 
344   procedure copy_special_table(
345                         X_table_name               in varchar2,
346                         X_from_schema              in varchar2,
347                         X_to_schema                in varchar2,
348                         X_copy_pk_cons             in boolean  default FALSE,
349                         X_preserve_partitions      in boolean  default FALSE,
350                         X_data_tablespace          in varchar2 default NULL,
351                         X_index_tablespace         in varchar2 default NULL,
352                         X_from_objtyp_schema in varchar2,
353                         X_to_objtyp_schema   in varchar2,
354                         X_overwrite                in boolean  default FALSE)
355 
356   is
357     l_stmt      varchar2(32000);
358     l_col_stmt  varchar2(512);
359     l_data_type_owner varchar2(512);
360     l_type_exists  boolean;
361 
362     cursor c_col is
363       select column_name, data_type, data_type_owner, data_length,
364              data_precision, data_scale, nullable
365       from   dba_tab_columns
366       where  owner = X_from_schema
367       and    table_name = X_table_name
368       order by column_id;
369   begin
370 
371      l_stmt := 'CREATE TABLE '||X_to_schema||'.'||X_table_name||' ( ';
372 
373      for c_rec in c_col loop
374 
375         if (l_col_stmt is not null) then
376           l_stmt := l_stmt||', ';
377         end if;
378 
379         l_col_stmt := c_rec.column_name;
380         l_data_type_owner := c_rec.data_type_owner;
381 
382         if (X_to_objtyp_schema is not null
383             and
384             c_rec.data_type_owner not in ('SYSTEM', 'MDSYS', X_from_schema))
385         then
386             grant_on_type(c_rec.data_type,
387                           X_to_objtyp_schema,
388                           X_to_schema,
389                           l_type_exists);
390 
391             if (l_type_exists = TRUE) then
392                l_data_type_owner := X_to_objtyp_schema;
393             end if;
394 
395         end if;
396 
397         if (l_data_type_owner is not null) then
398            l_col_stmt := l_col_stmt||' '||
399                              l_data_type_owner||'.'||c_rec.data_type;
400         else
401            l_col_stmt := l_col_stmt||' '||
402                              c_rec.data_type;
403 
404            if (c_rec.data_type = 'NUMBER')
405            then
406               if (c_rec.data_precision is not null) then
407                  l_col_stmt := l_col_stmt || '('||c_rec.data_precision;
408 
409                  if (c_rec.data_scale > 0) then
410                     l_col_stmt := l_col_stmt || ','||c_rec.data_scale||')';
411                  else
412                     l_col_stmt := l_col_stmt || ')';
413                  end if;
414 
415               end if;
416 
417            elsif (c_rec.data_type in ('VARCHAR2', 'CHAR', 'RAW')) then
418               l_col_stmt := l_col_stmt || '('||c_rec.data_length||')';
419            end if;
420 
421            if (c_rec.nullable = 'N') then
422              l_col_stmt := l_col_stmt || ' NOT NULL';
423            end if;
424 
425         end if;
426 
427         l_stmt := l_stmt || l_col_stmt;
428      end loop;
429 
430      l_stmt := l_stmt||')';
431 
432      -- println(l_stmt);
433 
434      EXECUTE IMMEDIATE l_stmt;
435 
436 
437   exception
438     when others then
439 
440        if (sqlcode = -955) then
441          --
442          -- table already exists. drop table and recreate it
443          --
444 
445          if (X_overwrite = TRUE) then
446            EXECUTE IMMEDIATE 'DROP TABLE '||X_to_schema||'.'||X_table_name;
447 
448            EXECUTE IMMEDIATE l_stmt;
449 
450          else
451            raise;
452          end if;
453        else
454          raise;
455        end if;
456   end;
457 
458   --
459   -- create a copy of table in the spec schema
460   -- Any type references in X_from_APPS_schema are changed to
461   -- X_to_APPS_schema
462   --
463   procedure clone_table(X_table_name            in varchar2,
464                         X_from_schema           in varchar2,
465                         X_to_schema             in varchar2,
466                         X_from_APPS_schema      in varchar2,
467                         X_to_APPS_schema        in varchar2,
468                         X_copy_pk_cons          in boolean  default TRUE,
469                         X_preserve_partitions   in boolean  default TRUE,
470                         X_data_tablespace       in varchar2 default NULL,
471                         X_index_tablespace      in varchar2 default NULL,
472                         X_overwrite             in boolean  default FALSE)
473   is
474 
475     l_stmt                   varchar2(32000);
476     l_col_list               varchar2(15000);
477     l_long_column_exist      boolean := FALSE;
478     l_type_column_exist      boolean := FALSE;
479     l_APPS_type_column_exist boolean := FALSE;
480 
481     l_spec_table_timestamp   varchar2(30);
482     l_source_table_timestamp varchar2(30);
483     l_spec_table_exists      boolean;
484     l_overwrite_spec_table   boolean;
485 
486     l_dummy                  varchar2(1);
487     l_temporary              varchar2(1);
488 
489   begin
490 
491     if (X_overwrite = TRUE) then
492        l_overwrite_spec_table := TRUE;
493     else
494        --
495        -- fisrt get timestamp for spec table. If table exists, then compare
496        -- timestamps
497        --
498 
499        --
500        -- find if table is a temporary table. You cannot perform a transaction
501        -- against a temporary table and then perform a DDL against that table
502        --
503        l_overwrite_spec_table := FALSE;
504 
505        begin
506           SELECT spec.timestamp, temporary
507           INTO   l_spec_table_timestamp, l_temporary
508           FROM   DBA_OBJECTS spec
509           WHERE  spec.OWNER = X_to_schema
510           AND    spec.OBJECT_NAME = X_table_name
511           AND    spec.OBJECT_TYPE = 'TABLE';
512 
513        exception
514           when NO_DATA_FOUND then
515              l_overwrite_spec_table := TRUE;
516              l_temporary := NULL;
517        end;
518 
519        --
520        -- now that spec table exists, compare timestamp with source table
521        --
522        if (l_overwrite_spec_table = FALSE) then
523 
524          begin
525             SELECT src.timestamp, nvl(l_temporary, temporary)
526             INTO   l_source_table_timestamp, l_temporary
527             FROM   DBA_OBJECTS src
528             WHERE  src.OWNER = X_from_schema
529             AND    src.OBJECT_NAME = X_table_name
530             AND    src.OBJECT_TYPE = 'TABLE';
531 
532             if (l_source_table_timestamp > l_spec_table_timestamp) then
533                l_overwrite_spec_table := TRUE;
534             end if;
535          end;
536        end if;
537     end if;
538 
539     if (l_overwrite_spec_table = FALSE) then
540        return;
541     end if;
542 
543     get_column_list(X_from_schema,
544                     X_table_name,
545                     X_from_APPS_schema,
546                     l_col_list,
547                     l_long_column_exist, l_type_column_exist,
548                     l_APPS_type_column_exist);
549 
550     --
551     -- grant on the table to ensure that the destination schema has proper
552     -- privileges on type referenced, if any, by the table
553     --
554     if (l_type_column_exist = TRUE) then
555 
556       ad_inst.do_apps_ddl(X_from_schema,
557                           'GRANT SELECT ON '||
558                           X_from_schema||'.'||X_table_name||
559                           ' TO '|| X_to_schema|| ' WITH GRANT OPTION');
560     end if;
561 
562     if ((dbms_metadata_supported = TRUE) or
563         ( l_long_column_exist = FALSE and l_APPS_type_column_exist = FALSE))
564     then
565 
566        copy_table_definition(
567                   X_table_name=>X_table_name,
568                   X_base_schema=>X_from_schema,
569                   X_spec_schema=>X_to_schema,
570                   X_copy_pk_cons=>X_copy_pk_cons,
571                   X_preserve_partitions=>X_preserve_partitions,
572                   X_data_tablespace=>X_data_tablespace,
573                   X_index_tablespace=>X_index_tablespace,
574                   X_from_objtyp_schema=>X_from_APPS_schema,
575                   X_to_objtyp_schema=>X_to_APPS_schema,
576                   X_overwrite=>l_overwrite_spec_table);
577     else
578 
579       copy_special_table(
580            X_table_name=>X_table_name,
581            X_from_schema=>X_from_schema,
582            X_to_schema=>X_to_schema,
583            X_copy_pk_cons=>X_copy_pk_cons,
584            X_preserve_partitions=>X_preserve_partitions,
585            X_data_tablespace=>X_data_tablespace,
586            X_index_tablespace=>X_index_tablespace,
587            X_from_objtyp_schema=>X_from_APPS_schema,
588            X_to_objtyp_schema=>X_to_APPS_schema,
589            X_overwrite=>l_overwrite_spec_table);
590 
591     end if;
592 
593     if (l_temporary = 'N') then
594       --
595       -- insert at least one row of data
596       --
597       l_stmt := ' INSERT INTO '||X_to_schema||'.'||X_table_name||
598                           '('|| l_col_list||') '||
599                 ' SELECT '||l_col_list||
600                 ' FROM '||X_from_schema||'.'||X_table_name||
601                 ' WHERE rownum = 1 '||
602                 ' AND NOT EXISTS ( '||
603                        ' SELECT null'||
604                        ' FROM '||X_to_schema||'.'||X_table_name||
605                        ' WHERE rownum = 1)';
606 
607       EXECUTE IMMEDIATE l_stmt;
608 
609       commit;
610     end if;
611 
612   end;
613 
614   procedure copy_ddl_package(X_name   in varchar2,
615                              X_type   in varchar2,
616                              X_source_schema in varchar2,
617                              X_clone_schema  in varchar2)
618   is
619     source_text  varchar2(10000):= NULL;
620 
621     cursor c1 is
622       select text
623       from   dba_source
624       where owner = X_source_schema
625       and name = X_name
626       and type = X_type
627       order by line;
628 
629   begin
630 
631      for crec in c1 loop
632        if (source_text is null) then
633           source_text := 'CREATE OR REPLACE '||X_type||' '||
634                          X_clone_schema||'.'||X_name||' AS ';
635        else
636           source_text := source_text||' '||crec.text;
637        end if;
638      end loop;
639 
640      EXECUTE IMMEDIATE source_text;
641 
642   end;
643 
644   procedure clone_schema(X_source_schema        in varchar2,
645                          X_clone_schema         in varchar2,
646                          X_degree               in number)
647   is
648     l_clone_phase varchar2(30);
649     l_clone_status varchar2(30);
650   begin
651 
652     validate_schema(X_source_schema, SOURCE_SCHEMA_TYPE);
653     validate_schema(X_clone_schema, CLONE_SCHEMA_TYPE);
654 
655     if (native_clone_supported = TRUE) then
656 
657        get_status(X_source_schema, X_clone_schema,
658                   l_clone_phase, l_clone_status);
659 
660        --
661        -- clone is allowed only if current status is one of
662        --    UNKNOWN phase and UNKNOWN status
663        --    CLONE   phase and INPROGRESS status
664        --    CLONE   phase and FAILED status
665        --    MERGE   phase and COMPLETED status
666 
667        if (not((l_clone_phase = UNKNOWN_PHASE and
668                 l_clone_status = STATUS_UNKNOWN)
669                or
670                (l_clone_phase = CLONE_PHASE and
671                 l_clone_status in (STATUS_INPROGRESS, STATUS_FAILED))
672                or
673                (l_clone_phase = MERGE_PHASE and
674                 l_clone_status = STATUS_COMPLETED)))
675        then
676           raise_application_error(-20001,
677                  'CLONE operation invalid for the current state '||
678                  'of the clone schema. '||
679                  '[ Current Phase : '||l_clone_phase||
680                  '  Status : '||l_clone_status||' ]');
681 
682        end if;
683 
684        --
685        -- recover from a prior clone if necessary
686        --
687        if (l_clone_phase = CLONE_PHASE AND
688            l_clone_status in (STATUS_INPROGRESS, STATUS_FAILED)) then
689 
690           println('The previous CLONE operation did not succeed '||
691                   'and requires recovery.');
692 
693           print_timestamp('Recovery operation started at :');
694 
695           EXECUTE IMMEDIATE
696              'begin '||
697              '  sys.dbms_schema_copy.clone_recovery('||
698                             'src_sch=>:a, ' ||
699                             'dst_sch=>:b, ' ||
700                             'threads=>:c); ' ||
701              'end;'
702              USING IN X_source_schema, X_clone_schema, X_degree;
703 
704           print_timestamp('Recovery operation completed at :');
705        else
706 
707           print_timestamp('CLONE operation started   at : ');
708 
709           EXECUTE IMMEDIATE
710              'begin '||
711              '  sys.dbms_schema_copy.clone('||
712                             'src_sch=>:a, ' ||
713                             'dst_sch=>:b, ' ||
714                             'threads=>:c); ' ||
715              'end;'
716              USING IN X_source_schema, X_clone_schema, X_degree;
717 
718           print_timestamp('CLONE operation completed at : ');
719        end if;
720 
721     else
722 
723        --
724        -- native clone is not specified, just copy DDL package to the
725        -- clone schema
726        --
727        copy_ddl_package( 'APPS_DDL',
728                          'PACKAGE',
729                          X_source_schema,
730                          X_clone_schema);
731 
732        copy_ddl_package( 'APPS_ARRAY_DDL',
733                          'PACKAGE',
734                          X_source_schema,
735                          X_clone_schema);
736 
737        copy_ddl_package( 'APPS_DDL',
738                          'PACKAGE BODY',
739                          X_source_schema,
740                          X_clone_schema);
741 
742        copy_ddl_package( 'APPS_ARRAY_DDL',
743                          'PACKAGE BODY',
744                          X_source_schema,
745                          X_clone_schema);
746     end if;
747   end;
748 
749   procedure sync_schema(X_source_schema         in varchar2,
750                         X_clone_schema          in varchar2,
751                         X_degree                in number)
752   is
753     l_clone_phase varchar2(30);
754     l_clone_status varchar2(30);
755   begin
756 
757     validate_schema(X_source_schema, SOURCE_SCHEMA_TYPE);
758     validate_schema(X_clone_schema, CLONE_SCHEMA_TYPE);
759 
760     if (native_clone_supported = TRUE) then
761 
762        get_status(X_source_schema, X_clone_schema,
763                   l_clone_phase, l_clone_status);
764 
765        --
766        -- SYNC is allowed only if current status is one of
767        --    CLONE   phase and COMPLETED status
768 
769        if (not((l_clone_phase = CLONE_PHASE and
770                 l_clone_status = STATUS_COMPLETED)))
771        then
772           raise_application_error(-20001,
773                'SYNC operation invalid for the current state of '||
774                'the clone schema. '||
775                '[ Current Phase : '||l_clone_phase||
776                '  Status : '||l_clone_status||' ]');
777        end if;
778 
779        print_timestamp('SYNC operation started at   : ');
780 
781        EXECUTE IMMEDIATE
782           'begin '||
783           '  sys.dbms_schema_copy.sync_code('||
784                          'src_sch=>:a,'||
785                          'dst_sch=>:b,'||
786                          'ignore_conflict=>TRUE); '||
787           'end;'
788           USING IN X_source_schema, X_clone_schema;
789 
790        print_timestamp('SYNC operation completed at : ');
791     end if;
792   end;
793 
794   procedure merge_schema(X_source_schema        in varchar2,
795                          X_clone_schema         in varchar2,
796                          X_degree               in number)
797   is
798     l_clone_phase varchar2(30);
799     l_clone_status varchar2(30);
800   begin
801 
802     validate_schema(X_source_schema, SOURCE_SCHEMA_TYPE);
803     validate_schema(X_clone_schema, CLONE_SCHEMA_TYPE);
804 
805     if (native_clone_supported = TRUE) then
806 
807        get_status(X_source_schema, X_clone_schema,
808                   l_clone_phase, l_clone_status);
809 
810        --
811        -- MERGE is allowed only if current status is one of
812        --    CLONE   phase and COMPLETED status
813 
814        if (not((l_clone_phase = CLONE_PHASE and
815                 l_clone_status = STATUS_COMPLETED)
816                or
817                (l_clone_phase = MERGE_PHASE and
818                 l_clone_status <> STATUS_COMPLETED)))
819        then
820           raise_application_error(-20001,
821                'MERGE operation invalid for the current state of '||
822                'the clone schema. '||
823                '[ Current Phase : '||l_clone_phase||
824                '  Status : '||l_clone_status||' ]');
825        end if;
826 
827        print_timestamp('MERGE operation started   at : ');
828 
829        EXECUTE IMMEDIATE
830           'begin '||
831           '  sys.dbms_schema_copy.swap('||
832                          'src_sch=>:a,'||
833                          'dst_sch=>:b,'||
834                          'ignore_conflict=>TRUE); '||
835           'end;'
836           USING IN X_source_schema, X_clone_schema;
837 
838        print_timestamp('MERGE operation completed at : ');
839 
840     end if;
841 
842   end;
843 
844   procedure cleanup_chkfile_info(X_apps_schema  in varchar2) is
845     cursor c_syn is
846       select synonym_name, table_name, table_owner
847       from   dba_synonyms
848       where owner = X_apps_schema
849       and    synonym_name = 'AD_PREPMODE_CHECK_FILES';
850   begin
851 
852     for c_rec in c_syn loop
853 
854        EXECUTE IMMEDIATE 'TRUNCATE TABLE '||
855                          c_rec.table_owner||'.'||c_rec.table_name;
856     end loop;
857 
858   end;
859 
860   procedure cleanup_spec_schema(X_spec_schema in varchar2) is
861 
862       TYPE spec_obj_type IS TABLE OF varchar2(128);
863       TYPE spec_obj_name IS TABLE OF varchar2(30);
864       spec_obj_type_tab   spec_obj_type;
865       spec_obj_name_tab   spec_obj_name;
866 
867       i            binary_integer;
868       l_sql_stmt   varchar2(2000);
869 
870   begin
871 
872      validate_schema(X_spec_schema, SPEC_SCHEMA_TYPE);
873 
874      print_timestamp('CLEANUP of Spec schema ('||
875                      X_spec_schema||') started at   : ');
876 
877 
878      begin
879 
880        select object_type, object_name
881        bulk collect into spec_obj_type_tab, spec_obj_name_tab
882        from dba_objects
883        where owner = X_spec_schema
884        and object_name not in ('APPS_DDL', 'APPS_ARRAY_DDL')
885        and object_type not in ('INDEX', 'LOB INDEX', 'LOB');
886 
887      exception
888        when NO_DATA_FOUND then
889           null;
890      end;
891 
892      --
893      -- drop individual objects
894      --
895      for i in 1..spec_obj_name_tab.count
896      loop
897         begin
898 
899           l_sql_stmt := 'DROP '||spec_obj_type_tab(i)||
900                        ' '||X_spec_schema||'."'||spec_obj_name_tab(i)||'"';
901           EXECUTE IMMEDIATE l_sql_stmt;
902         exception
903           when others then
904              println(l_sql_stmt);
905              if (SQLCODE in (-950, -942, -1434, -4043)) then
906                 null;
907              else
908                 raise;
909              end if;
910         end;
911      end loop;
912 
913      print_timestamp('CLEANUP of Spec schema ('||
914                      X_spec_schema||') completed at : ');
915   end;
916 
917   procedure cleanup_clone_schema(X_source_schema in varchar2,
918                                  X_clone_schema  in varchar2,
919                                  X_force_flag    in boolean,
920                                  X_threads       in number) is
921     l_force_str varchar2(10);
922     TYPE clone_obj_type IS TABLE OF varchar2(128);
923     TYPE clone_obj_name IS TABLE OF varchar2(30);
924     clone_obj_type_tab   clone_obj_type;
925     clone_obj_name_tab   clone_obj_name;
926 
927     i            binary_integer;
928     l_sql_stmt   varchar2(2000);
929     l_obj_count  number;
930 
931   begin
932      l_force_str := 'FALSE';
933      validate_schema(X_clone_schema, CLONE_SCHEMA_TYPE);
934 
935      print_timestamp('CLEANUP of Clone schema ('||
936                      X_clone_schema||') started at   : ');
937 
938      if (X_force_flag = TRUE) then
939        l_force_str := 'TRUE';
940      end if;
941 
942      begin
943 
944        EXECUTE IMMEDIATE
945           'begin '||
946             '  sys.dbms_schema_copy.clean_target('||
947                            ' dst_sch=>:a,'||
948                            ' force=>'||l_force_str||','||
949                            ' threads=>:c);'||
950           'end;'
951           USING IN X_clone_schema, X_threads;
952      exception
953         --
954         -- handle case where the clone operation may have failed
955         --
956         when others then
957            if (sqlcode = -39312) then
958              EXECUTE IMMEDIATE
959                 'begin '||
960                   '  sys.dbms_schema_copy.clean_failed_clone('||
961                                  ' src_sch=>:a,'||
962                                  ' dst_sch=>:b,'||
963                            ' threads=>:c);'||
964                 'end;'
965                 USING IN X_source_schema, X_clone_schema, X_threads;
966            else
967               raise;
968            end if;
969      end;
970 
971      begin
972         EXECUTE IMMEDIATE
973                 'begin '||
974                   '  sys.dbms_schema_copy.clean_up('||
975                                  ' src_sch=>:a,'||
976                                  ' dst_sch=>:b);'||
977                 'end;'
978                 USING IN X_source_schema, X_clone_schema;
979      exception
980         when others then
981           null;
982      end;
983 
984      begin
985 
986        select object_type, object_name
987        bulk collect into clone_obj_type_tab, clone_obj_name_tab
988        from dba_objects
989        where owner = X_clone_schema
990        and object_type not in ('INDEX', 'LOB INDEX', 'LOB')
991        and object_name not in ('APPS_DDL', 'APPS_ARRAY_DDL')
992        order by decode(object_type, 'PACKAGE', 1, 'VIEW', 2,
993                                     3);
994 
995      exception
996        when NO_DATA_FOUND then
997           null;
998      end;
999 
1000      println('Number of objects before the cleanup operation : '||
1001              clone_obj_name_tab.count);
1002 
1003      --
1004      -- drop individual objects
1005      --
1006      for i in 1..clone_obj_name_tab.count
1007      loop
1008         begin
1009 
1010           l_sql_stmt := 'DROP '||clone_obj_type_tab(i)||
1011                        ' '||X_clone_schema||'."'||clone_obj_name_tab(i)||'"';
1012 
1013           if (clone_obj_type_tab(i) in ('TYPE')) then
1014               l_sql_stmt := l_sql_stmt|| ' FORCE ';
1015           end if;
1016 
1017           if (clone_obj_type_tab(i) in ('DATABASE LINK')) then
1018              l_sql_stmt := 'DROP '||clone_obj_type_tab(i)||' "'||
1019                                     clone_obj_name_tab(i)||'"';
1020 
1021              EXECUTE IMMEDIATE
1022                    'BEGIN '||
1023                      X_clone_schema||'.'||'APPS_DDL.apps_ddl(:ddl_txt); '||
1024                    ' END; '
1025                    USING l_sql_stmt;
1026 
1027           else
1028              EXECUTE IMMEDIATE l_sql_stmt;
1029           end if;
1030         exception
1031           when others then
1032              dbms_output.put_Line(l_sql_stmt);
1033              println(l_sql_stmt);
1034              if (SQLCODE in (-950, -942, -1434, -4043)) then
1035                 null;
1036              else
1037                 raise;
1038              end if;
1039         end;
1040      end loop;
1041 
1042      select count(*)
1043      into   l_obj_count
1044      from   dba_objects
1045      where  owner = X_clone_schema
1046      and    object_name not in ('APPS_DDL', 'APPS_ARRAY_DDL');
1047 
1048      println('Number of objects remaining after the cleanup operation : '||
1049              l_obj_count);
1050 
1051      print_timestamp('CLEANUP of Clone schema ('||
1052                       X_clone_schema||') completed at : ');
1053   end;
1054 
1055   procedure clean_up(X_source_schema        in varchar2,
1056                      X_clone_schema         in varchar2,
1057                      X_spec_schema          in varchar2,
1058                      X_degree               in number  default null,
1059                      X_cleanup_clone        in boolean default FALSE,
1060                      X_cleanup_spec         in boolean default FALSE)
1061   is
1062      l_status varchar2(30);
1063      l_phase  varchar2(30);
1064   begin
1065     validate_schema(X_clone_schema, CLONE_SCHEMA_TYPE);
1066     validate_schema(X_spec_schema,  SPEC_SCHEMA_TYPE);
1067 
1068     if (native_clone_supported = TRUE) then
1069 
1070        get_status(X_source_schema, X_clone_schema,
1071                   l_phase, l_status);
1072 
1073        print_timestamp('CLEANUP operation started   at : ');
1074 
1075        --
1076        -- cleanup spec, if required
1077        --
1078        if (X_cleanup_spec = TRUE) then
1079           cleanup_spec_schema(X_spec_schema);
1080        end if;
1081 
1082        --
1083        -- cleanup the target, if required
1084        --
1085        if (X_cleanup_clone = TRUE) then
1086           cleanup_clone_schema(X_source_schema, X_clone_schema, TRUE, X_degree);
1087        end if;
1088 
1089        begin
1090           EXECUTE IMMEDIATE
1091              'begin '||
1092              '  sys.dbms_schema_copy.clean_up('||
1093                             'src_sch=>:a,  '||
1094                             'dst_sch=>:b); '||
1095              'end;'
1096              USING IN X_source_schema, X_clone_schema;
1097        exception
1098          when others then
1099            -- 39307 : operation illegal with initial clone
1100            if (SQLCODE = -39307) then
1101               null;
1102            else
1103               raise;
1104            end if;
1105        end;
1106 
1107        print_timestamp('CLEANUP operation completed at : ');
1108 
1109     end if;
1110   end;
1111 
1112   procedure get_status(X_source_schema       in varchar2,
1113                        X_clone_schema        in varchar2,
1114                        X_clone_phase        out NOCOPY varchar2,
1115                        X_clone_status       out NOCOPY varchar2)
1116   is
1117     type t_status     is table of varchar2(30)  index by binary_integer;
1118     type t_status_msg is table of varchar2(100) index by binary_integer;
1119     type StatusCurTyp is ref cursor;
1120 
1121     stat_c  StatusCurTyp;
1122     l_stmt  varchar2(300);
1123     l_status  t_status;
1124     l_message t_status_msg;
1125 
1126   begin
1127 
1128     if (native_clone_supported = FALSE) then
1129       begin
1130          ad_apps_private.check_for_apps_ddl(X_clone_schema);
1131 
1132          X_clone_phase  := 'CLONE';
1133          X_clone_status := 'COMPLETE';
1134       exception
1135          when others then
1136             X_clone_phase  := UNKNOWN_PHASE;
1137             X_clone_status := STATUS_UNKNOWN;
1138       end;
1139 
1140       return;
1141     end if;
1142 
1143     l_stmt := 'select status, message '||
1144               'from sys.dbms_upg_status$ s '||
1145               'where source_schema = :X_source_schema '||
1146               'and   target_schema = :x_target_schema '||
1147               'and ( status like ''CLONE%'' or '||
1148               '      status like ''SWAP%'') '||
1149               'order by sequence# desc';
1150 
1151     open stat_c for l_stmt using X_source_schema, X_clone_schema;
1152 
1153     X_clone_phase  := UNKNOWN_PHASE;
1154     X_clone_status := STATUS_UNKNOWN;
1155 
1156     loop
1157 
1158       fetch stat_c bulk collect into l_status, l_message limit 100;
1159       exit when l_status.count = 0;
1160 
1161       for i IN l_status.FIRST..l_status.LAST loop
1162         --
1163         -- exit the loop on first occurrence of CLONE or SWAP (COMPLETED)
1164         --
1165         if (l_status(i) like 'CLONE%')
1166         then
1167            X_clone_phase := CLONE_PHASE;
1168 
1169            if (l_message(i) = 'CLONE COMPLETED')
1170            then
1171               X_clone_status := STATUS_COMPLETED;
1172            elsif (l_message(i) = 'CLONE IN PROGRESS') then
1173               X_clone_status := STATUS_INPROGRESS;
1174            elsif (l_message(i) = 'CLONE FAILED') then
1175               X_clone_status := STATUS_FAILED;
1176            else
1177               X_clone_status := STATUS_INCOMPLETE;
1178            end if;
1179            exit;
1180         end if;
1181 
1182         if (l_status(i) like 'SWAP%')
1183         then
1184            X_clone_phase := MERGE_PHASE;
1185 
1186            if (l_message(i) = 'SWAP COMPLETED')
1187            then
1188               X_clone_status := STATUS_COMPLETED;
1189            else
1190               X_clone_status := STATUS_INCOMPLETE;
1191            end if;
1192            exit;
1193         end if;
1194       end loop;
1195     end loop;
1196 
1197     close stat_c;
1198 
1199   end;
1200 
1201   procedure is_phase_complete(X_source_schema in  varchar2,
1202                               X_clone_schema  in  varchar2,
1203                               X_phase_name    in  varchar2,
1204                               X_complete_flag out NOCOPY varchar2)
1205   is
1206     l_phase   varchar2(30);
1207     l_status  varchar2(30);
1208   begin
1209      if (X_phase_name not in (CLONE_PHASE, MERGE_PHASE)) then
1210         raise_application_error(-20001, 'Unknown phase : '||X_phase_name);
1211      end if;
1212 
1213      X_complete_flag := 'N';
1214 
1215      get_status(X_source_schema,
1216                 X_clone_schema,
1217                 l_phase, l_status);
1218 
1219      if (l_phase = X_phase_name) then
1220        if (l_status = STATUS_COMPLETED) then
1221           X_complete_flag := 'Y';
1222        else
1223           X_complete_flag := 'N';
1224        end if;
1225      end if;
1226 
1227   end;
1228 
1229   procedure create_schema(X_schema_un   in varchar2,
1230                           X_schema_pw   in varchar2,
1231                           X_tablespace  in varchar2)
1232   is
1233   begin
1234      EXECUTE IMMEDIATE ' create user '||X_schema_un||
1235                        ' identified by '||X_schema_pw||
1236                        ' default tablespace '||X_tablespace;
1237 
1238      EXECUTE IMMEDIATE 'grant connect, resource to '||X_schema_un;
1239 
1240   exception
1241     when others then
1242       if (sqlcode = -1920) then
1243          --
1244          -- make sure that CLONE schema has the correct password
1245          --
1246          EXECUTE IMMEDIATE 'alter user '||X_schema_un||' identified by '||
1247                                           X_schema_pw||
1248                            ' default tablespace '||X_tablespace;
1249       else
1250          raise;
1251       end if;
1252   end;
1253 
1254   procedure repoint_synonyms(X_source_schema  in varchar2,
1255                              X_clone_schema   in varchar2,
1256                              X_spec_schema    in varchar2)
1257   is
1258     type t_objname  is table of varchar2(30)  index by binary_integer;
1259 
1260     l_syntab   t_objname;
1261     l_tabtab   t_objname;
1262     l_owntab   t_objname;
1263 
1264     cursor c_syn is
1265       select synonym_name, table_name, table_owner
1266       from   dba_synonyms src
1267       where  src.owner = X_source_schema
1268       and    src.synonym_name in (
1269         select cl.synonym_name
1270         from   dba_synonyms cl
1271         where  cl.owner = X_clone_schema
1272         and    cl.table_owner = X_spec_schema);
1273 
1274   begin
1275     open c_syn;
1276 
1277     loop
1278       fetch c_syn bulk collect into l_syntab, l_tabtab, l_owntab limit 1000;
1279 
1280        exit when l_syntab.count = 0;
1281 
1282        for i in 1..l_syntab.last loop
1283 
1284           EXECUTE IMMEDIATE 'CREATE OR REPLACE SYNONYM '||
1285                             X_clone_schema||'.'||l_syntab(i)||
1286                             ' FOR '||l_owntab(i)||'.'||l_tabtab(i);
1287        end loop;
1288 
1289     end loop;
1290   end;
1291 
1292 
1293 begin
1294   g_db_version := get_db_version;
1295 
1296   if (g_db_version like '10%') then
1297     native_clone_supported := TRUE;
1298   end if;
1299 
1300   if (to_number(substr(g_db_version,
1301                        1, instr(g_db_version, '.', 1, 2) -1)) > 9.2) then
1302     dbms_metadata_supported := TRUE;
1303   end if;
1304 end;