DBA Data[Home] [Help]

PACKAGE BODY: APPS.HRI_BPL_ABV

Source


1 PACKAGE BODY hri_bpl_abv AS
2 /* $Header: hribabv.pkb 120.2 2008/05/22 08:54:12 smohapat noship $ */
3 
4 /* Global variables for formula ids based on business group id */
5 /* to improve performance where more than one person from the  */
6 /* same business group is being used */
7 
8 /* Type of record stored in a global temporary table */
9 TYPE budget_formula_rec IS RECORD(
10        fte_formula_id              NUMBER,
11        head_formula_id             NUMBER);
12 
13 /* Global temporary table used to store fast formula ids for a business group */
14 TYPE g_budget_formula_tabtype IS TABLE OF budget_formula_rec
15    INDEX BY BINARY_INTEGER;
16 
17 /* g_formula_ids will be indexed by business group id and hold the fast */
18 /* formulae to be used when no value is stored in the ABV table for a   */
19 /* person in that business group */
20 g_formula_ids     g_budget_formula_tabtype;
21 
22 /* Cache of formula names for uncompiled formulae */
23 TYPE g_formula_names_type IS TABLE OF VARCHAR2(80) INDEX BY BINARY_INTEGER;
24 
25 g_formula_names_tab    g_formula_names_type;
26 g_template_head_id     NUMBER;
27 g_formula_type_id      NUMBER;
28 --
29 -- Set to true to output to a concurrent log file
30 --
31 g_conc_request_id         NUMBER := fnd_global.conc_request_id;
32 --
33 -- Debuging flag
34 --
35 g_debug_flag              VARCHAR2(1) := NVL(fnd_profile.value('HRI_ENBL_DTL_LOG'),'N');
36 --
37 -- Inserts row into concurrent program log
38 --
39 PROCEDURE output(p_text  VARCHAR2) IS
40 BEGIN
41   --
42   IF (g_conc_request_id is not null) THEN
43     --
44     -- Write to the concurrent request log
45     --
46     fnd_file.put_line(fnd_file.log, p_text);
47     --
48   ELSE
49     --
50     hr_utility.trace(p_text);
51     --
52   END IF;
53   --
54 END output;
55 --
56 -- -----------------------------------------------------------------------------
57 -- Inserts row into concurrent program log if debugging is enabled
58 -- -----------------------------------------------------------------------------
59 --
60 PROCEDURE dbg(p_text  VARCHAR2) IS
61 --
62 BEGIN
63 --
64   IF (g_debug_flag = 'Y' ) THEN
65     --
66     -- Write to output
67     --
68     output(p_text);
69     --
70   END IF;
71 --
72 END dbg;
73 /******************************************************************************/
74 /* Function which, given a budget type and a business group id, retrieves the */
75 /* formula id of the ABV Fast Formula to be run.
76 /******************************************************************************/
77 FUNCTION fetch_formula_id(p_business_group_id  IN NUMBER,
78                           p_budget_type       IN VARCHAR2)
79                   RETURN NUMBER IS
80   --
81   -- The customer formula is called 'BUDGET_<budget type>'
82   --
83   CURSOR customer_formula_csr IS
84   SELECT fff.formula_id
85   FROM ff_formulas_f fff
86   WHERE fff.formula_type_id = g_formula_type_id
87   AND fff.business_group_id = p_business_group_id
88   AND trunc(sysdate) BETWEEN fff.effective_start_date AND fff.effective_end_date
89   AND fff.formula_name = 'BUDGET_' || p_budget_type;
90   --
91   -- The template formula is called 'TEMPLATE_<budget type>'
92   --
93   CURSOR template_formula_csr IS
94   SELECT fff.formula_id
95   FROM ff_formulas_f fff
96   WHERE fff.formula_type_id = g_formula_type_id
97   AND fff.business_group_id IS NULL
98   AND trunc(sysdate) BETWEEN fff.effective_start_date AND fff.effective_end_date
99   AND fff.formula_name = 'TEMPLATE_' || p_budget_type;
100   --
101   -- The customer formula is called 'GLOBAL_BUDGET_<budget type>'
102   --
103   CURSOR global_formula_csr IS
104   SELECT fff.formula_id
105   FROM   ff_formulas_f fff
106   WHERE  fff.formula_type_id = g_formula_type_id
107   AND    fff.business_group_id = 0
108   AND    trunc(sysdate) BETWEEN fff.effective_start_date AND fff.effective_end_date
109   AND    fff.formula_name = 'GLOBAL_BUDGET_' || p_budget_type;
110   --
111   l_temp_formula_id     NUMBER;  -- Variable to hold retrieved formula id
112   --
113 BEGIN
114   --
115   -- Try and retrieve a customer formula
116   --
117   OPEN customer_formula_csr;
118   FETCH customer_formula_csr INTO l_temp_formula_id;
119   CLOSE customer_formula_csr;
120   --
121   IF l_temp_formula_id is not null THEN
122     --
123     dbg('Using BUDGET_'||p_budget_type||' for bg = '||p_business_group_id);
124     --
125     RETURN l_temp_formula_id;
126     --
127   END IF;
128   --
129   -- 4273256 Customers can define a single formula for all business group
130   -- This formulas should be defined in the setup businesss group
131   -- and will only be invoked when the BUDGET formula is not defined
132   -- If no customer formula exists try the global formula defined in setup bg
133   --
134   OPEN  global_formula_csr;
135   FETCH global_formula_csr INTO l_temp_formula_id;
136   CLOSE global_formula_csr;
137   --
138   IF l_temp_formula_id is not null THEN
139     --
140     dbg('Using GLOBAL_BUDGET_'||p_budget_type||' formulas for bg = '||p_business_group_id);
141     --
142     RETURN l_temp_formula_id;
143     --
144   END IF;
145   --
146   -- If no global formula exists try the template formula
147   --
148   OPEN template_formula_csr;
149   FETCH template_formula_csr INTO l_temp_formula_id;
150   CLOSE template_formula_csr;
151   --
152   dbg('Using TEMPLATE_'||p_budget_type||' formulas for bg = '||p_business_group_id);
153   --
154   RETURN l_temp_formula_id;
155   --
156 END fetch_formula_id;
157 
158 /******************************************************************************/
159 /* This returns the assignment budget value of an applicant given their       */
160 /* assignment, the vacancy they are applying for, the effective date          */
161 /* the budget measurement type (BMT) and the applicant's business group       */
162 /*                                                                            */
163 /* Firstly the actual assignment budget value table is checked                */
164 /* Then the fast formula associated with the business group and BMT is run    */
165 /******************************************************************************/
166 FUNCTION calc_abv(p_assignment_id     IN NUMBER,
167                   p_business_group_id IN NUMBER,
168                   p_budget_type       IN VARCHAR2,
169                   p_effective_date    IN DATE,
170                   p_primary_flag      IN VARCHAR2 := NULL,
171                   p_run_formula       IN VARCHAR2 := NULL)
172 RETURN NUMBER IS
173   --
174   l_return_value    NUMBER := to_number(null);  -- Keeps the ABV to be returned
175   l_formula_id      NUMBER;                 -- Id of the Fast Formula to be run
176   l_inputs          ff_exec.inputs_t;
177   l_outputs         ff_exec.outputs_t;
178   --
179   -- Selects applicant's assignment budget value from the ABV table for a given
180   -- budget_measurement type (if it exists)
181   --
182   CURSOR applicant_csr IS
183   SELECT abv.value
184   FROM   per_assignment_budget_values_f abv
185   WHERE  abv.assignment_id = p_assignment_id
186   AND    abv.unit = p_budget_type
187   AND    p_effective_date BETWEEN abv.effective_start_date
188                           AND abv.effective_end_date;
189   --
190 BEGIN
191   --
192   IF (p_run_formula IS NULL) THEN
193     --
194     -- Try and find an ABV in the ABV table
195     --
196     OPEN applicant_csr;
197     FETCH applicant_csr INTO l_return_value;
198     CLOSE applicant_csr;
199     --
200   END IF;
201   --
202   -- If no ABV was found then get a fast formula
203   --
204   IF l_return_value IS NULL THEN
205     --
206     -- Split out by p_budget_type to make use of stored formula ids
207     --
208     IF (p_budget_type='HEAD') THEN
209       --
210       ----------------------------------------------------------------------------
211       -- Check stored table for formula id of formula to run.
212       --
213       --   - If a record has not yet been stored for the business group then
214       --     a "NO_DATA_FOUND" error is automatically raised.
215       --
216       --   - If a record has been stored for the business group, but not for
217       --     the head_formula_id, then the same error is raised when
218       --     head_formula_id shows as NULL.
219       --
220       -- In the error handling section the formula id is retrieved and stored
221       -- in the temporary. The use of the EXCEPTION section in this way
222       -- requires an enclosed PL/SQL block to trap any unforseen errors which
223       -- may occur within the EXCEPTION section.
224       ----------------------------------------------------------------------------
225       --
226       BEGIN
227         --
228         -- If value exists in global temporary table
229         -- Note that if no entry exists in g_formula_ids for p_business_group
230         -- then a NO_DATA_FOUND error will automatically be raised when it is
231         -- referenced
232         --
233         IF (g_formula_ids(p_business_group_id).head_formula_id IS NOT NULL) THEN
234           --
235           -- Use the stored value
236           --
237           l_formula_id := g_formula_ids(p_business_group_id).head_formula_id;
238           --
239         ELSE
240           --
241           -- fte_formula_id stored for p_business_group, but head_formula_id
242           -- is not
243           --
244           RAISE NO_DATA_FOUND;
245           --
246         END IF;
247         --
248       EXCEPTION
249         WHEN NO_DATA_FOUND THEN
250           --
251           -- Value not already stored
252           -- Fetch formula id for the business group and budget type
253           --
254           l_formula_id := fetch_formula_id(p_business_group_id,p_budget_type);
255           --
256           -- Store it in the temporary table for future use
257           --
258           g_formula_ids(p_business_group_id).head_formula_id := l_formula_id;
259           --
260       END;
261     ----------------------------------------------------------------------------
262     ELSIF (p_budget_type='FTE') THEN
263       --
264       -- Check temporary table
265       --
266       --------------------------------------------------------------------------
267       -- As above, but for the fte_formula_id
268       --------------------------------------------------------------------------
269       BEGIN
270         --
271         -- If value exists in global temporary table
272         -- Note that if no entry exists in g_formula_ids for p_business_group
273         -- then a NO_DATA_FOUND error will automatically be raised when it is
274         -- referenced
275         --
276         IF (g_formula_ids(p_business_group_id).fte_formula_id IS NOT NULL) THEN
277           --
278           -- Use the stored value
279           --
280           l_formula_id := g_formula_ids(p_business_group_id).fte_formula_id;
281           --
282         ELSE
283           --
284           -- head_formula_id stored for p_business_group, but fte_formula_id
285           -- is not
286           --
287           RAISE NO_DATA_FOUND;
288           --
289         END IF;
290         --
291       EXCEPTION
292         WHEN NO_DATA_FOUND THEN
293           --
294           -- Value not already stored
295           -- Fetch formula id for the business group and budget type
296           --
297           l_formula_id := fetch_formula_id(p_business_group_id,p_budget_type);
298           --
299           -- Store it in the temporary table for future use
300           --
301           g_formula_ids(p_business_group_id).fte_formula_id := l_formula_id;
302           --
303       END;
304     ----------------------------------------------------------------------------
305     ELSE
306       --
307       -- Budget type is not 'HEAD' or 'FTE' so no formula id for this
308       -- budget type is held in the temporary table
309       -- Fetch formula id for the business group and budget type
310       --
311       l_formula_id := fetch_formula_id(p_budget_type,p_business_group_id);
312       --
313     END IF;
314     --
315     -- If the fast formula does not exist then raise an error
316     --
317     IF (l_formula_id IS NULL) THEN
318       --
319       raise_ff_not_exist( p_budget_type );
320       --
321     END IF;
322     --
323     -- If the formula to run is TEMPLATE_HEAD and primary flag has been passed
324     -- then don't run the formula
325     --
326     IF (l_formula_id  = g_template_head_id AND
327         p_budget_type = 'HEAD' AND
328         p_primary_flag IS NOT NULL)
329     THEN
330       --
331       IF (p_primary_flag = 'Y') THEN
332         l_return_value := 1;
333       ELSE
334         l_return_value := 0;
335       END IF;
336       --
337     ELSE
338       --
339       -- Initialise the Inputs and  Outputs tables
340       --
341       FF_Exec.Init_Formula
342         ( l_formula_id
343         , SYSDATE
344         , l_inputs
345         , l_outputs );
346       --
347       IF (l_inputs.first IS NOT NULL AND l_inputs.last IS NOT NULL)
348       THEN
349         --
350         -- Set up context values for the formula
351         --
352         FOR i IN l_inputs.first..l_inputs.last LOOP
353           --
354           IF l_inputs(i).name = 'DATE_EARNED' THEN
355             l_inputs(i).value := FND_Date.Date_To_Canonical (p_effective_date);
356           ELSIF l_inputs(i).name = 'ASSIGNMENT_ID' THEN
357             l_inputs(i).value := p_assignment_id;
358           END IF;
359           --
360         END LOOP;
361         --
362       END IF;
363       --
364       -- Run the formula
365       --
366       FF_Exec.Run_Formula (l_inputs, l_outputs);
367       --
368       -- Get the result
369       --
370       l_return_value := FND_NUMBER.canonical_to_number( l_outputs(l_outputs.first).value );
371       --
372     END IF;
373     --
374   END IF;
375   --
376   RETURN l_return_value;
377   --
378 EXCEPTION
379   --
380   -- Normally due to Fast Formula not being compiled
381   --
382   WHEN OTHERS THEN
383     --
384     raise_ff_not_compiled( l_formula_id );
385     --
386 END calc_abv;
387 /******************************************************************************/
388 /* The CheckFastFormulaCompiled procedure should be called from the "Before   */
389 /* Report Trigger" of a report in all reports which use a fast formula.  It   */
390 /* checks if the fast formula exists and whether it is compiled. If not, then */
391 /* it raises the appropriate exception for the report trigger to catch and    */
392 /* display.                                                                   */
393 /******************************************************************************/
394 
395 /******************************************************************************/
396 /* Procedure to raise an exception if a fast formula does not exist           */
397 /******************************************************************************/
398 PROCEDURE raise_ff_not_exist(p_bgttyp IN VARCHAR2)
399 IS
400 BEGIN
401 
402   Fnd_Message.Set_Name('HRI', 'HR_BIS_FF_NOT_EXIST');
403 
404   RAISE ff_not_exist;
405 
406 END raise_ff_not_exist;
407 
408 /******************************************************************************/
409 /* Procedure to raise an exception if a fast formula is not compiled          */
410 /******************************************************************************/
411 PROCEDURE raise_ff_not_compiled( p_formula_id  IN NUMBER)
412 IS
413 
414   CURSOR fast_formula_csr IS
415   SELECT formula_name
416   FROM ff_formulas_f
417   WHERE formula_id = p_formula_id;
418 
419   l_formula_name    ff_formulas_f.formula_name%TYPE := NULL;
420 
421 BEGIN
422 
423 /* Get the formula name */
424   BEGIN
425 
426   /* Try the cache - if there's nothing there then an exception is raised */
427     l_formula_name := g_formula_names_tab(p_formula_id);
428 
429   EXCEPTION
430     WHEN OTHERS THEN
431 
432   /* If nothing's in the cache, get the formula name from the cursor */
433     OPEN  fast_formula_csr;
434     FETCH fast_formula_csr INTO l_formula_name;
435     CLOSE fast_formula_csr;
436 
437   /* Store the name retrieved in the cache for future use */
438     g_formula_names_tab(p_formula_id) := l_formula_name;
439 
440   END;
441 
442   Fnd_Message.Set_Name('HRI', 'HR_BIS_FF_NOT_COMPILED');
443   Fnd_Message.Set_Token('FORMULA', l_formula_name, FALSE);
444 
445   RAISE ff_not_compiled;
446 
447 END raise_ff_not_compiled;
448 
449 /******************************************************************************/
450 /* Procedure to checks if a fast formula exists and whether it is compiled    */
451 /******************************************************************************/
452 PROCEDURE check_ff_name_compiled( p_formula_name     IN VARCHAR2) IS
453 
454   CURSOR compiled_csr IS
455   SELECT fci.formula_id
456   FROM ff_compiled_info_f   fci
457   ,ff_formulas_f            fff
458   WHERE fci.formula_id = fff.formula_id
459   AND fff.formula_type_id = g_formula_type_id
460   AND fff.formula_name = p_formula_name
461   AND trunc(sysdate) BETWEEN fff.effective_start_date AND fff.effective_end_date
462   AND trunc(sysdate) BETWEEN fci.effective_start_date AND fci.effective_end_date;
463 
464   l_formula_id   ff_compiled_info_f.formula_id%TYPE := NULL;
465 
466 BEGIN
467 
468   OPEN compiled_csr;
469   FETCH compiled_csr INTO l_formula_id;
470   CLOSE compiled_csr;
471 
472   IF (l_formula_id IS NULL) THEN
473 
474     Fnd_Message.Set_Name('HRI', 'HR_BIS_FF_NOT_COMPILED');
475     Fnd_Message.Set_Token('FORMULA', p_formula_name, FALSE);
476     RAISE ff_not_compiled;
477 
478   END IF;
479 
480 END check_ff_name_compiled;
481 
482 PROCEDURE CheckFastFormulaCompiled(p_formula_id  IN NUMBER,
483                                    p_bgttyp      IN VARCHAR2)
484 IS
485 
486   CURSOR fast_formula_compiled_csr IS
487   SELECT formula_id
488   FROM   ff_compiled_info_f
489   WHERE  formula_id = p_formula_id;
490 
491   l_formula_id   ff_compiled_info_f.formula_id%TYPE := NULL;
492 
493 BEGIN
494 
495   IF p_formula_id IS NULL THEN
496     raise_ff_not_exist( p_bgttyp );
497   END IF;
498 
499   OPEN fast_formula_compiled_csr;
500   FETCH fast_formula_compiled_csr INTO l_formula_id;
501   CLOSE fast_formula_compiled_csr;
502 
503   IF l_formula_id IS NULL THEN
504     raise_ff_not_compiled( p_formula_id );
505   END IF;
506 
507 END CheckFastFormulaCompiled;
508 
509 BEGIN
510 
511   SELECT formula_type_id INTO g_formula_type_id
512   FROM ff_formula_types
513   WHERE formula_type_name = 'QuickPaint';
514 
515   SELECT formula_id INTO g_template_head_id
516   FROM ff_formulas_f
517   WHERE formula_type_id = g_formula_type_id
518   AND formula_name = 'TEMPLATE_HEAD'
519   AND business_group_id IS NULL
520   AND trunc(sysdate) BETWEEN effective_start_date AND effective_end_date;
521 
522 END hri_bpl_abv;