DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_PR_CP_GPA

Source


1 PACKAGE BODY IGS_PR_CP_GPA AS
2 /* $Header: IGSPR32B.pls 120.11 2006/07/07 05:28:26 swaghmar ship $ */
3 
4 /*
5   Created By : prchandr,Nishikanth,Rajesh
6   Created On : 24-NOV-2001
7   Purpose :
8   Known limitations, enhancements or remarks :
9   Change History :
10   Who      When        What
11 
12   nalkumar 22-Apr-2004 Modified get_cp_stats, get_gpa_stats, get_sua_gpa, get_sua_cp and get_sua_all
13                        procedures and added p_use_released_grade parameter.
14                        This is to fix Bug# 3547126
15   ddey     27-Oct-2003 Changes are done, so that the message stack is not initilized.(Bug # 3163305)
16   smanglm  06-Oct-2003 bug 3161343
17                        Consider all Outcomes for the Attempted Credit Points
18            including WITHDRAWN in get_sua_stats
19   smanglm  10-Jul-2003 changed get_all_stats for If no value is found for
20                        STORED stats the function should then return null
21   jhanda   28-May-2003 Changed gpa , gpa_quality points , gpa_credit_points
22                        procedure parameter types.
23   anilk    27-Dec-2002 Removed prefixed apps in the fnd calls. Bug# 2413841
24                        ex: apps.fnd_message.setname --> fnd_message.setname
25   prraj    18-Feb-2002 Removed parameter p_uc_achievable_credit_points from
26                        the parameter list of procedures get_cp and get_gpa.
27                        Also removed the functionality to obtain the achievable
28                        credit points from the unit section level (Bug# 2224366)
29   kdande   20-Sep-2002 Removed the references to columns progression_ind and
30                        fin_aid_ind from the c_org_stat cursor and c_inst_stat
31                        cursor for Bug# 2560160 in get_stat_dtls and
32                        get_unitstat_dtls procedures.
33                        Removed all the default values from the program
34                        units' parameters and replaced DEFAULT with := in the
35                        declaration sections of the program units.
36   prchandr 16-JUL-2002 Bug No. 2463175  Removed package and package body
37                        mismatch by adding default FND_API.G_TRUE FOR get_sua_cp
38   nalkumar 05-Dec-2002 Modified get_stat_dtls procedure as per the Bug# 2685741
39   jhanda   19-Dec-2002 Bug Fix 2707516 wrong GPA being calculated, changes
40                        specified in Bug Description in Bug DB.
41   kdande   26-Jul-2004 Changed the of get_sua_stats to return proper value for
42                        attempted_cp instead of NULL in those cases where the
43                        Student's Unit Attempt Outcome is not available.
44   jhanda   25-feb-2005     Bug 3843525 Added parameter p_enrolled_cp to GET_SUA_STATS
45   swaghmar 06-Jun-2005 Bug 4327987 Added chk_sua_ref_cd function
46   (reverse chronological order - newest change first)
47   jhanda   20-June-05   Build 4327991 -- check reference codes for adv standing units
48   swaghmar 15-Sep-05	Bug 4491456 - Modified the signature
49 */
50 --
51 -- Forward Declaration of Local procedures
52 --
53   PROCEDURE get_stat_dtls(
54     p_person_id         IN            igs_en_stdnt_ps_att.person_id%TYPE,
55     p_course_cd         IN            igs_en_stdnt_ps_att.course_cd%TYPE,
56     p_system_stat       IN            VARCHAR2,
57     p_cumulative_ind    IN            VARCHAR2,
58     p_stat_type         IN OUT NOCOPY igs_pr_stat_type.stat_type%TYPE,
59     p_org_unit_cd       OUT NOCOPY    igs_pr_org_stat.org_unit_cd%TYPE,
60     p_include_std_ind   OUT NOCOPY    igs_pr_org_stat.include_standard_ind%TYPE,
61     p_include_local_ind OUT NOCOPY    igs_pr_org_stat.include_local_ind%TYPE,
62     p_include_other_ind OUT NOCOPY    igs_pr_org_stat.include_other_ind%TYPE,
63     p_derivation        OUT NOCOPY    igs_pr_stat_type.derivation%TYPE,
64     p_init_msg_list     IN            VARCHAR2,
65     p_return_status     OUT NOCOPY    VARCHAR2,
66     p_msg_count         OUT NOCOPY    NUMBER,
67     p_msg_data          OUT NOCOPY    VARCHAR2);
68 
69   FUNCTION chk_unit_ref_cd(
70     p_unit_cd             IN            igs_ps_unit_ver.unit_cd%TYPE,
71     p_unit_version_number IN            igs_ps_unit_ver.version_number%TYPE,
72     p_org_unit_cd         IN            igs_pr_org_stat.org_unit_cd%TYPE,
73     p_stat_type           IN            igs_pr_stat_type.stat_type%TYPE,
74     p_init_msg_list       IN            VARCHAR2,
75     p_return_status       OUT NOCOPY    VARCHAR2,
76     p_msg_count           OUT NOCOPY    NUMBER,
77     p_msg_data            OUT NOCOPY    VARCHAR2)
78     RETURN VARCHAR2;
79 
80     FUNCTION chk_sua_ref_cd(
81     P_person_id IN igs_en_su_attempt_ALL.person_id%TYPE,
82     P_course_cd IN igs_en_su_attempt_ALL.course_cd%TYPE,
83     P_uoo_id IN  NUMBER,
84     p_org_unit_cd         IN            igs_pr_org_stat.org_unit_cd%TYPE,
85     p_stat_type           IN            igs_pr_stat_type.stat_type%TYPE,
86     p_init_msg_list       IN            VARCHAR2,
87     p_return_status       OUT NOCOPY    VARCHAR2,
88     p_msg_count           OUT NOCOPY    NUMBER,
89     p_msg_data            OUT NOCOPY    VARCHAR2)
90     RETURN VARCHAR2 ;
91   --
92   -- swaghmar; 15-Sep-2005; Bug 4491456
93   --	Modified the signature
94 
95   PROCEDURE get_adv_stats(
96     p_person_id               IN            igs_en_stdnt_ps_att.person_id%TYPE,
97     p_course_cd               IN            igs_en_stdnt_ps_att.course_cd%TYPE,
98     p_stat_type               IN            igs_pr_stat_type.stat_type%TYPE,
99     p_org_unit_cd             IN            igs_pr_org_stat.org_unit_cd%TYPE,
100     p_load_cal_type           IN            igs_ca_inst.cal_type%TYPE,
101     p_load_ci_sequence_number IN            igs_ca_inst.sequence_number%TYPE,
102     p_cumulative_ind          IN            VARCHAR2,
103     p_include_local_ind       IN            VARCHAR2,
104     p_include_other_ind       IN            VARCHAR2,
105     p_earned_cp     OUT NOCOPY    NUMBER,
106     p_attempted_cp  OUT NOCOPY    NUMBER,
107     p_gpa_cp                  OUT NOCOPY    NUMBER,
108     p_gpa_quality_points      OUT NOCOPY    NUMBER,
109     p_init_msg_list           IN            VARCHAR2,
110     p_return_status           OUT NOCOPY    VARCHAR2,
111     p_msg_count               OUT NOCOPY    NUMBER,
112     p_msg_data                OUT NOCOPY    VARCHAR2);
113 
114   --
115   -- kdande; 23-Apr-2003; Bug# 2829262
116   -- Added p_uoo_id parameter to the local PROCEDURE get_sua_stats
117   -- swaghmar; 15-Sep-2005; Bug 4491456
118   --	Modified the signature
119   --
120   PROCEDURE get_sua_stats(
121     p_person_id                IN         igs_en_su_attempt_ALL.person_id%TYPE,
122     p_course_cd                IN         igs_en_su_attempt_ALL.course_cd%TYPE,
123     p_unit_cd                  IN         igs_en_su_attempt_ALL.unit_cd%TYPE,
124     p_unit_version_number      IN         igs_en_su_attempt_ALL.version_number%TYPE,
125     p_teach_cal_type           IN         igs_en_su_attempt_ALL.cal_type%TYPE,
126     p_teach_ci_sequence_number IN         igs_en_su_attempt_ALL.ci_sequence_number%TYPE,
127     p_earned_cp                OUT NOCOPY NUMBER,
128     p_attempted_cp             OUT NOCOPY NUMBER,
129     p_gpa_value                OUT NOCOPY NUMBER,
130     p_gpa_cp                   OUT NOCOPY NUMBER,
131     p_gpa_quality_points       OUT NOCOPY NUMBER,
132     p_init_msg_list            IN         VARCHAR2,
133     p_return_status            OUT NOCOPY VARCHAR2,
134     p_msg_count                OUT NOCOPY NUMBER,
135     p_msg_data                 OUT NOCOPY VARCHAR2,
136     p_uoo_id                   IN         NUMBER,
137     p_use_released_grade       IN         VARCHAR2,
138     p_enrolled_cp	       OUT NOCOPY igs_pr_stu_acad_stat.gpa_quality_points%TYPE);
139 
140 
141    FUNCTION chk_av_unit_ref_cd (
142       p_av_stnd_unit_id   IN              igs_av_stnd_unit_all.av_stnd_unit_id%TYPE,
143       p_org_unit_cd       IN              igs_pr_org_stat.org_unit_cd%TYPE,
144       p_stat_type         IN              igs_pr_stat_type.stat_type%TYPE,
145       p_init_msg_list     IN              VARCHAR2,
146       p_return_status     OUT NOCOPY      VARCHAR2,
147       p_msg_count         OUT NOCOPY      NUMBER,
148       p_msg_data          OUT NOCOPY      VARCHAR2
149    )
150       RETURN VARCHAR2
151    AS
152 
153 --------------------------------------------------------------------------
154 --  Created By : Jitendra
155 --  Date Created On : 06-04-2005
156 --  Purpose: To check whether a unit is Excluded or Included by a reference code
157 --           for advanced standing
158 --  Know limitations, enhancements or remarks
159 --  Change History
160 --  Who             When            What
161 --  (reverse chronological order - newest change first)
162 --------------------------------------------------------------------------
163 
164       CURSOR c_org_setup
165       IS
166          SELECT ostr1.include_or_exclude
167            FROM igs_pr_org_stat_ref ostr1
168           WHERE ostr1.stat_type = p_stat_type
169             AND ostr1.org_unit_cd = p_org_unit_cd;
170 
171       CURSOR c_org_included
172       IS
173          SELECT 'X'
174            FROM igs_av_unt_ref_cds urc,
175                 igs_ge_ref_cd refcd,
176                 igs_ge_ref_cd_type rct
177           WHERE urc.av_stnd_unit_id = p_av_stnd_unit_id
178             AND urc.reference_code_id = refcd.reference_code_id
179             AND refcd.reference_cd_type = rct.reference_cd_type
180             AND rct.s_reference_cd_type = 'STATS'
181 	    AND urc.deleted_date IS NULL
182             AND EXISTS ( SELECT 'X'
183                            FROM igs_pr_org_stat_ref ostr1
184                           WHERE ostr1.stat_type = p_stat_type
185                             AND ostr1.org_unit_cd = p_org_unit_cd
186                             AND ostr1.unit_ref_cd = refcd.reference_cd
187                             AND ostr1.include_or_exclude = 'INCLUDE');
188 
189       CURSOR c_org_excluded
190       IS
191          SELECT 'X'
192            FROM igs_av_unt_ref_cds urc,
193                 igs_ge_ref_cd refcd,
194                 igs_ge_ref_cd_type rct
195           WHERE urc.av_stnd_unit_id = p_av_stnd_unit_id
196             AND urc.reference_code_id = refcd.reference_code_id
197             AND refcd.reference_cd_type = rct.reference_cd_type
198             AND rct.s_reference_cd_type = 'STATS'
199 	    AND urc.deleted_date IS NULL
200             AND EXISTS ( SELECT 'X'
201                            FROM igs_pr_org_stat_ref ostr1
202                           WHERE ostr1.stat_type = p_stat_type
203                             AND ostr1.org_unit_cd = p_org_unit_cd
204                             AND ostr1.unit_ref_cd = refcd.reference_cd
205                             AND ostr1.include_or_exclude = 'EXCLUDE');
206 
207       CURSOR c_inst_setup
208       IS
209          SELECT INSTR.include_or_exclude
210            FROM igs_pr_inst_sta_ref INSTR
211           WHERE INSTR.stat_type = p_stat_type;
212 
213       CURSOR c_inst_included
214       IS
215          SELECT 'X'
216            FROM igs_av_unt_ref_cds urc,
217                 igs_ge_ref_cd refcd,
218                 igs_ge_ref_cd_type rct
219           WHERE urc.av_stnd_unit_id = p_av_stnd_unit_id
220             AND urc.reference_code_id = refcd.reference_code_id
221             AND refcd.reference_cd_type = rct.reference_cd_type
222             AND rct.s_reference_cd_type = 'STATS'
223 	    AND urc.deleted_date IS NULL
224             AND EXISTS ( SELECT 'X'
225                            FROM igs_pr_inst_sta_ref instr1
226                           WHERE instr1.stat_type = p_stat_type
227                             AND instr1.unit_ref_cd = refcd.reference_cd
228                             AND instr1.include_or_exclude = 'INCLUDE');
229 
230       CURSOR c_inst_excluded
231       IS
232          SELECT 'X'
233            FROM igs_av_unt_ref_cds urc,
234                 igs_ge_ref_cd refcd,
235                 igs_ge_ref_cd_type rct
236           WHERE urc.av_stnd_unit_id = p_av_stnd_unit_id
237             AND urc.reference_code_id = refcd.reference_code_id
238             AND refcd.reference_cd_type = rct.reference_cd_type
239             AND rct.s_reference_cd_type = 'STATS'
240 	    AND urc.deleted_date IS NULL
241             AND EXISTS ( SELECT 'X'
242                            FROM igs_pr_inst_sta_ref instr1
243                           WHERE instr1.stat_type = p_stat_type
244                             AND instr1.unit_ref_cd = refcd.reference_cd
245                             AND instr1.include_or_exclude = 'EXCLUDE');
246 
247       l_include_or_exclude   VARCHAR2 (20);
248       l_include              VARCHAR2 (1);
249       l_dummy                VARCHAR2 (1);
250       l_message              VARCHAR2 (1000);
251    BEGIN
252       l_include := 'Y';
253       -- Initialize message list if p_init_msg_list is set to TRUE.
254       IF fnd_api.to_boolean (NVL (p_init_msg_list, fnd_api.g_true))
255       THEN
256          fnd_msg_pub.initialize;
257       END IF;
258 
259       -- The following parameters should not be null
260       IF (   p_av_stnd_unit_id IS NULL
261           OR p_stat_type IS NULL
262          )
263       THEN
264          l_message := 'IGS_GE_INSUFFICIENT_PARAM_VAL';
265          fnd_message.set_name ('IGS', l_message);
266          fnd_msg_pub.ADD;
267          RAISE fnd_api.g_exc_error;
268       END IF;
269 
270       -- If the Organizational Unit is not null then statistic type is
271       -- defined at Organizational level.  Check if any unit reference
272       -- codes are included or excluded at Org level.
273 
274       IF p_org_unit_cd IS NOT NULL
275       THEN
276          -- When no Unit Reference Codes are specifically included or excluded all
277          -- units should be included.
278          OPEN c_org_setup;
279          FETCH c_org_setup INTO l_include_or_exclude;
280 
281          IF (c_org_setup%FOUND)
282          THEN
283             IF (l_include_or_exclude = 'INCLUDE')
284             THEN
285                -- When Unit Reference Codes are specifically included then only those
286                -- units with the included Unit Refernce Code should be included
287                OPEN c_org_included;
288                FETCH c_org_included INTO l_dummy;
289 
290                IF (c_org_included%NOTFOUND)
291                THEN
292                   l_include := 'N';
293                END IF;
294 
295                CLOSE c_org_included;
296             ELSE
297                -- When Unit Reference Codes are specifically excluded all units except
298                -- those units with the excluded Unit Refernce Code should be included
299                OPEN c_org_excluded;
300                FETCH c_org_excluded INTO l_dummy;
301 
302                IF (c_org_excluded%FOUND)
303                THEN
304                   l_include := 'N';
305                END IF;
306 
307                CLOSE c_org_excluded;
308             END IF;
309          END IF;
310 
311          CLOSE c_org_setup;
312       -- If the Organizational Unit is null then statistic type must be
313       -- defined at Institution level.  Check if any unit reference
314       -- codes are included or excluded at Inst level.
315       ELSE
316          -- When no Unit Reference Codes are specifically included or excluded all
317          -- units should be included.
318 
319          OPEN c_inst_setup;
320          FETCH c_inst_setup INTO l_include_or_exclude;
321 
322          IF (c_inst_setup%FOUND)
323          THEN
324             IF (l_include_or_exclude = 'INCLUDE')
325             THEN
326                -- When Unit Reference Codes are specifically included then only those
327                -- units with the included Unit Refernce Code should be included
328                OPEN c_inst_included;
329                FETCH c_inst_included INTO l_dummy;
330 
331                IF (c_inst_included%NOTFOUND)
332                THEN
333                   l_include := 'N';
334                END IF;
335 
336                CLOSE c_inst_included;
337             ELSE
338                -- When Unit Reference Codes are specifically excluded all units except
339                -- those units with the excluded Unit Refernce Code should be included
340                OPEN c_inst_excluded;
341                FETCH c_inst_excluded INTO l_dummy;
342 
343                IF (c_inst_excluded%FOUND)
344                THEN
345                   l_include := 'N';
346                END IF;
347 
348                CLOSE c_inst_excluded;
349             END IF;
350          END IF;
351          CLOSE c_inst_setup;
352       END IF;
353 
354       -- Initialize API return status to success.
355       p_return_status := fnd_api.g_ret_sts_success;
356       -- Standard call to get message count and if count is 1, get message info
357       fnd_msg_pub.count_and_get (
358          p_encoded=> fnd_api.g_false,
359          p_count=> p_msg_count,
360          p_data=> p_msg_data
361       );
362       RETURN l_include;
363    EXCEPTION
364       WHEN fnd_api.g_exc_error
365       THEN
366          p_return_status := fnd_api.g_ret_sts_error;
367          fnd_msg_pub.count_and_get (
368             p_encoded=> fnd_api.g_false,
369             p_count=> p_msg_count,
370             p_data=> p_msg_data
371          );
372          RETURN NULL;
373       WHEN fnd_api.g_exc_unexpected_error
374       THEN
375          p_return_status := fnd_api.g_ret_sts_unexp_error;
376          fnd_msg_pub.count_and_get (
377             p_encoded=> fnd_api.g_false,
378             p_count=> p_msg_count,
379             p_data=> p_msg_data
380          );
381          RETURN NULL;
382       WHEN OTHERS
383       THEN
384          p_return_status := fnd_api.g_ret_sts_unexp_error;
385          fnd_message.set_name ('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
386          fnd_message.set_token ('NAME',    'chk_av_unit_ref_cd: '
387                                         || SQLERRM);
388          fnd_msg_pub.ADD;
389          fnd_msg_pub.count_and_get (
390             p_encoded=> fnd_api.g_false,
391             p_count=> p_msg_count,
392             p_data=> p_msg_data
393          );
394          RETURN NULL;
395    END chk_av_unit_ref_cd;
396 
397 
398 
399 
400   PROCEDURE get_stat_dtls(
401     p_person_id         IN            igs_en_stdnt_ps_att.person_id%TYPE,
402     p_course_cd         IN            igs_en_stdnt_ps_att.course_cd%TYPE,
403     p_system_stat       IN            VARCHAR2,
404     p_cumulative_ind    IN            VARCHAR2,
405     p_stat_type         IN OUT NOCOPY igs_pr_stat_type.stat_type%TYPE,
406     p_org_unit_cd       OUT NOCOPY    igs_pr_org_stat.org_unit_cd%TYPE,
407     p_include_std_ind   OUT NOCOPY    igs_pr_org_stat.include_standard_ind%TYPE,
408     p_include_local_ind OUT NOCOPY    igs_pr_org_stat.include_local_ind%TYPE,
409     p_include_other_ind OUT NOCOPY    igs_pr_org_stat.include_other_ind%TYPE,
410     p_derivation        OUT NOCOPY    igs_pr_stat_type.derivation%TYPE,
411     p_init_msg_list     IN            VARCHAR2,
412     p_return_status     OUT NOCOPY    VARCHAR2,
413     p_msg_count         OUT NOCOPY    NUMBER,
414     p_msg_data          OUT NOCOPY    VARCHAR2) IS
415     /*
416     ||Created By : Prajeesh Chandran
417     ||Created On : 6-Nov-2001
418     ||Purpose : Gets the Program and Statistics Details(Org or Institution)
419     ||Known limitations, enhancements or remarks :
420     ||Change History :
421     ||Who      When        What
422     ||(reverse chronological order - newest change first)
423     ||ddey     27-Oct-2003 Changes are done, so that the message stack is not initilized.(Bug # 3163305)
424     ||kdande   20-Sep-2002 Removed the references to columns progression_ind and
425     ||                    fin_aid_ind from the c_org_stat cursor and c_inst_stat
426     ||                     cursor for Bug# 560160. Defaulted the p_init_msg_list
427     ||                     parameter in the code since default value is removed
428     ||                     from the procedure signature
429     */
430     --
431     -- Cursor to get the Details at the Organization Level
432     --
433     CURSOR c_org_stat IS
434       SELECT orst.org_unit_cd,
435              st.stat_type,
436              st.derivation,
437              orst.include_standard_ind,
438              orst.include_local_ind,
439              orst.include_other_ind
440         FROM igs_en_stdnt_ps_att spa,
441              igs_ps_ver crv,
442              igs_pr_stat_type st,
443              igs_pr_org_stat orst
444        WHERE spa.person_id = p_person_id
445          AND spa.course_cd = p_course_cd
446          AND spa.course_cd = crv.course_cd
447          AND spa.version_number = crv.version_number
448          AND st.stat_type = orst.stat_type
449          AND orst.org_unit_cd = crv.responsible_org_unit_cd
450          AND (orst.stat_type = p_stat_type
451               OR p_stat_type IS NULL
452                  AND ((p_system_stat IS NULL AND orst.standard_ind = 'Y')
453                       OR (p_system_stat = 'STANDARD' AND orst.standard_ind = 'Y'))
454                  AND ((p_cumulative_ind = 'Y'
455                        AND (orst.timeframe = 'CUMULATIVE'
456                             OR orst.timeframe = 'BOTH'))
457                       OR (p_cumulative_ind = 'N' AND orst.timeframe = 'PERIOD'
458                           OR orst.timeframe = 'BOTH')));
459 
460     --
461     -- Cursor to retrieve records at the Institution Level.
462     --
463     CURSOR c_inst_stat IS
464       SELECT st.stat_type,
465              st.derivation,
466              inst.include_standard_ind,
467              inst.include_local_ind,
468              inst.include_other_ind
469         FROM igs_pr_stat_type st, igs_pr_inst_stat inst
470        WHERE st.stat_type = inst.stat_type
471          AND (inst.stat_type = p_stat_type
472               OR p_stat_type IS NULL
473                  AND ((p_system_stat IS NULL AND inst.standard_ind = 'Y')
474                       OR (p_system_stat = 'STANDARD' AND inst.standard_ind =
475                                                                            'Y'))
476                  AND ((p_cumulative_ind = 'Y'
477                        AND (inst.timeframe = 'CUMULATIVE'
478                             OR inst.timeframe = 'BOTH'))
479                       OR (p_cumulative_ind = 'N' AND inst.timeframe = 'PERIOD'
480                           OR inst.timeframe = 'BOTH'))); -- Bug Fix 2707516
481 
482     lc_org_stat  c_org_stat%ROWTYPE;
483     lc_inst_stat c_inst_stat%ROWTYPE;
484     l_message    VARCHAR2(1000);
485   BEGIN
486     --
487     -- Initialize message list if p_init_msg_list is set to TRUE.
488     --
489     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
490       fnd_msg_pub.initialize;
491     END IF;
492 
493     --
494     -- Check for the Parameters which are mandatory. If the parameters are
495     -- sent as NULL then raise an error
496     --
497     IF (p_person_id IS NULL
498         OR p_course_cd IS NULL) THEN
499       l_message := 'IGS_GE_INSUFFICIENT_PARAM_VAL';
500       fnd_message.set_name('IGS', l_message);
501       fnd_msg_pub.ADD;
502       RAISE fnd_api.g_exc_error;
503     END IF;
504 
505     --
506     -- Check whether the system stat is not within the given values
507     -- i.e standard,fin_aid or progession
508     -- If not raise an error
509     --
510     IF (p_system_stat IS NOT NULL
511         AND p_system_stat NOT IN ('STANDARD', 'FIN_AID', 'PROGRESSION')) THEN
512       l_message := 'IGS_PR_SYSTEM_STAT_INCORRECT';
513       fnd_message.set_name('IGS', l_message);
514       fnd_msg_pub.ADD;
515       RAISE fnd_api.g_exc_error;
516     END IF;
517 
518     --
519     -- ## Check if there records at Organization Level.
520     --
521     OPEN c_org_stat;
522     FETCH c_org_stat INTO lc_org_stat;
523 
524     IF c_org_stat%NOTFOUND THEN
525       NULL;
526     ELSE
527       p_stat_type := lc_org_stat.stat_type;
528       p_derivation := lc_org_stat.derivation;
529       p_org_unit_cd := lc_org_stat.org_unit_cd;
530       p_include_std_ind := lc_org_stat.include_standard_ind;
531       p_include_local_ind := lc_org_stat.include_local_ind;
532       p_include_other_ind := lc_org_stat.include_other_ind;
533     END IF;
534 
535     --
536     -- If there are No records at Organization Level then check for the same
537     -- at the Institutional Level.
538     -- If there are no records at the Institutional Level too then Raise
539     -- message saying No records exists
540     --
541     IF c_org_stat%NOTFOUND THEN
542       OPEN c_inst_stat;
543       FETCH c_inst_stat INTO lc_inst_stat;
544 
545       IF c_inst_stat%NOTFOUND THEN
546         -- p_stat_type  := NULL;
547         -- Added to fix Bug# 2685741
548         --
549         CLOSE c_inst_stat;
550         fnd_message.set_name('IGS', 'IGS_PR_INVALID_STAT_TYPE');
551         fnd_msg_pub.ADD;
552         RAISE fnd_api.g_exc_error;
553       --
554       -- End of new code added as per Bug# 2685741
555       --
556       ELSE
557         p_stat_type := lc_inst_stat.stat_type;
558         p_derivation := lc_inst_stat.derivation;
559         p_org_unit_cd := NULL;
560         p_include_std_ind := lc_inst_stat.include_standard_ind;
561         p_include_local_ind := lc_inst_stat.include_local_ind;
562         p_include_other_ind := lc_inst_stat.include_other_ind;
563       END IF;
564 
565       CLOSE c_inst_stat;
566     END IF;
567 
568     CLOSE c_org_stat;
569     -- Initialize API return status to success.
570     p_return_status := fnd_api.g_ret_sts_success;
571     -- Standard call to get message count and if count is 1, get message info
572     fnd_msg_pub.count_and_get(
573       p_encoded => fnd_api.g_false,
574       p_count => p_msg_count,
575       p_data => p_msg_data);
576 
577   EXCEPTION
578     WHEN fnd_api.g_exc_error THEN
579       p_return_status := fnd_api.g_ret_sts_error;
580       fnd_msg_pub.count_and_get(
581         p_encoded => fnd_api.g_false,
582         p_count => p_msg_count,
583         p_data => p_msg_data);
584     WHEN fnd_api.g_exc_unexpected_error THEN
585       p_return_status := fnd_api.g_ret_sts_unexp_error;
586       fnd_msg_pub.count_and_get(
587         p_encoded => fnd_api.g_false,
588         p_count => p_msg_count,
589         p_data => p_msg_data);
590     WHEN OTHERS THEN
591       p_return_status := fnd_api.g_ret_sts_unexp_error;
592       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
593       fnd_message.set_token('NAME', 'GET_STAT_DTLS: ' || SQLERRM);
594       fnd_msg_pub.ADD;
595       fnd_msg_pub.count_and_get(
596         p_encoded => fnd_api.g_false,
597         p_count => p_msg_count,
598         p_data => p_msg_data);
599   END get_stat_dtls;
600 
601   FUNCTION chk_unit_ref_cd(
602     p_unit_cd             IN            igs_ps_unit_ver.unit_cd%TYPE,
603     p_unit_version_number IN            igs_ps_unit_ver.version_number%TYPE,
604     p_org_unit_cd         IN            igs_pr_org_stat.org_unit_cd%TYPE,
605     p_stat_type           IN            igs_pr_stat_type.stat_type%TYPE,
606     p_init_msg_list       IN            VARCHAR2,
607     p_return_status       OUT NOCOPY    VARCHAR2,
608     p_msg_count           OUT NOCOPY    NUMBER,
609     p_msg_data            OUT NOCOPY    VARCHAR2)
610     RETURN VARCHAR2 AS
611 
612 --------------------------------------------------------------------------
613 --  Created By : Nishikant
614 --  Date Created On : 06-11-2001
615 --  Purpose: To check whether a unit is Excluded or Included by a reference code
616 --  Know limitations, enhancements or remarks
617 --  Change History
618 --  Who             When            What
619 --  (reverse chronological order - newest change first)
620 --  kdande   20-Sep-2002 Bug# 2560160: Defaulted the p_init_msg_list parameter
621 --                       in the code since default value is removed from the
622 --                       function signature.
623 --------------------------------------------------------------------------
624 
625     CURSOR c_org_setup IS
626       SELECT ostr1.include_or_exclude
627         FROM igs_pr_org_stat_ref ostr1
628        WHERE ostr1.stat_type = p_stat_type AND ostr1.org_unit_cd =
629                                                                   p_org_unit_cd;
630 
631     CURSOR c_org_included IS
632       SELECT 'X'
633         FROM igs_ps_unit_ref_cd urc, igs_ge_ref_cd_type rct
634        WHERE urc.unit_cd = p_unit_cd
635          AND urc.version_number = p_unit_version_number
636          AND urc.reference_cd_type = rct.reference_cd_type
637          AND rct.s_reference_cd_type = 'STATS'
638          AND EXISTS( SELECT 'X'
639                        FROM igs_pr_org_stat_ref ostr1
640                       WHERE ostr1.stat_type = p_stat_type
641                         AND ostr1.org_unit_cd = p_org_unit_cd
642                         AND ostr1.unit_ref_cd = urc.reference_cd
643                         AND ostr1.include_or_exclude = 'INCLUDE');
644 
645     CURSOR c_org_excluded IS
646       SELECT 'X'
647         FROM igs_ps_unit_ref_cd urc, igs_ge_ref_cd_type rct
648        WHERE urc.unit_cd = p_unit_cd
649          AND urc.version_number = p_unit_version_number
650          AND urc.reference_cd_type = rct.reference_cd_type
651          AND rct.s_reference_cd_type = 'STATS'
652          AND EXISTS( SELECT 'X'
653                        FROM igs_pr_org_stat_ref ostr1
654                       WHERE ostr1.stat_type = p_stat_type
655                         AND ostr1.org_unit_cd = p_org_unit_cd
656                         AND ostr1.unit_ref_cd = urc.reference_cd
657                         AND ostr1.include_or_exclude = 'EXCLUDE');
658 
659     CURSOR c_inst_setup IS
660       SELECT INSTR.include_or_exclude
661         FROM igs_pr_inst_sta_ref INSTR
662        WHERE INSTR.stat_type = p_stat_type;
663 
664     CURSOR c_inst_included IS
665       SELECT 'X'
666         FROM igs_ps_unit_ref_cd urc, igs_ge_ref_cd_type rct
667        WHERE urc.unit_cd = p_unit_cd
668          AND urc.version_number = p_unit_version_number
669          AND urc.reference_cd_type = rct.reference_cd_type
670          AND rct.s_reference_cd_type = 'STATS'
671          AND EXISTS( SELECT 'X'
672                        FROM igs_pr_inst_sta_ref instr1
673                       WHERE instr1.stat_type = p_stat_type
674                         AND instr1.unit_ref_cd = urc.reference_cd
675                         AND instr1.include_or_exclude = 'INCLUDE');
676 
677     CURSOR c_inst_excluded IS
678       SELECT 'X'
679         FROM igs_ps_unit_ref_cd urc, igs_ge_ref_cd_type rct
680        WHERE urc.unit_cd = p_unit_cd
681          AND urc.version_number = p_unit_version_number
682          AND urc.reference_cd_type = rct.reference_cd_type
683          AND rct.s_reference_cd_type = 'STATS'
684          AND EXISTS( SELECT 'X'
685                        FROM igs_pr_inst_sta_ref instr1
686                       WHERE instr1.stat_type = p_stat_type
687                         AND instr1.unit_ref_cd = urc.reference_cd
688                         AND instr1.include_or_exclude = 'EXCLUDE');
689 
690     l_include_or_exclude VARCHAR2(20);
691     l_include            VARCHAR2(1);
692     l_dummy              VARCHAR2(1);
693     l_message            VARCHAR2(1000);
694   BEGIN
695     l_include := 'Y';
696     -- Initialize message list if p_init_msg_list is set to TRUE.
697     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
698       fnd_msg_pub.initialize;
699     END IF;
700 
701     -- The following parameters should not be null
702     IF (p_unit_cd IS NULL
703         OR p_unit_version_number IS NULL
704         OR p_stat_type IS NULL) THEN
705       l_message := 'IGS_GE_INSUFFICIENT_PARAM_VAL';
706       fnd_message.set_name('IGS', l_message);
707       fnd_msg_pub.ADD;
708       RAISE fnd_api.g_exc_error;
709     END IF;
710 
711     -- If the Organizational Unit is not null then statistic type is
712     -- defined at Organizational level.  Check if any unit reference
713     -- codes are included or excluded at Org level.
714 
715     IF p_org_unit_cd IS NOT NULL THEN
716       -- When no Unit Reference Codes are specifically included or excluded all
717       -- units should be included.
718       OPEN c_org_setup;
719       FETCH c_org_setup INTO l_include_or_exclude;
720 
721       IF (c_org_setup%FOUND) THEN
722         IF (l_include_or_exclude = 'INCLUDE') THEN
723           -- When Unit Reference Codes are specifically included then only those
724           -- units with the included Unit Refernce Code should be included
725           OPEN c_org_included;
726           FETCH c_org_included INTO l_dummy;
727 
728           IF (c_org_included%NOTFOUND) THEN
729             l_include := 'N';
730           END IF;
731 
732           CLOSE c_org_included;
733         ELSE
734           -- When Unit Reference Codes are specifically excluded all units except
735           -- those units with the excluded Unit Refernce Code should be included
736           OPEN c_org_excluded;
737           FETCH c_org_excluded INTO l_dummy;
738 
739           IF (c_org_excluded%FOUND) THEN
740             l_include := 'N';
741           END IF;
742 
743           CLOSE c_org_excluded;
744         END IF;
745       END IF;
746 
747       CLOSE c_org_setup;
748     -- If the Organizational Unit is null then statistic type must be
749     -- defined at Institution level.  Check if any unit reference
750     -- codes are included or excluded at Inst level.
751     ELSE
752       -- When no Unit Reference Codes are specifically included or excluded all
753       -- units should be included.
754       OPEN c_inst_setup;
755       FETCH c_inst_setup INTO l_include_or_exclude;
756 
757       IF (c_inst_setup%FOUND) THEN
758         IF (l_include_or_exclude = 'INCLUDE') THEN
759           -- When Unit Reference Codes are specifically included then only those
760           -- units with the included Unit Refernce Code should be included
761           OPEN c_inst_included;
762           FETCH c_inst_included INTO l_dummy;
763 
764           IF (c_inst_included%NOTFOUND) THEN
765             l_include := 'N';
766           END IF;
767 
768           CLOSE c_inst_included;
769         ELSE
770           -- When Unit Reference Codes are specifically excluded all units except
771           -- those units with the excluded Unit Refernce Code should be included
772           OPEN c_inst_excluded;
773           FETCH c_inst_excluded INTO l_dummy;
774 
775           IF (c_inst_excluded%FOUND) THEN
776             l_include := 'N';
777           END IF;
778 
779           CLOSE c_inst_excluded;
780         END IF;
781       END IF;
782 
783       CLOSE c_inst_setup;
784     END IF;
785 
786     -- Initialize API return status to success.
787     p_return_status := fnd_api.g_ret_sts_success;
788     -- Standard call to get message count and if count is 1, get message info
789     fnd_msg_pub.count_and_get(
790       p_encoded => fnd_api.g_false,
791       p_count => p_msg_count,
792       p_data => p_msg_data);
793     RETURN l_include;
794   EXCEPTION
795     WHEN fnd_api.g_exc_error THEN
796       p_return_status := fnd_api.g_ret_sts_error;
797       fnd_msg_pub.count_and_get(
798         p_encoded => fnd_api.g_false,
799         p_count => p_msg_count,
800         p_data => p_msg_data);
801       RETURN NULL;
802     WHEN fnd_api.g_exc_unexpected_error THEN
803       p_return_status := fnd_api.g_ret_sts_unexp_error;
804       fnd_msg_pub.count_and_get(
805         p_encoded => fnd_api.g_false,
806         p_count => p_msg_count,
807         p_data => p_msg_data);
808       RETURN NULL;
809     WHEN OTHERS THEN
810       p_return_status := fnd_api.g_ret_sts_unexp_error;
811       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
812       fnd_message.set_token('NAME', 'chk_unit_ref_cd: ' || SQLERRM);
813       fnd_msg_pub.ADD;
814       fnd_msg_pub.count_and_get(
815         p_encoded => fnd_api.g_false,
816         p_count => p_msg_count,
817         p_data => p_msg_data);
818       RETURN NULL;
819   END chk_unit_ref_cd;
820 
821   PROCEDURE get_adv_stats(
822     p_person_id               IN            igs_en_stdnt_ps_att.person_id%TYPE,
823     p_course_cd               IN            igs_en_stdnt_ps_att.course_cd%TYPE,
824     p_stat_type               IN            igs_pr_stat_type.stat_type%TYPE,
825     p_org_unit_cd             IN            igs_pr_org_stat.org_unit_cd%TYPE,
826     p_load_cal_type           IN            igs_ca_inst.cal_type%TYPE,
827     p_load_ci_sequence_number IN            igs_ca_inst.sequence_number%TYPE,
828     p_cumulative_ind          IN            VARCHAR2,
829     p_include_local_ind       IN            VARCHAR2,
830     p_include_other_ind       IN            VARCHAR2,
831     p_earned_cp     OUT NOCOPY    NUMBER,
832     p_attempted_cp  OUT NOCOPY    NUMBER,
833     p_gpa_cp                  OUT NOCOPY    NUMBER,
834     p_gpa_quality_points      OUT NOCOPY    NUMBER,
835     p_init_msg_list           IN            VARCHAR2,
836     p_return_status           OUT NOCOPY    VARCHAR2,
837     p_msg_count               OUT NOCOPY    NUMBER,
838     p_msg_data                OUT NOCOPY    VARCHAR2) IS
839     /*
840     ||Created By : Prajeesh Chandran
841     ||Created On : 6-NOV-2001
842     ||Purpose : Gets the GPA AND Credit points incase of Advanced Standing
843     ||          (Org or Institution)
844     ||Known limitations, enhancements or remarks :
845     ||Change History :
846     ||Who      When       What
847     ||smanglm  25-06-2002 as per bug 2430606 modified
848     ||         asu.institution_cd = inst.institution_cd(+) in cursor c_asu to
849     ||         asu.exemption_institution_cd = inst.institution_cd(+) and
850     ||         asul.institution_cd = inst.institution_cd(+) in cursor c_asul to
851     ||         asul.exemption_institution_cd = inst.institution_cd(+)
852     ||         This is done to see Advanced Standing granted from the loca
853     ||         institution in the academic statistics calculation.
854     ||(reverse chronological order - newest change first)
855     ||kdande   20-Sep-2002 Bug# 2560160: Defaulted the p_init_msg_list parameter
856     ||         in the code since default value is removed from the procedure
857     ||         signature.
858     ||swaghmar 15-Sep-2005; Bug 4491456 - Modified the signature and variable datatypes
859     ||				for the fix
860     ||swaghmar 20-Jun-2006; Bug 5260180
861     */
862 
863     -- Cursor to get the Credit Point,Course code and Unitcode details with the
864     -- achievable and enrolled credit Points
865     CURSOR c_asu IS
866       SELECT asu.unit_cd,
867              asu.version_number,
868              asu.achievable_credit_points,
869              asu.grading_schema_cd,
870              asu.grd_sch_version_number,
871              asu.grade,
872              asu.av_stnd_unit_id
873         FROM igs_av_stnd_unit asu, igs_or_inst_org_base_v inst, igs_ca_inst ci
874        WHERE asu.person_id = p_person_id
875          AND asu.as_course_cd = p_course_cd
876          AND asu.s_adv_stnd_granting_status IN ('GRANTED', 'APPROVED')
877          AND asu.s_adv_stnd_recognition_type = 'CREDIT'
878          AND NVL(asu.expiry_dt, SYSDATE + 1) > SYSDATE
879          AND asu.exemption_institution_cd = inst.party_number(+) --swaghmar change
880          AND ((p_include_local_ind = 'Y' AND inst.oi_local_institution_ind = 'Y')
881               OR (p_include_other_ind = 'Y' AND inst.oi_local_institution_ind =
882                                                                            'N'))
883          AND asu.cal_type = ci.cal_type
884          AND asu.ci_sequence_number = ci.sequence_number
885 	 AND inst.inst_org_ind = 'I'
886          AND ((p_cumulative_ind = 'N'
887                AND p_load_cal_type = asu.cal_type
888                AND p_load_ci_sequence_number = asu.ci_sequence_number)
889               OR (p_cumulative_ind = 'Y'
890                   AND 0 < (SELECT COUNT(*)
891                              FROM igs_ca_inst ci2
892                             WHERE p_load_cal_type = ci2.cal_type
893                               AND p_load_ci_sequence_number =
894                                                             ci2.sequence_number
895                               AND ci.start_dt <= ci2.start_dt)));
896 
897     CURSOR c_gsg(
898       cp_grading_schema_cd igs_as_grd_sch_grade.grading_schema_cd%TYPE,
899       cp_gs_version_number igs_as_grd_sch_grade.version_number%TYPE,
900       cp_grade             igs_as_grd_sch_grade.grade%TYPE) IS
901       SELECT s_result_type,
902              gpa_val
903         FROM igs_as_grd_sch_grade gsg
904        WHERE gsg.grading_schema_cd = cp_grading_schema_cd
905          AND gsg.version_number = cp_gs_version_number
906          AND gsg.grade = cp_grade;
907 
908     CURSOR c_asul IS
909       SELECT SUM(NVL(asul.credit_points, 0)) sumvalue
910         FROM igs_av_stnd_unit_lvl asul, igs_or_inst_org_base_v inst, igs_ca_inst ci
911        WHERE asul.person_id = p_person_id
912          AND asul.as_course_cd = p_course_cd
913          AND asul.s_adv_stnd_granting_status IN ('GRANTED', 'APPROVED')
914          AND NVL(asul.expiry_dt, SYSDATE + 1) > SYSDATE
915          AND asul.exemption_institution_cd = inst.ou_institution_cd(+)
916          AND ((p_include_local_ind = 'Y' AND inst.oi_local_institution_ind = 'Y')
917               OR (p_include_other_ind = 'Y' AND inst.oi_local_institution_ind =
918                                                                            'N'))
919          AND asul.cal_type = ci.cal_type
920          AND asul.ci_sequence_number = ci.sequence_number
921          AND inst.inst_org_ind = 'I'
922 	 AND ((p_cumulative_ind = 'N'
923                AND p_load_cal_type = asul.cal_type
924                AND p_load_ci_sequence_number = asul.ci_sequence_number)
925               OR (p_cumulative_ind = 'Y'
926                   AND 0 < (SELECT COUNT(*)
927                              FROM igs_ca_inst ci2
928                             WHERE p_load_cal_type = ci2.cal_type
929                               AND p_load_ci_sequence_number =
930                                                             ci2.sequence_number
931                               AND ci.start_dt <= ci2.start_dt)));
932 
933     lc_asul              c_asul%ROWTYPE;
934     lc_gsg               c_gsg%ROWTYPE;
935     l_earned_cp_total    NUMBER   := 0;
936     l_attempted_cp_total NUMBER   := 0;
937     l_gpa_cp             NUMBER   := 0;
938     l_gpa_quality_points NUMBER   := 0;
939     l_init_msg_list      VARCHAR2(20);
940     l_return_status      VARCHAR2(30);
941     l_msg_count          NUMBER(2);
942     l_msg_data           VARCHAR2(30);
943   BEGIN
944     -- Initialize message list if p_init_msg_list is set to TRUE.
945     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
946       fnd_msg_pub.initialize;
947     END IF;
948     -- Unit Advanced Standing
949     FOR lc_asu IN c_asu LOOP
950       -- If achievable credit points is greater than zero, call Sub Function to
951       -- check included or excluded unit reference codes
952 
953       IF  NVL(lc_asu.achievable_credit_points, 0) > 0
954           AND (chk_unit_ref_cd(
955                 lc_asu.unit_cd,
956                 lc_asu.version_number,
957                 p_org_unit_cd,
958                 p_stat_type,
959                 l_init_msg_list,
960                 l_return_status,
961                 l_msg_count,
962                 l_msg_data) = 'Y'
963 	--jhanda
964            OR chk_av_unit_ref_cd (
965                   lc_asu.av_stnd_unit_id   ,
966                   p_org_unit_cd       ,
967                   p_stat_type         ,
968                   fnd_api.g_true      ,
969                   l_return_status     ,
970                   l_msg_count         ,
971                   l_msg_data
972                   )= 'Y' )
973            -- jhanda
974 	THEN
975         IF  lc_asu.grading_schema_cd IS NOT NULL
976             AND lc_asu.grd_sch_version_number IS NOT NULL
977             AND lc_asu.grade IS NOT NULL THEN
978           OPEN c_gsg(
979             lc_asu.grading_schema_cd,
980             lc_asu.grd_sch_version_number,
981             lc_asu.grade);
982           FETCH c_gsg INTO lc_gsg;
983           CLOSE c_gsg;
984 
985           -- Add credit points to the totals
986           IF lc_gsg.s_result_type = 'PASS' THEN
987             l_earned_cp_total :=
988                             l_earned_cp_total + lc_asu.achievable_credit_points;
989           END IF;
990 
991             l_attempted_cp_total :=
992                          l_attempted_cp_total + lc_asu.achievable_credit_points;
993 
994           -- Add values to the GPA totals
995           IF  lc_gsg.gpa_val IS NOT NULL
996               AND lc_gsg.s_result_type NOT IN ('WITHDRAWN', 'INCOMP') THEN
997             l_gpa_cp := l_gpa_cp + NVL(lc_asu.achievable_credit_points, 0);
998             l_gpa_quality_points :=   l_gpa_quality_points
999                                     + (  lc_gsg.gpa_val
1000                                        * NVL(
1001                                            lc_asu.achievable_credit_points,
1002                                            0));
1003           END IF;
1004         ELSE
1005           l_earned_cp_total :=
1006                      l_earned_cp_total + NVL(
1007                                            lc_asu.achievable_credit_points,
1008                                            0);
1009           l_attempted_cp_total :=
1010                   l_attempted_cp_total + NVL(
1011                                            lc_asu.achievable_credit_points,
1012                                            0);
1013         END IF;
1014       END IF;
1015     END LOOP;
1016 
1017     -- Unit Level Advanced Standing
1018     OPEN c_asul;
1019     FETCH c_asul INTO lc_asul;
1020     l_attempted_cp_total := l_attempted_cp_total + NVL(lc_asul.sumvalue, 0);
1021     l_earned_cp_total := l_earned_cp_total + NVL(lc_asul.sumvalue, 0);
1022     -- Set out NOCOPY parameter values
1023     p_gpa_cp := l_gpa_cp;
1024     p_gpa_quality_points := l_gpa_quality_points;
1025     p_attempted_cp := l_attempted_cp_total;
1026     p_earned_cp := l_earned_cp_total;
1027     -- Initialize API return status to success.
1028     p_return_status := fnd_api.g_ret_sts_success;
1029     -- Standard call to get message count and if count is 1, get message info.
1030     fnd_msg_pub.count_and_get(
1031       p_encoded => fnd_api.g_false,
1032       p_count => p_msg_count,
1033       p_data => p_msg_data);
1034 
1035   EXCEPTION
1036     WHEN fnd_api.g_exc_error THEN
1037       p_return_status := fnd_api.g_ret_sts_error;
1038       fnd_msg_pub.count_and_get(
1039         p_encoded => fnd_api.g_false,
1040         p_count => p_msg_count,
1041         p_data => p_msg_data);
1042     WHEN fnd_api.g_exc_unexpected_error THEN
1043       p_return_status := fnd_api.g_ret_sts_unexp_error;
1044       fnd_msg_pub.count_and_get(
1045         p_encoded => fnd_api.g_false,
1046         p_count => p_msg_count,
1047         p_data => p_msg_data);
1048     WHEN OTHERS THEN
1049       p_return_status := fnd_api.g_ret_sts_unexp_error;
1050       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1051       fnd_message.set_token('NAME', 'GET_ADV_STATS: ' || SQLERRM);
1052       fnd_msg_pub.ADD;
1053       fnd_msg_pub.count_and_get(
1054         p_encoded => fnd_api.g_false,
1055         p_count => p_msg_count,
1056         p_data => p_msg_data);
1057   END get_adv_stats;
1058 
1059   --
1060   -- kdande; 23-Apr-2003; Bug# 2829262
1061   -- Added p_uoo_id parameter to the local PROCEDURE get_sua_stats
1062   -- swaghmar; 15-Sep-2005; Bug 4491456
1063   --	Modified the signature
1064   --
1065   PROCEDURE get_sua_stats (
1066     p_person_id                IN         igs_en_su_attempt_ALL.person_id%TYPE,
1067     p_course_cd                IN         igs_en_su_attempt_ALL.course_cd%TYPE,
1068     p_unit_cd                  IN         igs_en_su_attempt_ALL.unit_cd%TYPE,
1069     p_unit_version_number      IN         igs_en_su_attempt_ALL.version_number%TYPE,
1070     p_teach_cal_type           IN         igs_en_su_attempt_ALL.cal_type%TYPE,
1071     p_teach_ci_sequence_number IN         igs_en_su_attempt_ALL.ci_sequence_number%TYPE,
1072     p_earned_cp                OUT NOCOPY NUMBER,
1073     p_attempted_cp             OUT NOCOPY NUMBER,
1074     p_gpa_value                OUT NOCOPY NUMBER,
1075     p_gpa_cp                   OUT NOCOPY NUMBER,
1076     p_gpa_quality_points       OUT NOCOPY NUMBER,
1077     p_init_msg_list            IN         VARCHAR2,
1078     p_return_status            OUT NOCOPY VARCHAR2,
1079     p_msg_count                OUT NOCOPY NUMBER,
1080     p_msg_data                 OUT NOCOPY VARCHAR2,
1081     p_uoo_id                   IN         NUMBER,
1082     p_use_released_grade       IN         VARCHAR2,
1083     p_enrolled_cp	       OUT NOCOPY igs_pr_stu_acad_stat.gpa_quality_points%TYPE) IS
1084     --------------------------------------------------------------------------
1085     --  Created By : David Larsen
1086     --  Date Created On : 06-11-2002
1087     --  Purpose:  To derive all of the statistic values for a given
1088     --            Statistic Type for a Student Unit Attempt.
1089     --  Know limitations, enhancements or remarks
1090     --  Change History
1091     --------------------------------------------------------------------------
1092     --  Who             When            What
1093     --------------------------------------------------------------------------
1094     --  Nalin Kumar     17-Feb-2004     Modified the SELECT part of C_SUA_UV CURSOR to fix Bug# 3419920;
1095     --  sarakshi        25-jun-2003     Enh#2930935,modified cursor c_sua_uv to select unit section enrolled and
1096     --                                  achievable credit points if exist else unit level
1097     --  kdande          23-Apr-2003     Bug# 2829262 Added uoo_id field to the WHERE clause of cursor c_sua_uv
1098     --  jhanda          25-feb-2005     Bug 3843525 Added parameter p_enrolled_cp
1099     -- swaghmar		15-Sep-2005	Bug# 4491456 - Modified the signature
1100     --------------------------------------------------------------------------
1101       CURSOR c_sua_uv IS
1102       SELECT sua.unit_attempt_status,
1103              NVL(sua.override_achievable_cp , sua.override_enrolled_cp ) sua_override_cp,
1104              NVL(uc.achievable_credit_points, uc.enrolled_credit_points) uc_credit_points,
1105              NVL(uv.achievable_credit_points, uv.enrolled_credit_points) uv_credit_points
1106           FROM igs_en_stdnt_ps_att spa,
1107                igs_ps_ver pv,
1108                igs_en_su_attempt_ALL sua,
1109                igs_ps_unit_ver uv,
1110                igs_ps_usec_cps uc
1111          WHERE spa.person_id = p_person_id
1112            AND spa.course_cd = p_course_cd
1113            AND spa.course_cd = pv.course_cd
1114            AND spa.version_number = pv.version_number
1115            AND sua.person_id = spa.person_id
1116            AND sua.course_cd = spa.course_cd
1117            AND sua.uoo_id = p_uoo_id
1118            AND sua.unit_cd = p_unit_cd
1119            AND sua.version_number = p_unit_version_number
1120            AND sua.cal_type = p_teach_cal_type
1121            AND sua.ci_sequence_number = p_teach_ci_sequence_number
1122            AND sua.unit_attempt_status IN
1123                              ('COMPLETED', 'DUPLICATE', 'ENROLLED', 'DISCONTIN')
1124            AND uv.unit_cd = sua.unit_cd
1125            AND uv.version_number = sua.version_number
1126            AND sua.uoo_id = uc.uoo_id(+)
1127            AND (   (sua.student_career_transcript = 'Y')
1128         OR (    NOT EXISTS (SELECT 'Y'
1129                               FROM igs_ps_prg_unit_rel pur
1130                              WHERE pur.unit_type_id = uv.unit_type_id
1131                                AND pur.student_career_level = pv.course_type
1132                                AND pur.student_career_transcript = 'N')
1133             AND NVL (sua.student_career_transcript, 'X') <> 'N'
1134            )
1135        )
1136       ORDER BY sua.unit_cd ASC, sua.ci_end_dt ASC;
1137 
1138     -- This cursor fetches the gpa_value for the Grading Schema Code
1139     -- ijeddy, bug 3489388 added show_in_earned_crdt_indto the cursor.
1140     CURSOR c_grad_schema_gpa(
1141       cp_grading_schema_cd igs_as_grd_sch_grade.grading_schema_cd%TYPE,
1142       cp_gs_version_number igs_as_grd_sch_grade.version_number%TYPE,
1143       cp_grade             igs_as_grd_sch_grade.grade%TYPE) IS
1144       SELECT gsg.gpa_val,
1145              NVL (gsg.show_in_earned_crdt_ind, 'N') show_in_earned_crdt_ind
1146         FROM igs_as_grd_sch_grade gsg
1147        WHERE gsg.grading_schema_cd = cp_grading_schema_cd
1148          AND gsg.version_number = cp_gs_version_number
1149          AND gsg.grade = cp_grade;
1150 
1151 
1152     l_init_msg_list               VARCHAR2(20);
1153     l_return_status               VARCHAR2(30);
1154     l_msg_count                   NUMBER(2);
1155     l_msg_data                    VARCHAR2(30);
1156     l_unit_attempt_status         igs_en_su_attempt_ALL.unit_attempt_status%TYPE;
1157     l_sua_override_cp             igs_ps_unit_ver.achievable_credit_points%TYPE;
1158     l_uc_credit_points            igs_ps_unit_ver.achievable_credit_points%TYPE;
1159     l_uv_credit_points            igs_ps_unit_ver.achievable_credit_points%TYPE;
1160     l_unit_cp                     NUMBER                                   := 0;
1161     l_result_type                 VARCHAR2(20);
1162     l_outcome_dt                  igs_as_su_stmptout.outcome_dt%TYPE;
1163     l_grading_schema_cd           igs_as_grd_sch_grade.grading_schema_cd%TYPE;
1164     l_gs_version_number           igs_as_grd_sch_grade.version_number%TYPE;
1165     l_grade                       igs_as_grd_sch_grade.grade%TYPE;
1166     l_mark                        igs_as_su_stmptout.mark%TYPE;
1167     l_gsg_gpa_value               NUMBER;
1168     l_gsg_show                    igs_as_grd_sch_grade.show_in_earned_crdt_ind%TYPE;
1169     l_origin_course_cd            igs_ps_stdnt_unt_trn.transfer_course_cd%TYPE;
1170   BEGIN
1171     -- Initialize message list if p_init_msg_list is set to TRUE.
1172     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
1173       fnd_msg_pub.initialize;
1174     END IF;
1175     --
1176     -- Getting the Student Unit Attempt details
1177     -- Modified the Fetch statment to fix Bug# 3419920; Nalin Kumar; 17-Feb-2004;
1178     --
1179     OPEN c_sua_uv;
1180     FETCH c_sua_uv INTO l_unit_attempt_status,
1181                         l_sua_override_cp,
1182                         l_uc_credit_points,
1183                         l_uv_credit_points;
1184       IF c_sua_uv%NOTFOUND THEN
1185         CLOSE c_sua_uv;
1186         -- Initialize API return status to success.
1187         p_return_status := fnd_api.g_ret_sts_success;
1188         RETURN;
1189       END IF;
1190     CLOSE c_sua_uv;
1191     --
1192     -- kdande; 23-Apr-2003; Bug# 2829262
1193     -- Added uoo_id parameter to the igs_as_gen_003.assp_get_sua_outcome FUNCTION call
1194     --
1195     -- Get the Student Unit Attempt Outcome details
1196     --
1197     l_result_type :=
1198         igs_as_gen_003.assp_get_sua_outcome(
1199           p_person_id,
1200           p_course_cd,
1201           p_unit_cd,
1202           p_teach_cal_type,
1203           p_teach_ci_sequence_number,
1204           l_unit_attempt_status,
1205           'Y',
1206           l_outcome_dt,
1207           l_grading_schema_cd,
1208           l_gs_version_number,
1209           l_grade,
1210           l_mark,
1211           l_origin_course_cd,
1212           p_uoo_id,
1213 	  NVL (p_use_released_grade, 'N'));
1214 
1215     ---deleted the condition for checking the released grade as it is
1216     ---already handled in the GEN 003 package,hence deleting the variable
1217     ---l_reased_ind.
1218 
1219 
1220     -- Determine the CP value for the Student Unit Attempt
1221     -- Modified the next statment as per the Bug# 3419920; Nalin Kumar; 17-Feb-2004;
1222     --
1223     l_unit_cp := NVL(l_sua_override_cp, NVL(l_uc_credit_points, l_uv_credit_points));
1224     --
1225     -- Getting the GPA value for the grading scema code
1226     --
1227     OPEN c_grad_schema_gpa(l_grading_schema_cd, l_gs_version_number, l_grade);
1228     FETCH c_grad_schema_gpa INTO l_gsg_gpa_value, l_gsg_show;
1229     IF c_grad_schema_gpa%FOUND THEN
1230     ---removed the if condition for checking the value of l_reased_ind as it is no more required.
1231         IF l_gsg_gpa_value IS NOT NULL AND
1232            l_result_type NOT IN ('WITHDRAWN', 'INCOMP') THEN
1233           p_gpa_cp := l_unit_cp;
1234           p_gpa_quality_points := l_gsg_gpa_value * l_unit_cp;
1235           IF NVL(p_gpa_cp, 0) = 0 THEN
1236             p_gpa_value := 0;
1237           ELSE
1238             p_gpa_value := p_gpa_quality_points / p_gpa_cp;
1239           END IF;
1240         END IF;
1241     END IF;
1242     CLOSE c_grad_schema_gpa;
1243     --
1244     -- Only Consider the PASS Outcomes for the Earned Credit Points.
1245     -- ijeddy, bug 3489388.
1246     IF ((l_result_type = 'PASS') AND (l_gsg_show = 'Y')) THEN
1247       p_earned_cp := l_unit_cp;
1248     ELSE
1249       p_earned_cp := NULL;
1250     END IF;
1251     --
1252     -- Consider all Outcomes for the Attempted Credit Points
1253     -- Return the Unit CP when there is no outcome for the SUA
1254     -- ijeddy, bug 3489388.
1255     IF (((l_gsg_show = 'Y') AND (l_grade IS NOT NULL)) OR (l_grade IS NULL)) THEN
1256       p_attempted_cp  := l_unit_cp;
1257     ELSE -- Rest all cases
1258       p_attempted_cp  := NULL;
1259     END IF;
1260 
1261     -- Consider all Outcomes for the enrolled Credit Points
1262     -- Return the Unit CP when there is SUA is in ENROLLED status
1263     -- jhanda  3843525
1264 
1265     IF l_unit_attempt_status = 'ENROLLED' THEN
1266        p_enrolled_cp := l_unit_cp;
1267     END IF;
1268 
1269     -- Initialize API return status to success.
1270     p_return_status := fnd_api.g_ret_sts_success;
1271     -- Standard call to get message count and if count is 1, get message info.
1272     fnd_msg_pub.count_and_get(
1273       p_encoded => fnd_api.g_false,
1274       p_count => p_msg_count,
1275       p_data => p_msg_data);
1276   EXCEPTION
1277     WHEN fnd_api.g_exc_error THEN
1278       p_return_status := fnd_api.g_ret_sts_error;
1279       fnd_msg_pub.count_and_get(
1280         p_encoded => fnd_api.g_false,
1281         p_count => p_msg_count,
1282         p_data => p_msg_data);
1283     WHEN fnd_api.g_exc_unexpected_error THEN
1284       p_return_status := fnd_api.g_ret_sts_unexp_error;
1285       fnd_msg_pub.count_and_get(
1286         p_encoded => fnd_api.g_false,
1287         p_count => p_msg_count,
1288         p_data => p_msg_data);
1289     WHEN OTHERS THEN
1290       p_return_status := fnd_api.g_ret_sts_unexp_error;
1291       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1292       fnd_message.set_token('NAME', 'GET_SUA_STATS: ' || SQLERRM);
1293       fnd_msg_pub.ADD;
1294       fnd_msg_pub.count_and_get(
1295         p_encoded => fnd_api.g_false,
1296         p_count => p_msg_count,
1297         p_data => p_msg_data);
1298   END get_sua_stats;
1299   --
1300   -- kdande; 23-Apr-2003; Bug# 2829262
1301   -- Added p_uoo_id parameter to the PROCEDURE get_sua_all
1302   --
1303 
1304   PROCEDURE get_sua_all (
1305     p_person_id                IN  igs_en_su_attempt.person_id%TYPE,
1306     p_course_cd                IN  igs_en_su_attempt.course_cd%TYPE,
1307     p_unit_cd                  IN  igs_en_su_attempt.unit_cd%TYPE,
1308     p_unit_version_number      IN  igs_en_su_attempt.version_number%TYPE,
1309     p_teach_cal_type           IN  igs_en_su_attempt.cal_type%TYPE,
1310     p_teach_ci_sequence_number IN  igs_en_su_attempt.ci_sequence_number%TYPE,
1311     p_stat_type                IN  igs_pr_org_stat.stat_type%TYPE,
1312     p_system_stat              IN  VARCHAR2,
1313     p_earned_cp                OUT NOCOPY NUMBER,
1314     p_attempted_cp             OUT NOCOPY NUMBER,
1315     p_gpa_value                OUT NOCOPY NUMBER,
1316     p_gpa_cp                   OUT NOCOPY NUMBER,
1317     p_gpa_quality_points       OUT NOCOPY NUMBER,
1318     p_init_msg_list            IN  VARCHAR2,
1319     p_return_status            OUT NOCOPY VARCHAR2,
1320     p_msg_count                OUT NOCOPY NUMBER,
1321     p_msg_data                 OUT NOCOPY VARCHAR2,
1322     p_uoo_id                   IN  NUMBER,
1323     p_use_released_grade       IN  VARCHAR2) IS
1324 
1325 -- Note param p_enrolled_cp needs to be added for bug 3843525
1326 
1327 --------------------------------------------------------------------------
1328 --  Created By : David Larsen
1329 --  Date Created On : 06-11-2002
1330 --  Purpose:  To check the statistic configuration, check if the unit is
1331 --            included or excluded and the derive all of the statistic
1332 --            values for a given Statistic Type for a Student Unit Attempt.
1333 --  Know limitations, enhancements or remarks
1334 --  Change History
1335 --  Who             When            What
1336 -- swaghmar; 15-Sep-2005; Bug 4491456 Modified the signature
1337 -- swaghmar;  15-Jun-2006;  Bug 5260180
1338 --------------------------------------------------------------------------
1339 
1340     l_stat_type          igs_pr_stat_type.stat_type%TYPE;
1341     l_org_unit_cd        igs_pr_org_stat.org_unit_cd%TYPE;
1342     l_include_std_ind    igs_pr_org_stat.include_standard_ind%TYPE;
1343     l_include_local_ind  igs_pr_org_stat.include_local_ind%TYPE;
1344     l_include_other_ind  igs_pr_org_stat.include_other_ind%TYPE;
1345     l_derivation         igs_pr_stat_type.derivation%TYPE;
1346     l_earned_cp          NUMBER;
1347     l_attempted_cp       NUMBER;
1348     l_gpa_cp             NUMBER;
1349     l_gpa_quality_points NUMBER;
1350     l_gpa_value          NUMBER;
1351     l_return_status      VARCHAR2(30);
1352     l_msg_count          NUMBER(2);
1353     l_msg_data           VARCHAR2(30);
1354     l_org_id             NUMBER(4);
1355     p_enrolled_cp        igs_ps_unit_ver.achievable_credit_points%TYPE :=0;
1356 
1357     -- Added as part of fix for Bug# 5260180
1358     v_inc_exc_ul         VARCHAR2(1) := 'Y';
1359     v_inc_exc_sua        VARCHAR2(1) := 'Y';
1360 
1361   BEGIN
1362     l_org_id := igs_ge_gen_003.get_org_id;
1363     igs_ge_gen_003.set_org_id(l_org_id);
1364 
1365     -- Initialize message list if p_init_msg_list is set to TRUE.
1366     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
1367       fnd_msg_pub.initialize;
1368     END IF;
1369 
1370     -- Validate the Parameters, so that must not be NULL
1371     IF (p_person_id IS NULL
1372         OR p_course_cd IS NULL
1373         OR p_unit_cd IS NULL
1374         OR p_unit_version_number IS NULL
1375         OR p_teach_cal_type IS NULL
1376         OR p_teach_ci_sequence_number IS NULL) THEN
1377       fnd_message.set_name('IGS', 'IGS_GE_INSUFFICIENT_PARAM_VAL');
1378       fnd_msg_pub.ADD;
1379       RAISE fnd_api.g_exc_error;
1380     END IF;
1381 
1382     p_gpa_value := NULL;
1383     p_gpa_cp := NULL;
1384     p_gpa_quality_points := NULL;
1385     p_attempted_cp := NULL;
1386     p_earned_cp := NULL;
1387     l_stat_type := p_stat_type;
1388     -- Call the Statistic Details Procedure to get the Statistic Details
1389     get_stat_dtls(  --**
1390       p_person_id,
1391       p_course_cd,
1392       p_system_stat,
1393       'N', -- Changed from NULL Bug Fix 2707516
1394       l_stat_type,
1395       l_org_unit_cd,
1396       l_include_std_ind,
1397       l_include_local_ind,
1398       l_include_other_ind,
1399       l_derivation,
1400       fnd_api.g_true,
1401       l_return_status,
1402       l_msg_count,
1403       l_msg_data);
1404 
1405     IF l_return_status <> fnd_api.g_ret_sts_success THEN
1406       p_gpa_value := NULL;
1407       p_gpa_cp := NULL;
1408       p_gpa_quality_points := NULL;
1409       p_earned_cp := NULL;
1410       p_attempted_cp := NULL;
1411       p_return_status := l_return_status;
1412       p_msg_count := l_msg_count;
1413       p_msg_data := l_msg_data;
1414       RETURN;
1415     END IF;
1416 
1417     -- If the Statistic Type is NULL then return the earned and attempted
1418     -- credit points as NULL
1419     IF l_stat_type IS NULL THEN
1420       p_gpa_value := NULL;
1421       p_gpa_cp := NULL;
1422       p_gpa_quality_points := NULL;
1423       p_earned_cp := NULL;
1424       p_attempted_cp := NULL;
1425       p_return_status := l_return_status;
1426       p_msg_count := l_msg_count;
1427       p_msg_data := l_msg_data;
1428       RETURN;
1429     END IF;
1430 
1431     -- Check for the Standard Indicator Flag then loop thru Student Unit Attempts
1432     IF l_include_std_ind = 'Y' THEN
1433       -- Check if the Unit Reference Code is included/excluded for this Stat Type
1434       IF chk_unit_ref_cd(
1435            p_unit_cd,
1436            p_unit_version_number,
1437            l_org_unit_cd,
1438            l_stat_type,
1439            fnd_api.g_true,
1440            l_return_status,
1441            l_msg_count,
1442            l_msg_data) = 'Y' THEN
1443         IF l_return_status <> fnd_api.g_ret_sts_success THEN
1444           p_return_status := l_return_status;
1445           p_msg_count := l_msg_count;
1446           p_msg_data := l_msg_data;
1447           RETURN;
1448         END IF;
1449         v_inc_exc_ul := 'Y';
1450       ELSE -- Added as part of fix for Bug# 5260180
1451         IF l_return_status <> fnd_api.g_ret_sts_success THEN
1452           p_return_status := l_return_status;
1453           p_msg_count := l_msg_count;
1454           p_msg_data := l_msg_data;
1455           RETURN;
1456         END IF;
1457         v_inc_exc_ul := 'N';
1458       END IF;
1459 
1460 	-- Calling the chk_sua_ref_cd() here and progress further only if the function returns 'Y'
1461         -- Check if Student Unit Attempt Reference Code is included/excluded for this Stat Type
1462         IF chk_sua_ref_cd(
1463              p_person_id,
1464              p_course_cd,
1465              p_uoo_id,
1466              l_org_unit_cd,
1467              l_stat_type,
1468              fnd_api.g_true,
1469              l_return_status,
1470              l_msg_count,
1471              l_msg_data) = 'Y' THEN
1472           IF l_return_status <> fnd_api.g_ret_sts_success THEN
1473             p_return_status := l_return_status;
1474             p_msg_count := l_msg_count;
1475             p_msg_data := l_msg_data;
1476             RETURN;
1477           END IF;
1478 	   v_inc_exc_sua := 'Y';
1479         ELSE -- Added as part of fix for Bug# 5260180
1480         IF l_return_status <> fnd_api.g_ret_sts_success THEN
1481           p_return_status := l_return_status;
1482           p_msg_count := l_msg_count;
1483           p_msg_data := l_msg_data;
1484           RETURN;
1485         END IF;
1486         v_inc_exc_sua := 'N';
1487       END IF;
1488 
1489          IF (v_inc_exc_sua = 'Y' OR v_inc_exc_ul = 'Y') THEN -- Added as part of fix for Bug# 5260180
1490 	-- Call GET_SUA_ALL to calculate the GPA and CP values for the Student
1491         -- Unit Attempt
1492         get_sua_stats(  --**
1493           p_person_id,
1494           p_course_cd,
1495           p_unit_cd,
1496           p_unit_version_number,
1497           p_teach_cal_type,
1498           p_teach_ci_sequence_number,
1499           l_earned_cp,
1500           l_attempted_cp,
1501           l_gpa_value,
1502           l_gpa_cp,
1503           l_gpa_quality_points,
1504           fnd_api.g_true,
1505           l_return_status,
1506           l_msg_count,
1507           l_msg_data,
1508           p_uoo_id,
1509           p_use_released_grade,
1510 	  p_enrolled_cp);
1511 
1512         IF l_return_status <> fnd_api.g_ret_sts_success THEN
1513           p_gpa_value := NULL;
1514           p_gpa_cp := NULL;
1515           p_gpa_quality_points := NULL;
1516           p_earned_cp := NULL;
1517           p_attempted_cp := NULL;
1518           p_return_status := l_return_status;
1519           p_msg_count := l_msg_count;
1520           p_msg_data := l_msg_data;
1521           RETURN;
1522         END IF;
1523       END IF;
1524     -- END IF;
1525     END IF;
1526 
1527     -- Set out NOCOPY parameters
1528     p_gpa_value := l_gpa_value;
1529     p_gpa_cp := l_gpa_cp;
1530     p_gpa_quality_points := l_gpa_quality_points;
1531     p_earned_cp := l_earned_cp;
1532     p_attempted_cp := l_attempted_cp;
1533     -- Initialize API return status to success.
1534     p_return_status := fnd_api.g_ret_sts_success;
1535     -- Standard call to get message count and if count is 1, get message info.
1536     fnd_msg_pub.count_and_get(
1537       p_encoded => fnd_api.g_false,
1538       p_count => p_msg_count,
1539       p_data => p_msg_data);
1540   EXCEPTION
1541     WHEN fnd_api.g_exc_error THEN
1542       p_return_status := fnd_api.g_ret_sts_error;
1543       fnd_msg_pub.count_and_get(
1544         p_encoded => fnd_api.g_false,
1545         p_count => p_msg_count,
1546         p_data => p_msg_data);
1547     WHEN fnd_api.g_exc_unexpected_error THEN
1548       p_return_status := fnd_api.g_ret_sts_unexp_error;
1549       fnd_msg_pub.count_and_get(
1550         p_encoded => fnd_api.g_false,
1551         p_count => p_msg_count,
1552         p_data => p_msg_data);
1553     WHEN OTHERS THEN
1554       p_return_status := fnd_api.g_ret_sts_unexp_error;
1555       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1556       fnd_message.set_token('NAME', 'GET_SUA_ALL: ' || SQLERRM);
1557       fnd_msg_pub.ADD;
1558       fnd_msg_pub.count_and_get(
1559         p_encoded => fnd_api.g_false,
1560         p_count => p_msg_count,
1561         p_data => p_msg_data);
1562   END get_sua_all;
1563 
1564   --
1565   -- kdande; 23-Apr-2003; Bug# 2829262
1566   -- Added p_uoo_id parameter to the FUNCTION get_sua_cp
1567   --
1568   PROCEDURE get_sua_cp(
1569     p_person_id                IN            igs_en_stdnt_ps_att.person_id%TYPE,
1570     p_course_cd                IN            igs_en_stdnt_ps_att.course_cd%TYPE,
1571     p_unit_cd                  IN            igs_ps_unit_ver.unit_cd%TYPE,
1572     p_unit_version_number      IN            igs_ps_unit_ver.version_number%TYPE,
1573     p_teach_cal_type           IN            igs_ca_inst.cal_type%TYPE,
1574     p_teach_ci_sequence_number IN            igs_ca_inst.sequence_number%TYPE,
1575     p_stat_type                IN            igs_pr_stat_type.stat_type%TYPE,
1576     p_system_stat              IN            VARCHAR2,
1577     p_earned_cp     OUT NOCOPY    NUMBER,
1578     p_attempted_cp  OUT NOCOPY    NUMBER,
1579     p_init_msg_list            IN            VARCHAR2,
1580     p_return_status            OUT NOCOPY    VARCHAR2,
1581     p_msg_count                OUT NOCOPY    NUMBER,
1582     p_msg_data                 OUT NOCOPY    VARCHAR2,
1583     p_uoo_id                   IN  NUMBER,
1584     p_use_released_grade       IN  VARCHAR2) AS
1585     /***************************************************************************
1586      Created By : rbezawad
1587      Date Created By : 31-Oct-2001
1588      Purpose : This procedure used to derive the Credit Point value for a given
1589                Statistics Type for a Student Unit Attempt
1590                1. Validate the Parameters if any of the required parameters Null
1591                   If any one is null then error out.
1592                2. Call get_unitstat_dtls() procedure to get the Statistic Type
1593                   Definition from Org Unit level or Inistitution Level.
1594                3. If there is no Static Type details available at Org Unit Level
1595                   or Inistitution Level then Error out.
1596                4. Get the Student Unit Attempt Details to calculate Credit Points
1597                   If there no Student Unit Attempt data then Error out.
1598                5. Call get_cp() procedure to Calculate Earned and Attempted
1599                   Credit points and return.
1600 
1601     Known limitations,enhancements,remarks:
1602     Change History
1603     Who      When      What
1604     ayedubat 24-1-2002 Changed the cursor c_sua_uv to consider the
1605                        Student_career_statics overriden at the Student Unit
1606                        Attempt Level
1607     swaghmar 15-9-2005 Bug 4491456 - Modified the signature
1608     ***************************************************************************/
1609 
1610     l_earned_cp          NUMBER;
1611     l_attempted_cp       NUMBER;
1612     l_gpa_cp             NUMBER;
1613     l_gpa_quality_points NUMBER;
1614     l_gpa_value          NUMBER;
1615     l_return_status      VARCHAR2(1);
1616     l_msg_count          NUMBER;
1617     l_msg_data           VARCHAR2(2000);
1618     l_org_id             NUMBER(4);
1619   BEGIN
1620     l_org_id := igs_ge_gen_003.get_org_id;
1621     igs_ge_gen_003.set_org_id(l_org_id);
1622 
1623     --Initialize message list if p_init_msg_list is set to TRUE.
1624     IF fnd_api.to_boolean(p_init_msg_list) THEN
1625       fnd_msg_pub.initialize;
1626     END IF;
1627 
1628     -- Validate the Parameters, so that must not be NULL
1629     IF (p_person_id IS NULL
1630         OR p_course_cd IS NULL
1631         OR p_unit_cd IS NULL
1632         OR p_unit_version_number IS NULL
1633         OR p_teach_cal_type IS NULL
1634         OR p_teach_ci_sequence_number IS NULL) THEN
1635       fnd_message.set_name('IGS', 'IGS_GE_INSUFFICIENT_PARAM_VAL');
1636       fnd_msg_pub.ADD;
1637       RAISE fnd_api.g_exc_error;
1638     END IF;
1639 
1640     -- Call GET_SUA_ALL to calculate the GPA and CP values for the Student Unit
1641     -- Attempt
1642     get_sua_all(
1643       p_person_id,
1644       p_course_cd,
1645       p_unit_cd,
1646       p_unit_version_number,
1647       p_teach_cal_type,
1648       p_teach_ci_sequence_number,
1649       p_stat_type,
1650       p_system_stat,
1651       l_earned_cp,
1652       l_attempted_cp,
1653       l_gpa_value,
1654       l_gpa_cp,
1655       l_gpa_quality_points,
1656       fnd_api.g_true,
1657       l_return_status,
1658       l_msg_count,
1659       l_msg_data,
1660       p_uoo_id,
1661       p_use_released_grade);
1662 
1663     -- If any Error is occurred in get_cp procedure Then return.
1664     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1665       p_return_status := l_return_status;
1666       p_msg_count := l_msg_count;
1667       p_msg_data := l_msg_data;
1668       RETURN;
1669     END IF;
1670 
1671     -- Set out NOCOPY parameters
1672     p_earned_cp := l_earned_cp;
1673     p_attempted_cp := l_attempted_cp;
1674     -- Initialize API return status to success.
1675     p_return_status := fnd_api.g_ret_sts_success;
1676     -- Standard call to get message count and if count is 1, get message info.
1677     fnd_msg_pub.count_and_get(
1678       p_encoded => fnd_api.g_false,
1679       p_count => p_msg_count,
1680       p_data => p_msg_data);
1681   EXCEPTION
1682     WHEN fnd_api.g_exc_error THEN
1683       p_return_status := fnd_api.g_ret_sts_error;
1684       fnd_msg_pub.count_and_get(
1685         p_encoded => fnd_api.g_false,
1686         p_count => p_msg_count,
1687         p_data => p_msg_data);
1688     WHEN fnd_api.g_exc_unexpected_error THEN
1689       p_return_status := fnd_api.g_ret_sts_unexp_error;
1690       fnd_msg_pub.count_and_get(
1691         p_encoded => fnd_api.g_false,
1692         p_count => p_msg_count,
1693         p_data => p_msg_data);
1694     WHEN OTHERS THEN
1695       p_return_status := fnd_api.g_ret_sts_unexp_error;
1696       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1697       fnd_message.set_token('NAME', 'get_sua_cp: ' || SQLERRM);
1698       fnd_msg_pub.ADD;
1699       fnd_msg_pub.count_and_get(
1700         p_encoded => fnd_api.g_false,
1701         p_count => p_msg_count,
1702         p_data => p_msg_data);
1703   END get_sua_cp;
1704 
1705   --
1706   -- kdande; 23-Apr-2003; Bug# 2829262
1707   -- Added p_uoo_id parameter to the FUNCTION get_sua_gpa
1708   -- swaghmar; 15-Sep-2005; Bug 4491456 - Modified the signature
1709   --
1710   PROCEDURE get_sua_gpa(
1711     p_person_id                IN            igs_en_stdnt_ps_att.person_id%TYPE,
1712     p_course_cd                IN            igs_en_stdnt_ps_att.course_cd%TYPE,
1713     p_unit_cd                  IN            igs_ps_unit_ver.unit_cd%TYPE,
1714     p_unit_version_number      IN            igs_ps_unit_ver.version_number%TYPE,
1715     p_teach_cal_type           IN            igs_ca_inst.cal_type%TYPE,
1716     p_teach_ci_sequence_number IN            igs_ca_inst.sequence_number%TYPE,
1717     p_stat_type                IN            igs_pr_stat_type.stat_type%TYPE,
1718     p_system_stat              IN            VARCHAR2,
1719     p_init_msg_list            IN            VARCHAR2,
1720     p_gpa_value                OUT NOCOPY    NUMBER,
1721     p_gpa_cp                   OUT NOCOPY    NUMBER,
1722     p_gpa_quality_points       OUT NOCOPY    NUMBER,
1723     p_return_status            OUT NOCOPY    VARCHAR2,
1724     p_msg_count                OUT NOCOPY    NUMBER,
1725     p_msg_data                 OUT NOCOPY    VARCHAR2,
1726     p_uoo_id                   IN            NUMBER,
1727     p_use_released_grade       IN            VARCHAR2) IS
1728 
1729 --------------------------------------------------------------------------
1730 --  Created By : Nishikant
1731 --  Date Created On : 06-11-2001
1732 --  Purpose:  To derive the GPA valua for a given Statistic Type for
1733 --            a Student Unit Attempt.
1734 --  Know limitations, enhancements or remarks
1735 --  Change History
1736 --  Who         When        What
1737 -- swaghmar; 15-Sep-2005; Bug 4491456 - Modified the signature
1738 --  ayedubat    24-1-2002   Changed the cursor c_sua_uv to consider
1739 --                          the Student_career_statics overriden
1740 --                          at the Student Unit Attempt Level
1741 --  (reverse chronological order - newest change first)
1742 --------------------------------------------------------------------------
1743 
1744     l_earned_cp          igs_ps_unit_ver.achievable_credit_points%TYPE;
1745     l_attempted_cp       igs_ps_unit_ver.achievable_credit_points%TYPE;
1746     l_gpa_cp             NUMBER;
1747     l_gpa_quality_points NUMBER;
1748     l_gpa_value          NUMBER;
1749     l_return_status      VARCHAR2(30);
1750     l_msg_count          NUMBER(2);
1751     l_msg_data           VARCHAR2(30);
1752     l_org_id             NUMBER(4);
1753   BEGIN
1754     l_org_id := igs_ge_gen_003.get_org_id;
1755     igs_ge_gen_003.set_org_id(l_org_id);
1756 
1757     --Initialize message list if p_init_msg_list is set to TRUE.
1758     IF fnd_api.to_boolean(p_init_msg_list) THEN
1759       fnd_msg_pub.initialize;
1760     END IF;
1761 
1762     -- Validate the Parameters, so that must not be NULL
1763     IF (p_person_id IS NULL
1764         OR p_course_cd IS NULL
1765         OR p_unit_cd IS NULL
1766         OR p_unit_version_number IS NULL
1767         OR p_teach_cal_type IS NULL
1768         OR p_teach_ci_sequence_number IS NULL) THEN
1769       fnd_message.set_name('IGS', 'IGS_GE_INSUFFICIENT_PARAM_VAL');
1770       fnd_msg_pub.ADD;
1771       RAISE fnd_api.g_exc_error;
1772     END IF;
1773 
1774     -- Call GET_SUA_ALL to calculate the GPA and CP values for the Student Unit
1775     -- Attempt
1776     get_sua_all(
1777       p_person_id,
1778       p_course_cd,
1779       p_unit_cd,
1780       p_unit_version_number,
1781       p_teach_cal_type,
1782       p_teach_ci_sequence_number,
1783       p_stat_type,
1784       p_system_stat,
1785       l_earned_cp,
1786       l_attempted_cp,
1787       l_gpa_value,
1788       l_gpa_cp,
1789       l_gpa_quality_points,
1790       fnd_api.g_true,
1791       l_return_status,
1792       l_msg_count,
1793       l_msg_data,
1794       p_uoo_id,
1795       p_use_released_grade);
1796 
1797     -- If any Error is occurred in get_cp procedure Then return.
1798     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
1799       p_return_status := l_return_status;
1800       p_msg_count := l_msg_count;
1801       p_msg_data := l_msg_data;
1802       RETURN;
1803     END IF;
1804 
1805     -- Set out NOCOPY parameters
1806     p_gpa_value := l_gpa_value;
1807     p_gpa_cp := l_gpa_cp;
1808     p_gpa_quality_points := l_gpa_quality_points;
1809     -- Initialize API return status to success.
1810     p_return_status := fnd_api.g_ret_sts_success;
1811     -- Standard call to get message count and if count is 1, get message info.
1812     fnd_msg_pub.count_and_get(
1813       p_encoded => fnd_api.g_false,
1814       p_count => p_msg_count,
1815       p_data => p_msg_data);
1816   EXCEPTION
1817     WHEN fnd_api.g_exc_error THEN
1818       p_return_status := fnd_api.g_ret_sts_error;
1819       fnd_msg_pub.count_and_get(
1820         p_encoded => fnd_api.g_false,
1821         p_count => p_msg_count,
1822         p_data => p_msg_data);
1823     WHEN fnd_api.g_exc_unexpected_error THEN
1824       p_return_status := fnd_api.g_ret_sts_unexp_error;
1825       fnd_msg_pub.count_and_get(
1826         p_encoded => fnd_api.g_false,
1827         p_count => p_msg_count,
1828         p_data => p_msg_data);
1829     WHEN OTHERS THEN
1830       p_return_status := fnd_api.g_ret_sts_unexp_error;
1831       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1832       fnd_message.set_token('NAME', 'GET_SUA_GPA: ' || SQLERRM);
1833       fnd_msg_pub.ADD;
1834       fnd_msg_pub.count_and_get(
1835         p_encoded => fnd_api.g_false,
1836         p_count => p_msg_count,
1837         p_data => p_msg_data);
1838   END get_sua_gpa;
1839 
1840  --
1841  -- swaghmar; 15-Sep-2005; Bug 4491456
1842  --	Modified the signature
1843  --
1844 
1845   PROCEDURE get_all_stats(
1846     p_person_id                   IN         igs_en_stdnt_ps_att.person_id%TYPE ,
1847     p_course_cd                   IN         igs_en_stdnt_ps_att.course_cd%TYPE ,
1848     p_stat_type                   IN         igs_pr_stat_type.stat_type%TYPE ,
1849     p_load_cal_type               IN         igs_ca_inst.cal_type%TYPE ,
1850     p_load_ci_sequence_number     IN         igs_ca_inst.sequence_number%TYPE ,
1851     p_system_stat                 IN         VARCHAR2,
1852     p_cumulative_ind              IN         VARCHAR2,
1853     p_earned_cp                   OUT NOCOPY NUMBER,
1854     p_attempted_cp                OUT NOCOPY NUMBER,
1855     p_gpa_value                   OUT NOCOPY NUMBER,
1856     p_gpa_cp                      OUT NOCOPY NUMBER,
1857     p_gpa_quality_points          OUT NOCOPY NUMBER,
1858     p_init_msg_list               IN         VARCHAR2,
1859     p_return_status               OUT NOCOPY VARCHAR2,
1860     p_msg_count                   OUT NOCOPY NUMBER,
1861     p_msg_data                    OUT NOCOPY VARCHAR2,
1862     p_use_released_grade          IN         VARCHAR2) IS
1863 
1864 
1865     p_enrolled_cp    igs_pr_stu_acad_stat.gpa_quality_points%TYPE;
1866   BEGIN
1867     ----  This procedure is being stubbed for the time being to reduce the impact of change for
1868     ----  Bug 3843525
1869 	get_all_stats_new(
1870 	    p_person_id                   ,
1871 	    p_course_cd                   ,
1872 	    p_stat_type                   ,
1873 	    p_load_cal_type               ,
1874 	    p_load_ci_sequence_number     ,
1875 	    p_system_stat                 ,
1876 	    p_cumulative_ind              ,
1877 	    p_earned_cp                   ,
1878 	    p_attempted_cp                ,
1879 	    p_gpa_value                   ,
1880 	    p_gpa_cp                      ,
1881 	    p_gpa_quality_points          ,
1882 	    p_init_msg_list               ,
1883 	    p_return_status               ,
1884 	    p_msg_count                   ,
1885 	    p_msg_data                    ,
1886 	    p_use_released_grade          ,
1887 	    p_enrolled_cp );
1888 
1889   END get_all_stats;
1890 
1891  --
1892  -- swaghmar; 15-Sep-2005; Bug 4491456
1893  --	Modified the signature
1894  --
1895 
1896   PROCEDURE get_all_stats_new(
1897     p_person_id                   IN         igs_en_stdnt_ps_att.person_id%TYPE ,
1898     p_course_cd                   IN         igs_en_stdnt_ps_att.course_cd%TYPE ,
1899     p_stat_type                   IN         igs_pr_stat_type.stat_type%TYPE ,
1900     p_load_cal_type               IN         igs_ca_inst.cal_type%TYPE ,
1901     p_load_ci_sequence_number     IN         igs_ca_inst.sequence_number%TYPE ,
1902     p_system_stat                 IN         VARCHAR2,
1903     p_cumulative_ind              IN         VARCHAR2,
1904     p_earned_cp                   OUT NOCOPY NUMBER,
1905     p_attempted_cp                OUT NOCOPY NUMBER,
1906     p_gpa_value                   OUT NOCOPY NUMBER,
1907     p_gpa_cp                      OUT NOCOPY NUMBER,
1908     p_gpa_quality_points          OUT NOCOPY NUMBER,
1909     p_init_msg_list               IN         VARCHAR2,
1910     p_return_status               OUT NOCOPY VARCHAR2,
1911     p_msg_count                   OUT NOCOPY NUMBER,
1912     p_msg_data                    OUT NOCOPY VARCHAR2,
1913     p_use_released_grade          IN         VARCHAR2,
1914     p_enrolled_cp                 OUT NOCOPY igs_pr_stu_acad_stat.gpa_quality_points%TYPE) IS
1915 
1916     -- Note param p_enrolled_cp  added for bug 3843525  jhanda
1917     /*
1918     ||==============================================================================||
1919     ||  Created By : Prajeesh Chandran                                              ||
1920     ||  Created On : 6-NOV-2001                                                     ||
1921     ||  Purpose : Gets the Cumulative CreditPoints or GPA                           ||
1922     ||  Known limitations, enhancements or remarks :                                ||
1923     ||  Change History :                                                            ||
1924     ||  Who      When        What                                                   ||
1925     ||  (reverse chronological order - newest change first)                         ||
1926     ||==============================================================================||
1927     ||  ayedubat    24-Jan-2002 Changed the cursor c_sua_uv to consider the         ||
1928     ||                       Student_career_statics overriden at the                ||
1929     ||                       Student Unit Attempt Level                             ||
1930     ||  kdande     20-Sep-2002 Bug# 2560160:Defaulted the p_init_msg_list parameter ||
1931     ||                       in the code since default value is removed from the    ||
1932     ||                       procedure signature.                                   ||
1933     ||==============================================================================||
1934     */
1935 
1936     -- Cursor to find the Student Unit Attempts for the Load Calendar
1937     --
1938     -- kdande; 23-Apr-2003; Bug# 2829262
1939     -- Added uoo_id field to the SELECT clause of cursor c_sua_uv
1940     --
1941     CURSOR c_sua_uv IS
1942 	SELECT   sua.person_id,sua.course_cd, sua.unit_cd, sua.version_number, sua.cal_type, sua.ci_sequence_number,
1943 		 sua.uoo_id ,sua.unit_attempt_status
1944 	    FROM igs_en_su_attempt_ALL sua, igs_ca_inst ci1
1945 	   WHERE sua.person_id = p_person_id
1946 	     AND sua.course_cd = p_course_cd
1947 	     AND sua.unit_attempt_status IN
1948 				     ('COMPLETED', 'DUPLICATE', 'ENROLLED', 'DISCONTIN')
1949 	     AND ci1.cal_type = sua.cal_type
1950 	     AND ci1.sequence_number = sua.ci_sequence_number
1951 	     AND (   (    p_cumulative_ind = 'N'
1952 		      AND EXISTS ( SELECT 'X'
1953 				     FROM igs_ca_load_to_teach_v ltt1
1954 				    WHERE p_load_cal_type = ltt1.load_cal_type
1955 				      AND p_load_ci_sequence_number =
1956 							  ltt1.load_ci_sequence_number
1957 				      AND sua.cal_type = ltt1.teach_cal_type
1958 				      AND sua.ci_sequence_number =
1959 							 ltt1.teach_ci_sequence_number)
1960 		     )
1961 		  OR (    p_cumulative_ind = 'Y'
1962 		      AND EXISTS ( SELECT 'X'
1963 				     FROM igs_ca_inst ci2, igs_ca_load_to_teach_v ltt2
1964 				    WHERE ci2.cal_type = p_load_cal_type
1965 				      AND ci2.sequence_number =
1966 							     p_load_ci_sequence_number
1967 				      AND sua.cal_type = ltt2.teach_cal_type
1968 				      AND sua.ci_sequence_number =
1969 							 ltt2.teach_ci_sequence_number
1970 				      AND ltt2.load_end_dt <= ci2.end_dt)
1971 		     )
1972 		 )
1973 	ORDER BY sua.unit_cd ASC, sua.ci_end_dt ASC;
1974 
1975 
1976     CURSOR c_sas(cp_stat_type igs_pr_stat_type.stat_type%TYPE) IS
1977       SELECT sas.earned_credit_points,
1978              sas.attempted_credit_points,
1979              sas.gpa,
1980              sas.gpa_credit_points,
1981              sas.gpa_quality_points
1982         FROM igs_pr_stu_acad_stat sas
1983        WHERE sas.person_id = p_person_id
1984          AND sas.course_cd = p_course_cd
1985          AND sas.cal_type = p_load_cal_type
1986          AND sas.ci_sequence_number = p_load_ci_sequence_number
1987          AND sas.stat_type = cp_stat_type
1988          AND ((sas.timeframe IN ('CUMULATIVE','BOTH') AND p_cumulative_ind = 'Y')
1989               OR (sas.timeframe IN ('PERIOD','BOTH') AND p_cumulative_ind = 'N'));
1990 
1991     lc_sua_uv            c_sua_uv%ROWTYPE;
1992     lc_sas               c_sas%ROWTYPE;
1993     l_earned_cp          NUMBER   := 0;
1994     l_attempted_cp       NUMBER   := 0;
1995     l_gpa_cp             NUMBER     := 0;
1996     l_gpa_quality_points NUMBER   := 0;
1997     l_earned_cp_total    NUMBER   := 0;
1998     l_attempted_cp_total NUMBER   := 0;
1999     l_gpa_cp_total       NUMBER   := 0;
2000     l_gpa_qp_total       NUMBER   := 0;
2001     l_gpa_value          NUMBER   := 0;
2002     l_stat_type          igs_pr_stat_type.stat_type%TYPE;
2003     l_org_unit_cd        igs_pr_org_stat.org_unit_cd%TYPE;
2004     l_include_std_ind    igs_pr_org_stat.include_standard_ind%TYPE;
2005     l_include_local_ind  igs_pr_org_stat.include_local_ind%TYPE;
2006     l_include_other_ind  igs_pr_org_stat.include_other_ind%TYPE;
2007     l_derivation         igs_pr_stat_type.derivation%TYPE;
2008     l_init_msg_list      VARCHAR2(20);
2009     l_return_status      VARCHAR2(30);
2010     l_msg_count          NUMBER(2);
2011     l_msg_data           VARCHAR2(30);
2012     l_org_id             NUMBER(4);
2013     l_enrolled_cp       igs_pr_stu_acad_stat.gpa_credit_points%TYPE   := 0;
2014     l_enrolled_cp_total  igs_ps_unit_ver.achievable_credit_points%TYPE   := 0;
2015 
2016     -- Added as part of fix for Bug# 5260180
2017     v_inc_exc_ul         VARCHAR2(1) := 'Y';
2018     v_inc_exc_sua        VARCHAR2(1) := 'Y';
2019 
2020   BEGIN
2021     l_org_id := igs_ge_gen_003.get_org_id;
2022     igs_ge_gen_003.set_org_id(l_org_id);
2023 
2024     -- Initialize message list if p_init_msg_list is set to TRUE.
2025     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
2026       fnd_msg_pub.initialize;
2027     END IF;
2028 
2029     -- Validate the Parameters, so that must not be NULL
2030     IF (p_person_id IS NULL
2031         OR p_course_cd IS NULL
2032         OR p_load_cal_type IS NULL
2033         OR p_load_ci_sequence_number IS NULL) THEN
2034       fnd_message.set_name('IGS', 'IGS_GE_INSUFFICIENT_PARAM_VAL');
2035       fnd_msg_pub.ADD;
2036       RAISE fnd_api.g_exc_error;
2037     END IF;
2038 
2039     p_gpa_value := NULL;
2040     p_gpa_cp := NULL;
2041     p_gpa_quality_points := NULL;
2042     p_attempted_cp := NULL;
2043     p_earned_cp := NULL;
2044     l_stat_type := p_stat_type;
2045     -- Call the Statistic Details Procedure to get the Statistic Details
2046     get_stat_dtls(
2047       p_person_id,
2048       p_course_cd,
2049       p_system_stat,
2050       p_cumulative_ind,
2051       l_stat_type,
2052       l_org_unit_cd,
2053       l_include_std_ind,
2054       l_include_local_ind,
2055       l_include_other_ind,
2056       l_derivation,
2057       fnd_api.g_true,
2058       l_return_status,
2059       l_msg_count,
2060       l_msg_data);
2061 
2062     IF l_return_status <> fnd_api.g_ret_sts_success THEN
2063       p_gpa_value := NULL;
2064       p_gpa_cp := NULL;
2065       p_gpa_quality_points := NULL;
2066       p_earned_cp := NULL;
2067       p_attempted_cp := NULL;
2068       p_return_status := l_return_status;
2069       p_msg_count := l_msg_count;
2070       p_msg_data := l_msg_data;
2071       p_enrolled_cp := NULL;
2072       RETURN;
2073     END IF;
2074 
2075     -- If the Statistic Type is NULL then return the earned and attempted
2076     -- credit points as NULL
2077     IF l_stat_type IS NULL THEN
2078       p_gpa_value := NULL;
2079       p_gpa_cp := NULL;
2080       p_gpa_quality_points := NULL;
2081       p_earned_cp := NULL;
2082       p_attempted_cp := NULL;
2083       p_return_status := l_return_status;
2084       p_msg_count := l_msg_count;
2085       p_msg_data := l_msg_data;
2086       p_enrolled_cp := NULL;
2087       RETURN;
2088     END IF;
2089 
2090     -- If the Stat Type can be stored check for stored values.
2091     IF l_derivation IN ('STORED') THEN
2092       OPEN c_sas(l_stat_type);
2093       FETCH c_sas INTO lc_sas;
2094 
2095       IF c_sas%FOUND THEN
2096         CLOSE c_sas;
2097         -- Assign the returned values to the Output parameters
2098         p_earned_cp := lc_sas.earned_credit_points;
2099         p_attempted_cp := lc_sas.attempted_credit_points;
2100         p_gpa_value := lc_sas.gpa;
2101         p_gpa_cp := lc_sas.gpa_credit_points;
2102         p_gpa_quality_points := lc_sas.gpa_quality_points;
2103         -- Initialize API return status to success.
2104         p_return_status := fnd_api.g_ret_sts_success;
2105         -- Standard call to get message count and if count is 1, get message info
2106         fnd_msg_pub.count_and_get(
2107           p_encoded => fnd_api.g_false,
2108           p_count => p_msg_count,
2109           p_data => p_msg_data);
2110         RETURN;
2111       ELSE
2112         -- that is no value found for STORED stats
2113         -- set out params to NULL as per bug 3042490
2114         p_earned_cp           :=NULL;
2115         p_attempted_cp        :=NULL;
2116         p_gpa_value           :=NULL;
2117         p_gpa_cp              :=NULL;
2118         p_gpa_quality_points  :=NULL;
2119 
2120         -- Initialize API return status to success.
2121         p_return_status := fnd_api.g_ret_sts_success;
2122         -- Standard call to get message count and if count is 1, get message info
2123         fnd_msg_pub.count_and_get(
2124           p_encoded => fnd_api.g_false,
2125           p_count => p_msg_count,
2126           p_data => p_msg_data);
2127 
2128         RETURN;
2129       END IF;
2130 
2131       CLOSE c_sas;
2132     END IF;
2133 
2134 
2135     IF l_derivation IN ('BOTH') THEN
2136       OPEN c_sas(l_stat_type);
2137       FETCH c_sas INTO lc_sas;
2138 
2139       IF c_sas%FOUND THEN
2140         CLOSE c_sas;
2141         -- Assign the returned values to the Output parameters
2142         p_earned_cp := lc_sas.earned_credit_points;
2143         p_attempted_cp := lc_sas.attempted_credit_points;
2144         p_gpa_value := lc_sas.gpa;
2145         p_gpa_cp := lc_sas.gpa_credit_points;
2146         p_gpa_quality_points := lc_sas.gpa_quality_points;
2147         -- Initialize API return status to success.
2148         p_return_status := fnd_api.g_ret_sts_success;
2149         -- Standard call to get message count and if count is 1, get message info
2150         fnd_msg_pub.count_and_get(
2151           p_encoded => fnd_api.g_false,
2152           p_count => p_msg_count,
2153           p_data => p_msg_data);
2154         RETURN;
2155       END IF;
2156 
2157       CLOSE c_sas;
2158     END IF;
2159 
2160 
2161     -- Check for the Standard Indicator Flag then loop through Student Unit
2162     -- Attempts
2163     IF l_include_std_ind = 'Y' THEN
2164       -- Loop through all of the Student Unit Attempts records (SUA)
2165       FOR lc_sua_uv IN c_sua_uv LOOP
2166         -- Check if Unit Reference Code is included/excluded for this Stat Type
2167         IF chk_unit_ref_cd(
2168              lc_sua_uv.unit_cd,
2169              lc_sua_uv.version_number,
2170              l_org_unit_cd,
2171              l_stat_type,
2172              fnd_api.g_true,
2173              l_return_status,
2174              l_msg_count,
2175              l_msg_data) = 'Y' THEN
2176           IF l_return_status <> fnd_api.g_ret_sts_success THEN
2177             p_return_status := l_return_status;
2178             p_msg_count := l_msg_count;
2179             p_msg_data := l_msg_data;
2180             RETURN;
2181 	  END IF;
2182         ELSE  -- Added as part of fix for Bug# 5260180
2183              v_inc_exc_ul := 'N';
2184              IF l_return_status <> fnd_api.g_ret_sts_success THEN
2185                 p_return_status := l_return_status;
2186                 p_msg_count := l_msg_count;
2187                 p_msg_data := l_msg_data;
2188                 RETURN;
2189              END IF;
2190         END IF;
2191 
2192         -- Calling the chk_sua_ref_cd() here and progress further only if the function returns 'Y'
2193         -- Check if Student Unit Attempt Reference Code is included/excluded for this Stat Type
2194 
2195         IF chk_sua_ref_cd(
2196              lc_sua_uv.person_id,
2197              lc_sua_uv.course_cd,
2198              lc_sua_uv.uoo_id,
2199              l_org_unit_cd,
2200              l_stat_type,
2201              fnd_api.g_true,
2202              l_return_status,
2203              l_msg_count,
2204              l_msg_data) = 'Y' THEN
2205           IF l_return_status <> fnd_api.g_ret_sts_success THEN
2206             p_return_status := l_return_status;
2207             p_msg_count := l_msg_count;
2208             p_msg_data := l_msg_data;
2209             RETURN;
2210 	    END IF;
2211          ELSE -- Added as part of fix for Bug# 5260180
2212              v_inc_exc_sua := 'N';
2213              IF l_return_status <> fnd_api.g_ret_sts_success THEN
2214                p_return_status := l_return_status;
2215                p_msg_count := l_msg_count;
2216                p_msg_data := l_msg_data;
2217                RETURN;
2218              END IF;
2219         END IF;
2220           -- Call GET_SUA_STATS to calculate the GPA and CP values for the
2221           -- Student Unit Attempt
2222           IF (v_inc_exc_sua = 'Y' OR v_inc_exc_ul = 'Y') THEN -- Added as part of fix for Bug# 5260180
2223 	  get_sua_stats(
2224             p_person_id,
2225             p_course_cd,
2226             lc_sua_uv.unit_cd,
2227             lc_sua_uv.version_number,
2228             lc_sua_uv.cal_type,
2229             lc_sua_uv.ci_sequence_number,
2230             l_earned_cp,
2231             l_attempted_cp,
2232             l_gpa_value,
2233             l_gpa_cp,
2234             l_gpa_quality_points,
2235             fnd_api.g_true,
2236             l_return_status,
2237             l_msg_count,
2238             l_msg_data,
2239             lc_sua_uv.uoo_id,
2240             p_use_released_grade,
2241 	    l_enrolled_cp);
2242 
2243           IF l_return_status <> fnd_api.g_ret_sts_success THEN
2244             p_gpa_value := NULL;
2245             p_gpa_cp := NULL;
2246             p_gpa_quality_points := NULL;
2247             p_earned_cp := NULL;
2248             p_attempted_cp := NULL;
2249             p_return_status := l_return_status;
2250             p_msg_count := l_msg_count;
2251             p_msg_data := l_msg_data;
2252             RETURN;
2253           END IF;
2254 
2255           --Total the Credit Points for all the Student Unit Attempts.
2256           l_attempted_cp_total := l_attempted_cp_total + NVL(l_attempted_cp, 0);
2257           l_earned_cp_total := l_earned_cp_total + NVL(l_earned_cp, 0);
2258           l_gpa_cp_total := l_gpa_cp_total + NVL(l_gpa_cp, 0);
2259           l_gpa_qp_total := l_gpa_qp_total + NVL(l_gpa_quality_points, 0);
2260 	  IF lc_sua_uv.unit_attempt_status = 'ENROLLED' THEN
2261          	  l_enrolled_cp_total := l_enrolled_cp_total +  NVL(l_enrolled_cp,0);
2262 	  END IF;
2263     --    END IF;
2264         END IF;
2265       END LOOP;
2266     END IF;
2267     -- Check the flag for Advanced Standing then call the Advanced Standing
2268     -- Procedure
2269     IF l_include_local_ind = 'Y'
2270        OR l_include_other_ind = 'Y' THEN
2271       get_adv_stats(
2272         p_person_id,
2273         p_course_cd,
2274         l_stat_type,
2275         l_org_unit_cd,
2276         p_load_cal_type,
2277         p_load_ci_sequence_number,
2278         p_cumulative_ind,
2279         l_include_local_ind,
2280         l_include_other_ind,
2281         l_earned_cp,
2282         l_attempted_cp,
2283         l_gpa_cp,
2284         l_gpa_quality_points,
2285         fnd_api.g_true,
2286         l_return_status,
2287         l_msg_count,
2288         l_msg_data);
2289       --Total the Credit Points for all the Student Unit Attempts.
2290       l_attempted_cp_total := l_attempted_cp_total + NVL(l_attempted_cp, 0);
2291       l_earned_cp_total := l_earned_cp_total + NVL(l_earned_cp, 0);
2292       l_gpa_cp_total := l_gpa_cp_total + NVL(l_gpa_cp, 0);
2293       l_gpa_qp_total := l_gpa_qp_total + NVL(l_gpa_quality_points, 0);
2294     END IF;
2295 
2296     -- Calculate the GPA Value
2297     IF NVL(l_gpa_cp_total, 0) > 0 THEN
2298       l_gpa_value := l_gpa_qp_total / l_gpa_cp_total;
2299     END IF;
2300 
2301     -- Assign the Output parameters
2302     p_gpa_value := l_gpa_value;
2303     p_gpa_cp := l_gpa_cp_total;
2304     p_gpa_quality_points := l_gpa_qp_total;
2305     p_attempted_cp := l_attempted_cp_total;
2306     p_earned_cp := l_earned_cp_total;
2307     p_enrolled_cp :=l_enrolled_cp_total;
2308     -- Initialize API return status to success.
2309     p_return_status := fnd_api.g_ret_sts_success;
2310     -- Standard call to get message count and if count is 1, get message
2311     -- info.
2312     fnd_msg_pub.count_and_get(
2313       p_encoded => fnd_api.g_false,
2314       p_count => p_msg_count,
2315       p_data => p_msg_data);
2316   EXCEPTION
2317     WHEN fnd_api.g_exc_error THEN
2318       p_return_status := fnd_api.g_ret_sts_error;
2319       fnd_msg_pub.count_and_get(
2320         p_encoded => fnd_api.g_false,
2321         p_count => p_msg_count,
2322         p_data => p_msg_data);
2323     WHEN fnd_api.g_exc_unexpected_error THEN
2324       p_return_status := fnd_api.g_ret_sts_unexp_error;
2325       fnd_msg_pub.count_and_get(
2326         p_encoded => fnd_api.g_false,
2327         p_count => p_msg_count,
2328         p_data => p_msg_data);
2329     WHEN OTHERS THEN
2330       p_return_status := fnd_api.g_ret_sts_unexp_error;
2331       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
2332       fnd_message.set_token('NAME', 'GET_ALL_STATS: ' || SQLERRM);
2333       fnd_msg_pub.ADD;
2334       fnd_msg_pub.count_and_get(
2335         p_encoded => fnd_api.g_false,
2336         p_count => p_msg_count,
2337         p_data => p_msg_data);
2338   END get_all_stats_new;
2339   --
2340   -- swaghmar; 15-Sep-2005; Bug 4491456
2341   --	Modified the signature
2342   --
2343   PROCEDURE get_cp_stats(
2344     p_person_id               IN         igs_en_stdnt_ps_att.person_id%TYPE,
2345     p_course_cd               IN         igs_en_stdnt_ps_att.course_cd%TYPE,
2346     p_stat_type               IN         igs_pr_stat_type.stat_type%TYPE,
2347     p_load_cal_type           IN         igs_ca_inst.cal_type%TYPE,
2348     p_load_ci_sequence_number IN         igs_ca_inst.sequence_number%TYPE,
2349     p_system_stat             IN         VARCHAR2,
2350     p_cumulative_ind          IN         VARCHAR2,
2351     p_earned_cp               OUT NOCOPY NUMBER,
2352     p_attempted_cp            OUT NOCOPY NUMBER,
2353     p_init_msg_list           IN         VARCHAR2,
2354     p_return_status           OUT NOCOPY VARCHAR2,
2355     p_msg_count               OUT NOCOPY NUMBER,
2356     p_msg_data                OUT NOCOPY VARCHAR2,
2357     p_use_released_grade      IN         VARCHAR2) IS
2358     /*
2359     ||  Created By : Prajeesh Chandran
2360     ||  Created On : 6-NOV-2001
2361     ||  Purpose : Main Procedure for Credit Point Calculation
2362     ||  Known limitations, enhancements or remarks :
2363     ||  Change History :
2364     ||  Who             When            What
2365     ||  (reverse chronological order - newest change first)
2366     */
2367 
2368     l_earned_cp          NUMBER   := 0;
2369     l_attempted_cp       NUMBER   := 0;
2370     l_gpa_value          NUMBER   := 0;
2371     l_gpa_cp             NUMBER   := 0;
2372     l_gpa_quality_points NUMBER   := 0;
2373     l_return_status      VARCHAR2(30);
2374     l_msg_count          NUMBER(2);
2375     l_msg_data           VARCHAR2(30);
2376     l_org_id             NUMBER(4);
2377   BEGIN
2378     l_org_id := igs_ge_gen_003.get_org_id;
2379     igs_ge_gen_003.set_org_id(l_org_id);
2380 
2381     -- Initialize message list if p_init_msg_list is set to TRUE.
2382     IF fnd_api.to_boolean(p_init_msg_list) THEN
2383       fnd_msg_pub.initialize;
2384     END IF;
2385 
2386     -- Validate the Parameters, so that must not be NULL
2387     IF (p_person_id IS NULL
2388         OR p_course_cd IS NULL
2389         OR p_load_cal_type IS NULL
2390         OR p_load_ci_sequence_number IS NULL) THEN
2391       fnd_message.set_name('IGS', 'IGS_GE_INSUFFICIENT_PARAM_VAL');
2392       fnd_msg_pub.ADD;
2393       RAISE fnd_api.g_exc_error;
2394     END IF;
2395 
2396     -- Call GET_ALL_STATS to calculate the GPA and CP values for the Student
2397     -- Unit Attempt
2398     get_all_stats(
2399       p_person_id               => p_person_id,
2400       p_course_cd               => p_course_cd,
2401       p_stat_type               => p_stat_type,
2402       p_load_cal_type           => p_load_cal_type,
2403       p_load_ci_sequence_number => p_load_ci_sequence_number,
2404       p_system_stat             => p_system_stat,
2405       p_cumulative_ind          => p_cumulative_ind,
2406       p_earned_cp               => l_earned_cp,
2407       p_attempted_cp            => l_attempted_cp,
2408       p_gpa_value               => l_gpa_value,
2409       p_gpa_cp                  => l_gpa_cp,
2410       p_gpa_quality_points      => l_gpa_quality_points,
2411       p_init_msg_list           => p_init_msg_list,
2412       p_return_status           => l_return_status,
2413       p_msg_count               => l_msg_count,
2414       p_msg_data                => l_msg_data,
2415       p_use_released_grade      => p_use_released_grade);
2416 
2417     -- If any Error is occurred in get_cp procedure Then return.
2418     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2419       p_return_status := l_return_status;
2420       p_msg_count := l_msg_count;
2421       p_msg_data := l_msg_data;
2422       RETURN;
2423     END IF;
2424 
2425     -- Set out NOCOPY parameters
2426     p_earned_cp := l_earned_cp;
2427     p_attempted_cp := l_attempted_cp;
2428     -- Initialize API return status to success.
2429     p_return_status := fnd_api.g_ret_sts_success;
2430     -- Standard call to get message count and if count is 1, get message info.
2431     fnd_msg_pub.count_and_get(
2432       p_encoded => fnd_api.g_false,
2433       p_count => p_msg_count,
2434       p_data => p_msg_data);
2435   EXCEPTION
2436     WHEN fnd_api.g_exc_error THEN
2437       p_return_status := fnd_api.g_ret_sts_error;
2438       fnd_msg_pub.count_and_get(
2439         p_encoded => fnd_api.g_false,
2440         p_count => p_msg_count,
2441         p_data => p_msg_data);
2442     WHEN fnd_api.g_exc_unexpected_error THEN
2443       p_return_status := fnd_api.g_ret_sts_unexp_error;
2444       fnd_msg_pub.count_and_get(
2445         p_encoded => fnd_api.g_false,
2446         p_count => p_msg_count,
2447         p_data => p_msg_data);
2448     WHEN OTHERS THEN
2449       p_return_status := fnd_api.g_ret_sts_unexp_error;
2450       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
2451       fnd_message.set_token('NAME', 'GET_CP_STATS: ' || SQLERRM);
2452       fnd_msg_pub.ADD;
2453       fnd_msg_pub.count_and_get(
2454         p_encoded => fnd_api.g_false,
2455         p_count => p_msg_count,
2456         p_data => p_msg_data);
2457   END get_cp_stats;
2458 
2459   PROCEDURE get_gpa_stats(
2460     p_person_id               IN         igs_en_stdnt_ps_att.person_id%TYPE,
2461     p_course_cd               IN         igs_en_stdnt_ps_att.course_cd%TYPE,
2462     p_stat_type               IN         igs_pr_stat_type.stat_type%TYPE,
2463     p_load_cal_type           IN         igs_ca_inst.cal_type%TYPE,
2464     p_load_ci_sequence_number IN         igs_ca_inst.sequence_number%TYPE,
2465     p_system_stat             IN         VARCHAR2,
2466     p_cumulative_ind          IN         VARCHAR2,
2467     p_gpa_value               OUT NOCOPY NUMBER,
2468     p_gpa_cp                  OUT NOCOPY NUMBER,
2469     p_gpa_quality_points      OUT NOCOPY NUMBER,
2470     p_init_msg_list           IN         VARCHAR2,
2471     p_return_status           OUT NOCOPY VARCHAR2,
2472     p_msg_count               OUT NOCOPY NUMBER,
2473     p_msg_data                OUT NOCOPY VARCHAR2,
2474     p_use_released_grade      IN         VARCHAR2) IS
2475     /*
2476     ||  Created By : Prajeesh Chandran
2477     ||  Created On : 6-NOV-2001
2478     ||  Purpose : Main Procedure for GPA
2479     ||  Known limitations, enhancements or remarks :
2480     ||  Change History :
2481     ||  Who             When            What
2482     ||  (reverse chronological order - newest change first)
2483     ||  swaghmar 15-Sep-2005 Bug 4491456 Modified the signature
2484     */
2485 
2486     l_earned_cp          NUMBER   := 0;
2487     l_attempted_cp       NUMBER   := 0;
2488     l_gpa_value          NUMBER   := 0;
2489     l_gpa_cp             NUMBER   := 0;
2490     l_gpa_quality_points NUMBER   := 0;
2491     l_return_status      VARCHAR2(30);
2492     l_msg_count          NUMBER(2);
2493     l_msg_data           VARCHAR2(30);
2494     l_org_id             NUMBER(4);
2495   BEGIN
2496     l_org_id := igs_ge_gen_003.get_org_id;
2497     igs_ge_gen_003.set_org_id(l_org_id);
2498 
2499     -- Initialize message list if p_init_msg_list is set to TRUE.
2500     IF fnd_api.to_boolean(p_init_msg_list) THEN
2501       fnd_msg_pub.initialize;
2502     END IF;
2503 
2504     -- Validate the Parameters, so that must not be NULL
2505     IF (p_person_id IS NULL
2506         OR p_course_cd IS NULL
2507         OR p_load_cal_type IS NULL
2508         OR p_load_ci_sequence_number IS NULL) THEN
2509       fnd_message.set_name('IGS', 'IGS_GE_INSUFFICIENT_PARAM_VAL');
2510       fnd_msg_pub.ADD;
2511       RAISE fnd_api.g_exc_error;
2512     END IF;
2513 
2514     -- Call GET_ALL_STATS to calculate the GPA and CP values for the
2515     -- Student Unit Attempt
2516     get_all_stats(
2517       p_person_id               => p_person_id,
2518       p_course_cd               => p_course_cd,
2519       p_stat_type               => p_stat_type,
2520       p_load_cal_type           => p_load_cal_type,
2521       p_load_ci_sequence_number => p_load_ci_sequence_number,
2522       p_system_stat             => p_system_stat,
2523       p_cumulative_ind          => p_cumulative_ind,
2524       p_earned_cp               => l_earned_cp,
2525       p_attempted_cp            => l_attempted_cp,
2526       p_gpa_value               => l_gpa_value,
2527       p_gpa_cp                  => l_gpa_cp,
2528       p_gpa_quality_points      => l_gpa_quality_points,
2529       p_init_msg_list           => p_init_msg_list,
2530       p_return_status           => l_return_status,
2531       p_msg_count               => l_msg_count,
2532       p_msg_data                => l_msg_data,
2533       p_use_released_grade      => p_use_released_grade);
2534 
2535     -- If any Error is occurred in get_cp procedure Then return.
2536     IF (l_return_status <> fnd_api.g_ret_sts_success) THEN
2537       p_return_status := l_return_status;
2538       p_msg_count := l_msg_count;
2539       p_msg_data := l_msg_data;
2540       RETURN;
2541     END IF;
2542 
2543     -- Set out NOCOPY parameters
2544     p_gpa_value := to_number(to_char(l_gpa_value,'99D999'));
2545     p_gpa_cp := l_gpa_cp;
2546     p_gpa_quality_points := l_gpa_quality_points;
2547     -- Initialize API return status to success.
2548     p_return_status := fnd_api.g_ret_sts_success;
2549     -- Standard call to get message count and if count is 1, get message info.
2550     fnd_msg_pub.count_and_get(
2551       p_encoded => fnd_api.g_false,
2552       p_count => p_msg_count,
2553       p_data => p_msg_data);
2554   EXCEPTION
2555     WHEN fnd_api.g_exc_error THEN
2556       p_return_status := fnd_api.g_ret_sts_error;
2557       fnd_msg_pub.count_and_get(
2558         p_encoded => fnd_api.g_false,
2559         p_count => p_msg_count,
2560         p_data => p_msg_data);
2561     WHEN fnd_api.g_exc_unexpected_error THEN
2562       p_return_status := fnd_api.g_ret_sts_unexp_error;
2563       fnd_msg_pub.count_and_get(
2564         p_encoded => fnd_api.g_false,
2565         p_count => p_msg_count,
2566         p_data => p_msg_data);
2567     WHEN OTHERS THEN
2568       p_return_status := fnd_api.g_ret_sts_unexp_error;
2569       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
2570       fnd_message.set_token('NAME', 'GET_GPA_STATS: ' || SQLERRM);
2571       fnd_msg_pub.ADD;
2572       fnd_msg_pub.count_and_get(
2573         p_encoded => fnd_api.g_false,
2574         p_count => p_msg_count,
2575         p_data => p_msg_data);
2576   END get_gpa_stats;
2577 
2578 --
2579 -- swaghmar; 24-Jun-2005; Bug# 4327987
2580 -- Added chk_sua_ref_cd function
2581 --
2582 
2583   FUNCTION chk_sua_ref_cd(
2584     P_person_id IN igs_en_su_attempt_ALL.person_id%TYPE,
2585     P_course_cd IN igs_en_su_attempt_ALL.course_cd%TYPE,
2586     P_uoo_id IN  NUMBER,
2587     p_org_unit_cd         IN            igs_pr_org_stat.org_unit_cd%TYPE,
2588     p_stat_type           IN            igs_pr_stat_type.stat_type%TYPE,
2589     p_init_msg_list       IN            VARCHAR2,
2590     p_return_status       OUT NOCOPY    VARCHAR2,
2591     p_msg_count           OUT NOCOPY    NUMBER,
2592     p_msg_data            OUT NOCOPY    VARCHAR2)
2593     RETURN VARCHAR2 AS
2594 
2595     CURSOR c_org_setup IS
2596       SELECT ostr1.include_or_exclude
2597         FROM igs_pr_org_stat_ref ostr1
2598        WHERE ostr1.stat_type = p_stat_type AND ostr1.org_unit_cd = p_org_unit_cd;
2599 
2600     CURSOR c_org_included IS
2601       SELECT 'X'
2602         FROM igs_as_sua_ref_cds urc,
2603              igs_ge_ref_cd_type rct
2604        WHERE urc.person_id = p_person_id
2605        AND   urc.uoo_id = p_uoo_id
2606        AND   urc.course_cd = p_course_cd
2607          AND urc.reference_cd_type = rct.reference_cd_type
2608 	 AND   urc.deleted_date IS NULL
2609          AND rct.s_reference_cd_type = 'STATS'
2610          AND EXISTS (
2611                SELECT 'X'
2612                  FROM igs_pr_org_stat_ref ostr1
2613                 WHERE ostr1.stat_type = p_stat_type
2614                   AND ostr1.org_unit_cd = p_org_unit_cd
2615                   AND ostr1.unit_ref_cd = urc.reference_cd
2616                   AND ostr1.include_or_exclude = 'INCLUDE');
2617 
2618 
2619     CURSOR c_org_excluded IS
2620       SELECT 'X'
2621         FROM igs_as_sua_ref_cds urc, igs_ge_ref_cd_type rct
2622         WHERE urc.person_id = p_person_id
2623         AND   urc.uoo_id = p_uoo_id
2624         AND   urc.course_cd = p_course_cd
2625         AND urc.reference_cd_type = rct.reference_cd_type
2626 	AND   urc.deleted_date IS NULL
2627         AND rct.s_reference_cd_type = 'STATS'
2628         AND EXISTS( SELECT 'X'
2629                        FROM igs_pr_org_stat_ref ostr1
2630                       WHERE ostr1.stat_type = p_stat_type
2631                         AND ostr1.org_unit_cd = p_org_unit_cd
2632                         AND ostr1.unit_ref_cd = urc.reference_cd
2633                         AND ostr1.include_or_exclude = 'EXCLUDE');
2634 
2635     CURSOR c_inst_setup IS
2636       SELECT INSTR.include_or_exclude
2637         FROM igs_pr_inst_sta_ref INSTR
2638        WHERE INSTR.stat_type = p_stat_type;
2639 
2640     CURSOR c_inst_included IS
2641       SELECT 'X'
2642         FROM igs_as_sua_ref_cds urc, igs_ge_ref_cd_type rct
2643        WHERE urc.person_id = p_person_id
2644        AND   urc.uoo_id = p_uoo_id
2645        AND   urc.course_cd = p_course_cd
2646          AND urc.reference_cd_type = rct.reference_cd_type
2647 	 AND   urc.deleted_date IS NULL
2648          AND rct.s_reference_cd_type = 'STATS'
2649          AND EXISTS( SELECT 'X'
2650                        FROM igs_pr_inst_sta_ref instr1
2651                       WHERE instr1.stat_type = p_stat_type
2652                         AND instr1.unit_ref_cd = urc.reference_cd
2653                         AND instr1.include_or_exclude = 'INCLUDE');
2654 
2655 
2656     CURSOR c_inst_excluded IS
2657       SELECT 'X'
2658         FROM igs_as_sua_ref_cds src, igs_ge_ref_cd_type rct
2659        WHERE src.person_id = p_person_id
2660        AND   src.uoo_id = p_uoo_id
2661        AND   src.course_cd = p_course_cd
2662          AND src.reference_cd_type = rct.reference_cd_type
2663 	 AND   src.deleted_date IS NULL
2664          AND rct.s_reference_cd_type = 'STATS'
2665          AND EXISTS( SELECT 'X'
2666                        FROM igs_pr_inst_sta_ref instr1
2667                       WHERE instr1.stat_type = p_stat_type
2668                         AND instr1.unit_ref_cd = src.reference_cd
2669                         AND instr1.include_or_exclude = 'EXCLUDE');
2670 
2671     l_include_or_exclude VARCHAR2(20);
2672     l_include            VARCHAR2(1);
2673     l_dummy              VARCHAR2(1);
2674     l_message            VARCHAR2(1000);
2675   BEGIN
2676     l_include := 'Y';
2677     -- Initialize message list if p_init_msg_list is set to TRUE.
2678     IF fnd_api.to_boolean(NVL(p_init_msg_list, fnd_api.g_true)) THEN
2679       fnd_msg_pub.initialize;
2680     END IF;
2681 
2682     -- The following parameters should not be null
2683     IF (p_person_id IS NULL
2684         OR p_uoo_id IS NULL
2685         OR p_course_cd IS NULL
2686         OR p_stat_type IS NULL) THEN
2687       l_message := 'IGS_GE_INSUFFICIENT_PARAM_VAL';
2688       fnd_message.set_name('IGS', l_message);
2689       fnd_msg_pub.ADD;
2690       RAISE fnd_api.g_exc_error;
2691     END IF;
2692 
2693     -- If the Organizational Unit is not null then statistic type is
2694     -- defined at Organizational level.  Check if any unit reference
2695     -- codes are included or excluded at Org level.
2696     IF p_org_unit_cd IS NOT NULL THEN
2697       -- When no Unit Reference Codes are specifically included or excluded, all
2698       -- units should be included.
2699       OPEN c_org_setup;
2700       FETCH c_org_setup INTO l_include_or_exclude;
2701 
2702       IF (c_org_setup%FOUND) THEN
2703         IF (l_include_or_exclude = 'INCLUDE') THEN
2704 
2705         -- When Unit Reference Codes are specifically included then only those
2706         -- units with the included Unit Refernce Code should be included
2707         OPEN c_org_included;
2708           FETCH c_org_included INTO l_dummy;
2709 
2710           IF (c_org_included%NOTFOUND) THEN
2711             l_include := 'N';
2712           END IF;
2713           CLOSE c_org_included;
2714 
2715         ELSE
2716         -- When Unit Reference Codes are specifically excluded all units Except
2717         -- those units with the excluded Unit Refernce Code should be included
2718           OPEN c_org_excluded;
2719           FETCH c_org_excluded INTO l_dummy;
2720 
2721           IF (c_org_excluded%FOUND) THEN
2722             l_include := 'N';
2723           END IF;
2724           CLOSE c_org_excluded;
2725         END IF;
2726       END IF;
2727 
2728       CLOSE c_org_setup;
2729     -- If the Organizational Unit is null then statistic type must be
2730     -- defined at Institution level.  Check if any unit reference
2731     -- codes are included or excluded at Inst level.
2732     ELSE
2733       -- When no Unit Reference Codes are specifically included or excluded all
2734       -- units should be included.
2735       OPEN c_inst_setup;
2736       FETCH c_inst_setup INTO l_include_or_exclude;
2737 
2738       IF (c_inst_setup%FOUND) THEN
2739         IF (l_include_or_exclude = 'INCLUDE') THEN
2740           -- When Unit Reference Codes are specifically included then only those
2741           -- units with the included Unit Refernce Code should be included
2742           OPEN c_inst_included;
2743           FETCH c_inst_included INTO l_dummy;
2744 
2745           IF (c_inst_included%NOTFOUND) THEN
2746             l_include := 'N';
2747           END IF;
2748 
2749           CLOSE c_inst_included;
2750         ELSE
2751           -- When Unit Reference Codes are specifically excluded all units except
2752           -- those units with the excluded Unit Refernce Code should be included
2753           OPEN c_inst_excluded;
2754           FETCH c_inst_excluded INTO l_dummy;
2755 
2756           IF (c_inst_excluded%FOUND) THEN
2757             l_include := 'N';
2758           END IF;
2759 
2760           CLOSE c_inst_excluded;
2761         END IF;
2762       END IF;
2763 
2764       CLOSE c_inst_setup;
2765     END IF;
2766 
2767     -- Initialize API return status to success.
2768     p_return_status := fnd_api.g_ret_sts_success;
2769     -- Standard call to get message count and if count is 1, get message info
2770     fnd_msg_pub.count_and_get(
2771       p_encoded => fnd_api.g_false,
2772       p_count => p_msg_count,
2773       p_data => p_msg_data);
2774     RETURN l_include;
2775   EXCEPTION
2776     WHEN fnd_api.g_exc_error THEN
2777       p_return_status := fnd_api.g_ret_sts_error;
2778       fnd_msg_pub.count_and_get(
2779         p_encoded => fnd_api.g_false,
2780         p_count => p_msg_count,
2781         p_data => p_msg_data);
2782       RETURN NULL;
2783     WHEN fnd_api.g_exc_unexpected_error THEN
2784       p_return_status := fnd_api.g_ret_sts_unexp_error;
2785       fnd_msg_pub.count_and_get(
2786         p_encoded => fnd_api.g_false,
2787         p_count => p_msg_count,
2788         p_data => p_msg_data);
2789       RETURN NULL;
2790     WHEN OTHERS THEN
2791       p_return_status := fnd_api.g_ret_sts_unexp_error;
2792       fnd_message.set_name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
2793       fnd_message.set_token('NAME', 'chk_sua_ref_cd: ' || SQLERRM);
2794       fnd_msg_pub.ADD;
2795       fnd_msg_pub.count_and_get(
2796         p_encoded => fnd_api.g_false,
2797         p_count => p_msg_count,
2798         p_data => p_msg_data);
2799      RETURN NULL;
2800     END chk_sua_ref_cd;
2801 END igs_pr_cp_gpa;