DBA Data[Home] [Help]

PACKAGE BODY: APPS.AD_PARALLEL_UPDATES_PKG

Source


1 package body ad_parallel_updates_pkg as
2 -- $Header: adprupdb.pls 120.7 2006/09/13 18:48:46 schadala ship $
3 
4 SUBTYPE update_info_type IS ad_parallel_updates%ROWTYPE;
5 
6 --
7 -- Global cache for the current Parallel Update Record and Options.
8 --
9 
10 TYPE global_cache_type IS RECORD
11   (
12    ui_initialized    BOOLEAN       := FALSE,
13    update_info       update_info_type,
14    batch_size        NUMBER        := 0,
15    debug_level       NUMBER        := 0,
16    processed_mode    NUMBER        := NULL,
17    lock_name         VARCHAR2(128),
18    lock_handle       VARCHAR2(128) := NULL,
19    worker_id         NUMBER        := NULL
20    );
21 
22   g_cache     global_cache_type;
23 
24 
25   type NumberTab is table of number index by binary_integer;
26   type StatusTab is table of varchar2(1) index by binary_integer;
27 
28   G_MAX_ROWS_IN_BLOCK    number := 9999;
29   DEFAULT_MIN_BLOCKS     CONSTANT number := 50;
30   g_max_blocks_multiple  number := 5;
31 
32 
33   UNASSIGNED_STATUS     CONSTANT VARCHAR2(1) := 'U';
34   ASSIGNED_STATUS       CONSTANT VARCHAR2(1) := 'A';
35   PROCESSED_STATUS      CONSTANT VARCHAR2(1) := 'P';
36 
37   --
38   -- Function
39   --   get_rowid
40   --
41   -- Purpose
42   --   Creates a rowid given file, block and row information
43   --
44   -- Arguments
45   --
46   -- Returns
47   --
48   -- Example
49   --   none
50   --
51   -- Notes
52   --   none
53   --
54 
55 function get_rowid
56           (X_object_no     in number,
57            X_relative_fno  in number,
58            X_block_no      in number,
59            X_row_no        in number)
60   return rowid
61 is
62   begin
63 
64      return(dbms_rowid.rowid_create(1, X_object_no, X_relative_fno,
65                                        X_block_no, X_row_no));
66   END get_rowid;
67 
68 PROCEDURE init_g_cache_update_info
69            (p_owner        IN VARCHAR2,
70             p_table_name   IN VARCHAR2,
71             p_script_name  IN VARCHAR2)
72 IS
73   BEGIN
74      g_cache.ui_initialized := FALSE;
75      SELECT *
76        INTO g_cache.update_info
77        FROM ad_parallel_updates
78        WHERE owner = p_owner
79        AND table_name = p_table_name
80        AND script_name = p_script_name;
81      g_cache.ui_initialized := TRUE;
82   END init_g_cache_update_info;
83 
84 PROCEDURE get_update_info
85            (x_update_info OUT nocopy update_info_type)
86 IS
87   BEGIN
88      IF (g_cache.ui_initialized) THEN
89    x_update_info := g_cache.update_info;
90       ELSE
91    raise_application_error(-20001,
92             'Not initialized.');
93      END IF;
94   END get_update_info;
95 
96 procedure debug_info
97            (msg  varchar2)
98 is
99   begin
100      if (g_cache.debug_level > 0) then
101          -- dbms_output.put_line(msg);
102          null;
103      end if;
104   END debug_info;
105 
106 procedure lock_table
107            (X_owner         in varchar2,
108             X_table         in varchar2,
109             X_mode          in varchar2,
110             X_CommitRelease in boolean default null)
111 IS
112        l_reqid  number;
113        l_lock_name VARCHAR2(128);
114        l_CommitRelease boolean;
115   BEGIN
116      l_lock_name := x_owner || '.' || x_table;
117 
118      if (g_cache.lock_name <> l_lock_name OR
119          g_cache.lock_handle is null) THEN
120 
121          dbms_lock.allocate_unique(l_lock_name, g_cache.lock_handle);
122          g_cache.lock_name := l_lock_name;
123 
124      end if;
125 
126      l_CommitRelease := nvl(X_CommitRelease, TRUE);
127 
128      l_reqid := dbms_lock.request(g_cache.lock_handle,
129                                   dbms_lock.x_mode, dbms_lock.maxwait,
130                                   l_CommitRelease);
131 
132      IF (l_reqid <> 0) THEN
133         raise_application_error(-20001,
134             'dbms_lock.request('|| g_cache.lock_handle ||
135             ', ' || dbms_lock.x_mode ||
136             ', ' || dbms_lock.maxwait ||
137             ', TRUE) returned : ' || l_reqid);
138      END IF;
139   END lock_table;
140 
141 
142 procedure unlock_table
143            (X_owner     in varchar2,
144             X_table     in varchar2)
145 is
146     l_reqid  number;
147     l_lock_name VARCHAR2(128);
148 begin
149     l_lock_name := x_owner || '.' || x_table;
150 
151     if (g_cache.lock_name is null
152         or
153         g_cache.lock_name <> l_lock_name)
154     then
155        raise_application_error(-20001, 'Invalid lock name : '||
156                                        l_lock_name);
157     end if;
158 
159     l_reqid := dbms_lock.release(g_cache.lock_handle);
160 
161     IF (l_reqid <> 0) THEN
162         raise_application_error(-20001,
163             'dbms_lock.release('|| g_cache.lock_handle ||
164             ') returned : ' || l_reqid);
165     END IF;
166   END unlock_table;
167 
168 procedure create_update_record
169            (X_update_type  in number,
170             X_owner        in varchar2,
171             X_table        in varchar2,
172             X_script       in varchar2,
173             X_id_column    in varchar2 default null,
174             X_num_workers  in number default null)
175 is
176     l_initialized varchar2(1);
177   begin
178 
179      IF (X_update_type in (ID_RANGE_BY_ROWID, ID_RANGE,
180                            ID_RANGE_SUB_RANGE,
181                            ID_RANGE_SUB_RANGE_SQL,
182                            ID_RANGE_SCAN_EQUI_ROWSETS))
183      THEN
184         if (X_id_column is null) then
185            raise_application_error(-20001,
186                'Cannot get name for the unique id column');
187         end if;
188 
189         if (X_num_workers is null) then
190            raise_application_error(-20001,
191                'Cannot get number of workers for ID range updates');
192         end if;
193      ELSIF (x_update_type = ROWID_RANGE) THEN
194         NULL;
195      ELSE
196         raise_application_error(-20001,
197                'Unknown update type : ' || x_update_type);
198      end if;
199 
200      begin
201         select null
202         into   l_initialized
203         from   ad_parallel_updates
204         where  owner = X_owner
205         and    table_name = X_table
206         and    script_name = X_script;
207 
208      exception
209         when NO_DATA_FOUND then
210           insert into ad_parallel_updates (
211                         update_id,
212                         update_type,
213                         owner, script_name, table_name,
214                         object_id,
215                         id_column, num_workers, creation_date,
216                         db_block_size, avg_row_len,
217                         initialized_flag)
218           select ad_parallel_updates_s.nextval,
219                  X_update_type,
220                  X_owner, X_script, X_table,
221                  nvl(o.dataobj#, o.obj#),
222                  X_id_column, X_num_workers, sysdate,
223                  8192, t.avgrln, 'N' -- only 8k block sizes for 11i and above
224           from   sys.obj$ o,
225                  sys.tab$ t,
226                  sys.user$ u
227           where  u.name = X_owner
228           and    o.owner# = u.user#
229           and    o.name   = X_table
230           and    o.type# = 2 -- TABLE
231           and    t.obj#   = o.obj#;
232 
233    --
234    -- Initialize the Global Cache Update Record Info.
235    --
236      end;
237 
238      init_g_cache_update_info(x_owner, x_table, x_script);
239 
240   END create_update_record;
241 
242 -- For bug 3447980, a view ad_extents is created via adgrants.sql,
243 -- using the huge select tested by APPS Performance team.
244 -- This is to replace the Rule optimization
245 -- in ad_parallel_updates_pkg() package.
246 
247 procedure populate_extent_info
248            (X_owner     in varchar2,
249             X_table     in varchar2,
250             X_script    in varchar2,
251             X_batch_size in number)
252 is
253     CURSOR c_ext IS
254       SELECT segment_name,
255              partition_name,
256              segment_type,
257              data_object_id,
258              relative_fno, block_id, blocks
259       from   sys.ad_extents
260       where  owner = X_owner
261       and    segment_name = X_table
262       and    segment_type in ('TABLE', 'TABLE PARTITION',
263                                 'TABLE SUBPARTITION')
264       order by segment_name, partition_name, relative_fno, block_id;
265 
266     object_id_tab     NumberTab;
267     unit_id_tab       NumberTab;
268     relative_fno_tab  NumberTab;
269     start_block_tab   NumberTab;
270     end_block_tab     NumberTab;
271 
272     cur_block   number;
273     max_block   number;
274     num_units   number;
275     l_unit_id   number;
276     i           integer;
277     j           integer;
278     k           integer;
279 
280     l_minblocks      number;
281     l_my_sid         number;
282     l_my_serialid    number;
283 
284     l_update_info    update_info_type;
285     l_statement         varchar2(500);
286     l_instance_version   varchar2(30);
287     l_first_space_in_version   number;
288     l_version_compare_result boolean;
289 
290   begin
291 
292      debug_info('populate_extent_info()+');
293 
294      -- Get instance version number from v$instanace,
295      -- this is part of bug 3557509 fix
296 
297      begin
298 
299        l_statement := 'select version from v$instance';
300        execute immediate l_statement into l_instance_version;
301 
302      exception
303        when others then
304            raise_application_error(-20000,
305            'Unable to get the version from v$instance.');
306      end;
307 
308      l_instance_version := rtrim(ltrim(l_instance_version, ' '),' ');
309      l_first_space_in_version := instr(l_instance_version,' ');
310 
311      if not l_first_space_in_version = 0 then
312        -- There is extra info, remove it
313        l_instance_version := substr(l_instance_version, 1,
314                              l_first_space_in_version - 1);
315      end if;
316      -- End of trimming.
317 
318      -- Check for instance version information,
319      -- Change "_push_join_union_view" to False if
320      -- instance is 9.2.0.5 or greater
321 
322      l_version_compare_result :=
323        system.ad_apps_private.compare_releases('9.2.0.5',
324                                        l_instance_version);
325 
326      if (l_version_compare_result = TRUE) then
327 
328        -- Bug 3557509, Alter the session using "alter session
329        -- set "_push_join_union_view"=false;"
330 
331        debug_info('Setting the session parameter ' ||
332                   '_push_join_union_view to FALSE..');
333 
334        select sid, serial#
335        into l_my_sid, l_my_serialid
336        from v$session where audsid = userenv('sessionid');
337 
338        DBMS_SYSTEM.SET_BOOL_PARAM_IN_SESSION(l_my_sid,
339                                         l_my_serialid,
340                                '_push_join_union_view',
341                                                 FALSE);
342        debug_info('Done setting.');
343        -- End alter session
344      end if;
345 
346 
347      create_update_record(ROWID_RANGE,
348                           X_owner,
349                           X_table,
350                           X_script);
351 
352      get_update_info(l_update_info);
353 
354      if (nvl(l_update_info.avg_row_len, 0) = 0) then
355         l_minblocks := DEFAULT_MIN_BLOCKS;
356      else
357         l_minblocks := round((X_batch_size*l_update_info.avg_row_len)/
358                                  l_update_info.db_block_size, -1);
359 
360         if (l_minblocks = 0) then
361            l_minblocks := DEFAULT_MIN_BLOCKS;
362         end if;
363      end if;
364 
365      select nvl(max(unit_id), 0)
366      into   l_unit_id
367      from   ad_parallel_update_units
368      where  update_id = l_update_info.update_id;
369 
370      FOR erec IN c_ext
371      LOOP
372 
373         cur_block := erec.block_id;
374 
375         IF (erec.blocks > 0)
376         THEN
377            max_block := erec.block_id + erec.blocks - 1;
378         ELSE
379            max_block := erec.block_id;
380         END IF;
381 
382         num_units := round(erec.blocks/l_minblocks + 0.5);
383 
384         i := 1;
385         j := 1;
386 
387         LOOP
388 
389            EXIT WHEN (i > num_units);
390 
391            unit_id_tab(j)      := l_unit_id + i;
392            object_id_tab(j)    := erec.data_object_id;
393            relative_fno_tab(j) := erec.relative_fno;
394            start_block_tab(j)  := erec.block_id +
395                                          ((i - 1) * l_minblocks);
396            end_block_tab(j)    := least(max_block,
397                                             erec.block_id +
398                                                  (i) * l_minblocks - 1);
399 
400            if (j = 100 or
401                i = num_units) then
402               FORALL k IN 1..j
403                  INSERT INTO ad_parallel_update_units(
404                    unit_id, update_id,
405                    data_object_id,
406                    relative_fno, start_block, end_block,
407                    status
408                  )
409                  values( unit_id_tab(k), l_update_info.update_id,
410                          object_id_tab(k),
411                          relative_fno_tab(k),
412                          start_block_tab(k),
413                          end_block_tab(k),
414                          UNASSIGNED_STATUS);
415               j := 0;
416            end if;
417 
418            i := i + 1;
419            j := j + 1;
420         END LOOP;
421 
422         l_unit_id := l_unit_id + i - 1;
423 
424      END LOOP;
425 
426      debug_info('populate_extent_info()-');
427   END populate_extent_info;
428 
429 procedure get_min_max_id
433             X_SQL_Stmt  in         varchar2,
430            (X_owner     in         varchar2,
431             X_table     in         varchar2,
432             X_id_column in         varchar2,
434             X_min_id    out nocopy number,
435             X_max_id    out nocopy number)
436 is
437     l_stmt      varchar2(500);
438     l_start_id  number;
439     l_end_id    number;
440   begin
441      debug_info('get_min_max_id()+');
442      X_min_id := null;
443      X_max_id := null;
444 
445      if (X_SQL_Stmt is null)
446      then
447 
448         l_stmt := 'select min('||X_id_column||') min_val '||
449                   'from '||X_owner||'.'||X_table;
450 
451         EXECUTE IMMEDIATE l_stmt INTO l_start_id;
452 
453         l_stmt := 'select max('||X_id_column||') max_val '||
454                   'from '||X_owner||'.'||X_table;
455 
456         EXECUTE IMMEDIATE l_stmt INTO l_end_id;
457 
458      else
459 
460         debug_info('get_min_max_id : '||X_SQL_Stmt);
461         EXECUTE IMMEDIATE X_SQL_Stmt INTO l_start_id, l_end_id;
462 
463      end if;
464 
465      X_min_id := l_start_id;
466      X_max_id := l_end_id;
467 
468      debug_info('get_min_max_id()-');
469 
470   END get_min_max_id;
471 
472 procedure populate_id_ranges(
473             X_update_type in number,
474             X_update_id   in number,
475             X_num_workers in number,
476             X_batch_size  in number,
477             X_SQL_Stmt    in varchar2)
478 is
479   l_status varchar2(1);
480 begin
481 
482   l_status := UNASSIGNED_STATUS;
483 
484   if ( instr(lower(X_SQL_Stmt), 'id_value', 1) = 0)
485   then
486      raise_application_error(-20001,
487          'The mandatory column alias (ID_VALUE) is missing '||
488          'from the supplied SQL statement. ');
489   end if;
490 
491   EXECUTE IMMEDIATE
492     ' INSERT INTO ad_parallel_update_units '||
493     ' (update_id, unit_id, start_id, end_id, status) '||
494     ' SELECT :update_id update_id, '||
495     '        unit_id+1 unit_id, '||
496     '        min(id_value) start_id_value, '||
497     '        max(id_value) end_id_value, '||
498     '        :status status '||
499     ' from ('||
500     '   select id_value, '||
501     '          floor(rank() over (order by id_value)/:batchsize) unit_id '||
502     '   from ( '||
503              X_SQL_Stmt||
504     '   ) '||
505     ' ) '||
506     ' group by unit_id '
507   using X_Update_id, l_status, X_batch_size;
508 
509 exception
510   when others then
511   raise_application_error(-20001,
512     SQLERRM||'. SQL statement is : '||
513     'INSERT INTO ad_parallel_update_units '||
514     ' (update_id, unit_id, start_id, end_id, status) '||
515     ' select :update_id, unit_id, start_id_value, end_id_value, :status '||
516     ' from ( '||
517              X_SQL_Stmt||
518     ' ) ');
519 end;
520 
521 procedure populate_id_info
522            (X_update_type in number,
523             X_owner       in varchar2,
524             X_table       in varchar2,
525             X_script      in varchar2,
526             X_id_column   in varchar2,
527             X_num_workers in number,
528             X_batch_size  in number,
529             X_SQL_Stmt    in varchar2,
530             X_Begin_ID    in number,
531             X_End_ID      in number)
532 is
533     l_table_start_id  number;
534     l_table_end_id    number;
535     l_unit_start_id   number;
536     l_unit_end_id     number;
537     l_unit_id         number;
538     l_num_units       number;
539 
540     unit_id_tab       NumberTab;
541     start_id_tab      NumberTab;
542     end_id_tab        NumberTab;
543 
544 
545     i                 number;
546     l_entire_range    boolean;
547 
548     l_update_info     update_info_type;
549     l_num_workers_used  number;
550 
551   begin
552       debug_info('populate_id_info()+');
553 
554       l_entire_range := (X_update_type = ID_RANGE_BY_ROWID);
555 
556       create_update_record(X_update_type,
557                            X_owner, X_table, X_script,
558                            X_id_column, X_num_workers);
559 
560       get_update_info(l_update_info);
561 
562       if (X_update_type = ID_RANGE_SCAN_EQUI_ROWSETS)
563       then
564          populate_id_ranges(
565             X_update_type,
566             l_update_info.update_id,
567             X_num_workers, X_batch_size,
568             X_SQL_Stmt);
569       else
570          if (X_update_type = ID_RANGE_SUB_RANGE)
571          then
572             l_table_start_id := X_Begin_ID;
573             l_table_end_id   := X_End_ID;
574          else
575             get_min_max_id(X_owner, X_table, X_id_column,
576                            X_SQL_Stmt,
577                            l_table_start_id, l_table_end_id);
578          end if;
579 
580          if (l_table_start_id is NOT NULL and l_table_end_id IS NOT NULL) then
581 
582             if (l_entire_range = TRUE) then
583 
584               FOR i IN 1..X_num_workers
588                 unit_id_tab(i)  := i;
585               LOOP
586                 start_id_tab(i) := l_table_start_id;
587                 end_id_tab(i)   := l_table_end_id;
589               END LOOP;
590 
591               FORALL i in 1..X_num_workers
592                 insert into ad_parallel_update_units(
593                     unit_id, update_id,
594                     start_id, end_id,
595                     status
596                  )
597                 values (unit_id_tab(i), l_update_info.update_id,
598                          start_id_tab(i), end_id_tab(i),
599                          UNASSIGNED_STATUS);
600             else
601                l_unit_start_id := l_table_start_id;
602                l_unit_id       := 0;
603                l_num_units     := 0;
604 
605                while (l_unit_start_id <= l_table_end_id)
606                loop
607 
608                   l_unit_id     := l_unit_id + 1;
609                   l_num_units   := l_num_units + 1;
610 
611                   l_unit_end_id := least((l_unit_start_id + X_batch_size - 1),
612                                           l_table_end_id);
613 
614                   unit_id_tab(l_num_units)  := l_unit_id;
615                   start_id_tab(l_num_units) := l_unit_start_id;
616                   end_id_tab(l_num_units)   := l_unit_end_id;
617 
618                   l_unit_start_id := l_unit_start_id + X_batch_size;
619 
620                   if (l_num_units = 500
621                       or
622                       l_unit_start_id > l_table_end_id)
623                   then
624 
625                     FORALL i in 1..l_num_units
626                       insert into ad_parallel_update_units(
627                         unit_id, update_id,
628                         start_id, end_id,
629                         status
630                        )
631                       values (unit_id_tab(i), l_update_info.update_id,
632                               start_id_tab(i), end_id_tab(i),
633                               UNASSIGNED_STATUS);
634 
635                       l_num_units := 0;
636 
637                   end if;
638 
639                end loop;
640 
641             end if; /* entire_range = FALSE */
642 
643          end if; /* l_table_start_id is not null */
644 
645       end if; /* if not X_Update_type = ID_RANGE_SCAN_EQUI_ROWSETS */
646 
647       debug_info('populate_id_info()-');
648 
649   END populate_id_info;
650 
651 procedure initialize
652            (X_update_type  in number,
653             X_owner        in varchar2,
654             X_table        in varchar2,
655             X_script       in varchar2,
656             X_ID_column    in varchar2,
657             X_worker_id    in number,
658             X_num_workers  in number,
659             X_batch_size   in number,
660             X_debug_level  in number,
661             X_processed_mode in number,
662             X_SQL_Stmt     in varchar2,
663             X_Begin_ID     in number,
664             X_End_ID       in number)
665 is
666     l_initialized  varchar2(1);
667     l_req_init     boolean := TRUE;
668     l_update_id    number;
669     l_num_workers  number;
670     l_unproc_units_exist  number;
671   begin
672       debug_info('initialize()+');
673 
674       if (X_processed_mode not in (PRESERVE_PROCESSED_UNITS,
675                                    DELETE_PROCESSED_UNITS))
676       then
677          raise_application_error(-20001,
678            'Incorrect mode specified for processed units. '||
679            'Must be either PRESERVE_PROCESSED_UNITS or '||
680            'DELETE_PROCESSED_UNITS. ');
681       end if;
682 
683       if (X_batch_size <= 0) then
684         raise_application_error(-20001,
685           'Invalid value for batch size ('||X_batch_size||'). '||
686           'The batch size must be a positive number greater than 0.');
687       end if;
688 
689       if (X_update_type = ID_RANGE_SCAN_EQUI_ROWSETS
690           and
691           X_SQL_Stmt is null)
692       then
693         raise_application_error(-20001,
694           'You must specify a SQL statement to derive processing units.');
695       end if;
696 
697       if (X_update_type = ID_RANGE_SUB_RANGE
698           and
699           X_SQL_Stmt is not null)
700       then
701         raise_application_error(-20001,
702           'You cannot specify a SQL statement for specific ID range.');
703       end if;
704 
705       if (X_update_type = ID_RANGE_SUB_RANGE_SQL
706           and
707           X_SQL_Stmt is null)
708       then
709           raise_application_error(-20001,
710           'You must specify a SQL statement for this ID range method.');
711       end if;
712 
713       --
714       -- lock the table to ensure that other workers are not initializing
715       --
716       lock_table(X_owner, X_table, 'EXCLUSIVE', FALSE);
717 
718       l_req_init := TRUE;
719 
720       begin
721         select update_id, initialized_flag, num_workers
722         into   l_update_id, l_initialized, l_num_workers
723         from   ad_parallel_updates
724         where  owner = X_owner
728         if (l_initialized = 'Y') then
725           and  table_name = X_table
726           and  script_name = X_script;
727 
729            --
730            -- already initialized
731            --
732            l_req_init := FALSE;
733         end if;
734 
735       exception
736         when no_data_found then
737           l_req_init := TRUE;
738           l_update_id := null;
739       end;
740 
741       if (l_req_init = TRUE) then
742 
743           --
744           -- to be safe, delete any rows that may have been inserted
745           --
746           if (l_update_id is not null) then
747              delete from ad_parallel_update_units
748              where update_id = l_update_id;
749           end if;
750 
751           debug_info('Populate information : ');
752 
753           if (X_update_type = ROWID_RANGE) then
754              populate_extent_info(X_owner, X_table, X_script, X_batch_size);
755           else
756              populate_id_info(X_update_type,
757                               X_owner, X_table, X_script, X_ID_column,
758                               X_num_workers, X_batch_size,
759                               X_SQL_Stmt, X_Begin_ID, X_End_ID);
760           end if;
761 
762           --
763           -- now set initialized_flag to Y
764           --
765           update ad_parallel_updates
766           set    initialized_flag = 'Y',
767                  num_workers = X_num_workers
768           where  owner = X_owner
769             and  table_name = X_table
770             and  script_name = X_script;
771 
772       else
773 
774          --
775          -- compare number of workers and recover unprocessed units
776          --
777          if (X_num_workers <> nvl(l_num_workers, -1)) then
778 
779            --
780            -- check if the update is already processed. do not do anything
781            -- if all units are processed.
782            --
783 
784            begin
785              select 1
786              into   l_unproc_units_exist
787              from   sys.dual
788              where  exists (
789                  select 1
790                  from   ad_parallel_update_units
791                  where  update_id = l_update_id
792                  and status in (UNASSIGNED_STATUS, ASSIGNED_STATUS));
793            exception
794              when no_data_found then
795                 l_unproc_units_exist := 0;
796            end;
797 
798            if (l_unproc_units_exist > 0) then
799 
800              if (X_update_type not in (ROWID_RANGE, ID_RANGE)) then
801                 --
802                 -- for ID over ROWID range methods, you cannot reduce the
803                 -- number of workers after initialization
804                 --
805                 if (X_num_workers <  l_num_workers) then
806 
807                    raise_application_error(-20001,
808               'Cannot reduce the number of workers after initialization.');
809                 end if;
810 
811              else
812                --
813                -- recover all units in ASSIGNED_STATUS by returning them
814                -- to the UNASSIGNED_STATUS pool
815                --
816                update ad_parallel_update_units
817                set    status = UNASSIGNED_STATUS,
818                       worker_id = null
819                where  update_id = l_update_id
820                and    status = ASSIGNED_STATUS
821                and    worker_id > X_num_workers;
822 
823                update ad_parallel_workers
824                set    start_unit_id = 0,
825                       end_unit_id = 0,
826                       start_rowid = null,
827                       start_id    = null,
828                       end_rowid   = null,
829                       end_id      = null
830                where update_id = l_update_id
831                and    worker_id > X_num_workers;
832 
833                update ad_parallel_updates
834                set    num_workers = X_num_workers
835                where  update_id = l_update_id;
836 
837              end if; -- ID range method
838 
839            end if; -- incomplete update
840 
841          end if; -- worker count changed
842 
843       end if;  -- require initialization
844 
845       --
846       -- g_cache might already be initialized by populate_* calls.
847       --
848       IF ((g_cache.ui_initialized = FALSE)
849           OR
850           (x_owner||'.'||x_owner||'.'||x_script <>
851              g_cache.update_info.owner||'.'||
852              g_cache.update_info.table_name||'.'||
853              g_cache.update_info.script_name)) THEN
854          init_g_cache_update_info(x_owner, x_table, x_script);
855       END IF;
856 
857       g_cache.debug_level    := X_debug_level;
858       g_cache.batch_size     := X_batch_size;
859       g_cache.worker_id      := X_worker_id;
860       g_cache.processed_mode := X_processed_mode;
861 
862       --
863       -- Release the lock. First do the commit so that other workers
864       -- would see the row.
865       --
866       COMMIT;
867       unlock_table(X_owner, X_table);
871         debug_info(sqlerrm);
868       debug_info('initialize()-');
869   exception
870       when others then
872         raise;
873   END initialize;
874 
875 
876 -- Bug 3611969 : FIXED FILE.SQL.35 GSCC WARNINGS
877 -- sraghuve (07/05/2004)
878 
879 
880 procedure initialize_rowid_range
881            (X_update_type  in number,
882             X_owner        in varchar2,
883             X_table        in varchar2,
884             X_script       in varchar2,
885             X_worker_id    in number,
886             X_num_workers  in number,
887             X_batch_size   in number,
888             X_debug_level  in number)
889 is
890 begin
891   initialize_rowid_range
892              (X_update_type => X_update_type,
893               X_owner       => X_owner,
894               X_table       => X_table,
895               X_script      => X_script,
896               X_worker_id   => X_worker_id,
897               X_num_workers => X_num_workers,
898               X_batch_size  => X_batch_size,
899               X_debug_level => X_debug_level,
900               X_processed_mode => PRESERVE_PROCESSED_UNITS);
901 
902 end;
903 
904 procedure initialize_rowid_range
905            (X_update_type  in number,
906             X_owner        in varchar2,
907             X_table        in varchar2,
908             X_script       in varchar2,
909             X_worker_id    in number,
910             X_num_workers  in number,
911             X_batch_size   in number,
912             X_debug_level  in number,
913             X_processed_mode in number)
914 is
915   begin
916      debug_info('initialize_rowid_range()+');
917      initialize(X_update_type,
918                 X_owner, X_table, X_script, null,
919                 X_worker_id, X_num_workers,
920                 X_batch_size, X_debug_level,
921                 X_processed_mode,
922                 null, null, null);
923      debug_info('initialize_rowid_range()-');
924   END initialize_rowid_range;
925 
926 procedure initialize_id_range
927            (X_update_type  in number,
928             X_owner        in varchar2,
929             X_table        in varchar2,
930             X_script       in varchar2,
931             X_ID_column    in varchar2,
932             X_worker_id    in number,
933             X_num_workers  in number,
934             X_batch_size   in number,
935             X_debug_level  in number,
936             X_SQL_Stmt     in varchar2 default NULL,
937             X_Begin_ID     in number   default NULL,
938             X_End_ID       in number   default NULL)
939 is
940   begin
941      initialize(X_update_type,
942                 X_owner, X_table, X_script, X_ID_column,
943                 X_worker_id, X_num_workers,
944                 X_batch_size, X_debug_level,
945                 ad_parallel_updates_pkg.PRESERVE_PROCESSED_UNITS,
946                 X_SQL_Stmt, X_Begin_ID, X_End_ID);
947   END initialize_id_range;
948 
949 
950 procedure get_restart_range
951            (X_worker_id        in         number,
952             X_update_id        in         number,
953             X_res_start_rowid  out nocopy rowid,
954             X_res_end_rowid    out nocopy rowid,
955             X_res_start_id     out nocopy number,
956             X_res_end_id       out nocopy number,
957             X_start_unit_id    out nocopy number,
958             X_end_unit_id      out nocopy number)
959   is
960   begin
961 
962      select start_rowid, end_rowid,
963             start_id, end_id,
964             start_unit_id, end_unit_id
965      into   X_res_start_rowid, X_res_end_rowid,
966             X_res_start_id, X_res_end_id,
967             X_start_unit_id, X_end_unit_id
968      from   ad_parallel_workers
969      where  worker_id = X_worker_id
970      and    update_id = X_update_id;
971 
972   exception
973      when no_data_found then
974        X_res_start_rowid := null;
975        X_res_end_rowid   := null;
976        X_res_start_id    := null;
977        X_res_end_id      := null;
978        X_start_unit_id   := null;
979        X_end_unit_id     := null;
980   END get_restart_range;
981 
982   --
983   -- updates worker record with processed information. If all
984   -- rows for a range are processed, update the work unit to
985   -- processed
986   --
987 procedure processed_unit
988            (X_rows_processed in  number,
989             X_last_rowid     in  rowid,
990             X_last_id        in  number)
991 is
992     l_res_start_rowid   rowid;
993     l_res_end_rowid     rowid;
994     l_start_unit_id     number;
995     l_end_unit_id       number;
996 
997     l_worker_id         NUMBER;
998     l_update_info       update_info_type;
999   begin
1000 
1001      get_update_info(l_update_info);
1002      l_worker_id := g_cache.worker_id;
1003 
1004      -- do not get the explicit lock
1005      -- lock_table(l_update_info.owner, l_update_info.table_name, 'EXCLUSIVE');
1006 
1007      select start_unit_id, end_unit_id
1008      into   l_start_unit_id, l_end_unit_id
1009      from   ad_parallel_workers
1013      --
1010      where  worker_id = l_worker_id
1011      and    update_id = l_update_info.update_id;
1012 
1014      -- set start_id to end_id+1 to handle cases where there is just one
1015      -- row per worker
1016      --
1017      update ad_parallel_workers
1018      set    start_rowid = nvl(X_last_rowid, start_rowid),
1019 	    start_id    = least(nvl(X_last_id, start_id)+1, end_id+1),
1020             rows_processed = nvl(rows_processed, 0) + nvl(X_rows_processed, 0)
1021      where  worker_id = l_worker_id
1022      and    update_id = l_update_info.update_id;
1023 
1024      if (g_cache.processed_mode = DELETE_PROCESSED_UNITS) then
1025         delete from ad_parallel_update_units
1026         where  update_id = l_update_info.update_id
1027         and    unit_id  between l_start_unit_id and l_end_unit_id;
1028      else
1029         update ad_parallel_update_units
1030         set    status = decode(l_update_info.update_type,
1031                                ROWID_RANGE, PROCESSED_STATUS,
1032                                decode(X_last_id,
1033                                       end_id, PROCESSED_STATUS,
1034                                       status)),
1035                end_date = sysdate,
1036                rows_processed = nvl(rows_processed, 0) +
1037                                 nvl(X_rows_processed, 0)
1038         where  update_id = l_update_info.update_id
1039         and    unit_id  between l_start_unit_id and l_end_unit_id;
1040 
1041      end if;
1042 
1043      --
1044      -- commit here to release lock
1045      --
1046      commit;
1047 
1048   END processed_unit;
1049 
1050   --
1051   -- procedure for processing by ROWID_RANGE
1052   --
1053 procedure processed_rowid_range
1054            (X_rows_processed in number,
1055             X_last_rowid     in  rowid)
1056 is
1057   begin
1058       processed_unit(X_rows_processed,
1059                      X_last_rowid,
1060                      null);
1061   END processed_rowid_range;
1062 
1063   --
1064   -- procedure for processing by ID_RANGE and ID_BY_ROWID_RANGE
1065   --
1066 procedure processed_id_range
1067            (X_rows_processed in number,
1068             X_last_id        in  number)
1069 is
1070   begin
1071       processed_unit(X_rows_processed,
1072                      null,
1073                      X_last_id);
1074   END processed_id_range;
1075 
1076 procedure set_current_range
1077            (X_worker_id     in  number,
1078             X_start_unit_id in  number,
1079             X_end_unit_id   in  number,
1080             X_start_rowid   in  rowid,
1081             X_end_rowid     in  rowid,
1082             X_start_id      in  number,
1083             X_end_id        in  number)
1084 is
1085     l_unit_id      number;
1086     l_update_info  update_info_type;
1087   begin
1088 
1089     debug_info('set_current_range()+');
1090 
1091     get_update_info(l_update_info);
1092 
1093     update ad_parallel_workers
1094     set    start_unit_id = X_start_unit_id,
1095            end_unit_id   = X_end_unit_id,
1096            start_rowid   = X_start_rowid,
1097            end_rowid     = X_end_rowid,
1098            start_id      = X_start_id,
1099            end_id        = X_end_id
1100     where  worker_id   = X_worker_id
1101     and    update_id   = l_update_info.update_id;
1102 
1103     --
1104     -- if no records updated, insert a new record
1105     --
1106     IF (SQL%ROWCOUNT = 0) THEN
1107        insert into ad_parallel_workers (
1108                       worker_id, update_id,
1109                       start_unit_id, end_unit_id,
1110                       start_rowid, end_rowid,
1111                       start_id, end_id
1112                    )
1113        values (X_worker_id, l_update_info.update_id,
1114                X_start_unit_id, X_end_unit_id,
1115                X_start_rowid, X_end_rowid,
1116                X_start_id, X_end_id
1117               );
1118     END IF;
1119 
1120     --
1121     -- Set status to ASSIGNED_STATUS
1122     --
1123 
1124     update ad_parallel_update_units
1125     set    status = ASSIGNED_STATUS,
1126            worker_id = X_worker_id,
1127            start_date = nvl(start_date, sysdate)
1128     where  update_id = l_update_info.update_id
1129     and    unit_id between X_start_unit_id and X_end_unit_id;
1130 
1131     debug_info('set_current_range()-');
1132 
1133   END set_current_range;
1134 
1135 procedure set_rowid_range
1136            (X_worker_id     in  number,
1137             X_start_unit_id in  number,
1138             X_end_unit_id   in  number,
1139             X_start_rowid   in  rowid,
1140             X_end_rowid     in  rowid)
1141 is
1142   begin
1143       set_current_range(X_worker_id,
1144                         X_start_unit_id, X_end_unit_id,
1145                         X_start_rowid, X_end_rowid,
1146                         null, null);
1147   end;
1148 
1149 procedure set_id_range
1150            (X_worker_id     in  number,
1151             X_start_unit_id in  number,
1152             X_end_unit_id   in  number,
1153             X_start_id      in  number,
1154             X_end_id        in  number)
1155 is
1156   begin
1160                         X_start_id, X_end_id);
1157       set_current_range(X_worker_id,
1158                         X_start_unit_id, X_end_unit_id,
1159                         null, null,
1161   end;
1162 
1163 --
1164 -- This is a wrapper around get_rowid_range() to enable
1165 -- programs written in other languages that do not support
1166 -- passing boolean parameters to PL/SQL stored procedures,
1167 -- like Java, to call get_rowid_range().
1168 --
1169 procedure get_rowid_range_wrapper
1170            (X_start_rowid  out nocopy rowid,
1171             X_end_rowid    out nocopy rowid,
1172             X_any_rows     out nocopy integer,
1173             X_num_rows     in         number  default NULL,
1174             X_restart      in         integer default 0)
1175 is
1176     l_any_rows  boolean;
1177     l_restart   boolean;
1178   begin
1179 
1180     debug_info('get_rowid_range_wrapper()+');
1181 
1182     -- Translate integer to boolean
1183     -- 1 = TRUE
1184     -- 0 = FALSE
1185     l_restart := x_restart > 0;
1186 
1187     get_rowid_range(X_START_ROWID,
1188                     X_END_ROWID,
1189                     l_any_rows,
1190                     X_NUM_ROWS,
1191                     l_restart);
1192 
1193     -- Translate boolean to integer for OUT variable
1194     if (l_any_rows) then
1195        X_ANY_ROWS := 1;
1196     else
1197        X_ANY_ROWS := 0;
1198     end if;
1199 
1200     debug_info('get_rowid_range_wrapper()-');
1201   END get_rowid_range_wrapper;
1202 
1203 procedure get_rowid_range
1204            (X_start_rowid out nocopy rowid,
1205             X_end_rowid   out nocopy rowid,
1206             X_any_rows    out nocopy boolean,
1207             X_num_rows    in         number  default NULL,
1208             X_restart     in         boolean default FALSE)
1209 is
1210     l_res_start_rowid      rowid;
1211     l_res_end_rowid        rowid;
1212     l_res_start_id         number;
1213     l_res_end_id           number;
1214     l_start_rowid          rowid;
1215     l_end_rowid            rowid;
1216     l_start_unit_id        number;
1217     l_end_unit_id          number;
1218     l_last_processed_unit  number;
1219     l_unit_rec             ad_parallel_update_units%rowtype;
1220 
1221     l_worker_id            NUMBER;
1222     l_update_info          update_info_type;
1223 
1224     cursor c_range(p_update_id number) is
1225       select /*+ FIRST_ROWS +*/ *
1226       from   ad_parallel_update_units
1227       where  update_id = p_update_id
1228       and status = UNASSIGNED_STATUS
1229       for update of status
1230       skip locked;
1231   begin
1232 
1233     debug_info('get_rowid_range()+');
1234 
1235     get_update_info(l_update_info);
1236     l_worker_id := g_cache.worker_id;
1237 
1238     get_restart_range(l_worker_id, l_update_info.update_id,
1239                       l_res_start_rowid, l_res_end_rowid,
1240                       l_res_start_id, l_res_end_id,
1241                       l_start_unit_id, l_end_unit_id);
1242 
1243     l_last_processed_unit := nvl(l_end_unit_id, 0);
1244 
1245     -- return the current range if there are still some rows to process
1246 
1247     X_any_rows := FALSE;
1248 
1249     if (l_res_start_rowid is not null
1250         and
1251         l_res_start_rowid <> l_res_end_rowid)
1252     then
1253         X_start_rowid  := l_res_start_rowid;
1254         X_end_rowid    := l_res_end_rowid;
1255         X_any_rows     := TRUE;
1256 
1257         debug_info('get_rowid_range()-');
1258         return;
1259     end if;
1260 
1261     l_start_rowid := null;
1262     l_end_rowid   := null;
1263 
1264     -- do not explicitly get the lock as we are now using the skip lock
1265     -- feature
1266     -- lock_table(l_update_info.owner, l_update_info.table_name, 'EXCLUSIVE');
1267 
1268     open c_range(l_update_info.update_id);
1269 
1270     fetch c_range into l_unit_rec;
1271 
1272     if (c_range%NOTFOUND) then
1273        debug_info('get_rowid_range() : no more rows found ');
1274     else
1275       debug_info('get_rowid_range() : getting from table');
1276 
1277       l_start_rowid := get_rowid(nvl(l_unit_rec.data_object_id,
1278                                      l_update_info.object_id),
1279                                  l_unit_rec.relative_fno,
1280                                  l_unit_rec.start_block,
1281                                  0);
1282 
1283       l_end_rowid   := get_rowid(nvl(l_unit_rec.data_object_id,
1284                                      l_update_info.object_id),
1285                                  l_unit_rec.relative_fno,
1286                                  l_unit_rec.end_block,
1287                                  G_MAX_ROWS_IN_BLOCK);
1288 
1289       debug_info('get_rowid_range() : rowids returned are '||
1290                            l_start_rowid||' and '||l_end_rowid);
1291 
1292     end if;
1293 
1294     X_start_rowid := l_start_rowid;
1295     X_end_rowid   := l_end_rowid;
1296     X_any_rows    := (l_start_rowid <> l_end_rowid);
1297 
1298     if (l_start_rowid is not null) then
1299        set_rowid_range(l_worker_id,
1303 
1300              l_unit_rec.unit_id, l_unit_rec.unit_id,
1301              l_start_rowid, l_end_rowid);
1302     end if;
1304     close c_range;
1305 
1306     commit;
1307 
1308     debug_info('get_rowid_range()-');
1309   END get_rowid_range;
1310 
1311 procedure get_id_range
1312            (X_start_id   out nocopy number,
1313             X_end_id     out nocopy number,
1314             X_any_rows   out nocopy boolean,
1315             X_num_rows   in         number  default NULL,
1316             X_restart    in         boolean default FALSE)
1317 is
1318     l_res_start_rowid    rowid;
1319     l_res_end_rowid      rowid;
1320     l_res_start_id       number;
1321     l_res_end_id         number;
1322     l_start_id           number;
1323     l_end_id             number;
1324     l_start_unit_id      number;
1325     l_end_unit_id        number;
1326     l_unit_rec           ad_parallel_update_units%rowtype;
1327     l_batch_size         number;
1328 
1329     l_status             varchar2(30);
1330 
1331     l_worker_id          NUMBER;
1332     l_update_info        update_info_type;
1333 
1334     cursor c_range(p_update_id in number) is
1335       select /*+ FIRST_ROWS +*/ *
1336       from   ad_parallel_update_units
1337       where  update_id = p_update_id
1338       and status = UNASSIGNED_STATUS
1339       for update of status
1340       skip locked;
1341   begin
1342 
1343     debug_info('get_id_range()+');
1344 
1345     get_update_info(l_update_info);
1346     l_worker_id := g_cache.worker_id;
1347 
1348     l_batch_size := nvl(X_num_rows, g_cache.batch_size);
1349 
1350     get_restart_range(l_worker_id, l_update_info.update_id,
1351                       l_res_start_rowid, l_res_end_rowid,
1352                       l_res_start_id, l_res_end_id,
1353                       l_start_unit_id, l_end_unit_id);
1354 
1355     -- return the current range if there are still some rows to process
1356 
1357     X_any_rows := FALSE;
1358 
1359     if (l_res_start_id is not null
1360         and
1361         l_res_start_id < l_res_end_id)
1362     then
1363         X_start_id  := l_res_start_id;
1364 
1365         --
1366         -- For Equi rowsets, return the entire range
1367         --
1368         if (l_update_info.update_type = ID_RANGE_SCAN_EQUI_ROWSETS) then
1369            X_end_id := l_res_end_id;
1370         else
1371            X_end_id    := least(l_res_start_id + l_batch_size-1, l_res_end_id);
1372         end if;
1373 
1374         X_any_rows  := TRUE;
1375         debug_info('get_id_range()-');
1376         return;
1377     end if;
1378 
1379     --
1380     -- to address the case where the start_id = end_id as used to be recorded
1381     -- earlier. The processing now stops when start_id > end_id
1382     --
1383     if (l_res_start_id is not null
1384         and
1385         l_res_start_id = l_res_end_id)
1386     then
1387        begin
1388           --
1389           -- check the actual unit to find out if it has already been processed
1390           --
1391           select status
1392           into   l_status
1393           from   ad_parallel_update_units
1394           where  update_id = l_update_info.update_id
1395           and    unit_id = l_start_unit_id;
1396 
1397           --
1398           -- return the same range if the unit is not yet marked as processed
1399           --
1400 
1401           if (l_status = ASSIGNED_STATUS) then
1402              X_start_id  := l_res_start_id;
1403 
1404              if (l_update_info.update_type = ID_RANGE_SCAN_EQUI_ROWSETS) then
1405                X_end_id := l_res_end_id;
1406 
1407              else
1408                X_end_id    := least(l_res_start_id + l_batch_size-1,
1409                                     l_res_end_id);
1410              end if;
1411 
1412              X_any_rows  := TRUE;
1413              debug_info('get_id_range()-');
1414              return;
1415           end if;
1416 
1417        exception
1418           when NO_DATA_FOUND then
1419             null;
1420        end;
1421     end if;
1422 
1423 
1424     l_start_id := null;
1425     l_end_id   := null;
1426 
1427     -- do not explicitly lock the update as we are now using the skip locked
1428     -- feature
1429     -- lock_table(l_update_info.owner, l_update_info.table_name, 'EXCLUSIVE');
1430 
1431     open c_range(l_update_info.update_id);
1432 
1433     while (TRUE)
1434     loop
1435       fetch c_range into l_unit_rec;
1436 
1437       if (c_range%NOTFOUND) then
1438          debug_info('get_id_range() : no more rows found ');
1439          X_start_id := null;
1440          X_end_id   := null;
1441          X_any_rows := FALSE;
1442          exit;
1443       else
1444         debug_info('get_id_range() : getting from table');
1445 
1446         l_start_id := l_unit_rec.start_id;
1447         l_end_id := l_unit_rec.end_id;
1451 
1448 
1449         debug_info('get_id_range() : ids returned are '||
1450                              l_start_id||' and '||l_end_id);
1452 
1453         X_start_id := l_start_id;
1454 
1455         if (l_update_info.update_type = ID_RANGE_SCAN_EQUI_ROWSETS) then
1456           X_end_id := l_end_id;
1457         else
1458           X_end_id   := least(l_start_id + l_batch_size-1, l_end_id);
1459         end if;
1460 
1461         X_any_rows := (X_start_id <= X_end_id);
1462 
1463         if (l_start_id is not null)
1464         then
1465           set_id_range(l_worker_id, l_unit_rec.unit_id, l_unit_rec.unit_id,
1466                        l_start_id, l_end_id);
1467 
1468           exit;
1469         else
1470 
1471           /* set unit as processed if ID values are null.  */
1472 
1473           update AD_PARALLEL_UPDATE_UNITS
1474           set STATUS = PROCESSED_STATUS
1475           where update_id = l_update_info.update_id
1476           and    unit_id = l_unit_rec.unit_id;
1477 
1478         end if;
1479       end if;
1480     end loop;
1481 
1482     close c_range;
1483 
1484     commit;
1485 
1486     debug_info('get_id_range()-');
1487   END get_id_range;
1488 
1489 procedure purge_processed_units
1490            (X_owner  in varchar2 default NULL,
1491             X_table  in varchar2 default NULL,
1492             X_script in varchar2 default NULL)
1493 is
1494     cursor c_purge is
1495        select update_id
1496        from   ad_parallel_updates p
1497        where  initialized_flag = 'Y'
1498        and    owner = nvl(upper(X_owner), owner)
1499        and    table_name = nvl(upper(X_table), table_name)
1500        and    script_name = nvl(X_script, script_name)
1501        and not exists (
1502            select update_id
1503            from   ad_parallel_update_units u
1504            where  u.update_id = p.update_id
1505            and    u.status in ('A', 'U'));
1506   begin
1507     for c_rec in c_purge loop
1508       --
1509       -- delete from ad_parallel_update_units
1510       --
1511       delete from ad_parallel_update_units
1512       where update_id = c_rec.update_id;
1513 
1514       --
1515       -- delete from ad_parallel_workers
1516       --
1517       delete from ad_parallel_workers
1518       where update_id = c_rec.update_id;
1519 
1520       commit;
1521 
1522     end loop;
1523   end;
1524 
1525 --
1526 -- Procedure Delete_Update_Information
1527 --
1528 --   Deletes rows associated with an update from AD tables so that the update
1529 --   is eligible for reprocessing
1530 --
1531 --   This procedure does an implicit commit of the transaction
1532 --
1533 
1534 procedure delete_update_information(
1535             X_update_type  in number,
1536             X_owner        in varchar2,
1537             X_table        in varchar2,
1538             X_script       in varchar2)
1539 is
1540   l_update_id  number;
1541 begin
1542 
1543   begin
1544 
1545     select update_id
1546     into   l_update_id
1547     from   ad_parallel_updates
1548     where  owner = upper(X_owner)
1549     and    table_name = upper(X_table)
1550     and    script_name = X_script;
1551 
1552   exception
1553     --
1554     -- just return, if an update row is not found
1555     --
1556     when NO_DATA_FOUND then
1557       return;
1558   end;
1559 
1560   --
1561   -- get lock for the update
1562   --
1563   lock_table(X_owner, X_table, 'EXCLUSIVE');
1564 
1565   delete from ad_parallel_workers
1566   where  update_id = l_update_id;
1567 
1568   delete from ad_parallel_update_units
1569   where  update_id = l_update_id;
1570 
1571   delete from ad_parallel_updates
1572   where  update_id = l_update_id;
1573 
1574   --
1575   -- commit and release the lock
1576   --
1577   commit;
1578 
1579 end;
1580 
1581 
1582 --
1583 -- ReInitialize_After_Table_Reorg
1584 --
1585 -- This procedure is only applicable for ROWID_RANGE processing.
1586 --
1587 -- It marks the update for reprocessing if it partially done and data in the
1588 -- driving table has been reorganized
1589 --
1590 procedure ReInitialize_After_Table_Reorg(
1591             X_owner        in varchar2 default NULL,
1592             X_table        in varchar2 default NULL,
1593             X_script       in varchar2 default NULL)
1594 is
1595 
1596   --
1597   -- updates that have pending units are candidates for reinitialization
1598   --
1599   cursor c_cur is
1600     select update_id, table_name, owner
1601     from   ad_parallel_updates pu
1602     where  owner = nvl(upper(X_owner), owner)
1603     and    table_name = nvl(upper(X_table), table_name)
1604     and    script_name = nvl(X_script, script_name)
1605     and    update_type = ROWID_RANGE
1606     and    initialized_flag = 'Y'
1607     and exists (
1608         select 'Unprocessed units exist'
1609         from   ad_parallel_update_units pun
1610         where  pun.update_id = pu.update_id
1611         and    pun.status in (UNASSIGNED_STATUS, ASSIGNED_STATUS));
1612 begin
1613 
1614   for crec in c_cur loop
1615 
1616      --
1617      -- get lock for the update
1618      --
1619      lock_table(crec.owner, crec.table_name, 'EXCLUSIVE');
1620 
1621      --
1622      -- set the update to un-initialized
1623      --
1624      update ad_parallel_updates
1625      set initialized_flag = 'N'
1626      where update_id = crec.update_id;
1627 
1628      --
1629      -- delete from ad_parallel_update_units
1630      --
1634      delete from ad_parallel_workers
1631      delete from ad_parallel_update_units
1632      where update_id = crec.update_id;
1633 
1635      where update_id = crec.update_id;
1636 
1637      --
1638      -- release the lock
1639      --
1640      commit;
1641 
1642   end loop;
1643 
1644 end ReInitialize_After_Table_Reorg;
1645 
1646 
1647 begin
1648    g_cache.ui_initialized := FALSE;
1649    g_cache.lock_name := '$';
1650 end;