DBA Data[Home] [Help]

PACKAGE BODY: APPS.GHR_PC_BASIC_PAY

Source


1 PACKAGE BODY ghr_pc_basic_pay AS
2 /* $Header: ghbasicp.pkb 120.29.12020000.2 2012/07/05 13:57:31 amnaraya ship $ */
3 --
4 --
5 
6 FUNCTION get_retained_grade_details (p_person_id      IN NUMBER
7                                     ,p_effective_date IN DATE
8                                     ,p_pa_request_id  IN NUMBER DEFAULT NULL)
9   RETURN ghr_pay_calc.retained_grade_rec_type IS
10 --
11 l_retained_grade_rec        ghr_pay_calc.retained_grade_rec_type;
12 l_last_retained_grade_rec   ghr_pay_calc.retained_grade_rec_type;
13 --
14 l_last_pay_table_value      NUMBER;
15 l_last_pay_table_value_conv NUMBER;
16 l_cur_pay_table_value       NUMBER;
17 --
18 l_record_found              BOOLEAN :=FALSE;
19 --
20 l_dummy_date                DATE;
21 
22 l_noa_code                  ghr_nature_of_actions.code%type;
23 
24 CURSOR cur_par IS
25 SELECT first_noa_code,second_noa_code
26 FROM ghr_pa_requests
27 WHERE pa_request_id = p_pa_request_id;
28 
29 CURSOR cur_temp_step IS
30 SELECT  rei_information3 temp_step
31 FROM    ghr_pa_request_extra_info
32 WHERE   pa_request_id = p_pa_request_id
33 AND     information_type = 'GHR_US_PAR_RG_TEMP_PROMO';
34 
35 --
36 CURSOR cur_pei IS
37   SELECT pei.person_extra_info_id
38          -- Bug#4423679 Added date_from,date_to columns.
39         ,fnd_date.canonical_to_date(pei.pei_information1) date_from
40         ,fnd_date.canonical_to_date(pei.pei_information2) date_to
41     	-- Bug#4423679
42         ,pei.pei_information3     retained_grade
43         ,pei.pei_information4     retained_step_or_rate
44         ,pei.pei_information5     retained_pay_plan
45         ,pei.pei_information6     retained_user_table_id
46   ----  ,pei.pei_information7     retained_locality_percent
47         ,pei.pei_information8     retained_pay_basis
48         ,pei.pei_information9     retained_temp_step
49   FROM   per_people_extra_info pei
50   WHERE  pei.person_id = p_person_id
51   AND    pei.information_type = 'GHR_US_RETAINED_GRADE'
52   AND    p_effective_date BETWEEN NVL(fnd_date.canonical_to_date(pei.pei_information1),p_effective_date)
53                           AND     NVL(fnd_date.canonical_to_date(pei.pei_information2),p_effective_date)
54   AND    fnd_date.canonical_to_date(pei.pei_information1) =
55                            (SELECT MIN (NVL(fnd_date.canonical_to_date(pei2.pei_information1),p_effective_date) )
56                             FROM   per_people_extra_info pei2
57                             WHERE  pei2.person_id = p_person_id
58                             AND    pei2.information_type = 'GHR_US_RETAINED_GRADE'
59                             AND    p_effective_date
60                                    BETWEEN NVL(fnd_date.canonical_to_date(pei2.pei_information1),p_effective_date)
61                                        AND NVL(fnd_date.canonical_to_date(pei2.pei_information2),p_effective_date)
62                             AND    to_char(pei2.person_extra_info_id) NOT IN (SELECT rei_information3
63                                           FROM   ghr_pa_request_extra_info rei
64                                           WHERE  pa_request_id = p_pa_request_id
65                                           AND    (rei_information5 is null OR rei_information5 = 'Y')
66 					    --Bug # 5584845
67                                           AND    ((information_type = 'GHR_US_PAR_TERM_RET_GRADE'
68 					          AND
69 						  fnd_date.canonical_to_date(rei_information6) = (select MIN (NVL(fnd_date.canonical_to_date(rei2.rei_information6),p_effective_date) )
70                                                                                                   FROM   ghr_pa_request_extra_info rei2
71                                                                                                   WHERE  pa_request_id = rei.pa_request_id
72                                                                                                   AND    information_type = rei.information_type)
73 						  )
74 						  OR
75                                                   information_type in ('GHR_US_PAR_TERM_RG_PROMO',
76                                                                        'GHR_US_PAR_TERM_RG_POSN_CHG')))
77                                          --Bug # 5584845
78                             )
79   AND    to_char(pei.person_extra_info_id) NOT IN (SELECT rei_information3
80                                           FROM   ghr_pa_request_extra_info rei
81                                           WHERE  pa_request_id = p_pa_request_id
82 					  AND    (rei_information5 is null OR rei_information5 = 'Y')
83                                            --Bug # 5584845
84                                           AND    ((information_type = 'GHR_US_PAR_TERM_RET_GRADE'
85 					          AND
86 						  fnd_date.canonical_to_date(rei_information6) = (select MIN (NVL(fnd_date.canonical_to_date(rei2.rei_information6),p_effective_date) )
87                                                                                                   FROM   ghr_pa_request_extra_info rei2
88                                                                                                   WHERE  pa_request_id = rei.pa_request_id
89                                                                                                   AND    information_type = rei.information_type)
90 						  )
91 						  OR
92                                                   information_type in ('GHR_US_PAR_TERM_RG_PROMO',
93                                                                        'GHR_US_PAR_TERM_RG_POSN_CHG')));
94                                          --Bug # 5584845
95 
96 
97 BEGIN
98   -- Just in case there is more than one retained grade with the same earliest start
99   -- date we have to return the one with the highest plan_table_value!!
100   -- I'm sure this is very very unlikely to happen!!
101   hr_utility.set_location(' get_retained_grade_details',1);
102   FOR cur_pei_rec IN cur_pei LOOP
103     hr_utility.set_location(' get_retained_grade_details',2);
104     IF l_record_found THEN
105       -- If we have already been here once store all the last details before we get the new ones
106       -- the main record group will always keep the last highest value!
107       l_last_retained_grade_rec := l_retained_grade_rec;
108     END IF;
109       hr_utility.set_location(' get_retained_grade_details person_extra_info_id' ||l_retained_grade_rec.person_extra_info_id ,3);
110     l_retained_grade_rec.person_extra_info_id :=  cur_pei_rec.person_extra_info_id;
111     -- Bug#4423679 Added date_from, date_to columns in the retained grade record.
112     l_retained_grade_rec.date_from            :=  cur_pei_rec.date_from;
113     l_retained_grade_rec.date_to              :=  cur_pei_rec.date_to;
114     -- Bug#4423679
115     l_retained_grade_rec.grade_or_level       :=  cur_pei_rec.retained_grade;
116     l_retained_grade_rec.step_or_rate         :=  cur_pei_rec.retained_step_or_rate;
117     l_retained_grade_rec.pay_plan             :=  cur_pei_rec.retained_pay_plan;
118     l_retained_grade_rec.user_table_id        :=  cur_pei_rec.retained_user_table_id;
119     l_retained_grade_rec.pay_basis            :=  cur_pei_rec.retained_pay_basis;
120     l_retained_grade_rec.temp_step            :=  cur_pei_rec.retained_temp_step;
121 
122     IF l_retained_grade_rec.grade_or_level IS NULL
123       OR l_retained_grade_rec.step_or_rate IS NULL
124       OR l_retained_grade_rec.pay_plan IS NULL
125       OR l_retained_grade_rec.user_table_id IS NULL
126       OR l_retained_grade_rec.pay_basis IS NULL THEN
127       hr_utility.set_message(8301, 'GHR_38255_MISSING_RETAINED_DET');
128       raise ghr_pay_calc.pay_calc_message;
129     END IF;
130     --
131     IF l_record_found THEN
132 hr_utility.set_location(' get_retained_grade_details ' ,5);
133       -- only if we have previously found a retained record with the same start date do we bother
134       -- getting the values to compare
135       ghr_pay_calc.get_pay_table_value (l_retained_grade_rec.user_table_id
136                                        ,l_retained_grade_rec.pay_plan
137                                        ,l_retained_grade_rec.grade_or_level
138                                        ,l_retained_grade_rec.step_or_rate
139                                        ,p_effective_date
140                                        ,l_cur_pay_table_value
141                                        ,l_dummy_date
142                                        ,l_dummy_date);
143 
144       ghr_pay_calc.get_pay_table_value (l_last_retained_grade_rec.user_table_id
145                                        ,l_last_retained_grade_rec.pay_plan
146                                        ,l_last_retained_grade_rec.grade_or_level
147                                        ,l_last_retained_grade_rec.step_or_rate
148                                        ,p_effective_date
149                                        ,l_last_pay_table_value
150                                        ,l_dummy_date
151                                        ,l_dummy_date);
152 
153       -- if they are different pay basis Convert the last retained ggrade to the pay basis
154       -- of the current
155       IF l_last_retained_grade_rec.pay_basis <> l_retained_grade_rec.pay_basis THEN
156        l_last_pay_table_value_conv := ghr_pay_calc.convert_amount
157                                          (l_last_pay_table_value
158                                          ,l_last_retained_grade_rec.pay_basis
159                                          ,l_retained_grade_rec.pay_basis);
160       ELSE
161         l_last_pay_table_value_conv := l_last_pay_table_value;
162       END IF;
163 
164       -- now compare the two and set the l_retained_grade_rec to the one with the highest value
165       IF NVL(l_last_pay_table_value_conv,-9) > NVL(l_cur_pay_table_value,-9) THEN
166          l_retained_grade_rec := l_last_retained_grade_rec;
167       END IF;
168 
169    END IF;
170 hr_utility.set_location(' get_retained_grade_details ' ,6);
171    l_record_found := TRUE;
172 
173   END LOOP;
174 
175   ------- Start Temp Promotion Code changes for 703 and 866 NOACs.
176   l_noa_code := null;
177   IF p_pa_request_id is not null THEN
178      FOR cur_par_rec IN cur_par LOOP
179          if cur_par_rec.first_noa_code = '002' then
180             l_noa_code := cur_par_rec.second_noa_code;
181          else
182             l_noa_code := cur_par_rec.first_noa_code;
183          end if;
184      EXIT;
185      END LOOP;
186      IF l_noa_code in ('703','866') THEN
187         l_retained_grade_rec.temp_step  := null;
188 		-- Bug 3221361 In case if TPS record is deleted, it shd return NULL as the value.
189 		FOR cur_temp_step_rec IN cur_temp_step LOOP
190 		    l_retained_grade_rec.temp_step  := cur_temp_step_rec.temp_step;
191         END LOOP;
192      END IF;
193   END IF;
194   IF l_noa_code = '740' THEN
195      l_retained_grade_rec.temp_step := NULL;
196   END IF;
197   -------End  Temp Promotion Code changes for 703 and 866 NOACs.
198   hr_utility.set_location(' get_retained_grade_details ' ,7);
199   IF l_record_found THEN
200   hr_utility.set_location(' get_retained_grade_details ' ,7);
201     RETURN (l_retained_grade_rec);
202   ELSE
203     hr_utility.set_message(8301, 'GHR_38256_NO_RETAINED_GRADE');
204     raise ghr_pay_calc.pay_calc_message;
205   END IF;
206 
207 END get_retained_grade_details ;
208 --
209 -- Bug#4016384 Created the following function to get the RG record available
210 --             before the MSL effective date.
211 FUNCTION get_expired_rg_details (p_person_id      IN NUMBER
212                             ,p_effective_date IN DATE
213                             ,p_pa_request_id  IN NUMBER DEFAULT NULL)
214   RETURN ghr_pay_calc.retained_grade_rec_type IS
215 --
216 l_retained_grade_rec        ghr_pay_calc.retained_grade_rec_type;
217 l_last_retained_grade_rec   ghr_pay_calc.retained_grade_rec_type;
218 --
219 l_last_pay_table_value      NUMBER;
220 l_last_pay_table_value_conv NUMBER;
221 l_cur_pay_table_value       NUMBER;
222 --
223 l_record_found              BOOLEAN :=FALSE;
224 --
225 l_dummy_date                DATE;
226 
227 --
228 CURSOR cur_pei IS
229   SELECT pei.person_extra_info_id
230          -- Bug#4423679 Added date_from,date_to columns.
231         ,fnd_date.canonical_to_date(pei.pei_information1) date_from
232         ,fnd_date.canonical_to_date(pei.pei_information2) date_to
233     	-- Bug#4423679
234         ,pei.pei_information3     retained_grade
235         ,pei.pei_information4     retained_step_or_rate
236         ,pei.pei_information5     retained_pay_plan
237         ,pei.pei_information6     retained_user_table_id
238   ----  ,pei.pei_information7     retained_locality_percent
239         ,pei.pei_information8     retained_pay_basis
240         ,pei.pei_information9     retained_temp_step
241   FROM   per_people_extra_info pei
242   WHERE  pei.person_id = p_person_id
243   AND    pei.information_type = 'GHR_US_RETAINED_GRADE'
244   AND    NVL(fnd_date.canonical_to_date(pei.pei_information2),p_effective_date) < p_effective_date
245   AND    fnd_date.canonical_to_date(pei.pei_information1) =
246                            (SELECT MIN (NVL(fnd_date.canonical_to_date(pei2.pei_information1),p_effective_date) )
247                             FROM   per_people_extra_info pei2
248                             WHERE  pei2.person_id = p_person_id
249                             AND    pei2.information_type = 'GHR_US_RETAINED_GRADE'
250                             AND    NVL(fnd_date.canonical_to_date(pei2.pei_information2),p_effective_date) < p_effective_date
251                             AND    pei2.person_extra_info_id NOT IN (SELECT rei_information3
252                                           FROM   ghr_pa_request_extra_info
253                                           WHERE  pa_request_id = p_pa_request_id
254                                           AND    (rei_information5 is null OR rei_information5 = 'Y')
255                                           AND    information_type in ('GHR_US_PAR_TERM_RET_GRADE',
256                                                                       'GHR_US_PAR_TERM_RG_PROMO',
257                                                                       'GHR_US_PAR_TERM_RG_POSN_CHG')
258                                                                       )
259                             )
260   AND    pei.person_extra_info_id NOT IN (SELECT rei_information3
261                                           FROM   ghr_pa_request_extra_info
262                                           WHERE  pa_request_id = p_pa_request_id
263                                           AND    information_type in ( 'GHR_US_PAR_TERM_RET_GRADE',
264                                                                        'GHR_US_PAR_TERM_RG_PROMO',
265                                                                        'GHR_US_PAR_TERM_RG_POSN_CHG')
266                                           AND    (rei_information5 is null OR rei_information5 = 'Y'));
267 
268 
269 BEGIN
270   -- Just in case there is more than one retained grade with the same earliest start
271   -- date we have to return the one with the highest plan_table_value!!
272   -- I'm sure this is very very unlikely to happen!!
273   hr_utility.set_location(' get_expired_rg_details',1);
274   FOR cur_pei_rec IN cur_pei LOOP
275     hr_utility.set_location(' get_expired_rg_details',2);
276     IF l_record_found THEN
277       -- If we have already been here once store all the last details before we get the new ones
278       -- the main record group will always keep the last highest value!
279       l_last_retained_grade_rec := l_retained_grade_rec;
280     END IF;
281       hr_utility.set_location(' get_expired_rg_details person_extra_info_id' ||l_retained_grade_rec.person_extra_info_id ,3);
282     l_retained_grade_rec.person_extra_info_id :=  cur_pei_rec.person_extra_info_id;
283     -- Bug#4423679 Added date_from, date_to columns in the retained grade record.
284     l_retained_grade_rec.date_from            :=  cur_pei_rec.date_from;
285     l_retained_grade_rec.date_to              :=  cur_pei_rec.date_to;
286     -- Bug#4423679
287     l_retained_grade_rec.grade_or_level       :=  cur_pei_rec.retained_grade;
288     l_retained_grade_rec.step_or_rate         :=  cur_pei_rec.retained_step_or_rate;
289     l_retained_grade_rec.pay_plan             :=  cur_pei_rec.retained_pay_plan;
290     l_retained_grade_rec.user_table_id        :=  cur_pei_rec.retained_user_table_id;
291     l_retained_grade_rec.pay_basis            :=  cur_pei_rec.retained_pay_basis;
292     l_retained_grade_rec.temp_step            :=  cur_pei_rec.retained_temp_step;
293 
294     IF l_retained_grade_rec.grade_or_level IS NULL
295       OR l_retained_grade_rec.step_or_rate IS NULL
296       OR l_retained_grade_rec.pay_plan IS NULL
297       OR l_retained_grade_rec.user_table_id IS NULL
298       OR l_retained_grade_rec.pay_basis IS NULL THEN
299       hr_utility.set_message(8301, 'GHR_38255_MISSING_RETAINED_DET');
300       raise ghr_pay_calc.pay_calc_message;
301     END IF;
302     --
303     IF l_record_found THEN
304 hr_utility.set_location(' get_expired_rg_details ' ,5);
305       -- only if we have previously found a retained record with the same start date do we bother
306       -- getting the values to compare
307       ghr_pay_calc.get_pay_table_value (l_retained_grade_rec.user_table_id
308                                        ,l_retained_grade_rec.pay_plan
309                                        ,l_retained_grade_rec.grade_or_level
310                                        ,l_retained_grade_rec.step_or_rate
311                                        ,p_effective_date
312                                        ,l_cur_pay_table_value
313                                        ,l_dummy_date
314                                        ,l_dummy_date);
315 
316       ghr_pay_calc.get_pay_table_value (l_last_retained_grade_rec.user_table_id
317                                        ,l_last_retained_grade_rec.pay_plan
318                                        ,l_last_retained_grade_rec.grade_or_level
319                                        ,l_last_retained_grade_rec.step_or_rate
320                                        ,p_effective_date
321                                        ,l_last_pay_table_value
322                                        ,l_dummy_date
323                                        ,l_dummy_date);
324 
325       -- if they are different pay basis Convert the last retained ggrade to the pay basis
326       -- of the current
327       IF l_last_retained_grade_rec.pay_basis <> l_retained_grade_rec.pay_basis THEN
328        l_last_pay_table_value_conv := ghr_pay_calc.convert_amount
329                                          (l_last_pay_table_value
330                                          ,l_last_retained_grade_rec.pay_basis
331                                          ,l_retained_grade_rec.pay_basis);
332       ELSE
333         l_last_pay_table_value_conv := l_last_pay_table_value;
334       END IF;
335 
336       -- now compare the two and set the l_retained_grade_rec to the one with the highest value
337       IF NVL(l_last_pay_table_value_conv,-9) > NVL(l_cur_pay_table_value,-9) THEN
338          l_retained_grade_rec := l_last_retained_grade_rec;
339       END IF;
340 
341    END IF;
342 hr_utility.set_location(' get_expired_rg_details ' ,6);
343    l_record_found := TRUE;
344 
345   END LOOP;
346 
347   IF l_record_found THEN
348     hr_utility.set_location(' get_expired_rg_details ' ,7);
349     RETURN (l_retained_grade_rec);
350   ELSE
351     hr_utility.set_message(8301, 'GHR_38256_NO_RETAINED_GRADE');
352     raise ghr_pay_calc.pay_calc_message;
353   END IF;
354 
355 END get_expired_rg_details ;
356 --
357 
358 PROCEDURE get_basic_pay_MAIN_per (p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
359                                  ,p_retained_grade    IN  ghr_pay_calc.retained_grade_rec_type
360                                  ,p_basic_pay         OUT NOCOPY NUMBER
361                                  ,p_PT_eff_start_date OUT NOCOPY DATE) IS
362 l_basic_pay  NUMBER;
363 l_dummy_date DATE;
364 BEGIN
365  IF p_retained_grade.temp_step is not null then
366       ghr_pay_calc.get_pay_table_value(p_pay_calc_data.user_table_id
367                                   ,p_pay_calc_data.pay_plan
368                                   ,p_pay_calc_data.grade_or_level
369                                   ,p_retained_grade.temp_step
370                                   ,p_pay_calc_data.effective_date
371                                   ,l_basic_pay
372                                   ,p_PT_eff_start_date
373                                   ,l_dummy_date);
374       p_basic_pay := l_basic_pay;
375   ELSE
376   ghr_pay_calc.get_pay_table_value(p_retained_grade.user_table_id
377                                   ,p_retained_grade.pay_plan
378                                   ,p_retained_grade.grade_or_level
379                                   ,p_retained_grade.step_or_rate
380                                   ,p_pay_calc_data.effective_date
381                                   ,l_basic_pay
382                                   ,p_PT_eff_start_date
383                                   ,l_dummy_date);
384   --
385   -- need to convert to whatever the displayed value is
386   p_basic_pay := ghr_pay_calc.convert_amount(l_basic_pay
387                                             ,p_retained_grade.pay_basis
388                                             ,p_pay_calc_data.pay_basis);
389  END IF;
390 
391 
392 EXCEPTION
393   WHEN others THEN
394      -- Reset IN OUT parameters and set OUT parameters
395 
396        p_basic_pay                 := NULL;
397        p_PT_eff_start_date         := NULL;
398 
399    RAISE;
400 
401 END get_basic_pay_MAIN_per;
402 --
403 PROCEDURE get_min_pay_table_value (p_user_table_id  IN  NUMBER
404                              ,p_pay_plan            IN  VARCHAR2
405                              ,p_grade_or_level      IN  VARCHAR2
406                              ,p_effective_date      IN  DATE
407                              ,p_step_or_rate        OUT NOCOPY VARCHAR2
408                              ,p_PT_value            OUT NOCOPY NUMBER
409                              ,p_PT_eff_start_date   OUT NOCOPY DATE
410                              ,p_PT_eff_end_date     OUT NOCOPY DATE) IS
411 
412 -- for a given pay_plan and grade this returns the minimum value and step
413 l_PT_value       NUMBER;
414 l_record_found      BOOLEAN := FALSE;
415 --
416 CURSOR cur_pay IS
417   SELECT cin.value             basic_pay
418         ,col.user_column_name  step_or_rate
419         ,cin.effective_start_date
420         ,cin.effective_end_date
421   FROM   pay_user_column_instances_f cin
422         ,pay_user_rows_f             urw
423         ,pay_user_columns            col
424   WHERE col.user_table_id = p_user_table_id
425   AND   urw.user_table_id = p_user_table_id
426   AND   urw.row_low_range_or_name = p_pay_plan||'-'||p_grade_or_level
427   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN urw.effective_start_date AND urw.effective_end_date
428   AND   cin.user_row_id = urw.user_row_id
429   AND   cin.user_column_id = col.user_column_id
430   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN cin.effective_start_date AND cin.effective_end_date
431   ORDER BY TO_NUMBER(cin.value) ASC;
432 --
433 -- The order by means we will get the lowest value first
434 BEGIN
435   FOR cur_pay_rec IN cur_pay LOOP
436     p_step_or_rate      := cur_pay_rec.step_or_rate;
437     l_PT_value          := ROUND(cur_pay_rec.basic_pay,2);
438     p_PT_value          := l_PT_value;
439     p_PT_eff_start_date := cur_pay_rec.effective_start_date;
440     p_PT_eff_end_date   := cur_pay_rec.effective_end_date;
441     l_record_found      := TRUE;
442     IF l_PT_value IS NULL THEN
443     -- Set tokens to give name of pay table, pay plan, grade, step and rate
444       hr_utility.set_message(8301,'GHR_38252_NULL_PAY_PLAN_VALUE');
445       hr_utility.set_message_token('PAY_TABLE_NAME',ghr_pay_calc.get_user_table_name(p_user_table_id) );
446       hr_utility.set_message_token('STEP',cur_pay_rec.step_or_rate);
447       hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
448       hr_utility.set_message_token('GRADE',p_grade_or_level);
449 --    hr_utility.set_message_token('EFF_DATE',TO_CHAR(p_effective_date,'DD-MON-YYYY') );
450       hr_utility.set_message_token('EFF_DATE',fnd_date.date_to_chardate(p_effective_date) );
451       raise ghr_pay_calc.pay_calc_message;
452     END IF;
453     EXIT;
454   END LOOP;
455   --
456   IF NOT l_record_found THEN
457     -- Set tokens to give name of pay table, pay plan, grade, step and rate
458     -- Note: the is no step!
459     hr_utility.set_message(8301,'GHR_38257_NO_MIN_PAY_PLAN_VAL');
460     hr_utility.set_message_token('PAY_TABLE_NAME',ghr_pay_calc.get_user_table_name(p_user_table_id) );
461     hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
462     hr_utility.set_message_token('GRADE',p_grade_or_level);
463 --  hr_utility.set_message_token('EFF_DATE',TO_CHAR(p_effective_date,'DD-MON-YYYY') );
464     hr_utility.set_message_token('EFF_DATE',fnd_date.date_to_chardate(p_effective_date) );
465     raise ghr_pay_calc.pay_calc_message;
466   END IF;
467   --
468 
469 EXCEPTION
470   WHEN others THEN
471      -- Reset IN OUT parameters and set OUT parameters
472 
473        p_step_or_rate          := NULL;
474        p_PT_value              := NULL;
475        p_PT_eff_start_date     := NULL;
476        p_PT_eff_end_date       := NULL;
477 
478    RAISE;
479 
480 END get_min_pay_table_value;
481 --
482 PROCEDURE get_max_pay_table_value (p_user_table_id  IN  NUMBER
483                              ,p_pay_plan            IN  VARCHAR2
484                              ,p_grade_or_level      IN  VARCHAR2
485                              ,p_effective_date      IN  DATE
486                              ,p_step_or_rate        OUT NOCOPY VARCHAR2
487                              ,p_PT_value            OUT NOCOPY NUMBER
488                              ,p_PT_eff_start_date   OUT NOCOPY DATE
489                              ,p_PT_eff_end_date     OUT NOCOPY DATE) IS
490 --
491 -- for a given pay_plan and grade this returns the minimum value and step
492 l_PT_value       NUMBER;
493 l_record_found   BOOLEAN := FALSE;
494 --
495 CURSOR cur_pay IS
496   SELECT cin.value             basic_pay
497         ,col.user_column_name  step_or_rate
498         ,cin.effective_start_date
499         ,cin.effective_end_date
500   FROM   pay_user_column_instances_f cin
501         ,pay_user_rows_f             urw
502         ,pay_user_columns            col
503   WHERE col.user_table_id = p_user_table_id
504   AND   urw.user_table_id = p_user_table_id
505   AND   urw.row_low_range_or_name = p_pay_plan||'-'||p_grade_or_level
506   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN urw.effective_start_date AND urw.effective_end_date
507   AND   cin.user_row_id = urw.user_row_id
508   AND   cin.user_column_id = col.user_column_id
509   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN cin.effective_start_date AND cin.effective_end_date
510   ORDER BY TO_NUMBER(cin.value) DESC;
511 --
512 -- The order by means we will get the HIGHEST value first
513 BEGIN
514   FOR cur_pay_rec IN cur_pay LOOP
515     p_step_or_rate      := cur_pay_rec.step_or_rate;
516     l_PT_value          := ROUND(cur_pay_rec.basic_pay,2);
517     p_PT_value          := l_PT_value;
518     p_PT_eff_start_date := cur_pay_rec.effective_start_date;
519     p_PT_eff_end_date   := cur_pay_rec.effective_end_date;
520     l_record_found      := TRUE;
521 
522     IF l_PT_value IS NULL THEN
523     -- Set tokens to give name of pay table, pay plan, grade, step and rate
524       hr_utility.set_message(8301,'GHR_38252_NULL_PAY_PLAN_VALUE');
525       hr_utility.set_message_token('PAY_TABLE_NAME',ghr_pay_calc.get_user_table_name(p_user_table_id) );
526       hr_utility.set_message_token('STEP',cur_pay_rec.step_or_rate);
527       hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
528       hr_utility.set_message_token('GRADE',p_grade_or_level);
529 --    hr_utility.set_message_token('EFF_DATE',TO_CHAR(p_effective_date,'DD-MON-YYYY') );
530       hr_utility.set_message_token('EFF_DATE',fnd_date.date_to_chardate(p_effective_date) );
531       raise ghr_pay_calc.pay_calc_message;
532     END IF;
533     EXIT;
534   END LOOP;
535   --
536   IF NOT l_record_found THEN
537     -- Set tokens to give name of pay table, pay plan, grade, step and rate
538     hr_utility.set_message(8301,'GHR_38258_NO_MAX_PAY_PLAN_VAL');
539     hr_utility.set_message_token('PAY_TABLE_NAME',ghr_pay_calc.get_user_table_name(p_user_table_id) );
540     hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
541     hr_utility.set_message_token('GRADE',p_grade_or_level);
542 --  hr_utility.set_message_token('EFF_DATE',TO_CHAR(p_effective_date,'DD-MON-YYYY') );
543     hr_utility.set_message_token('EFF_DATE',fnd_date.date_to_chardate(p_effective_date) );
544     raise ghr_pay_calc.pay_calc_message;
545   END IF;
546   --
547 
548 EXCEPTION
549   WHEN others THEN
550      -- Reset IN OUT parameters and set OUT parameters
551 
552        p_step_or_rate          := NULL;
553        p_PT_value              := NULL;
554        p_PT_eff_start_date     := NULL;
555        p_PT_eff_end_date       := NULL;
556 
557    RAISE;
558 
559 END get_max_pay_table_value;
560 ---
561 ---
562 --
563 PROCEDURE get_890_pay_table_value (p_user_table_id  IN  NUMBER
564                              ,p_pay_plan            IN  VARCHAR2
565                              ,p_grade_or_level      IN  VARCHAR2
566                              ,p_effective_date      IN  DATE
567                              ,p_current_val         IN  NUMBER
568 			     ,p_in_step_or_rate     IN  VARCHAR2
569                              ,p_step_or_rate        OUT NOCOPY VARCHAR2
570                              ,p_PT_value            OUT NOCOPY NUMBER
571                              ,p_PT_eff_start_date   OUT NOCOPY DATE
572                              ,p_PT_eff_end_date     OUT NOCOPY DATE) IS
573 --
574 -- for a given pay_plan and grade this returns the minimum value and step
575 l_PT_value       NUMBER;
576 l_record_found   BOOLEAN := FALSE;
577 ---BUG 6211029
578 l_in_PT_value    NUMBER;
579 l_in_PT_eff_start_date  DATE;
580 l_in_PT_eff_end_date    DATE;
581 -- BUG 6211029
582 --
583 CURSOR cur_pay IS
584   SELECT cin.value             basic_pay
585         ,col.user_column_name  step_or_rate
586         ,cin.effective_start_date
587         ,cin.effective_end_date
588   FROM   pay_user_column_instances_f cin
589         ,pay_user_rows_f             urw
590         ,pay_user_columns            col
591   WHERE col.user_table_id = p_user_table_id
592   AND   urw.user_table_id = p_user_table_id
593   AND   urw.row_low_range_or_name = p_pay_plan||'-'||p_grade_or_level
594   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN urw.effective_start_date AND urw.effective_end_date
595   AND   cin.user_row_id = urw.user_row_id
596   AND   cin.user_column_id = col.user_column_id
597   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN cin.effective_start_date AND cin.effective_end_date
598   ORDER BY TO_NUMBER(cin.value) ASC;
599 --
600 -- The order by means we will get the LOWEST value first
601 BEGIN
602   --BUG# 6211029 Added p_in_step_or_rate entered by the user initially after changing position
603   -- this will be passed as '01' if the value of User entered step or rate is greater than the
604   -- basic pay then need to consider the same otherwise need to be autopopulated with
605   -- the Minimum step or rate having value greater than the adjusted basic pay
606   IF p_in_step_or_rate is not null THEN
607      ghr_pay_calc.get_pay_table_value (p_user_table_id     => p_user_table_id
608                                     ,p_pay_plan          => p_pay_plan
609                                     ,p_grade_or_level    => p_grade_or_level
610                                     ,p_step_or_rate      => p_in_step_or_rate
611                                     ,p_effective_date    => p_effective_date
612                                     ,p_PT_value          => l_in_PT_value
613                                     ,p_PT_eff_start_date => l_in_PT_eff_start_date
614                                     ,p_PT_eff_end_date   => l_in_PT_eff_end_date);
615 
616   END IF;
617   IF NVL(l_in_PT_value,0) >= p_current_val AND p_in_step_or_rate is not null then
618      p_step_or_rate      := p_in_step_or_rate;
619      p_PT_value          := l_in_PT_value;
620      p_PT_eff_start_date := l_in_PT_eff_start_date;
621      p_PT_eff_end_date   := l_in_PT_eff_end_date;
622   ELSE
623   --End of BUG 6211029
624     FOR cur_pay_rec IN cur_pay LOOP
625       IF cur_pay_rec.basic_pay >= p_current_val then
626          p_step_or_rate      := cur_pay_rec.step_or_rate;
627          l_PT_value          := ROUND(cur_pay_rec.basic_pay,2);
628          p_PT_value          := l_PT_value;
629          p_PT_eff_start_date := cur_pay_rec.effective_start_date;
630          p_PT_eff_end_date   := cur_pay_rec.effective_end_date;
631          l_record_found      := TRUE;
632 
633         IF l_PT_value IS NULL THEN
634          -- Set tokens to give name of pay table, pay plan, grade, step and rate
635            hr_utility.set_message(8301,'GHR_38252_NULL_PAY_PLAN_VALUE');
636            hr_utility.set_message_token('PAY_TABLE_NAME',ghr_pay_calc.get_user_table_name(p_user_table_id) );
637 	   hr_utility.set_message_token('STEP',cur_pay_rec.step_or_rate);
638    	   hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
639 	   hr_utility.set_message_token('GRADE',p_grade_or_level);
640    --	   hr_utility.set_message_token('EFF_DATE',TO_CHAR(p_effective_date,'DD-MON-YYYY') );
641   	   hr_utility.set_message_token('EFF_DATE',fnd_date.date_to_chardate(p_effective_date) );
642 	   raise ghr_pay_calc.pay_calc_message;
643         END IF;
644         EXIT;
645       END IF;
646     END LOOP;
647 
648     --
649     IF NOT l_record_found THEN
650       -- Set tokens to give name of pay table, pay plan, grade, step and rate
651       hr_utility.set_message(8301,'GHR_38258_NO_MAX_PAY_PLAN_VAL');
652       hr_utility.set_message_token('PAY_TABLE_NAME',ghr_pay_calc.get_user_table_name(p_user_table_id) );
653       hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
654       hr_utility.set_message_token('GRADE',p_grade_or_level);
655     --  hr_utility.set_message_token('EFF_DATE',TO_CHAR(p_effective_date,'DD-MON-YYYY') );
656       hr_utility.set_message_token('EFF_DATE',fnd_date.date_to_chardate(p_effective_date) );
657       raise ghr_pay_calc.pay_calc_message;
658     END IF;
659   --
660  END IF;   -- p_in_step_or_rate Comparison
661 
662 EXCEPTION
663   WHEN others THEN
664      -- Reset IN OUT parameters and set OUT parameters
665 
666        p_step_or_rate          := NULL;
667        p_PT_value              := NULL;
668        p_PT_eff_start_date     := NULL;
669        p_PT_eff_end_date       := NULL;
670 
671    RAISE;
672 
673 END get_890_pay_table_value;
674 --
675 --
676 --
677 -- This procedure gets the minimum pay table value that is greater than a given value (X)
678 -- and returns the step associated with it
679 -- will return null if there is not one as opposed to error
680 PROCEDURE get_min_pay_table_value_GT_X (p_user_table_id  IN  NUMBER
681                              ,p_pay_plan            IN  VARCHAR2
682                              ,p_grade_or_level      IN  VARCHAR2
683                              ,p_effective_date      IN  DATE
684                              ,p_x                   IN  NUMBER
685                              ,p_step_or_rate        OUT NOCOPY VARCHAR2
686                              ,p_PT_value            OUT NOCOPY NUMBER) IS
687 
688 -- for a given pay_plan and grade this returns the minimum value and step
689 l_PT_value       NUMBER;
690 l_record_found   BOOLEAN := FALSE;
691 --
692 CURSOR cur_pay IS
693   SELECT cin.value             basic_pay
694         ,col.user_column_name  step_or_rate
695         ,cin.effective_start_date
696         ,cin.effective_end_date
697   FROM   pay_user_column_instances_f cin
698         ,pay_user_rows_f             urw
699         ,pay_user_columns            col
700   WHERE col.user_table_id = p_user_table_id
701   AND   urw.user_table_id = p_user_table_id
702   AND   urw.row_low_range_or_name = p_pay_plan||'-'||p_grade_or_level
703   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN urw.effective_start_date AND urw.effective_end_date
704   AND   cin.user_row_id = urw.user_row_id
705   AND   cin.user_column_id = col.user_column_id
706   AND   NVL(p_effective_date,TRUNC(SYSDATE)) BETWEEN cin.effective_start_date AND cin.effective_end_date
707   AND   cin.value >= p_x
708   ORDER BY TO_NUMBER(cin.value) ASC;
709 --
710 -- The order by means we will get the lowest value first
711 BEGIN
712   FOR cur_pay_rec IN cur_pay LOOP
713     p_step_or_rate      := cur_pay_rec.step_or_rate;
714     p_PT_value          := ROUND(cur_pay_rec.basic_pay,2);
715     l_record_found      := TRUE;
716     EXIT;
717   END LOOP;
718   --
719   IF NOT l_record_found THEN
720     p_step_or_rate      := null;
721     p_PT_value          := null;
722   END IF;
723   --
724 
725  EXCEPTION
726   WHEN others THEN
727      -- Reset IN OUT parameters and set OUT parameters
728 
729        p_step_or_rate          := NULL;
730        p_PT_value              := NULL;
731 
732    RAISE;
733 END get_min_pay_table_value_GT_X;
734 --
735 --
736 PROCEDURE get_basic_pay_SAL891_pos (p_pay_calc_data IN  ghr_pay_calc.pay_calc_in_rec_type
737                                    ,p_basic_pay     OUT NOCOPY NUMBER
738                                    ,p_step_or_rate  OUT NOCOPY VARCHAR2) IS
739 --
740 l_min_basic_pay  NUMBER;
741 l_min_step       VARCHAR2(30);
742 l_max_basic_pay  NUMBER;
743 l_max_step       VARCHAR2(30);
744 l_step_diff      INTEGER;
745 l_basic_pay      NUMBER;
746 l_dummy_date     DATE;
747 BEGIN
748   --
749   get_min_pay_table_value(p_pay_calc_data.user_table_id
750                           ,'GS'
751                           ,p_pay_calc_data.grade_or_level
752                           ,p_pay_calc_data.effective_date
753                           ,l_min_step
754                           ,l_min_basic_pay
755                           ,l_dummy_date
756                           ,l_dummy_date);
757   --
758   get_max_pay_table_value(p_pay_calc_data.user_table_id
759                           ,'GS'
760                           ,p_pay_calc_data.grade_or_level
761                           ,p_pay_calc_data.effective_date
762                           ,l_max_step
763                           ,l_max_basic_pay
764                           ,l_dummy_date
765                           ,l_dummy_date);
766 
767   --
768   -- May have to be careful using to_number since what we call the step is actually stored
769   -- as a varchar2 there ful it actually has the possibility of having characters in it
770   -- ORA-01722: invalid number will occur in this case
771   -- Also be careful if we got 0?
772   BEGIN
773     l_step_diff := TO_NUMBER(l_max_step) - TO_NUMBER(l_min_step);
774   END;
775   ----Basic Pay Calc issue in GMIT Pay --- Basically Matching with locality C2 step.
776   l_basic_pay := p_pay_calc_data.current_basic_pay + CEIL(( (l_max_basic_pay - l_min_basic_pay)/l_step_diff));
777   IF l_basic_pay > l_max_basic_pay THEN
778     p_basic_pay    := l_max_basic_pay;
779     p_step_or_rate := '00';                 ----------l_max_step;
780   ELSE
781     p_basic_pay    := l_basic_pay;
782     p_step_or_rate := '00';
783   END IF;
784   --
785 
786 EXCEPTION
787   WHEN others THEN
788      -- Reset IN OUT parameters and set OUT parameters
789 
790        p_step_or_rate          := NULL;
791        p_basic_pay             := NULL;
792 
793    RAISE;
794 END get_basic_pay_SAL891_pos;
795 --
796 PROCEDURE get_basic_pay_SAL891_per (p_pay_calc_data  IN  ghr_pay_calc.pay_calc_in_rec_type
797                                    ,p_retained_grade IN  ghr_pay_calc.retained_grade_rec_type
798                                    ,p_basic_pay      OUT NOCOPY NUMBER
799                                    ,p_step_or_rate   OUT NOCOPY VARCHAR2) IS
800 --
801 -- This one always uses the retained grade details no matter what
802 --
803 l_min_basic_pay  NUMBER;
804 l_min_step       VARCHAR2(30);
805 l_max_basic_pay  NUMBER;
806 l_max_step       VARCHAR2(30);
807 l_step_diff      INTEGER;
808 l_basic_pay      NUMBER;
809 l_dummy_date     DATE;
810 --
811 BEGIN
812   --
813   get_min_pay_table_value(p_retained_grade.user_table_id
814                           ,'GS'
815                           ,p_retained_grade.grade_or_level
816                           ,p_pay_calc_data.effective_date
817                           ,l_min_step
818                           ,l_min_basic_pay
819                           ,l_dummy_date
820                           ,l_dummy_date);
821    --
822    get_max_pay_table_value(p_retained_grade.user_table_id
823                           ,'GS'
824                           ,p_retained_grade.grade_or_level
825                           ,p_pay_calc_data.effective_date
826                           ,l_max_step
827                           ,l_max_basic_pay
828                           ,l_dummy_date
829                           ,l_dummy_date);
830 
831   --
832   -- May have to be careful using to_number since what we call the step is actually stored
833   -- as a varchar2 there ful it actually has the possibility of having characters in it
834   -- ORA-01722: invalid number will occur in this case
835   -- Also be careful if we got 0?
836   BEGIN
837     l_step_diff := TO_NUMBER(l_max_step) - TO_NUMBER(l_min_step);
838   END;
839   -----l_basic_pay := ROUND(p_pay_calc_data.current_basic_pay + ( (l_max_basic_pay - l_min_basic_pay)/l_step_diff) ,0);
840   l_basic_pay := p_pay_calc_data.current_basic_pay + CEIL(( (l_max_basic_pay - l_min_basic_pay)/l_step_diff));
841   IF l_basic_pay > l_max_basic_pay THEN
842     p_basic_pay    := l_max_basic_pay;
843     p_step_or_rate := '00';                 ----------l_max_step;
844   ELSE
845     p_basic_pay    := l_basic_pay;
846     p_step_or_rate := '00';
847   END IF;
848   --
849 
850 EXCEPTION
851   WHEN others THEN
852      -- Reset IN OUT parameters and set OUT parameters
853 
854        p_step_or_rate          := NULL;
855        p_basic_pay             := NULL;
856 
857    RAISE;
858 
859 END get_basic_pay_SAL891_per;
860 --
861 PROCEDURE check_current_PT (p_PT_date        IN DATE
862                            ,p_eff_start_date IN DATE) IS
863 BEGIN
864   IF p_PT_date <> p_eff_start_date THEN
865     hr_utility.set_message(8301,'GHR_38395_NOT_CURRENT_PT');
866     -- hr_utility.set_message_token('PAY_TABLE_NAME',get_user_table_name(p_user_table_id) );
867     raise ghr_pay_calc.pay_calc_message;
868   END IF;
869 END check_current_PT;
870 --
871 PROCEDURE check_old_PT (p_PT_date      IN DATE
872                        ,p_eff_end_date IN DATE) IS
873 BEGIN
874 /* This procedure is no more required as per Bug 3837402 .
875   IF p_PT_date -1 <> p_eff_end_date THEN
876     hr_utility.set_message(8301,'GHR_38396_NOT_OLD_PT');
877     -- hr_utility.set_message_token('PAY_TABLE_NAME',get_user_table_name(p_user_table_id) );
878     raise ghr_pay_calc.pay_calc_message;
879   END IF;
880 */
881  null;
882 
883 END check_old_PT;
884 --
885 PROCEDURE get_basic_pay_SAL894_6step(p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
886                                     ,p_retained_grade    IN  ghr_pay_calc.retained_grade_rec_type
887                                     ,p_pay_table_data    IN  VARCHAR2
888                                     ,p_basic_pay         OUT NOCOPY NUMBER
889                                     ,p_PT_eff_start_date OUT NOCOPY DATE
890                                     ,p_7dp               OUT NOCOPY NUMBER) IS
891 --
892 l_user_table_id      NUMBER;
893 l_pay_plan           VARCHAR2(30);
894 l_grade_or_level     VARCHAR2(60);
895 l_step_or_rate       VARCHAR2(30);
896 l_pay_basis          VARCHAR2(30);
897 --
898 l_PT_eff_start_date  DATE;
899 l_eff_start_date     DATE;
900 l_eff_end_date       DATE;
901 --
902 l_dummy_step         VARCHAR2(30);
903 --
904 l_old_basic_pay      NUMBER;
905 l_min_old_basic_pay  NUMBER;
906 l_max_old_basic_pay  NUMBER;
907 --
908 l_cur_basic_pay      NUMBER;
909 l_min_cur_basic_pay  NUMBER;
910 l_max_cur_basic_pay  NUMBER;
911 --
912 l_A NUMBER;
913 l_B NUMBER;
914 l_C NUMBER;
915 l_D NUMBER;
916 l_E NUMBER;
917 l_basic_pay NUMBER;
918 --
919 BEGIN
920   -- First work out what pay table data to use
921   --
922   -- bug 710171 Always use GS as the Pay plan
923   l_pay_plan := 'GS';
924   IF p_pay_table_data  = 'POSITION' THEN
925     l_user_table_id  := p_pay_calc_data.user_table_id;
926     l_grade_or_level := p_pay_calc_data.grade_or_level;
927     l_pay_basis      := p_pay_calc_data.pay_basis;
928     --
929   ELSE
930     l_user_table_id  := p_retained_grade.user_table_id;
931     l_grade_or_level := p_retained_grade.grade_or_level;
932     l_pay_basis      := p_retained_grade.pay_basis;
933     --
934   END IF;
935                                                                                           --AVR
936   IF p_pay_calc_data.noa_code = '894' AND p_pay_calc_data.pay_rate_determinant = 'M' THEN
937      IF p_retained_grade.grade_or_level IS NOT NULL THEN
938         l_grade_or_level := p_retained_grade.grade_or_level;
939         l_step_or_rate   := p_retained_grade.step_or_rate;
940      ELSE
941         l_grade_or_level := p_pay_calc_data.grade_or_level;
942         l_step_or_rate   := p_pay_calc_data.step_or_rate;
943      END IF;
944   END IF;
945                                                                                           --AVR
946   -- Get current value just to get the Pay Table effective date
947   ghr_pay_calc.get_pay_table_value(l_user_table_id
948                                   ,l_pay_plan
949                                   ,l_grade_or_level
950                                   ,'01'
951                                   ,p_pay_calc_data.effective_date
952                                   ,l_cur_basic_pay
953                                   ,l_eff_start_date
954                                   ,l_eff_end_date);
955   --
956   l_PT_eff_start_date := l_eff_start_date;
957   --
958   -- Step 1
959   ---------
960   get_min_pay_table_value(l_user_table_id
961                          ,l_pay_plan
962                          ,l_grade_or_level
963                          ,l_PT_eff_start_date - 1
964                          ,l_dummy_step
965                          ,l_min_old_basic_pay
966                          ,l_eff_start_date
967                          ,l_eff_end_date);
968   --
969   -- Check we used an old Pay Table
970   -- This vaidation is no more required as per bug 3837402.
971 --  check_old_PT (l_PT_eff_start_date, l_eff_end_date);
972   --
973   -- bug 710171 Use Current basic Pay as the starting point
974   l_A := p_pay_calc_data.current_basic_pay - l_min_old_basic_pay;
975   --
976   -- Step 2
977   ---------
978   get_max_pay_table_value(l_user_table_id
979                          ,l_pay_plan
980                          ,l_grade_or_level
981                          ,l_PT_eff_start_date - 1
982                          ,l_dummy_step
983                          ,l_max_old_basic_pay
984                          ,l_eff_start_date
985                          ,l_eff_end_date);
986   --
987   -- Check we used an old Pay Table
988  -- This vaidation is no more required as per bug 3837402.
989 -- check_old_PT (l_PT_eff_start_date, l_eff_end_date);
990   --
991   l_B := l_max_old_basic_pay - l_min_old_basic_pay;
992   --
993   -- Step 3 -- Otherwise refered to as the 7d.p. which is also used in the
994   --           locality adj calc
995   ---------
996   l_C := TRUNC( (l_A/l_B) ,7);
997   --
998   -- Step 4
999   ---------
1000   --
1001   get_min_pay_table_value(l_user_table_id
1002                          ,l_pay_plan
1003                          ,l_grade_or_level
1004                          ,l_PT_eff_start_date
1005                          ,l_dummy_step
1006                          ,l_min_cur_basic_pay
1007                          ,l_eff_start_date
1008                          ,l_eff_end_date);
1009   --
1010   -- Check we used a current Pay Table
1011   check_current_PT (l_PT_eff_start_date, l_eff_start_date);
1012   --
1013   get_max_pay_table_value(l_user_table_id
1014                          ,l_pay_plan
1015                          ,l_grade_or_level
1016                          ,l_PT_eff_start_date
1017                          ,l_dummy_step
1018                          ,l_max_cur_basic_pay
1019                          ,l_eff_start_date
1020                          ,l_eff_end_date);
1021   --
1022   -- Check we used a current Pay Table
1023   check_current_PT (l_PT_eff_start_date, l_eff_start_date);
1024   --
1025   l_D := l_max_cur_basic_pay - l_min_cur_basic_pay;
1026   --
1027   -- Step 5
1028   ---------
1029   l_E := l_C * l_D;
1030   --
1031   -- Step 6
1032   ---------
1033   ---l_basic_pay := ROUND(l_E + l_min_cur_basic_pay); --Bug#6603789 added round
1034 
1035    --BUG# 6680463 5 USC 531.205  --Basic rate should be rounded to the next whole dollar amount
1036 
1037   l_basic_pay := CEIL(l_E + l_min_cur_basic_pay);
1038 
1039   --
1040   p_basic_pay :=   ghr_pay_calc.convert_amount(l_basic_pay
1041                                               ,l_pay_basis
1042                                               ,p_pay_calc_data.pay_basis);
1043   --
1044   p_PT_eff_start_date := l_PT_eff_start_date;
1045   p_7dp := l_C;
1046   --
1047 
1048 EXCEPTION
1049   WHEN others THEN
1050      -- Reset IN OUT parameters and set OUT parameters
1051 
1052        p_7dp                   := NULL;
1053        p_basic_pay             := NULL;
1054        p_PT_eff_start_date      := NULL;
1055 
1056    RAISE;
1057 END get_basic_pay_SAL894_6step;
1058 --
1059 --
1060 PROCEDURE get_basic_pay_SAL894_50 (p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
1061                                   ,p_retained_grade    IN  ghr_pay_calc.retained_grade_rec_type
1062                                   ,p_pay_table_data    IN  VARCHAR2
1063                                   ,p_basic_pay         OUT NOCOPY NUMBER
1064                                   ,p_step              OUT NOCOPY VARCHAR2
1065                                   ,p_prd               OUT NOCOPY VARCHAR2
1066                                   ,p_PT_eff_start_date OUT NOCOPY DATE) IS
1067 --
1068 l_user_table_id      NUMBER;
1069 l_pay_plan           VARCHAR2(30);
1070 l_pc_pay_plan        VARCHAR2(30);
1071 l_grade_or_level     VARCHAR2(60);
1072 l_step_or_rate       VARCHAR2(30);
1073 l_pay_basis          VARCHAR2(30);
1074 
1075 l_dummy_step         VARCHAR2(30);
1076 l_max_cur_basic_pay  NUMBER;
1077 l_max_old_basic_pay  NUMBER;
1078 l_ret_basic_pay      NUMBER;
1079 l_pos_basic_pay      NUMBER;
1080 l_pos_step           VARCHAR2(30);
1081 --
1082 l_PT_eff_start_date  DATE;
1083 l_eff_start_date     DATE;
1084 l_eff_end_date       DATE;
1085 --
1086 l_cur_pos_basic_pay  NUMBER;
1087 --
1088 l_converted_increase NUMBER;
1089 --
1090 l_user_table_name    pay_user_tables.user_table_name%type;
1091 
1092 --Bug 3180991
1093 l_old_user_table_id  NUMBER;
1094 l_asg_ei_data        per_assignment_extra_info%rowtype;
1095 l_prd_effective_date date;
1096 l_retained_grade_rec ghr_pay_calc.retained_grade_rec_type;
1097 l_position_id        per_assignments_f.position_id%type;
1098 l_assignment_id      per_assignments_f.assignment_id%type;
1099 l_temp_step	     per_people_extra_info.pei_information6%type;
1100 l_effective_date     date;
1101 
1102 --Cursor to get the position id.
1103 CURSOR      cur_per_pos(p_effective_date date) is
1104   SELECT    asg.position_id, asg.assignment_id
1105   FROM      per_assignments_f asg
1106   WHERE     asg.person_id   =  p_pay_calc_data.person_id
1107   AND       trunc(nvl(p_effective_date,sysdate))
1108             between asg.effective_start_date and asg.effective_end_date
1109   AND       asg.assignment_type <> 'B'
1110   AND       asg.primary_flag = 'Y';
1111 
1112 CURSOR      cur_per_pos_2 is
1113   SELECT    asg.effective_start_date,asg.position_id, asg.assignment_id
1114   FROM      per_assignments_f asg
1115   WHERE     asg.person_id   =  p_pay_calc_data.person_id
1116   AND       asg.position_id is not null
1117   AND       asg.assignment_type <> 'B'
1118   AND       asg.primary_flag = 'Y'
1119   ORDER BY  asg.effective_start_date;
1120 
1121 
1122 CURSOR cur_pei (p_effective_date date) IS
1123   SELECT pei.person_extra_info_id
1124         ,pei.pei_information6     retained_user_table_id
1125         ,pei.pei_information9     retained_temp_step
1126   FROM   per_people_extra_info pei
1127   WHERE  pei.person_id = p_pay_calc_data.person_id
1128   AND    pei.information_type = 'GHR_US_RETAINED_GRADE'
1129   AND    p_effective_date BETWEEN NVL(fnd_date.canonical_to_date(pei.pei_information1),p_effective_date)
1130                           AND     NVL(fnd_date.canonical_to_date(pei.pei_information2),p_effective_date);
1131 --Bug 3180991
1132 
1133 BEGIN
1134 
1135   -- First work out what pay table data to use
1136 
1137   IF p_pay_table_data  = 'POSITION' THEN
1138     l_user_table_id  := p_pay_calc_data.user_table_id;
1139     l_pay_plan       := p_pay_calc_data.pay_plan;
1140     l_grade_or_level := p_pay_calc_data.grade_or_level;
1141     l_step_or_rate   := p_pay_calc_data.step_or_rate;
1142     l_pay_basis      := p_pay_calc_data.pay_basis;
1143     --
1144   ELSE
1145     l_user_table_id  := p_retained_grade.user_table_id;
1146     l_pay_plan       := p_retained_grade.pay_plan;
1147     l_grade_or_level := p_retained_grade.grade_or_level;
1148     l_step_or_rate   := p_retained_grade.step_or_rate;
1149     l_pay_basis      := p_retained_grade.pay_basis;
1150     --
1151   END IF;
1152   IF l_pay_plan IN ('GM','GH') THEN
1153     l_pay_plan := 'GS';
1154   END IF;
1155   --
1156 
1157   get_max_pay_table_value(l_user_table_id
1158                          ,l_pay_plan
1159                          ,l_grade_or_level
1160                          ,p_pay_calc_data.effective_date
1161                          ,l_dummy_step
1162                          ,l_max_cur_basic_pay
1163                          ,l_eff_start_date
1164                          ,l_eff_end_date);
1165 
1166   hr_utility.set_location(' get_basic_pay_SAL894_50 After first max pay' ||l_eff_start_date,12);
1167 
1168   -- set the Pay Table efective date as this is the first lookup we have done
1169   l_PT_eff_start_date  := l_eff_start_date;
1170 
1171   --Bug# 3180991
1172   l_effective_date     := p_pay_calc_data.effective_date ;
1173   l_prd_effective_date := l_effective_date - 1;
1174 
1175   -- get the positin id and assignment id as on l_PT_eff_start_date-1 using the cursor.
1176     FOR per_pos_id in cur_per_pos(l_PT_eff_start_date-1)
1177     LOOP
1178       l_position_id  :=  per_pos_id.position_id;
1179       l_assignment_id := per_pos_id.assignment_id;
1180       hr_utility.set_location(' get_basic_pay_SAL894_50 Position id ' ||l_position_id,12);
1181     END LOOP;
1182 
1183     IF l_assignment_id is null THEN
1184        FOR per_pos_id_2 in cur_per_pos_2
1185        LOOP
1186            l_prd_effective_date := per_pos_id_2.effective_start_date;
1187            l_position_id  :=  per_pos_id_2.position_id;
1188            l_assignment_id := per_pos_id_2.assignment_id;
1189            hr_utility.set_location(' get_basic_pay_SAL894_50 Position id ' ||l_position_id,12);
1190            exit;
1191        END LOOP;
1192     END IF;
1193 
1194   IF l_assignment_id is not null THEN
1195   -- This is used to get the prd.
1196   hr_utility.set_location(' get_basic_pay_SAL894_50 l_assignment_id' ||l_assignment_id,10);
1197   hr_utility.set_location(' get_basic_pay_SAL894_50 l_prd_effective_date' ||l_prd_effective_date,10);
1198 
1199   ghr_history_fetch.fetch_asgei( p_assignment_id      =>  l_assignment_id
1200                                  ,p_information_type  =>  'GHR_US_ASG_SF52'
1201                                  ,p_date_effective    =>  l_prd_effective_date
1202                                  ,p_asg_ei_data       =>  l_asg_ei_data
1203                                );
1204 
1205   hr_utility.set_location(' get_basic_pay_SAL894_50 l_asg_ei_data.aei_information6 ' ||l_asg_ei_data.aei_information6 ,11);
1206 
1207   IF l_asg_ei_data.aei_information6 NOT IN ('A','B','E','F','U','V') THEN
1208 
1209     l_old_user_table_id := ghr_pay_calc.get_user_table_id(  l_position_id , l_prd_effective_date );
1210     hr_utility.set_location(' get_basic_pay_SAL894_50 l_old_user_table_id ' ||l_old_user_table_id ,13);
1211 
1212   ELSE
1213 
1214     --Get the retain grade info as on l_PT_eff_start_date-1
1215     hr_utility.set_location(' get_basic_pay_SAL894_50 p_pay_calc_data.person_id' ||p_pay_calc_data.person_id,14);
1216     hr_utility.set_location(' get_basic_pay_SAL894_50 l_PT_eff_start_date-1' ||l_PT_eff_start_date,14);
1217     hr_utility.set_location(' get_basic_pay_SAL894_50 p_pay_calc_data.pa_request_id' ||p_pay_calc_data.pa_request_id,14);
1218 
1219     hr_utility.set_location(' get_basic_pay_SAL894_50 l_old_user_table_id ' ||l_old_user_table_id ,14);
1220 
1221 /*  We cannot use this procedure as pa_request_id is not available as of now.
1222 l_retained_grade_rec := ghr_pc_basic_pay.get_retained_grade_details
1223                                              (p_person_id      => p_pay_calc_data.person_id
1224                                              ,p_effective_date => l_prd_effective_date
1225 					     ,p_pa_request_id  => p_pay_calc_data.pa_request_id);
1226 
1227  */
1228     FOR cur_pei_rec IN cur_pei(l_prd_effective_date)
1229     LOOP
1230       l_old_user_table_id := cur_pei_rec.retained_user_table_id;
1231       l_temp_step         := cur_pei_rec.retained_temp_step;
1232     END LOOP;
1233 
1234     hr_utility.set_location(' get_basic_pay_SAL894_50 temp step after loop' ||l_temp_step ,14);
1235     hr_utility.set_location(' get_basic_pay_SAL894_50 l_old_user_table_id after loop' ||l_old_user_table_id ,14);
1236 
1237     --check for temp promotion and temp step is not null then use ghr_pay_calc.get_user_table_id.
1238     IF l_temp_step IS NOT NULL THEN
1239       l_old_user_table_id := ghr_pay_calc.get_user_table_id(  l_position_id , l_prd_effective_date );
1240       hr_utility.set_location(' get_basic_pay_SAL894_50 if l_old_user_table_id ' ||l_old_user_table_id ,15);
1241     END IF;
1242 
1243   END IF;
1244 
1245  ELSE
1246     l_old_user_table_id := l_user_table_id;
1247  END IF;
1248 
1249   --Bug# 3180991
1250 
1251     get_max_pay_table_value(l_old_user_table_id -- changed for 3180991
1252                          ,l_pay_plan
1253                          ,l_grade_or_level
1254                          ,l_effective_date - 1
1255                          ,l_dummy_step
1256                          ,l_max_old_basic_pay
1257                          ,l_eff_start_date
1258                          ,l_eff_end_date);
1259 
1260 
1261   --Bug# 3180991 Added If Statement
1262   -- This vaidation is no more required as per bug 3837402.
1263 /*  IF l_old_user_table_id = l_user_table_id THEN
1264   --
1265     -- Check we used an old Pay Table
1266 
1267     check_old_PT (l_PT_eff_start_date, l_eff_end_date);
1268     --
1269   END IF;
1270 */
1271   l_converted_increase :=   ghr_pay_calc.convert_amount( (l_max_cur_basic_pay - l_max_old_basic_pay)/2
1272                                                        ,l_pay_basis
1273                                                        ,p_pay_calc_data.pay_basis);
1274   --
1275 
1276 --- Bug 1579674
1277   if l_pay_basis = 'PH' then
1278      l_ret_basic_pay := ROUND(p_pay_calc_data.current_basic_pay + l_converted_increase,2);
1279   else
1280      l_ret_basic_pay := ROUND(p_pay_calc_data.current_basic_pay + l_converted_increase,0);
1281   end if;
1282 --- Bug 1579674
1283 
1284 
1285   p_PT_eff_start_date := l_PT_eff_start_date;
1286   --
1287   IF p_pay_calc_data.pay_plan IN ('GM','GH') THEN
1288     l_pc_pay_plan := 'GS';
1289   ELSE
1290     l_pc_pay_plan := p_pay_calc_data.pay_plan;
1291   END IF;
1292 
1293 
1294   get_min_pay_table_value_GT_X (l_user_table_id
1295                                ,l_pay_plan
1296                                ,l_grade_or_level
1297                                ,p_pay_calc_data.effective_date
1298                                ,l_ret_basic_pay
1299                                ,l_pos_step
1300                                ,l_pos_basic_pay);
1301 
1302 
1303   IF l_pos_basic_pay IS NULL THEN
1304     -- For pay plan CA need to check it hasn't exceeded EX-04 (table 0000 step 00)
1305     IF l_pay_plan = 'CA' THEN
1306       IF l_ret_basic_pay > ghr_pay_calc.get_standard_pay_table_value('EX'
1307                                                                    ,'04'
1308                                                                    ,'00'
1309                                                                    ,p_pay_calc_data.effective_date) THEN
1310         hr_utility.set_message(8301, 'GHR_38587_NO_CALC_EXCEED_EX_IV');
1311         hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
1312         raise ghr_pay_calc.unable_to_calculate;
1313       ELSE
1314         p_basic_pay := l_ret_basic_pay;
1315         p_step      := '00';
1316         p_prd       := NULL;
1317       END IF;
1318     ELSE
1319       p_basic_pay := l_ret_basic_pay;
1320       p_step      := '00';
1321       p_prd       := NULL;
1322     END IF;
1323   ELSE -- (pay retention is being terminated)
1324     -- Do not know what to do if pay plan is ES or IE and pay retention is terminated!
1325     IF l_pay_plan = 'CA' THEN
1326       hr_utility.set_message(8301, 'GHR_38588_NO_CALC_PAY_RET_END');
1327       hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
1328       raise ghr_pay_calc.unable_to_calculate;
1329     ELSE
1330       p_basic_pay := l_pos_basic_pay;
1331       p_step      := l_pos_step;
1332       l_user_table_name := ghr_pay_calc.get_user_table_name(l_user_table_id);
1333       IF p_pay_calc_data.pay_rate_determinant IN ('J','K','R','S','3') THEN
1334         IF l_pay_basis = 'PH' THEN
1335            p_prd := 0;
1336         ELSIF l_user_table_name = ghr_pay_calc.l_standard_table_name  THEN
1337           p_prd := '0';
1338         ELSE
1339           p_prd := '6';
1340         END IF;
1341       ELSIF p_pay_calc_data.pay_rate_determinant = 'U' THEN
1342             IF l_pay_basis = 'PH' THEN
1343                p_prd := 'B';
1344             ELSIF l_user_table_name = ghr_pay_calc.l_standard_table_name  THEN
1345                p_prd := 'B';
1346             ELSE
1347                p_prd := 'F';
1348             END IF;
1349       ELSIF p_pay_calc_data.pay_rate_determinant = 'V' THEN
1350             IF l_pay_basis = 'PH' THEN
1351                p_prd := 'A';
1352             ELSIF l_user_table_name = ghr_pay_calc.l_standard_table_name  THEN
1353                p_prd := 'A';
1354             ELSE
1355                p_prd := 'E';
1356             END IF;
1357       END IF; -- end of PRD check inside Pay rentention terminated
1358       --
1359     END IF;
1360   END IF;
1361 
1362 --
1363 EXCEPTION
1364   WHEN others THEN
1365      -- Reset IN OUT parameters and set OUT parameters
1366 
1367        p_step                  := NULL;
1368        p_prd                   := NULL;
1369        p_basic_pay             := NULL;
1370        p_PT_eff_start_date      := NULL;
1371 
1372    RAISE;
1373 
1374 END get_basic_pay_SAL894_50;
1375 --
1376 --
1377 PROCEDURE get_basic_pay_SAL894_100 (p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
1378                                    ,p_basic_pay         OUT NOCOPY NUMBER
1379                                    ,p_PT_eff_start_date OUT NOCOPY DATE) IS
1380 --
1381 l_dummy_step         VARCHAR2(30);
1382 l_pay_plan           VARCHAR2(30);
1383 l_max_cur_basic_pay  NUMBER;
1384 --
1385 l_max_old_basic_pay  NUMBER;
1386 --
1387 l_PT_eff_start_date  DATE;
1388 l_eff_start_date     DATE;
1389 l_eff_end_date       DATE;
1390 --For Bug 3180991
1391 l_old_user_table_id  NUMBER;
1392 l_effective_date     DATE;
1393 --
1394 BEGIN
1395   IF l_pay_plan IN ('GM','GH') THEN
1396     l_pay_plan := 'GS';
1397   ELSE
1398     l_pay_plan := p_pay_calc_data.pay_plan;
1399   END IF;
1400   --
1401   get_max_pay_table_value(p_pay_calc_data.user_table_id
1402                          ,l_pay_plan
1403                          ,p_pay_calc_data.grade_or_level
1404                          ,p_pay_calc_data.effective_date
1405                          ,l_dummy_step
1406                          ,l_max_cur_basic_pay
1407                          ,l_eff_start_date
1408                          ,l_eff_end_date);
1409   --
1410   -- Set eff_start date of the Pay Table
1411   l_PT_eff_start_date  := l_eff_start_date;
1412 
1413   l_effective_date     := p_pay_calc_data.effective_date;
1414   --
1415   --Bug# 3180991
1416   l_old_user_table_id := ghr_pay_calc.get_user_table_id(  p_pay_calc_data.position_id, l_PT_eff_start_date-1 );
1417   --Bug# 3180991
1418 
1419   get_max_pay_table_value(l_old_user_table_id
1420                          ,l_pay_plan
1421                          ,p_pay_calc_data.grade_or_level
1422                          ,l_effective_date   - 1
1423                          ,l_dummy_step
1424                          ,l_max_old_basic_pay
1425                          ,l_eff_start_date
1426                          ,l_eff_end_date);
1427 
1428   --Bug# 3180991 Added If Statement
1429   -- This vaidation is no more required as per bug 3837402.
1430 /*  IF l_old_user_table_id = p_pay_calc_data.user_table_id THEN
1431     --
1432     -- Check we used an old Pay Table
1433       -- This vaidation is no more required.
1434     check_old_PT (l_PT_eff_start_date, l_eff_end_date);
1435     --
1436   END IF;
1437 */
1438   p_basic_pay := ROUND(p_pay_calc_data.current_basic_pay + (l_max_cur_basic_pay - l_max_old_basic_pay) ,0);
1439   --
1440   p_PT_eff_start_date := l_PT_eff_start_date;
1441   --
1442 
1443 EXCEPTION
1444   WHEN others THEN
1445      -- Reset IN OUT parameters and set OUT parameters
1446 
1447        p_basic_pay             := NULL;
1448        p_PT_eff_start_date     := NULL;
1449 
1450    RAISE;
1451 END get_basic_pay_SAL894_100;
1452 --
1453 --
1454 FUNCTION get_next_WGI_step (p_pay_plan      IN VARCHAR2
1455                            ,p_current_step  IN VARCHAR2)
1456  RETURN VARCHAR2 IS
1457 --
1458 -- I assume there can only be one record for a given pay_plan and user table_id
1459 CURSOR cur_ppw IS
1460   SELECT ppw.to_step
1461         ,ppl.maximum_step
1462   FROM   ghr_pay_plan_waiting_periods ppw
1463         ,ghr_pay_plans                ppl
1464   WHERE  ppl.pay_plan            = p_pay_plan
1465   AND    ppl.equivalent_pay_plan = ppw.pay_plan
1466   AND    ppw.from_step           = p_current_step;
1467 --
1468 l_new_step     VARCHAR2(30);
1469 BEGIN
1470   FOR cur_ppw_rec IN cur_ppw LOOP
1471     l_new_step := cur_ppw_rec.to_step;
1472     --
1473     -- If the new step or rate is greater then the max then use the max
1474     IF l_new_step > cur_ppw_rec.maximum_step THEN
1475       l_new_step := cur_ppw_rec.maximum_step;
1476     END IF;
1477     --
1478     RETURN(l_new_step);
1479   END LOOP;
1480   --
1481   -- If we got here no record was returned
1482   -- set tokens to say the user table name and pay_plan that was used
1483   hr_utility.set_message(8301, 'GHR_38259_NO_WGI_STEP');
1484   hr_utility.set_message_token('PAY_PLAN',p_pay_plan);
1485   raise ghr_pay_calc.pay_calc_message;
1486   --
1487 END get_next_WGI_step;
1488 --
1489 PROCEDURE get_basic_pay_SALWGI_pos (p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
1490                                  ,p_basic_pay         OUT NOCOPY NUMBER
1491                                  ,p_new_step_or_rate  OUT NOCOPY VARCHAR2) IS
1492 --
1493 l_new_step_or_rate VARCHAR2(30);
1494 l_dummy_date       DATE;
1495 BEGIN
1496   -- This is the calcualation of a salary Change (SALARY_CHG) noac codes 867 - Interim Within Grade Increase,
1497   -- 892 - Quality Increase, 893 - Within-Grade Increase, PRD of 0 or 6:
1498   -- Basically you just get the next step by adding the wgi_step_or_rate on to the current step to get
1499   -- a new one you then use that to look up on the pay tables
1500   --
1501   --
1502   l_new_step_or_rate := get_next_WGI_step (p_pay_calc_data.pay_plan
1503                                           ,p_pay_calc_data.current_step_or_rate);
1504 
1505   ghr_pay_calc.get_pay_table_value(p_pay_calc_data.user_table_id
1506                                   ,p_pay_calc_data.pay_plan
1507                                   ,p_pay_calc_data.grade_or_level
1508                                   ,l_new_step_or_rate
1509                                   ,p_pay_calc_data.effective_date
1510                                   ,p_basic_pay
1511                                   ,l_dummy_date
1512                                   ,l_dummy_date);
1513   --
1514   p_new_step_or_rate := l_new_step_or_rate;
1515   --
1516 
1517 EXCEPTION
1518   WHEN others THEN
1519      -- Reset IN OUT parameters and set OUT parameters
1520 
1521        p_basic_pay             := NULL;
1522        p_new_step_or_rate      := NULL;
1523 
1524    RAISE;
1525 END get_basic_pay_SALWGI_pos;
1526 --
1527 PROCEDURE get_basic_pay_SALWGI_per (p_pay_calc_data   IN  ghr_pay_calc.pay_calc_in_rec_type
1528                                  ,p_retained_grade    IN  ghr_pay_calc.retained_grade_rec_type
1529                                  ,p_basic_pay         OUT NOCOPY NUMBER
1530                                  ,p_new_step_or_rate  OUT NOCOPY VARCHAR2) IS
1531 --
1532 -- This one always uses the retained grade details no matter what
1533 --
1534 l_basic_pay        NUMBER;
1535 l_new_step_or_rate VARCHAR2(30);
1536 --
1537 l_dummy_date       DATE;
1538 l_step_or_rate     VARCHAR2(30);
1539 l_pay_plan         VARCHAR2(30);
1540 l_grade_or_level   VARCHAR2(60);
1541 l_user_table_id    NUMBER;
1542 l_pay_basis        VARCHAR2(30);
1543 --Bug 3021003
1544 l_ret_flag BOOLEAN;
1545 l_retained_grade ghr_pay_calc.retained_grade_rec_type;
1546 l_temp_step VARCHAR2(30);
1547 
1548 BEGIN
1549   -- This is the calcualation of a salary Change (SALARY_CHG) noac codes 867 - Interim Within Grade Increase,
1550   -- 892 - Quality Increase, 893 - Within-Grade Increase, PRD of A , B, E  or F:
1551   -- As for SAL1_WGI above except you use the retained grade details to do the look up and return 00 as the
1552   -- step
1553   -- Basically you just get the next step by adding the wgi_step_or_rate on to the current step to get
1554   -- a new one you then use that to look up on the pay tables
1555   --
1556   -- Bug 3021003
1557   l_retained_grade.pay_plan := p_retained_grade.pay_plan;
1558   l_retained_grade.grade_or_level := p_retained_grade.grade_or_level;
1559   l_retained_grade.step_or_rate := p_retained_grade.step_or_rate;
1560   l_retained_grade.temp_step := p_retained_grade.temp_step;
1561 
1562   hr_utility.set_location('NAR inside wgi_per',0);
1563  if p_retained_grade.temp_step is not null then
1564     l_step_or_rate      := p_retained_grade.temp_step;
1565     l_user_table_id     := p_pay_calc_data.user_table_id;
1566     l_pay_plan          := p_pay_calc_data.pay_plan;
1567     l_grade_or_level    := p_pay_calc_data.grade_or_level;
1568     l_pay_basis         := p_pay_calc_data.pay_basis;
1569  else
1570     l_step_or_rate      := p_retained_grade.step_or_rate;
1571     l_user_table_id     := p_retained_grade.user_table_id;
1572     l_pay_plan          := p_retained_grade.pay_plan;
1573     l_grade_or_level    := p_retained_grade.grade_or_level;
1574     l_pay_basis         := p_retained_grade.pay_basis;
1575  end if;
1576 
1577  IF nvl(g_noa_family_code,'XXX') = 'CORRECT' then
1578 	-- Bug 3021003
1579     hr_utility.set_location('NAR inside noa_fam code = CORRECT ',5);
1580 	ghr_pay_calc.is_retained_ia(p_pay_calc_data.person_id,
1581 	                            p_pay_calc_data.effective_date,
1582 						       l_retained_grade.pay_plan,
1583 						       l_retained_grade.grade_or_level,
1584 						       l_retained_grade.step_or_rate,
1585 							   l_retained_grade.temp_step,
1586 							   l_ret_flag);
1587 			 IF l_ret_flag = TRUE THEN
1588 			     hr_utility.set_location('NAR ret step ' ||l_retained_grade.step_or_rate,10);
1589 			     hr_utility.set_location('NAR pay plan '||p_pay_calc_data.pay_plan,20);
1590 				-- Check for Temp step
1591 				 IF p_retained_grade.temp_step is not null then
1592 	                 l_new_step_or_rate := get_next_WGI_step (l_retained_grade.pay_plan,l_step_or_rate);
1593 				 ELSE
1594 					 l_new_step_or_rate := get_next_WGI_step (l_retained_grade.pay_plan,l_retained_grade.step_or_rate);
1595 				 END IF;
1596 			     hr_utility.set_location('NAR new step after getting the step ' ||l_new_step_or_rate,30);
1597 		     ELSE
1598     l_new_step_or_rate := l_step_or_rate;
1599 		     END IF;
1600 		      hr_utility.set_location('NAR new step after getting the step ' ||l_new_step_or_rate,40);
1601  ELSE
1602   l_new_step_or_rate := get_next_WGI_step (l_pay_plan
1603                                           ,l_step_or_rate);
1604  END IF;
1605 
1606   ghr_pay_calc.get_pay_table_value(l_user_table_id
1607                                   ,l_pay_plan
1608                                   ,l_grade_or_level
1609                                   ,l_new_step_or_rate
1610                                   ,p_pay_calc_data.effective_date
1611                                   ,l_basic_pay
1612                                   ,l_dummy_date
1613                                   ,l_dummy_date );
1614   --
1615   p_basic_pay := ghr_pay_calc.convert_amount(l_basic_pay
1616                                             ,l_pay_basis
1617                                             ,p_pay_calc_data.pay_basis);
1618   --
1619   p_new_step_or_rate := '00';
1620   --
1621 EXCEPTION
1622   WHEN others THEN
1623      -- Reset IN OUT parameters and set OUT parameters
1624 
1625        p_basic_pay             := NULL;
1626        p_new_step_or_rate      := NULL;
1627 
1628    RAISE;
1629 END get_basic_pay_SALWGI_per;
1630 
1631 
1632 PROCEDURE get_basic_pay_SAL894_PRDM (p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
1633                                     ,p_retained_grade    IN  ghr_pay_calc.retained_grade_rec_type
1634                                     ,p_basic_pay         OUT NOCOPY NUMBER
1635                                     ,p_prd               OUT NOCOPY VARCHAR2
1636                                     ,p_PT_eff_start_date OUT NOCOPY DATE) IS
1637 --
1638 l_user_table_id      NUMBER;
1639 l_pay_plan           VARCHAR2(30);
1640 l_pc_pay_plan        VARCHAR2(30);
1641 l_grade_or_level     VARCHAR2(60);
1642 l_step_or_rate       VARCHAR2(30);
1643 l_pay_basis          VARCHAR2(30);
1644 
1645 l_dummy_step         VARCHAR2(30);
1646 l_dummy_date         DATE;
1647 l_dummy_number       NUMBER;
1648 l_max_cur_basic_pay  NUMBER;
1649 l_max_old_basic_pay  NUMBER;
1650 l_ret_basic_pay      NUMBER;
1651 l_pos_basic_pay      NUMBER;
1652 l_pos_step           VARCHAR2(30);
1653 --
1654 l_PT_eff_start_date  DATE;
1655 l_eff_start_date     DATE;
1656 l_eff_end_date       DATE;
1657 
1658 l_basic_pay          NUMBER;
1659 l_new_adj_basic_pay  NUMBER;
1660 l_locality_adj       NUMBER;
1661 --
1662 ----l_cur_pos_basic_pay  NUMBER;
1663 --
1664 ----l_converted_increase NUMBER;
1665 --
1666 l_user_table_name            pay_user_tables.user_table_name%type;
1667 l_adjustment_percentage      ghr_locality_pay_areas_f.adjustment_percentage%TYPE;
1668 l_spl_basic_pay      NUMBER;
1669 l_spl_adj_basic_pay  NUMBER;
1670 l_spl_locality_adj   NUMBER;
1671 l_A                  NUMBER;
1672 l_B                  NUMBER;
1673 
1674 l_proc               varchar2(30) := 'SAL894_PRDM';
1675 
1676 l_new_std_relative_rate NUMBER;
1677 
1678 BEGIN
1679   hr_utility.set_location('Entering ' || l_proc,5);
1680   -- First work out what pay table data to use
1681   --
1682   IF p_retained_grade.grade_or_level is NULL THEN
1683   hr_utility.set_location('Entering  ..No Retained Grade Info.. ' || l_proc,10);
1684     l_user_table_id  := p_pay_calc_data.user_table_id;
1685     l_pay_plan       := p_pay_calc_data.pay_plan;
1686     l_grade_or_level := p_pay_calc_data.grade_or_level;
1687     l_step_or_rate   := p_pay_calc_data.step_or_rate;
1688     l_pay_basis      := p_pay_calc_data.pay_basis;
1689     --
1690   ELSE
1691   hr_utility.set_location('Entering  ..Retained Grade Info.. ' || l_proc,10);
1692     l_user_table_id  := p_retained_grade.user_table_id;
1693     l_pay_plan       := p_retained_grade.pay_plan;
1694     l_grade_or_level := p_retained_grade.grade_or_level;
1695     l_step_or_rate   := p_retained_grade.step_or_rate;
1696     l_pay_basis      := p_retained_grade.pay_basis;
1697     --
1698   END IF;
1699   ---------Pay Plan should be always 'GS'
1700   ---------l_pay_plan               := 'GS';
1701   l_user_table_name        := ghr_pay_calc.get_user_table_name(l_user_table_id);
1702   l_adjustment_percentage  := ghr_pay_calc.get_lpa_percentage
1703                                            (p_pay_calc_data.duty_station_id
1704                                            ,p_pay_calc_data.effective_date);
1705   --
1706   IF l_pay_plan = 'GS' THEN
1707 
1708             hr_utility.set_location('Calculating for GS Plan ..Basic Pay ' || l_proc,15);
1709             hr_utility.set_location('user_table_id..' || to_char(l_user_table_id) ,15);
1710 
1711             ghr_pay_calc.get_pay_table_value(l_user_table_id
1712                                             ,l_pay_plan
1713                                             ,l_grade_or_level
1714                                             ,l_step_or_rate
1715                                             ,p_pay_calc_data.effective_date
1716                                             ,l_basic_pay
1717                                             ,l_PT_eff_start_date
1718                                             ,l_dummy_date);
1719 
1720             hr_utility.set_location('Calculating for GS Plan ..Locality Pay ' || l_proc,20);
1721 
1722             ghr_pay_calc.get_locality_adj_894_PRDM_GS
1723                              (p_user_table_id     => l_user_table_id
1724                              ,p_pay_plan          => l_pay_plan
1725                              ,p_grade_or_level    => l_grade_or_level
1726                              ,p_step_or_rate      => l_step_or_rate
1727                              ,p_effective_date    => p_pay_calc_data.effective_date
1728                              ,p_cur_adj_basic_pay => p_pay_calc_data.current_adj_basic_pay
1729                              ,p_new_basic_pay     => l_basic_pay
1730                              ,p_new_adj_basic_pay => l_new_adj_basic_pay
1731                              ,p_new_locality_adj  => l_locality_adj );
1732 
1733         p_basic_pay             := nvl(l_basic_pay,0);
1734         p_PT_eff_start_date     := l_PT_eff_start_date;
1735 
1736         IF l_user_table_name = ghr_pay_calc.l_standard_table_name  THEN
1737            l_spl_basic_pay     := ghr_pay_calc.get_standard_pay_table_value
1738                                           (l_pay_plan
1739                                           ,l_grade_or_level
1740                                           ,l_step_or_rate
1741                                           ,p_pay_calc_data.effective_date);
1742            l_spl_locality_adj  := ROUND(l_spl_basic_pay * (NVL(l_adjustment_percentage,0)/100),0);
1743            l_spl_adj_basic_pay := (l_spl_basic_pay + l_spl_locality_adj);
1744         ELSE
1745            l_spl_basic_pay     := nvl(l_basic_pay,0);
1746            l_A                 := ghr_pay_calc.get_standard_pay_table_value
1747                                           ('GS'
1748                                           ,l_grade_or_level
1749                                           ,l_step_or_rate
1750                                           ,p_pay_calc_data.effective_date);
1751            l_B                 := NVL(l_A,0) + ROUND(l_A * (NVL(l_adjustment_percentage,0)/100),0);
1752            IF (l_spl_basic_pay > l_B ) OR (l_spl_basic_pay = l_B ) THEN
1753               l_spl_adj_basic_pay := l_spl_basic_pay;
1754            ELSE
1755               l_spl_adj_basic_pay := l_spl_basic_pay + (l_B - l_spl_basic_pay);
1756            END IF;
1757          END IF;
1758 
1759         -- Now do the comparison!
1760 
1761          IF (l_basic_pay > l_new_adj_basic_pay)  OR
1762             (l_spl_adj_basic_pay > l_new_adj_basic_pay) THEN
1763              IF l_user_table_name = ghr_pay_calc.l_standard_table_name THEN
1764                 p_prd := 0;
1765              ELSE
1766                 p_prd := 6;
1767              END IF;
1768          END IF;
1769 
1770   ELSIF l_pay_plan = 'GM' THEN
1771 
1772             hr_utility.set_location('Calculating for GM Plan ..Basic Pay ' || l_proc,25);
1773 
1774             get_basic_pay_SAL894_6step(p_pay_calc_data
1775                                       ,p_retained_grade
1776                                       ,'POSITION'
1777                                       ,l_basic_pay
1778                                       ,l_PT_eff_start_date
1779                                       ,l_dummy_number);
1780 
1781             hr_utility.set_location('Calculating for GM Plan ..Locality Pay ' || l_proc,20);
1782 
1783             ghr_pay_calc.get_locality_adj_894_PRDM_GM
1784                             (p_pay_calc_data     => p_pay_calc_data
1785                             ,p_retained_grade    => p_retained_grade
1786                             ,p_new_std_relative_rate => l_new_std_relative_rate
1787                             ,p_new_adj_basic_pay => l_new_adj_basic_pay
1788                             ,p_new_locality_adj  => l_locality_adj);
1789 
1790 
1791         l_new_std_relative_rate := l_new_std_relative_rate +
1792                                    ROUND(l_new_std_relative_rate *
1793                                           (NVL(l_adjustment_percentage,0)/100),0);
1794 
1795         IF l_new_std_relative_rate > l_new_adj_basic_pay THEN
1796            p_prd := 0;
1797            l_new_adj_basic_pay := l_new_std_relative_rate;
1798 ---------  l_locality_adj      := l_new_adj_basic_pay - l_basic_pay;
1799         ELSIF  (l_basic_pay > l_new_adj_basic_pay)  AND
1800            (l_user_table_name <> ghr_pay_calc.l_standard_table_name) THEN
1801                p_prd := 6;
1802                l_new_adj_basic_pay := l_basic_pay;
1803 -------------  l_locality_adj      := 0;
1804         END IF;
1805         p_basic_pay             := nvl(l_basic_pay,0);
1806         p_PT_eff_start_date     := l_PT_eff_start_date;
1807 
1808   END IF;
1809   hr_utility.set_location('Leaving .. ' || l_proc,5);
1810 
1811 EXCEPTION
1812   WHEN others THEN
1813      -- Reset IN OUT parameters and set OUT parameters
1814 
1815        p_basic_pay             := NULL;
1816        p_prd                   := NULL;
1817        p_PT_eff_start_date     := NULL;
1818 
1819        hr_utility.set_location('Leaving .. ' || l_proc,6);
1820    RAISE;
1821 END get_basic_pay_SAL894_PRDM;
1822 
1823 ----------------------------------------------------------------------------------------
1824 --                                                                                    --
1825 --------------------------- <get_basic_pay> --------------------------------------------
1826 --                                                                                    --
1827 ----------------------------------------------------------------------------------------
1828 PROCEDURE get_basic_pay (p_pay_calc_data     IN     ghr_pay_calc.pay_calc_in_rec_type
1829                         ,p_pay_calc_out_data    OUT NOCOPY ghr_pay_calc.pay_calc_out_rec_type
1830                         ,p_retained_grade    IN OUT NOCOPY ghr_pay_calc.retained_grade_rec_type) IS
1831 --
1832 -- This is the main bit of all the pay calc -- how we get the basic pay , everything else kinda
1833 -- falls out from that.
1834 -- Basically if we can calulate it we will otherwise raise ...
1835 -- Please note the return value will be in the given pay basis
1836 l_dummy_date       DATE;
1837 l_dummy_number     NUMBER;
1838 l_pay_plan         VARCHAR2(30);
1839 l_pay_basis        VARCHAR2(30);
1840 l_proc             VARCHAR2(20) := 'get_basic_pay';
1841 
1842 --1360547 Fix start
1843 cursor cfws is
1844 select 1 from ghr_pay_plans
1845 where EQUIVALENT_PAY_PLAN = 'FW'
1846 and   PAY_PLAN = l_pay_plan;
1847 
1848 --5470182
1849 cursor ces is
1850 select 1 from ghr_pay_plans
1851 where EQUIVALENT_PAY_PLAN = 'ES'
1852 and   PAY_PLAN = l_pay_plan;
1853 
1854 ---  Added for 5871233
1855 cursor chk_user_table(p_user_table_id in number)
1856     is
1857     SELECT  1
1858     FROM    PAY_USER_TABLES
1859     WHERE   USER_TABLE_ID    = p_user_table_id
1860     AND     USER_TABLE_NAME  like '0000%';
1861 
1862 l_fws_flag         VARCHAR2(5);
1863 l_es_flag         VARCHAR2(5);
1864 l_retained_grade   ghr_pay_calc.retained_grade_rec_type;
1865 --1360547 Fix
1866 l_open_range_basic_pay NUMBER;
1867 l_chk_user_table VARCHAR2(1) := 'N';
1868 l_890_current_adj_basic_pay NUMBER;
1869 BEGIN
1870 
1871   l_retained_grade := p_retained_grade ;
1872   l_fws_flag := 'FALSE';    ---Bug 1360547
1873   hr_utility.set_location('Entering ' || l_proc,5);
1874  -- get retained grade record if there is one, there MUST be one for 'A','B','E','F','U','V'
1875  -- and maybe one for 'M'
1876    IF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F','U','V','M') THEN
1877 	-- Begin Bug# 13619633, as per bug 1929382 for 866 we are passing eff date+1 this is casuing the issue.
1878 	--- So passing eff date -1 for noa 866.
1879        IF  nvl(p_pay_calc_data.noa_code,hr_api.g_varchar2) ='866' OR nvl(p_pay_calc_data.second_noa_code,hr_api.g_varchar2) ='866' THEN
1880 	   p_retained_grade := get_retained_grade_details (p_pay_calc_data.person_id
1881                                                       ,p_pay_calc_data.effective_date-1
1882                                                       ,p_pay_calc_data.pa_request_id);
1883        ELSE
1884        -- End Bug# 13619633
1885 	   p_retained_grade := get_retained_grade_details (p_pay_calc_data.person_id
1886                                                       ,p_pay_calc_data.effective_date
1887                                                       ,p_pay_calc_data.pa_request_id);
1888        END IF;-- Bug# 13619633
1889        l_pay_plan  := p_retained_grade.pay_plan;
1890        l_pay_basis := p_retained_grade.pay_basis;
1891        if p_pay_calc_data.noa_code = '740' then
1892           p_retained_grade.temp_step := NULL;
1893        end if;
1894        if p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') AND
1895           p_retained_grade.temp_step is not null AND
1896           p_pay_calc_data.noa_code <> '740' then
1897           l_pay_plan  := p_pay_calc_data.pay_plan;
1898           l_pay_basis := p_pay_calc_data.pay_basis;
1899        end if;
1900    ELSE
1901        l_pay_plan  := p_pay_calc_data.pay_plan;
1902        l_pay_basis := p_pay_calc_data.pay_basis;
1903    END IF;
1904 
1905 ---Open Pay Range Basic pay assignment from the in to out record.
1906    if p_pay_calc_data.open_range_out_basic_pay is not null then
1907       l_open_range_basic_pay := p_pay_calc_data.open_range_out_basic_pay;
1908       p_pay_calc_out_data.basic_pay := l_open_range_basic_pay;
1909    end if;
1910 ---Open Pay Range Code changes.
1911 --
1912 --1360547 Fix start
1913 --
1914  for cfws_rec in cfws
1915  loop
1916       l_fws_flag := 'TRUE';
1917  exit;
1918  end loop;
1919 --1360547 Fix
1920 
1921 --5470182 Fix start
1922 --
1923 l_es_flag := 'FALSE';
1924  for ces_rec in ces
1925  loop
1926       l_es_flag := 'TRUE';
1927  exit;
1928  end loop;
1929 --5470182 Fix
1930 
1931 
1932 
1933  -- Can not do pay calcs for dual actions -- 17/DEC/97 Can now the main pay calc
1934  -- routine should have set the the second noa to null to pass through this!
1935  --
1936 
1937 IF p_pay_calc_data.open_range_out_basic_pay IS NULL THEN
1938  IF p_pay_calc_data.second_noa_code IS NULL THEN
1939   -- Must have all the data to be here as the validation has checked it
1940   IF p_pay_calc_data.pay_basis IN ('PA','PH','BW')
1941     AND l_pay_basis IN ('PA','PH','BW') THEN
1942     --
1943     IF l_pay_plan NOT IN ('SL','ST', 'SR')
1944       AND SUBSTR(l_pay_plan,1,1) <> 'D' THEN
1945       --
1946       IF p_pay_calc_data.noa_family_code IN ('APP','CHG_DUTY_STATION','CONV_APP','EXT_NTE','POS_CHG'
1947                                           ,'REALIGNMENT','REASSIGNMENT', 'RETURN_TO_DUTY') THEN
1948         --
1949         --Bug# 5132113 added pay plan GR
1950         IF l_pay_plan NOT IN ('GM','GH','FM','GR') THEN
1951           --
1952           IF p_pay_calc_data.pay_rate_determinant IN ('0','5','6','7') THEN
1953             -- This is the easy one! refered to as MAIN_pos in the design doc
1954             -- all you have to do is a striaght look up on the user table given, using step,pay_plan,and
1955             -- grade given at the effective date also given
1956             -- Note: need for any conversion since it must already be in the given pay basis
1957 
1958 	    hr_utility.set_location('before Basic Pay',1000);
1959 	    FOR rec_chk_user_table  in chk_user_table(p_user_table_id  => p_pay_calc_data.user_table_id)
1960 	    LOOP
1961 	       l_chk_user_table := 'Y';
1962 	    END LOOP;
1963 
1964 	    ---  Added for 5871233
1965 	    --Modified to copy the current basic pay for realignment and AD pay plan and
1966 	    --Grade or Level '00' with Step or Rate 00 and PRD as 0
1967 	    --Bug 10244679 added pay plan EF
1968 	  IF p_pay_calc_data.noa_family_code = 'REALIGNMENT' and
1969 	       p_pay_calc_data.pay_plan  IN ('AD','EF')  and
1970 	       p_pay_calc_data.grade_or_level = '00' and
1971 	       p_pay_calc_data.step_or_rate  = '00' and
1972 	       p_pay_calc_data.pay_rate_determinant = '0'
1973 	       and NVL(l_chk_user_table,'N') = 'Y' THEN
1974 	       hr_utility.set_location('p_pay_calc_data.current_basic_pay'||p_pay_calc_data.current_basic_pay,1000);
1975 	         p_pay_calc_out_data.basic_pay  :=  p_pay_calc_data.current_basic_pay;
1976 
1977 	    ELSE
1978 
1979 
1980             ghr_pay_calc.get_pay_table_value(p_pay_calc_data.user_table_id
1981                                             ,p_pay_calc_data.pay_plan
1982                                             ,p_pay_calc_data.grade_or_level
1983                                             ,p_pay_calc_data.step_or_rate
1984                                             ,p_pay_calc_data.effective_date
1985                                             ,p_pay_calc_out_data.basic_pay
1986                                             ,l_dummy_date
1987                                             ,l_dummy_date);
1988             END IF;
1989           ELSIF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') THEN
1990             get_basic_pay_MAIN_per(p_pay_calc_data
1991                                   ,p_retained_grade
1992                                   ,p_pay_calc_out_data.basic_pay
1993                                   ,l_dummy_date);
1994           ELSE
1995             hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
1996             hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
1997             raise ghr_pay_calc.unable_to_calculate;
1998           END IF;
1999         --
2000         ELSE
2001           hr_utility.set_message(8301, 'GHR_38260_NO_CALC_PAY_PLAN');
2002           hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2003           raise ghr_pay_calc.unable_to_calculate;
2004         END IF;
2005       ELSIF SUBSTR(p_pay_calc_data.noa_family_code ,1,8) = 'GHR_SAL_' THEN
2006         -- For salary change family we need to further investigate the noac to determine
2007         -- how to do pay
2008         IF p_pay_calc_data.noa_code = '894' THEN
2009           IF (p_pay_calc_data.effective_date >= to_date('2007/01/07','YYYY/MM/DD') AND
2010               nvl(p_pay_calc_data.first_action_la_code1,'XXX') <> 'VGR') OR
2011               p_pay_calc_data.effective_date <  to_date('2007/01/07','YYYY/MM/DD')  THEN
2012           -- Bug! 658164 Since we were not able to calculate pay for PRD's 2,3,4,J,K,M,R,3,U,V
2013           -- in Appointment, don't attempt to do it in 894!!
2014           -- How to calculate for this NOAC basically depends on Pay Plan AND PRD:
2015           --Bug# 5132113 added pay plan GP
2016             IF    (    l_pay_plan IN ('GS','GL','GG','IE','GP')
2017                  AND p_pay_calc_data.pay_rate_determinant IN ('0','6') )
2018              OR (    (l_pay_plan IN ('EX') or l_fws_flag = 'TRUE')
2019                  AND p_pay_calc_data.pay_rate_determinant IN ('0') )
2020              OR (    l_pay_plan IN ('ES','EP','CA','FO','FP','FE','AL','AA')
2021                  AND p_pay_calc_data.pay_rate_determinant IN ('0','6') )
2022              OR  l_pay_plan IN ('IG') THEN --Bug# 7557159
2023             --
2024             -- This is what we refer to as MAIN_pos
2025             --
2026             ghr_pay_calc.get_pay_table_value(p_pay_calc_data.user_table_id
2027                                             ,p_pay_calc_data.pay_plan
2028                                             ,p_pay_calc_data.grade_or_level
2029                                             ,p_pay_calc_data.step_or_rate
2030                                             ,p_pay_calc_data.effective_date
2031                                             ,p_pay_calc_out_data.basic_pay
2032                                             ,p_pay_calc_out_data.PT_eff_start_date
2033                                             ,l_dummy_date);
2034             --
2035           ELSIF  (    (l_pay_plan IN ('GS','GL','GG','ES','EP','CA','FO','FP','FE','AL','AA','IE')
2036                      or l_fws_flag = 'TRUE')
2037                  AND p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') )  THEN
2038             --
2039             get_basic_pay_MAIN_per(p_pay_calc_data
2040                                   ,p_retained_grade
2041                                   ,p_pay_calc_out_data.basic_pay
2042                                   ,p_pay_calc_out_data.PT_eff_start_date);
2043             --
2044           ELSIF (    l_pay_plan IN ('GM','GH','GR')
2045                  AND p_pay_calc_data.pay_rate_determinant IN ('0','6') ) THEN
2046             --
2047             get_basic_pay_SAL894_6step(p_pay_calc_data
2048                                       ,p_retained_grade
2049                                       ,'POSITION'
2050                                       ,p_pay_calc_out_data.basic_pay
2051                                       ,p_pay_calc_out_data.PT_eff_start_date
2052                                       ,l_dummy_number);
2053             --
2054           ELSIF (    l_pay_plan IN ('GM','GH')
2055                  AND p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') ) THEN
2056             get_basic_pay_SAL894_6step(p_pay_calc_data
2057                                       ,p_retained_grade
2058                                       ,'PERSON'
2059                                       ,p_pay_calc_out_data.basic_pay
2060                                       ,p_pay_calc_out_data.PT_eff_start_date
2061                                       ,l_dummy_number);
2062             --
2063           ELSIF (    (l_pay_plan IN ('GS','GL','GM','GG','GH','ES','EP','FO','FP','FE','IE','AL','AA','CA')
2064                       or l_fws_flag = 'TRUE')
2065                  AND p_pay_calc_data.pay_rate_determinant IN ('J','K','R','3','S') ) THEN
2066             get_basic_pay_SAL894_50(p_pay_calc_data
2067                                    ,p_retained_grade
2068                                    ,'POSITION'
2069                                    ,p_pay_calc_out_data.basic_pay
2070                                    ,p_pay_calc_out_data.out_step_or_rate
2071                                    ,p_pay_calc_out_data.out_pay_rate_determinant
2072                                    ,p_pay_calc_out_data.PT_eff_start_date);
2073             --
2074           ELSIF (    (l_pay_plan IN ('GS','GL','GM','GG','GH','ES','EP','FO','FP','FE','IE','AL','AA','CA')
2075                       or l_fws_flag = 'TRUE')
2076                  AND p_pay_calc_data.pay_rate_determinant IN ('U','V') ) THEN
2077             get_basic_pay_SAL894_50(p_pay_calc_data
2078                                    ,p_retained_grade
2079                                    ,'PERSON'
2080                                    ,p_pay_calc_out_data.basic_pay
2081                                    ,p_pay_calc_out_data.out_step_or_rate
2082                                    ,p_pay_calc_out_data.out_pay_rate_determinant
2083                                    ,p_pay_calc_out_data.PT_eff_start_date);
2084 
2085           ELSIF (    l_pay_plan IN ('GS','GL','GM','GG','GH')
2086                  AND p_pay_calc_data.pay_rate_determinant IN ('2','4') ) THEN
2087             get_basic_pay_SAL894_100(p_pay_calc_data
2088                                     ,p_pay_calc_out_data.basic_pay
2089                                     ,p_pay_calc_out_data.PT_eff_start_date);
2090                                                                                           --AVR
2091           ELSIF (    l_pay_plan IN ('GS','GL','GM')
2092                  AND p_pay_calc_data.pay_rate_determinant = 'M' )  THEN
2093 
2094                   hr_utility.set_location('Calling ..SAL894_PRDM..  ' || l_proc,15);
2095                  get_basic_pay_SAL894_PRDM (p_pay_calc_data
2096                                            ,p_retained_grade
2097                                            ,p_pay_calc_out_data.basic_pay
2098                                            ,p_pay_calc_out_data.out_pay_rate_determinant
2099                                            ,p_pay_calc_out_data.PT_eff_start_date );
2100                   hr_utility.set_location('Called  ..SAL894_PRDM..  ' || l_proc,25);
2101 
2102                                                                                           --AVR
2103 
2104 
2105           --Begin Bug# 7557159
2106           ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2107             hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2108             raise ghr_pay_calc.open_pay_range_mesg;
2109           --End Bug# 7557159
2110           ELSE
2111             hr_utility.set_message(8301, 'GHR_38391_NO_CALC_PAY_PLAN_PRD');
2112             hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2113             hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2114             raise ghr_pay_calc.unable_to_calculate;
2115           END IF;
2116           --
2117           ELSIF (p_pay_calc_data.effective_date >= to_date('2007/01/07','YYYY/MM/DD') AND
2118                  p_pay_calc_data.first_action_la_code1 = 'VGR' ) THEN
2119               ---GPPA Update 46 894 NOAC will behave like 895 with VGR after 7-JAN-2007 onwards.
2120                 p_pay_calc_out_data.basic_pay := p_pay_calc_data.current_basic_pay;
2121          END IF;
2122         ELSIF p_pay_calc_data.noa_code = '895' THEN
2123           -- Easy this one I like this, no change in basic pay!!
2124           p_pay_calc_out_data.basic_pay := p_pay_calc_data.current_basic_pay;
2125           --
2126 
2127           --Bug# 5132113 added pay plan GR
2128         ELSIF l_pay_plan NOT IN ('GM','GH','GR') THEN
2129           IF p_pay_calc_data.noa_code = '891' AND
2130 			 p_pay_calc_data.effective_date < to_date('2007/01/07','YYYY/MM/DD')THEN --Bug# 5482191
2131             hr_utility.set_message(8301, 'GHR_38248_INV_PAY_PLAN_891');
2132             hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2133             raise ghr_pay_calc.pay_calc_message;
2134           --
2135           ELSIF p_pay_calc_data.noa_code IN ('867','892','893') THEN
2136             --
2137             IF p_pay_calc_data.pay_rate_determinant IN ('0','6','M') THEN
2138               get_basic_pay_SALWGI_pos(p_pay_calc_data
2139                                       ,p_pay_calc_out_data.basic_pay
2140                                       ,p_pay_calc_out_data.out_step_or_rate);
2141             ELSIF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') THEN
2142               get_basic_pay_SALWGI_per(p_pay_calc_data
2143                                       ,p_retained_grade
2144                                       ,p_pay_calc_out_data.basic_pay
2145                                       ,p_pay_calc_out_data.out_step_or_rate);
2146                 --Begin Bug# 7557159
2147             ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2148                 hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2149                 raise ghr_pay_calc.open_pay_range_mesg;
2150                 --End Bug# 7557159
2151             ELSE
2152               hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
2153               hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2154               raise ghr_pay_calc.unable_to_calculate;
2155             END IF;
2156 
2157           ELSIF (p_pay_calc_data.noa_code IN ('890') AND (l_fws_flag = 'TRUE' or l_es_flag = 'TRUE')) THEN
2158             --
2159             IF p_pay_calc_data.pay_rate_determinant IN ('0','6') THEN
2160          	--5470182 added NOA code '890' mass salary actions for 6step calculation
2161               IF l_es_flag = 'TRUE' THEN
2162 
2163            	 get_basic_pay_SAL890_6step(p_pay_calc_data     =>p_pay_calc_data
2164                                            ,p_retained_grade    =>p_retained_grade
2165                                            ,p_pay_table_data    =>'POSITION'
2166                                            ,p_basic_pay         =>p_pay_calc_out_data.basic_pay
2167 				           );
2168 
2169              ELSE
2170 ---- Bug 5913318
2171 ---- At this stage when a mixed pay  basis condition araises no variable for from pay basis to convert the
2172 ---- current_basic_pay. So evolving a hard coded logic below - Not correct but due to time constraint...
2173 
2174      --BUG 6211029 Modified the basic pay to Adjusted Basic Pay and added  p_pay_calc_data.step_or_rate to the
2175      -- call of  get_890_pay_table_value
2176 
2177      --BUG 6211029 removed the below call to get_890_pay_table_value as no need of defaulting the step or rate
2178      -- need to be calculated based on the entered step or rate
2179 
2180           /*     IF p_pay_calc_data.pay_basis = 'PH' AND p_pay_calc_data.current_adj_basic_pay > 100 THEN
2181                     l_890_current_adj_basic_pay   := ghr_pay_calc.convert_amount(p_pay_calc_data.current_adj_basic_pay ,'PA','PH');
2182                  ELSE
2183                     l_890_current_adj_basic_pay   := p_pay_calc_data.current_adj_basic_pay;
2184                  END IF;
2185 
2186 
2187                  get_890_pay_table_value(p_pay_calc_data.user_table_id
2188                           ,p_pay_calc_data.pay_plan
2189                           ,p_pay_calc_data.grade_or_level
2190                           ,p_pay_calc_data.effective_date
2191                           ,nvl(l_890_current_adj_basic_pay, p_pay_calc_data.current_adj_basic_pay)
2192 			  ,p_pay_calc_data.step_or_rate
2193                           ,p_pay_calc_out_data.out_step_or_rate
2194                           ,p_pay_calc_out_data.basic_pay
2195                           ,l_dummy_date
2196                           ,l_dummy_date);    */
2197 
2198               ghr_pay_calc.get_pay_table_value(p_pay_calc_data.user_table_id
2199                                               ,p_pay_calc_data.pay_plan
2200                                               ,p_pay_calc_data.grade_or_level
2201                                               ,p_pay_calc_data.step_or_rate
2202                                               ,p_pay_calc_data.effective_date
2203                                               ,p_pay_calc_out_data.basic_pay
2204                                               ,l_dummy_date
2205                                               ,l_dummy_date);
2206 
2207 
2208 	     END IF;
2209             ELSIF p_pay_calc_data.pay_rate_determinant IN ('J','K','R','3','S')  THEN
2210                   ghr_pay_calc.get_pay_table_value (p_user_table_id     => p_pay_calc_data.user_table_id
2211                                                    ,p_pay_plan          => p_pay_calc_data.pay_plan
2212                                                    ,p_grade_or_level    => p_pay_calc_data.grade_or_level
2213                                                    ,p_step_or_rate      => '05'
2214                                                    ,p_effective_date    => p_pay_calc_data.effective_date
2215                                                    ,p_PT_value          => p_pay_calc_out_data.basic_pay
2216                                                    ,p_PT_eff_start_date => l_dummy_date
2217                                                    ,p_PT_eff_end_date   => l_dummy_date);
2218                    p_pay_calc_out_data.out_step_or_rate := '05';
2219                    p_pay_calc_out_data.out_pay_rate_determinant := '0';
2220             ELSIF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') THEN
2221               get_basic_pay_MAIN_per(p_pay_calc_data
2222                                     ,p_retained_grade
2223                                     ,p_pay_calc_out_data.basic_pay
2224                                     ,l_dummy_date);
2225               --
2226             --Begin Bug# 7557159
2227             ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2228                 hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2229                 raise ghr_pay_calc.open_pay_range_mesg;
2230               --End Bug# 7557159
2231             ELSE
2232               hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
2233               hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2234               raise ghr_pay_calc.unable_to_calculate;
2235             END IF;
2236 
2237           ELSE -- All other NoaC's for the salary change family (not GM,GH)
2238 
2239 		    IF p_pay_calc_data.pay_rate_determinant IN ('0','6') THEN
2240               -- This is the easy one! refered to as MAIN_pos in the design doc
2241               -- all you have to do is a striaght look up on the user table given, using step,pay_plan,and
2242               -- grade given at the effective date also given
2243               -- Note: need for any conversion since it must already be in the given pay basis
2244               ghr_pay_calc.get_pay_table_value(p_pay_calc_data.user_table_id
2245                                               ,p_pay_calc_data.pay_plan
2246                                               ,p_pay_calc_data.grade_or_level
2247                                               ,p_pay_calc_data.step_or_rate
2248                                               ,p_pay_calc_data.effective_date
2249                                               ,p_pay_calc_out_data.basic_pay
2250                                               ,l_dummy_date
2251                                               ,l_dummy_date);
2252             ELSIF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') THEN
2253               get_basic_pay_MAIN_per(p_pay_calc_data
2254                                     ,p_retained_grade
2255                                     ,p_pay_calc_out_data.basic_pay
2256                                     ,l_dummy_date);
2257               --
2258             --Begin Bug# 7557159
2259             ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2260                 hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2261                 raise ghr_pay_calc.open_pay_range_mesg;
2262                 --End Bug# 7557159
2263             ELSE
2264               hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
2265               hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2266               raise ghr_pay_calc.unable_to_calculate;
2267             END IF;
2268 
2269 	    --Pradeep commented for Title 38 Changes
2270 	    -- IF NOAC = 850 or 855 open up pay fields as well as doing the calc:
2271             /*
2272             IF p_pay_calc_data.noa_code IN ('850','855') THEN
2273               p_pay_calc_out_data.open_pay_fields := TRUE;
2274             END IF;
2275             */
2276             --
2277           --
2278           END IF; -- end of noac check inside salary change family
2279           --
2280         ELSE -- Not 894, not 895 and must be GM, GH pay plans
2281           --
2282         --Bug# 5132113 added pay plan GR condition
2283        /*IF l_pay_plan in('GR') THEN
2284                 hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
2285                       hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2286                       raise ghr_pay_calc.unable_to_calculate;
2287 	  ELS*/ --Bug# 6342011 Commented
2288         IF p_pay_calc_data.noa_code IN ('891','892') THEN
2289             IF p_pay_calc_data.pay_rate_determinant IN ('0','6') THEN
2290               get_basic_pay_SAL891_pos(p_pay_calc_data
2291                                       ,p_pay_calc_out_data.basic_pay
2292                                       ,p_pay_calc_out_data.out_step_or_rate);
2293             ELSIF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') THEN
2294               get_basic_pay_SAL891_per(p_pay_calc_data
2295                                       ,p_retained_grade
2296                                       ,p_pay_calc_out_data.basic_pay
2297                                       ,p_pay_calc_out_data.out_step_or_rate);
2298             --Begin Bug# 7557159
2299             ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2300                 hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2301                 raise ghr_pay_calc.open_pay_range_mesg;
2302                 --End Bug# 7557159
2303             ELSE
2304               hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
2305               hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2306               raise ghr_pay_calc.unable_to_calculate;
2307             END IF;
2308 		  --Begin Bug 5661441 AFHR change
2309 
2310 		  ELSIF  p_pay_calc_data.noa_code IN ('893') THEN
2311 			IF p_pay_calc_data.effective_date < to_date('2007/01/07','YYYY/MM/DD')THEN
2312 				hr_utility.set_message(8301, 'GHR_INV_PAY_PLAN_893');
2313 				hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2314 				hr_utility.set_message_token('NOAC',p_pay_calc_data.noa_code);
2315 				raise ghr_pay_calc.pay_calc_message;
2316 			ELSE
2317 				IF p_pay_calc_data.pay_rate_determinant IN ('0','6') THEN
2318 				  get_basic_pay_SAL891_pos(p_pay_calc_data
2319 										  ,p_pay_calc_out_data.basic_pay
2320 										  ,p_pay_calc_out_data.out_step_or_rate);
2321 				ELSIF p_pay_calc_data.pay_rate_determinant IN ('A','B','E','F') THEN
2322 				  get_basic_pay_SAL891_per(p_pay_calc_data
2323 										  ,p_retained_grade
2324 										  ,p_pay_calc_out_data.basic_pay
2325 										  ,p_pay_calc_out_data.out_step_or_rate);
2326 				--Begin Bug# 7557159
2327                 ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2328                     hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2329                     raise ghr_pay_calc.open_pay_range_mesg;
2330                     --End Bug# 7557159
2331                 ELSE
2332 				  hr_utility.set_message(8301, 'GHR_38254_NO_CALC_PRD');
2333 				  hr_utility.set_message_token('PRD',p_pay_calc_data.pay_rate_determinant);
2334 				  raise ghr_pay_calc.unable_to_calculate;
2335 				END IF;
2336 			END IF;
2337 
2338 		  --end Bug 5661441 AFHR change
2339           ELSIF p_pay_calc_data.noa_code IN ('867') THEN --AFHR change 893 removed
2340             hr_utility.set_message(8301, 'GHR_INV_PAY_PLAN_893');
2341             hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2342             hr_utility.set_message_token('NOAC',p_pay_calc_data.noa_code);
2343             raise ghr_pay_calc.pay_calc_message;
2344           --
2345             --Begin Bug# 7557159
2346           ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2347             hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2348             raise ghr_pay_calc.open_pay_range_mesg;
2349             --End Bug# 7557159
2350           ELSE
2351             hr_utility.set_message(8301, 'GHR_38260_NO_CALC_PAY_PLAN');
2352             hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2353             raise ghr_pay_calc.unable_to_calculate;
2354           END IF;
2355           --
2356         END IF;
2357       --Begin Bug# 7557159
2358       ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2359         hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2360         raise ghr_pay_calc.open_pay_range_mesg;
2361         --End Bug# 7557159
2362       ELSE
2363         hr_utility.set_message(8301, 'GHR_38261_NO_CALC_FAMILY');
2364         hr_utility.set_message_token('FAMILY',p_pay_calc_data.noa_family_code);
2365         raise ghr_pay_calc.unable_to_calculate;
2366       END IF;
2367       --
2368     --Begin Bug# 7557159
2369     ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2370         hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2371         raise ghr_pay_calc.open_pay_range_mesg;
2372         --End Bug# 7557159
2373     ELSE
2374       hr_utility.set_message(8301, 'GHR_38260_NO_CALC_PAY_PLAN');
2375       hr_utility.set_message_token('PAY_PLAN',l_pay_plan);
2376       raise ghr_pay_calc.unable_to_calculate;
2377     END IF;
2378   --Begin Bug# 7557159
2379   ELSIF p_pay_calc_data.pay_rate_determinant = 'D' THEN
2380     hr_utility.set_message(8301, 'GHR_38520_PRD_D');
2381     raise ghr_pay_calc.open_pay_range_mesg;
2382     --End Bug# 7557159
2383   ELSE
2384     hr_utility.set_message(8301, 'GHR_38262_NO_CALC_PAY_BASIS');
2385     -- It could be either the position pay basis or the retained pay basis as to why we couldn't
2386     -- calculate
2387     IF p_pay_calc_data.pay_basis NOT IN ('PA','PH','BW') THEN
2388       hr_utility.set_message_token('PAY_BASIS',
2389                                     ghr_pa_requests_pkg.get_lookup_meaning(800,'GHR_US_PAY_BASIS'
2390                                                                           ,p_pay_calc_data.pay_basis));
2391     ELSE
2392       hr_utility.set_message_token('PAY_BASIS',
2393                                     ghr_pa_requests_pkg.get_lookup_meaning(800,'GHR_US_PAY_BASIS'
2394                                                                           ,l_pay_basis));
2395     END IF;
2396     raise ghr_pay_calc.unable_to_calculate;
2397   END IF;
2398  ELSE
2399    hr_utility.set_message(8301, 'GHR_38263_NO_CALC_DUAL_ACTION');
2400    raise ghr_pay_calc.unable_to_calculate;
2401  END IF;
2402 END IF;
2403 
2404 EXCEPTION
2405   WHEN others THEN
2406      -- Reset IN OUT parameters and set OUT parameters
2407 
2408        p_pay_calc_out_data  := NULL;
2409        p_retained_grade     := l_retained_grade;
2410 
2411    RAISE;
2412   hr_utility.set_location('Leaving ' || l_proc,8);
2413 END get_basic_pay;
2414 
2415 -- Bug#5114467 Calling proc for Calculating basic pay, locality rate and
2416 -- adjusted basic pay for employee in 'GM' pay plan and NOA 894 AC
2417 
2418 PROCEDURE get_894_GM_sp_basic_pay(p_grade_or_level          IN  VARCHAR2
2419                                  ,p_effective_date          IN  DATE
2420                                  ,p_user_table_id           IN  pay_user_tables.user_table_id%TYPE
2421                                  ,p_default_table_id        IN  NUMBER
2422                                  ,p_curr_basic_pay          IN  NUMBER
2423                                  ,p_duty_station_id         IN  ghr_duty_stations_f.duty_station_id%TYPE
2424                                  ,p_new_basic_pay           OUT NOCOPY NUMBER
2425 				                 ,p_new_adj_basic_pay       OUT NOCOPY NUMBER
2426                                  ,p_new_locality_adj        OUT NOCOPY NUMBER
2427                                  ,p_new_special_rate        OUT NOCOPY NUMBER
2428 				                 ) IS
2429 
2430 l_pay_plan                VARCHAR2(30);
2431 l_grade_or_level          VARCHAR2(60);
2432 l_PT_eff_start_date       DATE;
2433 l_eff_start_date          DATE;
2434 l_eff_end_date            DATE;
2435 --
2436 l_old_basic_pay           NUMBER;
2437 l_min_old_basic_pay       NUMBER;
2438 l_max_old_basic_pay       NUMBER;
2439 --
2440 l_new_basic_pay           NUMBER;
2441 l_cur_basic_pay           NUMBER;
2442 l_min_cur_basic_pay       NUMBER;
2443 l_max_cur_basic_pay       NUMBER;
2444 l_min_sr_basic_pay        NUMBER;
2445 l_max_sr_basic_pay        NUMBER;
2446 
2447 l_new_locality_adj        NUMBER;
2448 l_new_adj_basic_pay       NUMBER;
2449 
2450 l_temp_basic_pay          NUMBER;
2451 l_temp2_basic_pay         NUMBER;
2452 l_new_special_rate        NUMBER;
2453 
2454 l_new_locality_rate       NUMBER;
2455 l_loc_amnt_or_supp_rate   NUMBER;
2456 
2457 l_new_loc_perc_factor     NUMBER;
2458 l_user_table_id           NUMBER;
2459 l_dummy_step              NUMBER;
2460 l_grade                   NUMBER;
2461 
2462 l_default_table_id        NUMBER;
2463 l_duty_station_id         ghr_duty_stations_f.duty_station_id%TYPE;
2464 
2465 BEGIN
2466     l_grade_or_level := p_grade_or_level;
2467     l_PT_eff_start_date := p_effective_date;
2468     l_pay_plan := 'GS';
2469     l_default_table_id := p_default_table_id;
2470     l_user_table_id := p_user_table_id;
2471     l_old_basic_pay := p_curr_basic_pay;
2472     l_duty_station_id := p_duty_station_id;
2473 
2474     -- Start ->> Calculation Of New Basic Pay
2475 	get_min_pay_table_value(l_default_table_id
2476                          ,l_pay_plan
2477                          ,l_grade_or_level
2478                          ,l_PT_eff_start_date - 1
2479                          ,l_dummy_step
2480                          ,l_min_old_basic_pay
2481                          ,l_eff_start_date
2482                          ,l_eff_end_date);
2483 
2484 	 get_max_pay_table_value(l_default_table_id
2485                          ,l_pay_plan
2486                          ,l_grade_or_level
2487                          ,l_PT_eff_start_date - 1
2488                          ,l_dummy_step
2489                          ,l_max_old_basic_pay
2490                          ,l_eff_start_date
2491                          ,l_eff_end_date);
2492 
2493 	l_temp_basic_pay := l_old_basic_pay - l_min_old_basic_pay ;
2494     l_temp2_basic_pay := TRUNC( (l_temp_basic_pay/(l_max_old_basic_pay - l_min_old_basic_pay)),7);
2495 
2496     get_min_pay_table_value(l_default_table_id
2497                          ,l_pay_plan
2498                          ,l_grade_or_level
2499                          ,l_PT_eff_start_date
2500                          ,l_dummy_step
2501                          ,l_min_cur_basic_pay
2502                          ,l_eff_start_date
2503                          ,l_eff_end_date);
2504 
2505 	get_max_pay_table_value(l_default_table_id
2506                          ,l_pay_plan
2507                          ,l_grade_or_level
2508                          ,l_PT_eff_start_date
2509                          ,l_dummy_step
2510                          ,l_max_cur_basic_pay
2511                          ,l_eff_start_date
2512                          ,l_eff_end_date);
2513 
2514     l_new_basic_pay := l_min_cur_basic_pay + ROUND((l_temp2_basic_pay * (l_max_cur_basic_pay - l_min_cur_basic_pay)),0);
2515 	-- End ->> Calculation Of New Basic Pay
2516 
2517 	-- Start ->> Calculation of Adjusted Basic Pay
2518     l_new_loc_perc_factor       := (NVL(ghr_pay_calc.get_lpa_percentage(l_duty_station_id
2519 									                                   ,l_PT_eff_start_date
2520  	            						                               )
2521                                                                        ,0
2522                                        )
2523                                    )/100;
2524     l_new_locality_adj  := ROUND((l_new_basic_pay * l_new_loc_perc_factor),0);
2525 	l_new_locality_rate := l_new_basic_pay + l_new_locality_adj;
2526     -- End ->> Calculation of Adjusted Basic Pay
2527 
2528     -- Start ->> Calculation of special Rate amount
2529 
2530     get_min_pay_table_value(l_user_table_id
2531                          ,l_pay_plan
2532                          ,l_grade_or_level
2533                          ,l_PT_eff_start_date
2534                          ,l_dummy_step
2535                          ,l_min_sr_basic_pay
2536                          ,l_eff_start_date
2537                          ,l_eff_end_date);
2538 
2539 	get_max_pay_table_value(l_user_table_id
2540                          ,l_pay_plan
2541                          ,l_grade_or_level
2542                          ,l_PT_eff_start_date
2543                          ,l_dummy_step
2544                          ,l_max_sr_basic_pay
2545                          ,l_eff_start_date
2546                          ,l_eff_end_date);
2547 	l_new_special_rate := l_min_sr_basic_pay + ROUND((l_temp2_basic_pay*(l_max_sr_basic_pay - l_min_sr_basic_pay)),0);
2548 	-- End ->> Calculation of special Rate amount
2549 
2550     -- Start ->> Determining greater of  locality rate and Special rate
2551     IF l_new_locality_rate > l_new_special_rate THEN
2552         l_new_adj_basic_pay := l_new_locality_rate;
2553     ELSE
2554         l_new_adj_basic_pay := l_new_special_rate;
2555     END IF;
2556 
2557     l_loc_amnt_or_supp_rate := l_new_adj_basic_pay - l_new_basic_pay;
2558     -- End ->> Determining greater of  locality rate and Special rate
2559 
2560 	-- Assigning the OUT parameters
2561 	p_new_basic_pay     := l_new_basic_pay;
2562     p_new_adj_basic_pay := l_new_adj_basic_pay;
2563 	p_new_locality_adj  := l_loc_amnt_or_supp_rate;
2564     p_new_special_rate  := l_new_special_rate;
2565 
2566 
2567 END get_894_GM_sp_basic_pay;
2568 
2569 
2570 -- Bug#5114467 Calling proc for Calculating basic pay, locality rate and
2571 -- adjusted basic pay for WGI employee in 'GM' pay plan AC
2572 
2573 PROCEDURE get_wgi_GM_sp_basic_pay(p_grade_or_level          IN  VARCHAR2
2574                                  ,p_effective_date          IN  DATE
2575                                  ,p_user_table_id           IN  pay_user_tables.user_table_id%TYPE
2576                                  ,p_default_table_id        IN  NUMBER
2577                                  ,p_curr_basic_pay          IN  NUMBER
2578                                  ,p_duty_station_id         IN  ghr_duty_stations_f.duty_station_id%TYPE
2579                                  ,p_new_basic_pay           OUT NOCOPY NUMBER
2580 				                 ,p_new_adj_basic_pay       OUT NOCOPY NUMBER
2581 				                 ,p_new_locality_adj        OUT NOCOPY NUMBER
2582 				                 ) IS
2583 
2584 l_pay_plan                VARCHAR2(30);
2585 l_grade_or_level          VARCHAR2(60);
2586 l_PT_eff_start_date       DATE;
2587 l_eff_start_date          DATE;
2588 l_eff_end_date            DATE;
2589 --
2590 l_new_basic_pay           NUMBER;
2591 l_old_basic_pay           NUMBER;
2592 l_min_old_basic_pay       NUMBER;
2593 l_max_old_basic_pay       NUMBER;
2594 --
2595 l_cur_basic_pay           NUMBER;
2596 l_min_sp_basic_pay        NUMBER;
2597 l_max_sp_basic_pay        NUMBER;
2598 
2599 l_new_locality_adj        NUMBER;
2600 l_new_adj_basic_pay       NUMBER;
2601 
2602 l_temp_basic_pay          NUMBER;
2603 l_temp2_basic_pay         NUMBER;
2604 
2605 l_new_locality_rate       NUMBER;
2606 l_loc_amnt_or_supp_rate   NUMBER;
2607 l_new_special_rate        NUMBER;
2608 
2609 l_new_loc_perc_factor     NUMBER;
2610 l_user_table_id           NUMBER;
2611 l_dummy_step              NUMBER;
2612 l_grade                   NUMBER;
2613 
2614 l_default_table_id        NUMBER;
2615 l_duty_station_id         ghr_duty_stations_f.duty_station_id%TYPE;
2616 
2617 BEGIN
2618 --5919700 assigning p_grade_or_level to l_grade_or_level
2619     l_grade_or_level := p_grade_or_level;
2620     l_PT_eff_start_date := p_effective_date;
2621     l_pay_plan := 'GS';
2622     l_default_table_id := p_default_table_id;
2623     l_user_table_id := p_user_table_id;
2624     l_old_basic_pay := p_curr_basic_pay;
2625     l_duty_station_id := p_duty_station_id;
2626 
2627      -- Start ->> Calculation Of New Basic Pay
2628 	 get_min_pay_table_value(l_default_table_id
2629                              ,'GS'
2630                              ,l_grade_or_level
2631                              ,l_PT_eff_start_date
2632                              ,l_dummy_step
2633                              ,l_min_old_basic_pay
2634                              ,l_eff_start_date
2635                              ,l_eff_end_date);
2636 
2637      get_max_pay_table_value(l_default_table_id
2638                              ,'GS'
2639                              ,l_grade_or_level
2640                              ,l_PT_eff_start_date
2641                              ,l_dummy_step
2642                              ,l_max_old_basic_pay
2643                              ,l_eff_start_date
2644                              ,l_eff_end_date);
2645 
2646 	 l_new_basic_pay := l_old_basic_pay + (l_max_old_basic_pay - l_min_old_basic_pay)/9;
2647      -- End ->> Calculation Of New Basic Pay
2648 
2649 	 -- Start ->> Calculation of special Rate amount
2650 	 l_new_special_rate := TRUNC(((l_new_basic_pay - l_min_old_basic_pay)/
2651                                     (l_max_old_basic_pay - l_min_old_basic_pay)
2652 				                   )
2653 				                    , 7
2654 				                  );
2655 	 -- End ->> Calculation of special Rate amount
2656 
2657      -- Start -->> Calculate relative rate in range for the special rate
2658      get_min_pay_table_value( l_user_table_id
2659                              ,'GS'
2660                              ,l_grade_or_level
2661                              ,l_PT_eff_start_date
2662                              ,l_dummy_step
2663                              ,l_min_sp_basic_pay
2664                              ,l_eff_start_date
2665                              ,l_eff_end_date);
2666 
2667      get_max_pay_table_value(l_user_table_id
2668                              ,'GS'
2669                              ,l_grade_or_level
2670                              ,l_PT_eff_start_date
2671                              ,l_dummy_step
2672                              ,l_max_sp_basic_pay
2673                              ,l_eff_start_date
2674                              ,l_eff_end_date);
2675 
2676      l_new_special_rate := l_min_sp_basic_pay + ROUND (((l_max_sp_basic_pay - l_min_sp_basic_pay) * l_new_special_rate),0);
2677      -- End -->> Calculate relative rate in range for the special rate
2678 
2679      -- Start ->> Calculation of Locality Rate
2680      l_new_loc_perc_factor       := (NVL(ghr_pay_calc.get_lpa_percentage(l_duty_station_id
2681 									                                   ,l_PT_eff_start_date
2682  	            						                               )
2683                                                                        ,0
2684                                        )
2685                                    )/100;
2686      l_new_locality_adj  := ROUND((l_new_basic_pay * l_new_loc_perc_factor),0);
2687      l_new_locality_rate := l_new_basic_pay + l_new_locality_adj;
2688      -- End ->> Calculation of Locality Rate
2689 
2690      -- Start ->> Calculation of Adjusted Basic Pay
2691      IF l_new_special_rate > l_new_locality_rate THEN
2692          l_new_adj_basic_pay := l_new_special_rate;
2693      ELSE
2694          l_new_adj_basic_pay := l_new_locality_rate;
2695      END IF;
2696      l_loc_amnt_or_supp_rate := l_new_adj_basic_pay - l_new_basic_pay;
2697      -- End ->> Calculation of Adjusted Basic Pay
2698 
2699 	 -- Assigning the OUT parameters
2700 	 p_new_basic_pay     := l_new_basic_pay;
2701      p_new_adj_basic_pay := l_new_adj_basic_pay;
2702 	 p_new_locality_adj  := l_loc_amnt_or_supp_rate;
2703 
2704 END get_wgi_GM_sp_basic_pay;
2705 --
2706 
2707 PROCEDURE get_basic_pay_SAL890_6step(p_pay_calc_data     IN  ghr_pay_calc.pay_calc_in_rec_type
2708                                     ,p_retained_grade    IN  ghr_pay_calc.retained_grade_rec_type
2709                                     ,p_pay_table_data    IN  VARCHAR2
2710                                     ,p_basic_pay         OUT NOCOPY NUMBER
2711 				    ) IS
2712 l_user_table_id      NUMBER;
2713 l_pay_plan           VARCHAR2(30);
2714 l_grade_or_level     VARCHAR2(60);
2715 l_step_or_rate       VARCHAR2(30);
2716 l_pay_basis          VARCHAR2(30);
2717 l_effective_date     DATE;
2718 
2719 l_curr_basic_pay      NUMBER;
2720 l_old_rangeval_min    NUMBER;
2721 l_old_rangeval_max    NUMBER;
2722 l_calc_basic_pay      NUMBER;
2723 l_new_rangeval_min    NUMBER;
2724 l_new_rangeval_max    NUMBER;
2725 
2726 -- perf cert
2727 l_business_group_id	per_positions.organization_id%TYPE;
2728 l_agency_subele_code	per_position_definitions.segment4%TYPE;
2729 l_org_id		per_positions.organization_id%TYPE;
2730 l_old_non_perfagn_max   NUMBER;
2731 l_new_non_perfagn_max   NUMBER;
2732 
2733 
2734 stp_1 NUMBER;
2735 stp_2 NUMBER;
2736 stp_3 NUMBER;
2737 stp_4 NUMBER;
2738 stp_5 NUMBER;
2739 l_basic_pay NUMBER;
2740 
2741 CURSOR cur_get_pos_org(p_pos_id		per_positions.position_id%TYPE,
2742 		      p_eff_Date ghr_pa_requests.effective_date%TYPE)
2743 IS
2744 SELECT ORGANIZATION_ID FROM HR_POSITIONS_F
2745 WHERE  position_id=p_pos_id
2746 AND    p_eff_date between effective_start_Date and effective_end_date;
2747 
2748 BEGIN
2749   -- First work out what pay table data to use
2750   --
2751 
2752   IF p_pay_table_data  = 'POSITION' THEN
2753     l_pay_plan       := p_pay_calc_data.pay_plan;
2754     l_user_table_id  := p_pay_calc_data.user_table_id;
2755     l_grade_or_level := p_pay_calc_data.grade_or_level;
2756     l_pay_basis      := p_pay_calc_data.pay_basis;
2757   ELSE
2758     l_pay_plan       := p_retained_grade.pay_plan;
2759     l_user_table_id  := p_retained_grade.user_table_id;
2760     l_grade_or_level := p_retained_grade.grade_or_level;
2761     l_pay_basis      := p_retained_grade.pay_basis;
2762   END IF;
2763 
2764   l_curr_basic_pay := p_pay_calc_data.current_basic_pay;
2765   l_effective_date := NVL(p_pay_calc_data.effective_date,TRUNC(sysdate));
2766 
2767   -- Added for Perf certification
2768   l_business_group_id	 := FND_PROFILE.value('PER_BUSINESS_GROUP_ID');
2769   FOR cur_get_pos_org_rec IN cur_get_pos_org (p_pay_calc_data.position_id, l_effective_date)
2770   LOOP
2771      l_org_id	:=	cur_get_pos_org_rec.organization_id;
2772   END LOOP;
2773 
2774   --fetching min and max range values on the preceding day of pay adjustment
2775   ghr_pay_calc.get_open_pay_table_values(p_user_table_id     => l_user_table_id
2776                                         ,p_pay_plan          => l_pay_plan
2777                                         ,p_grade_or_level    => l_grade_or_level
2778                                         ,p_effective_date    => l_effective_date-1
2779                                         ,p_row_high          => l_old_rangeval_max
2780                                         ,p_row_low           => l_old_rangeval_min);
2781 
2782   --fetching current min and max range values
2783   ghr_pay_calc.get_open_pay_table_values(p_user_table_id     => l_user_table_id
2784                                         ,p_pay_plan          => l_pay_plan
2785                                         ,p_grade_or_level    => l_grade_or_level
2786                                         ,p_effective_date    => l_effective_date
2787                                         ,p_row_high          => l_new_rangeval_max
2788                                         ,p_row_low           => l_new_rangeval_min);
2789 
2790   -- checking for perf certification of the agency if the agency non certified need to
2791   -- consider EX03 pay table value as a max value
2792 
2793  -- Bug # 8374810 added to fetch EX-03 value of current and previous years for
2794  -- non certified agencies
2795 
2796   l_agency_subele_code := ghr_api.get_position_agency_code_pos(
2797 				p_position_id		=> p_pay_calc_data.position_id,
2798 				p_business_group_id	=> l_business_group_id,
2799 				p_effective_date	=> l_effective_date);
2800 
2801   IF NOT(ghr_pay_caps.perf_certified(l_agency_subele_code,l_org_id, l_pay_plan, l_effective_date))  THEN
2802         l_new_non_perfagn_max := ghr_pay_calc.get_standard_pay_table_value('EX'
2803   			                                                  ,'03'
2804 					     			          ,'00'
2805                                                                           ,l_effective_date);
2806         l_old_non_perfagn_max := ghr_pay_calc.get_standard_pay_table_value('EX'
2807               	                                                          ,'03'
2808 								          ,'00'
2809                                                                           ,l_effective_date-1);
2810         l_new_rangeval_max  :=  l_new_non_perfagn_max;
2811 	l_old_rangeval_max  :=  l_old_non_perfagn_max;
2812   END IF;
2813 
2814   --Step 1
2815   stp_1 := l_curr_basic_pay - l_old_rangeval_min;
2816 
2817   --Step 2
2818   stp_2 := l_old_rangeval_max - l_old_rangeval_min;
2819 
2820   --Step 3
2821   stp_3 := TRUNC(stp_1/stp_2,7);
2822 
2823   -- Step 4
2824   stp_4 := l_new_rangeval_max - l_new_rangeval_min;
2825 
2826   --Step 5
2827   --stp_5 := CEIL(stp_3 * stp_4);
2828     stp_5 := ROUND(stp_3 * stp_4);
2829 
2830   --Step 6
2831   l_calc_basic_pay := stp_5 + l_new_rangeval_min;
2832 
2833 p_basic_pay := l_calc_basic_pay;
2834 
2835 EXCEPTION
2836   WHEN others THEN
2837      -- Reset IN OUT parameters and set OUT parameters
2838        p_basic_pay             := NULL;
2839 
2840    RAISE;
2841 
2842 END get_basic_pay_SAL890_6step;
2843 
2844 END ghr_pc_basic_pay;