DBA Data[Home] [Help]

PACKAGE BODY: APPS.GHR_LACS_REMARKS

Source


1 PACKAGE BODY GHR_LACS_REMARKS AS
2 /* $Header: ghlacrem.pkb 120.15.12020000.2 2012/07/06 09:58:57 vmididho ship $ */
3   g_requests_rec		ghr_pa_requests%ROWTYPE;
4   g_position_id                ghr_pa_requests.from_position_id%TYPE;
5   g_pay_plan                   ghr_pa_requests.from_step_or_rate%TYPE;
6   g_step_or_rate               ghr_pa_requests.from_pay_plan%TYPE;
7   g_grade_or_level             ghr_pa_requests.from_grade_or_level%TYPE;
8   g_loc_percentage	       ghr_locality_pay_areas_f.adjustment_percentage%TYPE;
9   -- Added for MSL expanded func
10   g_pay_table_id               VARCHAR2(4);
11   g_new_prd                    VARCHAR2(10);
12   g_leo_posn_indicator         per_position_extra_info.poei_information16%TYPE;
13   g_intl_posn_indicator        per_position_extra_info.poei_information15%TYPE; ---- variable declared for Bug#4130683
14   g_equivalent_pay_plan        ghr_pay_plans.equivalent_pay_plan%TYPE;
15   l_pos_extra_info_rec         per_position_extra_info%ROWTYPE;
16   l_package                    VARCHAR2(30) := 'GHR_LACS_REMARKS';
17   l_location                   VARCHAR2(200);
18 
19   PROCEDURE Fetch_Data(
20      p_pa_request_id  ghr_pa_requests.pa_request_id%TYPE)
21   IS
22      l_grade_id            per_grades.grade_id%TYPE;
23      l_assignment_id       per_assignments_f.assignment_id%TYPE;
24      l_retained_grade_rec  ghr_pay_calc.retained_grade_rec_type;
25      l_multi_error_flag    boolean;
26      cursor c_grade_kff (grd_id number) is
27              select gdf.segment1
28                    ,gdf.segment2
29                from per_grades grd,
30                     per_grade_definitions gdf
31               where grd.grade_id = grd_id
32                 and grd.grade_definition_id = gdf.grade_definition_id;
33   BEGIN
34     -- Fetch PA_REQUESTS Table
35     l_location := 'Apply_894_Rules:Fetch_Data:Fetching PA_REQUESTS';
36     SELECT *
37       INTO g_requests_rec
38       FROM ghr_pa_requests
39      WHERE pa_request_id = p_pa_request_id;
40     g_position_id :=  g_requests_rec.from_position_id;
41     BEGIN
42       l_location := 'Apply_894_Rules:Fetch_Data:' ||
43                     '=>ghr_pc_basic_pay.get_retained_grade_details';
44       l_retained_grade_rec := ghr_pc_basic_pay.get_retained_grade_details
45                                 ( g_requests_rec.person_id,
46                                   g_requests_rec.effective_date);
47     EXCEPTION
48       WHEN ghr_pay_calc.pay_calc_message THEN
49         NULL;
50     END;
51     -- Bug#4901888
52 
53     IF l_retained_grade_rec.pay_plan IS NOT NULL THEN
54       g_step_or_rate   := l_retained_grade_rec.step_or_rate;
55       g_pay_plan       := l_retained_grade_rec.pay_plan;
56       g_grade_or_level := l_retained_grade_rec.grade_or_level;
57       g_pay_table_id   := SUBSTR(ghr_pay_calc.get_user_table_name(
58                                   l_retained_grade_rec.user_table_id), 1, 4);
59     ELSE
60       l_location := 'Apply_894_Rules:Fetch_Data:Fetching Assignments';
61       SELECT paf.assignment_id, paf.grade_id
62         INTO l_assignment_id, l_grade_id
63         FROM per_assignments_f paf
64        WHERE paf.person_id = g_requests_rec.person_id
65          AND paf.primary_flag = 'Y'
66          AND paf.assignment_type <> 'B'
67          AND g_requests_rec.effective_date BETWEEN
68                 paf.effective_start_date AND
69                 NVL(paf.effective_end_date,
70                     g_requests_rec.effective_date+1);
71 
72       FOR c_grade_kff_rec IN c_grade_kff (l_grade_id)
73       LOOP
74          g_pay_plan          := c_grade_kff_rec.segment1;
75          g_grade_or_level    := c_grade_kff_rec.segment2;
76          EXIT;
77       END LOOP;
78 
79       -- Fetch GHR_US_POS_VALID_GRADE information
80       l_location := 'Apply_894_Rules:Fetch_Data:' ||
81                     'Fetching GHR_US_POS_VALID_GRADE info';
82       ghr_history_fetch.fetch_positionei
83        (p_position_id      => g_position_id,
84         p_information_type => 'GHR_US_POS_VALID_GRADE',
85         p_date_effective   => g_requests_rec.effective_date,
86         p_pos_ei_data      => l_pos_extra_info_rec);
87       g_pay_table_id := SUBSTR(ghr_pay_calc.get_user_table_name(
88                                 l_pos_extra_info_rec.poei_information5), 1, 4);
89     END IF;
90     hr_utility.set_location('Pay Table ID Bef Calc Pay Table'||g_pay_table_id,10);
91     -- Bug#4901888 Added the following IF condition to consider the Calculation
92     --             pay table to determine the LAC/Remarks.(using TO PAY TABLE ID
93     --             AS IT HOLDS THE CALC PAY TABLE ID).
94     IF g_requests_rec.to_pay_table_identifier IS NOT NULL THEN
95         g_pay_table_id := SUBSTR(ghr_pay_calc.get_user_table_name(
96                                 g_requests_rec.to_pay_table_identifier), 1, 4);
97     END IF;
98     hr_utility.set_location('Pay Table ID Aft Calc Pay Table'||g_pay_table_id,50);
99     -- Bug#4901888 End
100     l_location := 'Apply_894_Rules:Fetch_Data:Fetching Extra Information';
101     -- Fetch GHR_US_POS_GRP2 information
102     ghr_history_fetch.fetch_positionei
103      (p_position_id      => g_position_id,
104       p_information_type => 'GHR_US_POS_GRP2',
105       p_date_effective   => g_requests_rec.effective_date,
106       p_pos_ei_data      => l_pos_extra_info_rec);
107     g_leo_posn_indicator := NVL(l_pos_extra_info_rec.poei_information16,'0');
108     g_intl_posn_indicator := NVL(l_pos_extra_info_rec.poei_information15,'0'); -- variable for Bug#4130683
109     -- Fetch Equivalent Pay Plan
110     SELECT equivalent_pay_plan
111       INTO g_equivalent_pay_plan
112       FROM ghr_pay_plans
113      WHERE pay_plan = g_pay_plan;
114 
115   END;
116 
117   PROCEDURE Apply_894_Rules(
118      p_pa_request_id  ghr_pa_requests.pa_request_id%TYPE,
119      p_new_prd        ghr_pa_requests.pay_rate_determinant%TYPE,
120      p_old_prd        ghr_pa_requests.pay_rate_determinant%TYPE,
121      p_out_step_or_rate GHR_PA_REQUESTS.TO_STEP_OR_RATE%TYPE,
122      p_eo_nbr         VARCHAR2 := NULL,
123      p_eo_date        DATE := NULL,
124      p_opm_nbr        VARCHAR2 := NULL,
125      p_opm_date       DATE := NULL,
126      p_errbuf         IN OUT NOCOPY VARCHAR2,
127      p_retcode        IN OUT NOCOPY NUMBER)
128   IS
129      l_la_code1                   ghr_pa_requests.first_action_la_code1%TYPE;
130      l_la_code2                   ghr_pa_requests.first_action_la_code2%TYPE;
131      l_la_desc1                   ghr_pa_requests.first_action_la_desc1%TYPE;
132      --Bug#4256022 Declared l_la_desc1_out variable.
133      l_la_desc1_out               ghr_pa_requests.first_action_la_desc1%TYPE;
134      l_la_desc2                   ghr_pa_requests.first_action_la_desc2%TYPE;
135      --Bug#4256022 Declared l_la_desc2_out variable.
136      l_la_desc2_out               ghr_pa_requests.first_action_la_desc1%TYPE;
137      l_insrt_value1                ghr_pa_requests.first_lac1_information1%TYPE;
138      l_insrt_value2                ghr_pa_requests.first_lac1_information2%TYPE;
139      l_retcode			  VARCHAR2(50) ; --For NOCOPY Changes
140      l_errbuf			  NUMBER ;  --For NOCOPY Changes
141 
142      l_adj_bp                     ghr_pa_requests.from_adj_basic_pay%type;
143      l_pay_cap_amount             ghr_pa_requests.from_adj_basic_pay%type;
144      l_create_rmk                 BOOLEAN:=FALSE;
145      l_remark_id                  ghr_pa_remarks.pa_remark_id%type;
146      l_loc_area_id		  ghr_duty_Stations_f.locality_pay_area_id%type;
147      l_loc_perc  		  ghr_locality_pay_areas_f.adjustment_percentage%TYPE;
148      --Begin Bug 10387022
149      l_rpa_type			  ghr_pa_requests.rpa_type%type;
150      CURSOR cur_rpa_type
151 	     IS
152 	     SELECT   rpa_type
153 	     FROM     ghr_pa_requests
154 	     WHERE   pa_request_id =p_pa_request_id;
155      -- End Bug 10387022
156 
157      CURSOR cur_loc_area_id(p_ds_id	ghr_duty_Stations_f.duty_station_id%type,
158 			    p_eff_date  ghr_pa_requests.effective_date%type)
159      IS
160      SELECT   locality_pay_area_id
161      FROM     ghr_duty_stations_f
162      WHERE    duty_station_id=p_ds_id
163      AND      p_eff_date between effective_start_date and effective_end_date;
164 
165      CURSOR cur_loc_perc
166       (p_ds_loc_area_id	 ghr_duty_Stations_f.locality_pay_area_id%type,
167        p_eff_date        ghr_pa_requests.effective_date%type)
168      IS
169       SELECT adjustment_percentage
170       FROM   ghr_locality_pay_areas_f
171       WHERE  locality_pay_area_id = p_ds_loc_area_id
172       AND    p_eff_date between effective_start_date and effective_end_date;
173 
174      PROCEDURE Create_Remark(p_remark_code  in ghr_remarks.code%TYPE,
175                              p_out_step_or_rate GHR_PA_REQUESTS.TO_STEP_OR_RATE%TYPE)
176      IS
177        l_remark_id           ghr_remarks.remark_id%TYPE;
178        l_pa_remark_id        ghr_pa_remarks.pa_remark_id%TYPE;
179        l_object_version_nbr  ghr_pa_remarks.object_version_number%TYPE;
180        l_remark_desc         ghr_remarks.description%TYPE;
181        l_remark_information1 ghr_pa_remarks.remark_code_information1%TYPE;
182        l_remark_information2 ghr_pa_remarks.remark_code_information2%TYPE;
183        l_remark_information3 ghr_pa_remarks.remark_code_information3%TYPE;
184        l_remark_information4 ghr_pa_remarks.remark_code_information4%TYPE;
185        l_remark_information5 ghr_pa_remarks.remark_code_information5%TYPE;
186 			--Pradeep added for the Bug#3974979.
187        l_remark_desc_out     ghr_remarks.description%TYPE;
188 
189      BEGIN
190        l_location := 'Apply_894_Rules:Create_Remark(' || p_remark_code || ')';
191        ghr_mass_actions_pkg.get_remark_id_desc
192          (p_remark_code       => p_remark_code,
193           p_effective_date    => g_requests_rec.effective_date,
194           p_remark_id         => l_remark_id,
195           p_remark_desc       => l_remark_desc);
196 
197        l_remark_information1 := NULL;
198        l_remark_information2 := NULL;
199        l_remark_information3 := NULL;
200        l_remark_information4 := NULL;
201        l_remark_information5 := NULL;
202 
203        -- Remarks with Insertion Values
204        IF p_remark_code IN ('X44','P81','P99','P70','P71','P07','P72','P92') THEN
205          IF p_remark_code = 'X44' THEN
206            l_remark_information1 := nvl(p_out_step_or_rate,g_step_or_rate);
207            l_remark_information2 := g_pay_plan || '-' || g_grade_or_level;
208          ELSIF p_remark_code = 'P70' THEN
209            l_remark_information1 := TO_CHAR(g_requests_rec.to_retention_allowance);
210          ELSIF p_remark_code = 'P71' THEN
211            l_remark_information1 := TO_CHAR(g_requests_rec.to_staffing_differential);
212          ELSIF p_remark_code = 'P72' THEN
213            l_remark_information1 := TO_CHAR(g_requests_rec.to_supervisory_differential);
214          -- GPPA Update 46
215          ELSIF p_remark_code = 'P07' THEN
216            l_remark_information1 := g_pay_table_id;
217          --
218          ELSIF p_remark_code = 'P81' THEN
219            l_remark_information1 := TO_CHAR(g_requests_rec.to_au_overtime);
220          ELSIF p_remark_code = 'P99' THEN
221            l_remark_information1 := TO_CHAR(g_requests_rec.to_availability_pay);
222          -- MSL expanded percentage
223 	 ELSIF p_remark_code = 'P92' THEN
224 
225 	    FOR loc_area IN cur_loc_area_id(g_requests_rec.duty_station_id,
226 	  			            g_requests_rec.effective_date )
227   	    LOOP
228 		l_loc_area_id	:= loc_area.locality_pay_area_id;
229 
230 		-- Can find percentage only when there is percentage
231 		--
232 		FOR loc_perc IN cur_loc_perc(l_loc_area_id,g_requests_rec.effective_date )
233 		LOOP
234 	 	 l_loc_perc	  := loc_perc.adjustment_percentage;
235 		 g_loc_percentage := l_loc_perc;
236 		END LOOP;
237 	    END LOOP;
238                  l_remark_desc := replace(l_remark_desc,'__',to_char(g_loc_percentage));
239 
240 		-- HARD CODING for this remark only. replacing 2 hyphens with the percent
241          END IF;
242 		--Pradeep commented l_remark_desc and added l_remark_desc_out for the Bug#3974979.
243          ghr_mass_actions_pkg.replace_insertion_values
244            (p_desc              => l_remark_desc,
245             p_information1      => l_remark_information1,
246             p_information2      => l_remark_information2,
247             p_information3      => l_remark_information3,
248             p_information4      => l_remark_information4,
249             p_information5      => l_remark_information5,
250             p_desc_out          => l_remark_desc_out
251 				);
252 			l_remark_desc := l_remark_desc_out;
253 
254        END IF;
255        ghr_pa_remarks_api.create_pa_remarks
256          (p_pa_request_id            => p_pa_request_id,
257           p_remark_id                => l_remark_id,
258           p_description              => l_remark_desc,
259           p_remark_code_information1 => l_remark_information1,
260           p_remark_code_information2 => l_remark_information2,
261           p_remark_code_information3 => l_remark_information3,
262           p_remark_code_information4 => l_remark_information4,
263           p_remark_code_information5 => l_remark_information5,
264           p_pa_remark_id             => l_pa_remark_id,
265           p_object_version_number    => l_object_version_nbr);
266      END;
267 
268   BEGIN
269     p_retcode := 0;
270     p_errbuf  := NULL;
271     g_new_prd := p_new_prd;
272     Fetch_Data(p_pa_request_id);
273     -- 894 LAC/Remarks Rules
274   --Begin Bug 10387022
275   FOR p_rpa_type IN cur_rpa_type LOOP
276 	l_rpa_type := p_rpa_type.rpa_type;
277   END LOOP;
278   --Begin Bug 10387022
279   IF g_requests_rec.first_noa_code = '894' AND l_rpa_type <> 'MLC' THEN -- Bug 10387022 added MLC condition
280       -- GS Equivalent Rules
281       IF g_equivalent_pay_plan = 'GS' THEN
282         l_location := 'Apply_894_Rules:GS Equivalent Plan Rules';
283         IF g_pay_plan IN ('GS','GM','GH') AND
284            p_new_prd  IN ('2','4')
285         THEN
286           l_la_code1 := 'QWM';
287           l_la_code2 := 'ZLM';
288         ELSIF g_pay_plan = 'GG' AND p_new_prd NOT IN ('U','V')THEN  ------and p_new_prd <> 'M' THEN
289             -- Bug#4882715 Added the IF condition
290             --IF g_leo_posn_indicator IN ('1','2') THEN
291 	    -- Bug#4130683 Changed the IF condition
292 	    IF g_intl_posn_indicator IN ('2') THEN
293                 l_la_code1 := 'UAM';
294                 l_la_code2 := 'ZLM';
295             ELSE
296                 l_la_code1 := 'ZLM';
297             END IF;
298         -- Bug#4130683 Added on ELSEIF condition to include 'GL' pay plan
299 	ELSIF g_pay_plan = 'GL' THEN
300 	    IF p_new_prd NOT IN ('U','V') THEN
301                 IF g_intl_posn_indicator IN ('2') THEN
302                     l_la_code1 := 'UAM';
303                     l_la_code2 := 'ZLM';
304                 ELSE
305                     l_la_code1 := 'ZTW';
306 		END IF;
307             ELSIF g_intl_posn_indicator NOT IN ('2') THEN
308 	            l_la_code1 := 'ZTW';
309 	    END IF;
310             -- Bug#4882715
311         ELSIF g_pay_plan in ('CA','AA','AL') AND p_new_prd IN ('A','B','E','F') THEN
312           l_la_code1 := 'ZLM';
313         ELSIF g_pay_plan in ('CA','AA','AL') AND
314               p_new_prd NOT IN ('A','B','E','F','U','V','J','K','R','S','3','M','2','4') THEN
315           l_la_code1 := 'ZLM';
316         ELSIF g_pay_plan IN ('EX') AND
317               p_new_prd NOT IN ('A','B','E','F','U','V','J','K','R','S','3','M','2','4') AND
318               g_pay_table_id = '0000'
319         THEN
320           l_la_code1 := 'ZLM';
321         ELSIF g_pay_plan IN ('SL','ST','IP') AND
322               p_new_prd NOT IN ('A','B','E','F','U','V','J','K','R','S','3','M','2','4') AND
323               g_pay_table_id = 'ESSL'
324         THEN
325           l_la_code1 := 'ZLM';
326           l_la_code2 := 'ZLM';
327         ELSE
328           IF p_new_prd = 'M' THEN
329             l_la_code1 := 'QHP';
330             l_la_code2 := 'ZLM';
331           ELSE
332               l_la_code2 := 'ZLM';
333               IF g_pay_table_id = '0000' THEN
334                 l_la_code1 := 'QWM';
335               ELSIF g_pay_table_id <> '0491' THEN
336                 IF p_new_prd IN ('J','K','R','S','U','V','3') THEN
337                   l_la_code1 := 'QJP';
338                 ELSE
339                   l_la_code1 := 'QHP';
340                 END IF;
341               END IF;
342             IF g_leo_posn_indicator IN ('1','2') AND
343                   g_pay_table_id = '0491'
344             THEN
345               l_la_code1 := 'ZTW';
346               l_la_code2 := NULL;
347             END IF;
348           END IF;
349         END IF;
350       --Bug 5931199 added pay plan = FE condition as FE is nomore ES equ pay plan
351       ELSIF g_equivalent_pay_plan = 'ES' OR g_pay_plan = 'FE' THEN -- ES Equivalent Rules
352         l_location := 'Apply_894_Rules:ES Equivalent Plan Rules';
353 
354         IF g_pay_plan IN ('ES','EP','IE','FE') AND g_pay_table_id = 'ESSL' THEN
355               l_la_code1 := 'VWZ';
356 
357                 l_adj_bp := g_requests_rec.from_adj_basic_pay;
358 
359                       l_pay_cap_amount := ghr_pay_calc.get_standard_pay_table_value('EX'
360                                                                    ,'02'
361                                                                    ,'00'
362                                                                    ,g_requests_rec.effective_date);
363 
364                       If l_adj_bp >= (l_pay_cap_amount * 86.5)/100 THEN
365                               l_create_rmk :=TRUE;
366                       ELSE
367                               l_create_rmk :=FALSE;
368                       END IF;
369 
370                       IF l_create_rmk THEN
371                          Create_remark('M97',p_out_step_or_rate);
372                       END IF;
373 
374         END IF;
375       ELSIF g_equivalent_pay_plan = 'SL' THEN
376         IF g_pay_plan IN ('SL','ST','IP') AND
377               p_new_prd NOT IN ('A','B','E','F','U','V','J','K','R','S','3','M','2','4') AND
378               g_pay_table_id = 'ESSL'      THEN
379           l_la_code1 := 'ZLM';
380           l_la_code2 := 'ZLM';
381         END IF;
382       ELSIF g_equivalent_pay_plan = 'FW' THEN -- FWS Equivalent Rules
383         l_location := 'Apply_894_Rules:FWS Equivalent Plan Rules';
384         IF p_new_prd NOT IN ('A','B','E','F','U','V','J','K','R','S','3') THEN
385           l_la_code1 := 'FNM';
386         ELSIF p_new_prd IN ('A','B','E','F') THEN
387           l_la_code1 := 'FNM';
388           l_la_code2 := 'VLJ';
389         ELSIF p_new_prd IN ('J','K','R','S','U','V','3') THEN
390           l_la_code1 := 'FNM';
391           l_la_code2 := 'VSJ';
392         END IF;
393       END IF; -- Pay Plan Equivalent Rules
394 
395       --7636318
396       IF  g_pay_plan IN ('IG') THEN
397 	  l_la_code1 := 'ZLM';
398       END IF;
399 	  --7636318
400 
401 
402       -- Insertion Values for LAC ZLM (EO Nbr or OPM Nbr will be used).
403       -- Updated 11-SEP-1999: EO Nbr will be the only one used for Ins. Value
404       l_location := 'Apply_894_Rules:Determining Insertion Value';
405       IF l_la_code1 IN ('ZLM', 'UNM') OR l_la_code2 IN ('ZLM', 'UNM') THEN
406         l_insrt_value1 := 'E.O. ' || p_eo_nbr || ', Dated ' ||
407                          TO_CHAR(p_eo_date, 'DD-MON-YYYY');
408         l_insrt_value2 := 'E.O. ' || p_eo_nbr || ', Dated ' ||
409                          TO_CHAR(p_eo_date, 'DD-MON-YYYY');
410       END IF;
411       IF g_pay_plan IN ('SL','ST','IP') AND
412               p_new_prd NOT IN ('A','B','E','F','U','V','J','K','R','S','3','M','2','4') AND
413               g_pay_table_id = 'ESSL' THEN
414               l_insrt_value1 := 'Reg. 534.504';
415       END IF;
416 
417       IF p_retcode = 0 THEN
418         IF l_la_code1 IS NOT NULL THEN -- Update GHR_PA_REQUESTS with new LACs
419           l_location := 'Apply_894_Rules:Replacing Insertion Value';
420           SELECT description
421             INTO l_la_desc1
422             FROM fnd_common_lookups fcl
423            WHERE fcl.lookup_code = l_la_code1
424              AND fcl.application_id = 800
425              AND fcl.lookup_type = 'GHR_US_LEGAL_AUTHORITY'
426              AND fcl.enabled_flag = 'Y'
427              AND g_requests_rec.effective_date BETWEEN
428                  NVL(fcl.start_date_active,
429                      g_requests_rec.effective_date) AND
430                  NVL(fcl.end_date_active, g_requests_rec.effective_date);
431           IF l_la_code1 in ('ZLM','UNM')  THEN
432 	    -- Bug#4256022 Passed the variable l_la_desc1_out and assigned
433 	    -- the value back to l_la_desc1 to avoid NOCOPY related problems.
434             ghr_mass_actions_pkg.replace_insertion_values
435               (p_desc              => l_la_desc1,
436                p_information1      => l_insrt_value1,
437                p_desc_out          => l_la_desc1_out);
438 	       l_la_desc1 := l_la_desc1_out;
439           END IF;
440           IF l_la_code2 IS NOT NULL THEN
441             SELECT description
442               INTO l_la_desc2
443               FROM fnd_common_lookups fcl
444              WHERE fcl.lookup_code = l_la_code2
445                AND fcl.application_id = 800
446                AND fcl.lookup_type = 'GHR_US_LEGAL_AUTHORITY'
447                AND fcl.enabled_flag = 'Y'
448                AND g_requests_rec.effective_date BETWEEN
449                    NVL(fcl.start_date_active,
450                        g_requests_rec.effective_date) AND
451                    NVL(fcl.end_date_active,
452                        g_requests_rec.effective_date);
453           END IF;
454           IF l_la_code2 in ('ZLM','UNM')  THEN
455 	    -- Bug#4256022 Passed the variable l_la_desc2_out and
456 	    -- assigned the value back to l_la_desc2 to avoid NOCOPY related problems..
457             ghr_mass_actions_pkg.replace_insertion_values
458               (p_desc              => l_la_desc2,
459                p_information1      => l_insrt_value2,
460                p_desc_out          => l_la_desc2_out);
461 	       l_la_desc2 := l_la_desc2_out;
462           END IF;
463           l_location := 'Apply_894_Rules:Updating GHR_PA_REQUESTS';
464           UPDATE GHR_PA_REQUESTS
465              SET first_action_la_code1   = l_la_code1,
466                  first_action_la_code2   = l_la_code2,
467                  first_action_la_desc1   = l_la_desc1,
468                  first_action_la_desc2   = DECODE(l_la_code2, NULL, NULL,
469                                                 l_la_desc2),
470                  first_lac1_information1 = DECODE(l_la_code1, 'ZLM',
471                                                   l_insrt_value1,'UNM',l_insrt_value1, NULL),
472                  first_lac1_information2 = NULL,
473                  first_lac1_information3 = NULL,
474                  first_lac1_information4 = NULL,
475                  first_lac1_information5 = NULL,
476                  first_lac2_information1 = DECODE(l_la_code2, 'ZLM',
477                                                   l_insrt_value2, NULL),
478                  first_lac2_information2 = NULL,
479                  first_lac2_information3 = NULL,
480                  first_lac2_information4 = NULL,
481                  first_lac2_information5 = NULL
482           WHERE pa_request_id = p_pa_request_id;
483           -- Create Remarks
484           l_location := 'Apply_894_Rules:Creating Remarks';
485           IF  (l_la_code1 in ('QHP','QJP') AND l_la_code2 = 'ZLM')  THEN
486              Create_Remark('P05',p_out_step_or_rate);
487              Create_Remark('P07',p_out_step_or_rate);
488 ----          ELSIF p_new_prd IN ('6','E','F') then
489 ----             Create_Remark('P05',p_out_step_or_rate);
490           END IF;
491           IF p_new_prd IN ('A','B','E','F') THEN
492             Create_Remark('X44',p_out_step_or_rate);
493           ELSIF   p_new_prd IN ('J','K','R','S','3') THEN
494             Create_Remark('X40',p_out_step_or_rate);
495           ELSIF p_new_prd IN ('U','V') THEN
496               -- Bug#4130683 Added this IF condition for 'GL' pay plan
497 	      IF g_pay_plan IN ('GL') AND g_intl_posn_indicator NOT IN ('2') THEN
498                   Create_Remark('X44',p_out_step_or_rate);
499 	      ELSE
500 	          Create_Remark('X40',p_out_step_or_rate);
501                   Create_Remark('X44',p_out_step_or_rate);
502 	      END IF;
503           END IF;
504  /*       IF ((l_la_code1 = 'QWM' AND l_la_code2 = 'ZLM') OR
505               (l_la_code1 = 'QHP' AND l_la_code2 = 'ZLM') OR
506               (l_la_code1 = 'ZTW' AND l_la_code2 IS NULL) OR
507               (l_la_code1 = 'ZLM' AND l_la_code2 IS NULL) OR
508               (l_la_code1 = 'UNM' AND l_la_code2 IS NULL) OR
509               (l_la_code1 = 'UAM' AND l_la_code2 = 'ZLM') OR
510               (l_la_code1 = 'FNM' AND l_la_code2 = 'VLJ')) AND
511              p_new_prd IN ('A','B','E','F')
512           THEN
513             Create_Remark('X44',p_out_step_or_rate);
514           ELSIF ((l_la_code1 = 'QWM' AND l_la_code2 = 'ZLM') OR
515                  (l_la_code1 = 'QJP' AND l_la_code2 = 'ZLM') OR
516                  (l_la_code1 = 'ZTW' AND l_la_code2 IS NULL) OR
517                  (l_la_code1 = 'UAM' AND l_la_code2 = 'ZLM') OR
518                  (l_la_code1 = 'ZLM' AND l_la_code2 IS NULL) OR
519                  (l_la_code1 = 'FNM' AND l_la_code2 = 'VSJ')) AND
520                 p_new_prd IN ('J','K','R','S','U','V','3')
521           THEN
522             Create_Remark('X40',p_out_step_or_rate);
523           END IF;
524           IF  ((l_la_code1 = 'QWM' AND l_la_code2 = 'ZLM') OR
525                (l_la_code1 = 'QJP' AND l_la_code2 = 'ZLM') OR
526                (l_la_code1 = 'FNM' AND l_la_code2 = 'VSJ')) AND
527                 p_new_prd IN ('U','V') THEN
528              Create_Remark('X44',p_out_step_or_rate);
529           END IF; */
530         END IF;
531         IF p_old_prd IN ('J','K','R','S','U','V','3')    AND
532            p_new_prd NOT IN ('J','K','R','S','U','V','3')
533           THEN
534            -- Needs to be fixed to generate X42
535            -- leaving it as X40 for the moment. 13-JAN-2001
536            -- modified as X42 by AVR as of 18-JAN-2002
537         Create_Remark('X42',p_out_step_or_rate);
538         END IF;
539         -- Create Extra Remarks depending on some element values
540         IF g_requests_rec.to_auo_premium_pay_indicator IS NOT NULL AND
541            g_requests_rec.to_au_overtime > 0
542         THEN
543           Create_Remark('P81',p_out_step_or_rate);
544         END IF;
545         IF g_requests_rec.to_ap_premium_pay_indicator IS NOT NULL AND
546            g_requests_rec.to_availability_pay > 0
547         THEN
548           Create_Remark('P99',p_out_step_or_rate);
549         END IF;
550         -- Bug#5719467 Added the date condition to avoid P70 remark printing.
551 	l_location := 'Apply_894_Rules:Creating Remark P70';
552         IF g_requests_rec.to_retention_allowance > 0 THEN
553             IF g_requests_rec.effective_date < to_date('02/09/2006','DD/MM/YYYY') THEN
554                 Create_Remark('P70',p_out_step_or_rate);
555             ELSE
556                 p_errbuf := 'Error: Retention Allowance not terminated. Terminate Retention Allowance and process the Pay Adjustment';
557             END IF;
558         END IF;
559         IF g_requests_rec.to_staffing_differential > 0 THEN
560           Create_Remark('P71',p_out_step_or_rate);
561         END IF;
562         IF g_requests_rec.to_supervisory_differential > 0 THEN
563           Create_Remark('P72',p_out_step_or_rate);
564         END IF;
565         -- Calling USER HOOK
566         l_location := 'Apply_894_Rules:Calling User-hook';
567         ghr_agency_check.mass_salary_lacs_remarks(p_pa_request_id,
568                                                   p_new_prd,
569                                                   p_eo_nbr, p_eo_date,
570                                                   p_opm_nbr, p_opm_date,
571                                                   p_retcode, p_errbuf);
572 
573         IF p_retcode = 0 THEN
574           -- Checking existence of LAC in GHR_PA_REQUESTS
575           SELECT first_action_la_code1
576             INTO l_la_code1
577             FROM GHR_PA_REQUESTS
578            WHERE pa_request_id = p_pa_request_id;
579           IF l_la_code1 IS NULL THEN
580             p_retcode := 2;
581             p_errbuf  := 'Error in Apply_894_Rules: ' ||
582                          'Legal Authority Code is NULL or No Default ' ||
583                          'LACS were specified';
584           END IF;
585         END IF;
586       END IF;
587 
588   --- ADDED for MSL Expaned functionality MADHURI
589   ---
590   ELSIF  (g_requests_rec.first_noa_code = '895') OR (g_requests_rec.first_noa_code = '894' AND l_rpa_type = 'MLC')  THEN --Bug# 10387022
591         -- IF THE NOA CODE IS 895
592         -- 894 LAC/Remarks Rules
593 
594 --    IF g_requests_rec.first_la_action_code1 IS NULL THEN
595     -- {
596       IF (g_requests_rec.first_noa_code = '894' AND l_rpa_type = 'MLC') THEN --Bug# 10387022
597 		l_la_code1:='VGR';
598       ELSIF g_leo_posn_indicator = 0 THEN
599 	      l_la_code1:='VGR';
600       ELSIF g_leo_posn_indicator IN ('1','2') THEN
601 	      l_la_code1:='ZTX';
602       END IF;
603     -- }
604 --    END IF;
605 
606       IF l_la_code1 IS NOT NULL THEN
607       -- {
608          -- STAGE 1
609          l_location := 'Apply_895_Rules:Replacing Insertion Value';
610 
611 	   SELECT description
612             INTO l_la_desc1
613             FROM fnd_common_lookups fcl
614            WHERE fcl.lookup_code = l_la_code1
615              AND fcl.application_id = 800
616              AND fcl.lookup_type = 'GHR_US_LEGAL_AUTHORITY'
617              AND fcl.enabled_flag = 'Y'
618              AND g_requests_rec.effective_date BETWEEN
619                  NVL(fcl.start_date_active,
620                      g_requests_rec.effective_date) AND
621                  NVL(fcl.end_date_active, g_requests_rec.effective_date);
622        END IF;
623 
624        BEGIN
625 	  -- STAGE 2
626 	  l_location := 'Apply_895_Rules:Updating GHR_PA_REQUESTS';
627 
628 	  UPDATE GHR_PA_REQUESTS
629              SET first_action_la_code1   = l_la_code1,
630                  first_action_la_desc1   = l_la_desc1,
631                  first_lac1_information1 = NULL,
632                  first_lac1_information2 = NULL,
633                  first_lac1_information3 = NULL,
634                  first_lac1_information4 = NULL,
635                  first_lac1_information5 = NULL
636           WHERE pa_request_id = p_pa_request_id;
637        -- }
638        END;
639       -- Create Remarks
640       l_location := 'Apply_895_Rules:Creating Remarks';
641       --Begin Bug 10387022
642       IF (g_requests_rec.first_noa_code = '894' AND l_rpa_type = 'MLC') THEN
643 	 IF p_new_prd IN ('A','B','E','F') THEN
644 		Create_Remark('X44',p_out_step_or_rate);
645 	 ELSIF g_pay_plan IN ('GL') AND g_intl_posn_indicator NOT IN ('2') THEN
646 		Create_Remark('P11',p_out_step_or_rate);
647 	 ---Begin Bug# 13627988
648 	 ELSIF   p_new_prd IN ('J','K','R','S','3') THEN
649                 Create_Remark('X40',p_out_step_or_rate);
650 		Create_Remark('X67',p_out_step_or_rate);
651 	 ELSIF p_old_prd IN ('J','K','R','S','U','V','3')    AND
652 	       p_new_prd NOT IN ('J','K','R','S','U','V','3') THEN
653 		Create_Remark('X42',p_out_step_or_rate);
654          ---End Bug# 13627988
655 	 END IF;
656       --End Bug 10387022
657       ELSIF (p_new_prd = '6' and g_requests_rec.to_locality_adj=0) THEN
658 	Create_Remark('P93',p_out_step_or_rate);
659 
660       ELSIF ( (p_new_prd IN ('0','6') AND
661                g_leo_posn_indicator in ('1','2') ) AND
662                 g_requests_rec.to_locality_adj=0
663 	    ) THEN
664 	Create_Remark('P95',p_out_step_or_rate);
665 
666       ELSIF ( p_new_prd IN ('M','P') AND
667               g_requests_rec.to_locality_adj > 0
668 	    ) THEN
669 	Create_Remark('P96',p_out_step_or_rate);
670 
671       ELSE
672         Create_Remark('P92',p_out_step_or_rate);
673 
674       END IF;
675         -- Calling USER HOOK
676         l_location := 'Apply_895_Rules:Calling User-hook';
677         ghr_agency_check.mass_salary_lacs_remarks(p_pa_request_id,
678                                                   p_new_prd,
679                                                   p_eo_nbr, p_eo_date,
680                                                   p_opm_nbr, p_opm_date,
681                                                   p_retcode, p_errbuf);
682 
683         IF p_retcode = 0 THEN
684           -- Checking existence of LAC in GHR_PA_REQUESTS
685           SELECT first_action_la_code1
686             INTO l_la_code1
687             FROM GHR_PA_REQUESTS
688            WHERE pa_request_id = p_pa_request_id;
689           IF l_la_code1 IS NULL THEN
690             p_retcode := 2;
691             p_errbuf  := 'Error in Apply_895_Rules: ' ||
692                          'Legal Authority Code is NULL or No Default ' ||
693                          'LACS were specified';
694           END IF;
695         END IF;
696 
697     END IF; -- 894 LAC/Remarks Rules
698 
699   EXCEPTION
700     WHEN OTHERS THEN
701       p_retcode := 2;
702       p_errbuf  := l_location;
703   END;
704 
705   -- FWFA Changes Bug#4444609
706 
707   PROCEDURE apply_fwfa_rules( p_pa_request_id  GHR_PA_REQUESTS.PA_REQUEST_ID%TYPE,
708                               p_noa_code       GHR_PA_REQUESTS.FIRST_NOA_CODE%TYPE,
709 			                  p_pay_plan       GHR_PA_REQUESTS.TO_PAY_PLAN%TYPE,
710                               p_errbuf         IN OUT NOCOPY VARCHAR2,
711                               p_retcode        IN OUT NOCOPY NUMBER
712                               ) is
713     l_la_code1                   ghr_pa_requests.first_action_la_code1%TYPE;
714     l_la_code2                   ghr_pa_requests.first_action_la_code2%TYPE;
715     l_la_desc1                   ghr_pa_requests.first_action_la_desc1%TYPE;
716     l_la_desc1_out               ghr_pa_requests.first_action_la_desc1%TYPE;
717     l_la_desc2                   ghr_pa_requests.first_action_la_desc2%TYPE;
718     l_la_desc2_out               ghr_pa_requests.first_action_la_desc2%TYPE;
719     l_insrt_value                ghr_pa_requests.first_lac1_information1%TYPE;
720 
721   BEGIN
722     p_retcode := 0;
723     p_errbuf  := NULL;
724 
725 	IF p_noa_code = '800' THEN
726 		IF p_pay_plan <> 'GG' THEN
727             l_la_code1 := 'CGM';
728         END IF;
729 	ELSIF p_noa_code = '894' THEN
730         IF p_pay_plan <> 'GG' THEN
731             l_la_code1 := 'ZLM';
732         ELSE
733             l_la_code1 := 'UAM';
734             l_la_code2 := 'ZLM';
735         END IF;
736 	END IF;
737 
738     l_la_desc1 := ghr_pa_requests_pkg.get_lookup_description(800,'GHR_US_LEGAL_AUTHORITY',l_la_code1);
739     l_la_desc2 := ghr_pa_requests_pkg.get_lookup_description(800,'GHR_US_LEGAL_AUTHORITY',l_la_code2);
740 
741     IF (l_la_code1 = 'ZLM') THEN
742       l_insrt_value :=  'P.L. 108-411, Sec. 301 dated 10-30-04.';
743       ghr_mass_actions_pkg.replace_insertion_values
744           (p_desc              => l_la_desc1,
745            p_information1      => l_insrt_value,
746            p_desc_out          => l_la_desc1_out);
747        l_la_desc1 := l_la_desc1_out;
748     END IF;
749 
750     IF (l_la_code2 = 'ZLM') THEN
751       l_insrt_value :=  'P.L. 108-411, Sec. 301 dated 10-30-04.';
752       ghr_mass_actions_pkg.replace_insertion_values
753           (p_desc              => l_la_desc2,
754            p_information1      => l_insrt_value,
755            p_desc_out          => l_la_desc2_out);
756        l_la_desc2 := l_la_desc2_out;
757      END IF;
758 
759      UPDATE GHR_PA_REQUESTS
760         SET first_action_la_code1   = l_la_code1,
761             first_action_la_code2   = l_la_code2,
762             first_action_la_desc1   = l_la_desc1,
763             first_action_la_desc2   = l_la_Desc2,
764             first_lac1_information1 = DECODE(l_la_code1, 'ZLM',
765                                              l_insrt_value,NULL),
766             first_lac1_information2 = NULL,
767             first_lac1_information3 = NULL,
768             first_lac1_information4 = NULL,
769             first_lac1_information5 = NULL,
770             first_lac2_information1 = DECODE(l_la_code2, 'ZLM',
771                                              l_insrt_value, NULL),
772             first_lac2_information2 = NULL,
773             first_lac2_information3 = NULL,
774             first_lac2_information4 = NULL,
775             first_lac2_information5 = NULL
776       WHERE pa_request_id = p_pa_request_id;
777 
778   EXCEPTION
779     WHEN OTHERS THEN
780       p_retcode := 2;
781       p_errbuf  := sqlerrm;
782 
783   END apply_fwfa_rules;
784   -- FWFA Changes
785 
786 END GHR_LACS_REMARKS;