DBA Data[Home] [Help]

PACKAGE BODY: APPS.PER_RIC_PKG

Source


1 PACKAGE BODY per_ric_pkg as
2 /* $Header: pericpkg.pkb 120.3 2011/06/15 12:14:12 sidsaxen noship $ */
3 
4  g_package varchar2(30) := 'per_ric_pkg';
5  g_debug boolean := true;
6 
7  --
8  -- ----------------------------------------------------------------------------
9  -- |-----------------------------< col_info_rec >-----------------------------|
10  -- ----------------------------------------------------------------------------
11  -- {Start Of Comments}
12  --
13  -- Description:
14  --   This function is used to turn attribute arguments into the record
15  --   structure column_info_rec.
16  --
17  -- Pre Conditions:
18  --   This is a public function and can only be called to build up record type column_info_rec.
19  --
20  -- In Arguments:
21  --
22  -- Post Success:
23  --   A returning record structure will be returned.
24  --
25  -- Post Failure:
26  --   No direct error handling is required within this function. Any possible
27  --   errors within this function will be a PL/SQL value error due to conversion
28  --   of datatypes or data lengths.
29  --
30  -- Developer Implementation Notes:
31  --   None.
32  --
33  -- Access Status:
34  --   Internal Table Handler Use Only.
35  --
36  -- {End Of Comments}
37   function col_info_rec(
38    column_NAME IN VARCHAR2,
39    value_VARCHAR IN VARCHAR2 default null,
40    value_NUMBER IN NUMBER default null,
41    value_DATE IN DATE default null)
42   return column_info_rec is
43    column_info_record column_info_rec;
44    l_func varchar2(240) := g_package||'.col_info_rec';
45   begin
46 
47     if g_debug then
48       hr_utility.set_location('Entering: '||l_func,10);
49     end if;
50 
51     column_info_record.column_NAME := column_NAME;
52     column_info_record.value_NUMBER := value_NUMBER;
53     column_info_record.value_VARCHAR := value_VARCHAR;
54     column_info_record.value_DATE := value_DATE;
55 
56     if g_debug then
57       hr_utility.set_location('Leaving: '||l_func,100);
58     end if;
59 
60   return column_info_record;
61   end;
62 
63 --
64  -- ----------------------------------------------------------------------------
65  -- |-----------------------------< ref_info_rec >-----------------------------|
66  -- ----------------------------------------------------------------------------
67  -- {Start Of Comments}
68  --
69  -- Description:
70  --   This function is used to turn attribute arguments into the record
71  --   structure ref_entity_rec.
72  --
73  -- Pre Conditions:
74  --   This is a public function and can only be called to build up record type ref_entity_rec.
75  --
76  -- In Arguments:
77  --
78  -- Post Success:
79  --   A returning record structure will be returned.
80  --
81  -- Post Failure:
82  --   No direct error handling is required within this function. Any possible
83  --   errors within this function will be a PL/SQL value error due to conversion
84  --   of datatypes or data lengths.
85  --
86  -- Developer Implementation Notes:
87  --   None.
88  --
89  -- Access Status:
90  --   Internal Table Handler Use Only.
91  --
92  -- {End Of Comments}
93   function ref_info_rec(
94    p_ref_entity_NAME IN VARCHAR2,
95    p_column_info_rec IN column_info_tbl)
96   return ref_entity_rec is
97     ref_info_record ref_entity_rec;
98     l_func varchar2(240) := g_package||'.ref_info_rec';
99   begin
100 
101     if g_debug then
102       hr_utility.set_location('Entering: '||l_func,10);
103     end if;
104 
105     ref_info_record.ref_entity := p_ref_entity_NAME;
106     ref_info_record.column_info := p_column_info_rec;
107 
108     if g_debug then
109       hr_utility.set_location('Leaving: '||l_func,100);
110     end if;
111 
112   return ref_info_record;
113   end;
114 
115   -- If there is only 1 reference entity and 1 column
116   PROCEDURE chk_integrity (
117     p_entity_NAME           IN VARCHAR2,
118     p_ref_entity            IN varchar2,
119     p_ref_column_NAME       IN varchar2,
120     p_ref_col_value_NUMBER  IN number  default null,
121     p_ref_col_value_VARCHAR IN varchar2  default null,
122     p_ref_col_value_DATE    IN date    default null,
123     p_ref_type              IN VARCHAR2) is
124 
125   l_integrity_error varchar2(2000):= 'N';
126   l_func varchar2(240) := g_package||'.chk_integrity prototype 1';
127 
128   begin
129 
130     if g_debug then
131       hr_utility.set_location('Entering: '||l_func,10);
132     end if;
133 
134     per_ric_pkg.chk_integrity(
135       p_entity_NAME     => p_entity_NAME
136       ,p_ref_entity_info =>
137           per_ric_pkg.ref_entity_tbl(
138             ref_info_rec(
139               p_ref_entity_NAME => p_ref_entity
140               ,p_column_info_rec =>
141                  per_ric_pkg.column_info_tbl(
142                    col_info_rec(
143                      column_NAME   => p_ref_column_NAME
144                      ,value_VARCHAR => p_ref_col_value_VARCHAR
145                      ,value_NUMBER  => p_ref_col_value_NUMBER
146                      ,value_DATE    => p_ref_col_value_DATE))))
147       ,p_ref_type => p_ref_type
148       ,p_integrity_error => l_integrity_error);
149 
150     if g_debug then
151       hr_utility.set_location('Leaving: '||l_func,100);
152     end if;
153 
154   end;
155 
156   -- If there is only 1 reference entity and 1 column and the error name is needed in the OUT parameter.
157   PROCEDURE chk_integrity (
158     p_entity_NAME           IN VARCHAR2,
159     p_ref_entity            IN varchar2,
160     p_ref_column_NAME       IN varchar2,
161     p_ref_col_value_NUMBER  IN number  default null,
162     p_ref_col_value_VARCHAR IN number  default null,
163     p_ref_col_value_DATE    IN date    default null,
164     p_ref_type              IN VARCHAR2,
165     p_integrity_error       IN OUT nocopy VARCHAR2) is
166 
167    l_proc varchar2(240) := g_package||'.chk_integrity prototype 2';
168 
169   begin
170 
171     if g_debug then
172       hr_utility.set_location('Entering: '||l_proc,10);
173     end if;
174 
175     per_ric_pkg.chk_integrity(
176       p_entity_NAME     => p_entity_NAME
177       ,p_ref_entity_info =>
178           per_ric_pkg.ref_entity_tbl(
179             ref_info_rec(
180               p_ref_entity_NAME => p_ref_entity
181               ,p_column_info_rec =>
182                  per_ric_pkg.column_info_tbl(
183                    col_info_rec(
184                      column_NAME   => p_ref_column_NAME
185                      ,value_VARCHAR => p_ref_col_value_VARCHAR
186                      ,value_NUMBER  => p_ref_col_value_NUMBER
187                      ,value_DATE    => p_ref_col_value_DATE))))
188       ,p_ref_type => p_ref_type
189       ,p_integrity_error => p_integrity_error);
190 
191     if g_debug then
192       hr_utility.set_location('Leaving: '||l_proc,100);
193     end if;
194 
195   end;
196 
197   -- If there is 1 reference entity and more than 1 columns.
198   PROCEDURE chk_integrity (
199     p_entity_NAME          IN VARCHAR2,
200     p_ref_entity           IN varchar2,
201     p_ref_column_info      IN column_info_tbl,
202     p_ref_type             IN VARCHAR2) is
203 
204   l_integrity_error varchar2(2000):='N';
205   l_proc varchar2(240) := g_package||'.chk_integrity prototype 3';
206 
207   begin
208 
209     if g_debug then
210       hr_utility.set_location('Entering: '||l_proc,10);
211     end if;
212 
213     per_ric_pkg.chk_integrity(
214       p_entity_NAME     => p_entity_NAME
215       ,p_ref_entity_info =>
216           per_ric_pkg.ref_entity_tbl(
217             ref_info_rec(
218               p_ref_entity_NAME => p_ref_entity
219               ,p_column_info_rec => p_ref_column_info))
220       ,p_ref_type => p_ref_type
221       ,p_integrity_error => l_integrity_error);
222 
223     if g_debug then
224       hr_utility.set_location('Leaving: '||l_proc,100);
225     end if;
226 
227   end;
228 
229   -- If there is 1 reference entities and more than 1 columns and the error name is needed in the OUT parameter.
230   PROCEDURE chk_integrity (
231     p_entity_NAME          IN VARCHAR2,
232     p_ref_entity           IN varchar2,
233     p_ref_column_info      IN column_info_tbl,
234     p_ref_type             IN VARCHAR2,
235     p_integrity_error      IN OUT nocopy VARCHAR2) is
236 
237   l_proc varchar2(240) := g_package||'.chk_integrity prototype 4';
238 
239   begin
240 
241     if g_debug then
242       hr_utility.set_location('Entering: '||l_proc,10);
243     end if;
244 
245     per_ric_pkg.chk_integrity(
246       p_entity_NAME     => p_entity_NAME
247       ,p_ref_entity_info =>
248           per_ric_pkg.ref_entity_tbl(
249             ref_info_rec(
250               p_ref_entity_NAME => p_ref_entity
251               ,p_column_info_rec => p_ref_column_info))
252       ,p_ref_type => p_ref_type
253       ,p_integrity_error => p_integrity_error);
254 
255     if g_debug then
256       hr_utility.set_location('Leaving: '||l_proc,100);
257     end if;
258 
259   end;
260 
261 
262   -- If there are more than 1 reference entities and more than 1 columns.
263   PROCEDURE chk_integrity (
264     p_entity_NAME          IN  VARCHAR2,
265     p_ref_entity_info      IN  ref_entity_tbl,
266     p_ref_type             IN  VARCHAR2) is
267 
268    l_proc varchar2(240) := g_package||'.chk_integrity prototype 5';
269    l_integrity_error varchar2(2000):= 'N';
270 
271   begin
272 
273     if g_debug then
274       hr_utility.set_location('Entering: '||l_proc,10);
275     end if;
276 
277     per_ric_pkg.chk_integrity(
278       p_entity_NAME      => p_entity_NAME
279       ,p_ref_entity_info => p_ref_entity_info
280       ,p_ref_type        => p_ref_type
281       ,p_integrity_error => l_integrity_error);
282 
283     if g_debug then
284       hr_utility.set_location('Leaving: '||l_proc,100);
285     end if;
286 
287   end;
288 
289   -- If there are more than 1 reference entities and more than 1 columns and the error name is needed in the OUT parameter..
290 
291   -- ---------------------------------------------------------------------------+
292   -- |--------------------------< chk_integrity >-------------------------------|
293   -- ---------------------------------------------------------------------------+
294   -- Description:
295   --  To check the referencial integrity of an entity.
296   --
297   -- Pre Conditions:
298   --   A variable of ref_entity_tbl table type has been populated with details of the entities need to check
299   --   for the mail entry.
300   --
301   -- In Parameters:
302   --   Name                Reqd  Type             Description
303   --   p_entity_NAME        Yes  varchar2         Name of the entity
304   --                                              for which the reference check will execute.
305   --   p_ref_entity_info    Yes  ref_entity_tbl   This pl-sql table contains the information
306   --                                              of the entities which are used to maintain
307   --                                              the referencial relation with the main entity.
308   --   p_ref_type           Yes  varchar2         Define the type of referential integrity check,
309   --                                              either 'INS' or 'DEL'.
310   --   p_integrity_error    Yes  VARCHAR2         If this parameter is passed 'Y' then the procedure
311   --                                              will return error message in the same parameter
312   --                                              else the procedure will raise an error if the
313   --                                              referential integrity voilates.
314   --
315   -- Post Success:
316   --   No error will be raised.
317   --
318   -- Post Failure:
319   --   An error is raised if the correct reference has not found.
320   --
321   -- Developer Implementation Notes:
322   -- For the 'Zero Down Time' project, Foreign Key constraints on the seed tables are deleted.
323   -- So this procedure is created to maintain the integrity of the seed tables.
324   --
325   -- All the input parameters are mandatory. An error will be raised if any
326   -- input parameter is passed as NULL.
327   --
328   -- All the reference entities passed to parameter 'p_ref_entities' must
329   -- exist in the database. If any entity does not exist this procedure will
330   -- raise an error.
331   --
332   -- Once above checks are passed, SQL statements are prepared and executed
333   -- to check the referencial integrity.
334   --
335   -- If the above executed SQL fetches the results then the validation is done
336   -- whether the entity is being checked for INS/DEL operation and then this will
337   -- raise an error accordingly(if any).
338   --
339   -- Access Status:
340   --   Internal Development Use Only.
341 
342   PROCEDURE chk_integrity (
343     p_entity_NAME          IN  VARCHAR2,
344     p_ref_entity_info      IN  ref_entity_tbl,
345     p_ref_type             IN  VARCHAR2,
346     p_integrity_error      IN OUT nocopy VARCHAR2)
347 
348   IS
349 
350     l_proc                varchar2(240) := g_package||'.chk_integrity MAIN';
351 
352     l_num_of_enity_rec          NUMBER := 0;
353     l_num_of_column_rec         NUMBER := 0;
354 
355     l_sql_condition       VARCHAR2(2000) := NULL;
356     l_sql_stmt            VARCHAR2(2000) := NULL;
357     l_table_NAME          VARCHAR2(240)  := NULL;
358     l_exists              NUMBER := NULL; --changed for bug 12643264
359     l_argument            VARCHAR2(240);
360     l_counter             NUMBER;
361 
362     e_integrity_constraint EXCEPTION;
363     PRAGMA EXCEPTION_INIT(e_integrity_constraint,-02291);
364 
365   BEGIN
366 
367     if g_debug then
368       hr_utility.set_location('Entering: '||l_proc,10);
369     end if;
370 		--
371 		-- Checking whether a NULL parameter is passed to the procedure
372 		--
373     IF p_entity_NAME IS NULL
374      OR p_ref_entity_info.COUNT = 0
375      OR p_ref_type IS NULL
376     THEN
377       --
378       IF p_entity_NAME IS NULL THEN
379         l_argument := 'p_entity_NAME';
383         l_argument := 'p_ref_type';
380       ELSIF p_ref_entity_info.COUNT = 0 THEN
381         l_argument := 'p_ref_entities';
382       ELSIF p_ref_type IS NULL THEN
384       END IF;
385 
386       hr_utility.set_message(801, 'HR_7207_API_MANDATORY_ARG');
387       hr_utility.set_message_token('API_NAME', 'per_integrity_check_pkg');
388 			hr_utility.set_message_token('ARGUMENT', l_argument);
389       hr_utility.raise_error;
390       --
391     END IF;
392 
393     if g_debug then
394       hr_utility.set_location('p_entity_NAME: '||p_entity_NAME,20);
395     end if;
396 		--
397 		-- Checking p_ref_type passed is either INS/DEL to raise the
398 		-- error(if INS/DEL is not passed).
399 		--
400 		IF p_ref_type IS NOT NULL and upper(p_ref_type) NOT IN ('INS', 'DEL')
401 		THEN
402 				Raise_application_error(-20020,
403           'Error: p_ref_type passed should be either INS or DEL.');
404 		END IF;
405 
406 		--
407 		-- Checking p_entity_NAME passed exists in DB or not to raise the
408 		-- error(if the entity doe not exist).
409 		--
410     BEGIN
411         l_sql_stmt := 'SELECT 1 FROM '
412                       || p_entity_NAME;
413 
414         EXECUTE IMMEDIATE l_sql_stmt;
415 
416     EXCEPTION
417         WHEN OTHERS THEN
418           Raise_application_error(-20021,
419           'Error: Entity name passed is incorrect');
420     END;
421 
422     if g_debug then
423       hr_utility.set_location('p_ref_type: '||p_ref_type,30);
424     end if;
425     --
426 		-- Checking whether the passed entities in pl-sql table p_ref_entities exists or not
427 		--
428      FOR j IN 1..p_ref_entity_info.COUNT LOOP
429        l_sql_stmt := NULL;
430        l_table_NAME := to_char(p_ref_entity_info(j).ref_entity);
431 
432        l_sql_stmt := 'SELECT 1 FROM '
433                      || l_table_NAME;
434 
435        if g_debug then
436          hr_utility.set_location('p_ref_table_NAME: '||l_table_NAME,40);
437        end if;
438        --
439        BEGIN
440          EXECUTE IMMEDIATE l_sql_stmt;
441        EXCEPTION
442          WHEN OTHERS THEN
443            Raise_application_error(-20022,
444            'Error: The referring entities passed are not correct'
445            );
446        END;
447        --
448 
449     END LOOP;
450 
451     l_table_NAME    := NULL;
452     l_sql_condition := NULL;
453     l_sql_stmt      := NULL;
454 
455     l_num_of_enity_rec := p_ref_entity_info.COUNT;
456 
457 	  --
458 		-- Preparing the SQL statement for checking the referential integrity
459 		-- between the entities passed.
460 		--
461     IF p_ref_entity_info.count > 0 THEN
462       FOR i IN 1..l_num_of_enity_rec LOOP
463 					l_table_NAME := p_ref_entity_info(i).ref_entity;
464           l_num_of_column_rec := p_ref_entity_info(i).column_info.count;
465           l_sql_condition := null;
466           l_exists:= NULL; --Added for bug 12643264
467 
468           For j In 1..l_num_of_column_rec loop
469            IF p_ref_entity_info(i).column_info(j).value_VARCHAR IS NOT NULL THEN
470             IF l_sql_condition IS NULL THEN
471               l_sql_condition := p_ref_entity_info(i).column_info(j).column_NAME
472                         ||' = '''
473                         ||p_ref_entity_info(i).column_info(j).value_VARCHAR
474                         ||'''';
475             ELSE
476               l_sql_condition := l_sql_condition
477                         ||'  and  '
478                         ||p_ref_entity_info(i).column_info(j).column_NAME
479                         ||' = '''
480                         ||p_ref_entity_info(i).column_info(j).value_VARCHAR
481                         ||'''';
482             END IF;
483            ELSIF p_ref_entity_info(i).column_info(j).value_NUMBER IS NOT NULL THEN
484             IF l_sql_condition IS NULL THEN
485               l_sql_condition := p_ref_entity_info(i).column_info(j).column_NAME
486                         ||' = '
487                         ||p_ref_entity_info(i).column_info(j).value_NUMBER;
488 						 hr_utility.set_location(l_sql_condition,300);
489             ELSE
490               l_sql_condition := l_sql_condition
491                         ||'  and  '
492                         ||p_ref_entity_info(i).column_info(j).column_NAME
493                         ||' = '
494                         ||p_ref_entity_info(i).column_info(j).value_NUMBER;
495             END IF;
496            ELSIF p_ref_entity_info(i).column_info(j).value_DATE IS NOT NULL THEN
497             IF l_sql_condition IS NULL THEN
498               l_sql_condition := p_ref_entity_info(i).column_info(j).column_NAME
499                         ||' = '
500                         ||p_ref_entity_info(i).column_info(j).value_DATE;
501             ELSE
502               l_sql_condition := l_sql_condition
503                         ||'  and  '
504                         ||p_ref_entity_info(i).column_info(j).column_NAME
505                         ||' = '
506                         ||p_ref_entity_info(i).column_info(j).value_DATE;
507             END IF;
508           END IF;
509       END LOOP;
510 
511       if l_sql_condition is not null then
512         --
513         l_sql_stmt   := 'SELECT COUNT(1) FROM '
514                         ||l_table_NAME
515                         ||' where '
516                         ||l_sql_condition;
517          if g_debug then
518            --
519            l_counter := 1;
520            while l_counter < length(l_sql_stmt)
521            loop
522              hr_utility.set_location(substr(l_sql_stmt,l_counter,l_counter+70),60);
523              l_counter := l_counter + 70;
524            end loop;
528 
525            --
526          end if;
527          --
529          EXECUTE IMMEDIATE l_sql_stmt INTO l_exists; -- changed for bug 12554707
530 
531       end if;
532 
533       if l_exists > 0 AND p_ref_type = 'DEL' then
534             exit;
535       end if;
536 
537 		 end loop;
538     END IF;
539 
540 	  --
541 		-- Checking the type of operation performed on the entity passed to raise
542 		-- the appropriate error(if the referential integrity is failing).
543 	  --
544     IF l_exists <> 0 AND p_ref_type = 'DEL' and p_integrity_error = 'N' THEN
545         raise e_integrity_constraint;
546     ELSIF l_exists = 0 AND p_ref_type = 'INS' and p_integrity_error = 'N' THEN
547         raise e_integrity_constraint;
548     ELSIF l_exists <> 0 AND p_ref_type = 'DEL' and p_integrity_error <> 'N' then
549        p_integrity_error :=  p_entity_NAME||'.'||p_ref_type||'_REFERENTIAL_INTEGRITY_VIOLATED';
550     ELSIF l_exists = 0 AND p_ref_type = 'INS' and p_integrity_error <> 'N' THEN
551        p_integrity_error := p_entity_NAME||'.'||p_ref_type||'_REFERENTIAL_INTEGRITY_VIOLATED';
552     END IF;
553 
554     --
555 		-- Executing the SQL prepared in the above code.
556 		--
557 
558     if g_debug then
559       hr_utility.set_location('Leaving: '||l_proc,100);
560     end if;
561 
562  --
563  -- Exception to throw the referential integrity error.
564  --
565 
566  EXCEPTION
567   WHEN e_integrity_constraint THEN
568     if g_debug then
569       hr_utility.set_location('Exception Leaving: '||l_proc,100);
570     end if;
571     hr_utility.set_message(801, 'HR_7877_API_INVALID_CONSTRAINT');
572     hr_utility.set_message_token('PROCEDURE', l_proc);
573     hr_utility.set_message_token('CONSTRAINT_NAME',p_entity_NAME||'.'||p_ref_type||'_REFERENTIAL_INTEGRITY');
574     hr_utility.raise_error;
575 END;
576 
577 END per_ric_pkg;