DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_EN_PRC_LOAD

Source


1 PACKAGE BODY Igs_En_Prc_Load AS
2 /* $Header: IGSEN18B.pls 120.16 2006/02/24 00:45:42 ckasu ship $ */
3 
4 
5 /**************************************************************************************
6  Who           When           What
7  knaraset      04-Nov-2003    Added two functions enrp_get_inst_attendance enrp_get_inst_cp as part
8                               of build EN212, bug 3198180
9  sarakshi      27-Jun-2003    Enh#2930935, added parameter uoo_id to teh function ENRP_CLC_SUA_LOAD
10                               also modified the call to include the uoo_id
11  kkillams      09-MAY-2002    procedure enrp_clc_cp_upto_tp_start_dt to calculate
12                               the total credit points with in a given load calendar
13                               w.r.t. bug 2352142
14  jbegum        21 Mar 02      As part of bug fix 2192616 added
15                               pragma exception_init(NO_AUSL_RECORD_FOUND , -20010);
16                               to the user defined exception NO_AUSL_RECORD_FOUND
17                               in order to catch the exception in the form IGSPS047.
18                               The function that got modified is ENRP_GET_LOAD_INCUR.
19  Modified by:Prajeesh
20  Modified Date:7-JAN-2002
21  Purpose      : Modified as part of career impact on attendance type dld
22                 created 2 new functions one to calculate key programs
23                 and other to get institution level attendance type
24                 for both career centric and program centric model. Also
25                 Modified 2 functions to add 2 parameters key_course_cd and
26                 key_version_number
27 msrinivi      28 Oct 2002       Added 1 new function enrp_get_prg_att_type
28                                 and 1 new procedure get_latest_load_for_acad_cal
29 amuthu     15-NOV-2002          Modified as per the SS Worksheet Redesign TD
30 pradhakr   15-Jan-2003    Added one more parameter no_assessment_ind to the
31                           procedure ENRP_CLC_SUA_EFTSU and ENRP_GET_LOAD_INCUR.
32                           Changes wrt ENCR026. Bug# 2743459
33 myoganat      23-MAY-2003       Removed reference to profile
34                                                         IGS_EN_INCL_AUDIT_CP in procedures
35                                                         ENRP_GET_LOAD_INCUR and ENRP_CLC_SUA_EFTSU
36                                                         as part of the ENCR032 Build - Bug #2855870
37 vkarthik                22-Jul-2004             ENRP_CLC_SUA_LOAD changed for Build EN308 Billable credit points #3782329
38                                                         All calls to ENRP_CLC_SUA_LOAD modified to take up three dummy arguments
39 vijrajag       07-Jul-05      Added Function get_term_credits
40 sgurusam   07-Jul-2005    Modified enrp_get_load_incur
41 rvangala   13-Sep-2005    Modified enrp_get_inst_latt for EN 321 build 	#4606948
42 stutta     23-Feb-2006    Modified c_sua_cir in enrp_clc_eftsu_total for perf bug #5048405
43 ckasu      24-Feb-2006    Modified cur_stud_ua_acad curson in enrp_clc_cp_upto_tp_start_dt
44                           for perf bug #5059308
45 ********************************************************************************************/
46 
47   g_wlst_prfl CONSTANT VARCHAR2(240) := FND_PROFILE.VALUE('IGS_EN_VAL_WLST');
48 
49   -- To calculate the EFTSU total for a UNIT attempt across all load cals
50   FUNCTION ENRP_CLC_SUA_EFTSUT(
51   P_PERSON_ID               IN NUMBER ,
52   P_COURSE_CD               IN VARCHAR2 ,
53   P_CRV_VERSION_NUMBER      IN NUMBER ,
54   P_UNIT_CD                 IN VARCHAR2 ,
55   P_UNIT_VERSION_NUMBER     IN NUMBER ,
56   P_TEACH_CAL_TYPE          IN VARCHAR2 ,
57   P_TEACH_SEQUENCE_NUMBER   IN NUMBER ,
58   p_uoo_id                  IN NUMBER ,
59   p_override_enrolled_cp    IN NUMBER ,
60   p_override_eftsu          IN NUMBER ,
61   p_sca_cp_total            IN NUMBER ,
62   p_original_eftsu          OUT NOCOPY NUMBER )
63   RETURN NUMBER  AS
64   -------------------------------------------------------------------------------------------
65   -- enrp_clc_sua_eftsut
66   -- Calculate the total EFTSU figure for a student UNIT attempt,
67   --  disregarding any
68   -- splits or truncation. This will return a 'nominal' figure for the
69   -- purposes of
70   -- displaying on forms.
71   -- note: p_sca_cp_total - this is an optional parameter (ie. May be null) - is
72   -- included
73   -- as a parameter to avoid recalculating the credit points passed figure in the
74   -- situation
75   -- where the logic is calc'ing EFTSU for all of a students unit attempts. If it
76   -- is not
77   -- specified the routine will be called to derive it.
78   -- p_override_eftsu - if specified, this is passed to the enrp_clc_sua_load and
79   -- is used
80   -- as the basis for the eftsu calculation. The figure is still split across
81   -- load calendars
82   -- and truncated according to the standard logic.
83   --Change History:
84   --Who         When            What
85   --kkillams    28-04-2003      Modified c_sua cursor due to change in pk of the student unit attempt
86   --                            w.r.t. bug number 2829262
87   -------------------------------------------------------------------------------------------
88   BEGIN
89   DECLARE
90     v_load_eftsu        NUMBER(6,3);
91     v_eftsu_total       NUMBER(6,3);
92     v_original_eftsu_total  NUMBER(6,3);
93     v_credit_points     NUMBER(6,3);
94     cst_academic        CONSTANT    VARCHAR2(10) := 'ACADEMIC';
95     cst_active          CONSTANT    VARCHAR2(7) := 'ACTIVE';
96     cst_load            CONSTANT    VARCHAR2(5) := 'LOAD';
97 
98     CURSOR  c_sua IS
99         SELECT  sua.discontinued_dt,
100                 sua.administrative_unit_status,
101                 sua.unit_attempt_status,
102                 sua.no_assessment_ind
103         FROM    IGS_EN_SU_ATTEMPT sua
104         WHERE   sua.person_id   = p_person_id   AND
105                 sua.course_cd   = p_course_cd   AND
106                 sua.uoo_id      = p_uoo_id;
107     v_sua_rec   c_sua%ROWTYPE;
108 
109     CURSOR  c_cir   (cp_discontinued_dt             IGS_EN_SU_ATTEMPT.discontinued_dt%TYPE,
110                      cp_administrative_unit_status  IGS_EN_SU_ATTEMPT.administrative_unit_status%TYPE,
111                      cp_unit_attempt_status         IGS_EN_SU_ATTEMPT.unit_attempt_status%TYPE,
112                      cp_no_assessment_ind           IGS_EN_SU_ATTEMPT.no_assessment_ind%TYPE) IS
113         SELECT  lci.cal_type,
114                 lci.sequence_number
115         FROM    IGS_CA_INST_REL acir,
116                 IGS_CA_INST         aci,
117                 IGS_CA_TYPE         acat,
118                 IGS_CA_STAT         acs,
119                 IGS_CA_INST_REL     lcir,
120                 IGS_CA_INST         lci,
121                 IGS_CA_TYPE         lcat,
122                 IGS_CA_STAT         lcs
123         WHERE   acir.sub_cal_type       = p_teach_cal_type AND
124                 acir.sub_ci_sequence_number = p_teach_sequence_number AND
125                 aci.cal_type            = acir.sup_cal_type AND
126                 aci.sequence_number     = acir.sup_ci_sequence_number AND
127                 acat.cal_type           = aci.cal_type AND
128                 acat.s_cal_cat          = cst_academic AND
129                 acs.cal_status          = aci.cal_status AND
130                 acs.s_cal_status        = cst_active AND
131                 lcir.sup_cal_type       = aci.cal_type AND
132                 lcir.sup_ci_sequence_number = aci.sequence_number AND
133                 lci.cal_type            = lcir.sub_cal_type AND
134                 lci.sequence_number     = lcir.sub_ci_sequence_number AND
135                 lcat.cal_type           = lci.cal_type AND
136                 lcat.s_cal_cat          = cst_load AND
137                 lcs.cal_status          = lci.cal_status AND
138                 lcs.s_cal_status        = cst_active AND
139                 ENRP_GET_LOAD_INCUR(
140                             p_teach_cal_type,
141                             p_teach_sequence_number,
142                             cp_discontinued_dt,
143                             cp_administrative_unit_status,
144                             cp_unit_attempt_status,
145                             cp_no_assessment_ind,
146                             lci.cal_type,
147                             lci.sequence_number,
148                             -- anilk, Audit special fee build
149                             NULL, -- for p_uoo_id
150                             'N'
151                             ) = 'Y';
152   BEGIN
153     v_eftsu_total := 0.000;
154     v_original_eftsu_total := 0.000;
155     OPEN c_sua;
156     FETCH c_sua INTO v_sua_rec;
157     IF c_sua%NOTFOUND THEN
158         CLOSE c_sua;
159         RETURN 0.000;
160     END IF;
161     CLOSE c_sua;
162     FOR v_cir_rec IN c_cir  (v_sua_rec.discontinued_dt,
163                              v_sua_rec.administrative_unit_status,
164                              v_sua_rec.unit_attempt_status,
165                              v_sua_rec.no_assessment_ind) LOOP
166         v_load_eftsu := enrp_clc_sua_eftsu(
167                                 p_person_id,
168                                 p_course_cd,
169                                 p_crv_version_number,
170                                 p_unit_cd,
171                                 p_unit_version_number,
172                                 p_teach_cal_type,
173                                 p_teach_sequence_number,
174                                 p_uoo_id,
175                                 v_cir_rec.cal_type,
176                                 v_cir_rec.sequence_number,
177                                 p_override_enrolled_cp,
178                                 p_override_eftsu,
179                                 'Y',
180                                 NULL,
181                                 NULL,
182                                 NULL,
183                                 v_credit_points,
184                                 -- anilk, Audit special fee build
185                                 'N');
186         v_eftsu_total := v_eftsu_total + v_load_eftsu;
187 
188         IF p_override_eftsu IS NOT NULL THEN
189             v_load_eftsu := enrp_clc_sua_eftsu(
190                                     p_person_id,
191                                     p_course_cd,
192                                     p_crv_version_number,
193                                     p_unit_cd,
194                                     p_unit_version_number,
195                                     p_teach_cal_type,
196                                     p_teach_sequence_number,
197                                     p_uoo_id,
198                                     v_cir_rec.cal_type,
199                                     v_cir_rec.sequence_number,
200                                     p_override_enrolled_cp,
201                                     NULL,
202                                     'Y',
203                                     NULL,
204                                     NULL,
205                                     NULL,
206                                     v_credit_points,
207                                     -- anilk, Audit special fee build
208                                     'N');
209             v_original_eftsu_total := v_original_eftsu_total + v_load_eftsu;
210         END IF;
211     END LOOP;
212     p_original_eftsu := v_original_eftsu_total;
213     RETURN v_eftsu_total;
214   EXCEPTION
215     WHEN OTHERS THEN
216         IF (c_cir%ISOPEN) THEN
217             CLOSE c_cir;
218         END IF;
219         IF (c_sua%ISOPEN) THEN
220             CLOSE c_sua;
221         END IF;
222                 RETURN v_eftsu_total;
223         -- RAISE;
224 
225   END;
226   END enrp_clc_sua_eftsut;
227   --
228   -- To calc the total EFTSU figure for a SCA within a load cal instance
229   -- Modified by Prajeesh to add 2 parameters key_coursecd and keyversion number
230   -- as part of the dld career impact attendance type ccr
231   FUNCTION enrp_clc_eftsu_total(
232   p_person_id             IN NUMBER ,
233   p_course_cd             IN VARCHAR2 ,
234   p_acad_cal_type         IN VARCHAR2 ,
235   p_acad_sequence_number  IN NUMBER ,
236   p_load_cal_type         IN VARCHAR2 ,
237   p_load_sequence_number  IN NUMBER ,
238   p_truncate_ind          IN VARCHAR2 ,
239   p_include_research_ind  IN VARCHAR2 ,
240   p_key_course_cd         IN igs_en_su_attempt.course_cd%TYPE,
241   p_key_version_number    IN igs_en_su_attempt.version_number%TYPE,
242   p_credit_points         OUT NOCOPY NUMBER )
243   RETURN NUMBER  AS
244   BEGIN
245   DECLARE
246     cst_enrolled    CONSTANT    VARCHAR2(10) := 'ENROLLED';
247     cst_discontin   CONSTANT    VARCHAR2(10) := 'DISCONTIN';
248     cst_completed   CONSTANT    VARCHAR2(10) := 'COMPLETED';
249     cst_waitlisted  CONSTANT VARCHAR2(10)        := 'WAITLISTED';
250 
251     v_version_number        IGS_EN_STDNT_PS_ATT.version_number%TYPE;
252     v_sca_total_cp          NUMBER;
253     v_eftsu_total           NUMBER;
254     v_cp_total              NUMBER;
255     v_sua_cp                NUMBER;
256     v_census_dt             IGS_CA_DA_INST.absolute_val%TYPE;
257     v_sca_total_calculated  BOOLEAN;
258 
259     CURSOR c_sca IS
260         SELECT  sca.version_number
261         FROM    IGS_EN_STDNT_PS_ATT sca
262         WHERE   sca.person_id = p_person_id AND
263             sca.course_cd = p_course_cd;
264     CURSOR c_load_to_teach IS
265 	SELECT teach_cal_type, teach_ci_sequence_number
266 	FROM igs_ca_load_to_teach_v
267 	WHERE load_cal_type = p_load_cal_type
268 	AND load_ci_sequence_number = p_load_sequence_number;
269 
270     CURSOR c_sua_cir(cp_cal_type igs_ca_inst.cal_type%TYPE, cp_seq_num igs_ca_inst.sequence_number%TYPE) IS
271         SELECT  sua.unit_cd,
272             sua.version_number,
273             sua.cal_type,
274             sua.ci_sequence_number,
275             sua.override_enrolled_cp,
276             sua.override_eftsu,
277             sua.administrative_unit_status,
278             sua.unit_attempt_status,
279             sua.discontinued_dt,
280             sua.uoo_id,
281             sua.no_assessment_ind
282         FROM    IGS_EN_SU_ATTEMPT       sua,
283                 IGS_CA_INST_REL cir,
284                 IGS_PS_UNIT_VER         uv
285         WHERE   sua.person_id           = p_person_id AND
286                 sua.course_cd           = p_course_cd AND
287                 sua.unit_attempt_status     IN  (cst_enrolled,
288                                                  cst_discontin,
289                                                  cst_completed,
290                                                  cst_waitlisted) AND
291                 uv.unit_cd          = sua.unit_cd AND
292                 uv.version_number       = sua.version_number AND
293                 (p_include_research_ind     = 'Y' OR
294                 uv.research_unit_ind        = 'N') AND
295                 cir.sup_cal_type        = p_acad_cal_type AND
296                 cir.sup_ci_sequence_number  = p_acad_sequence_number AND
297                 cir.sub_cal_type        = sua.cal_type AND
298                 cir.sub_ci_sequence_number  = sua.ci_sequence_number AND
299                 sua.cal_type = cp_cal_type AND
300                 sua.ci_sequence_number = cp_seq_num;
301 
302 
303     CURSOR c_sgcc_dai (
304             cp_cal_type     IGS_EN_SU_ATTEMPT.cal_type%TYPE,
305             cp_ci_sequence_number   IGS_EN_SU_ATTEMPT.ci_sequence_number%TYPE) IS
306         SELECT  NVL(    dai.absolute_val,
307                 IGS_CA_GEN_001.CALP_GET_ALIAS_VAL (
308                             dai.dt_alias,
309                             dai.sequence_number,
310                             dai.cal_type,
311                             dai.ci_sequence_number)) AS census_dt
312         FROM    IGS_GE_S_GEN_CAL_CON            sgcc,
313                 IGS_CA_DA_INST      dai
314         WHERE   sgcc.s_control_num      = 1 AND
315                 dai.cal_type            = cp_cal_type AND
316                 dai.ci_sequence_number      = cp_ci_sequence_number AND
317                 dai.dt_alias            = sgcc.census_dt_alias
318         ORDER BY 1 ASC;         -- use earliest date value
319   BEGIN
320     -- Calculate the EFTSU total for a student course attempt within a
321     -- nominated load calendar instance.
322     -- Note: p_truncate_ind indicates whether the EFTSU figures should be
323     --   truncated in accordance with the DEETYA reporting guidelines.
324     -- Note: p_credit_points is used to return the total credit point
325     --   value from which the EFTSU was calculated.
326     -- Note: p_include_research_ind is used to eliminate research units
327     --   from  the total, creating a total of 'coursework' units -
328     --   a measure which is used within the research sub-system.
329     ----------
330     -- 1. Load student course attempt details.
331     OPEN    c_sca;
332     FETCH   c_sca   INTO    v_version_number;
333     IF (c_sca%NOTFOUND) THEN
334         CLOSE   c_sca;
335         p_credit_points := 0;
336         RETURN 0.000;
337     END IF;
338     CLOSE   c_sca;
339 
340 
341     -- 3. Loop through all unit attempt that are child records of the academic
342     -- calendar instance.
343     v_eftsu_total := 0.000;
344     v_cp_total := 0;
345 
346     FOR rec_cal IN c_load_to_teach LOOP
347 	OPEN c_sgcc_dai (
348 			    rec_cal.teach_cal_type,
349 			    rec_cal.teach_ci_sequence_number);
350 	FETCH c_sgcc_dai INTO v_census_dt;
351 	IF c_sgcc_dai%NOTFOUND THEN
352 	    CLOSE c_sgcc_dai;
353 	    v_census_dt := TRUNC(SYSDATE);
354 	ELSE
355 	    CLOSE c_sgcc_dai;
356 	END IF;
357 	v_sca_total_calculated := FALSE;
358 
359 
360 
361 	    FOR v_sua_cir_rec IN c_sua_cir(rec_cal.teach_cal_type,rec_cal.teach_ci_sequence_number) LOOP
362 	    -- As part of the bug# 1956374 changed to the below call from IGS_EN_GEN_005.ENRP_GET_LOAD_INCUR
363 		IF ENRP_GET_LOAD_INCUR(
364 				v_sua_cir_rec.cal_type,
365 				v_sua_cir_rec.ci_sequence_number,
366 				v_sua_cir_rec.discontinued_dt,
367 				v_sua_cir_rec.administrative_unit_status ,
368 				v_sua_cir_rec.unit_attempt_status,
369 				v_sua_cir_rec.no_assessment_ind,
370 				p_load_cal_type,
371 				p_load_sequence_number,
372 				v_sua_cir_rec.uoo_id,
373 				-- anilk, Audit special fee build
374 				'N') = 'Y' THEN
375 
376 			-- Call routine to calculate the total credit points passed in the students
377 			-- course attempt. This is used by a child routine.
378 			IF NOT v_sca_total_calculated  THEN
379 				v_sca_total_cp := Igs_En_Gen_001.ENRP_CLC_SCA_PASS_CP(
380 						p_person_id,
381 						p_course_cd,
382 						v_census_dt);
383 				v_sca_total_calculated := TRUE;
384 			END IF;
385 		    -- 3.1 Call the routine to calculate the EFTSU figure for the selected
386 		    -- student unit attempt within the nominated load calendar instance.
387 				-- Passed 2 parameters key_course_cd and key_version_number as
388 				-- part of the dld for career impact on attendance type ccr
389 		    v_eftsu_total := v_eftsu_total +
390 			    enrp_clc_sua_eftsu(
391 					p_person_id,
392 					p_course_cd,
393 					v_version_number, -- from c_sca
394 					v_sua_cir_rec.unit_cd,
395 					v_sua_cir_rec.version_number,
396 					v_sua_cir_rec.cal_type,
397 					v_sua_cir_rec.ci_sequence_number,
398 					v_sua_cir_rec.uoo_id,
399 					p_load_cal_type,
400 					p_load_sequence_number,
401 					v_sua_cir_rec.override_enrolled_cp,
402 					v_sua_cir_rec.override_eftsu,
403 					p_truncate_ind,
404 					v_sca_total_cp,
405 					p_key_course_cd ,
406 					p_key_version_number,
407 					v_sua_cp ,
408 					-- anilk, Audit special fee build
409 					'N');
410 		    v_cp_total := v_cp_total + v_sua_cp;
411 		END IF;
412 	    END LOOP;
413      END LOOP;
414     p_credit_points := v_cp_total;
415     RETURN v_eftsu_total;
416   EXCEPTION
417     WHEN OTHERS THEN
418         IF c_sca%ISOPEN THEN
419             CLOSE c_sca;
420         END IF;
421         IF c_sua_cir%ISOPEN THEN
422             CLOSE c_sua_cir;
423         END IF;
424         IF c_sgcc_dai%ISOPEN THEN
425             CLOSE c_sgcc_dai;
426         END IF;
427         RAISE;
428   END;
429   END enrp_clc_eftsu_total;
430 
431   FUNCTION enrp_clc_sua_eftsu(
432   p_person_id             IN NUMBER ,
433   p_course_cd             IN VARCHAR2 ,
434   p_crv_version_number    IN NUMBER ,
435   p_unit_cd               IN VARCHAR2 ,
436   p_unit_version_number   IN NUMBER ,
437   p_teach_cal_type        IN VARCHAR2 ,
438   p_teach_sequence_number IN NUMBER ,
439   p_uoo_id                IN NUMBER ,
440   p_load_cal_type         IN VARCHAR2 ,
441   p_load_sequence_number  IN NUMBER ,
442   p_override_enrolled_cp  IN NUMBER ,
443   p_override_eftsu        IN NUMBER ,
444   p_truncate_ind          IN VARCHAR2 ,
445   p_sca_cp_total          IN NUMBER ,
446   p_key_course_cd         IN igs_en_su_attempt.course_cd%TYPE,
447   p_key_version_number    IN igs_en_su_attempt.version_number%TYPE,
448   p_credit_points         OUT NOCOPY NUMBER ,
449   -- anilk, Audit special fee build
450   p_include_audit         IN VARCHAR2)
451   -------------------------------------------------------------------------------------------
452   -- enrp_clc_sua_eftsu
453   -- This module calculates the EFTSU value of a
454   -- student unit attempt within a load calendar
455   -- instance (this routine also returns the credit
456   -- point figure on which the EFTSU was based - this
457   -- avoids having to call two routines to get the same
458   -- values)
459   -- Note : p_sca_cp_total is an optional parameter (may
460   --    be NULL) - is included as a parameter to avoid
461   --    recalculating the credit points passed figure in the
462   --    situation where the logic is calculating EFTSU for
463   --    all students IGS_PS_UNIT attempts.  If it is not specified,
464   --    the routine will be called to derive it.
465   -- Note : p_load_cal_type - this is a mandatory parameter
466   --    to EFTSU (as apposed to CP's calculations where it
467   --    was optional), due to the nature of the EFTSU truncation
468   --    logic.
469   -- Note : p_truncate_ind - this indicates whether the figure
470   --    should be truncated according to the DEETYA guidelines.
471   --Who         When            What
472   --kkillams    28-04-2003      Modified c_uooid cursor due to change in pk of the student unit attempt
473   --                            w.r.t. bug number 2829262
474   --myoganat    23-MAY-2003     Removed reference to profile
475   --                            IGS_EN_INCL_AUDIT_CP
476   --                            as part of Bug #2855870
477   -------------------------------------------------------------------------------------------
478   RETURN NUMBER  AS
479   BEGIN
480   DECLARE
481     v_research_unit_ind VARCHAR2(1);
482     l_include_as_audit  VARCHAR2(1);
483     v_annual_load       NUMBER;
484     v_sua_cp            NUMBER;
485     v_sua_eftsu         NUMBER;
486     v_trunc_eftsu       NUMBER;
487     v_return_eftsu      NUMBER;
488     v_uoo_id            IGS_PS_UNIT_OFR_OPT.uoo_id%TYPE;
489     l_no_assessment_ind igs_en_su_attempt.no_assessment_ind%TYPE;
490     --dummy variable to pick up audit, billing, enrolled credit points
491     --due to signature change by EN308 Billing credit hours
492     l_audit_cp          IGS_PS_USEC_CPS.billing_credit_points%TYPE;
493     l_billing_cp        IGS_PS_USEC_CPS.billing_hrs%TYPE;
494     l_enrolled_cp       IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
495 
496     CURSOR  c_uooid IS
497         SELECT  sua.uoo_id,
498                 NVL(sua.no_assessment_ind,'N')
499         FROM    IGS_EN_SU_ATTEMPT sua
500         WHERE   sua.person_id       = p_person_id AND
501                 sua.course_cd       = p_course_cd AND
502                 sua.uoo_id          = p_uoo_id;
503 
504     CURSOR c_uv IS
505         SELECT  uv.research_unit_ind
506         FROM    IGS_PS_UNIT_VER uv
507         WHERE   uv.unit_cd          = p_unit_cd AND
508                 uv.version_number   = p_unit_version_number;
509 
510   BEGIN
511 
512     -- Get the no_assessement_ind value
513     OPEN c_uooid;
514     FETCH c_uooid INTO v_uoo_id, l_no_assessment_ind ;
515     CLOSE c_uooid;
516 
517     -- Check whether the passed in Unit Attempt is a Audit Unit
518     -- If so, return '0' for EFTSU and credit points else use the existing logic to get the EFTSU
519     -- and credit points of the unit attempt.
520     IF p_override_enrolled_cp = 0 OR p_override_eftsu = 0  OR
521     (p_override_enrolled_cp IS NULL AND p_override_eftsu IS NULL) THEN
522 
523     IF l_no_assessment_ind = 'Y' THEN
524       IF  p_include_audit = 'N' THEN
525         p_credit_points := 0;
526         RETURN 0;
527       ELSE
528         l_include_as_audit := 'Y';
529       END IF;
530     ELSE
531       l_include_as_audit := 'N';
532     END IF;
533     ELSE
534       l_include_as_audit := 'N';
535     END IF;
536 
537 
538     -- determine wheter the unit version is a 'research unit'.
539     -- If so, an alternate path is used to calculate the EFTSU figure.
540     OPEN c_uv;
541     FETCH c_uv INTO v_research_unit_ind;
542     IF c_uv%NOTFOUND THEN
543         CLOSE c_uv;
544         RETURN 0;
545     END IF;
546     CLOSE c_uv;
547 
548     IF v_research_unit_ind = 'Y' THEN
549         v_trunc_eftsu := IGS_RE_GEN_001.RESP_CLC_SUA_EFTSU(
550                     p_person_id,
551                     p_course_cd,
552                     p_unit_cd,
553                     p_teach_cal_type,
554                     p_teach_sequence_number,
555                     p_load_cal_type,
556                     p_load_sequence_number,
557                     p_truncate_ind,
558                     p_uoo_id);
559         p_credit_points := 0;
560     END IF;
561 
562     IF v_research_unit_ind = 'N' OR v_trunc_eftsu IS NULL THEN
563         -- determine the annual load figure of the student course
564         -- attempt for the particular unit attempt being studied
565            --Modified by Prajeesh as part of career impact on attendance type dld
566                -- First check if key_coursecd and version number exists then
567                -- pass that as coursecd parameters for annual load procedure
568                -- implies keyprogram is used to calculate the annual load that is
569                -- it is career centric model as do asusual
570 
571           IF p_key_course_cd IS NOT NULL AND p_key_version_number IS NOT NULL THEN
572 
573                v_annual_load := enrp_get_ann_load(
574                     p_person_id,
575                     p_key_course_cd,
576                     p_key_version_number,
577                     NULL,
578                     NULL,
579                     NULL,
580                     NULL,
581                     p_sca_cp_total);
582 
583           ELSE
584 
585             v_annual_load := enrp_get_ann_load(
586                     p_person_id,
587                     p_course_cd,
588                     p_crv_version_number,
589                     p_unit_cd,
590                     p_unit_version_number,
591                     p_teach_cal_type,
592                     p_teach_sequence_number,
593                     p_sca_cp_total);
594 
595           END IF;
596         -- check the value of v_annual_load and
597         -- return 0 if it has a value of 0
598         IF (v_annual_load = 0) THEN
599             p_credit_points := 0;
600             RETURN 0;
601         END IF;
602 
603         -- call routine to calcualte the credit point figure
604         -- for the student unit attmpt
605             v_sua_cp := enrp_clc_sua_load(
606                                             p_unit_cd,
607                                             p_unit_version_number,
608                                             p_teach_cal_type,
609                                             p_teach_sequence_number,
610                                             p_load_cal_type,
611                                             p_load_sequence_number,
612                                             p_override_enrolled_cp,
613                                             p_override_eftsu,
614                                             v_return_eftsu,
615                                             p_uoo_id,
616                                             -- anilk, Audit special fee build
617                                             l_include_as_audit,
618                                             l_audit_cp,
619                                             l_billing_cp,
620                                             l_enrolled_cp
621                                             );
622 
623         -- check the value of v_sua_cp and
624         -- return 0 if it has a value of 0
625         IF (v_sua_cp = 0.000) THEN
626             p_credit_points := 0;
627             RETURN 0;
628         END IF;
629 
630         IF (p_override_eftsu IS NOT NULL AND v_return_eftsu IS NOT NULL) THEN
631             v_sua_eftsu := v_return_eftsu;
632         ELSE
633             -- calculate the base EFTSU figure
634             v_sua_eftsu := v_sua_cp / v_annual_load;
635         END IF;
636 
637         IF (p_truncate_ind = 'Y') THEN
638             IF p_uoo_id IS NOT NULL THEN
639                 v_uoo_id := p_uoo_id;
640             END IF;
641             -- call the routine to handle the rounding/truncation
642             -- of the EFTSU figure
643             v_trunc_eftsu := enrp_clc_eftsu_trunc(
644                         p_unit_cd,
645                         p_unit_version_number,
646                         v_uoo_id,
647                         v_sua_eftsu);
648         ELSE
649             v_trunc_eftsu := v_sua_eftsu;
650         END IF;
651 
652         -- set the out NOCOPY paramter to the credit point figure used
653         -- to calculate the EFTSU amount
654         p_credit_points := v_sua_cp;
655     END IF;
656     -- return the EFTSU figure
657     RETURN v_trunc_eftsu;
658 
659 
660 
661   EXCEPTION
662     WHEN OTHERS THEN
663         IF c_uv%ISOPEN THEN
664             CLOSE c_uv;
665         END IF;
666         IF c_uooid%ISOPEN THEN
667             CLOSE c_uooid;
668         END IF;
669         RAISE;
670   END;
671   END enrp_clc_sua_eftsu;
672   --
673   -- To calculate the WEFTSU for a student unit attempt
674   FUNCTION ENRP_CLC_SUA_WEFTSU(
675   p_unit_cd IN VARCHAR2 ,
676   p_version_number IN NUMBER ,
677   p_discipline_group_cd IN VARCHAR2 ,
678   p_org_unit_cd IN VARCHAR2 ,
679   p_sua_eftsu IN NUMBER ,
680   p_local_ins_deakin_ind IN VARCHAR2 )
681   RETURN NUMBER  AS
682 
683   BEGIN
684   DECLARE
685     v_funding_index_1       IGS_PS_DSCP.funding_index_1%TYPE;
686     v_funding_index_2       IGS_PS_DSCP.funding_index_2%TYPE;
687     v_weftsu_factor         IGS_PS_UNIT_INT_LVL.weftsu_factor%TYPE;
688     v_unit_level            IGS_PS_UNIT_VER.unit_level%TYPE;
689     v_unit_int_course_level_cd  IGS_PS_UNIT_VER.unit_int_course_level_cd%TYPE;
690     v_count             NUMBER;
691     v_sua_weftsu            NUMBER;
692     v_local_ins_deakin_ind      VARCHAR2(1);
693     CURSOR c_di IS
694         SELECT  di.funding_index_1,
695             di.funding_index_2
696         FROM    IGS_PS_DSCP di
697         WHERE   di.discipline_group_cd = p_discipline_group_cd;
698     CURSOR c_uv_uicl IS
699         SELECT  uicl.weftsu_factor,
700             uv.unit_level,
701             uv.unit_int_course_level_cd
702         FROM    IGS_PS_UNIT_VER     uv,
703             IGS_PS_UNIT_INT_LVL uicl
704         WHERE   uv.unit_cd          = p_unit_cd AND
705             uv.version_number       = p_version_number AND
706             uicl.unit_int_course_level_cd   = uv.unit_int_course_level_cd;
707     CURSOR c_ins IS
708         SELECT  COUNT(*)
709         FROM    IGS_OR_INSTITUTION  ins
710         WHERE   ins.govt_institution_cd = 3030 AND
711             local_institution_ind   = 'Y';
712   BEGIN
713     -- Routine calculates the WEFTSU figure for a Student unit Attempt.
714     -- This routine requires the IGS_PS_DSCP group code and org unit code as
715     -- parameters,  so where units are split across multiples the calling
716     -- routine must call this function multiple times and sum the results.
717     -- Special Logic:
718     -- Deakin University has two special scenarios which involve using the second
719     -- funding index for particular matches on IGS_PS_DSCP group code, org unit,
720     -- unit internal course level and unit level. These senarios have been coded,
721     -- but surrounded by a check as to whether the local INSTITUTION (in which
722     -- the system is running) is Deakin - all other institutions will revert to
723     -- the standard check.
724     IF (p_sua_eftsu = 0.000) THEN
725         RETURN 0.000;
726     END IF;
727     -- Load the funding indexes from the IGS_PS_DSCP table.
728     OPEN    c_di;
729     FETCH   c_di    INTO    v_funding_index_1,
730                 v_funding_index_2;
731     IF (c_di%NOTFOUND) THEN
732         CLOSE   c_di;
733         RETURN 0.000;
734     END IF;
735     CLOSE   c_di;
736     -- Load the weftsu factor, unit level and IGS_PS_UNIT_INT_LVL from
737     -- their respective tables.
738     OPEN    c_uv_uicl;
739     FETCH   c_uv_uicl   INTO    v_weftsu_factor,
740                     v_unit_level,
741                     v_unit_int_course_level_cd;
742     IF (c_uv_uicl%NOTFOUND) THEN
743         CLOSE   c_uv_uicl;
744         RETURN 0.000;
745     END IF;
746     CLOSE   c_uv_uicl;
747     -- Load the INSTITUTION code and the 'local' indicator from the IGS_OR_INSTITUTION
748     -- table.
749     IF (p_local_ins_deakin_ind IS NOT NULL) THEN
750         v_local_ins_deakin_ind := p_local_ins_deakin_ind;
751     ELSE
752         OPEN    c_ins;
753         FETCH   c_ins   INTO    v_count;
754         CLOSE   c_ins;
755         IF (v_count > 0) THEN
756             -- records found
757             -- Deakin is the local INSTITUTION
758             v_local_ins_deakin_ind := 'Y';
759         ELSE
760             v_local_ins_deakin_ind := 'N';
761         END IF;
762     END IF;
763     IF (v_local_ins_deakin_ind = 'Y') THEN -- if records found
764         -- The institution is local and Deakin University,
765         -- so apply the 'special case' scenarios.
766         IF (p_discipline_group_cd = '201' AND
767                 p_org_unit_cd = '03' AND
768                 v_unit_int_course_level_cd <> '1') THEN
769             v_sua_weftsu := p_sua_eftsu *
770                     v_funding_index_2 *
771                     v_weftsu_factor;
772         ELSIF (p_discipline_group_cd = '503' AND
773                 p_org_unit_cd = '0504' AND
774                 v_unit_level IN ('3', '4', '8', '9')) THEN
775             v_sua_weftsu := p_sua_eftsu *
776                     v_funding_index_2 *
777                     v_weftsu_factor;
778         ELSE
779             v_sua_weftsu := p_sua_eftsu *
780                     v_funding_index_1 *
781                     v_weftsu_factor;
782         END IF;
783     ELSE
784         -- The institution is not Deakin University;
785         -- apply the standard calculation.
786         v_sua_weftsu := p_sua_eftsu *
787                 v_funding_index_1 *
788                 v_weftsu_factor;
789     END IF;
790     RETURN NVL(v_sua_weftsu,0.000);
791   END;
792   EXCEPTION
793     WHEN OTHERS THEN
794          IF SQLCODE <>-20001 THEN
795         Fnd_Message.Set_name('IGS','IGS_GE_UNHANDLED_EXP');
796         FND_MESSAGE.SET_TOKEN('NAME','IGS_EN_PRC_LOAD.enrp_clc_sua_weftsu');
797         IGS_GE_MSG_STACK.ADD;
798         App_Exception.Raise_Exception(NULL,NULL,fnd_message.get);
799          ELSE
800           RAISE;
801        END IF;
802   END enrp_clc_sua_weftsu;
803   --
804   -- To calculate the truncated EFTSU figure according to DEETYA IGS_RU_RULEs
805   FUNCTION ENRP_CLC_EFTSU_TRUNC(
806   p_unit_cd IN VARCHAR2 ,
807   p_version_number IN NUMBER ,
808   p_uoo_id IN NUMBER ,
809   p_eftsu IN NUMBER )
810   RETURN NUMBER  AS
811 
812   BEGIN
813   DECLARE
814     v_eftsu_total           NUMBER;
815     --modified cursor for perf bug :3712541
816     CURSOR c_tr IS
817        SELECT tr.percentage
818        FROM IGS_PS_UNIT_OFR_OPT uoo, IGS_PS_TCH_RESP tr
819        WHERE uoo.uoo_id = p_uoo_id
820        AND NOT EXISTS ( SELECT unit_cd
821                         FROM IGS_PS_TCH_RESP_OVRD
822                         WHERE uoo_id =  uoo.uoo_id )
823        AND tr.unit_cd = uoo.unit_cd
824        AND tr.version_number = uoo.version_number
825        UNION ALL
826        SELECT tro.percentage
827        FROM IGS_PS_TCH_RESP_OVRD tro
828        WHERE tro.uoo_id = p_uoo_id;
829     CURSOR c_ud IS
830         SELECT  ud.percentage
831         FROM    IGS_PS_UNIT_DSCP    ud
832         WHERE   ud.unit_cd = p_unit_cd AND
833             ud.version_number = p_version_number;
834   BEGIN
835     -- Routine to perform the necessary truncation on the DEETYA reported
836     -- EFTSU - this is in accordance with the DEETYA guidelines, and  is required
837     -- to be able to reconcile EFTSU figures calculated on a day to day basis
838     -- with those reported in the DEETYA submissions.
839     -- This routine will 'roll down the EFTSU to the lowest common denominator,
840     -- being split across organisational units and IGS_PS_DSCP groups, truncate the
841     -- value and then 'roll up' to the required level.
842     -- Refer to Enrolments Analysis Document for example of this logic.
843     -- Note: This routine is assuming that load has already been split across load
844     -- calendars (ie: Semesters) and that there can be not further splitting of
845     -- the values below OU/IGS_PS_DSCP.
846     v_eftsu_total := 0.000;
847     FOR v_tr_rec    IN  c_tr    LOOP
848         FOR v_ud_rec    IN  c_ud    LOOP
849             v_eftsu_total := v_eftsu_total +
850                     TRUNC(
851                         p_eftsu *
852                         (v_tr_rec.percentage / 100) *
853                         (v_ud_rec.percentage / 100), 3);
854         END LOOP;
855     END LOOP;
856     RETURN v_eftsu_total;
857   END;
858   END enrp_clc_eftsu_trunc;
859   --
860   -- To get the annual load for a unit attempt within a course
861   FUNCTION ENRP_GET_ANN_LOAD(
862   p_person_id IN NUMBER ,
863   p_course_cd IN VARCHAR2 ,
864   p_version_number IN NUMBER ,
865   p_unit_cd IN VARCHAR2 ,
866   p_unit_version_number IN NUMBER ,
867   p_cal_type IN VARCHAR2 ,
868   p_ci_sequence_number IN NUMBER ,
869   p_sca_cp_total IN NUMBER )
870   RETURN NUMBER  AS
871 
872   BEGIN
873   DECLARE
874     v_count         NUMBER;
875     v_std_annual_load   IGS_PS_VER.std_annual_load%TYPE;
876     v_annual_load_val   IGS_PS_ANL_LOAD.annual_load_val%TYPE;
877     v_sca_cp_total      NUMBER;
878     v_cumulative_load   NUMBER;
879     v_census_dt     IGS_CA_DA_INST.absolute_val%TYPE;
880     CURSOR c_cal IS
881         SELECT  COUNT(*)
882         FROM    IGS_PS_ANL_LOAD     cal
883         WHERE   cal.course_cd           = p_course_cd AND
884             cal.version_number      = p_version_number AND
885             cal.effective_start_dt      <= SYSDATE AND
886             (cal.effective_end_dt       IS NULL OR
887             cal.effective_end_dt        >= SYSDATE);
888     CURSOR c_crv IS
889         SELECT  NVL(crv.std_annual_load, 0)
890         FROM    IGS_PS_VER          crv
891         WHERE   crv.course_cd           = p_course_cd AND
892             crv.version_number      = p_version_number;
893     CURSOR c_calul_cal IS
894         SELECT  cal.annual_load_val
895         FROM    IGS_PS_ANL_LOAD_U_LN    calul,
896             IGS_PS_ANL_LOAD     cal
897         WHERE   calul.course_cd         = p_course_cd AND
898             calul.crv_version_number    = p_version_number AND
899             calul.effective_start_dt    <= SYSDATE AND
900             calul.unit_cd           = p_unit_cd AND
901             calul.uv_version_number     = p_unit_version_number AND
902             calul.course_cd         = cal.course_cd AND
903             calul.crv_version_number    = cal.version_number AND
904             calul.yr_num            = cal.yr_num AND
905             calul.effective_start_dt    = cal.effective_start_dt AND
906             (cal.effective_end_dt       IS NULL OR
907             cal.effective_end_dt        >= SYSDATE)
908         ORDER BY calul.effective_start_dt DESC,
909             cal.yr_num;
910     CURSOR c_cal2 IS
911         SELECT  cal.annual_load_val
912         FROM    IGS_PS_ANL_LOAD     cal
913         WHERE   cal.course_cd           = p_course_cd AND
914             cal.version_number      = p_version_number AND
915             cal.effective_start_dt      <= SYSDATE AND
916             (cal.effective_end_dt       IS NULL OR
917             cal.effective_end_dt        >= SYSDATE)
918         ORDER BY cal.yr_num;
919     CURSOR c_sgcc_dai IS
920         SELECT  NVL (   absolute_val,
921                 IGS_CA_GEN_001.CALP_GET_ALIAS_VAL(
922                             dai.dt_alias,
923                             dai.sequence_number,
924                             dai.cal_type,
925                             dai.ci_sequence_number)) AS census_dt
926         FROM    IGS_GE_S_GEN_CAL_CON            sgcc,
927             IGS_CA_DA_INST      dai
928         WHERE   sgcc.s_control_num      = 1 AND
929             dai.dt_alias            = sgcc.census_dt_alias AND
930             dai.cal_type            = p_cal_type AND
931             dai.ci_sequence_number      = p_ci_sequence_number
932         ORDER BY 1 ASC;         --  use earliest value
933   BEGIN
934     -- Get the annual load figure of a student unit attempt within a course
935     -- version.
936     -- This figure may come from one of three places:
937     --  Method 1. If the IGS_PS_COURSE has a standard annual load across all years then
938     -- the IGS_PS_VER.std_annual_load figure is used. This is defined by the
939     -- non-existence of a current IGS_PS_ANL_LOAD record for the course version.
940     --  Method 2. By interrogating the IGS_PS_ANL_LOAD structure to determine
941     -- which annual load value is applicable, given the students current passed
942     -- credit  point total. This is used when no annual load unit link is
943     -- defined (refer method 3).
944     --  Method 3. By using the IGS_PS_ANL_LOAD_U_LN structure, which
945     -- explicitely links the unit version to a IGS_PS_ANL_LOAD record, dictating
946     --  the annual load figure.
947     -- 1. Check whether course version has a 'standard' annual load across all
948     --      years -  this is done by searching for the existence of a current
949     --      IGS_PS_ANL_LOAD record -
950     -- no records means a 'standard' structure.
951     OPEN    c_cal;
952     FETCH   c_cal   INTO    v_count;
953     CLOSE   c_cal;
954     IF (v_count = 0) THEN
955         -- 1.1 Retrieve the annual load from the course version table and return it.
956         OPEN    c_crv;
957         FETCH   c_crv   INTO    v_std_annual_load;
958         IF (c_crv%NOTFOUND) THEN
959             CLOSE   c_crv;
960             RETURN 0;
961         END IF;
962         CLOSE   c_crv;
963         RETURN v_std_annual_load;
964     END IF;
965     -- 2. Check whether the unit version is explicitely linked to the course annual
966     --      load structure - if so, use the annual load value in the structure.
967     OPEN    c_calul_cal;
968     FETCH   c_calul_cal INTO    v_annual_load_val;
969     IF (c_calul_cal%FOUND) THEN
970         CLOSE   c_calul_cal;
971         RETURN v_annual_load_val;
972     END IF;
973     CLOSE   c_calul_cal;
974     -- 3. IF the parameter was not set then call routine to determine the student's
975     -- completed credit points.
976     IF (p_sca_cp_total IS NOT NULL) AND
977             (p_sca_cp_total <> 0) THEN
978         v_sca_cp_total := p_sca_cp_total;
979     ELSE
980         IF p_cal_type IS NOT NULL AND
981                 p_ci_sequence_number IS NOT NULL THEN
982             OPEN c_sgcc_dai;
983             FETCH c_sgcc_dai INTO v_census_dt;
984             IF c_sgcc_dai%NOTFOUND THEN
985                 CLOSE c_sgcc_dai;
986                 v_census_dt := TRUNC(SYSDATE);
987             ELSE
988                 CLOSE c_sgcc_dai;
989             END IF;
990         ELSE
991             v_census_dt := TRUNC(SYSDATE);
992         END IF;
993         v_sca_cp_total := Igs_En_Gen_001.ENRP_CLC_SCA_PASS_CP(
994                         p_person_id,
995                         p_course_cd,
996                         v_census_dt);
997     END IF;
998     -- 4. Determine the course annual load record which applies to the students
999     -- passed credit points range.
1000     v_cumulative_load := 0;
1001     v_annual_load_val := 0;
1002     FOR v_cal_rec   IN  c_cal2 LOOP
1003         v_cumulative_load := v_cumulative_load + v_cal_rec.annual_load_val;
1004         IF (v_sca_cp_total < v_cumulative_load) THEN
1005             v_annual_load_val := v_cal_rec.annual_load_val;
1006             EXIT;
1007         END IF;
1008     END LOOP;
1009     IF (v_annual_load_val = 0) THEN
1010         -- Revert to the course_version annual load value.
1011         OPEN    c_crv;
1012         FETCH   c_crv   INTO    v_std_annual_load;
1013         IF (c_crv%NOTFOUND) THEN
1014             -- At present, this will not occur because to reach this point
1015             -- a record must exist in IGS_PS_ANL_LOAD and for the course
1016             -- to exist in IGS_PS_ANL_LOAD it must exist in IGS_PS_VER.
1017             CLOSE   c_crv;
1018             RETURN 0;
1019         END IF;
1020         CLOSE   c_crv;
1021         v_annual_load_val := v_std_annual_load;
1022     END IF;
1023     RETURN v_annual_load_val;
1024   EXCEPTION
1025     WHEN OTHERS THEN
1026         IF c_cal%ISOPEN THEN
1027             CLOSE c_cal;
1028         END IF;
1029         IF c_crv%ISOPEN THEN
1030             CLOSE c_crv;
1031         END IF;
1032         IF c_calul_cal%ISOPEN THEN
1033             CLOSE c_calul_cal;
1034         END IF;
1035         IF c_cal2%ISOPEN THEN
1036             CLOSE c_cal2;
1037         END IF;
1038         IF c_sgcc_dai%ISOPEN THEN
1039             CLOSE c_sgcc_dai;
1040         END IF;
1041         RAISE;
1042   END;
1043   END enrp_get_ann_load;
1044   --
1045   -- To calc the total load for an SCA for a load period
1046   FUNCTION ENRP_CLC_LOAD_TOTAL(
1047   p_person_id IN NUMBER ,
1048   p_course_cd IN VARCHAR2 ,
1049   p_acad_cal_type IN VARCHAR2 ,
1050   p_acad_sequence_number IN NUMBER ,
1051   p_load_cal_type IN VARCHAR2 ,
1052   p_load_sequence_number IN NUMBER )
1053   RETURN NUMBER  AS
1054   BEGIN
1055   DECLARE
1056     cst_active          CONSTANT VARCHAR2(10) := 'ACTIVE';
1057     cst_teaching        CONSTANT VARCHAR2(10) := 'TEACHING';
1058     cst_enrolled        CONSTANT VARCHAR2(10) := 'ENROLLED';
1059     cst_completed       CONSTANT VARCHAR2(10) := 'COMPLETED';
1060     cst_discontin       CONSTANT VARCHAR2(10) := 'DISCONTIN';
1061     cst_waitlisted      CONSTANT VARCHAR2(10) := 'WAITLISTED';
1062 
1063     v_calendar_load     NUMBER;
1064     v_return_eftsu      NUMBER;
1065     --dummy variable to pick up audit, billing, enrolled credit points
1066     --due to signature change by EN308 Billing credit hours
1067     l_audit_cp          IGS_PS_USEC_CPS.billing_credit_points%TYPE;
1068     l_billing_cp        IGS_PS_USEC_CPS.billing_hrs%TYPE;
1069     l_enrolled_cp       IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
1070     CURSOR  c_cal_type_instance(  cp_cal_type IGS_CA_INST.cal_type%TYPE,
1071                 cp_sequence_number IGS_CA_INST.sequence_number%TYPE)IS
1072         SELECT  CI.cal_type,
1073             CI.sequence_number
1074         FROM    IGS_CA_INST_REL CIR,
1075             IGS_CA_INST CI,
1076             IGS_CA_TYPE CT,
1077             IGS_CA_STAT CS
1078         WHERE   CT.closed_ind = 'N' AND
1079             CT.s_cal_cat = cst_teaching AND
1080             CS.s_cal_status = cst_active AND
1081             CI.cal_status = CS.cal_status AND
1082             CI.cal_type = CT.cal_type AND
1083             CIR.sup_cal_type = cp_cal_type AND
1084             CIR.sup_ci_sequence_number =  cp_sequence_number AND
1085             CIR.sub_cal_type = CI.cal_type AND
1086             CIR.sub_ci_sequence_number = CI.sequence_number;
1087   --            (IGS_EN_GEN_014.ENRS_GET_WITHIN_CI(cp_cal_type,
1088   --                cp_sequence_number,
1089   --                CI.cal_type,
1090   --                CI.sequence_number,
1091   --                'N') = 'Y');
1092     CURSOR  c_stu_unit_atmpt(
1093             cp_person_id IGS_PE_PERSON.person_id%TYPE,
1094             cp_course_cd IGS_PS_COURSE.course_cd%TYPE,
1095             cp_cal_type IGS_CA_INST.cal_type%TYPE,
1096             cp_sequence_number IGS_CA_INST.sequence_number%TYPE) IS
1097         SELECT  SUA.unit_cd,
1098                 SUA.version_number,
1099                 SUA.cal_type,
1100                 SUA.ci_sequence_number,
1101                 SUA.override_enrolled_cp,
1102                 SUA.override_eftsu,
1103                 SUA.unit_attempt_status,
1104                 SUA.administrative_unit_status,
1105                 SUA.discontinued_dt,
1106                 SUA.uoo_id,
1107                 SUA.no_assessment_ind
1108         FROM    IGS_EN_SU_ATTEMPT SUA
1109         WHERE   SUA.person_id = cp_person_id AND
1110                 SUA.course_cd = cp_course_cd AND
1111                 SUA.cal_type = cp_cal_type AND
1112                 SUA.ci_sequence_number = cp_sequence_number AND
1113                 SUA.unit_attempt_status IN (cst_enrolled, cst_completed, cst_discontin, cst_waitlisted);
1114   BEGIN
1115     -- Calculate a students total load within a nominated LOAD calendar.
1116     -- This routine will call other routines to determine the load apportionment
1117     -- values for the students unit attempts.
1118     v_calendar_load := 0;
1119     FOR v_cal_type_instance_rec IN c_cal_type_instance(
1120                             p_acad_cal_type,
1121                             p_acad_sequence_number)
1122     LOOP
1123          FOR v_stu_unit_atmpt_rec IN c_stu_unit_atmpt(
1124                 p_person_id,
1125                 p_course_cd,
1126                 v_cal_type_instance_rec.cal_type,
1127                 v_cal_type_instance_rec.sequence_number)
1128          LOOP
1129             IF (ENRP_GET_LOAD_INCUR(
1130                     v_cal_type_instance_rec.cal_type,
1131                     v_cal_type_instance_rec.sequence_number,
1132                     v_stu_unit_atmpt_rec.discontinued_dt,
1133                     v_stu_unit_atmpt_rec.administrative_unit_status,
1134                     v_stu_unit_atmpt_rec.unit_attempt_status,
1135                     v_stu_unit_atmpt_rec.no_assessment_ind,
1136                     p_load_cal_type,
1137                     p_load_sequence_number,
1138                     v_stu_unit_atmpt_rec.uoo_id,
1139                     -- anilk, Audit special fee build
1140                     'N') = 'Y') THEN
1141 
1142                     v_calendar_load := v_calendar_load + ENRP_CLC_SUA_LOAD(
1143                                         v_stu_unit_atmpt_rec.unit_cd,
1144                                         v_stu_unit_atmpt_rec.version_number,
1145                                         v_stu_unit_atmpt_rec.cal_type,
1146                                         v_stu_unit_atmpt_rec.ci_sequence_number,
1147                                         p_load_cal_type,
1148                                         p_load_sequence_number,
1149                                         v_stu_unit_atmpt_rec.override_enrolled_cp,
1150                                         v_stu_unit_atmpt_rec.override_eftsu,
1151                                         v_return_eftsu,
1152                                         v_stu_unit_atmpt_rec.uoo_id,
1153                                         -- anilk, Audit special fee build
1154                                         'N',
1155                                         l_audit_cp,
1156                                         l_billing_cp,
1157                                         l_enrolled_cp);
1158 
1159             END IF;
1160        END LOOP;
1161     END LOOP;
1162     RETURN v_calendar_load;
1163   EXCEPTION
1164     WHEN OTHERS THEN
1165        IF SQLCODE <>-20001 THEN
1166         Fnd_Message.Set_name('IGS','IGS_GE_UNHANDLED_EXP');
1167         FND_MESSAGE.SET_TOKEN('NAME','IGS_EN_PRC_LOAD.enrp_clc_load_total');
1168         IGS_GE_MSG_STACK.ADD;
1169         App_Exception.Raise_Exception(NULL,NULL,fnd_message.get);
1170     ELSE
1171         RAISE;
1172     END IF;
1173   END;
1174   END enrp_clc_load_total;
1175   --
1176   -- To calculate the load for a sua (optionally within a load calendar)
1177   FUNCTION ENRP_CLC_SUA_LOAD(
1178   p_unit_cd IN VARCHAR2 ,
1179   p_version_number IN NUMBER ,
1180   p_cal_type IN VARCHAR2 ,
1181   p_ci_sequence_number IN NUMBER ,
1182   p_load_cal_type IN VARCHAR2 ,
1183   p_load_ci_sequence_number IN NUMBER ,
1184   p_override_enrolled_cp IN NUMBER ,
1185   p_override_eftsu IN NUMBER ,
1186   p_return_eftsu OUT NOCOPY NUMBER ,
1187   p_uoo_id        IN NUMBER,
1188   -- anilk, Audit special fee build
1189   p_include_as_audit IN VARCHAR2,
1190   p_audit_cp                    OUT NOCOPY NUMBER,
1191   p_billing_cp          OUT NOCOPY NUMBER,
1192   p_enrolled_cp         OUT NOCOPY NUMBER)
1193   RETURN NUMBER  AS
1194 /*
1195 who          when     What
1196 sarakshi 27-Jun-2003  Enh#2930935,modified cursor c_unit_version such that it picks enrolled credit points
1197                       from the usec level if exist else from the unit level
1198 vkarthik 21-Jul-2004  Added two out parameters p_audit_cp and p_billing_cp for
1199                       EN308 for Billable credit points build.  Changed code logic to get various cps.
1200                       Added logic to get audit_cp
1201 */
1202   BEGIN
1203     BEGIN
1204     DECLARE
1205         v_enrolled_credit_points    IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
1206         v_enrolled_cp               IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
1207         v_billing_cp                IGS_PS_USEC_CPS.billing_hrs%TYPE;
1208         v_percentage                IGS_ST_DFT_LOAD_APPO.percentage%TYPE;
1209         v_second_percentage         IGS_ST_DFT_LOAD_APPO.second_percentage%TYPE;
1210         v_acad_cal_type             IGS_CA_INST.cal_type%TYPE;
1211         v_acad_ci_sequence_number   IGS_CA_INST.sequence_number%TYPE;
1212         v_acad_ci_start_dt          IGS_CA_INST.start_dt%TYPE;
1213         v_acad_ci_end_dt            IGS_CA_INST.end_dt%TYPE;
1214         v_first_cal_type            IGS_CA_INST.cal_type%TYPE;
1215         v_first_ci_sequence_number  IGS_CA_INST.sequence_number%TYPE;
1216         v_first_ci_start_dt         IGS_CA_INST.start_dt%TYPE;
1217         v_first_ci_end_dt           IGS_CA_INST.end_dt%TYPE;
1218         v_dummy_alt_cd              IGS_CA_INST.alternate_code%TYPE;
1219         v_message_name              VARCHAR2(30);
1220         v_audit_cp                  IGS_PS_USEC_CPS.billing_credit_points%TYPE;
1221 
1222         CURSOR  c_dflt_load_apportion(
1223                 cp_acad_cal_type IGS_ST_DFT_LOAD_APPO.cal_type%TYPE,
1224                 cp_acad_ci_sequence_number IGS_ST_DFT_LOAD_APPO.ci_sequence_number%TYPE,
1225                 cp_cal_type IGS_ST_DFT_LOAD_APPO.teach_cal_type%TYPE)IS
1226             SELECT  DLA.percentage,
1227                 DLA.second_percentage
1228             FROM    IGS_ST_DFT_LOAD_APPO DLA
1229             WHERE   DLA.cal_type = cp_acad_cal_type AND
1230                 DLA.ci_sequence_number = cp_acad_ci_sequence_number AND
1231                 DLA.teach_cal_type = cp_cal_type;
1232     BEGIN
1233         p_audit_cp := NULL;
1234         p_billing_cp := NULL;
1235         p_enrolled_cp := NULL;
1236         -- Calculate the load (credit points) for a nominated unit attempt within
1237         -- a nominated calendar instance. The calendar instance may be either a load
1238         -- period or null. If a calendar instance is specified, a search for a matching
1239         -- IGS_ST_DFT_LOAD_APPO record will be performed; if not found the apportionment
1240         -- is assumed to be 0%. If no calendar is specified the apportionment is always
1241         -- 100%.
1242         --get the various cps, using the inheritance model of PSP
1243         igs_ps_val_uv.get_cp_values(p_uoo_id,
1244                                     v_enrolled_cp,
1245                                     v_billing_cp,
1246                                     v_audit_cp);
1247 
1248         --set the valud of enrolled_credit_points according to overide_enrolled_cp, auditable,
1249         --non-auditable units
1250         IF p_override_enrolled_cp IS NOT NULL AND p_include_as_audit = 'N' THEN
1251                 v_enrolled_credit_points := p_override_enrolled_cp;
1252         ELSIF p_include_as_audit = 'Y' THEN
1253                 v_enrolled_credit_points := v_audit_cp;
1254         ELSE
1255                 v_enrolled_credit_points := v_enrolled_cp;
1256         END IF;
1257         --set out cp parameters
1258         p_audit_cp := v_audit_cp;
1259         p_billing_cp := v_billing_cp;
1260         p_enrolled_cp := NVL(p_override_enrolled_cp, v_enrolled_cp);
1261         --return zero when values are not defined
1262         IF      p_billing_cp IS NULL                    AND
1263                 v_enrolled_credit_points = 0    AND
1264                 p_audit_cp IS NULL                      AND
1265                 p_enrolled_cp IS NULL           THEN
1266                 RETURN 0;
1267         END IF;
1268         -- Search for a apportionment record between the academic calendar
1269         -- instance and teaching calendar type. If not found, percentage is assumed
1270         -- to be 100 (assuming all of the teaching period is within the academic
1271         -- calendar instance).
1272         IF(p_load_cal_type IS NOT NULL AND p_load_ci_sequence_number IS NOT NULL) THEN
1273             OPEN    c_dflt_load_apportion(
1274                         p_load_cal_type,
1275                         p_load_ci_sequence_number,
1276                         p_cal_type);
1277             FETCH   c_dflt_load_apportion INTO v_percentage,  v_second_percentage;
1278             IF(c_dflt_load_apportion%NOTFOUND) THEN
1279                   v_percentage := 0;
1280             ELSIF (v_second_percentage IS NULL) THEN
1281                   NULL;
1282             ELSE
1283               v_dummy_alt_cd := Igs_En_Gen_002.ENRP_GET_ACAD_ALT_CD(
1284                             p_load_cal_type,
1285                             p_load_ci_sequence_number,
1286                             v_acad_cal_type,
1287                             v_acad_ci_sequence_number,
1288                             v_acad_ci_start_dt,
1289                             v_acad_ci_end_dt,
1290                             v_message_name);
1291               IF(v_dummy_alt_cd IS NULL) THEN
1292                 NULL;
1293               ELSE
1294                 v_dummy_alt_cd := Igs_En_Gen_002.ENRP_GET_ACAD_ALT_CD(
1295                                 p_cal_type,
1296                                 p_ci_sequence_number,
1297                                 v_first_cal_type,
1298                                 v_first_ci_sequence_number,
1299                                 v_first_ci_start_dt,
1300                                 v_first_ci_end_dt,
1301                                 v_message_name);
1302 
1303                 IF(v_dummy_alt_cd IS NULL) THEN
1304                   NULL;
1305                 ELSE
1306                   IF((v_acad_cal_type = v_first_cal_type) AND
1307                  (v_acad_ci_sequence_number = v_first_ci_sequence_number)) THEN
1308                     NULL;
1309                   ELSE
1310                     v_percentage := v_second_percentage;
1311                   END IF;
1312                 END IF;
1313               END IF;
1314             END IF;
1315             CLOSE   c_dflt_load_apportion;
1316         ELSE
1317             v_percentage := 100;
1318         END IF;
1319         -- If the override eftsu is passed then calculate the proportion of the EFTSU
1320         -- figure whch is incurred within the load calendar instance specified.
1321         IF p_override_eftsu IS NOT NULL THEN
1322             p_return_eftsu := p_override_eftsu * (v_percentage / 100);
1323         ELSE
1324             p_return_eftsu := NULL;
1325         END IF;
1326         IF p_billing_cp IS NOT NULL THEN
1327                 p_billing_cp := v_billing_cp * (v_percentage/100);
1328         END IF;
1329         IF p_audit_cp IS NOT NULL THEN
1330                 p_audit_cp := v_audit_cp * (v_percentage/100);
1331         END IF;
1332         IF p_enrolled_cp IS NOT NULL THEN
1333                 p_enrolled_cp := p_enrolled_cp * (v_percentage/100);
1334         END IF;
1335                 RETURN (v_enrolled_credit_points * (v_percentage/100));
1336      END;
1337   END enrp_clc_sua_load;
1338   END;
1339 
1340   --
1341   -- To get the attendance type of load within a nominated load calendar
1342   FUNCTION ENRP_GET_LOAD_ATT(
1343   p_load_cal_type IN VARCHAR2 ,
1344   p_load_figure IN NUMBER )
1345   RETURN VARCHAR2  AS
1346   BEGIN
1347   DECLARE
1348     v_record_found      BOOLEAN;
1349     v_record_count      NUMBER;
1350     v_attendance_type   IGS_EN_ATD_TYPE_LOAD.attendance_type%TYPE;
1351     CURSOR  c_attendance_type(
1352             cp_cal_type IGS_CA_TYPE.cal_type%TYPE,
1353             cp_load_figure IGS_EN_ATD_TYPE_LOAD.lower_enr_load_range%TYPE) IS
1354         SELECT  ATL.attendance_type
1355         FROM    IGS_EN_ATD_TYPE_LOAD ATL
1356         WHERE   ATL.cal_type = p_load_cal_type AND
1357                 ATL.lower_enr_load_range <= p_load_figure AND
1358                 ATL.upper_enr_load_range >= p_load_figure;
1359   BEGIN
1360     -- Get the attendance type for a nominated CP load in a nominated load calendar
1361     -- This is done by searching for an IGS_EN_ATD_TYPE_LOAD record which specifies
1362     -- the load ranges for the different attendance types within the load calendar
1363     -- types. If no record is found then NULL is returned, as it is not possible to
1364     -- derive the figure.
1365     IF p_load_figure = 0 THEN
1366         RETURN NULL;
1367     END IF;
1368     v_record_found := FALSE;
1369     v_record_count := 0;
1370     FOR v_attendance_type_rec IN c_attendance_type(
1371                         p_load_cal_type,
1372                         trunc(p_load_figure,3))
1373     LOOP
1374         v_record_found := TRUE;
1375         v_record_count := v_record_count + 1;
1376         v_attendance_type := v_attendance_type_rec.attendance_type;
1377     END LOOP;
1378     IF(v_record_found = FALSE) THEN
1379         RETURN NULL;
1380     END IF;
1381     IF(v_record_count > 1) THEN
1382         RETURN NULL;
1383     ELSE
1384         RETURN v_attendance_type;
1385     END IF;
1386 
1387   END;
1388   END enrp_get_load_att;
1389   --
1390   -- To get whether a UA incurs load within a nominated load calendar
1391   FUNCTION ENRP_GET_LOAD_INCUR(
1392   p_cal_type IN VARCHAR2 ,
1393   p_sequence_number IN NUMBER ,
1394   p_discontinued_dt IN DATE ,
1395   p_administrative_unit_status IN VARCHAR2 ,
1396   p_unit_attempt_status IN VARCHAR2 ,
1397   p_no_assessment_ind IN VARCHAR2,
1398   p_load_cal_type IN VARCHAR2 ,
1399   p_load_sequence_number IN NUMBER,
1400   p_uoo_id IN NUMBER,
1401   -- anilk, Audit special fee build
1402   p_include_audit IN VARCHAR2 )
1403   RETURN VARCHAR2  AS
1404   /*   Who           When                What
1405       pradhakr      15-Jan-03           Added one parameter no_assessment_ind wrt ENCR026 build.
1406                                         Bug# 2743459
1407       jbegum        21 Mar 02           As part of bug fix 2192616 added
1408                                         pragma exception_init(NO_AUSL_RECORD_FOUND , -20010);
1409                                         to the user defined exception NO_AUSL_RECORD_FOUND
1410                                         in order to catch the exception in the form IGSPS047.
1411       pradhakr      30-Jul-01           Added the parameter uoo_id as part of Enrollment Process.
1412                                         Bug# 1832130
1413      myoganat      23-MAY-2003          Removed reference to profile
1414                                         IGS_EN_INCL_AUDIT_CP in
1415                                         procedure ENRP_GET_LOAD_INCUR
1416                                         as part of the ENCR032 Build Bug
1417                                         #2855870
1418                                         */
1419   BEGIN
1420   DECLARE
1421     NO_AUSL_RECORD_FOUND EXCEPTION;
1422     PRAGMA EXCEPTION_INIT(NO_AUSL_RECORD_FOUND , -20010);
1423 
1424     cst_completed       CONSTANT VARCHAR2(10) := 'COMPLETED';
1425     cst_enrolled        CONSTANT VARCHAR2(10) := 'ENROLLED';
1426     cst_discontin       CONSTANT VARCHAR2(10) := 'DISCONTIN';
1427     cst_waitlisted      CONSTANT VARCHAR2(10) := 'WAITLISTED';
1428 
1429     CURSOR  c_dla(
1430             cp_load_cal_type IGS_CA_INST.cal_type%TYPE,
1431             cp_load_sequence_number IGS_CA_INST.sequence_number%TYPE,
1432             cp_cal_type IGS_CA_INST.cal_type%TYPE) IS
1433         SELECT  ci.start_dt,
1434                 ci.end_dt
1435         FROM    IGS_ST_DFT_LOAD_APPO dla,
1436                 IGS_CA_INST ci
1437         WHERE   dla.cal_type = cp_load_cal_type AND
1438                 dla.ci_sequence_number = cp_load_sequence_number AND
1439                 dla.teach_cal_type = cp_cal_type AND
1440                 ci.cal_type = dla.cal_type AND
1441                 ci.sequence_number = dla.ci_sequence_number;
1442 
1443     CURSOR  c_ausl(
1444              cp_load_cal_type IGS_CA_INST.cal_type%TYPE,
1445              cp_load_sequence_number IGS_CA_INST.sequence_number%TYPE,
1446              cp_cal_type IGS_CA_INST.cal_type%TYPE,
1447              cp_administrative_unit_status
1448                IGS_EN_SU_ATTEMPT.administrative_unit_status%TYPE) IS
1449         SELECT  AUSL.load_incurred_ind
1450         FROM    IGS_AD_ADM_UT_STT_LD AUSL
1451         WHERE   AUSL.cal_type = cp_load_cal_type AND
1452                 AUSL.ci_sequence_number = cp_load_sequence_number AND
1453                 AUSL.teach_cal_type = cp_cal_type AND
1454                 AUSL.administrative_unit_status = cp_administrative_unit_status;
1455 
1456    CURSOR incl_org_wlst_cp is
1457           SELECT asses_chrg_for_wlst_stud
1458           FROM IGS_EN_OR_UNIT_WLST
1459           WHERE cal_type = p_load_cal_type AND
1460           closed_flag = 'N' AND
1461           org_unit_cd = (SELECT NVL(uoo.owner_org_unit_cd, uv.owner_org_unit_cd)
1462                          FROM igs_ps_unit_ofr_opt uoo,
1463                               igs_ps_unit_ver uv
1464                           WHERE uoo.uoo_id = p_uoo_id AND
1465                                 uv.unit_cd = uoo.unit_cd AND
1466                                 uv.version_number = uoo.version_number);
1467   CURSOR incl_inst_wlst_cp is
1468          SELECT include_waitlist_cp_flag
1469          FROM IGS_EN_INST_WL_STPS;
1470 
1471     v_alias_val     IGS_CA_DA_INST_V.alias_val%TYPE;
1472     v_load_incurred_ind IGS_AD_ADM_UT_STT_LD.load_incurred_ind%TYPE;
1473     v_start_dt      IGS_CA_INST.start_dt%TYPE;
1474     v_end_dt        IGS_CA_INST.end_dt%TYPE;
1475     v_dummy_aus     VARCHAR2(10);
1476     v_admin_unit_status_str VARCHAR2(2000);
1477     v_incl_wlst_cp VARCHAR2(1);
1478   BEGIN
1479 
1480     -- Routine to determine whether a nominated student unit attempt incurs load
1481     -- for a nominated load calendar.
1482     -- For DISCONTIN unit attempts, the routine  determines the date alias instance
1483     -- which was used in the original discontinuation.  If this alias_val :
1484     -- 1. if prior to the load calendar instance - then load is never incurred
1485     -- 2. is after the load calendar instance - then load is always incurred.
1486     -- ELSE
1487     -- it checks the IGS_AD_ADM_UT_STT_LD table for a link between the
1488     --  administrative
1489     -- unit status and the load calendar as at the effective date.
1490     -- For ENROLLED or COMPLETED unit attempts - the load is always incurred.
1491     -- For other statuses - load cannot be incurred.
1492     -- Check whether the teaching calendar has a load apportionment link
1493     -- th the load calendar. If no IGS_ST_DFT_LOAD_APPO detail exists then
1494     -- load is definitely not incurred. Processing concludes.
1495     -- Note: this query joints to the IGS_CA_INST tabel to get the start
1496     -- and end dates - this is to possibly save doing it later
1497 
1498 
1499     -- Check whether the passed in Unit Attempt is a Audit Unit
1500     -- If so, return 'N' else use the existing logic to get the EFTSU and credit points of the
1501     -- unit attempt.
1502     IF NVL(p_no_assessment_ind,'N') = 'Y'  AND p_include_audit = 'N' THEN
1503       RETURN 'N';
1504     END IF;
1505 
1506     OPEN    c_dla(
1507             p_load_cal_type,
1508             p_load_sequence_number,
1509             p_cal_type);
1510     FETCH c_dla INTO v_start_dt,  v_end_dt;
1511     IF (c_dla%NOTFOUND) THEN
1512         CLOSE c_dla;
1513         RETURN 'N';
1514     END IF;
1515     CLOSE c_dla;
1516    --fetch teh waitlist values, added as part of waitlist enhancement build #3052426
1517      OPEN incl_org_wlst_cp;
1518      FETCH incl_org_wlst_cp into v_incl_wlst_cp;
1519 
1520        IF incl_org_wlst_cp%NOTFOUND then
1521           OPEN incl_inst_wlst_cp;
1522           FETCH incl_inst_wlst_cp INTO v_incl_wlst_cp;
1523           CLOSE incl_inst_wlst_cp;
1524        END IF;
1525      CLOSE incl_org_wlst_cp;
1526 
1527     -- If the unit attempt is discontinued, select the load incurred indicator for
1528     -- the administrative unit status.
1529     IF(p_unit_attempt_status = cst_discontin) THEN
1530         -- call the routine to determine the alias_val of
1531         -- the original discontinuation criteria
1532         v_dummy_aus := Igs_En_Gen_008.ENRP_GET_UDDC_AUS (
1533                     p_discontinued_dt,
1534                     p_cal_type,
1535                     p_sequence_number,
1536                     v_admin_unit_status_str,
1537                     v_alias_val,
1538                     p_uoo_id);
1539         -- only continue with the below tests
1540         -- if a value was returned for the v_alias_val
1541 
1542 
1543         IF (v_alias_val IS NOT NULL) THEN
1544             -- if the alias_val is prior to the start date of
1545             -- the load calendar instance, then load is not
1546             -- incurred
1547             IF (v_alias_val < v_start_dt) THEN
1548                 RETURN 'N';
1549             END IF;
1550             -- if the alias_val is after the end date of the
1551             -- load calendar instance, then load is always
1552             -- incurred
1553             IF (v_alias_val > v_end_dt) THEN
1554                 RETURN 'Y';
1555             END IF;
1556         END IF;
1557         -- if none of the above is true, then look for
1558         -- the administrative unit status load details
1559         OPEN    c_ausl(
1560                 p_load_cal_type,
1561                 p_load_sequence_number,
1562                 p_cal_type,
1563                 p_administrative_unit_status);
1564         FETCH   c_ausl INTO v_load_incurred_ind;
1565         -- if no records found, raise an exception
1566         IF(c_ausl%NOTFOUND) THEN
1567             CLOSE   c_ausl;
1568             RAISE NO_AUSL_RECORD_FOUND;
1569         END IF;
1570         CLOSE c_ausl;
1571         IF(v_load_incurred_ind = 'Y') THEN
1572             RETURN 'Y';
1573         ELSE
1574             RETURN 'N';
1575         END IF;
1576     ELSIF (p_unit_attempt_status = cst_enrolled OR
1577            p_unit_attempt_status = cst_completed) THEN
1578         RETURN 'Y';
1579     --logic to determine waitlisted credit points . earlier the profile IGS_EN_INCL_WLST_CP was used
1580     --this has been obsoleted as part of wailist enhancement build to determine form the checkbox setup at
1581     -- various level
1582     -- as per the functional requirement , if the check box to include waitlist CP  is unchecked then
1583     --check the profile value. If this is yes then include waitlist CP in validations. IF the institution level
1584     --   checkbox is checked then no need to check profile. The profile does not override the institution level
1585     --setup.
1586 
1587     ELSIF (p_unit_attempt_status = cst_waitlisted )AND
1588     (v_incl_wlst_cp = 'Y' OR ( v_incl_wlst_cp is null and g_wlst_prfl = 'Y' ) )THEN
1589                          RETURN 'Y';
1590     ELSE
1591         RETURN 'N';
1592     END IF;
1593 
1594   END;
1595 
1596   END ENRP_GET_LOAD_INCUR;
1597   --
1598   -- To get whether a load applies to a UA within a nominated load calendar
1599   FUNCTION ENRP_GET_LOAD_APPLY(
1600   p_teach_cal_type          IN VARCHAR2 ,
1601   p_teach_sequence_number   IN NUMBER ,
1602   p_discontinued_dt         IN DATE ,
1603   p_administrative_unit_status IN VARCHAR2 ,
1604   p_unit_attempt_status     IN VARCHAR2 ,
1605   p_no_assessment_ind       IN VARCHAR2,
1606   p_load_cal_type           IN VARCHAR2 ,
1607   p_load_sequence_number    IN NUMBER,
1608   -- anilk, Audit special fee build
1609   p_include_audit           IN VARCHAR2)
1610   RETURN VARCHAR2  AS
1611   BEGIN
1612   DECLARE
1613     -- cursor to check if a load and teaching calendar instance are related to
1614     -- the same academic period calendar instance.
1615     CURSOR  c_cal_reln(
1616             cp_load_cal_type        IGS_CA_INST.cal_type%TYPE,
1617             cp_load_sequence_number     IGS_CA_INST.sequence_number%TYPE,
1618             cp_teach_cal_type       IGS_CA_INST.cal_type%TYPE,
1619             cp_teach_sequence_number    IGS_CA_INST.sequence_number%TYPE) IS
1620         SELECT  'X'
1621         FROM    IGS_CA_INST_REL cir1,
1622                 IGS_CA_TYPE ct,
1623                 IGS_CA_INST_REL cir2
1624         WHERE   cir1.sub_cal_type = cp_load_cal_type AND
1625                 cir1.sub_ci_sequence_number = cp_load_sequence_number AND
1626                 ct.cal_type = cir1.sup_cal_type AND
1627                 ct.s_cal_cat = 'ACADEMIC' AND
1628                 cir2.sup_cal_type = cir1.sup_cal_type AND
1629                 cir2.sup_ci_sequence_number = cir1.sup_ci_sequence_number AND
1630                 cir2.sub_cal_type = cp_teach_cal_type AND
1631                 cir2.sub_ci_sequence_number = cp_teach_sequence_number;
1632     v_dummy     VARCHAR2(1);
1633   BEGIN
1634 
1635     -- Routine to determine whether load applies to a nominated student unit
1636     -- attempt for a nominated load calendar.
1637     OPEN    c_cal_reln(
1638             p_load_cal_type,
1639             p_load_sequence_number,
1640             p_teach_cal_type,
1641             p_teach_sequence_number);
1642     FETCH c_cal_reln INTO v_dummy;
1643     IF (c_cal_reln%NOTFOUND) THEN
1644         CLOSE c_cal_reln;
1645         RETURN 'N';
1646     END IF;
1647     CLOSE c_cal_reln;
1648     -- Call routine to check if load is incurred.
1649     RETURN ENRP_GET_LOAD_INCUR(
1650                     p_teach_cal_type,
1651                     p_teach_sequence_number,
1652                     p_discontinued_dt,
1653                     p_administrative_unit_status,
1654                     p_unit_attempt_status,
1655                     p_no_assessment_ind,
1656                     p_load_cal_type,
1657                     p_load_sequence_number,
1658                     -- anilk, Audit special fee build
1659                     NULL, -- for p_uoo_id
1660                     p_include_audit
1661                     );
1662 
1663   END;
1664   END ENRP_GET_LOAD_APPLY;
1665 
1666 FUNCTION enrp_clc_key_prog(p_person_id                     IN   hz_parties.party_id%TYPE,
1667                            p_version_number                OUT NOCOPY  igs_en_su_attempt.version_number%TYPE,
1668                            p_term_cal_type                 IN VARCHAR2,
1669                            p_term_sequence_number          IN NUMBER
1670                            )
1671 RETURN igs_en_su_attempt.course_cd%TYPE
1672 
1673 /*******************************************************************************************
1674   Created By   :    Prajeesh Chandran .K
1675   Creation Date:    8-JAN-2002
1676   Purpose      :    Bug No:2174101
1677                     Added this Function to get the Key Programs for the Particular Person
1678 *******************************************************************************************/
1679 AS
1680  /*   Who           When                What
1681       stutta        24-NOV-2003         Introduced a new cursor c_term_key_prog to check the term records
1682                                         for the key program before checking the program attempt table. Term records Build  */
1683   CURSOR c_key_prog IS
1684          SELECT course_cd,
1685                 version_number
1686          FROM
1687          igs_en_stdnt_ps_att WHERE
1688          key_program='Y' AND
1689          person_id=p_person_id;
1690 
1691   CURSOR c_term_key_prog IS
1692         SELECT program_cd, program_version
1693         FROM igs_en_spa_terms
1694         WHERE person_id = p_person_id
1695         AND   term_cal_type = p_term_cal_type
1696         AND   term_sequence_number = p_term_sequence_number
1697         AND   key_program_flag = 'Y';
1698 
1699   l_key_prog      igs_en_stdnt_ps_att.course_cd%TYPE;
1700   l_key_prog_ver  igs_en_stdnt_ps_att.version_number%TYPE;
1701 
1702 BEGIN
1703 
1704   -- This Function gets the Person and finds the key_program for that particular person and returns that Key
1705   -- Program and version Number
1706 
1707   --## if the parameters are not sent withproper values it raises a error
1708 
1709   IF p_person_id IS NULL THEN
1710     FND_MESSAGE.SET_NAME('IGS','IGS_GE_INSUFFICIENT_PARAMETER');
1711     IGS_GE_MSG_STACK.ADD;
1712     p_version_number := NULL;
1713     RETURN NULL;
1714   END IF;
1715 
1716   OPEN c_term_key_prog;
1717   FETCH c_term_key_prog INTO l_key_prog, l_key_prog_ver;
1718   IF c_term_key_prog%NOTFOUND THEN
1719      OPEN c_key_prog;
1720      FETCH c_key_prog INTO l_key_prog,l_key_prog_ver;
1721      IF c_key_prog%NOTFOUND THEN
1722          p_version_number := NULL;
1723         CLOSE c_key_prog;
1724         CLOSE c_term_key_prog;
1725         RETURN NULL;
1726      END IF;
1727      CLOSE c_key_prog;
1728   END IF;
1729 
1730   CLOSE c_term_key_prog;
1731   p_version_number := l_key_prog_ver;
1732 
1733   RETURN l_key_prog;
1734 
1735 EXCEPTION
1736        WHEN OTHERS THEN
1737         IF c_key_prog%ISOPEN THEN
1738            CLOSE c_key_prog;
1739         END IF;
1740         IF c_term_key_prog%ISOPEN THEN
1741            CLOSE c_term_key_prog;
1742         END IF;
1743         p_version_number:=NULL;
1744         FND_MESSAGE.SET_NAME('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1745         FND_MESSAGE.SET_TOKEN('NAME','enrp_clc_key_prog: '||SQLERRM);
1746         IGS_GE_MSG_STACK.ADD;
1747         APP_EXCEPTION.RAISE_EXCEPTION(NULL,NULL,fnd_message.get);
1748 
1749 
1750 
1751 END enrp_clc_key_prog;
1752 
1753 PROCEDURE enrp_get_inst_latt(p_person_id                  IN  hz_parties.party_id%TYPE,
1754                              p_load_cal_type              IN  igs_ca_inst.cal_type%TYPE,
1755                              p_load_seq_number            IN  igs_ca_inst.sequence_number%TYPE,
1756                              p_attendance                 OUT NOCOPY igs_en_atd_type_load.attendance_type%TYPE,
1757                              p_credit_points              OUT NOCOPY igs_en_su_attempt.override_achievable_cp%TYPE,
1758                              p_fte                        OUT NOCOPY igs_en_su_attempt.override_achievable_cp%TYPE
1759                             )
1760 AS
1761 
1762 /*******************************************************************************************
1763   Created By   :    Prajeesh Chandran .K
1764   Creation Date:    8-JAN-2002
1765   Purpose      :    Bug No:2174101
1766                     Added this Function to get the Institution Level Attendance Type
1767                     crecit Points and Full Time Equivalent for the Person in a
1768                     load calendar
1769                     Logic for this Program:
1770                     1. First check for the existence of Key Programs
1771                        if it doesnot exists it is returned with error message
1772                     2. If it exists check it is career centric or Program Centric Model
1773                        If Career Centric Model then
1774                        a) Get all the active  Primary Programs (Active implies program_attempt_status
1775                            is ENROLLED,INACTIVE) and call the function enrp_clc_eftsu_total to get
1776                            the eftsu total for the primary programs. sum all the eftsu total
1777                            to get the total eftsu
1778                        b) If Program Centric Model then get all the active programs for the
1779                           person and call eftsu total to get the tota eftsu for each programs
1780                           sum all the eftsu to get the total eftsu
1781 
1782                      3. Call the igs_en_get_std_att procedure to get the attendance
1783                         type for the given FTE range
1784 *******************************************************************************************/
1785  /*   Who          When          What
1786       stutta       24-NOV-2003   Modified cursor c_active_cd to consider term records while
1787                                  finding out the primary program of a student. Term Records Build.
1788  */
1789  l_acad_cal_type                 igs_ca_inst.cal_type%TYPE;
1790  l_acad_ci_sequence_number       igs_ca_inst.sequence_number%TYPE;
1791  l_acad_ci_start_dt              igs_ca_inst.start_dt%TYPE;
1792  l_acad_ci_end_dt                igs_ca_inst.end_dt%TYPE;
1793  l_message_name                  VARCHAR2(100) := NULL;
1794  l_credit_points                 igs_en_su_attempt.override_achievable_cp%TYPE  := 0;
1795  l_tot_credit_points             igs_en_su_attempt.override_achievable_cp%TYPE  := 0;
1796  l_eftsu_total                   igs_en_su_attempt.override_eftsu%TYPE  := 0;
1797  l_alternate_code                igs_ca_inst.alternate_code%TYPE := NULL;
1798  l_course_cd                     igs_en_su_attempt.course_cd%TYPE;
1799  l_version_number                igs_en_su_attempt.version_number%TYPE;
1800  l_attendance_type               igs_en_atd_type_load.attendance_type%TYPE;
1801 
1802 
1803  --## CURSOR to get the Person number for the person id for message tokens
1804 
1805  CURSOR c_person IS
1806         SELECT party_number
1807         FROM hz_parties
1808         WHERE party_id=p_person_id;
1809 
1810  l_person             hz_parties.party_number%TYPE;
1811 
1812    CURSOR c_spa(cp_person_id       IGS_PE_PERSON.person_id%TYPE,
1813               cp_load_cal_type   IGS_EN_SPA_TERMS.term_cal_type%TYPE,
1814               cp_load_seq_number IGS_EN_SPA_TERMS.term_sequence_number%TYPE) IS
1815   Select sca.course_cd
1816   From   igs_en_stdnt_ps_att_all sca,
1817          igs_ps_ver_all pv
1818         WHERE  sca.person_id = cp_person_id
1819       AND    sca.course_cd = pv.course_cd
1820       AND    sca.version_number = pv.version_number
1821       AND   (
1822        (NVL(FND_PROFILE.VALUE('CAREER_MODEL_ENABLED'),'N') = 'Y' AND igs_en_spa_terms_api.get_spat_primary_prg(sca.person_id, sca.course_cd, cp_load_cal_type,cp_load_seq_number)='PRIMARY')
1823        OR
1824        (NVL(FND_PROFILE.VALUE('CAREER_MODEL_ENABLED'),'N') = 'N')
1825        );
1826 
1827 
1828   vc_spa c_spa%ROWTYPE;
1829 
1830 
1831 BEGIN
1832 
1833 --## if the parameters are not sent withproper values it raises a error
1834 
1835 IF p_load_cal_type IS NULL OR p_load_seq_number IS NULL OR p_person_id IS NULL THEN
1836   FND_MESSAGE.SET_NAME('IGS','IGS_GE_INSUFFICIENT_PARAMETER');
1837   IGS_GE_MSG_STACK.ADD;
1838   p_fte           := NULL;
1839   p_credit_points := NULL;
1840   p_attendance    := NULL;
1841   app_exception.raise_exception;
1842 END IF;
1843 
1844 --## It is a Cursor to retrive the Message tokens(Person Number) and hence
1845 --## cursor is just closed if no record exist and no error is shown
1846 
1847 OPEN c_person;
1848 FETCH c_person INTO l_person;
1849 CLOSE c_person;
1850 
1851 
1852 
1853 --## First get the Key Programs  if it doesnot exists raise a error
1854 l_course_cd := NULL;
1855 l_course_cd  := enrp_clc_key_prog(p_person_id,l_version_number,p_load_cal_type,p_load_seq_number);
1856 IF l_course_cd IS NULL THEN
1857   FND_MESSAGE.SET_NAME('IGS','IGS_EN_NO_KEY_PRG');
1858   FND_MESSAGE.SET_TOKEN('PERSON',l_person);
1859   IGS_GE_MSG_STACK.ADD;
1860   p_fte           := NULL;
1861   p_credit_points := NULL;
1862   p_attendance    := NULL;
1863   app_exception.raise_exception;
1864 END IF;
1865 
1866 --## Get the academic Calendar for the given load calendar
1867 
1868 l_alternate_code:=  Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd
1869                              (
1870                              p_load_cal_type ,
1871                              p_load_seq_number,
1872                              l_acad_cal_type ,
1873                              l_acad_ci_sequence_number,
1874                              l_acad_ci_start_dt,
1875                              l_acad_ci_end_dt ,
1876                              l_message_name
1877                              );
1878 
1879 --## If academic Calendar doesnot exists raise a error and stop the process
1880 
1881 IF l_acad_cal_type IS NULL OR l_acad_ci_sequence_number IS NULL THEN
1882   FND_MESSAGE.SET_NAME('IGS','IGS_EN_NO_ACAD_CAL');
1883   IGS_GE_MSG_STACK.ADD;
1884   p_fte           := NULL;
1885   p_credit_points := NULL;
1886   p_attendance    := NULL;
1887   app_exception.raise_exception;
1888 END IF;
1889 
1890 
1891  --loop through the program attempts related to the term records for the student
1892  -- in the passed in load cal type and sequence number
1893   FOR vc_spa IN c_spa(p_person_id, p_load_cal_type, p_load_seq_number) LOOP
1894 
1895     l_eftsu_total := l_eftsu_total +  ENRP_CLC_EFTSU_TOTAL
1896                                                 (
1897                                                 p_person_id ,
1898                                                 vc_spa.course_cd,
1899                                                 l_acad_cal_type ,
1900                                                 l_acad_ci_sequence_number,
1901                                                 p_load_cal_type ,
1902                                                 p_load_seq_number,
1903                                                'N',
1904                                                'N' ,
1905                                                 l_course_cd ,
1906                                                 l_version_number,
1907                                                 l_credit_points
1908                                                 );
1909 
1910    l_tot_credit_points := l_tot_credit_points + NVL(l_credit_points,0);
1911 
1912   END LOOP;
1913 
1914  --end of new code
1915 
1916   p_credit_points := l_tot_credit_points;
1917   p_fte           := l_eftsu_total;
1918 
1919   --## Get the the attendance type by passing the load caltype and fte
1920 
1921   l_attendance_type :=     ENRP_GET_LOAD_ATT
1922                                 (
1923                                 p_load_cal_type ,
1924                                 p_fte
1925                                 );
1926    p_attendance    := l_attendance_type;
1927 
1928 
1929 END enrp_get_inst_latt;
1930 
1931 
1932 
1933 PROCEDURE enrp_get_inst_latt_fte(p_person_id              IN  hz_parties.party_id%TYPE,
1934                              p_load_cal_type              IN  igs_ca_inst.cal_type%TYPE,
1935                              p_load_seq_number            IN  igs_ca_inst.sequence_number%TYPE,
1936                              p_attendance                 OUT NOCOPY igs_en_atd_type_load.attendance_type%TYPE,
1937                              p_credit_points              OUT NOCOPY igs_en_su_attempt.override_achievable_cp%TYPE,
1938                              p_fte                        OUT NOCOPY igs_en_su_attempt.override_achievable_cp%TYPE
1939                             )
1940 AS
1941 
1942 /*******************************************************************************************
1943   Created By   :    anilk
1944   Creation Date:    06-AUG-2003
1945   Purpose      :    Bug No# 3046897
1946                     Added this Function to get the Institution Level Attendance Type
1947                     crecit Points and Full Time Equivalent for the Person in a
1948                     load calendar
1949                 This procedure is called from ViewAcademicHistoryAMImpl.java, getFteValue()
1950 *******************************************************************************************/
1951 /*   Who          When          What
1952      stutta       24-NOV-2003   Modified cursor c_active_cd to consider term records while
1953                                 finding out the primary program of a student. Term Records Build.
1954 */
1955 
1956  cst_enrolled    CONSTANT        VARCHAR2(10) := 'ENROLLED';
1957  cst_inactive    CONSTANT        VARCHAR2(10) := 'INACTIVE';
1958  cst_discontin   CONSTANT        VARCHAR2(10) := 'DISCONTIN';
1959  cst_completed   CONSTANT        VARCHAR2(10) := 'COMPLETED';
1960  l_acad_cal_type                 igs_ca_inst.cal_type%TYPE;
1961  l_acad_ci_sequence_number       igs_ca_inst.sequence_number%TYPE;
1962  l_acad_ci_start_dt              igs_ca_inst.start_dt%TYPE;
1963  l_acad_ci_end_dt                igs_ca_inst.end_dt%TYPE;
1964  l_message_name                  VARCHAR2(100) := NULL;
1965  l_credit_points                 igs_en_su_attempt.override_achievable_cp%TYPE  := 0;
1966  l_tot_credit_points             igs_en_su_attempt.override_achievable_cp%TYPE  := 0;
1967  l_eftsu_total                   igs_en_su_attempt.override_eftsu%TYPE  := 0;
1968  l_alternate_code                igs_ca_inst.alternate_code%TYPE := NULL;
1969  l_course_cd                     igs_en_su_attempt.course_cd%TYPE;
1970  l_version_number                igs_en_su_attempt.version_number%TYPE;
1971  l_attendance_type               igs_en_atd_type_load.attendance_type%TYPE;
1972 
1973  CURSOR c_active_cd(l_career VARCHAR2) IS
1974         SELECT course_cd,
1975                igs_en_spa_terms_api.get_spat_program_version(p_person_id, course_cd,
1976                p_load_cal_type, p_load_seq_number)
1977 
1978         FROM igs_en_stdnt_ps_att sca
1979         WHERE person_id            = p_person_id AND
1980               --anilk, Bug# 3046897
1981               course_attempt_status IN (cst_enrolled, cst_inactive, cst_discontin, cst_completed) AND
1982               ((l_career            ='Y' AND
1983                (EXISTS (SELECT 'x' FROM igs_en_spa_terms spat
1984                         WHERE spat.person_id = sca.person_id
1985                         AND   spat.program_cd = sca.course_cd
1986                         AND   spat.term_cal_type = p_load_cal_type
1987                         AND   spat.term_sequence_number = p_load_seq_number)
1988                  OR
1989                 (sca.primary_program_type='PRIMARY' AND
1990                  NOT EXISTS (SELECT 'x'
1991                             FROM igs_en_spa_terms spat, igs_ps_ver pv1, igs_ps_ver pv2
1992                             WHERE spat.person_id = sca.person_id
1993                             AND   spat.program_cd = pv1.course_cd
1994                             AND   spat.program_version = pv1.version_number
1995                             AND   sca.course_cd = pv2.course_cd
1996                             AND   sca.version_number = pv2.version_number
1997                             AND   pv1.course_type = pv2.course_type
1998                             AND   spat.term_cal_type = p_load_cal_type
1999                             AND   spat.term_sequence_number = p_load_seq_number)
2000                 )
2001                )
2002               )OR
2003               (l_career            ='N'
2004               ));
2005 
2006  l_active_cd          c_active_cd%ROWTYPE;
2007 
2008 BEGIN
2009 
2010 --## First get the Key Programs  if it doesnot exists raise a error
2011 
2012 l_course_cd  := enrp_clc_key_prog(p_person_id,l_version_number,p_load_cal_type,p_load_seq_number);
2013 IF l_course_cd IS NULL THEN
2014   p_fte           := NULL;
2015   p_credit_points := NULL;
2016   p_attendance    := NULL;
2017   RETURN;
2018 END IF;
2019 
2020 --## Get the academic Calendar for the given load calendar
2021 l_alternate_code:=  Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd
2022                              (
2023                              p_load_cal_type ,
2024                              p_load_seq_number,
2025                              l_acad_cal_type ,
2026                              l_acad_ci_sequence_number,
2027                              l_acad_ci_start_dt,
2028                              l_acad_ci_end_dt ,
2029                              l_message_name
2030                              );
2031 
2032 --## If academic Calendar doesnot exists raise a error and stop the process
2033 IF l_acad_cal_type IS NULL OR l_acad_ci_sequence_number IS NULL THEN
2034   p_fte           := NULL;
2035   p_credit_points := NULL;
2036   p_attendance    := NULL;
2037   RETURN;
2038 END IF;
2039 
2040 --## Check for the type of Model whether career centric or Program Centric
2041  IF NVL(FND_PROFILE.VALUE('CAREER_MODEL_ENABLED'),'N')='N' THEN
2042   OPEN c_active_cd('N');
2043   FETCH c_active_cd INTO l_active_cd;
2044   IF c_active_cd%NOTFOUND THEN
2045      close c_active_cd;
2046      p_fte           := NULL;
2047      p_credit_points := NULL;
2048      p_attendance    := NULL;
2049      RETURN;
2050   END IF;
2051 
2052  --## Loop thru all the Primary programs and get the total eftsu
2053   LOOP
2054     l_eftsu_total := l_eftsu_total +  ENRP_CLC_EFTSU_TOTAL
2055                                                 (
2056                                                 p_person_id ,
2057                                                 l_active_cd.course_cd,
2058                                                 l_acad_cal_type ,
2059                                                 l_acad_ci_sequence_number,
2060                                                 p_load_cal_type ,
2061                                                 p_load_seq_number,
2062                                                'N',
2063                                                'N' ,
2064                                                 l_course_cd ,
2065                                                 l_version_number,
2066                                                 l_credit_points
2067                                                 );
2068    l_tot_credit_points := l_tot_credit_points + NVL(l_credit_points,0);
2069    FETCH c_active_cd INTO l_active_cd;
2070     IF c_active_cd%NOTFOUND THEN
2071        CLOSE c_active_cd;
2072        EXIT;
2073     END IF;
2074   END LOOP;
2075 ELSE
2076  --##Incase of Career Centric check if Primary program is defined
2077   OPEN c_active_cd('Y');
2078   FETCH c_active_cd INTO l_active_cd;
2079   IF c_active_cd%NOTFOUND THEN
2080      close c_active_cd;
2081      p_fte           := NULL;
2082      p_credit_points := NULL;
2083      p_attendance    := NULL;
2084      RETURN;
2085   END IF;
2086 
2087   --## Loop through all the programs and get the eftsu total
2088   LOOP
2089     l_eftsu_total := l_eftsu_total + ENRP_CLC_EFTSU_TOTAL
2090                                                    (
2091                                                     p_person_id ,
2092                                                     l_active_cd.course_cd,
2093                                                     l_acad_cal_type ,
2094                                                     l_acad_ci_sequence_number,
2095                                                     p_load_cal_type ,
2096                                                     p_load_seq_number,
2097                                                    'N',
2098                                                    'N' ,
2099                                                     l_course_cd ,
2100                                                     l_version_number,
2101                                                     l_credit_points
2102                                                     );
2103    l_tot_credit_points := l_tot_credit_points + NVL(l_credit_points,0);
2104    FETCH c_active_cd INTO l_active_cd;
2105     IF c_active_cd%NOTFOUND THEN
2106        CLOSE c_active_cd;
2107        EXIT;
2108     END IF;
2109   END LOOP;
2110 END IF;
2111 
2112   p_credit_points := l_tot_credit_points;
2113   p_fte           := l_eftsu_total;
2114   --## Get the the attendance type by passing the load caltype and fte
2115   l_attendance_type :=     ENRP_GET_LOAD_ATT  ( p_load_cal_type ,
2116                                                 p_fte  );
2117    p_attendance    := l_attendance_type;
2118 
2119 END enrp_get_inst_latt_fte;
2120 
2121 
2122 PROCEDURE enrp_clc_cp_upto_tp_start_dt
2123                            (
2124                               p_person_id             IN  NUMBER,
2125                               p_load_cal_type         IN  VARCHAR2,
2126                               p_load_sequence_number  IN  NUMBER,
2127                               p_include_research_ind  IN  VARCHAR2,
2128                               p_tp_sd_cut_off_date    IN  DATE ,
2129                               p_credit_points         OUT NOCOPY NUMBER  )  AS
2130 /**********************************************************************************************************************
2131   Created By   :    kkillams
2132   Creation Date:    09-MAY-2002
2133   Purpose      :    Bug No:2352142
2134                     Calculate Student's Total Credit Points with in a given load calendar when load calendar's teaching
2135                     calendar instances start dates are less than or equal to given cut off date (Point in time)
2136                     Note :This procedure is designed only for Career Model, will not work for ProgramCentric Model.
2137 ***********************************************************************************************************************/
2138 /*   Who          When          What
2139      stutta       24-NOV-2003   Modified cursor cur_stud_ua_acad to consider term records while
2140                                 finding out the primary program of a student. Term Records Build.
2141      ckasu      24-Feb-2006    Modified cur_stud_ua_acad curson in for perf bug #5059308
2142  */
2143 
2144 --added by ckasu as a part of bug#5059308
2145 --Fetches the Teach calendar details
2146 CURSOR c_get_teach_cal_dtls(cp_load_cal_type igs_ca_inst.cal_type%TYPE,
2147                             cp_load_seq_num igs_ca_inst.sequence_number%TYPE,
2148                             cp_tp_sd_cut_off_date DATE) IS
2149 SELECT teach_cal_type,
2150        teach_ci_sequence_number
2151 FROM  IGS_CA_LOAD_TO_TEACH_V  lt
2152 WHERE  lt.load_cal_type           = cp_load_cal_type
2153 AND    lt.load_ci_sequence_number = cp_load_seq_num
2154 AND    lt.teach_start_dt          <= cp_tp_sd_cut_off_date
2155 ORDER BY teach_cal_type ASC,teach_ci_sequence_number ASC;
2156 
2157 --modified by ckasu as a part of bug#5059308
2158 CURSOR cur_stud_ua_acad(cp_teach_cal_type igs_ca_inst.cal_type%TYPE,
2159                         cp_teach_seq_num igs_ca_inst.sequence_number%TYPE) IS
2160 
2161                         SELECT   sua.person_id,
2162                                     sua.course_cd,
2163                                     sua.unit_cd,
2164                                     sua.version_number,
2165                                     sua.cal_type,
2166                                     sua.ci_sequence_number,
2167                                     sua.override_enrolled_cp,
2168                                     sua.override_eftsu,
2169                                     sua.administrative_unit_status,
2170                                     sua.unit_attempt_status,
2171                                     sua.discontinued_dt,
2172                                     sua.uoo_id,
2173                                     sua.no_assessment_ind
2174                             FROM    IGS_EN_SU_ATTEMPT sua,
2175                                     IGS_EN_STDNT_PS_ATT sca,
2176                                     IGS_PS_UNIT_VER uv
2177                            WHERE
2178                                    sca.person_id             = p_person_id   AND
2179                                    sca.person_id             = sua.person_id AND
2180                                    sca.course_cd             = sua.course_cd AND
2181                                    (   EXISTS (SELECT 'x' FROM igs_en_spa_terms spat
2182                                                 WHERE spat.person_id = sca.person_id
2183                                                 AND   spat.program_cd = sca.course_cd
2184                                                 AND   spat.term_cal_type = p_load_cal_type
2185                                                 AND   spat.term_sequence_number = p_load_sequence_number)
2186                                        OR
2187                                        (sca.primary_program_type='PRIMARY' AND
2188                                         NOT EXISTS (SELECT 'x'
2189                                                  FROM igs_en_spa_terms spat, igs_ps_ver pv1, igs_ps_ver pv2
2190                                                  WHERE spat.person_id = sca.person_id
2191                                                  AND   spat.program_cd = pv1.course_cd
2192                                                  AND   spat.program_version = pv1.version_number
2193                                                  AND   sca.course_cd = pv2.course_cd
2194                                                  AND   sca.version_number = pv2.version_number
2195                                                  AND   pv1.course_type = pv2.course_type
2196                                                  AND   spat.term_cal_type = p_load_cal_type
2197                                                  AND   spat.term_sequence_number = p_load_sequence_number)
2198                                        )
2199                                    )   AND
2200                                    sua.unit_attempt_status   IN ('ENROLLED','DISCONTIN','COMPLETED','WAITLISTED') AND
2201                                    uv.unit_cd                = sua.unit_cd   AND
2202                                    uv.version_number         = sua.version_number AND
2203                                   (NVL(p_include_research_ind,'N')= 'Y' OR  uv.research_unit_ind       = 'N') AND
2204                                    sua.cal_type  = cp_teach_cal_type AND
2205                                    sua.ci_sequence_number = cp_teach_seq_num;
2206 
2207 lv_sua_cp                  NUMBER(10) := 0;
2208 lv_return_eftsu            NUMBER(10);
2209 l_audit_cp              IGS_PS_USEC_CPS.billing_credit_points%TYPE;
2210 l_billing_cp            IGS_PS_USEC_CPS.billing_hrs%TYPE;
2211 l_enrolled_cp   IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
2212 BEGIN
2213 lv_sua_cp := 0;
2214 FOR l_get_teach_cal_dtls IN c_get_teach_cal_dtls(p_load_cal_type,p_load_sequence_number,p_tp_sd_cut_off_date) LOOP
2215 
2216         FOR rec_stud_ua_acad IN cur_stud_ua_acad(l_get_teach_cal_dtls.teach_cal_type,l_get_teach_cal_dtls.teach_ci_sequence_number)
2217         LOOP
2218              IF enrp_get_load_incur(
2219                              rec_stud_ua_acad.cal_type,
2220                              rec_stud_ua_acad.ci_sequence_number,
2221                              rec_stud_ua_acad.discontinued_dt,
2222                              rec_stud_ua_acad.administrative_unit_status ,
2223                              rec_stud_ua_acad.unit_attempt_status,
2224                              rec_stud_ua_acad.no_assessment_ind,
2225                              p_load_cal_type,
2226                              p_load_sequence_number,
2227                              -- anilk, Audit special fee build
2228                              NULL, -- for p_uoo_id
2229                              'N') = 'Y' THEN
2230 
2231                     lv_sua_cp := lv_sua_cp + enrp_clc_sua_load(
2232                                                                 rec_stud_ua_acad.unit_cd,
2233                                                                 rec_stud_ua_acad.version_number,
2234                                                                 rec_stud_ua_acad.cal_type,
2235                                                                 rec_stud_ua_acad.ci_sequence_number,
2236                                                                 p_load_cal_type,
2237                                                                 p_load_sequence_number,
2238                                                                 rec_stud_ua_acad.override_enrolled_cp,
2239                                                                 rec_stud_ua_acad.override_eftsu,
2240                                                                 lv_return_eftsu,
2241                                                                 rec_stud_ua_acad.uoo_id,
2242                                                                 -- anilk, Audit special fee build
2243                                                                 'N',
2244                                                                 l_audit_cp,
2245                                                                 l_billing_cp,
2246                                                                 l_enrolled_cp);
2247             END IF;
2248         END LOOP;
2249 END LOOP;-- end loop for l_get_teach_cal_dtls
2250 p_credit_points := lv_sua_cp;
2251 
2252 END enrp_clc_cp_upto_tp_start_dt;
2253 
2254 FUNCTION  enrp_get_prg_att_type
2255                            (
2256                               p_person_id             IN  NUMBER,
2257                               p_course_cd             IN  VARCHAR2,
2258                               p_cal_type              IN  VARCHAR2,
2259                               p_sequence_number       IN  NUMBER
2260                            ) RETURN VARCHAR2 AS
2261 /**********************************************************************************************************************
2262   Created By   :    msrinivi
2263   Creation Date:    28-Oct-2002
2264   Purpose      :    Order Documents Build
2265                     Attendance type for a student, course and academic or load calendar
2266 ***********************************************************************************************************************/
2267 CURSOR c_cal_cat IS
2268 SELECT  S_CAL_CAT
2269 FROM    igs_ca_type
2270 WHERE   cal_type = p_cal_type;
2271 
2272 l_cal_cat igs_ca_type.s_cal_cat%TYPE;
2273 
2274 l_load_cal_type   igs_ca_inst.cal_type%TYPE;
2275 l_load_ci_seq_num igs_ca_inst.sequence_number%TYPE;
2276 
2277 l_acad_cal_type   igs_ca_inst.cal_type%TYPE;
2278 l_acad_ci_seq_num igs_ca_inst.sequence_number%TYPE;
2279 
2280 l_acad_ci_start_dt DATE;
2281 l_acad_ci_end_dt DATE;
2282 l_message_name     VARCHAR2(1000);
2283 
2284 
2285 l_course_cd       igs_ps_ver.course_cd%TYPE;
2286 l_version_number   igs_ps_ver.version_number%TYPE;
2287 
2288 l_credit_points NUMBER :=0;
2289 
2290 l_eftsu_total   NUMBER :=0;
2291 
2292 l_attendance_type IGS_EN_ATD_TYPE_ALL.ATTENDANCE_TYPE%TYPE;
2293 
2294 lRet_for_cal VARCHAR2(100);
2295 
2296 BEGIN
2297 
2298 
2299 
2300 OPEN  c_cal_cat;
2301 FETCH c_cal_cat INTO l_cal_cat;
2302 CLOSE c_cal_cat;
2303 
2304 IF l_cal_cat = 'ACADEMIC' THEN
2305   l_acad_cal_type    :=  p_cal_type         ;
2306   l_acad_ci_seq_num  :=  p_sequence_number  ;
2307 
2308   get_latest_load_for_acad_cal(
2309   p_acad_cal_type           => p_cal_type       ,
2310   p_acad_ci_sequence_number => p_sequence_number,
2311   p_load_cal_type           => l_load_cal_type ,
2312   p_load_ci_sequence_number => l_load_ci_seq_num
2313   );
2314 
2315 
2316 END IF;
2317 
2318 IF l_cal_cat = 'LOAD' THEN
2319 
2320   l_load_cal_type   :=   p_cal_type         ;
2321   l_load_ci_seq_num :=   p_sequence_number  ;
2322 
2323 lRet_for_cal := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd
2324          (
2325          p_cal_type         ,
2326          p_sequence_number  ,
2327          l_acad_cal_type    ,
2328          l_acad_ci_seq_num   ,
2329          l_acad_ci_start_dt,
2330          l_acad_ci_end_dt ,
2331          l_message_name
2332          );
2333 END IF;
2334 l_course_cd  := enrp_clc_key_prog(p_person_id,l_version_number,l_load_cal_type
2335                                                 ,l_load_ci_seq_num );
2336 
2337     l_eftsu_total := l_eftsu_total + ENRP_CLC_EFTSU_TOTAL
2338                                                    (
2339                                                     p_person_id ,
2340                                                     p_course_cd,
2341                                                     l_acad_cal_type    ,
2342                                                     l_acad_ci_seq_num    ,
2343                             l_load_cal_type ,
2344                             l_load_ci_seq_num ,
2345                                                    'N',
2346                                                    'N' ,
2347                                                     l_course_cd ,
2348                                                     l_version_number,
2349                                                     l_credit_points
2350                                                     );
2351 
2352   --## Get the the attendance type by passing the load caltype and fte
2353 
2354   l_attendance_type :=     ENRP_GET_LOAD_ATT
2355                                 (
2356                                   l_load_cal_type ,
2357                                   l_eftsu_total
2358                                 );
2359 RETURN l_attendance_type;
2360 
2361 END enrp_get_prg_att_type;
2362 
2363 
2364 PROCEDURE get_latest_load_for_acad_cal
2365 (
2366   p_acad_cal_type      IN igs_ca_inst.cal_type%TYPE,
2367   p_acad_ci_sequence_number IN igs_ca_inst.sequence_number%TYPE,
2368   p_load_cal_type      OUT NOCOPY  igs_ca_inst.cal_type%TYPE,
2369   p_load_ci_sequence_number OUT NOCOPY igs_ca_inst.sequence_number%TYPE
2370  )
2371  AS
2372 /**********************************************************************************************************************
2373   Created By   :    msrinivi
2374   Creation Date:    28-Oct-2002
2375   Purpose      :    Order Documents Build
2376                     Fetches the latest load under the given given academic calendar
2377 ***********************************************************************************************************************/
2378 CURSOR c_latest_load IS
2379 SELECT rel.SUB_CAL_TYPE    , rel.SUB_CI_SEQUENCE_NUMBER , NVL(dai.absolute_val, cai.start_dt) load_effective_dt
2380 FROM  igs_ca_inst_rel rel,
2381       igs_ca_da_inst dai,
2382       igs_en_cal_conf conf,
2383       igs_ca_inst cai
2384 WHERE
2385     rel.SUB_CAL_TYPE           =     dai.CAL_TYPE
2386 AND rel.SUB_CI_SEQUENCE_NUMBER =     dai.CI_SEQUENCE_NUMBER
2387 AND cai.CAL_TYPE               =     rel.SUB_CAL_TYPE
2388 AND cai.SEQUENCE_NUMBER        =     rel.SUB_CI_SEQUENCE_NUMBER
2389 AND dai.DT_ALIAS               =     conf.LOAD_EFFECT_DT_ALIAS
2390 AND NVL(dai.absolute_val, cai.start_dt)         < SYSDATE
2391 AND SUP_CAL_TYPE               =     p_acad_cal_type
2392 AND SUP_CI_SEQUENCE_NUMBER     =     p_acad_ci_sequence_number
2393 ORDER BY 3 DESC;
2394 
2395 l_load_cal_type igs_ca_inst.cal_type%TYPE;
2396 l_load_ci_sequence_number   igs_ca_inst.sequence_number%TYPE ;
2397 l_load_effective_dt DATE;
2398 
2399  BEGIN
2400 
2401 OPEN  c_latest_load;
2402 FETCH c_latest_load INTO l_load_cal_type, l_load_ci_sequence_number,l_load_effective_dt;
2403 CLOSE c_latest_load;
2404 
2405 p_load_cal_type           :=  l_load_cal_type;
2406 p_load_ci_sequence_number :=  l_load_ci_sequence_number;
2407 
2408 END get_latest_load_for_acad_cal;
2409 
2410 FUNCTION enrp_get_prg_load_cp(p_person_id             IN  NUMBER,
2411                               p_course_cd             IN VARCHAR2,
2412                               p_cal_type              IN  VARCHAR2,
2413                               p_sequence_number       IN  NUMBER) RETURN VARCHAR2 AS
2414 
2415 /**********************************************************************************************************************
2416   Created By   :    svanukur
2417   Creation Date:    2-dec-2005
2418   Purpose      :    wrapper over enrp_get_prg_eftsu_cp to get the CP for a student for a given term and program
2419 ***********************************************************************************************************************/
2420 L_EFTSU_TOTAL  NUMBER := 0;
2421 L_CREDIT_POINTS NUMBER := 0;
2422 
2423 begin
2424 
2425 enrp_get_prg_eftsu_cp(
2426                               p_person_id            ,
2427                               p_course_cd             ,
2428                               p_cal_type             ,
2429                               p_sequence_number       ,
2430                               L_EFTSU_TOTAL           ,
2431                               L_CREDIT_POINTS         );
2432 return L_CREDIT_POINTS;
2433 exception
2434 when others then
2435 return null;
2436 
2437 end;
2438 
2439 
2440 PROCEDURE enrp_get_prg_eftsu_cp
2441                            (
2442                               p_person_id             IN  NUMBER,
2443                               p_course_cd             IN VARCHAR2,
2444                               p_cal_type              IN  VARCHAR2,
2445                               p_sequence_number       IN  NUMBER,
2446                               P_EFTSU_TOTAL           OUT NOCOPY NUMBER,
2447                               P_CREDIT_POINTS         OUT NOCOPY NUMBER
2448                            ) AS
2449 /**********************************************************************************************************************
2450   Created By   :    amuthu
2451   Creation Date:    14-NOV-2002
2452   Purpose      :    SS Worksheet Redesign
2453 ***********************************************************************************************************************/
2454 CURSOR c_cal_cat IS
2455 SELECT  S_CAL_CAT
2456 FROM    igs_ca_type
2457 WHERE   cal_type = p_cal_type;
2458 
2459 l_cal_cat igs_ca_type.s_cal_cat%TYPE;
2460 l_load_cal_type   igs_ca_inst.cal_type%TYPE;
2461 l_load_ci_seq_num igs_ca_inst.sequence_number%TYPE;
2462 l_acad_cal_type   igs_ca_inst.cal_type%TYPE;
2463 l_acad_ci_seq_num igs_ca_inst.sequence_number%TYPE;
2464 l_acad_ci_start_dt DATE;
2465 l_acad_ci_end_dt DATE;
2466 lRet_for_cal VARCHAR2(100);
2467 
2468 l_message_name     VARCHAR2(1000);
2469 
2470 l_course_cd       igs_ps_ver.course_cd%TYPE;
2471 l_version_number   igs_ps_ver.version_number%TYPE;
2472 
2473 
2474 BEGIN
2475 
2476 
2477 
2478 OPEN  c_cal_cat;
2479 FETCH c_cal_cat INTO l_cal_cat;
2480 CLOSE c_cal_cat;
2481 
2482 -- if the passed in calendar is academic the determine the load calendar
2483 IF l_cal_cat = 'ACADEMIC' THEN
2484   l_acad_cal_type    :=  p_cal_type         ;
2485   l_acad_ci_seq_num  :=  p_sequence_number  ;
2486 
2487   get_latest_load_for_acad_cal(
2488   p_acad_cal_type           => p_cal_type       ,
2489   p_acad_ci_sequence_number => p_sequence_number,
2490   p_load_cal_type           => l_load_cal_type ,
2491   p_load_ci_sequence_number => l_load_ci_seq_num
2492   );
2493 
2494 
2495 END IF;
2496 
2497 -- if the passed in calendar is load calendar then find the Academic calendar
2498 IF l_cal_cat = 'LOAD' THEN
2499 
2500   l_load_cal_type   :=   p_cal_type         ;
2501   l_load_ci_seq_num :=   p_sequence_number  ;
2502 
2503 lRet_for_cal := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd
2504          (
2505          p_cal_type         ,
2506          p_sequence_number  ,
2507          l_acad_cal_type    ,
2508          l_acad_ci_seq_num   ,
2509          l_acad_ci_start_dt,
2510          l_acad_ci_end_dt ,
2511          l_message_name
2512          );
2513 END IF;
2514 
2515 l_course_cd  := enrp_clc_key_prog(p_person_id,l_version_number,l_load_cal_type ,
2516                                                        l_load_ci_seq_num);
2517 
2518 -- calculate the total EFTSU and Credit Points by making a call to ENRP_CLC_EFTSU_TOTAL
2519 
2520     P_EFTSU_TOTAL :=ENRP_CLC_EFTSU_TOTAL
2521                       (
2522                        p_person_id ,
2523                        p_course_cd,
2524                        l_acad_cal_type    ,
2525                        l_acad_ci_seq_num    ,
2526                        l_load_cal_type ,
2527                        l_load_ci_seq_num ,
2528                        'N',
2529                        'N' ,
2530                        l_course_cd ,
2531                        l_version_number,
2532                        P_CREDIT_POINTS
2533                        );
2534 
2535 
2536 
2537   END enrp_get_prg_eftsu_cp;
2538 
2539 -- Function to calculate the Institutional Level Attendance Type
2540 
2541 FUNCTION enrp_get_inst_attendance(
2542                           p_person_id        IN  hz_parties.party_id%TYPE,
2543                           p_load_cal_type    IN  igs_ca_inst.cal_type%TYPE,
2544                           p_load_seq_number  IN  igs_ca_inst.sequence_number%TYPE
2545                           ) RETURN VARCHAR2 AS
2546 
2547  l_attendance    igs_en_atd_type_load.attendance_type%TYPE;
2548  l_credit_points igs_en_su_attempt.override_achievable_cp%TYPE;
2549  l_fte           igs_en_su_attempt.override_achievable_cp%TYPE;
2550 
2551 BEGIN
2552 
2553 enrp_get_inst_latt(p_person_id      => p_person_id ,
2554                  p_load_cal_type    => p_load_cal_type,
2555                  p_load_seq_number  => p_load_seq_number,
2556                  p_attendance       => l_attendance,
2557                  p_credit_points    => l_credit_points,
2558                  p_fte              => l_fte
2559                 );
2560 
2561   RETURN l_attendance;
2562 
2563 EXCEPTION
2564   WHEN OTHERS THEN
2565   -- Supressing any exception raised and returning NULL, as this function is called from a View
2566     RETURN NULL;
2567 
2568 END enrp_get_inst_attendance;
2569 
2570 -- Function to calculate the Institutional Level Attendance Type
2571 FUNCTION enrp_get_inst_cp(
2572                           p_person_id                  IN  hz_parties.party_id%TYPE,
2573                           p_load_cal_type              IN  igs_ca_inst.cal_type%TYPE,
2574                           p_load_seq_number            IN  igs_ca_inst.sequence_number%TYPE
2575                           ) RETURN VARCHAR2 AS
2576 
2577  l_attendance    igs_en_atd_type_load.attendance_type%TYPE;
2578  l_credit_points igs_en_su_attempt.override_achievable_cp%TYPE;
2579  l_fte           igs_en_su_attempt.override_achievable_cp%TYPE;
2580 
2581 BEGIN
2582 
2583 enrp_get_inst_latt(p_person_id      => p_person_id ,
2584                  p_load_cal_type    => p_load_cal_type,
2585                  p_load_seq_number  => p_load_seq_number,
2586                  p_attendance       => l_attendance,
2587                  p_credit_points    => l_credit_points,
2588                  p_fte              => l_fte
2589                 );
2590 
2591   RETURN l_credit_points;
2592 
2593 EXCEPTION
2594   WHEN OTHERS THEN
2595   -- Supressing any exception raised and returning NULL, as this function is called from a View
2596     RETURN NULL;
2597 
2598 END enrp_get_inst_cp;
2599 
2600 -- get_term_credits: Gets the total credits for the given person, program and term.
2601 FUNCTION get_term_credits ( p_n_person_id IN NUMBER,
2602                             p_c_program IN VARCHAR2,
2603                             p_c_load_cal IN VARCHAR2,
2604                             p_n_load_seq_num IN NUMBER,
2605 			    p_c_acad_cal IN VARCHAR2,
2606 			    p_c_acad_seq_num IN NUMBER)
2607 RETURN NUMBER IS
2608 
2609     CURSOR c_total_swap_credits ( cp_n_perosn_id IN NUMBER,
2610                                   cp_c_program IN VARCHAR2,
2611 				  cp_c_load_cal IN VARCHAR2,
2612 				  cp_n_load_seq_num IN NUMBER) IS
2613     SELECT NVL(SUM(igs_ss_enr_details.get_apor_credits ( uoo_id, override_enrolled_cp,ca.load_cal_type,ca.load_ci_sequence_number)),0) apor_cp
2614     FROM   IGS_EN_SU_ATTEMPT sua,
2615            IGS_CA_TEACH_TO_LOAD_V ca
2616     WHERE  sua.unit_attempt_status = 'UNCONFIRM'
2617     AND    sua.person_id = cp_n_perosn_id
2618     AND    sua.course_cd = cp_c_program
2619     AND    sua.ss_source_ind = 'S'
2620     AND    sua.cal_type = ca.teach_cal_type
2621     AND    sua.ci_sequence_number = ca.teach_ci_sequence_number
2622     AND    ca.load_cal_type = cp_c_load_cal
2623     AND    ca.load_ci_sequence_number = cp_n_load_seq_num;
2624 
2625   l_n_schd_credits NUMBER; -- Total aportioned credits for given person and term in an academic year
2626   l_n_credits NUMBER;      -- Total aportioned credit
2627 
2628 BEGIN
2629 
2630    -- Getting total aportioned credits for a student in a term (Schedule credits for this term for the student).
2631    l_n_schd_credits := enrp_clc_load_total(p_person_id => p_n_person_id,
2632                                            p_course_cd => p_c_program,
2633                                            p_acad_cal_type => p_c_acad_cal,
2634                                            p_acad_sequence_number => p_c_acad_seq_num,
2635                                            p_load_cal_type => p_c_load_cal,
2636                                            p_load_sequence_number => p_n_load_seq_num);
2637 
2638    -- Getting total aportioned credits for the unit section added as a part of Swap.
2639    OPEN c_total_swap_credits ( p_n_person_id, p_c_program, p_c_load_cal, p_n_load_seq_num);
2640    FETCH c_total_swap_credits INTO l_n_credits;
2641    CLOSE c_total_swap_credits;
2642 
2643    RETURN  NVL(l_n_schd_credits,0) + NVL(l_n_credits,0);
2644 
2645 END get_term_credits;
2646 
2647 
2648 END Igs_En_Prc_Load;