DBA Data[Home] [Help]

PACKAGE BODY: APPS.DT_API

Source


1 PACKAGE BODY DT_API AS
2 /* $Header: dtapiapi.pkb 120.0 2005/05/27 23:09:43 appldev noship $ */
3 g_package     VARCHAR2(33) := ' dt_api.'; -- Global package name
4 g_debug       BOOLEAN; -- debug var. no need to initialise here because
5                        -- it is set on every entry point into dt_api
6                        -- (i.e. every public proc/fct)
7 g_oracle_db_version     CONSTANT NUMBER := hr_general2.get_oracle_db_version;
8                         -- holds the current ORACLE DB Major
9                         -- release number (e.g. 8.1, 9.0, 9.1)
10 g_dynamic_sql_comment   CONSTANT VARCHAR2(500) :=
11   ' /* dynamic SQL from dt_api.{proc} for'||
12   ' ORACLE '||TO_CHAR(g_oracle_db_version)||' */'; -- dynamic SQL comment str
13 g_dynamic_sql           VARCHAR2(2000); -- dynamic SQL text string
14 -- set private package vars once to avoid cross package calls to hr_api
15 -- even though it might be redundant because they are defined as
16 -- constants in hr_api.
17 g_sot                   CONSTANT DATE         := hr_api.g_sot;
18 g_eot                   CONSTANT DATE         := hr_api.g_eot;
19 g_insert                CONSTANT VARCHAR2(30) := hr_api.g_insert;
20 g_correction            CONSTANT VARCHAR2(30) := hr_api.g_correction;
21 g_update                CONSTANT VARCHAR2(30) := hr_api.g_update;
22 g_update_override       CONSTANT VARCHAR2(30) := hr_api.g_update_override;
23 g_update_change_insert  CONSTANT VARCHAR2(30) := hr_api.g_update_change_insert;
24 g_zap                   CONSTANT VARCHAR2(30) := hr_api.g_zap;
25 g_delete                CONSTANT VARCHAR2(30) := hr_api.g_delete;
26 g_future_change         CONSTANT VARCHAR2(30) := hr_api.g_future_change;
27 g_delete_next_change    CONSTANT VARCHAR2(30) := hr_api.g_delete_next_change;
28 g_varchar2              CONSTANT VARCHAR2(9)  := hr_api.g_varchar2;
29 g_number                CONSTANT NUMBER       := hr_api.g_number;
30 g_date                  CONSTANT DATE         := hr_api.g_date;
31 -- define the effective rows record type
32 TYPE g_dt_effective_rows_rec IS RECORD
33       (effective_start_date DATE,
34        effective_end_date   DATE);
35 -- define the effective rows table
36 TYPE g_dt_effective_rows_tab IS TABLE OF
37      g_dt_effective_rows_rec INDEX BY BINARY_INTEGER;
38 -- define weak REF CURSOR type
39 TYPE g_csr_type IS REF CURSOR;
40 -- define a table of date's type
41 TYPE g_date_tab_type IS TABLE OF DATE INDEX BY BINARY_INTEGER;
42 -- define an empty table which is NEVER set and only used to support
43 -- NOCOPY reset behaviour. This var is only referenced in get_effective_rows
44 -- procedure and is defined as a global to minimise the number or
45 -- instanations to 1.
46 g_empty_effective_rows g_dt_effective_rows_tab; -- only referenced on an
47                                                 -- error and always empty
48 -- ----------------------------------------------------------------------------
49 -- |--------------------------< get_effective_rows >--------------------------|
50 -- ----------------------------------------------------------------------------
51 --
52 -- PRIVATE
53 --
54 -- Description: this procedure is used to select (and lock if required) a set
55 --              of effective rows for the base table/column/key combo. all rows
56 --              are returned as a table of records (p_effective_rows), together
57 --              with the index position indicated which element contains the
58 --              current effective row as of the passed in p_date_from
59 --              parameter. to ensure that a current row exist the
60 --              p_date_from_valid parameter can be set to TRUE. if the check
61 --              fails (e.g. no current row) then an error is raised. the rows
62 --              can be locked by setting p_lock_rows to TRUE.
63 -- ----------------------------------------------------------------------------
64 PROCEDURE get_effective_rows
65             (p_date_from        IN     DATE,
66              p_base_table_name  IN     VARCHAR2,
67              p_base_key_column  IN     VARCHAR2,
68              p_base_key_value   IN     NUMBER,
69              p_lock_rows        IN     BOOLEAN,
70              p_date_from_valid  IN     BOOLEAN,
71              p_effective_rows      OUT NOCOPY g_dt_effective_rows_tab,
72              p_date_from_row_idx   OUT NOCOPY BINARY_INTEGER) IS
73   --
74   l_csr                  g_csr_type;
75   l_idx                  PLS_INTEGER;
76   l_cnt                  BINARY_INTEGER;
77   l_effective_start_date g_date_tab_type;
78   l_effective_end_date   g_date_tab_type;
79   l_proc VARCHAR2(72);
80   --
81 BEGIN
82   IF g_debug THEN
83     l_proc := g_package||'get_effective_rows';
84     hr_utility.Set_Location('Entering:'||l_proc, 5);
85   END IF;
86   -- If the p_key_value is null and we are locking then we must not
87   -- process the sql as it could be a nullable column.
88   IF (p_base_key_value IS NULL AND p_lock_rows) THEN
89     IF g_debug THEN
90       hr_utility.Set_Location('Leaving :'||l_proc, 10);
91       -- the resulting p_effective_rows and p_date_from_row_idx will be NULL
92     END IF;
93     RETURN;
94   END IF;
95   -- note: for ORACLE 8.1.6 and beyond you don't need to specify an
96   --       ORDER BY clause but has just been placed in for backwards compat.
97   --       for 8.1.6+ no performance impact will be incurred because the CBO
98   --       will realise that the rows being returned are in a sorted format.
99   --       just being ultra defensive...
100   g_dynamic_sql :=
101     'SELECT t1.effective_start_date, t1.effective_end_date '||
102     'FROM '||LOWER(p_base_table_name)||' t1 '||
103     'WHERE t1.'||LOWER(p_base_key_column)||' = :p_key_value '||
104     'AND t1.effective_end_date >= :p_date_from '||
105     'ORDER BY t1.effective_start_date';
106   -- check to see if the rows needs to be locked
107   IF p_lock_rows THEN
108     -- add locking condition
109     g_dynamic_sql := g_dynamic_sql || ' FOR UPDATE NOWAIT';
110   END IF;
111   -- set the dynamic SQL comment for identification
112   dt_api.g_dynamic_sql :=
113     dt_api.g_dynamic_sql||
114     REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','get_effective_rows');
115   -- open cursor, bulk fetch all the rows and close
116   OPEN l_csr FOR g_dynamic_sql USING p_base_key_value, p_date_from;
117   -- NOTE: ORACLE VERSION CODE SWITCH
118   -- ================================
119   -- Oracle 8/8i does not support BULK COLLECT of a dynamic PL/SQL
120   -- statement.
121   IF g_oracle_db_version >= 9 THEN
122     -- Oracle 9+ being used so perform a BULK COLLECT
123     FETCH l_csr BULK COLLECT INTO l_effective_start_date,
124                                   l_effective_end_date;
125   ELSE
126     -- Pre Oracle 9 so fetch each row individually
127     l_cnt := 1;
128     LOOP
129       -- A Pre Oracle 9 DB is being used so LOOP through fetching each row
130       FETCH l_csr INTO l_effective_start_date(l_cnt), l_effective_end_date(l_cnt);
131       EXIT WHEN l_csr%NOTFOUND;
132       l_cnt := l_cnt + 1;
133     END LOOP;
134   END IF;
135   CLOSE l_csr;
136   -- set the current effective row indicator to 0
137   l_idx := 0;
138   -- loop through each returned date and place in p_effective_rows OUT structure
139   FOR l_counter IN 1..l_effective_start_date.COUNT LOOP
140     p_effective_rows(l_counter).effective_start_date :=
141       l_effective_start_date(l_counter);
142     p_effective_rows(l_counter).effective_end_date :=
143       l_effective_end_date(l_counter);
144     -- check to see if this is a current row
145     IF l_effective_start_date(l_counter) <= p_date_from AND
146        l_effective_end_date(l_counter) >= p_date_from THEN
147       -- set the current row as of the date index var
148       p_date_from_row_idx := l_counter;
149       l_idx := l_counter;
150     END IF;
151   END LOOP;
152   -- do we need to check that the current row exists and raise an error?
153   IF p_date_from_valid AND l_idx = 0 THEN
154     -- clear the returning OUTs
155     p_effective_rows := dt_api.g_empty_effective_rows;
156     p_date_from_row_idx := NULL;
157     -- As no rows were returned we must error
158     hr_utility.set_message(801, 'HR_7180_DT_NO_ROW_EXIST');
159     hr_utility.set_message_token('TABLE_NAME', p_base_table_name);
160     hr_utility.set_message_token('SESSION_DATE',
161                                  fnd_date.date_to_chardate(p_date_from));
162     hr_utility.raise_error;
163   END IF;
164   IF g_debug THEN
165     hr_utility.Set_Location('Leaving :'||l_proc, 15);
166   END IF;
167 EXCEPTION
168   WHEN NO_DATA_FOUND THEN
169     -- close the cursor if open
170     IF l_csr%ISOPEN THEN
171       CLOSE l_csr;
172     END IF;
173     -- clear the returning OUTs
174     p_effective_rows := dt_api.g_empty_effective_rows;
175     p_date_from_row_idx := NULL;
176     -- no rows exist as of the date passed in
177     -- therefore a serious integrity problem has ocurred
178     hr_utility.set_message(801, 'HR_7423_DT_INVALID_ID');
179     hr_utility.set_message_token('ARGUMENT', UPPER(p_base_key_column));
180     hr_utility.raise_error;
181   WHEN hr_api.object_locked THEN
182     -- close the cursor if open
183     IF l_csr%ISOPEN THEN
184       CLOSE l_csr;
185     END IF;
186     -- clear the returning OUTs
187     p_effective_rows := dt_api.g_empty_effective_rows;
188     p_date_from_row_idx := NULL;
189     -- The object is locked therefore we need to supply a meaningful
190     -- error message.
191     hr_utility.set_message(801, 'HR_7165_OBJECT_LOCKED');
192     hr_utility.set_message_token('TABLE_NAME', p_base_table_name);
193     hr_utility.raise_error;
194   WHEN OTHERS THEN
195     -- close the cursor if open
196     IF l_csr%ISOPEN THEN
197       CLOSE l_csr;
198     END IF;
199     -- clear the returning OUTs
200     p_effective_rows := dt_api.g_empty_effective_rows;
201     p_date_from_row_idx := NULL;
202     -- unexpected system error, so raise
203     RAISE;
204 END get_effective_rows;
205 -- ----------------------------------------------------------------------------
206 -- |----------------------< return_parent_min_date >--------------------------|
207 -- ----------------------------------------------------------------------------
208 --
209 -- PRIVATE
210 --
211 -- Description: returns the parent min end date.
212 --
213 -- ----------------------------------------------------------------------------
214 FUNCTION return_parent_min_date
215           (p_effective_date IN DATE,
216            p_lock_rows      IN BOOLEAN,
217            p_table_name1    IN VARCHAR2,
218            p_key_column1    IN VARCHAR2,
219            p_key_value1     IN NUMBER,
220            p_table_name2    IN VARCHAR2,
221            p_key_column2    IN VARCHAR2,
222            p_key_value2     IN NUMBER,
223            p_table_name3    IN VARCHAR2,
224            p_key_column3    IN VARCHAR2,
225            p_key_value3     IN NUMBER,
226            p_table_name4    IN VARCHAR2,
227            p_key_column4    IN VARCHAR2,
228            p_key_value4     IN NUMBER,
229            p_table_name5    IN VARCHAR2,
230            p_key_column5    IN VARCHAR2,
231            p_key_value5     IN NUMBER,
232            p_table_name6    IN VARCHAR2,
233            p_key_column6    IN VARCHAR2,
234            p_key_value6     IN NUMBER,
235            p_table_name7    IN VARCHAR2,
236            p_key_column7    IN VARCHAR2,
237            p_key_value7     IN NUMBER,
238            p_table_name8    IN VARCHAR2,
239            p_key_column8    IN VARCHAR2,
240            p_key_value8     IN NUMBER,
241            p_table_name9    IN VARCHAR2,
242            p_key_column9    IN VARCHAR2,
243            p_key_value9     IN NUMBER,
244            p_table_name10   IN VARCHAR2,
245            p_key_column10   IN VARCHAR2,
246            p_key_value10    IN NUMBER)
247          RETURN DATE IS
248   --
249   l_table_name  VARCHAR2(30);
250   l_key_column  VARCHAR2(30);
251   l_key_value   NUMBER(15);
252   l_proc        VARCHAR2(72);
253   l_return_date DATE := dt_api.g_eot;  -- default the returning date to eot
254   l_max_date    DATE;
255   l_csr         g_csr_type;
256   --
257 BEGIN
258   IF g_debug THEN
259     l_proc := g_package||'return_parent_min_date';
260     hr_utility.Set_Location('Entering:'||l_proc, 5);
261   END IF;
262   -- setup the table with info
263   FOR l_counter IN 1..10 LOOP
264     IF    (l_counter = 1) THEN
265       l_table_name := p_table_name1;
266       l_key_column := p_key_column1;
267       l_key_value  := p_key_value1;
268     ELSIF (l_counter = 2) THEN
269       l_table_name := p_table_name2;
270       l_key_column := p_key_column2;
271       l_key_value  := p_key_value2;
272     ELSIF (l_counter = 3) THEN
273       l_table_name := p_table_name3;
274       l_key_column := p_key_column3;
275       l_key_value  := p_key_value3;
276     ELSIF (l_counter = 4) THEN
277       l_table_name := p_table_name4;
278       l_key_column := p_key_column4;
279       l_key_value  := p_key_value4;
280     ELSIF (l_counter = 5) THEN
281       l_table_name := p_table_name5;
282       l_key_column := p_key_column5;
283       l_key_value  := p_key_value5;
284     ELSIF (l_counter = 6) THEN
285       l_table_name := p_table_name6;
286       l_key_column := p_key_column6;
287       l_key_value  := p_key_value6;
288     ELSIF (l_counter = 7) THEN
289       l_table_name := p_table_name7;
290       l_key_column := p_key_column7;
291       l_key_value  := p_key_value7;
292     ELSIF (l_counter = 8) THEN
293       l_table_name := p_table_name8;
294       l_key_column := p_key_column8;
295       l_key_value  := p_key_value8;
296     ELSIF (l_counter = 9) THEN
297       l_table_name := p_table_name9;
298       l_key_column := p_key_column9;
299       l_key_value  := p_key_value9;
300     ELSE
301       l_table_name := p_table_name10;
302       l_key_column := p_key_column10;
303       l_key_value  := p_key_value10;
304     END IF;
305     -- Ensure that all the working details have been specified
306     -- note: it is ignored if not set correctly
307     IF NOT ((NVL(l_table_name, dt_api.g_varchar2) =
308              dt_api.g_varchar2) OR
309             (NVL(l_key_column, dt_api.g_varchar2) =
310              dt_api.g_varchar2) OR
311             (NVL(l_key_value, dt_api.g_number)    =
312              dt_api.g_number)) THEN
313       -- we lower the table and column name to always ensure that the
314       -- SQL will be exactly the same because callers may have passed
315       -- the table/column name in any case format
316       l_table_name := LOWER(l_table_name);
317       l_key_column := LOWER(l_key_column);
318       -- define the the max end date SQL
319       -- we only need to return the max row
320       -- the MAX function couldn't be used because
321       -- you cannot perform a FOR UPDATE.
322       -- error if no rows exist.
323       -- note: if locking is required, then all rows identified by the query
324       --       (not just the 1 row returned) will be locked.
325       -- the subquery is used to ensure that at least one row exists before
326       -- the proposed effective date
327       dt_api.g_dynamic_sql :=
328         'SELECT oq.effective_end_date '||
329         'FROM '||l_table_name||' oq '||
330         'WHERE oq.'||l_key_column||' = :l_key_value '||
331         'AND oq.effective_end_date >= :p_effective_date '||
332         'AND EXISTS (SELECT NULL FROM '||l_table_name||
333         ' sq WHERE sq.'||l_key_column||' = oq.'||l_key_column||
334         ' AND sq.effective_start_date <= :p_effective_date) '||
335         'ORDER BY oq.effective_end_date DESC';
336       -- do we need to lock?
337       IF p_lock_rows THEN
338         dt_api.g_dynamic_sql := dt_api.g_dynamic_sql||' FOR UPDATE NOWAIT';
339       END IF;
340       -- set the dynamic SQL comment for identification
341       dt_api.g_dynamic_sql :=
342         dt_api.g_dynamic_sql||
343         REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','return_parent_min_date');
344       -- OPEN the cursor
345       OPEN  l_csr
346       FOR   g_dynamic_sql
347       USING l_key_value, p_effective_date, p_effective_date;
348       -- although the query can return more than one row we are only interested
349       -- in FETCHing the 1st row
353         RAISE NO_DATA_FOUND;
350       FETCH l_csr INTO l_max_date;
351       IF l_csr%NOTFOUND THEN
352         -- no rows returned, raise an error
354       END IF;
355       -- CLOSE the cursor
356       CLOSE l_csr;
357       -- if the returned l_max_date is less than the
358       -- effective_date then error because a parental row does NOT exist.
359       IF (l_max_date < p_effective_date) THEN
360         -- the parental rows specified do not exist as of the effective date
361         -- therefore a serious integrity problem has ocurred
362         RAISE NO_DATA_FOUND;
363       ELSE
364         -- the LEAST function will then compare the working l_return_date with
365         -- the returned maximum effective end date (l_max_date) and set the
366         -- l_return_date to the minimum of these dates
367         l_return_date := LEAST(l_return_date, l_max_date);
368       END IF;
369     END IF;
370   END LOOP;
371   IF g_debug THEN
372     hr_utility.Set_Location('Leaving:'||l_proc, 10);
373   END IF;
374   RETURN(l_return_date);
375 EXCEPTION
376   WHEN NO_DATA_FOUND THEN
377     -- CLOSE the cursor if its open
378     IF l_csr%ISOPEN THEN
379       CLOSE l_csr;
380     END IF;
381     -- The parental row specified does not exist as of the effective date
382     -- therefore a serious integrity problem has ocurred
383     -- bug 3788667
384     hr_utility.set_message(801, 'HR_7423_DT_INVALID_ID');
385     hr_utility.set_message_token('ARGUMENT', UPPER(l_key_column));
386     hr_utility.raise_error;
387   WHEN hr_api.object_locked THEN
388     -- CLOSE the cursor if its open
389     IF l_csr%ISOPEN THEN
390       CLOSE l_csr;
391     END IF;
392     -- bug 3788667
393     -- The object is locked therefore we need to supply a meaningful
394     -- error message.
395     hr_utility.set_message(801, 'HR_7165_OBJECT_LOCKED');
396     hr_utility.set_message_token('TABLE_NAME', UPPER(l_table_name));
397     hr_utility.raise_error;
398   WHEN OTHERS THEN
399     -- CLOSE the cursor if its open
400     IF l_csr%ISOPEN THEN
401       CLOSE l_csr;
402     END IF;
403     -- bug 3788667
404     -- raise system error
405     RAISE;
406 END return_parent_min_date;
407 -- ----------------------------------------------------------------------------
408 -- |-------------------------< Effective_Date_Valid >-------------------------|
409 -- ----------------------------------------------------------------------------
410 --
411 -- PRIVATE
412 --
413 -- Description: Procedure ensures that the effective date is not null and
414 --              exists on or after the start of time.
415 --
416 -- ----------------------------------------------------------------------------
417 PROCEDURE Effective_Date_Valid(p_effective_date IN DATE) IS
418   l_proc VARCHAR2(72);
419 BEGIN
420   IF g_debug THEN
421     l_proc := g_package||'Effective_Date_Valid';
422     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
423   END IF;
424   -- Ensure that all the mandatory arguments are not null
425   -- [ start of change 30.14 ]
426   IF p_effective_date IS NULL THEN
427     hr_api.mandatory_arg_error(p_api_name       => l_proc,
428                                p_argument       => 'p_effective_date',
429                                p_argument_value => p_effective_date);
430   END IF;
431   -- [ end of change 30.14 ]
432   IF (p_effective_date < dt_api.g_sot) THEN
433     hr_utility.set_message(801, 'HR_6153_ALL_PROCEDURE_FAIL');
434     hr_utility.set_message_token('PROCEDURE', l_proc);
435     hr_utility.set_message_token('STEP','10');
436     hr_utility.raise_error;
437   END IF;
438   -- Ensure p_effective_date is not later than dt_api.g_eot end of time
439   IF (p_effective_date > dt_api.g_eot) THEN
440     hr_utility.set_message(801, 'HR_6153_ALL_PROCEDURE_FAIL');
441     hr_utility.set_message_token('PROCEDURE', l_proc);
442     hr_utility.set_message_token('STEP','20');
443     hr_utility.raise_error;
444   END IF;
445   -- Check that effective_date does not include a time component. If set
446   -- then raise an error because it should have been truncated to just a day,
447   -- month year value before the DT logic is called.
448   IF p_effective_date <> TRUNC(p_effective_date) THEN
449     hr_utility.set_message(801, 'HR_51322_DT_TIME_SET');
450     hr_utility.raise_error;
451   END IF;
452   IF g_debug THEN
453     Hr_Utility.Set_Location('Leaving :'||l_proc, 10);
454   END IF;
455 END Effective_Date_Valid;
456 -- ----------------------------------------------------------------------------
457 -- |------------------------< Return_Max_End_Date >---------------------------|
458 -- ----------------------------------------------------------------------------
459 --
460 -- PRIVATE
461 --
462 -- Description: Function returns the maximum effective_end_date for the
463 --              specified table and primary key.
464 --              NOTE: if the maximum end date doesn't exist (i.e. no rows
465 --                    exist for the specified table, key values) then we
466 --                    return the null value.
467 -- ----------------------------------------------------------------------------
468 FUNCTION return_max_end_date
469          (p_base_table_name IN VARCHAR2,
470           p_base_key_column IN VARCHAR2,
471           p_base_key_value  IN NUMBER)
472          RETURN DATE IS
473   --
474   l_proc     VARCHAR2(72);
475   l_max_date DATE;
476   --
477 BEGIN
481     hr_utility.set_location('Entering:'||l_proc, 5);
478   g_debug := hr_utility.debug_enabled;
479   IF g_debug THEN
480     l_proc := g_package||'return_max_end_date';
482   END IF;
483   -- Ensure that all the mandatory arguments are not null
484   -- [ start of change 30.14 ]
485   IF p_base_table_name IS NULL OR p_base_key_column IS NULL OR
486      p_base_key_value IS NULL THEN
487     hr_api.mandatory_arg_error(p_api_name       => l_proc,
488                                p_argument       => 'p_base_table_name',
489                                p_argument_value => p_base_table_name);
490     hr_api.mandatory_arg_error(p_api_name       => l_proc,
491                                p_argument       => 'p_base_key_column',
492                                p_argument_value => p_base_key_column);
493     hr_api.mandatory_arg_error(p_api_name       => l_proc,
494                                p_argument       => 'p_base_key_value',
495                                p_argument_value => p_base_key_value);
496   END IF;
497   -- [ end of change 30.14 ]
498   -- Define dynamic sql text with substitution tokens
499   g_dynamic_sql:=
500     'SELECT MAX(t.effective_end_date) '||
501     'FROM '||LOWER(p_base_table_name)||' t '||
502     'WHERE t.'||LOWER(p_base_key_column)||' = :p_base_key_value';
503   -- set the dynamic SQL comment for identification
504   dt_api.g_dynamic_sql :=
505     dt_api.g_dynamic_sql||
506     REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','return_max_end_date');
507   --
508   EXECUTE IMMEDIATE g_dynamic_sql
509   INTO  l_max_date
510   USING p_base_key_value;
511   --
512   IF g_debug THEN
513     hr_utility.set_location('Leaving :'||l_proc, 10);
514   END IF;
515   RETURN(l_max_date);
516 END return_max_end_date;
517 -- ----------------------------------------------------------------------------
518 -- |----------------------------< Lck_Child >---------------------------------|
519 -- ----------------------------------------------------------------------------
520 --
521 -- PUBLIC
522 --
523 -- Description: Locks the specified child entity maximum row for the specified
524 --              parent key value:
525 --
526 --              E.g. ('X' denotes locked rows)
527 --
528 --              |---------------------------------------| Parent Entity
529 --              |---------|XXXXXXXXXX|                    Child DT Rows 1
530 --              |-------------|XXXXXXXXXXXXXXX|           Child DT Rows 2
531 --              |---|-----|XXXXXXXXXXXXX|                 Child DT Rows 3
532 --
533 --              After locking the maximum row, we must ensure that the
534 --              effective end date of the locked row cannot exceed
535 --              the validation start date.
536 --
537 --              No processing will be completed if the p_parent_key_value is
538 --              null because the column could be defined as nullable.
539 --
540 -- ----------------------------------------------------------------------------
541 PROCEDURE lck_child
542          (p_child_table_name      IN VARCHAR2,
543           p_child_key_column      IN VARCHAR2,
544           p_parent_key_column     IN VARCHAR2,
545           p_parent_key_value      IN NUMBER,
546           p_validation_start_date IN DATE) IS
547 --
548   l_proc        VARCHAR2(72);
549   l_cursor      g_csr_type;
550   l_date_tab    g_date_tab_type;
551   l_cnt         BINARY_INTEGER;
552 --
553 BEGIN
554   IF g_debug THEN
555     l_proc := g_package||'lck_child';
556     hr_utility.set_location('Entering:'||l_proc, 5);
557   END IF;
558   --
559   -- Ensure that all the required parameters exist
560   -- Note: we don't check the p_parent_key_value argument
561   --
562   -- [ start of change 30.14 ]
563   --
564   -- hr_api.mandatory_arg_error(p_api_name       => l_proc,
565   --                           p_argument       => 'p_child_table_name',
566   --                           p_argument_value => p_child_table_name);
567   -- hr_api.mandatory_arg_error(p_api_name       => l_proc,
568   --                            p_argument       => 'p_child_key_column',
569   --                            p_argument_value => p_child_key_column);
570   IF p_parent_key_column IS NULL THEN
571     hr_api.mandatory_arg_error(p_api_name       => l_proc,
572                                p_argument       => 'p_parent_key_column',
573                                p_argument_value => p_parent_key_column);
574   END IF;
575   -- Define dynamic sql text with substitution tokens
576   -- old SQL before optimisations (see next SQL text below)
577   -- g_dynamic_sql :=
578   --  'select t1.effective_end_date effective_end_date '||
579   --  'from '||p_child_table_name||' t1 '||
580   --  'where (t1.'||p_child_key_column||',t1.effective_start_date,'||
581   --  't1.effective_end_date) in '||
582   --  '(select t2.'||p_child_key_column||',max(t2.effective_start_date),'||
583   --  'max(t2.effective_end_date) from '||p_child_table_name||' t2 '||
584   --  'where t2.'||p_parent_key_column||' = :p_parent_key_value '||
585   --  'group by t2.'||p_child_key_column||')'||
586   --  'order by t1.'||p_child_key_column||
587   --  ' for update nowait';
588   g_dynamic_sql :=
589     'SELECT t1.effective_end_date effective_end_date '||
590     'FROM '||p_child_table_name||' t1 '||
591     'WHERE t1.'||p_parent_key_column||' = :p_parent_key_value '||
592     'AND (t1.'||p_child_key_column||',t1.effective_start_date,'||
593     't1.effective_end_date) IN '||
597     ' GROUP BY t2.'||p_child_key_column||')'||
594     '(SELECT t2.'||p_child_key_column||',MAX(t2.effective_start_date),'||
595     'MAX(t2.effective_end_date) FROM '||p_child_table_name||' t2 '||
596     'WHERE t2.'||p_child_key_column||' = t1.'||p_child_key_column||
598     ' FOR UPDATE NOWAIT';
599   -- set the dynamic SQL comment for identification
600   dt_api.g_dynamic_sql :=
601     dt_api.g_dynamic_sql||
602     REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','lck_child');
603   -- open a cursor
604   OPEN l_cursor FOR g_dynamic_sql USING p_parent_key_value;
605   -- NOTE: ORACLE VERSION CODE SWITCH
606   -- ================================
607   -- Oracle 8/8i does not support BULK COLLECT of a dynamic PL/SQL
608   -- statement.
609   IF g_oracle_db_version >= 9 THEN
610     -- Oracle 9+ being used so perform a BULK COLLECT
611     FETCH l_cursor BULK COLLECT INTO l_date_tab;
612   ELSE
613     -- Pre Oracle 9 so fetch each row individually
614     l_cnt := 1;
615     LOOP
616       -- A Pre Oracle 9 DB is being used so LOOP through fetching each row
617       FETCH l_cursor INTO l_date_tab(l_cnt);
618       EXIT WHEN l_cursor%NOTFOUND;
619       l_cnt := l_cnt + 1;
620     END LOOP;
621   END IF;
622   CLOSE l_cursor;
623   --
624   FOR l_counter IN 1..l_date_tab.COUNT LOOP
625     -- For each locked row we must ensure that the maximum end date is NOT
626     -- greater than the validation start date
627     IF (l_date_tab(l_counter) >= p_validation_start_date) THEN
628       -- The maximum end date is greater than or equal to the
629       -- validation start date therefore we must error
630       hr_utility.set_message(801, 'HR_7201_DT_NO_DELETE_CHILD');
631       hr_utility.raise_error;
632     END IF;
633   END LOOP;
634   IF g_debug THEN
635     hr_utility.set_location(' Leaving:'||l_proc, 35);
636   END IF;
637 EXCEPTION
638   WHEN hr_api.object_locked THEN
639     IF l_cursor%ISOPEN THEN
640       CLOSE l_cursor;
641     END IF;
642     -- The object is locked therefore we need to supply a meaningful
643     -- error message.
644     hr_utility.set_message(801, 'HR_7165_OBJECT_LOCKED');
645     hr_utility.set_message_token('TABLE_NAME', p_child_table_name);
646     hr_utility.raise_error;
647   WHEN OTHERS THEN
648     IF l_cursor%ISOPEN THEN
649       CLOSE l_cursor;
650     END IF;
651     RAISE;
652 END lck_child;
653 -- ----------------------------------------------------------------------------
654 -- |-------------------------< Find_DT_Upd_Modes >----------------------------|
655 -- ----------------------------------------------------------------------------
656 --
657 -- PUBLIC
658 --
659 -- Description: Returns corresponding boolean values for the respective DT
660 --              update modes.
661 --
662 -- ----------------------------------------------------------------------------
663 PROCEDURE Find_DT_Upd_Modes
664           (p_effective_date       IN            DATE,
665            p_base_table_name      IN            VARCHAR2,
666            p_base_key_column      IN            VARCHAR2,
667            p_base_key_value       IN            NUMBER,
668            p_correction              OUT NOCOPY BOOLEAN,
669            p_update                  OUT NOCOPY BOOLEAN,
670            p_update_override         OUT NOCOPY BOOLEAN,
671            p_update_change_insert    OUT NOCOPY BOOLEAN) IS
672   --
673   l_proc                    varchar2(72);
674   l_correction_start_date   DATE;
675   l_correction_end_date     DATE;
676   l_update_start_date       DATE;
677   l_update_end_date         DATE;
678   l_upd_chg_start_date      DATE;
679   l_upd_chg_end_date        DATE;
680   l_override_start_date     DATE;
681   l_override_end_date       DATE;
682   --
683 BEGIN
684   g_debug := hr_utility.debug_enabled;
685   IF g_debug THEN
686     l_proc := g_package||'Find_DT_Upd_Modes';
687     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
688   END IF;
689   find_dt_upd_modes_and_dates
690    (p_effective_date      => p_effective_date
691    ,p_base_table_name     => p_base_table_name
692    ,p_base_key_column     => p_base_key_column
693    ,p_base_key_value      => p_base_key_value
694    ,p_correction          => p_correction
695    ,p_update              => p_update
696    ,p_update_override     => p_update_override
697    ,p_update_change_insert    => p_update_change_insert
698    ,p_correction_start_date   => l_correction_start_date
699    ,p_correction_end_date     => l_correction_end_date
700    ,p_update_start_date       => l_update_start_date
701    ,p_update_end_date         => l_update_end_date
702    ,p_upd_chg_start_date      => l_upd_chg_start_date
703    ,p_upd_chg_end_date        => l_upd_chg_end_date
704    ,p_override_start_date     => l_override_start_date
705    ,p_override_end_date       => l_override_end_date
706   );
707 
708   IF g_debug THEN
709     Hr_Utility.Set_Location('Leaving :'||l_proc, 20);
710   END IF;
711 EXCEPTION
712   WHEN OTHERS THEN
713     -- set all OUTs to NULL and RAISE
714     p_correction           := NULL;
715     p_update               := NULL;
716     p_update_override      := NULL;
717     p_update_change_insert := NULL;
718     RAISE;
719 END Find_DT_Upd_Modes;
720 -- ----------------------------------------------------------------------------
721 -- |-------------------------< Find_DT_Del_Modes >----------------------------|
722 -- ----------------------------------------------------------------------------
723 --
724 -- PUBLIC
728 --
725 --
726 -- Description: Returns corresponding boolean values for the respective DT
727 --              delete modes.
729 -- ----------------------------------------------------------------------------
730 PROCEDURE Find_DT_Del_Modes
731           (p_effective_date      IN         DATE,
732            p_base_table_name     IN         VARCHAR2,
733            p_base_key_column     IN         VARCHAR2,
734            p_base_key_value      IN         NUMBER,
735            p_parent_table_name1  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
736            p_parent_key_column1  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
737            p_parent_key_value1   IN         NUMBER   DEFAULT hr_api.g_number,
738            p_parent_table_name2  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
739            p_parent_key_column2  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
740            p_parent_key_value2   IN         NUMBER   DEFAULT hr_api.g_number,
741            p_parent_table_name3  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
742            p_parent_key_column3  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
743            p_parent_key_value3   IN         NUMBER   DEFAULT hr_api.g_number,
744            p_parent_table_name4  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
745            p_parent_key_column4  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
746            p_parent_key_value4   IN         NUMBER   DEFAULT hr_api.g_number,
747            p_parent_table_name5  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
748            p_parent_key_column5  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
749            p_parent_key_value5   IN         NUMBER   DEFAULT hr_api.g_number,
750            p_parent_table_name6  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
751            p_parent_key_column6  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
752            p_parent_key_value6   IN         NUMBER   DEFAULT hr_api.g_number,
753            p_parent_table_name7  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
754            p_parent_key_column7  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
755            p_parent_key_value7   IN         NUMBER   DEFAULT hr_api.g_number,
756            p_parent_table_name8  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
757            p_parent_key_column8  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
758            p_parent_key_value8   IN         NUMBER   DEFAULT hr_api.g_number,
759            p_parent_table_name9  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
760            p_parent_key_column9  IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
761            p_parent_key_value9   IN         NUMBER   DEFAULT hr_api.g_number,
762            p_parent_table_name10 IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
763            p_parent_key_column10 IN         VARCHAR2 DEFAULT hr_api.g_varchar2,
764            p_parent_key_value10  IN         NUMBER   DEFAULT hr_api.g_number,
765            p_zap                 OUT NOCOPY BOOLEAN,
766            p_delete              OUT NOCOPY BOOLEAN,
767            p_future_change       OUT NOCOPY BOOLEAN,
768            p_delete_next_change  OUT NOCOPY BOOLEAN) IS
769   --
770   l_proc                        varchar2(72);
771   l_zap_start_date              DATE;
772   l_zap_end_date                DATE;
773   l_delete_start_date           DATE;
774   l_delete_end_date             DATE;
775   l_del_future_start_date       DATE;
776   l_del_future_end_date         DATE;
777   l_del_next_start_date         DATE;
778   l_del_next_end_date           DATE;
779   --
780 BEGIN
781   g_debug := hr_utility.debug_enabled;
782   IF g_debug THEN
783     l_proc := g_package||'Find_DT_Del_Modes';
784     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
785   END IF;
786   find_dt_del_modes_and_dates
787   (p_effective_date     =>   p_effective_date
788   ,p_base_table_name    =>   p_base_table_name
789   ,p_base_key_column    =>   p_base_key_column
790   ,p_base_key_value     =>   p_base_key_value
791   ,p_parent_table_name1 =>   p_parent_table_name1
792   ,p_parent_key_column1 =>   p_parent_key_column1
793   ,p_parent_key_value1  =>   p_parent_key_value1
794   ,p_parent_table_name2 =>   p_parent_table_name2
795   ,p_parent_key_column2 =>   p_parent_key_column2
796   ,p_parent_key_value2  =>   p_parent_key_value2
797   ,p_parent_table_name3 =>   p_parent_table_name3
798   ,p_parent_key_column3 =>   p_parent_key_column3
799   ,p_parent_key_value3  =>   p_parent_key_value3
800   ,p_parent_table_name4 =>   p_parent_table_name4
801   ,p_parent_key_column4 =>   p_parent_key_column4
802   ,p_parent_key_value4  =>   p_parent_key_value4
803   ,p_parent_table_name5 =>   p_parent_table_name5
804   ,p_parent_key_column5 =>   p_parent_key_column5
805   ,p_parent_key_value5  =>   p_parent_key_value5
806   ,p_parent_table_name6 =>   p_parent_table_name6
807   ,p_parent_key_column6 =>   p_parent_key_column6
808   ,p_parent_key_value6  =>   p_parent_key_value6
809   ,p_parent_table_name7 =>   p_parent_table_name7
810   ,p_parent_key_column7 =>   p_parent_key_column7
811   ,p_parent_key_value7  =>   p_parent_key_value7
812   ,p_parent_table_name8 =>   p_parent_table_name8
813   ,p_parent_key_column8 =>   p_parent_key_column8
814   ,p_parent_key_value8  =>   p_parent_key_value8
815   ,p_parent_table_name9 =>   p_parent_table_name9
816   ,p_parent_key_column9 =>   p_parent_key_column9
817   ,p_parent_key_value9  =>   p_parent_key_value9
818   ,p_parent_table_name10 =>  p_parent_table_name10
819   ,p_parent_key_column10 =>  p_parent_key_column10
820   ,p_parent_key_value10  =>  p_parent_key_value10
821   ,p_zap                 =>  p_zap
822   ,p_delete              =>  p_delete
826   ,p_zap_end_date        =>  l_zap_end_date
823   ,p_future_change       =>  p_future_change
824   ,p_delete_next_change  =>  p_delete_next_change
825   ,p_zap_start_date      =>  l_zap_start_date
827   ,p_delete_start_date   =>  l_delete_start_date
828   ,p_delete_end_date     =>  l_delete_end_date
829   ,p_del_future_start_date   =>  l_del_future_start_date
830   ,p_del_future_end_date     =>  l_del_future_end_date
831   ,p_del_next_start_date  =>  l_del_next_start_date
832   ,p_del_next_end_date    =>  l_del_next_end_date
833   );
834 
835   IF g_debug THEN
836     Hr_Utility.Set_Location('Leaving :'||l_proc, 25);
837   END IF;
838 EXCEPTION
839   WHEN OTHERS THEN
840     p_zap                := NULL;
841     p_delete             := NULL;
842     p_future_change      := NULL;
843     p_delete_next_change := NULL;
844     RAISE;
845 END Find_Dt_Del_Modes;
846 -- ----------------------------------------------------------------------------
847 -- |-------------------------< Get_Insert_Dates >-----------------------------|
848 -- ----------------------------------------------------------------------------
849 --
850 -- PRIVATE
851 --
852 -- Description: Locks and parental entity rows (if supplied) and Returns
853 --              the validation start and end dates for the DateTrack
854 --              INSERT mode
855 --
856 -- ----------------------------------------------------------------------------
857 PROCEDURE Get_Insert_Dates
858           (p_effective_date          IN   DATE,
859            p_base_table_name         IN   VARCHAR2,
860            p_base_key_column         IN   VARCHAR2,
861            p_base_key_value          IN   NUMBER,
862            p_parent_table_name1      IN   VARCHAR2,
863            p_parent_key_column1      IN   VARCHAR2,
864            p_parent_key_value1       IN   NUMBER,
865            p_parent_table_name2      IN   VARCHAR2,
866            p_parent_key_column2      IN   VARCHAR2,
867            p_parent_key_value2       IN   NUMBER,
868            p_parent_table_name3      IN   VARCHAR2,
869            p_parent_key_column3      IN   VARCHAR2,
870            p_parent_key_value3       IN   NUMBER,
871            p_parent_table_name4      IN   VARCHAR2,
872            p_parent_key_column4      IN   VARCHAR2,
873            p_parent_key_value4       IN   NUMBER,
874            p_parent_table_name5      IN   VARCHAR2,
875            p_parent_key_column5      IN   VARCHAR2,
876            p_parent_key_value5       IN   NUMBER,
877            p_parent_table_name6      IN   VARCHAR2,
878            p_parent_key_column6      IN   VARCHAR2,
879            p_parent_key_value6       IN   NUMBER,
880            p_parent_table_name7      IN   VARCHAR2,
881            p_parent_key_column7      IN   VARCHAR2,
882            p_parent_key_value7       IN   NUMBER,
883            p_parent_table_name8      IN   VARCHAR2,
884            p_parent_key_column8      IN   VARCHAR2,
885            p_parent_key_value8       IN   NUMBER,
886            p_parent_table_name9      IN   VARCHAR2,
887            p_parent_key_column9      IN   VARCHAR2,
888            p_parent_key_value9       IN   NUMBER,
889            p_parent_table_name10     IN   VARCHAR2,
890            p_parent_key_column10     IN   VARCHAR2,
891            p_parent_key_value10      IN   NUMBER,
892            p_enforce_foreign_locking IN   BOOLEAN,
893            p_validation_start_date   OUT  NOCOPY DATE,
894            p_validation_end_date     OUT  NOCOPY DATE) IS
895 --
896   l_proc VARCHAR2(72);
897 --
898 BEGIN
899   IF g_debug THEN
900     l_proc := g_package||'Get_Insert_Dates';
901     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
902   END IF;
903   -- set the returning validation start and end dates
904   p_validation_start_date := p_effective_date;
905   p_validation_end_date   :=
906     return_parent_min_date
907       (p_effective_date => p_effective_date,
908        p_lock_rows    => p_enforce_foreign_locking,
909        p_table_name1  => p_parent_table_name1,
910        p_key_column1  => p_parent_key_column1,
911        p_key_value1   => p_parent_key_value1,
912        p_table_name2  => p_parent_table_name2,
913        p_key_column2  => p_parent_key_column2,
914        p_key_value2   => p_parent_key_value2,
915        p_table_name3  => p_parent_table_name3,
916        p_key_column3  => p_parent_key_column3,
917        p_key_value3   => p_parent_key_value3,
918        p_table_name4  => p_parent_table_name4,
919        p_key_column4  => p_parent_key_column4,
920        p_key_value4   => p_parent_key_value4,
921        p_table_name5  => p_parent_table_name5,
922        p_key_column5  => p_parent_key_column5,
923        p_key_value5   => p_parent_key_value5,
924        p_table_name6  => p_parent_table_name6,
925        p_key_column6  => p_parent_key_column6,
926        p_key_value6   => p_parent_key_value6,
927        p_table_name7  => p_parent_table_name7,
928        p_key_column7  => p_parent_key_column7,
929        p_key_value7   => p_parent_key_value7,
930        p_table_name8  => p_parent_table_name8,
931        p_key_column8  => p_parent_key_column8,
932        p_key_value8   => p_parent_key_value8,
933        p_table_name9  => p_parent_table_name9,
934        p_key_column9  => p_parent_key_column9,
935        p_key_value9   => p_parent_key_value9,
936        p_table_name10 => p_parent_table_name10,
937        p_key_column10 => p_parent_key_column10,
938        p_key_value10  => p_parent_key_value10);
939   IF g_debug THEN
943   WHEN OTHERS THEN
940     Hr_Utility.Set_Location('Leaving :'||l_proc, 20);
941   END IF;
942 EXCEPTION
944     -- reset the OUT params to NULL to cater for NOCOPY
945     p_validation_start_date := NULL;
946     p_validation_end_date := NULL;
947     RAISE;
948 END Get_Insert_Dates;
949 -- ----------------------------------------------------------------------------
950 -- |-----------------------< Get_Correction_Dates >---------------------------|
951 -- ----------------------------------------------------------------------------
952 --
953 -- PRIVATE
954 --
955 -- Description: Returns the validation start and end dates for the
956 --              DateTrack CORRECTION mode.
957 --
958 -- ----------------------------------------------------------------------------
959 PROCEDURE Get_Correction_Dates
960          (p_effective_date        IN     DATE,
961           p_base_table_name       IN     VARCHAR2,
962           p_base_key_column       IN     VARCHAR2,
963           p_base_key_value        IN     NUMBER,
964           p_validation_start_date    OUT NOCOPY DATE,
965           p_validation_end_date      OUT NOCOPY DATE) IS
966   --
967   l_proc VARCHAR2(72);
968   --
969 BEGIN
970   IF g_debug THEN
971     l_proc := g_package||'Get_Correction_Dates';
972     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
973   END IF;
974   -- Define dynamic sql text with substitution tokens
975   g_dynamic_sql :=
976     'SELECT t.effective_start_date,t.effective_end_date '||
977     'FROM '||LOWER(p_base_table_name)||' t '||
978     'WHERE t.'||LOWER(p_base_key_column)||' = :p_base_key_value '||
979     'AND :p_effective_date '||
980     'BETWEEN t.effective_start_date AND t.effective_end_date';
981   -- set the dynamic SQL comment for identification
982   dt_api.g_dynamic_sql :=
983     dt_api.g_dynamic_sql||
984     REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','get_correction_dates');
985   -- native dynamic PL/SQL call placing result directly into
986   -- OUT params
987   EXECUTE IMMEDIATE g_dynamic_sql
988   INTO    p_validation_start_date
989          ,p_validation_end_date
990   USING   p_base_key_value
991          ,p_effective_date;
992   IF g_debug THEN
993     hr_utility.set_location('Leaving :'||l_proc, 10);
994   END IF;
995 EXCEPTION
996   WHEN NO_DATA_FOUND THEN
997     -- reset the OUT params to NULL to cater for NOCOPY
998     p_validation_start_date := NULL;
999     p_validation_end_date := NULL;
1000     -- As no rows were returned we must error
1001     hr_utility.set_message(801, 'HR_7180_DT_NO_ROW_EXIST');
1002     hr_utility.set_message_token('TABLE_NAME', p_base_table_name);
1003     hr_utility.set_message_token
1004       ('SESSION_DATE'
1005       ,fnd_date.date_to_chardate(p_effective_date)
1006       );
1007     hr_utility.raise_error;
1008   WHEN TOO_MANY_ROWS THEN
1009     -- reset the OUT params to NULL to cater for NOCOPY
1010     p_validation_start_date := NULL;
1011     p_validation_end_date := NULL;
1012     hr_utility.set_message(801, 'HR_7181_DT_OVERLAP_ROWS');
1013     hr_utility.set_message_token('TABLE_NAME', p_base_table_name);
1014     hr_utility.set_message_token
1015       ('SESSION_DATE'
1016       ,fnd_date.date_to_chardate(p_effective_date)
1017       );
1018     hr_utility.set_message_token('PRIMARY_VALUE', to_char(p_base_key_value));
1019     hr_utility.raise_error;
1020   WHEN OTHERS THEN
1021     -- reset the OUT params to NULL to cater for NOCOPY
1022     p_validation_start_date := NULL;
1023     p_validation_end_date := NULL;
1024     RAISE;
1025 END Get_Correction_Dates;
1026 -- ----------------------------------------------------------------------------
1027 -- |--------------------------< Get_Update_Dates >----------------------------|
1028 -- ----------------------------------------------------------------------------
1029 --
1030 -- PRIVATE
1031 --
1032 -- Description: Returns the validation start and end dates for the
1033 --              DateTrack UPDATE mode if allowed.
1034 --
1035 -- ----------------------------------------------------------------------------
1036 PROCEDURE Get_Update_Dates
1037          (p_effective_date         IN  DATE,
1038           p_base_table_name        IN  VARCHAR2,
1039           p_base_key_column        IN  VARCHAR2,
1040           p_base_key_value         IN  NUMBER,
1041           p_validation_start_date  OUT NOCOPY DATE,
1042           p_validation_end_date    OUT NOCOPY DATE) IS
1043   --
1044   l_proc                  VARCHAR2(72);
1045   l_effective_rows        g_dt_effective_rows_tab;
1046   l_date_from_row_idx     BINARY_INTEGER;
1047   --
1048 BEGIN
1049   IF g_debug THEN
1050     l_proc := g_package||'Get_Update_Dates';
1051     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1052   END IF;
1053   -- get the effective rows
1054   get_effective_rows
1055     (p_date_from         => p_effective_date,
1056      p_base_table_name   => p_base_table_name,
1057      p_base_key_column   => p_base_key_column,
1058      p_base_key_value    => p_base_key_value,
1059      p_lock_rows         => FALSE,
1060      p_date_from_valid   => TRUE,
1061      p_effective_rows    => l_effective_rows,
1062      p_date_from_row_idx => l_date_from_row_idx);
1063   -- check to ensure that no future rows exist
1064   IF l_effective_rows.COUNT > l_date_from_row_idx THEN
1065     -- future rows exist so error
1066     hr_utility.set_message(801, 'HR_7211_DT_UPD_ROWS_IN_FUTURE');
1067     hr_utility.raise_error;
1071     -- date we must return the the validation start and end dates
1068   ELSE
1069     -- future rows do no exist
1070     -- providing the current effective start date is not equal to the effective
1072     IF (l_effective_rows(l_date_from_row_idx).effective_start_date <>
1073         p_effective_date) THEN
1074       p_validation_start_date := p_effective_date;
1075       p_validation_end_date   :=
1076         l_effective_rows(l_date_from_row_idx).effective_end_date;
1077     ELSE
1078       -- we cannot perform a DateTrack update operation where the effective
1079       -- date is the same as the current effective end date
1080       hr_utility.set_message(801, 'HR_7179_DT_UPD_NOT_ALLOWED');
1081       hr_utility.raise_error;
1082     END IF;
1083   END IF;
1084   IF g_debug THEN
1085     Hr_Utility.Set_Location('Leaving :'||l_proc, 10);
1086   END IF;
1087 EXCEPTION
1088   WHEN OTHERS THEN
1089     -- reset the OUT params to NULL to cater for NOCOPY
1090     p_validation_start_date := NULL;
1091     p_validation_end_date := NULL;
1092     RAISE;
1093 END Get_Update_Dates;
1094 -- ----------------------------------------------------------------------------
1095 -- |-------------------< Get_Update_Override_Dates >--------------------------|
1096 -- ----------------------------------------------------------------------------
1097 --
1098 -- PRIVATE
1099 --
1100 -- Description: Returns the validation start and end dates for the
1101 --              DateTrack UPDATE_OVERRIDE mode if allowed.
1102 --
1103 -- ----------------------------------------------------------------------------
1104 PROCEDURE Get_Update_Override_Dates
1105          (p_effective_date         IN  DATE,
1106           p_base_table_name        IN  VARCHAR2,
1107           p_base_key_column        IN  VARCHAR2,
1108           p_base_key_value         IN  NUMBER,
1109           p_validation_start_date  OUT NOCOPY DATE,
1110           p_validation_end_date    OUT NOCOPY DATE) IS
1111   --
1112   l_proc               VARCHAR2(72);
1113   l_effective_rows     g_dt_effective_rows_tab;
1114   l_date_from_row_idx  BINARY_INTEGER;
1115   --
1116 Begin
1117   IF g_debug THEN
1118     l_proc := g_package||'Get_Update_Override_Dates';
1119     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1120   END IF;
1121   -- get and lock the effective rows
1122   get_effective_rows
1123     (p_date_from         => p_effective_date,
1124      p_base_table_name   => p_base_table_name,
1125      p_base_key_column   => p_base_key_column,
1126      p_base_key_value    => p_base_key_value,
1127      p_lock_rows         => TRUE,
1128      p_date_from_valid   => TRUE,
1129      p_effective_rows    => l_effective_rows,
1130      p_date_from_row_idx => l_date_from_row_idx);
1131   -- if the current effective start date is not the same as the effective date
1132   -- and at least one future row exists then we must return the validation
1133   -- start and end dates
1134   IF (l_effective_rows(l_date_from_row_idx).effective_start_date <>
1135       p_effective_date) THEN
1136     -- as the current row does not start on the effective date we determine if
1137     -- any future rows exist
1138     IF l_effective_rows.COUNT > l_date_from_row_idx THEN
1139       p_validation_start_date := p_effective_date;
1140       p_validation_end_date   :=
1141         l_effective_rows(l_effective_rows.LAST).effective_end_date;
1142     ELSE
1143       hr_utility.set_message(801, 'HR_7183_DT_NO_FUTURE_ROWS');
1144       hr_utility.set_message_token('DT_MODE', 'update override');
1145       hr_utility.raise_error;
1146     END IF;
1147   ELSE
1148     hr_utility.set_message(801, 'HR_7179_DT_UPD_NOT_ALLOWED');
1149     hr_utility.raise_error;
1150   END IF;
1151   IF g_debug THEN
1152     Hr_Utility.Set_Location('Leaving :'||l_proc, 20);
1153   END IF;
1154 EXCEPTION
1155   WHEN OTHERS THEN
1156     -- reset the OUT params to NULL to cater for NOCOPY
1157     p_validation_start_date := NULL;
1158     p_validation_end_date := NULL;
1159     RAISE;
1160 END Get_Update_Override_Dates;
1161 -- ----------------------------------------------------------------------------
1162 -- |-----------------< Get_Update_Change_Insert_Dates >-----------------------|
1163 -- ----------------------------------------------------------------------------
1164 --
1165 -- PRIVATE
1166 --
1167 -- Description: Returns the validation start and end dates for the
1168 --              DateTrack UPDATE_CHANGE_INSERT mode if allowed.
1169 --
1170 -- ----------------------------------------------------------------------------
1171 PROCEDURE Get_Update_Change_Insert_Dates
1172          (p_effective_date         IN  DATE,
1173           p_base_table_name        IN  VARCHAR2,
1174           p_base_key_column        IN  VARCHAR2,
1175           p_base_key_value         IN  NUMBER,
1176           p_validation_start_date  OUT NOCOPY DATE,
1177           p_validation_end_date    OUT NOCOPY DATE) IS
1178   --
1179   l_proc                  VARCHAR2(72);
1180   l_effective_rows        g_dt_effective_rows_tab;
1181   l_date_from_row_idx     BINARY_INTEGER;
1182   --
1183 BEGIN
1184   IF g_debug THEN
1185     l_proc := g_package||'Get_Update_Change_Insert_Dates';
1186     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1187   END IF;
1188   -- get the effective rows
1189   get_effective_rows
1190     (p_date_from         => p_effective_date,
1191      p_base_table_name   => p_base_table_name,
1192      p_base_key_column   => p_base_key_column,
1193      p_base_key_value    => p_base_key_value,
1197      p_date_from_row_idx => l_date_from_row_idx);
1194      p_lock_rows         => FALSE,
1195      p_date_from_valid   => TRUE,
1196      p_effective_rows    => l_effective_rows,
1198   -- if the current effective start date is not the same as the effective date
1199   -- and at least one future row exists then we must return the validation
1200   -- start and end dates
1201   IF (l_effective_rows(l_date_from_row_idx).effective_start_date <>
1202       p_effective_date) THEN
1203     -- as the current row does not start on the effective date we determine if
1204     -- any future rows exist
1205     IF l_effective_rows.COUNT > l_date_from_row_idx THEN
1206       p_validation_start_date := p_effective_date;
1207       p_validation_end_date   :=
1208         l_effective_rows(l_date_from_row_idx).effective_end_date;
1209     ELSE
1210       hr_utility.set_message(801, 'HR_7183_DT_NO_FUTURE_ROWS');
1211       hr_utility.set_message_token('DT_MODE', 'update change insert');
1212       hr_utility.raise_error;
1213     END IF;
1214   ELSE
1215     hr_utility.set_message(801, 'HR_7179_DT_UPD_NOT_ALLOWED');
1216     hr_utility.raise_error;
1217   END IF;
1218   IF g_debug THEN
1219     Hr_Utility.Set_Location('Leaving :'||l_proc, 20);
1220   END IF;
1221 EXCEPTION
1222   WHEN OTHERS THEN
1223     -- reset the OUT params to NULL to cater for NOCOPY
1224     p_validation_start_date := NULL;
1225     p_validation_end_date := NULL;
1226     RAISE;
1227 END Get_Update_Change_Insert_Dates;
1228 -- ----------------------------------------------------------------------------
1229 -- |----------------------------< Get_Zap_Dates >-----------------------------|
1230 -- ----------------------------------------------------------------------------
1231 --
1232 -- PRIVATE
1233 --
1234 -- Description: Returns the validation start and end dates for the
1235 --              DateTrack ZAP mode.
1236 --
1237 -- ----------------------------------------------------------------------------
1238 Procedure Get_Zap_Dates
1239          (p_effective_date        IN  DATE,
1240           p_base_table_name       IN  VARCHAR2,
1241           p_base_key_column       IN  VARCHAR2,
1242           p_base_key_value        IN  NUMBER,
1243           p_validation_start_date OUT NOCOPY DATE,
1244           p_validation_end_date   OUT NOCOPY DATE) IS
1245 --
1246   l_proc                  VARCHAR2(72);
1247   l_effective_rows        g_dt_effective_rows_tab;
1248   l_date_from_row_idx     BINARY_INTEGER;
1249 --
1250 BEGIN
1251   IF g_debug THEN
1252     l_proc := g_package||'Get_Zap_Dates';
1253     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1254   END IF;
1255   -- get and lock the effective rows from the start of time
1256   get_effective_rows
1257     (p_date_from         => dt_api.g_sot,
1258      p_base_table_name   => p_base_table_name,
1259      p_base_key_column   => p_base_key_column,
1260      p_base_key_value    => p_base_key_value,
1261      p_lock_rows         => TRUE,
1262      p_date_from_valid   => FALSE,
1263      p_effective_rows    => l_effective_rows,
1264      p_date_from_row_idx => l_date_from_row_idx);
1265   -- at least one row will exist otherwise the get_effective_rows would of
1266   -- raised an error therefore just set the p_validation_start_date and
1267   -- p_validation_end_date OUT parameters
1268   p_validation_start_date :=
1269     l_effective_rows(l_effective_rows.FIRST).effective_start_date;
1270   p_validation_end_date :=
1271     l_effective_rows(l_effective_rows.LAST).effective_end_date;
1272   IF g_debug THEN
1273     Hr_Utility.Set_Location('Leaving :'||l_proc, 20);
1274   END IF;
1275 EXCEPTION
1276   WHEN OTHERS THEN
1277     -- reset the OUT params to NULL to cater for NOCOPY
1278     p_validation_start_date := NULL;
1279     p_validation_end_date := NULL;
1280     RAISE;
1281 END Get_Zap_Dates;
1282 -- ----------------------------------------------------------------------------
1283 -- |--------------------------< Get_Delete_Dates >----------------------------|
1284 -- ----------------------------------------------------------------------------
1285 --
1286 -- PRIVATE
1287 --
1288 -- Description: Returns the validation start and end dates for the
1289 --              DateTrack DELETE mode if allowed.
1290 --
1291 -- ----------------------------------------------------------------------------
1292 PROCEDURE Get_Delete_Dates
1293          (p_effective_date              IN  DATE,
1294           p_base_table_name             IN  VARCHAR2,
1295           p_base_key_column             IN  VARCHAR2,
1296           p_base_key_value              IN  NUMBER,
1297           p_child_table_name1           IN  VARCHAR2,
1298           p_child_key_column1           IN  VARCHAR2,
1299           p_child_table_name2           IN  VARCHAR2,
1300           p_child_key_column2           IN  VARCHAR2,
1301           p_child_table_name3           IN  VARCHAR2,
1302           p_child_key_column3           IN  VARCHAR2,
1303           p_child_table_name4           IN  VARCHAR2,
1304           p_child_key_column4           IN  VARCHAR2,
1305           p_child_table_name5           IN  VARCHAR2,
1306           p_child_key_column5           IN  VARCHAR2,
1307           p_child_table_name6           IN  VARCHAR2,
1308           p_child_key_column6           IN  VARCHAR2,
1309           p_child_table_name7           IN  VARCHAR2,
1310           p_child_key_column7           IN  VARCHAR2,
1311           p_child_table_name8           IN  VARCHAR2,
1312           p_child_key_column8           IN  VARCHAR2,
1316           p_child_key_column10          IN  VARCHAR2,
1313           p_child_table_name9           IN  VARCHAR2,
1314           p_child_key_column9           IN  VARCHAR2,
1315           p_child_table_name10          IN  VARCHAR2,
1317           p_child_alt_base_key_column1  IN  VARCHAR2,
1318           p_child_alt_base_key_column2  IN  VARCHAR2,
1319           p_child_alt_base_key_column3  IN  VARCHAR2,
1320           p_child_alt_base_key_column4  IN  VARCHAR2,
1321           p_child_alt_base_key_column5  IN  VARCHAR2,
1322           p_child_alt_base_key_column6  IN  VARCHAR2,
1323           p_child_alt_base_key_column7  IN  VARCHAR2,
1324           p_child_alt_base_key_column8  IN  VARCHAR2,
1325           p_child_alt_base_key_column9  IN  VARCHAR2,
1326           p_child_alt_base_key_column10 IN  VARCHAR2,
1327           p_enforce_foreign_locking     IN  BOOLEAN,
1328           p_validation_start_date       OUT NOCOPY DATE,
1329           p_validation_end_date         OUT NOCOPY DATE) IS
1330   --
1331   l_proc                      VARCHAR2(72);
1332   l_effective_date_plus_one   CONSTANT DATE := p_effective_date + 1;
1333   l_child_table_name          VARCHAR2(30);
1334   l_child_key_column          VARCHAR2(30);
1335   l_child_alt_base_key_column VARCHAR2(30);
1336   l_effective_rows            g_dt_effective_rows_tab;
1337   l_date_from_row_idx         BINARY_INTEGER;
1338   --
1339 BEGIN
1340   IF g_debug THEN
1341     l_proc := g_package||'Get_Delete_Dates';
1342     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1343   END IF;
1344   -- get and lock the effective rows
1345   get_effective_rows
1346     (p_date_from         => p_effective_date,
1347      p_base_table_name   => p_base_table_name,
1348      p_base_key_column   => p_base_key_column,
1349      p_base_key_value    => p_base_key_value,
1350      p_lock_rows         => TRUE,
1351      p_date_from_valid   => TRUE,
1352      p_effective_rows    => l_effective_rows,
1353      p_date_from_row_idx => l_date_from_row_idx);
1354   -- lock child records if p_enforce_foreign_locking is specified
1355   IF p_enforce_foreign_locking THEN
1356     FOR l_counter IN 1..10 LOOP
1357       -- Set the current working arguments to the corresponding functional
1358       -- argument values
1359       If    (l_counter = 1) THEN
1360         l_child_table_name := p_child_table_name1;
1361         l_child_key_column := p_child_key_column1;
1362         l_child_alt_base_key_column := p_child_alt_base_key_column1;
1363       ELSIF (l_counter = 2) THEN
1364         l_child_table_name := p_child_table_name2;
1365         l_child_key_column := p_child_key_column2;
1366         l_child_alt_base_key_column := p_child_alt_base_key_column2;
1367       ELSIF (l_counter = 3) THEN
1368         l_child_table_name := p_child_table_name3;
1369         l_child_key_column := p_child_key_column3;
1370         l_child_alt_base_key_column := p_child_alt_base_key_column3;
1371       ELSIF (l_counter = 4) THEN
1372         l_child_table_name := p_child_table_name4;
1373         l_child_key_column := p_child_key_column4;
1374         l_child_alt_base_key_column := p_child_alt_base_key_column4;
1375       ELSIF (l_counter = 5) THEN
1376         l_child_table_name := p_child_table_name5;
1377         l_child_key_column := p_child_key_column5;
1378         l_child_alt_base_key_column := p_child_alt_base_key_column5;
1379       ELSIF (l_counter = 6) THEN
1380         l_child_table_name := p_child_table_name6;
1381         l_child_key_column := p_child_key_column6;
1382         l_child_alt_base_key_column := p_child_alt_base_key_column6;
1383       ELSIF (l_counter = 7) THEN
1384         l_child_table_name := p_child_table_name7;
1385         l_child_key_column := p_child_key_column7;
1386         l_child_alt_base_key_column := p_child_alt_base_key_column7;
1387       ELSIF (l_counter = 8) THEN
1388         l_child_table_name := p_child_table_name8;
1389         l_child_key_column := p_child_key_column8;
1390         l_child_alt_base_key_column := p_child_alt_base_key_column8;
1391       ELSIF (l_counter = 9) THEN
1392         l_child_table_name := p_child_table_name9;
1393         l_child_key_column := p_child_key_column9;
1394         l_child_alt_base_key_column := p_child_alt_base_key_column9;
1395       ELSE
1396         l_child_table_name := p_child_table_name10;
1397         l_child_key_column := p_child_key_column10;
1398         l_child_alt_base_key_column := p_child_alt_base_key_column10;
1399       END IF;
1400       -- ensure that all the working child details have been specified
1401       IF ((p_base_key_value IS NOT NULL) AND NOT
1402          ((NVL(l_child_table_name, dt_api.g_varchar2) =
1403                dt_api.g_varchar2) OR
1404               (NVL(l_child_key_column, dt_api.g_varchar2) =
1405                dt_api.g_varchar2))) THEN
1406         -- all the child arguments have been specified therefore we must lock
1407         -- the child rows (if they exist).
1408         Lck_Child
1409           (p_child_table_name      => LOWER(l_child_table_name),
1410            p_child_key_column      => LOWER(l_child_key_column),
1411            p_parent_key_column     => NVL(LOWER(l_child_alt_base_key_column),
1412                                           LOWER(p_base_key_column)),
1413            p_parent_key_value      => p_base_key_value,
1414            p_validation_start_date => l_effective_date_plus_one);
1415       END IF;
1416     END LOOP;
1417   END IF;
1418   -- Providing the maximum effective end date is not the same as the current
1419   -- effective date then we must return the validation start and end dates.
1423       l_effective_rows(l_effective_rows.LAST).effective_end_date) THEN
1420   -- However, if you attempt to do a datetrack delete where the session date is
1421   -- the same as your maximum date then we must error.
1422   IF (p_effective_date <>
1424     p_validation_start_date := l_effective_date_plus_one;
1425     p_validation_end_date   :=
1426       l_effective_rows(l_effective_rows.LAST).effective_end_date;
1427   ELSE
1428     -- We cannot perform a DateTrack delete operation where the effective date
1429     -- is the same as the maximum effective end date.
1430     hr_utility.set_message(801, 'HR_7185_DT_DEL_NOT_ALLOWED');
1431     hr_utility.raise_error;
1432   END IF;
1433   IF g_debug THEN
1434     Hr_Utility.Set_Location('Leaving :'||l_proc, 10);
1435   END IF;
1436 EXCEPTION
1437   WHEN OTHERS THEN
1438     -- reset the OUT params to NULL to cater for NOCOPY
1439     p_validation_start_date := NULL;
1440     p_validation_end_date := NULL;
1441     RAISE;
1442 END Get_Delete_Dates;
1443 -- ----------------------------------------------------------------------------
1444 -- |-----------------------< Get_Future_Change_Dates >------------------------|
1445 -- ----------------------------------------------------------------------------
1446 --
1447 -- PRIVATE
1448 --
1449 -- Description: Returns the validation start and end dates for the
1450 --              DateTrack FUTURE_CHANGE mode if allowed.
1451 --
1452 -- ----------------------------------------------------------------------------
1453 PROCEDURE Get_Future_Change_Dates
1454          (p_effective_date        IN  DATE,
1455           p_base_table_name       IN  VARCHAR2,
1456           p_base_key_column       IN  VARCHAR2,
1457           p_base_key_value        IN  NUMBER,
1458           p_parent_table_name1    IN  VARCHAR2,
1459           p_parent_key_column1    IN  VARCHAR2,
1460           p_parent_key_value1     IN  NUMBER,
1461           p_parent_table_name2    IN  VARCHAR2,
1462           p_parent_key_column2    IN  VARCHAR2,
1463           p_parent_key_value2     IN  NUMBER,
1464           p_parent_table_name3    IN  VARCHAR2,
1465           p_parent_key_column3    IN  VARCHAR2,
1466           p_parent_key_value3     IN  NUMBER,
1467           p_parent_table_name4    IN  VARCHAR2,
1468           p_parent_key_column4    IN  VARCHAR2,
1469           p_parent_key_value4     IN  NUMBER,
1470           p_parent_table_name5    IN  VARCHAR2,
1471           p_parent_key_column5    IN  VARCHAR2,
1472           p_parent_key_value5     IN  NUMBER,
1473           p_parent_table_name6    IN  VARCHAR2,
1474           p_parent_key_column6    IN  VARCHAR2,
1475           p_parent_key_value6     IN  NUMBER,
1476           p_parent_table_name7    IN  VARCHAR2,
1477           p_parent_key_column7    IN  VARCHAR2,
1478           p_parent_key_value7     IN  NUMBER,
1479           p_parent_table_name8    IN  VARCHAR2,
1480           p_parent_key_column8    IN  VARCHAR2,
1481           p_parent_key_value8     IN  NUMBER,
1482           p_parent_table_name9    IN  VARCHAR2,
1483           p_parent_key_column9    IN  VARCHAR2,
1484           p_parent_key_value9     IN  NUMBER,
1485           p_parent_table_name10   IN  VARCHAR2,
1486           p_parent_key_column10   IN  VARCHAR2,
1487           p_parent_key_value10    IN  NUMBER,
1488           p_validation_start_date OUT NOCOPY DATE,
1489           p_validation_end_date   OUT NOCOPY DATE) IS
1490   --
1491   l_proc                  VARCHAR2(72);
1492   l_validation_end_date   DATE;
1493   l_effective_rows        g_dt_effective_rows_tab;
1494   l_date_from_row_idx     BINARY_INTEGER;
1495   --
1496 BEGIN
1497   IF g_debug THEN
1498     l_proc := g_package||'Get_Future_Change_Dates';
1499     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1500   END IF;
1501   -- get and lock the effective rows
1502   get_effective_rows
1503     (p_date_from         => p_effective_date,
1504      p_base_table_name   => p_base_table_name,
1505      p_base_key_column   => p_base_key_column,
1506      p_base_key_value    => p_base_key_value,
1507      p_lock_rows         => TRUE,
1508      p_date_from_valid   => TRUE,
1509      p_effective_rows    => l_effective_rows,
1510      p_date_from_row_idx => l_date_from_row_idx);
1511   -- Providing the current effective end date is not the end of time
1512   -- then we must set the validation dates
1513   IF (l_effective_rows(l_date_from_row_idx).effective_end_date <>
1514       dt_api.g_eot) THEN
1515     -- get the parent min end date
1516     l_validation_end_date :=
1517       return_parent_min_date
1518         (p_effective_date => p_effective_date,
1519          p_lock_rows    => FALSE,
1520          p_table_name1  => p_parent_table_name1,
1521          p_key_column1  => p_parent_key_column1,
1522          p_key_value1   => p_parent_key_value1,
1523          p_table_name2  => p_parent_table_name2,
1524          p_key_column2  => p_parent_key_column2,
1525          p_key_value2   => p_parent_key_value2,
1526          p_table_name3  => p_parent_table_name3,
1527          p_key_column3  => p_parent_key_column3,
1528          p_key_value3   => p_parent_key_value3,
1529          p_table_name4  => p_parent_table_name4,
1530          p_key_column4  => p_parent_key_column4,
1531          p_key_value4   => p_parent_key_value4,
1532          p_table_name5  => p_parent_table_name5,
1533          p_key_column5  => p_parent_key_column5,
1534          p_key_value5   => p_parent_key_value5,
1535          p_table_name6  => p_parent_table_name6,
1536          p_key_column6  => p_parent_key_column6,
1537          p_key_value6   => p_parent_key_value6,
1541          p_table_name8  => p_parent_table_name8,
1538          p_table_name7  => p_parent_table_name7,
1539          p_key_column7  => p_parent_key_column7,
1540          p_key_value7   => p_parent_key_value7,
1542          p_key_column8  => p_parent_key_column8,
1543          p_key_value8   => p_parent_key_value8,
1544          p_table_name9  => p_parent_table_name9,
1545          p_key_column9  => p_parent_key_column9,
1546          p_key_value9   => p_parent_key_value9,
1547          p_table_name10 => p_parent_table_name10,
1548          p_key_column10 => p_parent_key_column10,
1549          p_key_value10  => p_parent_key_value10);
1550     -- If the validation end date is set to the current effective end date
1551     -- then we must error as we cannot extend the end date of the current
1552     -- row
1553     IF (l_validation_end_date <=
1554         l_effective_rows(l_date_from_row_idx).effective_end_date) THEN
1555       hr_utility.set_message(801, 'HR_7187_DT_CANNOT_EXTEND_END');
1556       hr_utility.set_message_token('DT_MODE', ' future changes');
1557       hr_utility.raise_error;
1558     ELSE
1559       -- set the validation_start/end_date OUT params
1560       p_validation_start_date :=
1561         l_effective_rows(l_date_from_row_idx).effective_end_date + 1;
1562       p_validation_end_date := l_validation_end_date;
1563     END IF;
1564   ELSE
1565     -- The current effective end date is alreay the end of time therefore
1566     -- we cannot extend the end date
1567     hr_utility.set_message(801, 'HR_7188_DT_DATE_IS_EOT');
1568     hr_utility.raise_error;
1569   END IF;
1570   IF g_debug THEN
1571     Hr_Utility.Set_Location(' Leaving:'||l_proc, 15);
1572   END IF;
1573 EXCEPTION
1574   WHEN OTHERS THEN
1575     -- reset the OUT params to NULL to cater for NOCOPY
1576     p_validation_start_date := NULL;
1577     p_validation_end_date := NULL;
1578     RAISE;
1579 END Get_Future_Change_Dates;
1580 -- ----------------------------------------------------------------------------
1581 -- |--------------------< Get_Delete_Next_Change_Dates >----------------------|
1582 -- ----------------------------------------------------------------------------
1583 --
1584 -- PRIVATE
1585 --
1586 -- Description: Returns the validation start and end dates for the
1587 --              DateTrack FUTURE_CHANGE mode if allowed.
1588 --
1589 -- ----------------------------------------------------------------------------
1590 PROCEDURE Get_Delete_Next_Change_Dates
1591          (p_effective_date        IN  DATE,
1592           p_base_table_name       IN  VARCHAR2,
1593           p_base_key_column       IN  VARCHAR2,
1594           p_base_key_value        IN  NUMBER,
1595           p_parent_table_name1    IN  VARCHAR2,
1596           p_parent_key_column1    IN  VARCHAR2,
1597           p_parent_key_value1     IN  NUMBER,
1598           p_parent_table_name2    IN  VARCHAR2,
1599           p_parent_key_column2    IN  VARCHAR2,
1600           p_parent_key_value2     IN  NUMBER,
1601           p_parent_table_name3    IN  VARCHAR2,
1602           p_parent_key_column3    IN  VARCHAR2,
1603           p_parent_key_value3     IN  NUMBER,
1604           p_parent_table_name4    IN  VARCHAR2,
1605           p_parent_key_column4    IN  VARCHAR2,
1606           p_parent_key_value4     IN  NUMBER,
1607           p_parent_table_name5    IN  VARCHAR2,
1608           p_parent_key_column5    IN  VARCHAR2,
1609           p_parent_key_value5     IN  NUMBER,
1610           p_parent_table_name6    IN  VARCHAR2,
1611           p_parent_key_column6    IN  VARCHAR2,
1612           p_parent_key_value6     IN  NUMBER,
1613           p_parent_table_name7    IN  VARCHAR2,
1614           p_parent_key_column7    IN  VARCHAR2,
1615           p_parent_key_value7     IN  NUMBER,
1616           p_parent_table_name8    IN  VARCHAR2,
1617           p_parent_key_column8    IN  VARCHAR2,
1618           p_parent_key_value8     IN  NUMBER,
1619           p_parent_table_name9    IN  VARCHAR2,
1620           p_parent_key_column9    IN  VARCHAR2,
1621           p_parent_key_value9     IN  NUMBER,
1622           p_parent_table_name10   IN  VARCHAR2,
1623           p_parent_key_column10   IN  VARCHAR2,
1624           p_parent_key_value10    IN  NUMBER,
1625           p_validation_start_date OUT NOCOPY DATE,
1626           p_validation_end_date   OUT NOCOPY DATE) IS
1627 --
1628   l_proc                        VARCHAR2(72);
1629   l_validation_end_date         DATE;
1630   l_future_effective_end_date   DATE;   -- Holds the end date of next row
1631   l_effective_rows              g_dt_effective_rows_tab;
1632   l_date_from_row_idx           BINARY_INTEGER;
1633   --
1634 Begin
1635   IF g_debug THEN
1636     l_proc := g_package||'Get_Delete_Next_Change_Dates';
1637     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1638   END IF;
1639   -- get and lock the effective rows
1640   get_effective_rows
1641     (p_date_from         => p_effective_date,
1642      p_base_table_name   => p_base_table_name,
1643      p_base_key_column   => p_base_key_column,
1644      p_base_key_value    => p_base_key_value,
1645      p_lock_rows         => TRUE,
1646      p_date_from_valid   => TRUE,
1647      p_effective_rows    => l_effective_rows,
1648      p_date_from_row_idx => l_date_from_row_idx);
1649   -- Providing the current effective end date is not the end of time
1650   -- then we must set the validation dates
1651   IF (l_effective_rows(l_date_from_row_idx).effective_end_date <>
1652       dt_api.g_eot) THEN
1653     -- check to see if future rows exist
1657       -- effective date
1654     IF l_effective_rows.COUNT > l_date_from_row_idx THEN
1655       -- future rows exist so set the future effective end date
1656       -- to the end date of the next datetrack row after the row for the
1658       l_future_effective_end_date :=
1659         l_effective_rows(l_date_from_row_idx + 1).effective_end_date;
1660     ELSE
1661       -- although the date should be NULL because it has not been set we'll set
1662       -- it anyway for readability and defensive style coding
1663       l_future_effective_end_date := NULL;
1664     END IF;
1665     -- To determine the validation end date we must take the minimum date
1666     -- from the following three possible dates:
1667     -- 1: Minimum parent entity entity end date
1668     -- 2: If future rows exist then the effective end date of the next row
1669     -- 3: If no future rows exist then the end of time
1670     l_validation_end_date :=
1671       LEAST
1672       (return_parent_min_date
1673         (p_effective_date => p_effective_date,
1674          p_lock_rows    => FALSE,
1675          p_table_name1  => p_parent_table_name1,
1676          p_key_column1  => p_parent_key_column1,
1677          p_key_value1   => p_parent_key_value1,
1678          p_table_name2  => p_parent_table_name2,
1679          p_key_column2  => p_parent_key_column2,
1680          p_key_value2   => p_parent_key_value2,
1681          p_table_name3  => p_parent_table_name3,
1682          p_key_column3  => p_parent_key_column3,
1683          p_key_value3   => p_parent_key_value3,
1684          p_table_name4  => p_parent_table_name4,
1685          p_key_column4  => p_parent_key_column4,
1686          p_key_value4   => p_parent_key_value4,
1687          p_table_name5  => p_parent_table_name5,
1688          p_key_column5  => p_parent_key_column5,
1689          p_key_value5   => p_parent_key_value5,
1690          p_table_name6  => p_parent_table_name6,
1691          p_key_column6  => p_parent_key_column6,
1692          p_key_value6   => p_parent_key_value6,
1693          p_table_name7  => p_parent_table_name7,
1694          p_key_column7  => p_parent_key_column7,
1695          p_key_value7   => p_parent_key_value7,
1696          p_table_name8  => p_parent_table_name8,
1697          p_key_column8  => p_parent_key_column8,
1698          p_key_value8   => p_parent_key_value8,
1699          p_table_name9  => p_parent_table_name9,
1700          p_key_column9  => p_parent_key_column9,
1701          p_key_value9   => p_parent_key_value9,
1702          p_table_name10 => p_parent_table_name10,
1703          p_key_column10 => p_parent_key_column10,
1704          p_key_value10  => p_parent_key_value10),
1705       NVL(l_future_effective_end_date,dt_api.g_eot));
1706     -- if the validation end date is set to the current effective end date
1707     -- then we must error as we cannot extend the end date of the current
1708     -- row
1709     IF (l_validation_end_date <=
1710         l_effective_rows(l_date_from_row_idx).effective_end_date) THEN
1711       hr_utility.set_message(801, 'HR_7187_DT_CANNOT_EXTEND_END');
1712       hr_utility.set_message_token('DT_MODE', ' delete next change');
1713       hr_utility.raise_error;
1714     ELSE
1715       -- set the OUT validation params
1716       -- set the validation start date to the current effective end date + 1
1717       p_validation_start_date :=
1718         l_effective_rows(l_date_from_row_idx).effective_end_date + 1;
1719       p_validation_end_date := l_validation_end_date;
1720     END IF;
1721   ELSE
1722     -- the current effective end date is alreay the end of time therefore
1723     -- we cannot extend the end date
1724     hr_utility.set_message(801, 'HR_7188_DT_DATE_IS_EOT');
1725     hr_utility.raise_error;
1726   END IF;
1727   IF g_debug THEN
1728     Hr_Utility.Set_Location(' Leaving:'||l_proc, 25);
1729   END IF;
1730 EXCEPTION
1731   WHEN OTHERS THEN
1732     -- reset the OUT params to NULL to cater for NOCOPY
1733     p_validation_start_date := NULL;
1734     p_validation_end_date := NULL;
1735     RAISE;
1736 END Get_Delete_Next_Change_Dates;
1737 -- ----------------------------------------------------------------------------
1738 -- |----------------------------< Validate_DT_Mode >--------------------------|
1739 -- ----------------------------------------------------------------------------
1740 --
1741 -- PUBLIC
1742 --
1743 -- Description: Validates and returns the validation start and end dates for
1744 --              the DateTrack mode provided.
1745 --              Locking is also enforced within this procedure.
1746 --              The argument p_enforce_foreign_locking determines if for the
1747 --              correct DT mode (INSERT or DELETE) parental or child
1748 --              foreign key entities should be locked. If this value if set to
1749 --              false this procedure will not perform any foreign lockng
1750 --              and it is expected to be handled by the calling process
1751 --              (this is useful if a different method of locking is required
1752 --              where the row  exclusive locking mechanisms is too
1753 --              restrictive).
1754 --
1755 --              Locking Processing:
1756 --
1757 --              1. Entity range row locking:
1758 --                 Mode                  Lock Comments
1759 --                 --------------        ---- ---------------------------------
1760 --                 INSERT                  N  No rows exists at this point
1761 --                 UPDATE                  N  Current row already locked
1762 --                 CORRECTION              N  Current row already locked
1766 --                 FUTURE_CHANGE           Y  Have to lock future rows
1763 --                 UPDATE_OVERRIDE         Y  Have to lock future rows
1764 --                 UPDATE_CHANGE_INSERT    N  Current row already locked
1765 --                 DELETE                  Y  Have to lock future rows
1767 --                 DELETE_NEXT_CHANGE      Y  Have to lock future rows
1768 --                                            We always lock all future rows
1769 --                                            too ensure consistency. This
1770 --                                            means that we may over-lock some
1771 --                                            future rows unnessarily.
1772 --                 ZAP                     Y  Have to lock all rows
1773 --
1774 --              2. Insert
1775 --                 Parental rows are locked provided the argument
1776 --                 p_enforce_foreign_locking has been set to TRUE.
1777 --
1778 --              3. Delete
1779 --                 Child rows are locked provided the argument
1780 --                 p_enforce_foreign_locking has been set to TRUE.
1781 --
1782 -- ----------------------------------------------------------------------------
1783 PROCEDURE Validate_DT_Mode
1784          (p_datetrack_mode              IN VARCHAR2,
1785           p_effective_date              IN DATE,
1786           p_base_table_name             IN VARCHAR2,
1787           p_base_key_column             IN VARCHAR2,
1788           p_base_key_value              IN NUMBER,
1789           p_parent_table_name1          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1790           p_parent_key_column1          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1791           p_parent_key_value1           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1792           p_parent_table_name2          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1793           p_parent_key_column2          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1794           p_parent_key_value2           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1795           p_parent_table_name3          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1796           p_parent_key_column3          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1797           p_parent_key_value3           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1798           p_parent_table_name4          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1799           p_parent_key_column4          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1800           p_parent_key_value4           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1801           p_parent_table_name5          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1802           p_parent_key_column5          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1803           p_parent_key_value5           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1804           p_parent_table_name6          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1805           p_parent_key_column6          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1806           p_parent_key_value6           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1807           p_parent_table_name7          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1808           p_parent_key_column7          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1809           p_parent_key_value7           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1810           p_parent_table_name8          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1811           p_parent_key_column8          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1812           p_parent_key_value8           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1813           p_parent_table_name9          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1814           p_parent_key_column9          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1815           p_parent_key_value9           IN NUMBER   DEFAULT HR_API.G_NUMBER,
1816           p_parent_table_name10         IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1817           p_parent_key_column10         IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1818           p_parent_key_value10          IN NUMBER   DEFAULT HR_API.G_NUMBER,
1819           p_child_table_name1           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1820           p_child_key_column1           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1821           p_child_table_name2           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1822           p_child_key_column2           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1823           p_child_table_name3           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1824           p_child_key_column3           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1825           p_child_table_name4           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1826           p_child_key_column4           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1827           p_child_table_name5           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1828           p_child_key_column5           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1829           p_child_table_name6           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1830           p_child_key_column6           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1831           p_child_table_name7           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1832           p_child_key_column7           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1833           p_child_table_name8           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1834           p_child_key_column8           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1835           p_child_table_name9           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1836           p_child_key_column9           IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1837           p_child_table_name10          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1838           p_child_key_column10          IN VARCHAR2 DEFAULT HR_API.G_VARCHAR2,
1839           p_child_alt_base_key_column1  IN VARCHAR2 DEFAULT NULL,
1840           p_child_alt_base_key_column2  IN VARCHAR2 DEFAULT NULL,
1841           p_child_alt_base_key_column3  IN VARCHAR2 DEFAULT NULL,
1842           p_child_alt_base_key_column4  IN VARCHAR2 DEFAULT NULL,
1846           p_child_alt_base_key_column8  IN VARCHAR2 DEFAULT NULL,
1843           p_child_alt_base_key_column5  IN VARCHAR2 DEFAULT NULL,
1844           p_child_alt_base_key_column6  IN VARCHAR2 DEFAULT NULL,
1845           p_child_alt_base_key_column7  IN VARCHAR2 DEFAULT NULL,
1847           p_child_alt_base_key_column9  IN VARCHAR2 DEFAULT NULL,
1848           p_child_alt_base_key_column10 IN VARCHAR2 DEFAULT NULL,
1849           p_enforce_foreign_locking     IN BOOLEAN  DEFAULT TRUE,
1850           p_validation_start_date       OUT NOCOPY  DATE,
1851           p_validation_end_date         OUT NOCOPY  DATE) IS
1852 --
1853   l_proc            VARCHAR2(72);
1854   l_datetrack_mode  VARCHAR2(30);
1855 --
1856 BEGIN
1857   g_debug := hr_utility.debug_enabled;
1858   IF g_debug THEN
1859     l_proc := g_package||'Validate_DT_Mode';
1860     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
1861   END IF;
1862   -- upper the datetrack mode
1863   l_datetrack_mode := upper(p_datetrack_mode);
1864   -- check the effective date
1865   Effective_Date_Valid(p_effective_date => p_effective_date);
1866   --
1867   -- Ensure that all the mandatory arguments are not null
1868   -- [ start of change 30.14 ]
1869   --
1870   IF p_datetrack_mode IS NULL OR p_base_table_name IS NULL OR
1871      p_base_key_column IS NULL THEN
1872     hr_api.mandatory_arg_error(p_api_name       => l_proc,
1873                                p_argument       => 'p_datetrack_mode',
1874                                p_argument_value => p_datetrack_mode);
1875     hr_api.mandatory_arg_error(p_api_name       => l_proc,
1876                                p_argument       => 'p_base_table_name',
1877                                p_argument_value => p_base_table_name);
1878     hr_api.mandatory_arg_error(p_api_name       => l_proc,
1879                                p_argument       => 'p_base_key_column',
1880                                p_argument_value => p_base_key_column);
1881   END IF;
1882   -- [ start of change 30.15 ]
1883   -- removed the hr_api.mandatory_arg_error for p_base_key_value
1884   -- [ end of change 30.15 ]
1885   -- [ end of change 30.14 ]
1886   --
1887   IF    (l_datetrack_mode = dt_api.g_insert) THEN
1888     --
1889     Get_Insert_Dates
1890       (p_effective_date          => p_effective_date,
1891        p_base_table_name         => p_base_table_name,
1892        p_base_key_column         => p_base_key_column,
1893        p_base_key_value          => p_base_key_value,
1894        p_parent_table_name1      => p_parent_table_name1,
1895        p_parent_key_column1      => p_parent_key_column1,
1896        p_parent_key_value1       => p_parent_key_value1,
1897        p_parent_table_name2      => p_parent_table_name2,
1898        p_parent_key_column2      => p_parent_key_column2,
1899        p_parent_key_value2       => p_parent_key_value2,
1900        p_parent_table_name3      => p_parent_table_name3,
1901        p_parent_key_column3      => p_parent_key_column3,
1902        p_parent_key_value3       => p_parent_key_value3,
1903        p_parent_table_name4      => p_parent_table_name4,
1904        p_parent_key_column4      => p_parent_key_column4,
1905        p_parent_key_value4       => p_parent_key_value4,
1906        p_parent_table_name5      => p_parent_table_name5,
1907        p_parent_key_column5      => p_parent_key_column5,
1908        p_parent_key_value5       => p_parent_key_value5,
1909        p_parent_table_name6      => p_parent_table_name6,
1910        p_parent_key_column6      => p_parent_key_column6,
1911        p_parent_key_value6       => p_parent_key_value6,
1912        p_parent_table_name7      => p_parent_table_name7,
1913        p_parent_key_column7      => p_parent_key_column7,
1914        p_parent_key_value7       => p_parent_key_value7,
1915        p_parent_table_name8      => p_parent_table_name8,
1916        p_parent_key_column8      => p_parent_key_column8,
1917        p_parent_key_value8       => p_parent_key_value8,
1918        p_parent_table_name9      => p_parent_table_name9,
1919        p_parent_key_column9      => p_parent_key_column9,
1920        p_parent_key_value9       => p_parent_key_value9,
1921        p_parent_table_name10     => p_parent_table_name10,
1922        p_parent_key_column10     => p_parent_key_column10,
1923        p_parent_key_value10      => p_parent_key_value10,
1924        p_enforce_foreign_locking => p_enforce_foreign_locking,
1925        p_validation_start_date   => p_validation_start_date,
1926        p_validation_end_date     => p_validation_end_date);
1927     --
1928   ELSIF (l_datetrack_mode = dt_api.g_correction) THEN
1929     --
1930     Get_Correction_Dates
1931       (p_effective_date        => p_effective_date,
1932        p_base_table_name       => p_base_table_name,
1933        p_base_key_column       => p_base_key_column,
1934        p_base_key_value        => p_base_key_value,
1935        p_validation_start_date => p_validation_start_date,
1936        p_validation_end_date   => p_validation_end_date);
1937     --
1938   ELSIF (l_datetrack_mode = dt_api.g_update) THEN
1939     --
1940     Get_Update_Dates
1941       (p_effective_date        => p_effective_date,
1942        p_base_table_name       => p_base_table_name,
1943        p_base_key_column       => p_base_key_column,
1944        p_base_key_value        => p_base_key_value,
1945        p_validation_start_date => p_validation_start_date,
1946        p_validation_end_date   => p_validation_end_date);
1947     --
1948   ELSIF (l_datetrack_mode = dt_api.g_zap) THEN
1949     --
1950     Get_Zap_Dates
1951       (p_effective_date        => p_effective_date,
1955        p_validation_start_date => p_validation_start_date,
1952        p_base_table_name       => p_base_table_name,
1953        p_base_key_column       => p_base_key_column,
1954        p_base_key_value        => p_base_key_value,
1956        p_validation_end_date   => p_validation_end_date);
1957     --
1958   ELSIF (l_datetrack_mode = dt_api.g_delete) THEN
1959     --
1960     Get_Delete_Dates
1961       (p_effective_date              => p_effective_date,
1962        p_base_table_name             => p_base_table_name,
1963        p_base_key_column             => p_base_key_column,
1964        p_base_key_value              => p_base_key_value,
1965        p_child_table_name1           => p_child_table_name1,
1966        p_child_key_column1           => p_child_key_column1,
1967        p_child_table_name2           => p_child_table_name2,
1968        p_child_key_column2           => p_child_key_column2,
1969        p_child_table_name3           => p_child_table_name3,
1970        p_child_key_column3           => p_child_key_column3,
1971        p_child_table_name4           => p_child_table_name4,
1972        p_child_key_column4           => p_child_key_column4,
1973        p_child_table_name5           => p_child_table_name5,
1974        p_child_key_column5           => p_child_key_column5,
1975        p_child_table_name6           => p_child_table_name6,
1976        p_child_key_column6           => p_child_key_column6,
1977        p_child_table_name7           => p_child_table_name7,
1978        p_child_key_column7           => p_child_key_column7,
1979        p_child_table_name8           => p_child_table_name8,
1980        p_child_key_column8           => p_child_key_column8,
1981        p_child_table_name9           => p_child_table_name9,
1982        p_child_key_column9           => p_child_key_column9,
1983        p_child_table_name10          => p_child_table_name10,
1984        p_child_key_column10          => p_child_key_column10,
1985        p_child_alt_base_key_column1  => p_child_alt_base_key_column1,
1986        p_child_alt_base_key_column2  => p_child_alt_base_key_column2,
1987        p_child_alt_base_key_column3  => p_child_alt_base_key_column3,
1988        p_child_alt_base_key_column4  => p_child_alt_base_key_column4,
1989        p_child_alt_base_key_column5  => p_child_alt_base_key_column5,
1990        p_child_alt_base_key_column6  => p_child_alt_base_key_column6,
1991        p_child_alt_base_key_column7  => p_child_alt_base_key_column7,
1992        p_child_alt_base_key_column8  => p_child_alt_base_key_column8,
1993        p_child_alt_base_key_column9  => p_child_alt_base_key_column9,
1994        p_child_alt_base_key_column10 => p_child_alt_base_key_column10,
1995        p_enforce_foreign_locking     => p_enforce_foreign_locking,
1996        p_validation_start_date       => p_validation_start_date,
1997        p_validation_end_date         => p_validation_end_date);
1998     --
1999   ELSIF (l_datetrack_mode = dt_api.g_update_override) THEN
2000     --
2001     Get_Update_Override_Dates
2002       (p_effective_date        => p_effective_date,
2003        p_base_table_name       => p_base_table_name,
2004        p_base_key_column       => p_base_key_column,
2005        p_base_key_value        => p_base_key_value,
2006        p_validation_start_date => p_validation_start_date,
2007        p_validation_end_date   => p_validation_end_date);
2008     --
2009   ELSIF (l_datetrack_mode = dt_api.g_update_change_insert) THEN
2010     --
2011     Get_Update_Change_Insert_Dates
2012       (p_effective_date        => p_effective_date,
2013        p_base_table_name       => p_base_table_name,
2014        p_base_key_column       => p_base_key_column,
2015        p_base_key_value        => p_base_key_value,
2016        p_validation_start_date => p_validation_start_date,
2017        p_validation_end_date   => p_validation_end_date);
2018     --
2019   ELSIF (l_datetrack_mode = dt_api.g_future_change) THEN
2020     --
2021     Get_Future_Change_Dates
2022       (p_effective_date        => p_effective_date,
2023        p_base_table_name       => p_base_table_name,
2024        p_base_key_column       => p_base_key_column,
2025        p_base_key_value        => p_base_key_value,
2026        p_parent_table_name1    => p_parent_table_name1,
2027        p_parent_key_column1    => p_parent_key_column1,
2028        p_parent_key_value1     => p_parent_key_value1,
2029        p_parent_table_name2    => p_parent_table_name2,
2030        p_parent_key_column2    => p_parent_key_column2,
2031        p_parent_key_value2     => p_parent_key_value2,
2032        p_parent_table_name3    => p_parent_table_name3,
2033        p_parent_key_column3    => p_parent_key_column3,
2034        p_parent_key_value3     => p_parent_key_value3,
2035        p_parent_table_name4    => p_parent_table_name4,
2036        p_parent_key_column4    => p_parent_key_column4,
2037        p_parent_key_value4     => p_parent_key_value4,
2038        p_parent_table_name5    => p_parent_table_name5,
2039        p_parent_key_column5    => p_parent_key_column5,
2040        p_parent_key_value5     => p_parent_key_value5,
2041        p_parent_table_name6    => p_parent_table_name6,
2042        p_parent_key_column6    => p_parent_key_column6,
2043        p_parent_key_value6     => p_parent_key_value6,
2044        p_parent_table_name7    => p_parent_table_name7,
2045        p_parent_key_column7    => p_parent_key_column7,
2046        p_parent_key_value7     => p_parent_key_value7,
2047        p_parent_table_name8    => p_parent_table_name8,
2048        p_parent_key_column8    => p_parent_key_column8,
2049        p_parent_key_value8     => p_parent_key_value8,
2050        p_parent_table_name9    => p_parent_table_name9,
2054        p_parent_key_column10   => p_parent_key_column10,
2051        p_parent_key_column9    => p_parent_key_column9,
2052        p_parent_key_value9     => p_parent_key_value9,
2053        p_parent_table_name10   => p_parent_table_name10,
2055        p_parent_key_value10    => p_parent_key_value10,
2056        p_validation_start_date => p_validation_start_date,
2057        p_validation_end_date   => p_validation_end_date);
2058     --
2059   ELSIF (l_datetrack_mode = dt_api.g_delete_next_change) THEN
2060     --
2061     Get_Delete_Next_Change_Dates
2062       (p_effective_date        => p_effective_date,
2063        p_base_table_name       => p_base_table_name,
2064        p_base_key_column       => p_base_key_column,
2065        p_base_key_value        => p_base_key_value,
2066        p_parent_table_name1    => p_parent_table_name1,
2067        p_parent_key_column1    => p_parent_key_column1,
2068        p_parent_key_value1     => p_parent_key_value1,
2069        p_parent_table_name2    => p_parent_table_name2,
2070        p_parent_key_column2    => p_parent_key_column2,
2071        p_parent_key_value2     => p_parent_key_value2,
2072        p_parent_table_name3    => p_parent_table_name3,
2073        p_parent_key_column3    => p_parent_key_column3,
2074        p_parent_key_value3     => p_parent_key_value3,
2075        p_parent_table_name4    => p_parent_table_name4,
2076        p_parent_key_column4    => p_parent_key_column4,
2077        p_parent_key_value4     => p_parent_key_value4,
2078        p_parent_table_name5    => p_parent_table_name5,
2079        p_parent_key_column5    => p_parent_key_column5,
2080        p_parent_key_value5     => p_parent_key_value5,
2081        p_parent_table_name6    => p_parent_table_name6,
2082        p_parent_key_column6    => p_parent_key_column6,
2083        p_parent_key_value6     => p_parent_key_value6,
2084        p_parent_table_name7    => p_parent_table_name7,
2085        p_parent_key_column7    => p_parent_key_column7,
2086        p_parent_key_value7     => p_parent_key_value7,
2087        p_parent_table_name8    => p_parent_table_name8,
2088        p_parent_key_column8    => p_parent_key_column8,
2089        p_parent_key_value8     => p_parent_key_value8,
2090        p_parent_table_name9    => p_parent_table_name9,
2091        p_parent_key_column9    => p_parent_key_column9,
2092        p_parent_key_value9     => p_parent_key_value9,
2093        p_parent_table_name10   => p_parent_table_name10,
2094        p_parent_key_column10   => p_parent_key_column10,
2095        p_parent_key_value10    => p_parent_key_value10,
2096        p_validation_start_date => p_validation_start_date,
2097        p_validation_end_date   => p_validation_end_date);
2098   ELSE
2099     hr_utility.set_message(801, 'HR_7184_DT_MODE_UNKNOWN');
2100     hr_utility.set_message_token('DT_MODE', l_datetrack_mode);
2101     hr_utility.raise_error;
2102   END IF;
2103   IF g_debug THEN
2104     Hr_Utility.Set_Location(' Leaving:'||l_proc, 55);
2105   END IF;
2106 EXCEPTION
2107   WHEN OTHERS THEN
2108     -- reset the OUT params to NULL to cater for NOCOPY
2109     p_validation_start_date := NULL;
2110     p_validation_end_date := NULL;
2111     RAISE;
2112 END Validate_DT_Mode;
2113 -- ----------------------------------------------------------------------------
2114 -- |------------------------< Validate_DT_Upd_Mode >--------------------------|
2115 -- ----------------------------------------------------------------------------
2116 --
2117 -- PUBLIC
2118 --
2119 -- Description: Functions returns TRUE if the datetrack update mode is valid.
2120 --
2121 -- ----------------------------------------------------------------------------
2122 FUNCTION Validate_DT_Upd_Mode(p_datetrack_mode IN VARCHAR2) RETURN BOOLEAN IS
2123   --
2124   l_proc VARCHAR2(72);
2125   --
2126 BEGIN
2127   g_debug := hr_utility.debug_enabled;
2128   IF g_debug THEN
2129     l_proc := g_package||'Validate_DT_Upd_Mode';
2130     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
2131   END IF;
2132   IF p_datetrack_mode IS NULL THEN
2133     -- Ensure that the mode is not null
2134     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2135                                p_argument       => 'datetrack_mode',
2136                                p_argument_value => p_datetrack_mode);
2137   END IF;
2138   -- Check the mode is valid
2139   IF (p_datetrack_mode = dt_api.g_correction      OR
2140       p_datetrack_mode = dt_api.g_update          OR
2141       p_datetrack_mode = dt_api.g_update_override OR
2142       p_datetrack_mode = dt_api.g_update_change_insert) THEN
2143     IF g_debug THEN
2144       Hr_Utility.Set_Location(' Leaving:'||l_proc, 10);
2145     END IF;
2146     RETURN(TRUE);
2147   ELSE
2148     IF g_debug THEN
2149       Hr_Utility.Set_Location(' Leaving:'||l_proc, 15);
2150     END IF;
2151     RETURN(FALSE);
2152   END If;
2153 END Validate_DT_Upd_Mode;
2154 -- ----------------------------------------------------------------------------
2155 -- |------------------------< Validate_DT_Del_Mode >--------------------------|
2156 -- ----------------------------------------------------------------------------
2157 --
2158 -- PUBLIC
2159 --
2160 -- Description: Functions returns TRUE if the datetrack delete mode is valid.
2161 --
2162 -- ----------------------------------------------------------------------------
2163 FUNCTION Validate_DT_Del_Mode(p_datetrack_mode IN VARCHAR2) RETURN BOOLEAN IS
2164   --
2165   l_proc VARCHAR2(72);
2166   --
2167 BEGIN
2168   g_debug := hr_utility.debug_enabled;
2172   END IF;
2169   IF g_debug THEN
2170     l_proc := g_package||'Validate_DT_Del_Mode';
2171     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
2173   IF p_datetrack_mode IS NULL THEN
2174     -- Ensure that the mode is not null
2175     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2176                                p_argument       => 'datetrack_mode',
2177                                p_argument_value => p_datetrack_mode);
2178   END IF;
2179   -- Check the mode is valid
2180   IF (p_datetrack_mode = dt_api.g_zap                  OR
2181       p_datetrack_mode = dt_api.g_delete               OR
2182       p_datetrack_mode = dt_api.g_future_change        OR
2183       p_datetrack_mode = dt_api.g_delete_next_change)  THEN
2184     IF g_debug THEN
2185       Hr_Utility.Set_Location(' Leaving:'||l_proc, 10);
2186     END IF;
2187     RETURN(TRUE);
2188   ELSE
2189     IF g_debug THEN
2190       Hr_Utility.Set_Location(' Leaving:'||l_proc, 10);
2191     END IF;
2192     RETURN(FALSE);
2193   END IF;
2194 END Validate_DT_Del_Mode;
2195 -- ----------------------------------------------------------------------------
2196 -- |------------------------< Validate_DT_Upd_Mode >--------------------------|
2197 -- ----------------------------------------------------------------------------
2198 --
2199 -- PUBLIC
2200 --
2201 -- Description: Validates the datetrack update mode.
2202 --
2203 -- ----------------------------------------------------------------------------
2204 PROCEDURE Validate_DT_Upd_Mode(p_datetrack_mode IN VARCHAR2) IS
2205 --
2206   l_proc VARCHAR2(72);
2207 --
2208 BEGIN
2209   g_debug := hr_utility.debug_enabled;
2210   IF g_debug THEN
2211     l_proc := g_package||'Validate_DT_Upd_Mode';
2212     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
2213   END IF;
2214   -- Check the mode is valid
2215   IF (NOT Validate_DT_Upd_Mode(p_datetrack_mode => p_datetrack_mode)) THEN
2216     -- The datetrack mode is invalid therefore we must error
2217     hr_utility.set_message(801, 'HR_7203_DT_UPD_MODE_INVALID');
2218     hr_utility.raise_error;
2219   END IF;
2220   IF g_debug THEN
2221     Hr_Utility.Set_Location(' Leaving:'||l_proc, 10);
2222   END IF;
2223 END Validate_DT_Upd_Mode;
2224 -- ----------------------------------------------------------------------------
2225 -- |------------------------< Validate_DT_Del_Mode >--------------------------|
2226 -- ----------------------------------------------------------------------------
2227 --
2228 -- PUBLIC
2229 --
2230 -- Description: Validates the datetrack delete mode.
2231 --
2232 -- ----------------------------------------------------------------------------
2233 PROCEDURE Validate_DT_Del_Mode(p_datetrack_mode IN VARCHAR2) IS
2234   --
2235   l_proc VARCHAR2(72);
2236   --
2237 BEGIN
2238   g_debug := hr_utility.debug_enabled;
2239   IF g_debug THEN
2240     l_proc := g_package||'Validate_DT_Del_Mode';
2241     Hr_Utility.Set_Location('Entering:'||l_proc, 5);
2242   END IF;
2243   -- Check the mode is valid
2244   IF (NOT Validate_DT_Del_Mode(p_datetrack_mode => p_datetrack_mode)) THEN
2245     -- The datetrack mode is invalid therefore we must error
2246     hr_utility.set_message(801, 'HR_7204_DT_DEL_MODE_INVALID');
2247     hr_utility.raise_error;
2248   END IF;
2249   IF g_debug THEN
2250     Hr_Utility.Set_Location(' Leaving:'||l_proc, 10);
2251   END IF;
2252 End Validate_DT_Del_Mode;
2253 -- ----------------------------------------------------------------------------
2254 -- |-----------------------< Get_Object_Version_Number >----------------------|
2255 -- ----------------------------------------------------------------------------
2256 --
2257 -- PUBLIC
2258 --
2259 -- Description: Function will return the next object version number to be used
2260 --              within datetrack for an insert or update dml operation. The
2261 --              returned object version number will be determined by taking
2262 --              the maximum object version number for the datetracked rows
2263 --              and then incrementing by 1. All datetrack modes will call
2264 --              this function except ZAP.
2265 --
2266 -- ----------------------------------------------------------------------------
2267 FUNCTION get_object_version_number
2268         (p_base_table_name  IN VARCHAR2,
2269          p_base_key_column  IN VARCHAR2,
2270          p_base_key_value   IN NUMBER)
2271         RETURN NUMBER IS
2272 --
2273   l_proc        VARCHAR2(72);
2274   l_object_num  NUMBER;      -- Holds new object version number
2275 --
2276 BEGIN
2277   g_debug := hr_utility.debug_enabled;
2278   IF g_debug THEN
2279     l_proc := g_package||'get_object_version_number';
2280     hr_utility.set_location('Entering:'||l_proc, 5);
2281   END IF;
2282   -- Ensure that all the mandatory arguments are not null
2283   -- [ start of change 30.14 ]
2284   IF p_base_table_name IS NULL OR
2285      p_base_key_column IS NULL OR
2286      p_base_key_value IS NULL THEN
2287     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2288                                p_argument       => 'p_base_table_name',
2289                                p_argument_value => p_base_table_name);
2290     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2291                                p_argument       => 'p_base_key_column',
2292                                p_argument_value => p_base_key_column);
2293     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2297   -- [ end of change 30.14 ]
2294                                p_argument       => 'p_base_key_value',
2295                                p_argument_value => p_base_key_value);
2296   END IF;
2298   --
2299   -- Define dynamic sql text with substitution tokens
2300   --
2301   g_dynamic_sql :=
2302     'SELECT NVL(MAX(t.object_version_number),0) + 1 '||
2303     'FROM '||LOWER(p_base_table_name)||' t '||
2304     'WHERE t.'||LOWER(p_base_key_column)||' = :p_base_key_value';
2305   -- set the dynamic SQL comment for identification
2306   dt_api.g_dynamic_sql :=
2307     dt_api.g_dynamic_sql||
2308     REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','get_object_version_number');
2309   --
2310   EXECUTE IMMEDIATE g_dynamic_sql
2311   INTO  l_object_num
2312   USING p_base_key_value;
2313   IF g_debug THEN
2314     hr_utility.set_location('Leaving :'||l_proc, 10);
2315   END IF;
2316   RETURN(l_object_num);
2317 END get_object_version_number;
2318 -- ----------------------------------------------------------------------------
2319 --
2320 -- PUBLIC
2321 --
2322 -- Description: Function returns a boolean value. TRUE will be set if
2323 --              row exists for the specified table between the from and to
2324 --              dates else FALSE will be returned.
2325 --              If the p_base_key_value is NULL then this function will
2326 --              always return FALSE. The reason for this is that, the
2327 --              calling process might have an option foreign key column which
2328 --              is null.
2329 --
2330 -- ----------------------------------------------------------------------------
2331 FUNCTION rows_exist
2332          (p_base_table_name IN VARCHAR2,
2333           p_base_key_column IN VARCHAR2,
2334           p_base_key_value  IN NUMBER,
2335           p_from_date       IN DATE,
2336           p_to_date         IN DATE DEFAULT hr_api.g_eot)
2337          RETURN BOOLEAN IS
2338 --
2339   l_proc        VARCHAR2(72);
2340   l_ret_column  number(1);      -- Returning Sql Column
2341 --
2342 BEGIN
2343   g_debug := hr_utility.debug_enabled;
2344   IF g_debug THEN
2345     l_proc := g_package||'rows_exist';
2346     hr_utility.set_location('Entering:'||l_proc, 5);
2347   END IF;
2348   IF (p_base_key_value IS NOT NULL) THEN
2349     IF p_base_table_name IS NULL OR
2350        p_base_key_column IS NULL OR
2351        p_from_date IS NULL OR
2352        p_to_date IS NULL THEN
2353       -- Mandatory arg checking
2354       hr_api.mandatory_arg_error
2355         (p_api_name       => l_proc,
2356          p_argument       => 'p_base_table_name',
2357          p_argument_value => p_base_table_name);
2358       --
2359       hr_api.mandatory_arg_error
2360         (p_api_name       => l_proc,
2361          p_argument       => 'p_base_key_column',
2362          p_argument_value => p_base_key_column);
2363       --
2364       hr_api.mandatory_arg_error
2365         (p_api_name       => l_proc,
2366          p_argument       => 'p_from_date',
2367          p_argument_value => p_from_date);
2368       --
2369       hr_api.mandatory_arg_error
2370         (p_api_name       => l_proc,
2371          p_argument       => 'p_to_date',
2372          p_argument_value => p_to_date);
2373     END IF;
2374     -- Define dynamic sql text with substitution tokens
2375     g_dynamic_sql :=
2376       'SELECT NULL '||
2377       'FROM '||LOWER(p_base_table_name)||' t '||
2378       'WHERE t.'||LOWER(p_base_key_column)||' = :p_base_key_value '||
2379       'AND t.effective_start_date <= :p_to_date '||
2380       'AND t.effective_end_date >= :p_from_date';
2381     -- set the dynamic SQL comment for identification
2382     dt_api.g_dynamic_sql :=
2383       dt_api.g_dynamic_sql||
2384       REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','rows_exist');
2385     --
2386     EXECUTE IMMEDIATE g_dynamic_sql
2387     INTO  l_ret_column
2388     USING p_base_key_value, p_to_date, p_from_date;
2389     -- one row exists so return true
2390     IF g_debug THEN
2391       hr_utility.set_location('Leaving:'||l_proc, 10);
2392     END IF;
2393     RETURN(TRUE);
2394   END IF;
2395 EXCEPTION
2396   WHEN NO_DATA_FOUND THEN
2397     IF g_debug THEN
2398       hr_utility.set_location('Leaving:'||l_proc, 15);
2399     END IF;
2400     -- return false as no rows exist
2401     RETURN(FALSE);
2402   WHEN TOO_MANY_ROWS THEN
2403     IF g_debug THEN
2404       hr_utility.set_location('Leaving:'||l_proc, 20);
2405     END IF;
2406     -- return TRUE because more than one row exists
2407     RETURN(TRUE);
2408   WHEN OTHERS THEN
2409     RAISE;
2410 END rows_exist;
2411 -- ----------------------------------------------------------------------------
2412 --
2413 -- PUBLIC
2414 --
2415 -- Description: This function is used to determine if datetrack rows exist
2416 --              between the from and to date specified.
2417 --              If the datetrack rows do exist for the duration then a TRUE
2418 --              value will be returned else FALSE will be returned.
2419 --              If the p_base_key_value is null then this function will assume
2420 --              that an optional relationship is in force and will return TRUE
2421 --
2422 -- ----------------------------------------------------------------------------
2423 FUNCTION check_min_max_dates
2424          (p_base_table_name IN  VARCHAR2,
2425           p_base_key_column IN  VARCHAR2,
2429          RETURN BOOLEAN IS
2426           p_base_key_value  IN  NUMBER,
2427           p_from_date       IN  DATE,
2428           p_to_date         IN  DATE)
2430 --
2431   l_proc        VARCHAR2(72);
2432   l_min_date    DATE;
2433   l_max_date    DATE;
2434 --
2435 BEGIN
2436   g_debug := hr_utility.debug_enabled;
2437   IF g_debug THEN
2438     l_proc := g_package||'check_min_max_dates';
2439     hr_utility.set_location('Entering:'||l_proc, 5);
2440   END IF;
2441   IF (p_base_key_value IS NOT NULL) THEN
2442     IF p_base_table_name IS NULL OR
2443        p_base_key_column IS NULL OR
2444        p_from_date IS NULL OR
2445        p_to_date IS NULL THEN
2446       -- Mandatory arg checking
2447       hr_api.mandatory_arg_error
2448         (p_api_name       => l_proc,
2449          p_argument       => 'p_base_table_name',
2450          p_argument_value => p_base_table_name);
2451       --
2452       hr_api.mandatory_arg_error
2453         (p_api_name       => l_proc,
2454          p_argument       => 'p_base_key_column',
2455          p_argument_value => p_base_key_column);
2456       --
2457       hr_api.mandatory_arg_error
2458         (p_api_name       => l_proc,
2459          p_argument       => 'p_from_date',
2460          p_argument_value => p_from_date);
2461       --
2462       hr_api.mandatory_arg_error
2463         (p_api_name       => l_proc,
2464          p_argument       => 'p_to_date',
2465          p_argument_value => p_to_date);
2466     END IF;
2467     -- Define dynamic sql text with substitution tokens
2468     g_dynamic_sql :=
2469       'SELECT MIN(t.effective_start_date),MAX(t.effective_end_date) '||
2470       'FROM '||LOWER(p_base_table_name)||' t '                   ||
2471       'WHERE t.'||LOWER(p_base_key_column)||' = :p_base_key_value';
2472     -- set the dynamic SQL comment for identification
2473     dt_api.g_dynamic_sql :=
2474       dt_api.g_dynamic_sql||
2475       REPLACE(dt_api.g_dynamic_sql_comment,'{proc}','check_min_max_dates');
2476     --
2477     EXECUTE IMMEDIATE g_dynamic_sql
2478     INTO  l_min_date, l_max_date
2479     USING p_base_key_value;
2480     -- Determine if the aggregate functions returned null.
2481     -- If they are null then no rows were found therefore we must error
2482     -- as either the table name, base key column name or base key value
2483     -- was incorrectly specified.
2484     IF (l_min_date IS NULL AND l_max_date IS NULL) THEN
2485       hr_utility.set_message(801, 'HR_6153_ALL_PROCEDURE_FAIL');
2486       hr_utility.set_message_token('PROCEDURE', l_proc);
2487       hr_utility.set_message_token('STEP','40');
2488       hr_utility.raise_error;
2489     ELSE
2490       -- Ensure that the min and max dates fall within the from and to
2491       -- dates
2492       IF (p_from_date >= l_min_date AND p_to_date <= l_max_date) THEN
2493         IF g_debug THEN
2494           hr_utility.set_location(' Leaving:'||l_proc, 10);
2495         END IF;
2496         RETURN(TRUE);
2497       ELSE
2498         IF g_debug THEN
2499           Hr_utility.set_location(' Leaving:'||l_proc, 15);
2500         END IF;
2501         RETURN(FALSE);
2502       END IF;
2503     END IF;
2504   ELSE
2505     IF g_debug THEN
2506       hr_utility.set_location(' Leaving:'||l_proc, 20);
2507     END IF;
2508   -- The key value has not been specified
2509     RETURN(TRUE);
2510   END IF;
2511 END check_min_max_dates;
2512 --
2513 --
2514 -- ----------------------------------------------------------------------------
2515 -- |---------------------< find_dt_upd_modes_and_dates >----------------------|
2516 -- ----------------------------------------------------------------------------
2517 --
2518 --
2519 procedure find_dt_upd_modes_and_dates
2520   (p_effective_date                in     date
2521   ,p_base_table_name               in     varchar2
2522   ,p_base_key_column               in     varchar2
2523   ,p_base_key_value                in     number
2524   ,p_correction                       out nocopy boolean
2525   ,p_update                           out nocopy boolean
2526   ,p_update_override                  out nocopy boolean
2527   ,p_update_change_insert             out nocopy boolean
2528   ,p_correction_start_date            out nocopy date
2529   ,p_correction_end_date              out nocopy date
2530   ,p_update_start_date                out nocopy date
2531   ,p_update_end_date                  out nocopy date
2532   ,p_override_start_date              out nocopy date
2533   ,p_override_end_date                out nocopy date
2534   ,p_upd_chg_start_date                out nocopy date
2535   ,p_upd_chg_end_date                  out nocopy date
2536   ) IS
2537   --
2538   -- Local variables
2539   --
2540 
2541   l_effective_rows          g_dt_effective_rows_tab;
2542   l_date_from_row_idx       BINARY_INTEGER;
2543   l_proc   varchar2(80) ;
2544 
2545 begin
2546    g_debug := hr_utility.debug_enabled;
2547    IF g_debug THEN
2548      l_proc :=  g_package||'find_dt_upd_modes_and_dates';
2549      hr_utility.set_location('Entering: '||l_proc,10);
2550    END IF;
2551   Effective_Date_Valid(p_effective_date => p_effective_date);
2552   -- Ensure that all the mandatory arguments are not null
2553   -- [ start of change 30.14 ]
2554   IF p_base_table_name IS NULL OR
2555      p_base_key_column IS NULL OR
2556      p_base_key_value IS NULL THEN
2557     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2558                                p_argument       => 'p_base_table_name',
2562                                p_argument_value => p_base_key_column);
2559                                p_argument_value => p_base_table_name);
2560     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2561                                p_argument       => 'p_base_key_column',
2563     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2564                                p_argument       => 'p_base_key_value',
2565                                p_argument_value => p_base_key_value);
2566   END IF;
2567   -- [ end of change 30.14 ]
2568   --
2569   -- CORRECTION: always set to TRUE
2570   p_correction := TRUE;
2571   -- get the effective rows
2572   get_effective_rows
2573     (p_date_from         => p_effective_date,
2574      p_base_table_name   => p_base_table_name,
2575      p_base_key_column   => p_base_key_column,
2576      p_base_key_value    => p_base_key_value,
2577      p_lock_rows         => FALSE,
2578      p_date_from_valid   => TRUE,
2579      p_effective_rows    => l_effective_rows,
2580      p_date_from_row_idx => l_date_from_row_idx);
2581   -- If the current effective start date is not the same as the effective
2582   -- date then we must check to see if update operations are allowed, else
2583   -- no update operations are allowed
2584   IF (l_effective_rows(l_date_from_row_idx).effective_start_date <>
2585       p_effective_date) THEN
2586     -- As the current row does not start on the effective date we
2587     -- determine if any future rows exist.
2588     IF (l_effective_rows.COUNT > l_date_from_row_idx) THEN
2589       -- As future rows exist we must set:
2590       -- 1) UPDATE must be set to FALSE
2591       -- 2) UPDATE_OVERRIDE and UPDATE_CHANGE_INSERT must be set TRUE
2592       IF g_debug THEN
2593         hr_utility.set_location(l_proc,20);
2594       END IF;
2595       p_update               := FALSE;
2596       p_update_start_date    := NULL;
2597       p_update_end_date      := NULL;
2598       p_update_override      := TRUE;
2599       p_override_start_date := p_effective_date;
2600       p_override_end_date   :=
2601               l_effective_rows(l_effective_rows.LAST).effective_end_date;
2602       p_update_change_insert := TRUE;
2603       p_upd_chg_start_date := p_effective_date;
2604       p_upd_chg_end_date   :=
2605              l_effective_rows(l_date_from_row_idx).effective_end_date;
2606     ELSE
2607       -- As future rows don't exist we must set:
2608       -- 1) UPDATE must be set to TRUE
2609       -- 2) UPDATE_OVERRIDE and UPDATE_CHANGE_INSERT must be set FALSE
2610       IF g_debug THEN
2611         hr_utility.set_location(l_proc,30);
2612       END IF;
2613       p_update               := TRUE;
2614       p_update_start_date    := p_effective_date;
2615       p_update_end_date      :=
2616              l_effective_rows(l_date_from_row_idx).effective_end_date;
2617       p_update_override      := FALSE;
2618       p_override_start_date  := NULL;
2619       p_override_end_date    := NULL;
2620       p_update_change_insert := FALSE;
2621       p_upd_chg_start_date   := NULL;
2622       p_upd_chg_end_date     := NULL;
2623     END IF;
2624   ELSE
2625     -- As the current effective start date is the same as the effective date
2626     -- we must set:
2630       hr_utility.set_location(l_proc,40);
2627     -- 1) UPDATE must be set to FALSE
2628     -- 2) UPDATE_OVERRIDE and UPDATE_CHANGE_INSERT must be set FALSE
2629     IF g_debug THEN
2631     END IF;
2632     p_update               := FALSE;
2633     p_update_start_date    := NULL;
2634     p_update_end_date      := NULL;
2635     p_update_override      := FALSE;
2636     p_override_start_date  := NULL;
2637     p_override_end_date    := NULL;
2638     p_update_change_insert := FALSE;
2639     p_upd_chg_start_date   := NULL;
2640     p_upd_chg_end_date     := NULL;
2641   END IF;
2642 
2643 --Set validation start date and end date for each of the modes
2644   IF p_correction = TRUE THEN
2645      IF g_debug THEN
2646        hr_utility.set_location(l_proc,50);
2647      END IF;
2648 
2649      p_correction_start_date :=
2650      l_effective_rows(l_date_from_row_idx).effective_start_date;
2651      p_correction_end_date :=
2652      l_effective_rows(l_date_from_row_idx).effective_end_date;
2653   END IF;
2654   IF g_debug THEN
2655     hr_utility.set_location('Leaving :'||l_proc, 60);
2656   END IF;
2657 EXCEPTION
2658   WHEN OTHERS THEN
2659     -- set all OUTs to NULL and RAISE
2660     p_correction           := NULL;
2661     p_update               := NULL;
2662     p_update_override      := NULL;
2663     p_update_change_insert := NULL;
2664     p_correction_start_date  := NULL;
2665     p_correction_end_date    := NULL;
2666     p_update_start_date   := NULL;
2667     p_update_end_date     := NULL;
2668     p_upd_chg_start_date   := NULL;
2669     p_upd_chg_end_date     := NULL;
2670     p_override_start_date := NULL;
2671     p_override_end_date    := NULL;
2672     RAISE;
2673 end find_dt_upd_modes_and_dates;
2674 --
2675 -- ----------------------------------------------------------------------------
2676 -- |---------------------< find_dt_del_modes_and_dates >----------------------|
2677 -- ----------------------------------------------------------------------------
2678 --
2679 procedure find_dt_del_modes_and_dates
2680   (p_effective_date                in     date
2681   ,p_base_table_name               in     varchar2
2682   ,p_base_key_column               in     varchar2
2683   ,p_base_key_value                in     number
2684   ,p_parent_table_name1            in     varchar2 default hr_api.g_varchar2
2685   ,p_parent_key_column1  	   in     varchar2 default hr_api.g_varchar2
2686   ,p_parent_key_value1   	   in     number   default hr_api.g_number
2687   ,p_parent_table_name2  	   in     varchar2 default hr_api.g_varchar2
2688   ,p_parent_key_column2  	   in     varchar2 default hr_api.g_varchar2
2689   ,p_parent_key_value2   	   in     number   default hr_api.g_number
2690   ,p_parent_table_name3  	   in     varchar2 default hr_api.g_varchar2
2691   ,p_parent_key_column3  	   in     varchar2 default hr_api.g_varchar2
2697   ,p_parent_key_column5  	   in     varchar2 default hr_api.g_varchar2
2692   ,p_parent_key_value3   	   in     number   default hr_api.g_number
2693   ,p_parent_table_name4  	   in     varchar2 default hr_api.g_varchar2
2694   ,p_parent_key_column4  	   in     varchar2 default hr_api.g_varchar2
2695   ,p_parent_key_value4   	   in     number   default hr_api.g_number
2696   ,p_parent_table_name5  	   in     varchar2 default hr_api.g_varchar2
2698   ,p_parent_key_value5   	   in     number   default hr_api.g_number
2699   ,p_parent_table_name6  	   in     varchar2 default hr_api.g_varchar2
2700   ,p_parent_key_column6  	   in     varchar2 default hr_api.g_varchar2
2701   ,p_parent_key_value6   	   in     number   default hr_api.g_number
2702   ,p_parent_table_name7  	   in     varchar2 default hr_api.g_varchar2
2703   ,p_parent_key_column7  	   in     varchar2 default hr_api.g_varchar2
2704   ,p_parent_key_value7   	   in     number   default hr_api.g_number
2705   ,p_parent_table_name8  	   in     varchar2 default hr_api.g_varchar2
2706   ,p_parent_key_column8  	   in     varchar2 default hr_api.g_varchar2
2707   ,p_parent_key_value8   	   in     number   default hr_api.g_number
2708   ,p_parent_table_name9  	   in     varchar2 default hr_api.g_varchar2
2709   ,p_parent_key_column9  	   in     varchar2 default hr_api.g_varchar2
2710   ,p_parent_key_value9   	   in     number   default hr_api.g_number
2711   ,p_parent_table_name10 	   in     varchar2 default hr_api.g_varchar2
2712   ,p_parent_key_column10 	   in     varchar2 default hr_api.g_varchar2
2713   ,p_parent_key_value10  	   in     number   default hr_api.g_number
2714   ,p_zap                              out nocopy boolean
2715   ,p_delete                           out nocopy boolean
2716   ,p_future_change                    out nocopy boolean
2717   ,p_delete_next_change               out nocopy boolean
2718   ,p_zap_start_date                   out nocopy date
2719   ,p_zap_end_date                     out nocopy date
2720   ,p_delete_start_date                out nocopy date
2721   ,p_delete_end_date                  out nocopy date
2722   ,p_del_future_start_date                out nocopy date
2723   ,p_del_future_end_date                  out nocopy date
2724   ,p_del_next_start_date               out nocopy date
2725   ,p_del_next_end_date                 out nocopy date
2726  ) is
2727 
2728 
2729   l_effective_rows          g_dt_effective_rows_tab;
2730   l_date_from_row_idx       BINARY_INTEGER;
2731   l_future_effective_end_date DATE;
2732   l_validation_end_date       DATE;
2733   l_parent_min_date           DATE;
2734   l_proc   varchar2(80) ;
2735 begin
2736    g_debug := hr_utility.debug_enabled;
2737    if g_debug then
2738      l_proc :=  g_package||'get_update_modes_for_oaf';
2739      hr_utility.set_location('Entering: '||l_proc,10);
2740    end if;
2741 
2742   Effective_Date_Valid(p_effective_date => p_effective_date);
2743   -- Ensure that all the mandatory arguments are not null
2744   -- [ start of change 30.14 ]
2745   IF p_base_table_name IS NULL OR
2746      p_base_key_column IS NULL OR
2747      p_base_key_value IS NULL THEN
2748     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2749                                p_argument       => 'p_base_table_name',
2750                                p_argument_value => p_base_table_name);
2751     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2752                                p_argument       => 'p_base_key_column',
2753                                p_argument_value => p_base_key_column);
2754     hr_api.mandatory_arg_error(p_api_name       => l_proc,
2755                                p_argument       => 'p_base_key_value',
2756                                p_argument_value => p_base_key_value);
2757   END IF;
2758   -- [ end of change 30.14 ]
2759   -- ZAP: always set to TRUE
2760   p_zap := TRUE;
2761   -- get the effective rows
2762   l_date_from_row_idx := 0;
2763   get_effective_rows
2764     (p_date_from         => dt_api.g_sot,
2765      p_base_table_name   => p_base_table_name,
2766      p_base_key_column   => p_base_key_column,
2767      p_base_key_value    => p_base_key_value,
2768      p_lock_rows         => FALSE,
2769      p_date_from_valid   => FALSE,
2770      p_effective_rows    => l_effective_rows,
2771      p_date_from_row_idx => l_date_from_row_idx);
2772   IF p_zap = TRUE THEN
2773   -- at least one row will exist otherwise the get_effective_rows would of
2774   -- raised an error therefore just set the p_validation_start_date and
2775   -- p_validation_end_date OUT parameters
2776      p_zap_start_date :=
2777        l_effective_rows(l_effective_rows.FIRST).effective_start_date;
2778      p_zap_end_date :=
2779        l_effective_rows(l_effective_rows.LAST).effective_end_date;
2780   END IF;
2781   -- Now that the ZAP dates are set, set the l_date_from_row_idx to point
2782   -- to the current row as of p_effective_date
2783   <<get_row_idx>>
2784   FOR i IN l_effective_rows.FIRST..l_effective_rows.LAST
2785   LOOP
2786   -- Check if we are on the current row as of p_effective_date
2787   IF l_effective_rows(i).EFFECTIVE_START_DATE <= p_effective_date AND
2788    l_effective_rows(i).EFFECTIVE_END_DATE >= p_effective_date THEN
2789    --ok found the row, so set the index
2790    l_date_from_row_idx := i;
2791    -- exit loop
2792    EXIT get_row_idx;
2793   END IF;
2794   END LOOP;
2795   IF l_date_from_row_idx = 0 THEN
2796   -- a serious internal error has occured. Thisis defensive as this
2797   -- error should not be raised here
2798     hr_utility.set_message(801, 'HR_7180_DT_NO_ROW_EXIST');
2799     hr_utility.set_message_token('TABLE_NAME', p_base_table_name);
2800     hr_utility.set_message_token('SESSION_DATE',
2801                                  fnd_date.date_to_chardate(p_effective_date));
2802     hr_utility.raise_error;
2803   END IF;
2804   -- DELETE: always set to TRUE if the maximum effective end date is not the
2805   --         same as the effective date and the effective date if not the
2806   --         end of time
2807   IF ((p_effective_date <>
2808        l_effective_rows(l_effective_rows.LAST).effective_end_date) AND
2809       (p_effective_date <> dt_api.g_eot)) THEN
2810     p_delete := TRUE;
2811   ELSE
2815   END IF;
2812     p_delete := FALSE;
2813     p_delete_start_date := NULL;
2814     p_delete_end_date   := NULL;
2816   -- FUTURE_CHANGE
2817   -- DELETE_NEXT_CHANGE: always set to FALSE if the current effective end date
2818   --                     is the end of time or the minimum parental effective
2819   --                     end date is less than or equal to the effective end
2820   --                     date
2821   IF (l_effective_rows(l_date_from_row_idx).effective_end_date <>
2822       dt_api.g_eot) THEN
2823     l_parent_min_date := return_parent_min_date
2824         (p_effective_date => p_effective_date,
2825          p_lock_rows      => FALSE,
2826          p_table_name1    => p_parent_table_name1,
2827          p_key_column1    => p_parent_key_column1,
2828          p_key_value1     => p_parent_key_value1,
2829          p_table_name2    => p_parent_table_name2,
2830          p_key_column2    => p_parent_key_column2,
2831          p_key_value2     => p_parent_key_value2,
2832          p_table_name3    => p_parent_table_name3,
2833          p_key_column3    => p_parent_key_column3,
2834          p_key_value3     => p_parent_key_value3,
2835          p_table_name4    => p_parent_table_name4,
2836          p_key_column4    => p_parent_key_column4,
2837          p_key_value4     => p_parent_key_value4,
2838          p_table_name5    => p_parent_table_name5,
2839          p_key_column5    => p_parent_key_column5,
2840          p_key_value5     => p_parent_key_value5,
2841          p_table_name6    => p_parent_table_name6,
2842          p_key_column6    => p_parent_key_column6,
2843          p_key_value6     => p_parent_key_value6,
2844          p_table_name7    => p_parent_table_name7,
2845          p_key_column7    => p_parent_key_column7,
2846          p_key_value7     => p_parent_key_value7,
2847          p_table_name8    => p_parent_table_name8,
2848          p_key_column8    => p_parent_key_column8,
2849          p_key_value8     => p_parent_key_value8,
2850          p_table_name9    => p_parent_table_name9,
2851          p_key_column9    => p_parent_key_column9,
2852          p_key_value9     => p_parent_key_value9,
2853          p_table_name10   => p_parent_table_name10,
2854          p_key_column10   => p_parent_key_column10,
2855          p_key_value10    => p_parent_key_value10);
2856     -- get the min parent end date
2857     IF l_parent_min_date  <=
2858        l_effective_rows(l_date_from_row_idx).effective_end_date THEN
2859       p_future_change      := FALSE;
2860       p_delete_next_change := FALSE;
2861       p_del_future_start_date := NULL;
2862       p_del_future_end_date   := NULL;
2863       p_del_next_start_date := NULL;
2864       p_del_next_end_date   := NULL;
2865     ELSE
2866       p_future_change      := TRUE;
2867       p_delete_next_change := TRUE;
2868     END IF;
2869   ELSE
2870     p_future_change      := FALSE;
2871     p_delete_next_change := FALSE;
2872     p_del_future_start_date := NULL;
2873     p_del_future_end_date   := NULL;
2874     p_del_next_start_date := NULL;
2875     p_del_next_end_date   := NULL;
2876   END IF;
2877 
2878   IF p_delete = TRUE THEN
2879   -- Providing the maximum effective end date is not the same as the current
2880   -- effective date then we must return the validation start and end dates.
2881   -- However, if you attempt to do a datetrack delete where the session date is
2882   -- the same as your maximum date then we must error.
2883       IF (p_effective_date <>
2884           l_effective_rows(l_effective_rows.LAST).effective_end_date) THEN
2885         p_delete_start_date :=  p_effective_date + 1;
2886         p_delete_end_date   :=
2887           l_effective_rows(l_effective_rows.LAST).effective_end_date;
2888       ELSE
2889         -- We cannot perform a DateTrack delete operation where the effective date
2890         -- is the same as the maximum effective end date.
2891         hr_utility.set_message(801, 'HR_7185_DT_DEL_NOT_ALLOWED');
2892         hr_utility.raise_error;
2893       END IF;
2894   END IF;
2895 
2896   IF p_future_change = TRUE THEN
2897   -- Providing the current effective end date is not the end of time
2898   -- then we must set the validation dates
2899       IF (l_effective_rows(l_date_from_row_idx).effective_end_date <>
2900           dt_api.g_eot) THEN
2901 
2902         -- If the validation end date is set to the current effective end date
2903         -- then we must error as we cannot extend the end date of the current
2904         -- row
2905         l_validation_end_date := l_parent_min_date;
2906         IF (l_validation_end_date <=
2907             l_effective_rows(l_date_from_row_idx).effective_end_date) THEN
2908           hr_utility.set_message(801, 'HR_7187_DT_CANNOT_EXTEND_END');
2909           hr_utility.set_message_token('DT_MODE', ' future changes');
2910           hr_utility.raise_error;
2911         ELSE
2912           -- set the validation_start/end_date OUT params
2913           p_del_future_start_date :=
2914             l_effective_rows(l_date_from_row_idx).effective_end_date + 1;
2915           p_del_future_end_date := l_validation_end_date;
2916         END IF;
2917       ELSE
2918         -- The current effective end date is alreay the end of time therefore
2919         -- we cannot extend the end date
2920         hr_utility.set_message(801, 'HR_7188_DT_DATE_IS_EOT');
2921         hr_utility.raise_error;
2922       END IF;
2923   END IF;
2924 
2925   IF p_delete_next_change = TRUE THEN
2926    -- Providing the current effective end date is not the end of time
2927    -- then we must set the validation dates
2928     IF (l_effective_rows(l_date_from_row_idx).effective_end_date <>
2929         dt_api.g_eot) THEN
2930       -- check to see if future rows exist
2931       IF l_effective_rows.COUNT > l_date_from_row_idx THEN
2932         -- future rows exist so set the future effective end date
2933         -- to the end date of the next datetrack row after the row for the
2934         -- effective date
2938         -- although the date should be NULL because it has not been set we'll set
2935         l_future_effective_end_date :=
2936           l_effective_rows(l_date_from_row_idx + 1).effective_end_date;
2937       ELSE
2939         -- it anyway for readability and defensive style coding
2940         l_future_effective_end_date := NULL;
2941       END IF;
2942       -- To determine the validation end date we must take the minimum date
2943       -- from the following three possible dates:
2944       -- 1: Minimum parent entity entity end date
2945       -- 2: If future rows exist then the effective end date of the next row
2946       -- 3: If no future rows exist then the end of time
2947       l_validation_end_date :=
2948         LEAST
2949         (l_parent_min_date,NVL(l_future_effective_end_date,dt_api.g_eot));
2950       -- if the validation end date is set to the current effective end date
2951       -- then we must error as we cannot extend the end date of the current
2952       -- row
2953       IF (l_validation_end_date <=
2954           l_effective_rows(l_date_from_row_idx).effective_end_date) THEN
2955         hr_utility.set_message(801, 'HR_7187_DT_CANNOT_EXTEND_END');
2956         hr_utility.set_message_token('DT_MODE', ' delete next change');
2957         hr_utility.raise_error;
2958       ELSE
2959         -- set the OUT validation params
2960         -- set the validation start date to the current effective end date + 1
2961         p_del_next_start_date :=
2962           l_effective_rows(l_date_from_row_idx).effective_end_date + 1;
2963         p_del_next_end_date := l_validation_end_date;
2964       END IF;
2965     ELSE
2966       -- the current effective end date is alreay the end of time therefore
2967       -- we cannot extend the end date
2968       hr_utility.set_message(801, 'HR_7188_DT_DATE_IS_EOT');
2969       hr_utility.raise_error;
2970     END IF;
2971   END IF;
2972 
2973 
2974   IF g_debug THEN
2975     Hr_Utility.Set_Location('Leaving :'||l_proc, 30);
2976   END IF;
2977 
2978 exception
2979    when others then
2980    -- set all OUTs to NULL and RAISE
2981      p_zap := null;
2982      p_delete := null;
2983      p_future_change := null;
2984      p_delete_next_change := null;
2985      p_zap_start_date := null;
2986      p_zap_end_date   := null;
2987      p_delete_start_date := null;
2988      p_delete_end_date   := null;
2989      p_del_future_start_date := null;
2990      p_del_future_end_date   := null;
2991      p_del_next_start_date := null;
2992      p_del_next_end_date   := null;
2993      RAISE;
2994 end find_dt_del_modes_and_dates;
2995 END dt_api;