DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_HE_FTE_CALC_PKG

Source


1 PACKAGE BODY igs_he_fte_calc_pkg AS
2 /* $Header: IGSHE21B.pls 120.8 2006/05/23 03:58:38 jtmathew ship $ */
3 
4   p_fte_start_dt igs_ca_inst.start_dt%TYPE ;
5   p_fte_end_dt igs_ca_inst.end_dt%TYPE ;
6   p_fte_cal_type igs_ca_inst.cal_type%TYPE ;
7   p_fte_sequence_number igs_ca_inst.sequence_number%TYPE ;
8 
9 
10   FUNCTION research_st ( p_course_cd igs_ps_ver_all.course_cd%TYPE , p_version_number igs_ps_ver_all.version_number%TYPE )
11   RETURN BOOLEAN AS
12   /*************************************************************
13     Created By      : smaddali
14     Date Created By : 15-APR-2002
15     Purpose :  To find If the passed person is research candidate or not
16        it can return TRUE/FALSE
17     Know limitations, enhancements or remarks
18     Change History
19     Who             When            What
20     (reverse chronological order - newest change first)
21   ***************************************************************/
22 
23     l_res_st VARCHAR2(1) := 'N' ;
24 
25     --find if the passed program attempt has a candidacy details record
26     CURSOR c_res_st IS
27     SELECT 'Y'
28     FROM igs_ps_type_all pt, igs_ps_ver_all cv
29     WHERE cv.course_cd = p_course_cd  AND
30           cv.version_number = p_version_number AND
31           cv.course_type = pt.course_type AND
32           pt.research_type_ind = 'Y' AND
33           pt.closed_ind = 'N' ;
34 
35   BEGIN
36         -- If the student has a candidacy details record for the passed program then
37         -- the student is a research student and return TRUE , else return FALSE
38         OPEN c_res_st ;
39         FETCH c_res_st INTO l_res_st ;
40         IF c_res_st%FOUND THEN
41           CLOSE c_res_st ;
42           RETURN TRUE ;
43         ELSE
44           CLOSE c_res_st ;
45           RETURN FALSE ;
46         END IF ;
47 
48   EXCEPTION
49       WHEN OTHERS THEN
50           RAISE  ;
51 
52   END research_st ;
53 
54 
55   PROCEDURE coo_type (p_person_id  IN igs_pe_person.person_id%TYPE ,
56                       p_unit_set_cd  IN igs_en_unit_set.unit_set_cd%TYPE,
57                       p_us_version_number  IN igs_en_unit_set.version_number%TYPE,
58                       p_sequence_number IN igs_as_su_setatmpt.sequence_number%TYPE ,
59                       p_coo_id IN igs_ps_ofr_opt_all.coo_id%TYPE ,
60                       p_coo_type  OUT NOCOPY VARCHAR2 ,
61                       p_hesa_mode OUT NOCOPY VARCHAR2 ,
62                       p_message OUT NOCOPY VARCHAR2 )  AS
63   /*************************************************************
64     Created By      : smaddali
65     Date Created By : 15-APR-2002
66     Purpose :  To find the If the passed program offering option is part-time or full time.
67        it can return 'PT'/'FT' or NULL
68     Know limitations, enhancements or remarks
69     Change History
70     Who             When            What
71     --sarakshi   24-Feb-2003   Enh#2797116,modified cursor c_coo,c_crs_dets.Added delete_flag check in the where clause
72     (reverse chronological order - newest change first)
73   ***************************************************************/
74 
75     l_coo_type VARCHAR2(2)  ;
76     l_oss_mode  igs_he_poous_all.mode_of_study%TYPE  ;
77     l_hesa_mode igs_he_code_map_val.map1%TYPE  ;
78     l_course_cd igs_ps_ver_all.course_cd%TYPE ;
79     l_version_number igs_ps_ver_all.version_number%TYPE ;
80     l_cal_type igs_ps_ofr_opt_all.cal_type%TYPE ;
81     l_location_cd igs_ps_ofr_opt_all.location_cd%TYPE ;
82     l_attendance_type igs_ps_ofr_opt_all.attendance_type%TYPE ;
83     l_attendance_mode igs_ps_ofr_opt_all.attendance_mode%TYPE ;
84 
85     -- get the  mode of study at  program offering unit set level
86     CURSOR c_poous IS
87     SELECT mode_of_study
88     FROM  igs_he_poous_all
89     WHERE unit_set_cd = p_unit_set_cd AND
90           us_version_number = p_us_version_number AND
91           course_cd = l_course_cd AND
92           crv_version_number = l_version_number AND
93           cal_type = l_cal_type AND
94           location_cd = l_location_cd AND
95           attendance_type = l_attendance_type AND
96           attendance_mode = l_attendance_mode ;
97 
98     -- get the  mode of study at student unit set attempt level
99     CURSOR c_susa IS
100     SELECT study_mode
101     FROM  igs_he_en_susa
102     WHERE person_id = p_person_id AND
103           course_cd = l_course_cd AND
104           unit_set_cd = p_unit_set_cd AND
105           sequence_number = p_sequence_number ;
106 
107     -- get the HESA attendance type associated to the program offering option attendance mode
108     CURSOR c_coo IS
109     SELECT map1
110     FROM  IGS_HE_CODE_MAP_VAL
111     WHERE association_code = 'OSS_HESA_ATTEND_MODE_ASSOC' AND
112     map2 = (SELECT attendance_type
113              FROM igs_ps_ofr_opt_all
114              WHERE coo_id = p_coo_id
115              AND delete_flag = 'N');
116 
117     -- get the HESA mode of study associated with OSS mode of study
118     CURSOR c_hesa_mode(cp_oss_mode_of_study igs_he_poous_all.mode_of_study%TYPE)  IS
119     SELECT map1
120     FROM IGS_HE_CODE_MAP_VAL
121     WHERE map2  = cp_oss_mode_of_study AND
122     association_code = 'OSS_HESA_MODE_ASSOC' ;
123 
124     -- get the course details for the program offering option passed
125     CURSOR c_crs_dets IS
126     SELECT course_cd , version_number, cal_type, location_cd ,attendance_type ,attendance_mode
127     FROM igs_ps_ofr_opt_all
128     WHERE coo_id = p_coo_id
129     AND   delete_flag = 'N';
130 
131 
132   BEGIN
133 
134       -- get the course details for the passed program offering option ID
135      OPEN c_crs_dets ;
136      FETCH c_crs_dets INTO l_course_cd ,l_version_number , l_cal_type ,l_location_cd ,
137          l_attendance_type , l_attendance_mode ;
138      CLOSE c_crs_dets ;
139 
140      -- If mode of study is defined at unit set attempt then it overrides the
141      -- value at unit set level an program offering level
142      OPEN c_susa ;
143      FETCH c_susa INTO l_oss_mode ;
144      CLOSE c_susa ;
145      IF l_oss_mode IS NOT NULL THEN
146          -- get the HESA mode of study for the oss mode of study value set at unit set attempt level
147          OPEN c_hesa_mode (l_oss_mode) ;
148          FETCH c_hesa_mode INTO l_hesa_mode ;
149          CLOSE c_hesa_mode ;
150      ELSE
151           -- if mode of study not setup at unit set attempt level then get it from the program offering unit set level
152           OPEN c_poous ;
153           FETCH c_poous INTO l_oss_mode ;
154           CLOSE c_poous ;
155           -- get the HESA mode of study value for the OSS mode of study set at program offering unit set level
156           IF l_oss_mode IS NOT NULL THEN
157              OPEN c_hesa_mode (l_oss_mode) ;
158              FETCH c_hesa_mode INTO l_hesa_mode ;
159              CLOSE c_hesa_mode ;
160           ELSE
161               -- if mode of study is not setup at either unit set attempt or unit set level then
162               -- get the HESA attendance type associated to the OSS attendance_type set up at
163               -- the program offering option level
164               OPEN c_coo ;
165               FETCH c_coo INTO l_hesa_mode ;
166               CLOSE c_coo ;
167           END IF;
168       END IF ;
169 
170       -- If hesa code is not associated to the oss mode of study then log an error message
171       -- else if hesa mode lies in 31-39 or 44 it is part-time offering ,ale it is full time offering
172       IF l_hesa_mode IS NULL THEN
173          p_message := 'IGS_HE_NO_CODE' ;
174          p_coo_type := NULL ;
175       -- if hesa mode of study lies in '31' to '39' or '44' then program offering is part-time else full time
176       ELSIF l_hesa_mode IN ('31','32','33','34','35','36','37','38','39','44') THEN
177           p_coo_type := 'PT' ;
178       p_message := NULL ;
179       ELSE
180           p_coo_type := 'FT' ;
181       p_message := NULL ;
182       END IF;
183        p_hesa_mode := l_hesa_mode ;
184 
185   EXCEPTION
186       WHEN OTHERS THEN
187           FND_MESSAGE.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
188           FND_MESSAGE.Set_Token('NAME','igs_he_fte_calc_pkg.coo_type');
189           IGS_GE_MSG_STACK.ADD ;
190           APP_EXCEPTION.RAISE_EXCEPTION;
191 
192   END coo_type  ;
193 
194 
195   PROCEDURE fte_type_intensity ( p_person_id IN igs_pe_person.person_id%TYPE ,
196                 p_coo_id  IN igs_ps_ofr_opt_all.coo_id%TYPE ,
197                 p_unit_set_cd  IN igs_en_unit_set.unit_set_cd%TYPE ,
198                 p_us_version_number  IN igs_en_unit_set.version_number%TYPE ,
199                 p_sequence_number  IN igs_as_su_setatmpt.sequence_number%TYPE  ,
200                 P_att_prc_st_fte   IN  VARCHAR2,
201                 p_fte_calc_type  OUT NOCOPY igs_he_poous_all.fte_calc_type%TYPE ,
202                 p_fte_intensity OUT NOCOPY igs_he_poous_all.fte_intensity%TYPE ,
203                 p_selection_dt_from     IN  VARCHAR2,
204                 p_selection_dt_to       IN  VARCHAR2,
205                 p_message OUT NOCOPY VARCHAR2 )  AS
206 
207   /*************************************************************
208     Created By      : smaddali
209     Date Created By : 15-APR-2002
210     Purpose :  To find the FTE calculation type . It can return 'U' /'I'/'B'
211         Or to find the FTE_intensity value . If the parameters p_unit_set_cd ,p_us_version_number,p_sequence_number
212         are NULL then FTE_calculation type is determined else if all are passed FTE_intensity is determined
213     Know limitations, enhancements or remarks
214     Change History
215     Who       When          What
216     jtmathew  05-Apr-2006   Changes for HE370 - Introduced 'Use Attendance Percentage for Research' functionality
217     jtmathew  25-Jan-2005   Changes for HE357 - modified c_year
218     smaddali  08-Oct-2003   Removed cursor c_prg_limit and its code for bug#3175107 since std_pt_completion_time and
219                             std_ft_completion_time fields are obsolete
220     sarakshi  24-Feb-2003   Enh#2797116,modified cursor c_coo,c_crs_dets,c_crs_off.Added delete_flag check in the where clause
221     smaddali  05-Jul-2002   modified cursor c_year for bug 2448315
222     (reverse chronological order - newest change first)
223   ***************************************************************/
224 
225     l_hesa_att_type igs_he_code_map_val.map1%TYPE := NULL;
226     l_coo_type VARCHAR2(2) := NULL ;
227     l_pt VARCHAR2(1) := NULL;
228     l_ft VARCHAR2(1) := NULL;
229     l_message fnd_new_messages.message_name%TYPE := NULL;
230     l_course_cd igs_ps_ofr_opt_all.course_cd%TYPE ;
231     l_version_number igs_ps_ofr_opt_all.version_number%TYPE ;
232     l_cal_type igs_ps_ofr_opt_all.cal_type%TYPE ;
233     l_location_cd igs_ps_ofr_opt_all.location_cd%TYPE ;
234     l_attendance_type igs_ps_ofr_opt_all.attendance_type%TYPE ;
235     l_attendance_mode igs_ps_ofr_opt_all.attendance_mode%TYPE ;
236     l_hesa_mode igs_he_code_map_val.map1%TYPE := NULL;
237 
238     -- Get the current year of program  which either started, completed or ended in the FTE period
239     -- jtmathew modified this cursor to use optional cp_selection_dt parameters for HE370 changes
240     -- jtmathew modified this cursor for end_dt selection for HE357 changes
241     -- smaddali modified this cursor to modify where caluse for selection and completion_dt for bug 2448315
242     CURSOR c_year IS
243     SELECT susa.unit_set_cd , susa.us_version_number , susa.sequence_number
244       FROM igs_as_su_setatmpt susa, igs_ps_us_prenr_cfg us
245      WHERE susa.unit_set_cd = us.unit_set_cd
246        AND susa.person_id = p_person_id
247        AND susa.course_cd  = l_course_cd
248        AND susa.selection_dt IS NOT NULL
249        AND susa.selection_dt < p_fte_end_dt
250        AND ((susa.rqrmnts_complete_dt > p_fte_start_dt OR susa.end_dt > p_fte_start_dt)
251             OR (susa.end_dt IS NULL AND susa.rqrmnts_complete_dt IS NULL))
252        AND (p_selection_dt_from IS NULL
253             OR susa.selection_dt BETWEEN p_selection_dt_from AND p_selection_dt_to)
254   ORDER BY NVL(susa.rqrmnts_complete_dt, susa.end_dt) DESC;
255     c_year_rec  c_year%ROWTYPE;
256 
257     --get fte calc type set up at  program offering unit set level
258     CURSOR c_poous (cp_unit_set_cd igs_en_unit_set.unit_set_cd%TYPE ,
259                       cp_us_version_number igs_en_unit_set.version_number%TYPE
260                       ) IS
261     SELECT fte_calc_type , fte_intensity
262     FROM  igs_he_poous_all
263     WHERE unit_set_cd = cp_unit_set_cd AND
264        us_version_number = cp_us_version_number AND
265        course_cd = l_course_cd AND
266        crv_version_number = l_version_number AND
267        cal_type = l_cal_type AND
268        location_cd = l_location_cd AND
269        attendance_type = l_attendance_type AND
270        attendance_mode = l_attendance_mode ;
271     c_poous_rec  c_poous%ROWTYPE ;
272 
273     -- get fte calculation type set up at student unit set attempt level
274     CURSOR c_susa (cp_unit_set_cd igs_en_unit_set.unit_set_cd%TYPE ,
275                       cp_sequence_number igs_as_su_setatmpt.sequence_number%TYPE
276                       )IS
277     SELECT fte_calc_type , fte_intensity
278     FROM  igs_he_en_susa
279     WHERE person_id = p_person_id AND
280            course_cd = l_course_cd AND
281            unit_set_cd = cp_unit_set_cd AND
282            sequence_number = cp_sequence_number ;
283     c_susa_rec  c_susa%ROWTYPE ;
284 
285      -- get the HESA attendance type associated to the program offering option attendance type
286     CURSOR c_coo IS
287     SELECT map1
288     FROM  IGS_HE_CODE_MAP_VAL
289     WHERE association_code = 'OSS_HESA_ATTEND_MODE_ASSOC' AND
290     map2 = (SELECT attendance_type
291              FROM igs_ps_ofr_opt_all
292              WHERE coo_id = p_coo_id
293              AND   delete_flag = 'N');
294 
295     -- get the course details for the program offering option passed
296     CURSOR c_crs_dets IS
297     SELECT course_cd , version_number, cal_type, location_cd ,attendance_type ,attendance_mode
298     FROM igs_ps_ofr_opt_all
299     WHERE coo_id = p_coo_id
300     AND   delete_flag = 'N';
301 
302     -- get the attendance percentage for the research student which will be his fte intensity
303     CURSOR c_research IS
304     SELECT attendance_percentage
305     FROM igs_re_candidature_all
306     WHERE person_id = p_person_id AND
307         sca_course_cd = l_course_cd ;
308     c_research_rec  c_research%ROWTYPE ;
309 
310     -- Get the FTE intensity set at program level
311     CURSOR c_prog IS
312     SELECT fte_intensity
313     FROM igs_he_st_prog_all
314     WHERE course_cd = l_course_cd AND
315           version_number = l_version_number ;
316     c_prog_rec  c_prog%ROWTYPE ;
317 
318     -- get all the program offering optiond for the current program
319     CURSOR c_crs_off IS
320     SELECT coo_id
321     FROM igs_ps_ofr_opt_all
322     WHERE course_cd = l_course_cd AND
323          version_number = l_version_number AND
324          delete_flag = 'N';
325 
326 
327   BEGIN
328 
329         -- get the course details of the passed program offering
330         OPEN c_crs_dets ;
331         FETCH c_crs_dets INTO l_course_cd ,l_version_number , l_cal_type ,l_location_cd ,
332               l_attendance_type , l_attendance_mode ;
333         CLOSE c_crs_dets ;
334 
335     IF p_unit_set_cd IS NULL THEN
336 /* Finding the FTE Calculation type */
337 
338 
339         -- For a research student fte calculation type is Intensity based
340         IF research_st(l_course_cd ,l_version_number) THEN
341           p_message := NULL ;
342           p_fte_calc_type := 'I' ;
343 
344         ELSE
345             -- Get the current Year of program for the student program attempt
346             OPEN    c_year ;
347             FETCH  c_year INTO c_year_rec ;
348             -- If current year of program is not found then log a message
349             IF c_year%NOTFOUND THEN
350                p_message := 'IGS_HE_NO_YOP' ;
351                p_fte_calc_type := NULL ;
352             ELSE
353                 -- If fte calculation type is set up at Student unit set attmept level  for the current year of program
354                 -- then it overrides the value set at Program offering unit set level
355                 OPEN c_susa ( c_year_rec.unit_set_cd , c_year_rec.sequence_number );
356                 FETCH c_susa INTO c_susa_rec ;
357                 CLOSE c_susa ;
358 
359                 IF c_susa_rec.fte_calc_type IS NOT NULL THEN
360                      p_message := NULL ;
361                      p_fte_calc_type := c_susa_rec.fte_calc_type ;
362                 ELSE
363                     -- If fte_calc_type is not set at unit set attempt level then get the value set at
364                     -- program offering unit set lelvel corresponding to the current year of program
365                     OPEN c_poous (c_year_rec.unit_set_cd , c_year_rec.us_version_number ) ;
366                     FETCH c_poous INTO c_poous_rec ;
367                     CLOSE c_poous ;
368 
369                     IF c_poous_rec.fte_calc_type IS NOT NULL THEN
370                           p_message := NULL ;
371                           p_fte_calc_type := c_poous_rec.fte_calc_type ;
372                     ELSE
373                         -- If fte calculation type is not set up at either unit set level/ unit set attempt level then
374                         -- for a part-time program offering option it is Unit based ,for others it is Intensity based
375                         OPEN c_coo ;
376                         FETCH c_coo INTO l_hesa_att_type ;
377                         CLOSE c_coo ;
378 
379                         -- If hesa attendance type lies in '31 to 39' or '44' then the program offering is part-time ,
380                         -- else it is full-time , If no hesa mapping is found then log a message
381                         IF l_hesa_att_type IS NULL THEN
382                             p_message := 'IGS_HE_NO_CODE' ;
383                             p_fte_calc_type := NULL ;
384                         ELSIF l_hesa_att_type IN ('31','32','33','34','35','36','37','38','39','44') THEN
385                             p_message := NULL ;
386                             p_fte_calc_type := 'U'  ;
387                         ELSE
388                             p_message := NULL ;
389                             p_fte_calc_type := 'I';
390                         END IF;
391                     END IF;  -- if fte type not found at poous level
392 
393                 END IF ;  -- if fte type not found at susa level
394 
395             END IF ;
396             CLOSE  c_year ;
397 
398         END IF; -- if student is not a research student
399 
400 /* end of finding FTE calculation type  */
401 
402     ELSE
403 /* Finding the FTE Intensity  */
404         c_susa_rec := NULL ;
405         c_poous_rec := NULL ;
406         c_prog_rec := NULL;
407 
408         -- Get the fte intensity for a research student
409         OPEN  c_research ;
410         FETCH c_research INTO c_research_rec ;
411         CLOSE c_research ;
412 
413         -- get the fte intensity at the unit set and unit set attemt levels
414         OPEN c_susa ( p_unit_set_cd ,p_sequence_number );
415         FETCH c_susa INTO c_susa_rec ;
416         CLOSE c_susa ;
417 
418         OPEN c_poous (p_unit_set_cd , p_us_version_number ) ;
419         FETCH c_poous INTO c_poous_rec ;
420         CLOSE c_poous ;
421 
422         OPEN c_prog  ;
423         FETCH c_prog INTO c_prog_rec ;
424         CLOSE c_prog ;
425 
426         -- For a research student fte calculation type is Intensity based
427         IF research_st( l_course_cd , l_version_number)  AND c_research_rec.attendance_percentage IS NOT NULL
428         AND P_att_prc_st_fte = 'Y'
429         THEN
430             p_fte_intensity := c_research_rec.attendance_percentage ;
431             p_message := NULL ;
432         -- If fte calculation type is set up at Student unit set attempt level for the current year of program
433         -- then it overrides the value defined at the Program Offering Option Unit Set level
434         ELSIF c_susa_rec.fte_intensity IS NOT NULL THEN
435                 p_fte_intensity := c_susa_rec.fte_intensity ;
436                 p_message := NULL ;
437         -- If fte_calc_type is not set at Student Unit Set Attempt level then get the value set at
438         -- Program Offering Option Unit Set level corresponding to the current year of program
439         ELSIF c_poous_rec.fte_intensity IS NOT NULL THEN
440                  p_fte_intensity := c_poous_rec.fte_intensity ;
441          p_message := NULL ;
442         ELSE
443 
444                 l_pt := 'N'  ;
445                 l_ft := 'N'  ;
446                 -- loop thru all the program offering options for this program and exit when you find both
447                 -- full-time and part-time offerings
448                 FOR c_crs_off_rec IN c_crs_off LOOP
449                    l_coo_type  := NULL ;
450                    l_hesa_mode := NULL ;
451 
452                    coo_type (p_person_id , p_unit_set_cd , p_us_version_number,
453                       p_sequence_number , c_crs_off_rec.coo_id , l_coo_type, l_hesa_mode, l_message ) ;
454                    IF l_coo_type = 'PT' THEN
455                       l_pt  := 'Y' ;
456                    ELSIF l_coo_type = 'FT' THEN
457                        l_ft := 'Y' ;
458                    END IF;
459                    EXIT WHEN ( l_pt = 'Y' AND l_ft = 'Y' ) ;
460 
461                 END LOOP ;
462 
463 
464                 -- If the program has both full-time and part-time offering then the FTE_INTENSITY
465                 -- should be set up at the program offering option unit set level or unit set attempt level
466                 -- we shouldnot pick fte intensity from program level
467                 IF l_pt = 'Y' AND l_FT = 'Y' THEN
468                     p_message := 'IGS_HE_PT_FT' ;
469                     p_fte_intensity := NULL ;
470                 ELSIF c_prog_rec.fte_intensity IS NOT NULL THEN
471                     p_fte_intensity := c_prog_rec.fte_intensity ;
472                     p_message := NULL ;
473                 ELSE
474                     l_coo_type := NULL ;
475                     -- now if fte intensity is not setup at any level then ,
476                     -- if program is full-time then intensity=100  ,for part time it is calcuated as
477                     -- the ratio of full time completion time and part-time completion time
478                     coo_type (p_person_id , p_unit_set_cd , p_us_version_number,
479                     p_sequence_number , p_coo_id , l_coo_type, l_hesa_mode , p_message ) ;
480                     IF l_coo_type = 'PT' THEN
481                          -- if the standard full time and part time completion periods are not set then log error message
482                          -- Cannot derive fte intensity so log error
483                          -- smaddali removed code to derive intensity from std_ft_completion_time , for bug#3175107
484                          p_fte_intensity := NULL ;
485                          p_message := 'IGS_HE_NO_COMP_PRD' ;
486                     ELSE
487                          p_fte_intensity := 100 ;
488                     END IF;
489                 END IF;
490         END IF ;
491 
492 
493 /* end of finding the FTE intensity  */
494 
495     END IF;
496 
497 
498 
499   EXCEPTION
500       WHEN OTHERS THEN
501           FND_MESSAGE.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
502           FND_MESSAGE.Set_Token('NAME','igs_he_fte_calc_pkg.fte_type_intensity');
503           IGS_GE_MSG_STACK.ADD ;
504           APP_EXCEPTION.RAISE_EXCEPTION ;
505 
506   END  fte_type_intensity ;
507 
508   PROCEDURE log_messages ( p_msg_name IN VARCHAR2 ,
509                            p_msg_val  IN VARCHAR2
510                          ) IS
511   ------------------------------------------------------------------
512   --Created by  : smaddali, Oracle IDC
513   --Date created:15/04/2002
514   --
515   --Purpose: This procedure is private to this package body .
516   --         The procedure logs all the parameter values ,
517   --         in the log file
518   --  called from job procedure rollover_fac_task
519   --Known limitations/enhancements and/or remarks:
520   --
521   --Change History:
522   --Who         When            What
523   -------------------------------------------------------------------
524   BEGIN
525 
526     FND_MESSAGE.SET_NAME('IGS','IGS_FI_CAL_BALANCES_LOG');
527     FND_MESSAGE.SET_TOKEN('PARAMETER_NAME',p_msg_name);
528     FND_MESSAGE.SET_TOKEN('PARAMETER_VAL' ,p_msg_val) ;
529     FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET);
530 
531   END log_messages ;
532 
533 
534   PROCEDURE fte_calculation(errbuf OUT NOCOPY VARCHAR2 ,
535                             retcode OUT NOCOPY NUMBER ,
536                             P_FTE_cal               IN  VARCHAR2,
537                             P_Person_id             IN  NUMBER,
538                             P_Person_id_grp         IN  VARCHAR2,
539                             P_Course_cd             IN  VARCHAR2,
540                             P_Course_cat            IN  VARCHAR2,
541                             P_Coo_id                IN  NUMBER,
542                             P_Selection_dt_from     IN  VARCHAR2,
543                             P_Selection_dt_to       IN  VARCHAR2,
544                             P_App_res_st_fte        IN  VARCHAR2,
545                             P_Att_prc_st_fte        IN  VARCHAR2) IS
546    /*************************************************************
547     Created By      : smaddali
548     Date Created By : 15-APR-2002
549     Purpose : To calculate the fte and save it in igs_he_en_susa
550      for each eligible student program attempt
551     Know limitations, enhancements or remarks
552     Change History
553     Who      When           What
554     sarakshi 26-jun-2003    Enh#2930935,modified cursors c_sua,c_trn_from_units to include uoo_id
555                             and cursor c_unit_cp to pick enrolled credit point from unit section
556                             level if exists else from unit level
557     smaddali                modified cursors c_crs_year , c_year , c_sca for bug 2448315
558     smaddali                modified cursors c_crs_year and c_year_cal for bug 2452785
559     smaddali 08-Oct-2003    Removed cursor c_prg_limit and its code for bug#3175107 since std_pt_completion_time and
560                             std_ft_completion_time fields are obsolete
561     smaddali 10-Oct-2003    Modified code to apportion fte for research students ,
562                             to check that commencement_dt and discontinued_dt lie in the FTE period ,
563                             for bug#3177328
564     smaddali 13-Oct-2003    Modified cursor c_sca , removed cursors c_trn_from and c_sca_sin for bug#3171373
565     smaddali 02-Dec-2003    Modified code logic for coo_id and course_cat parameters for HECR214 build, Bug#3291656
566     ayedubat 29-Apr-2004    Changed the cursors, c_intermit and c_intm_part to add a new condition to check
567                             for approved intermissions, if approval is required for Bug, 3494224
568     rnirwani 13-Sep-2004    changed cursor c_intermit to not consider logically deleted records and
569                             also to avoid un-approved intermission records. Bug# 3885804
570     jbaber   30-Nov-2004    Removed c_intermit, using isDormant instead for bug# 4037237
571     jtmathew 25-Jan-2005    Changes for HE357 - modified c_sua, c_trn_from_units, c_year, c_crs_year, c_fte_prop
572                             and rewrote c_year_cal. Created c_multi_yop and TYPE year_cal_type. Also modified
573                             intensity based calculation algorithm.
574     jtmathew 24-Oct-2005    Created c_en_hist for bug 4221427
575     anwest   18-jan-2006    Bug# 4950285 R12 Disable OSS Mandate
576     jchakrab 20-Feb-2006    Modified for 4251041 - removed ORDER BY from cursor c_sua query
577     jtmathew 23-Feb-2006    Modified c_poous_app for bug 5051155
578     jtmathew 05-Apr-2006    Changes for HE370 - Additional parameters: P_Person_id_grp, P_Selection_dts, P_att_prc_st_fte
579                             Modified cursors: c_sua, c_year, c_crs_year, c_year_cal, c_multi_yop
580                             c_spa has been removed and is now implemented using dynamic sql.
581   ***************************************************************/
582   BEGIN
583 
584     DECLARE
585     cst_enrolled                 CONSTANT    VARCHAR2(10) := 'ENROLLED';
586     cst_discontin                CONSTANT    VARCHAR2(10) := 'DISCONTIN';
587     cst_completed                CONSTANT    VARCHAR2(10) := 'COMPLETED';
588     cst_intermit                 CONSTANT    VARCHAR2(10) := 'INTERMIT';
589     cst_inactive                 CONSTANT    VARCHAR2(10) := 'INACTIVE';
590     cst_lapsed                   CONSTANT    VARCHAR2(10) := 'LAPSED';
591     i                            NUMBER := 1;
592 
593     l_fte_calc_type              igs_he_poous_all.fte_calc_type%TYPE ;
594     l_fte_intensity              igs_he_en_susa.fte_intensity%TYPE ;
595     l_calculated_intensity       igs_he_en_susa.fte_intensity%TYPE ;
596     l_total_credit_points        NUMBER := NULL ;
597     l_unit_cp                    NUMBER := NULL ;
598     l_message                    fnd_new_messages.message_name%TYPE := NULL;
599     l_dummy1                     igs_he_poous_all.fte_calc_type%TYPE;
600     l_dummy2                     igs_he_poous_all.fte_intensity%TYPE;
601     l_calculated_FTE             igs_he_en_susa.calculated_fte%TYPE := NULL;
602     l_trn_from_crs               igs_ps_ver.course_cd%TYPE := NULL;
603     l_unit_ver_cp                igs_ps_unit_ver.enrolled_credit_points%TYPE := NULL;
604     l_std_annual_load            igs_ps_ver.std_annual_load%TYPE := NULL;
605     l_fte_perc                   igs_he_fte_proprt.fte_perc%TYPE := NULL;
606     l_intm_flag                  BOOLEAN := FALSE ;
607     l_intm_part_days             NUMBER ;
608     l_apportion_flag             BOOLEAN := FALSE ;
609     l_app_start_dt               DATE := NULL ;
610     l_app_end_dt                 DATE := NULL ;
611     l_actual_start_dt            DATE := NULL ;
612     l_actual_end_dt              DATE := NULL ;
613     l_selection_dt_to            DATE := NULL;
614     l_selection_dt_from          DATE := NULL;
615     l_hesa_mode                  igs_he_code_map_val.map1%TYPE ;
616     l_coo_type                   VARCHAR2(2) := NULL;
617     l_app_days                   NUMBER := NULL ;
618     l_actual_days                NUMBER := NULL;
619     l_rowid                      VARCHAR2(40) := NULL;
620     l_hesa_en_susa_id            NUMBER := NULL;
621     l_exit_flag                  BOOLEAN := FALSE ;
622     l_multi_yop                  BOOLEAN := FALSE ;
623     l_fte_prop_flag              BOOLEAN := FALSE ;
624 
625     -- Variables for dynamic sql
626     l_prs_grp_sql                VARCHAR2(32767);
627     l_group_type                 igs_pe_persid_group_v.group_type%TYPE;
628     l_prs_grp_status             VARCHAR2(1)     := NULL;
629     l_cursor_id                  NUMBER;
630     l_num_rows                   NUMBER;
631     l_fte_calc_sql               VARCHAR2(32767);
632 
633     TYPE spa_type IS RECORD
634        (person_number              hz_parties.party_number%TYPE,
635         person_id                  igs_en_stdnt_ps_att_all.person_id%TYPE,
636         course_cd                  igs_en_stdnt_ps_att_all.course_cd%TYPE,
637         version_number             igs_en_stdnt_ps_att_all.version_number%TYPE,
638         coo_id                     igs_en_stdnt_ps_att_all.coo_id%TYPE,
639         course_attempt_status      igs_en_stdnt_ps_att_all.course_attempt_status%TYPE,
640         discontinued_dt            igs_en_stdnt_ps_att_all.discontinued_dt%TYPE,
641         course_rqrmnts_complete_dt igs_en_stdnt_ps_att_all.course_rqrmnts_complete_dt%TYPE,
642         commencement_dt            igs_en_stdnt_ps_att_all.commencement_dt%TYPE,
643         course_rqrmnt_complete_ind igs_en_stdnt_ps_att_all.course_rqrmnt_complete_ind%TYPE,
644         student_inst_number        igs_he_st_spa_all.student_inst_number%TYPE);
645     c_sca_rec  spa_type;
646 
647     TYPE ref_spa IS REF CURSOR;
648     c_ref_spa  ref_spa;
649 
650     TYPE year_cal_type IS RECORD
651        (cal_type           igs_ca_inst.cal_type%TYPE,
652         sequence_number    igs_ca_inst.sequence_number%TYPE,
653         start_dt           igs_ca_inst.start_dt%TYPE,
654         end_dt             igs_ca_inst.end_dt%TYPE);
655     l_year_cal_rec year_cal_type;
656 
657     -- get the start and end dates for the passed FTE calendar
658     CURSOR c_fte_prd IS
659     SELECT ci.start_dt , ci.end_dt
660     FROM igs_ca_inst ci
661     WHERE ci.cal_type = p_fte_cal_type AND
662           ci.sequence_number = p_fte_sequence_number ;
663 
664     -- check whether student has previously had an enrollment history
665     CURSOR c_en_hist (cp_person_id igs_as_sc_attempt_h_all.person_id%TYPE,
666                       cp_course_cd igs_as_sc_attempt_h_all.course_cd%TYPE) IS
667     SELECT 'X'
668     FROM igs_as_sc_attempt_h_all
669     WHERE person_id = cp_person_id
670     AND course_cd = cp_course_cd
671     AND hist_start_dt < p_fte_end_dt + 1
672     AND course_attempt_status = cst_enrolled;
673     c_en_hist_rec c_en_hist%ROWTYPE;
674 
675     -- get the student unit attempts for the current program attempt
676     -- jtmathew modified cursor to use unit section override start date (if exists) otherwise teaching period start date
677     -- jchakrab modified for 4251041 - removed redundant ORDER BY clause
678     CURSOR c_sua(cp_person_id igs_pe_person.person_id%TYPE ,
679                  cp_course_cd  igs_ps_ver.course_cd%TYPE ) IS
680     SELECT sua.unit_cd,
681            sua.version_number,
682            sua.enrolled_dt ,
683            sua.override_enrolled_cp ,
684            sua.cal_type,
685            sua.ci_sequence_number   ,
686            sua.unit_attempt_status ,
687            sua.discontinued_dt         ,
688            sua.uoo_id
689       FROM IGS_EN_SU_ATTEMPT_ALL       sua,
690            IGS_HE_ST_UNT_VS_ALL        hsu,
691            IGS_PS_UNIT_OFR_OPT_ALL     uoo
692      WHERE sua.person_id           = cp_person_id
693        AND sua.course_cd           = cp_course_cd
694        AND sua.unit_cd = hsu.unit_cd (+)
695        AND sua.version_number = hsu.version_number (+)
696        AND NVL(hsu.exclude_flag, 'N') = 'N'
697        AND sua.unit_attempt_status IN (cst_enrolled,cst_discontin,cst_completed)
698        AND sua.unit_cd = uoo.unit_cd (+)
699        AND sua.version_number = uoo.version_number (+)
700        AND sua.cal_type = uoo.cal_type (+)
701        AND sua.ci_sequence_number = uoo.ci_sequence_number (+)
702        AND sua.location_cd = uoo.location_cd (+)
703        AND sua.unit_class = uoo.unit_class (+)
704        AND ( NVL(uoo.unit_section_start_date, sua.ci_start_dt) BETWEEN  p_fte_start_dt AND p_fte_end_dt);
705 
706     --get the enrolled credit points for the unit
707     CURSOR c_unit_cp (cp_uoo_id   IN NUMBER) IS
708     SELECT NVL(cps.enrolled_credit_points,uv.enrolled_credit_points) enrolled_credit_points
709     FROM igs_ps_unit_ver_all uv,
710              igs_ps_unit_ofr_opt uoo,
711              igs_ps_usec_cps cps
712     WHERE uoo.uoo_id=cps.uoo_id(+) AND
713               uoo.unit_cd=uv.unit_cd AND
714               uoo.version_number=uv.version_number AND
715               uoo.uoo_id=cp_uoo_id;
716 
717     -- check if the student has transferred to the current program from other program
718     CURSOR c_trn_to (cp_person_id igs_pe_person.person_id%TYPE ,
719                         cp_course_cd igs_ps_ver.course_cd%TYPE) IS
720     SELECT  transfer_course_cd
721     FROM igs_ps_stdnt_trn
722     WHERE person_id = cp_person_id AND
723           course_cd = cp_course_cd AND
724          ( transfer_dt  BETWEEN  p_fte_start_dt AND p_fte_end_dt );
725 
726     -- get all the completed unit attempts of the program transferred from
727     CURSOR c_trn_from_units (cp_person_id igs_pe_person.person_id%TYPE ,
728                         cp_course_cd igs_ps_ver.course_cd%TYPE) IS
729     SELECT unit_cd,
730         version_number,
731         ci_start_dt,
732         override_enrolled_cp ,
733                 uoo_id
734     FROM igs_en_su_attempt_all
735     WHERE person_id = cp_person_id AND
736     course_cd = cp_course_cd AND
737     unit_attempt_status = cst_completed AND
738     (ci_start_dt BETWEEN p_fte_start_dt AND p_fte_end_dt) ;
739 
740     -- get all the year of programs lying in the fte calculation period
741     -- jtmathew modified this cursor to use optional cp_selection_dt parameters for HE370 changes
742     -- jtmathew modified this cursor to allow for end_dts for HE357 changes
743     -- smaddali modified this cursors where clause for selection and completion dates for bug 2448315
744     -- smaddali modified this cursor to pick up acad_perd field from igs_ps_us_prenr_cfg instead of
745     -- from igs_en_susa_year_v for bug 2452785
746     CURSOR c_crs_year(cp_person_id         igs_pe_person.person_id%TYPE ,
747                       cp_course_cd         igs_ps_ver.course_cd%TYPE,
748                       cp_selection_dt_from igs_as_su_setatmpt.selection_dt%TYPE,
749                       cp_selection_dt_to   igs_as_su_setatmpt.selection_dt%TYPE) IS
750     SELECT usv.unit_set_cd , usv.us_version_number , usv.sequence_number,
751            us.sequence_no acad_perd, usv.selection_dt, usv.rqrmnts_complete_dt completion_dt, usv.end_dt
752       FROM igs_as_su_setatmpt usv  , igs_ps_us_prenr_cfg us
753      WHERE usv.unit_set_cd = us.unit_set_cd
754        AND usv.person_id = cp_person_id
755        AND usv.course_cd  = cp_course_cd
756        AND usv.selection_dt IS NOT NULL
757        AND usv.selection_dt < p_fte_end_dt
758        AND ((usv.rqrmnts_complete_dt > p_fte_start_dt OR usv.end_dt > p_fte_start_dt)
759             OR (usv.end_dt IS NULL AND usv.rqrmnts_complete_dt IS NULL))
760        AND (cp_selection_dt_from IS NULL
761             OR usv.selection_dt BETWEEN cp_selection_dt_from AND cp_selection_dt_to)
762   ORDER BY NVL(usv.rqrmnts_complete_dt, usv.end_dt) DESC;
763     c_crs_year_rec  c_crs_year%ROWTYPE ;
764 
765     -- Retrieve the number of student program attempts that have more than one year of program
766     -- within the FTE calculation period
767     -- jtmathew modified this cursor to use optional cp_selection_dt parameters for HE370 changes
768     -- jtmathew created this cursor for HE357 changes
769     CURSOR c_multi_yop(cp_person_id         igs_pe_person.person_id%TYPE ,
770                        cp_course_cd         igs_ps_ver.course_cd%TYPE,
771                        cp_selection_dt_from igs_as_su_setatmpt.selection_dt%TYPE,
772                        cp_selection_dt_to   igs_as_su_setatmpt.selection_dt%TYPE) IS
773     SELECT usv.person_id, usv.course_cd, count(*) multi_yop_count
774     FROM   igs_as_su_setatmpt usv  , igs_ps_us_prenr_cfg us
775      WHERE usv.unit_set_cd = us.unit_set_cd
776        AND usv.person_id = cp_person_id
777        AND usv.course_cd  = cp_course_cd
778        AND usv.selection_dt IS NOT NULL
779        AND usv.selection_dt < p_fte_end_dt
780        AND ((usv.rqrmnts_complete_dt > p_fte_start_dt OR usv.end_dt > p_fte_start_dt)
781             OR (usv.end_dt IS NULL AND usv.rqrmnts_complete_dt IS NULL))
782        AND (cp_selection_dt_from IS NULL
783             OR usv.selection_dt BETWEEN cp_selection_dt_from AND cp_selection_dt_to)
784   GROUP BY usv.person_id, usv.course_cd
785     HAVING count(*) > 1;
786     c_multi_yop_rec  c_multi_yop%ROWTYPE ;
787 
788     -- get the academic calendar instance corresponding to the passed year of program
789     -- jtmathew modified this cursor to use optional cp_selection_dt parameters for HE370 changes
790     -- jtmathew rewrote c_year_cal cursor to select calendar instance
791     -- based on yop selection, completion and end dates for HE357 changes
792     -- smaddali modified the cursor to add DISTINCT ,to eliminate duplicate records for bug 2452785
793     CURSOR c_year_cal (cp_person_id         igs_pe_person.person_id%TYPE,
794                        cp_course_cd         igs_ps_ver.course_cd%TYPE,
795                        cp_unit_set_cd       igs_as_su_setatmpt.unit_set_cd%TYPE,
796                        cp_selection_dt_from igs_as_su_setatmpt.selection_dt%TYPE,
797                        cp_selection_dt_to   igs_as_su_setatmpt.selection_dt%TYPE) IS
798     SELECT ci.cal_type, ci.sequence_number, ci.start_dt, ci.end_dt
799       FROM igs_ca_inst ci,
800            igs_ca_type cat,
801            igs_ca_stat cs,
802            igs_en_stdnt_ps_att_all sca,
803            igs_as_su_setatmpt susa
804      WHERE sca.person_id = susa.person_id
805        AND sca.course_cd = susa.course_cd
806        AND sca.cal_type = ci.cal_type
807        AND ci.cal_type = cat.cal_type
808        AND ci.cal_status = cs.cal_status
809        AND cs.s_cal_status = 'ACTIVE'
810        AND cat.s_cal_cat = 'ACADEMIC'
811        AND sca.person_id = cp_person_id
812        AND sca.course_cd = cp_course_cd
813        AND susa.unit_set_cd = cp_unit_set_cd
814        AND ((susa.selection_dt < ci.end_dt ) OR
815            ( susa.rqrmnts_complete_dt IS NOT NULL AND
816                   (ci.end_dt BETWEEN susa.selection_dt AND susa.rqrmnts_complete_dt)) OR
817            ( susa.end_dt IS NOT NULL AND
818                   (ci.end_dt BETWEEN susa.selection_dt AND susa.end_dt)))
819        AND ci.start_dt < p_fte_end_dt
820        AND (cp_selection_dt_from IS NULL
821             OR susa.selection_dt BETWEEN cp_selection_dt_from AND cp_selection_dt_to)
822   ORDER BY ci.start_dt DESC;
823     c_year_cal_rec  c_year_cal%ROWTYPE ;
824 
825     -- get the standard annual load for the program
826     CURSOR c_ann_load (cp_course_cd  igs_ps_ver.course_cd%TYPE ,
827                        cp_version_number  igs_ps_ver.version_number%TYPE ) IS
828     SELECT std_annual_load
829     FROM igs_ps_ver_all
830     WHERE course_cd = cp_course_cd AND
831          version_number = cp_version_number ;
832 
833     -- get the current year of program for the passed program attempt which has
834     -- either started, completed or ended in the fte period
835     -- jtmathew modified this cursor to use optional cp_selection_dt parameters for HE370 changes
836     -- jtmathew modified this cursor to allow for end_dts for HE357 changes
837     -- smaddali modified this cursors where clause of selection_dt and completion_dt for bug 2448315
838     CURSOR c_year (cp_person_id         igs_pe_person.person_id%TYPE,
839                    cp_course_cd         igs_ps_ver.course_cd%TYPE,
840                    cp_selection_dt_from igs_as_su_setatmpt.selection_dt%TYPE,
841                    cp_selection_dt_to   igs_as_su_setatmpt.selection_dt%TYPE) IS
842     SELECT susa.unit_set_cd , susa.us_version_number , susa.sequence_number
843       FROM igs_as_su_setatmpt susa, igs_ps_us_prenr_cfg us
844      WHERE susa.unit_set_cd = us.unit_set_cd
845        AND susa.person_id = cp_person_id
846        AND susa.course_cd  = cp_course_cd
847        AND susa.selection_dt IS NOT NULL
848        AND susa.selection_dt < p_fte_end_dt
849        AND ((susa.rqrmnts_complete_dt > p_fte_start_dt OR susa.end_dt > p_fte_start_dt)
850             OR (susa.end_dt IS NULL AND susa.rqrmnts_complete_dt IS NULL))
851        AND (cp_selection_dt_from IS NULL
852             OR susa.selection_dt BETWEEN cp_selection_dt_from AND cp_selection_dt_to)
853   ORDER BY NVL(susa.rqrmnts_complete_dt, susa.end_dt) DESC;
854     c_year_rec  c_year%ROWTYPE;
855 
856     -- get the HESA unit set attempt corresponding to the current year of program
857     -- in which to save the calculated fte
858     CURSOR c_susa_upd (cp_person_id igs_pe_person.person_id%TYPE ,
859                        cp_course_cd  igs_ps_ver.course_cd%TYPE ,
860            cp_unit_set_cd  igs_en_unit_set.unit_set_cd%TYPE ,
861            cp_sequence_number igs_as_su_setatmpt.sequence_number%TYPE ) IS
862     SELECT rowid , susa.*
863     FROM igs_he_en_susa susa
864     WHERE person_id = cp_person_id AND
865           course_cd = cp_course_cd AND
866       unit_set_cd = cp_unit_set_cd AND
867       sequence_number = cp_sequence_number ;
868     c_susa_upd_rec  c_susa_upd%ROWTYPE ;
869 
870     -- jtmathew modified for HE357 to avoid the selection of proportions that are closed
871     -- get the apportioned fte % for the current academic calendar
872     CURSOR c_fte_prop( cp_cal_type igs_ca_inst.cal_type%TYPE ,
873                        cp_ci_sequence_number igs_ca_inst.sequence_number%TYPE ,
874            cp_acad_perd igs_ps_us_prenr_cfg.sequence_no%TYPE )  IS
875     SELECT fte_perc
876     FROM   igs_he_fte_proprt
877     WHERE  cal_type = cp_cal_type AND
878            ci_sequence_number = cp_ci_sequence_number AND
879            fte_cal_type = p_fte_cal_type AND
880            fte_sequence_num = p_fte_sequence_number AND
881            year_of_program = cp_acad_perd AND
882            closed_ind = 'N';
883     c_fte_prop_rec  c_fte_prop%ROWTYPE ;
884 
885     -- check if the program has been intermitted for some part of the fte period
886     CURSOR c_intm_part (cp_person_id igs_pe_person.person_id%TYPE ,
887                         cp_course_cd igs_ps_ver.course_cd%TYPE ,
888                         cp_start_dt DATE ,
889                         cp_end_dt DATE) IS
890     SELECT  start_dt , end_dt
891     FROM igs_en_stdnt_ps_intm spi
892     WHERE spi.person_id = cp_person_id AND
893       spi.course_cd = cp_course_cd AND
894       spi.start_dt < cp_end_dt AND
895       spi.end_dt > cp_start_dt AND
896           spi.logical_delete_date = TO_DATE('31-12-4712','DD-MM-YYYY') AND
897       (spi.approved = 'Y' OR
898       EXISTS( SELECT 1 FROM igs_en_intm_types
899               WHERE intermission_type = spi.intermission_type AND
900                     appr_reqd_ind = 'N' ));
901 
902     c_intm_part_rec  c_intm_part%ROWTYPE ;
903 
904     -- get the apportionment period set up at the program level
905     CURSOR c_prog_app(cp_course_cd igs_ps_ver_all.course_cd%TYPE ,
906                       cp_version_number igs_ps_ver_all.version_number%TYPE )  IS
907     SELECT teach_period_start_dt , teach_period_end_dt
908     FROM igs_he_st_prog_all prog
909     WHERE prog.course_cd = cp_course_cd AND
910           prog.version_number = cp_version_number ;
911     c_prog_app_rec  c_prog_app%ROWTYPE ;
912 
913     -- get the apportionment period set up at the POOUS level
914     CURSOR c_poous_app(cp_coo_id igs_ps_ofr_opt_all.coo_id%TYPE ,
915                        cp_unit_set_cd  igs_en_unit_set.unit_set_cd%TYPE ,
916                        cp_us_version_number  igs_en_unit_set.version_number%TYPE )  IS
917     SELECT teach_period_start_dt , teach_period_end_dt
918     FROM igs_he_poous_all poous, igs_ps_ofr_opt_all coo
919     WHERE poous.course_cd = coo.course_cd AND
920           poous.crv_version_number = coo.version_number AND
921           poous.cal_type = coo.cal_type AND
922           poous.location_cd = coo.location_cd AND
923           poous.attendance_type = coo.attendance_type AND
924           poous.attendance_mode = coo.attendance_mode AND
925           coo.coo_id = cp_coo_id AND
926           unit_set_cd = cp_unit_set_cd AND
927           us_version_number = cp_us_version_number ;
928     c_poous_app_rec  c_poous_app%ROWTYPE ;
929 
930     -- get the apportionment period setup at the fte calendar level
931     CURSOR c_fte_app IS
932     SELECT ci.start_dt , ci.end_dt
933     FROM igs_he_fte_cal_prd fp , igs_ca_inst ci
934     WHERE fp.teach_cal_type = ci.cal_type AND
935           fp.teach_sequence_num = ci.sequence_number AND
936           fp.fte_cal_type = p_fte_cal_type AND
937       fp.fte_sequence_num = p_fte_sequence_number ;
938 
939 
940     -- get the start and end dates of the teaching calendar passed
941     CURSOR c_cal_inst(cp_cal_type igs_ca_inst.cal_type%TYPE ,
942                 cp_sequence_number igs_ca_inst.sequence_number%TYPE ) IS
943     SELECT start_dt , end_dt
944     FROM igs_ca_inst
945     WHERE cal_type = cp_cal_type AND
946             sequence_number = cp_sequence_number ;
947     c_cal_inst_rec    c_cal_inst%ROWTYPE ;
948 
949     -- smaddali added these variables and cursor for bug#3171373
950     l_old_person_id  igs_he_st_spa_all.person_id%TYPE ;
951     l_old_stin       igs_he_st_spa_all.student_inst_number%TYPE;
952     l_trn_commencement_dt  igs_en_stdnt_ps_att_all.commencement_dt%TYPE ;
953 
954     -- Get the min commencement dt of the person with passed student instance number
955     CURSOR  c_trn_commencement( cp_person_id igs_he_st_spa_all.person_id%TYPE ,
956                                 cp_stin   igs_he_st_spa_all.student_inst_number%TYPE) IS
957     SELECT  MIN(sca.commencement_dt) trn_commencement_dt
958     FROM    igs_en_stdnt_ps_att sca,
959         igs_he_st_spa    hspa
960     WHERE   hspa.person_id             = cp_person_id
961       AND  hspa.student_inst_number   = cp_stin
962       AND  sca.person_id              = hspa.person_id
963       AND  sca.course_cd              = hspa.course_cd;
964 
965     -- smaddali added cursors for HECR214 - term based fees enhancement build, bug#3291656
966     -- Get the latest Term record for the Leavers during which the student left
967     CURSOR c_term1_lev( cp_person_id  igs_en_spa_terms.person_id%TYPE,
968                         cp_course_cd  igs_en_spa_terms.program_cd%TYPE,
969                         cp_lev_dt  DATE ) IS
970     SELECT  tr.program_version , tr.coo_id
971     FROM  igs_en_spa_terms tr , igs_ca_inst_all ca
972     WHERE  tr.term_cal_type = ca.cal_type AND
973            tr.term_sequence_number = ca.sequence_number AND
974            tr.person_id = cp_person_id AND
975            tr.program_cd = cp_course_cd AND
976            cp_lev_dt BETWEEN ca.start_dt AND ca.end_dt
977     ORDER BY  ca.start_dt DESC;
978     c_term1_lev_rec   c_term1_lev%ROWTYPE ;
979 
980     -- Get the latest Term record for the Leavers just before the student left
981     CURSOR c_term2_lev( cp_person_id  igs_en_spa_terms.person_id%TYPE,
982                         cp_course_cd  igs_en_spa_terms.program_cd%TYPE,
983                         cp_lev_dt  DATE ) IS
984     SELECT  tr.program_version , tr.coo_id
985     FROM  igs_en_spa_terms tr , igs_ca_inst_all ca
986     WHERE  tr.term_cal_type = ca.cal_type AND
987            tr.term_sequence_number = ca.sequence_number AND
988            tr.person_id = cp_person_id AND
989            tr.program_cd = cp_course_cd AND
990            cp_lev_dt > ca.start_dt AND
991            ca.start_dt BETWEEN p_fte_start_dt AND p_fte_end_dt
992     ORDER BY  ca.start_dt DESC;
993     c_term2_lev_rec    c_term2_lev%ROWTYPE ;
994 
995     -- Get the latest term record for the Continuing students
996     CURSOR c_term_con ( cp_person_id  igs_en_spa_terms.person_id%TYPE,
997                         cp_course_cd  igs_en_spa_terms.program_cd%TYPE) IS
998     SELECT  tr.program_version , tr.coo_id
999     FROM  igs_en_spa_terms tr , igs_ca_inst_all ca
1000     WHERE  tr.term_cal_type = ca.cal_type AND
1001            tr.term_sequence_number = ca.sequence_number AND
1002            tr.person_id = cp_person_id AND
1003            tr.program_cd = cp_course_cd AND
1004            ca.start_dt BETWEEN p_fte_start_dt AND p_fte_end_dt
1005     ORDER BY  ca.start_dt DESC;
1006     c_term_con_rec    c_term_con%ROWTYPE ;
1007     l_lev_dt   igs_en_stdnt_ps_att_all.discontinued_dt%TYPE ;
1008 
1009     -- Check if the passed course version belongs to the course category parameter
1010     CURSOR c_prg_cat ( cp_course_cd  igs_ps_ver_all.course_cd%TYPE,
1011                        cp_version_number  igs_ps_ver_all.version_number%TYPE ) IS
1012     SELECT course_cd,version_number
1013     FROM igs_ps_categorise_all ct where
1014       ct.course_cd = cp_course_cd AND
1015       ct.version_number = cp_version_number AND
1016       ct.course_cat = p_course_cat ;
1017     c_prg_cat_rec     c_prg_cat%ROWTYPE ;
1018 
1019     -- Determine type (static or dynamic) of person id group
1020     CURSOR c_group_type IS
1021     SELECT group_type
1022       FROM igs_pe_persid_group_v
1023     WHERE group_id = p_person_id_grp;
1024 
1025     BEGIN
1026 
1027       --anwest 18-JAN-2006 Bug# 4950285 R12 Disable OSS Mandate
1028       IGS_GE_GEN_003.SET_ORG_ID;
1029 
1030       -- Calculate the EFTSU total for a student course attempt within a
1031       -- nominated FTE calendar instance.
1032       -- Note: p_app_res_st_fte indicates whether the FTE figures should be
1033       --       apportioned for research students who haven't studied the entire academic session.
1034       -- Note: p_credit_points is used to return the total credit point
1035       --       value from which the EFTSU was calculated.
1036       ----------
1037 
1038       retcode := 0;
1039 
1040       l_selection_dt_from := TO_DATE(p_selection_dt_from, 'yyyy/mm/dd hh24:mi:ss');
1041       l_selection_dt_to   := TO_DATE(p_selection_dt_to,   'yyyy/mm/dd hh24:mi:ss');
1042 
1043       IF (l_selection_dt_from IS NULL AND l_selection_dt_to IS NOT NULL) OR
1044          (l_selection_dt_from IS NOT NULL AND l_selection_dt_to IS NULL) THEN
1045           fnd_message.set_name('IGS','IGS_HE_FTE_US_SEL_DT_ERR');
1046           errbuf  := fnd_message.get;
1047           fnd_file.put_line(fnd_file.log, fnd_message.get);
1048           retcode := 2 ;
1049           RETURN ;
1050       END IF;
1051 
1052       --get the following values from the passed parameters
1053       p_fte_cal_type := RTRIM( SUBSTR(p_fte_cal,1,10) ) ;
1054       p_fte_sequence_number := TO_NUMBER( RTRIM (SUBSTR(p_fte_cal,11,6) ) ) ;
1055 
1056       OPEN c_fte_prd ;
1057       FETCH c_fte_prd INTO p_fte_start_dt , p_fte_end_dt ;
1058       CLOSE c_fte_prd ;
1059 
1060        /** logs all the parameters in the LOG **/
1061       --
1062       Fnd_Message.Set_Name('IGS','IGS_FI_ANC_LOG_PARM');
1063       Fnd_File.Put_Line(Fnd_File.LOG,FND_MESSAGE.GET);
1064       log_messages('P_FTE_CAL              ',p_fte_cal);
1065       log_messages('P_FTE_START_DT         ',p_fte_start_dt);
1066       log_messages('P_FTE_END_DT           ',p_fte_end_dt);
1067       log_messages('P_PERSON_ID            ',p_person_id);
1068       log_messages('P_PERSON_ID_GRP        ',p_person_id_grp);
1069       log_messages('P_COURSE_CD            ',p_course_cd);
1070       log_messages('P_COURSE_CAT           ',p_course_cat);
1071       log_messages('P_COO_ID               ',p_coo_id);
1072       log_messages('P_SELECTION_DT_FROM    ',p_selection_dt_from);
1073       log_messages('P_SELECTION_DT_TO      ',p_selection_dt_to);
1074       log_messages('P_ASS_RES_ST_FTE       ',p_app_res_st_fte);
1075       log_messages('P_ATT_PRC_ST_FTE       ',p_att_prc_st_fte);
1076 
1077       -- initialize fnd_dsql data-structures
1078       fnd_dsql.init;
1079 
1080       -- Construct Initial SPA Selection SQL statement.
1081       fnd_dsql.add_text('SELECT pe.person_number,spa.person_id, spa.course_cd ,spa.version_number,spa.coo_id,');
1082       fnd_dsql.add_text('       spa.course_attempt_status, spa.discontinued_dt,');
1083       fnd_dsql.add_text('       spa.course_rqrmnts_complete_dt, spa.commencement_dt,');
1084       fnd_dsql.add_text('       spa.course_rqrmnt_complete_ind, hspa.student_inst_number');
1085       fnd_dsql.add_text('  FROM igs_en_stdnt_ps_att_all spa, igs_he_st_spa_all hspa, igs_pe_person_base_v pe ');
1086       fnd_dsql.add_text(' WHERE hspa.person_id = spa.person_id ');
1087       fnd_dsql.add_text('   AND hspa.course_cd = spa.course_cd ');
1088       fnd_dsql.add_text('   AND pe.person_id = spa.person_id ');
1089 
1090       -- Include person id criteria if required
1091       IF p_person_id IS NOT NULL THEN
1092 
1093         fnd_dsql.add_text('   AND spa.person_id = ');
1094         fnd_dsql.add_bind(p_person_id);
1095 
1096       END IF;
1097 
1098       -- Include program code criteria if required
1099       IF p_course_cd IS NOT NULL THEN
1100 
1101         fnd_dsql.add_text('   AND spa.course_cd = ');
1102         fnd_dsql.add_bind(p_course_cd);
1103 
1104       END IF;
1105 
1106       -- Include person ID group criteria if required (person_id cannot be entered)
1107       IF p_person_id_grp IS NOT NULL AND p_person_id IS NULL THEN
1108 
1109           -- Determine type (static or dynamic) of person id group
1110           OPEN c_group_type;
1111           FETCH c_group_type INTO l_group_type;
1112           CLOSE c_group_type;
1113 
1114           IF l_group_type = 'STATIC' THEN
1115 
1116               fnd_dsql.add_text('    AND EXISTS ' );
1117               fnd_dsql.add_text('       (SELECT ''X'' ');
1118               fnd_dsql.add_text('          FROM igs_pe_prsid_grp_mem_all a ' );
1119               fnd_dsql.add_text('         WHERE a.person_id = spa.person_id ' );
1120               fnd_dsql.add_text('           AND a.group_id = ');
1121               fnd_dsql.add_bind(p_person_id_grp);
1122               fnd_dsql.add_text('           AND (a.end_date IS NULL OR a.end_date > sysdate) ');
1123               fnd_dsql.add_text(       ')');
1124 
1125           ELSE
1126               -- Use library to get dynamic person id group members
1127               l_prs_grp_sql := IGS_PE_DYNAMIC_PERSID_GROUP.IGS_GET_DYNAMIC_SQL(p_person_id_grp, l_prs_grp_status);
1128 
1129               IF l_prs_grp_status <> 'S' THEN
1130               fnd_message.set_name('IGS','IGS_HE_UT_PRSN_ID_GRP_ERR');
1131               fnd_message.set_token('PRSNIDGRP',p_person_id_grp);
1132               errbuf := fnd_message.get();
1133               fnd_file.put_line(fnd_file.log, errbuf);  -- this message need to be displayed to user.
1134               retcode := '2';
1135               RETURN;
1136               END IF;
1137 
1138               fnd_dsql.add_text(  'AND spa.person_id IN (');
1139               fnd_dsql.add_text(l_prs_grp_sql);
1140               fnd_dsql.add_text(                       ')');
1141 
1142           END IF; -- Static / Dynamic
1143 
1144       END IF; -- Person ID Group Criteria
1145 
1146       -- Finish constructing SPA Selection SQL statement WHERE CLAUSE
1147       fnd_dsql.add_text('    AND spa.commencement_dt < ' );
1148       fnd_dsql.add_bind(p_fte_end_dt);
1149       fnd_dsql.add_text('    AND (spa.discontinued_dt IS NULL OR spa.discontinued_dt > ' );
1150       fnd_dsql.add_bind(p_fte_start_dt);
1151       fnd_dsql.add_text(        ')');
1152       fnd_dsql.add_text('    AND (spa.course_rqrmnts_complete_dt IS NULL OR  spa.course_rqrmnts_complete_dt > ' );
1153       fnd_dsql.add_bind(p_fte_start_dt);
1154       fnd_dsql.add_text(        ')');
1155       fnd_dsql.add_text('    AND spa.course_attempt_status IN ');
1156       fnd_dsql.add_text('        (''ENROLLED'',''DISCONTIN'',''COMPLETED'',''INTERMIT'',''INACTIVE'',''LAPSED'')');
1157 
1158       -- If Selection dates from and to are specified append additional condition to WHERE clause
1159       IF l_selection_dt_from IS NOT NULL THEN
1160 
1161         fnd_dsql.add_text('    AND EXISTS (');
1162         fnd_dsql.add_text('      SELECT b.person_id, b.course_cd');
1163         fnd_dsql.add_text('        FROM igs_as_su_setatmpt b ');
1164         fnd_dsql.add_text('       WHERE b.person_id = spa.person_id ');
1165         fnd_dsql.add_text('         AND b.course_cd = spa.course_cd ');
1166         fnd_dsql.add_text('         AND b.selection_dt between ');
1167         fnd_dsql.add_bind(l_selection_dt_from);
1168         fnd_dsql.add_text(        ' AND ');
1169         fnd_dsql.add_bind(l_selection_dt_to);
1170         fnd_dsql.add_text(               ')');
1171 
1172       END IF;
1173 
1174       -- Finish constructing SPA Selection SQL statement with ORDER BY
1175       fnd_dsql.add_text(' ORDER BY spa.person_id, hspa.student_inst_number, discontinued_dt DESC,');
1176       fnd_dsql.add_text('          course_rqrmnts_complete_dt DESC,  spa.commencement_dt DESC');
1177 
1178       l_cursor_id := DBMS_SQL.OPEN_CURSOR;
1179       fnd_dsql.set_cursor(l_cursor_id);
1180 
1181       l_fte_calc_sql := fnd_dsql.get_text(FALSE);
1182 
1183       DBMS_SQL.PARSE(l_cursor_id, l_fte_calc_sql, DBMS_SQL.NATIVE);
1184       fnd_dsql.do_binds;
1185 
1186       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 1, c_sca_rec.person_number,30);
1187       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 2, c_sca_rec.person_id);
1188       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 3, c_sca_rec.course_cd, 6);
1189       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 4, c_sca_rec.version_number);
1190       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 5, c_sca_rec.coo_id);
1191       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 6, c_sca_rec.course_attempt_status, 30);
1192       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 7, c_sca_rec.discontinued_dt);
1193       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 8, c_sca_rec.course_rqrmnts_complete_dt);
1194       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 9, c_sca_rec.commencement_dt);
1195       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 10, c_sca_rec.course_rqrmnt_complete_ind, 1);
1196       DBMS_SQL.DEFINE_COLUMN(l_cursor_id, 11, c_sca_rec.student_inst_number, 20);
1197 
1198       l_num_rows := DBMS_SQL.EXECUTE(l_cursor_id);
1199 
1200       -- check if there are no student programs satisfying the passed parameters
1201       -- fetch a row
1202       IF DBMS_SQL.FETCH_ROWS(l_cursor_id) = 0 THEN
1203          DBMS_SQL.CLOSE_CURSOR(l_cursor_id);
1204          FND_MESSAGE.SET_NAME('IGS','IGS_UC_HE_NO_DATA');
1205          FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.Get) ;
1206          RETURN ;
1207 
1208       ELSE
1209 
1210           FND_MESSAGE.SET_NAME('IGS','IGS_HE_FTE_PROC');
1211           FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.Get) ;
1212           FND_FILE.PUT_LINE(FND_FILE.LOG,'------------------------------------------------------') ;
1213 
1214           -- loop through all the student program attempts and calculate FTE for each program attempt
1215           LOOP
1216 
1217             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 1,c_sca_rec.person_number);
1218             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 2,c_sca_rec.person_id);
1219             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 3,c_sca_rec.course_cd);
1220             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 4,c_sca_rec.version_number);
1221             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 5,c_sca_rec.coo_id);
1222             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 6,c_sca_rec.course_attempt_status);
1223             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 7,c_sca_rec.discontinued_dt);
1224             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 8,c_sca_rec.course_rqrmnts_complete_dt);
1225             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 9,c_sca_rec.commencement_dt);
1226             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 10,c_sca_rec.course_rqrmnt_complete_ind);
1227             DBMS_SQL.COLUMN_VALUE(l_cursor_id, 11,c_sca_rec.student_inst_number);
1228 
1229             l_exit_flag    := FALSE ;
1230             l_lev_dt       := NULL;
1231 
1232             IF c_sca_rec.course_attempt_status IN (cst_inactive, cst_lapsed) THEN
1233                 OPEN c_en_hist(c_sca_rec.person_id, c_sca_rec.course_cd);
1234                 FETCH c_en_hist INTO c_en_hist_rec;
1235                 IF (c_en_hist%NOTFOUND) THEN
1236                     l_exit_flag := TRUE;
1237                 END IF;
1238                 CLOSE c_en_hist;
1239             END IF;
1240 
1241             IF NOT l_exit_flag THEN
1242              -- smaddali removed code to check the Transfer table for bug#3171373.
1243              -- check if fte has to be calculated for the current program
1244              -- smaddali replaced l_fet_falg with person_id , student_inst_number comparision for bug#3171373
1245              IF l_old_person_id     = c_sca_rec.person_id AND
1246                 l_old_stin          = c_sca_rec.student_inst_number  THEN
1247                    -- this program attempt is a continuation of the Previous program attempt
1248                    -- because of Program transfer and hence need not calculate FTE for this program attempt
1249                    -- donot replace this condition with converse condition because it requires NVL check
1250                    NULL;
1251              ELSE
1252 
1253                -- calculate FTE for this program as this is a new person's record
1254                -- and also copy this student instance number and person_id to the old value parameters
1255                l_old_person_id :=  c_sca_rec.person_id ;
1256                l_old_stin      :=  c_sca_rec.student_inst_number ;
1257 
1258                -- smaddali added following code for HECR214 - term based fees enhancement build , Bug#3291656
1259                -- to get coo_id,version_number from the Term record and validate coo_id and course_cat parameters
1260 
1261                -- Get the Leaving date for the student to  determine if he is a continuing student or a leaver
1262                l_lev_dt       := NVL(c_sca_rec.course_rqrmnts_complete_dt,c_sca_rec.discontinued_dt) ;
1263 
1264                -- Get the coo_id and version_number for this student program attempt from the corresponding Term record
1265                -- The term record is obtained based on whether the student is a leaver or a continuing student
1266                -- The leaving dt either lies in the Fte period in which case the student is a leaver
1267                -- or is GT the FTE end_dt or is NULL in this case the student is a Continuing student within the FTE period
1268                -- If student is a Leaver then get the corresponding Term record details
1269                IF l_lev_dt BETWEEN p_fte_start_dt AND p_fte_end_dt THEN
1270                             -- get the latest term record within which the Leaving date falls
1271                             c_term1_lev_rec        := NULL ;
1272                             OPEN c_term1_lev (c_sca_rec.person_id, c_sca_rec.course_cd, l_lev_dt );
1273                             FETCH c_term1_lev INTO c_term1_lev_rec ;
1274                             IF c_term1_lev%NOTFOUND THEN
1275                                 -- Get the latest term record just before the Leaving date
1276                                 c_term2_lev_rec    := NULL ;
1277                                 OPEN c_term2_lev(c_sca_rec.person_id, c_sca_rec.course_cd, l_lev_dt ) ;
1278                                 FETCH c_term2_lev INTO c_term2_lev_rec ;
1279                                 IF  c_term2_lev%FOUND THEN
1280                                     -- Override the version_number,coo_id in the SCA record with the term record values
1281                                     c_sca_rec.version_number   := c_term2_lev_rec.program_version ;
1282                                     c_sca_rec.coo_id           := c_term2_lev_rec.coo_id ;
1283                                 END IF ;
1284                                 CLOSE c_term2_lev ;
1285                             ELSE
1286                                 -- Override the version_number,coo_id in the SCA record with the term record values
1287                                 c_sca_rec.version_number   := c_term1_lev_rec.program_version ;
1288                                 c_sca_rec.coo_id           := c_term1_lev_rec.coo_id ;
1289                             END IF ;
1290                             CLOSE c_term1_lev ;
1291                -- If student is a continuing student then get the corresponding Term record details
1292                ELSE
1293                            -- Get the latest term record which falls within the FTE period and term start date > commencement dt
1294                            c_term_con_rec  := NULL ;
1295                            OPEN c_term_con(c_sca_rec.person_id, c_sca_rec.course_cd);
1296                            FETCH c_term_con INTO c_term_con_rec ;
1297                            IF c_term_con%FOUND THEN
1298                                 -- Override the version_number,coo_id in the SCA record with the term record values
1299                                 c_sca_rec.version_number   := c_term_con_rec.program_version ;
1300                                 c_sca_rec.coo_id           := c_term_con_rec.coo_id ;
1301                            END IF ;
1302                            CLOSE c_term_con ;
1303                END IF ;
1304 
1305                -- coo_id parameter filter
1306                -- If the current student's coo_id doesnot match the passed coo_id parameter then skip this program attempt
1307                IF p_coo_id IS NOT NULL AND c_sca_rec.coo_id <> p_coo_id THEN
1308                         l_exit_flag := TRUE ;
1309                END IF;
1310 
1311                -- course_cat paramater filter
1312                -- If the current student's course is not a member of the passed course category parameter then skip this program attempt
1313                IF p_course_cat IS NOT NULL THEN
1314                        c_prg_cat_rec           := NULL;
1315                        OPEN c_prg_cat(c_sca_rec.course_cd, c_sca_rec.version_number ) ;
1316                        FETCH c_prg_cat INTO c_prg_cat_rec;
1317                        IF c_prg_cat%NOTFOUND THEN
1318                            l_exit_flag := TRUE ;
1319                        END IF;
1320                        CLOSE c_prg_cat ;
1321                END IF ;
1322 
1323             END IF;
1324             -- end of l_exit_flag check
1325 
1326                 -- If the course_cat and coo_id parameter validations have passed
1327                 -- then calculate fte for this program attempt
1328                 IF NOT l_exit_flag  THEN
1329 
1330                         FND_MESSAGE.SET_NAME('IGS','IGS_HE_SPA');
1331                         -- smaddali moved set token to after set message name for bug 2429893
1332                         FND_MESSAGE.SET_TOKEN('PERSON_ID',c_sca_rec.person_number);
1333                         FND_MESSAGE.SET_TOKEN('COURSE_CD',c_sca_rec.course_cd);
1334                         FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.Get) ;
1335 
1336                         -- check if the program attempt has been intermitted for the whole FTE period then fte=0
1337                         IF igs_he_extract_fields_pkg.isDormant
1338                             (p_person_id        => c_sca_rec.person_id,
1339                              p_course_cd        => c_sca_rec.course_cd,
1340                              p_version_number   => c_sca_rec.version_number,
1341                              p_enrl_start_dt    => p_fte_start_dt,
1342                              p_enrl_end_dt      => p_fte_end_dt)
1343                         THEN
1344                             l_Calculated_FTE :=  0;
1345                         ELSE
1346 
1347                             l_Calculated_FTE := 0 ;
1348                             l_fte_calc_type := NULL ;
1349                             l_message := NULL ;
1350 
1351                             -- derive the fte calculation type as per the setup,
1352                             -- if not able to find fte calculation type then p_message will be not null
1353                             fte_type_intensity (p_person_id => c_sca_rec.person_id,
1354                                                 p_unit_set_cd => NULL,
1355                                                 p_us_version_number => NULL,
1356                                                 p_sequence_number => NULL,
1357                                                 p_att_prc_st_fte  => p_att_prc_st_fte,
1358                                                 p_coo_id => c_sca_rec.coo_id ,
1359                                                 p_fte_calc_type => l_fte_calc_type ,
1360                                                 p_fte_intensity => l_dummy2 ,
1361                                                 p_selection_dt_from => l_selection_dt_from,
1362                                                 p_selection_dt_to => l_selection_dt_to,
1363                                                 p_message => l_message) ;
1364 
1365                             IF l_message IS NOT NULL OR l_fte_calc_type IS NULL THEN
1366                               -- ie current year of program not found  / hesa mapping for attendance type not found
1367                               -- implies that fte calculation type could not be found
1368 
1369                               FND_MESSAGE.SET_NAME('IGS','IGS_HE_NO_CALC_TYPE') ;
1370                               FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET );
1371                               FND_MESSAGE.SET_NAME('IGS', l_message );
1372                               FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET) ;
1373                                l_exit_flag := TRUE ; -- skip this current program attempt and go to the next program attempt
1374                             END IF ;
1375 
1376                             -- start of unit based calculation
1377                             IF l_fte_calc_type IN ('U','B') AND NOT l_exit_flag  THEN
1378 
1379                                l_total_credit_points := 0 ;
1380                                l_std_annual_load := NULL ;
1381 
1382                                --  Loop through all unit attempts for the program attempt in context
1383                                FOR c_sua_rec IN c_sua(c_sca_rec.person_id , c_sca_rec.course_cd) LOOP
1384                                   l_unit_cp := NULL ;
1385                                   l_unit_ver_cp := NULL ;
1386                                   l_app_days := NULL ;
1387                                   l_actual_days := NULL ;
1388 
1389 
1390                                   IF c_sua_rec.override_enrolled_cp IS NOT NULL THEN
1391                                        l_unit_cp := c_sua_rec.override_enrolled_cp ;
1392                                   ELSE
1393                                        -- get the enrolled credit points defined at unit version level
1394                                        OPEN c_unit_cp (c_sua_rec.uoo_id);
1395                                        FETCH c_unit_cp INTO l_unit_ver_cp ;
1396                                        CLOSE c_unit_cp ;
1397                                        l_unit_cp := l_unit_ver_cp ;
1398                                   END IF;
1399 
1400                                   --If the program attempt is discontinued or intermitted then
1401                                   -- apportion the credit points
1402                                   IF ( c_sua_rec.unit_attempt_status = cst_discontin AND
1403                                         c_sca_rec.course_attempt_status IN (cst_discontin , cst_intermit) ) THEN
1404                                       OPEN c_cal_inst(c_sua_rec.cal_type, c_sua_rec.ci_sequence_number );
1405                                       FETCH c_cal_inst INTO c_cal_inst_rec ;
1406                                       CLOSE c_cal_inst ;
1407                                       -- smaddali ,modified actual_days and app_days to add 1 after subtraction
1408                                       -- for bug 2453209
1409                                       l_actual_days :=  TRUNC(c_sua_rec.discontinued_dt) - c_cal_inst_rec.start_dt + 1 ;
1410                                       l_app_days :=  c_cal_inst_rec.end_dt - c_cal_inst_rec.start_dt + 1 ;
1411                                       l_unit_cp := l_unit_cp * ( l_actual_days / l_app_days ) ;
1412                                   END IF ;
1413 
1414                                   l_total_credit_points := l_total_credit_points + l_unit_cp  ;
1415 
1416                                END LOOP ;
1417 
1418                                -- If the current program was transferred from some other program then
1419                                -- completed units of the from program will also incurr load
1420                                OPEN c_trn_to( c_sca_rec.person_id , c_sca_rec.course_cd) ;
1421                                FETCH c_trn_to INTO l_trn_from_crs ;
1422                                IF c_trn_to%FOUND THEN
1423 
1424                                    FOR c_trn_from_units_rec IN c_trn_from_units(c_sca_rec.person_id ,l_trn_from_crs ) LOOP
1425                                       l_unit_cp := NULL ;
1426                                       l_unit_ver_cp := NULL ;
1427 
1428                                       IF c_trn_from_units_rec.override_enrolled_cp IS NOT NULL THEN
1429                                            l_unit_cp := c_trn_from_units_rec.override_enrolled_cp ;
1430                                       ELSE
1431                                            -- get the enrolled credit points defined at unit version level
1432                                            OPEN c_unit_cp(c_trn_from_units_rec.uoo_id);
1433                                            FETCH c_unit_cp INTO l_unit_ver_cp ;
1434                                            CLOSE c_unit_cp ;
1435                                            l_unit_cp := l_unit_ver_cp ;
1436                                       END IF;
1437                                       l_total_credit_points := l_total_credit_points + l_unit_cp ;
1438 
1439                                    END LOOP ;
1440 
1441                                 END IF ;
1442                                 CLOSE c_trn_to ;
1443 
1444                                 -- get the standard annual load for the program
1445                                 OPEN c_ann_load (c_sca_rec.course_cd , c_sca_rec.version_number) ;
1446                                 FETCH c_ann_load INTO l_std_annual_load ;
1447                                 IF l_std_annual_load  IS NULL OR l_std_annual_load = 0  THEN
1448                                     FND_MESSAGE.SET_NAME('IGS','IGS_HE_NO_ANN_LOAD');
1449                                     FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET );
1450                                      l_exit_flag := TRUE ; -- skip this current program attempt and go to the next program attempt
1451 
1452                                 ELSE
1453                                   l_calculated_FTE := l_calculated_FTE + ( ( l_total_credit_points * 100 ) / l_std_annual_load );
1454 
1455                                 END IF;
1456                                 CLOSE c_ann_load;
1457 
1458                             END IF ;
1459                             -- end of unit based calculation
1460 
1461                             -- start of intensity based calculation
1462                             IF l_fte_calc_type IN ('I','B') AND NOT l_exit_flag  THEN
1463 
1464                                -- jtmathew added for for HE357
1465                                -- check whether there are multiple student year of programs
1466                                l_multi_yop := FALSE ;
1467                                OPEN c_multi_yop(c_sca_rec.person_id , c_sca_rec.course_cd,
1468                                                 l_selection_dt_from,  l_selection_dt_to);
1469                                FETCH c_multi_yop INTO c_multi_yop_rec;
1470                                   IF c_multi_yop%FOUND THEN
1471                                      l_multi_yop := TRUE ;
1472                                   END IF;
1473                                CLOSE c_multi_yop;
1474 
1475                                -- for each year of program falling in the FTE period calculate FTE
1476                                FOR c_crs_year_rec IN c_crs_year( c_sca_rec.person_id , c_sca_rec.course_cd,
1477                                                                  l_selection_dt_from,  l_selection_dt_to) LOOP
1478                                   -- derive the fte_intensity set up '
1479                                   l_fte_intensity := NULL ;
1480                                   l_message := NULL ;
1481 
1482                                   fte_type_intensity (p_person_id => c_sca_rec.person_id,
1483                                                       p_unit_set_cd => c_crs_year_rec.unit_set_cd,
1484                                                       p_us_version_number => c_crs_year_rec.us_version_number,
1485                                                       p_sequence_number => c_crs_year_rec.sequence_number,
1486                                                       p_att_prc_st_fte => p_att_prc_st_fte,
1487                                                       p_coo_id => c_sca_rec.coo_id ,
1488                                                       p_fte_calc_type => l_dummy1 ,
1489                                                       p_fte_intensity => l_fte_intensity ,
1490                                                       p_selection_dt_from => l_selection_dt_from,
1491                                                       p_selection_dt_to => l_selection_dt_to,
1492                                                       p_message => l_message) ;
1493 
1494                                   IF l_message IS NOT NULL OR l_fte_intensity IS NULL THEN
1495                                       -- ie  program has both full time and part-time offerings
1496                                       -- implies that fte intensity could not be found
1497 
1498                                       FND_MESSAGE.SET_NAME('IGS','IGS_HE_NO_INTENSITY') ;
1499                                       FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET );
1500                                       FND_MESSAGE.SET_NAME('IGS', l_message );
1501                                       FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET) ;
1502                                       l_exit_flag := TRUE ;
1503                                       EXIT ; -- exit the year of program loop and go to the next program attempt
1504 
1505                                   ELSE
1506                                        l_calculated_intensity := l_fte_intensity ;
1507                                        l_app_start_dt := NULL ;
1508                                        l_app_end_dt := NULL ;
1509                                        l_actual_start_dt := NULL ;
1510                                        l_actual_end_dt := NULL ;
1511                                        l_intm_part_days := 0 ;
1512                                        l_intm_flag := FALSE ;
1513                                        l_actual_days := NULL ;
1514                                        l_app_days := NULL ;
1515                                        l_message := NULL ;
1516 
1517                                        -- get the apportionment period i.e the length of the current year of program
1518                                        IF   research_st(c_sca_rec.course_cd , c_sca_rec.version_number ) THEN
1519                                           l_app_start_dt := p_fte_start_dt ;
1520                                           l_app_end_dt := p_fte_end_dt ;
1521                                        ELSE
1522 
1523                                           OPEN c_poous_app(c_sca_rec.coo_id ,c_crs_year_rec.unit_set_cd ,
1524                                                       c_crs_year_rec.us_version_number);
1525                                           FETCH c_poous_app INTO c_poous_app_rec ;
1526                                           IF c_poous_app%FOUND AND
1527                                               c_poous_app_rec.teach_period_start_dt IS NOT NULL AND
1528                                               c_poous_app_rec.teach_period_end_dt IS NOT NULL THEN
1529                                               l_app_start_dt := c_poous_app_rec.teach_period_start_dt ;
1530                                               l_app_end_dt := c_poous_app_rec.teach_period_end_dt ;
1531                                           ELSE
1532                                             OPEN c_prog_app(c_sca_rec.course_cd,c_sca_rec.version_number);
1533                                             FETCH c_prog_app INTO c_prog_app_rec ;
1534                                             IF c_prog_app%FOUND AND
1535                                                c_prog_app_rec.teach_period_start_dt IS NOT NULL AND
1536                                                c_prog_app_rec.teach_period_end_dt IS NOT NULL THEN
1537                                                  l_app_start_dt := c_prog_app_rec.teach_period_start_dt ;
1538                                                  l_app_end_dt := c_prog_app_rec.teach_period_end_dt ;
1539                                             ELSE
1540                                                  OPEN c_fte_app ;
1541                                                  FETCH c_fte_app INTO l_app_start_dt , l_app_end_dt ;
1542                                                  CLOSE c_fte_app ;
1543                                             END IF;
1544                                             CLOSE c_prog_app ;
1545 
1546                                           END IF;
1547                                           CLOSE c_poous_app ;
1548 
1549                                        END IF ;
1550                                        -- smaddali modified app_days to add 1 after subtraction for bug 2453209
1551                                        l_app_days := l_app_end_dt - l_app_start_dt + 1 ;
1552 
1553                                        -- check if the student has periods of intermission
1554                                        -- in the present apportionment period
1555                                        FOR c_intm_part_rec IN  c_intm_part(c_sca_rec.person_id , c_sca_rec.course_cd ,
1556                                                l_app_start_dt , l_app_end_dt )
1557                                        LOOP
1558                                             l_intm_flag := TRUE ;
1559                                             IF c_intm_part_rec.start_dt < l_app_start_dt THEN
1560                                                   c_intm_part_rec.start_dt := l_app_start_dt ;
1561                                             END IF;
1562                                             IF (c_intm_part_rec.end_dt > l_app_end_dt OR
1563                                                 c_intm_part_rec.end_dt > c_sca_rec.discontinued_dt )THEN
1564                                                 c_intm_part_rec.end_dt := NVL(c_sca_rec.discontinued_dt,l_app_end_dt) ;
1565                                             END IF;
1566                                             -- smaddali modified intm_days to add 1 after subtraction for bug 2453209
1567                                             l_intm_part_days :=  l_intm_part_days +
1568                                                   (c_intm_part_rec.end_dt - c_intm_part_rec.start_dt + 1 ) ;
1569                                        END LOOP ;
1570 
1571                                        -- calculate the actual period of study of the student in the current year of program
1572                                        -- in the following cases
1573                                        -- If the research student started or completed mid apportionment session or if he
1574                                        --discontinued before the end of the apportionment period then
1575                                        IF ( research_st(c_sca_rec.course_cd , c_sca_rec.version_number)  AND
1576                                             (c_sca_rec.commencement_dt > l_app_start_dt OR
1577                                               c_sca_rec.course_rqrmnts_complete_dt < l_app_end_dt) ) OR
1578                                               ( c_sca_rec.course_attempt_status = cst_discontin  AND
1579                                              c_sca_rec.discontinued_dt < l_app_end_dt )  OR
1580                                               l_intm_flag THEN
1581 
1582                                             -- get the actual period of the student contributing to fte for apportioning
1583                                             -- or remove intermission period if p_app_res_st_fte is 'N'
1584                                             IF  research_st(c_sca_rec.course_cd , c_sca_rec.version_number)  AND
1585                                                   p_app_res_st_fte = 'N' THEN
1586 
1587                                                   -- smaddali removed the logic based on acad_perd and hesa_mode_of_study for bug#3175107
1588                                                   -- apportion the fte to remove student intermissions in the fte period
1589                                                   l_calculated_intensity := l_calculated_intensity ;
1590                                                   -- If student has intermission periods then apportion the intensity
1591                                                   IF l_intm_flag THEN
1592                                                         l_calculated_intensity := l_calculated_intensity * ((l_app_days - l_intm_part_days) / l_app_days ) ;
1593                                                   END IF ;
1594 
1595                                             ELSE
1596 
1597                                                 -- smaddali added code to derive the commencement_dt of the trasnfer from program , for bug#3171373
1598                                                 l_trn_commencement_dt  := NULL ;
1599                                                 OPEN  c_trn_commencement(c_sca_rec.person_id, c_sca_rec.student_inst_number ) ;
1600                                                 FETCH c_trn_commencement INTO l_trn_commencement_dt ;
1601                                                 CLOSE c_trn_commencement ;
1602 
1603                                                 -- smaddali added condition to check that commencement_dt and
1604                                                 -- discontinued_dt lie in the FTE period , for bug#3177328
1605                                                 IF research_st(c_sca_rec.course_cd , c_sca_rec.version_number) THEN
1606                                                    -- use the commencement_dt of the transfer FROM program for apportioning fte
1607                                                    --for research students if it lies in the fte period
1608                                                    -- smaddali added code to consider the commencement date of
1609                                                    -- the transfer from program also, for bug#3171373
1610                                                     IF l_trn_commencement_dt > l_app_start_dt THEN
1611                                                          l_actual_start_dt :=  l_trn_commencement_dt ;
1612                                                     -- else use  this program's commencement_dt if it lies in the fte period
1613                                                     ELSIF c_sca_rec.commencement_dt > l_app_start_dt  THEN
1614                                                          l_actual_start_dt := c_sca_rec.commencement_dt ;
1615                                                     -- else apportion period start dt is the actual start date
1616                                                     ELSE
1617                                                          l_actual_start_dt := l_app_start_dt ;
1618                                                     END IF;
1619                                                 ELSE
1620                                                     l_actual_start_dt := l_app_start_dt ;
1621                                                 END IF;
1622 
1623                                                 IF (c_sca_rec.discontinued_dt < l_app_end_dt
1624                                                    AND c_sca_rec.course_rqrmnt_complete_ind = 'N') THEN
1625                                                    l_actual_end_dt := c_sca_rec.discontinued_dt ;
1626                                                 ELSIF (c_sca_rec.course_rqrmnts_complete_dt < l_app_end_dt) THEN
1627                                                    l_actual_end_dt := c_sca_rec.course_rqrmnts_complete_dt;
1628                                                 ELSE
1629                                                    l_actual_end_dt := l_app_end_dt ;
1630                                                 END IF;
1631 
1632                                                 --smaddali modified actual_days to add 1 after subtraction of dates for bug 2453209
1633                                                 l_actual_days := ( l_actual_end_dt - l_actual_start_dt + 1 ) - l_intm_part_days ;
1634 
1635                                                 l_calculated_intensity := l_calculated_intensity * (l_actual_days / l_app_days ) ;
1636 
1637                                             END IF;
1638                                        END IF;
1639 
1640                                        -- If the program's academic year does not mirror the fte calculation period then
1641                                        --Adjust the fte_intensity as per the Academic calendar for the current year of program
1642                                        c_year_cal_rec := NULL ;
1643                                        l_year_cal_rec := NULL ;
1644 
1645                                        -- get the academic calendar instance corresponding to the current year of program
1646                                        OPEN c_year_cal(c_sca_rec.person_id,c_sca_rec.course_cd, c_crs_year_rec.unit_set_cd,
1647                                                        l_selection_dt_from, l_selection_dt_to) ;
1648 
1649                                        LOOP
1650 
1651                                            FETCH c_year_cal INTO c_year_cal_rec;
1652                                            EXIT WHEN c_year_cal%NOTFOUND;
1653 
1654                                            -- if l_year_cal_rec is null, then we are at the first row in the cursor
1655                                            -- so store c_year_cal_rec in l_year_cal_rec
1656                                            IF l_year_cal_rec.cal_type IS NULL THEN
1657                                                l_year_cal_rec := c_year_cal_rec;
1658                                            END IF;
1659 
1660                                            IF  (c_crs_year_rec.completion_dt IS NOT NULL) AND
1661                                                (c_year_cal_rec.end_dt >= c_crs_year_rec.completion_dt)
1662                                            THEN
1663                                                -- If year of program has been completed then find closest
1664                                                -- calendar instance to the year of program
1665                                                IF  (l_year_cal_rec.end_dt > c_year_cal_rec.end_dt) AND
1666                                                    (c_year_cal_rec.end_dt - c_crs_year_rec.completion_dt >= 0) THEN
1667                                                    l_year_cal_rec := c_year_cal_rec;
1668 
1669                                                END IF;
1670 
1671                                            ELSIF (c_crs_year_rec.end_dt IS NOT NULL) AND
1672                                                  (c_year_cal_rec.end_dt >= c_crs_year_rec.end_dt) THEN
1673                                                -- If year of program has been ended then find closest
1674                                                -- calendar instance to the year of program
1675 
1676                                                IF  (l_year_cal_rec.end_dt > c_year_cal_rec.end_dt) AND
1677                                                    (c_year_cal_rec.end_dt - c_crs_year_rec.end_dt >= 0) THEN
1678                                                    l_year_cal_rec := c_year_cal_rec;
1679 
1680                                                END IF;
1681 
1682 
1683                                            END IF;
1684 
1685 
1686                                        END LOOP;
1687 
1688                                        CLOSE c_year_cal ;
1689 
1690                                        l_fte_prop_flag := FALSE;
1691                                        -- get the fte% contribution by the current academic calendar instance to the fte period
1692                                        OPEN c_fte_prop( l_year_cal_rec.cal_type, l_year_cal_rec.sequence_number ,
1693                                        c_crs_year_rec.acad_perd) ;
1694                                        FETCH c_fte_prop INTO c_fte_prop_rec ;
1695                                        IF c_fte_prop%FOUND THEN
1696                                            l_fte_perc := c_fte_prop_rec.fte_perc ;
1697                                            l_fte_prop_flag := TRUE;
1698                                        ELSE
1699                                            l_fte_perc := 100;
1700                                        END IF;
1701                                        CLOSE c_fte_prop ;
1702 
1703 
1704                                        -- If more than one year of program for student program attempt
1705                                        IF l_multi_yop THEN
1706 
1707                                            IF l_fte_prop_flag AND l_fte_perc < 100 THEN
1708                                               -- This is a normal calendar proportion for year of program so calculate as normal
1709                                                l_calculated_intensity := (l_calculated_intensity * l_fte_perc ) / 100 ;
1710 
1711                                            ELSIF NOT (c_crs_year_rec.selection_dt between p_fte_start_dt and p_fte_end_dt) THEN
1712                                                -- Ignore all year of programs that do not have a selection date within
1713                                                -- the FTE calculation period
1714                                                l_calculated_intensity := 0;
1715                                            END IF;
1716 
1717                                        ELSE
1718                                            -- Only one year of program for the student program attempt that fits
1719                                            -- within the FTE calculation period
1720                                            l_calculated_intensity := (l_calculated_intensity * l_fte_perc ) / 100 ;
1721 
1722                                        END IF;
1723 
1724                                        -- summation of the calculated fte
1725                                        l_calculated_fte := l_calculated_fte + l_calculated_intensity ;
1726 
1727                                   END IF;  -- if fte intensity is found
1728                                END LOOP ; -- for each year of program
1729 
1730                             END IF ;
1731                             -- end of  intensity based calculation
1732 
1733                         END IF ; -- program intermitted for whole fte period
1734 
1735                         -- check if the flag to skip the current program attempt has been set
1736                         -- if it hasn't been set then save the fte calculated for this program attempt
1737                         IF  NOT l_exit_flag THEN
1738                           -- get the current year of program record
1739                           -- if not found then lof an error message and go to the next program attempt record
1740                           OPEN c_year(c_sca_rec.person_id , c_sca_rec.course_cd,
1741                                       l_selection_dt_from, l_selection_dt_to);
1742                           FETCH c_year INTO c_year_rec ;
1743                           IF c_year%FOUND THEN
1744 
1745                             -- if hesa unit set attempt record exists then update it else create a hesa unit set attempt
1746                             -- record corresponding to the oss unit set attempt record
1747                             OPEN c_susa_upd (c_sca_rec.person_id , c_sca_rec.course_cd , c_year_rec.unit_set_cd ,
1748                                     c_year_rec.sequence_number) ;
1749                             FETCH c_susa_upd INTO c_susa_upd_rec ;
1750                             IF c_susa_upd%FOUND THEN
1751                               -- save the calculated FTE in the student hesa unit set attempt record
1752                               igs_he_en_susa_pkg.update_row(
1753                                      X_ROWID                        => c_susa_upd_rec.rowid ,
1754                                      X_HESA_EN_SUSA_ID              => c_susa_upd_rec.hesa_en_susa_id ,
1755                                      X_PERSON_ID                    => c_susa_upd_rec.person_id ,
1756                                      X_COURSE_CD                    => c_susa_upd_rec.course_cd ,
1757                                      X_UNIT_SET_CD                  => c_susa_upd_rec.unit_set_cd ,
1758                                      X_US_VERSION_NUMBER            => c_susa_upd_rec.us_version_number ,
1759                                      X_SEQUENCE_NUMBER              => c_susa_upd_rec.sequence_number ,
1760                                      X_NEW_HE_ENTRANT_CD            => c_susa_upd_rec.new_he_entrant_cd ,
1761                                      X_TERM_TIME_ACCOM              => c_susa_upd_rec.term_time_accom ,
1762                                      X_DISABILITY_ALLOW             => c_susa_upd_rec.disability_allow ,
1763                                      X_ADDITIONAL_SUP_BAND          => c_susa_upd_rec.additional_sup_band ,
1764                                      X_SLDD_DISCRETE_PROV           => c_susa_upd_rec.sldd_discrete_prov,
1765                                      X_STUDY_MODE                   => c_susa_upd_rec.study_mode ,
1766                                      X_STUDY_LOCATION               => c_susa_upd_rec.study_location ,
1767                                      X_FTE_PERC_OVERRIDE            => c_susa_upd_rec.fte_perc_override ,
1768                                      X_FRANCHISING_ACTIVITY         => c_susa_upd_rec.franchising_activity ,
1769                                      X_COMPLETION_STATUS            => c_susa_upd_rec.completion_status,
1770                                      X_GOOD_STAND_MARKER            => c_susa_upd_rec.good_stand_marker ,
1771                                      X_COMPLETE_PYR_STUDY_CD        => c_susa_upd_rec.complete_pyr_study_cd ,
1772                                      X_CREDIT_VALUE_YOP1            => c_susa_upd_rec.credit_value_yop1 ,
1773                                      X_CREDIT_VALUE_YOP2            => c_susa_upd_rec.credit_value_yop2 ,
1774                                      X_CREDIT_VALUE_YOP3            => c_susa_upd_rec.credit_value_yop3 ,
1775                                      X_CREDIT_VALUE_YOP4            => c_susa_upd_rec.credit_value_yop4 ,
1776                                      X_CREDIT_LEVEL_ACHIEVED1       => c_susa_upd_rec.credit_level_achieved1 ,
1777                                      X_CREDIT_LEVEL_ACHIEVED2       => c_susa_upd_rec.credit_level_achieved2 ,
1778                                      X_CREDIT_LEVEL_ACHIEVED3       => c_susa_upd_rec.credit_level_achieved3 ,
1779                                      X_CREDIT_LEVEL_ACHIEVED4       => c_susa_upd_rec.credit_level_achieved4 ,
1780                                      X_CREDIT_PT_ACHIEVED1          => c_susa_upd_rec.credit_pt_achieved1 ,
1781                                      X_CREDIT_PT_ACHIEVED2          => c_susa_upd_rec.credit_pt_achieved2 ,
1782                                      X_CREDIT_PT_ACHIEVED3          => c_susa_upd_rec.credit_pt_achieved3 ,
1783                                      X_CREDIT_PT_ACHIEVED4          => c_susa_upd_rec.credit_pt_achieved4 ,
1784                                      X_CREDIT_LEVEL1                => c_susa_upd_rec.credit_level1 ,
1785                                      X_CREDIT_LEVEL2                => c_susa_upd_rec.credit_level2 ,
1786                                      X_CREDIT_LEVEL3                => c_susa_upd_rec.credit_level3 ,
1787                                      X_CREDIT_LEVEL4                => c_susa_upd_rec.credit_level4 ,
1788                                      X_ADDITIONAL_SUP_COST          => c_susa_upd_rec.additional_sup_cost ,
1789                                      X_ENH_FUND_ELIG_CD             => c_susa_upd_rec.enh_fund_elig_cd ,
1790                                      X_DISADV_UPLIFT_FACTOR         => c_susa_upd_rec.disadv_uplift_factor ,
1791                                      X_YEAR_STU                     => c_susa_upd_rec.year_stu ,
1792                                      X_GRAD_SCH_GRADE               => c_susa_upd_rec.grad_sch_grade ,
1793                                      X_MARK                         => c_susa_upd_rec.mark ,
1794                                      X_TEACHING_INST1               => c_susa_upd_rec.teaching_inst1 ,
1795                                      X_TEACHING_INST2               => c_susa_upd_rec.teaching_inst2 ,
1796                                      X_PRO_NOT_TAUGHT               => c_susa_upd_rec.pro_not_taught ,
1797                                      X_FUNDABILITY_CODE             => c_susa_upd_rec.fundability_code ,
1798                                      X_FEE_ELIGIBILITY              => c_susa_upd_rec.fee_eligibility ,
1799                                      X_FEE_BAND                     => c_susa_upd_rec.fee_band ,
1800                                      X_NON_PAYMENT_REASON           => c_susa_upd_rec.non_payment_reason ,
1801                                      X_STUDENT_FEE                  => c_susa_upd_rec.student_fee ,
1802                                      X_FTE_INTENSITY                => c_susa_upd_rec.fte_intensity ,
1803                                      X_CALCULATED_FTE               => l_calculated_fte ,
1804                                      X_FTE_CALC_TYPE                => c_susa_upd_rec.fte_calc_type ,
1805                                      X_TYPE_OF_YEAR                 => c_susa_upd_rec.type_of_year ,
1806                                      X_MODE                         => 'R'
1807                                      ) ;
1808                             ELSE
1809                                igs_he_en_susa_pkg.insert_row(
1810                                      X_ROWID                        => l_rowid ,
1811                                      X_HESA_EN_SUSA_ID              => l_hesa_en_susa_id ,
1812                                      X_PERSON_ID                    => c_sca_rec.person_id ,
1813                                      X_COURSE_CD                    => c_sca_rec.course_cd ,
1814                                      X_UNIT_SET_CD                  => c_year_rec.unit_set_cd ,
1815                                      X_US_VERSION_NUMBER            => c_year_rec.us_version_number ,
1816                                      X_SEQUENCE_NUMBER              => c_year_rec.sequence_number ,
1817                                      X_NEW_HE_ENTRANT_CD            =>  NULL ,
1818                                      X_TERM_TIME_ACCOM              =>  NULL ,
1819                                      X_DISABILITY_ALLOW             =>  NULL ,
1820                                      X_ADDITIONAL_SUP_BAND          =>  NULL ,
1821                                      X_SLDD_DISCRETE_PROV           =>  NULL ,
1822                                      X_STUDY_MODE                   =>  NULL ,
1823                                      X_STUDY_LOCATION               =>  NULL ,
1824                                      X_FTE_PERC_OVERRIDE            =>  NULL ,
1825                                      X_FRANCHISING_ACTIVITY         =>  NULL ,
1826                                      X_COMPLETION_STATUS            =>  NULL ,
1827                                      X_GOOD_STAND_MARKER            =>  NULL ,
1828                                      X_COMPLETE_PYR_STUDY_CD        =>  NULL ,
1829                                      X_CREDIT_VALUE_YOP1            =>  NULL ,
1830                                      X_CREDIT_VALUE_YOP2            =>  NULL ,
1831                                      X_CREDIT_VALUE_YOP3            =>  NULL ,
1832                                      X_CREDIT_VALUE_YOP4            =>  NULL ,
1833                                      X_CREDIT_LEVEL_ACHIEVED1       =>  NULL ,
1834                                      X_CREDIT_LEVEL_ACHIEVED2       =>  NULL ,
1835                                      X_CREDIT_LEVEL_ACHIEVED3       =>  NULL ,
1836                                      X_CREDIT_LEVEL_ACHIEVED4       =>  NULL ,
1837                                      X_CREDIT_PT_ACHIEVED1          =>  NULL ,
1838                                      X_CREDIT_PT_ACHIEVED2          =>  NULL ,
1839                                      X_CREDIT_PT_ACHIEVED3          =>  NULL ,
1840                                      X_CREDIT_PT_ACHIEVED4          =>  NULL ,
1841                                      X_CREDIT_LEVEL1                =>  NULL ,
1842                                      X_CREDIT_LEVEL2                =>  NULL ,
1843                                      X_CREDIT_LEVEL3                =>  NULL ,
1844                                      X_CREDIT_LEVEL4                =>  NULL ,
1845                                      X_ADDITIONAL_SUP_COST          =>  NULL ,
1846                                      X_ENH_FUND_ELIG_CD             =>  NULL ,
1847                                      X_DISADV_UPLIFT_FACTOR         =>  NULL ,
1848                                      X_YEAR_STU                     =>  NULL ,
1849                                      X_GRAD_SCH_GRADE               =>  NULL ,
1850                                      X_MARK                         =>  NULL ,
1851                                      X_TEACHING_INST1               =>  NULL ,
1852                                      X_TEACHING_INST2               =>  NULL ,
1853                                      X_PRO_NOT_TAUGHT               =>  NULL ,
1854                                      X_FUNDABILITY_CODE             =>  NULL ,
1855                                      X_FEE_ELIGIBILITY              =>  NULL ,
1856                                      X_FEE_BAND                     =>  NULL ,
1857                                      X_NON_PAYMENT_REASON           =>  NULL ,
1858                                      X_STUDENT_FEE                  =>  NULL ,
1859                                      X_FTE_INTENSITY                =>  NULL ,
1860                                      X_CALCULATED_FTE               => l_calculated_fte ,
1861                                      X_FTE_CALC_TYPE                => l_fte_calc_type ,
1862                                      X_TYPE_OF_YEAR                 => NULL ,
1863                                      X_MODE                         => 'R'
1864                                      ) ;
1865                             END IF; -- end of hesa unit set attempt record found
1866                             CLOSE c_susa_upd ;
1867                             FND_MESSAGE.SET_NAME('IGS','IGS_HE_FTE_SUCC');
1868                             -- smaddali moved set token to after set message name for bug 2429893
1869                             FND_MESSAGE.SET_TOKEN('UNIT_SET',c_year_rec.unit_set_cd) ;
1870                             FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET) ;
1871                           ELSE
1872                               FND_MESSAGE.SET_NAME('IGS','IGS_HE_NO_YOP');
1873                               FND_FILE.PUT_LINE(FND_FILE.LOG,FND_MESSAGE.GET) ;
1874                           END IF ; --end of current year of program found
1875                           CLOSE c_year ;
1876 
1877                         END IF; -- end of skip the current program attempt
1878 
1879                 END IF ;  -- End of coo_id, course_cat parameter validations
1880 
1881               END IF ;-- fte needs to be calculated
1882 
1883               -- fetch a row
1884               IF DBMS_SQL.FETCH_ROWS(l_cursor_id) = 0 THEN
1885                 EXIT;
1886               END IF;
1887 
1888           END LOOP ; -- end looping of student program attempts
1889 
1890           DBMS_SQL.CLOSE_CURSOR(l_cursor_id);
1891 
1892       END IF;
1893 
1894     END;
1895 
1896   EXCEPTION
1897     WHEN OTHERS THEN
1898       ROLLBACK;
1899       retcode :=2;
1900       Fnd_File.Put_Line(FND_FILE.LOG,SQLERRM);
1901       FND_MESSAGE.Set_Name('IGS','IGS_GE_UNHANDLED_EXP');
1902       FND_MESSAGE.Set_Token('NAME','igs_he_fte_calc_pkg.fte_calculation');
1903       Errbuf := FND_MESSAGE.GET;
1904       IGS_GE_MSG_STACK.CONC_EXCEPTION_HNDL;
1905 
1906   END fte_calculation ;
1907 
1908 END igs_he_fte_calc_pkg;