DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_IN_GEN_001

Source


1 PACKAGE BODY IGS_IN_GEN_001   AS
2  /* $Header: IGSIN01B.pls 120.0 2005/06/01 21:01:06 appldev noship $ */
3 
4 /* Change History :
5    Who             When             What
6    jbegum          25-Jun-2003      BUG#2930935
7                                     Modified local procedure INQP_GET_PRG_CP
8    rvivekan        09-sep-2003      Modified the behaviour of repeatable_ind
9                                     column in igs_ps_unit_ver table. PSP integration build #3052433
10 -- rnirwani   13-Sep-2004       changed cursor c_sci, procedure inqp_get_sci, inqp_get_sca_status to not consider logically
11 --				deleted records and also to avoid un-approved intermission records. Bug# 3885804
12 
13 */
14 
15 
16 FUNCTION inqp_get_appl_ind(
17   p_person_id IN NUMBER )
18 RETURN BOOLEAN AS
19        gv_other_detail             VARCHAR2(255);
20 BEGIN  -- inqp_get_appl_ind
21        -- This module determines if the student is an applicant.
22        -- An applicant is a person that has an incomplete application.
23 DECLARE
24        cst_completed CONSTANT      VARCHAR2(12) := 'COMPLETED';
25        cst_withdrawn CONSTANT      VARCHAR2(12) := 'WITHDRAWN';
26        v_dummy                            VARCHAR2(1);
27        CURSOR c_aa IS
28               SELECT 'x'
29               FROM   IGS_AD_APPL   aa
30               WHERE  aa.person_id         = p_person_id AND
31                      aa.adm_appl_status   IN
32                             (SELECT       aas.adm_appl_status
33                             FROM   IGS_AD_APPL_STAT     aas
34                             WHERE  aas.s_adm_appl_status NOT IN
35                                                         (cst_completed,
36                                                         cst_withdrawn));
37 BEGIN
38        OPEN c_aa;
39        FETCH c_aa INTO v_dummy;
40        IF (c_aa%NOTFOUND) THEN
41               CLOSE c_aa;
42               RETURN FALSE;
43        END IF;
44        CLOSE c_aa;
45        RETURN TRUE;
46 EXCEPTION
47        WHEN OTHERS THEN
48               IF c_aa%ISOPEN THEN
49                      CLOSE c_aa;
50               END IF;
51               RAISE;
52 END;
53 EXCEPTION
54        WHEN OTHERS THEN
55               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
56               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 1');
57               IGS_GE_MSG_STACK.ADD;
58                App_Exception.Raise_Exception;
59 END inqp_get_appl_ind;
60 
61 
62 FUNCTION inqp_get_encmb(
63   p_person_id IN NUMBER ,
64   p_course_cd IN VARCHAR2 ,
65   p_level IN VARCHAR2 ,
66   p_effective_dt IN DATE ,
67   p_serious_only_ind IN VARCHAR2 ,
68   p_include_all_course_ind IN VARCHAR2 ,
69   p_academic_ind OUT NOCOPY VARCHAR2 ,
70   p_admin_ind OUT NOCOPY VARCHAR2 )
71 RETURN boolean AS
72        gv_other_detail             VARCHAR2(255);
73 BEGIN  -- inqp_get_encmb
74        -- Retrieve encumbrance lamps, at a number of possible detail levels, being:
75        -- ALL        - Will return true if encumbrances exist for the person at any level
76        -- PERSON     - Will return true if encumbrances exist against the person
77        -- ENROLMENT  - Will return true if encumbrances exist against either course
78        --              or units
79        -- COURSE     - Will return true if encumbrances exist against the course
80        -- UNITSET    - Will return true if encumbrances exist against the unit set
81        -- UNIT              - Will return true if encumbrances exist against any unit
82        -- The 'p_include_all_course' parameter controls which course based
83        -- ncumbrances are reported at the COURSE level. eg. Unit exclusions and unit
84        -- set exclusions don't directly affect the course, and as such only sometimes
85        -- result in a lamp. This indicator is only really applicable to 'COURSE'
86        -- level calls.
87 DECLARE
88        cst_academic  CONSTANT      IGS_FI_ENCMB_TYPE.s_encumbrance_cat%TYPE := 'ACADEMIC';
89        cst_sus_srvc  CONSTANT
90                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'SUS_SRVC';
91        cst_rvk_srvc  CONSTANT
92                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'RVK_SRVC';
93        cst_exc_course       CONSTANT
94                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'EXC_COURSE';
95        cst_sus_course       CONSTANT
96                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'SUS_COURSE';
97        cst_exc_crs_gp       CONSTANT
98                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'EXC_CRS_GP';
99        cst_exc_crs_u CONSTANT
100                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'EXC_CRS_U';
101        cst_rqrd_crs_u       CONSTANT
102                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'RQRD_CRS_U';
103        cst_exc_crs_us       CONSTANT
104                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'EXC_CRS_US';
105        cst_rstr_ge_cp       CONSTANT
106                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'RSTR_GE_CP';
107        cst_rstr_le_cp       CONSTANT
108                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'RSTR_LE_CP';
109        cst_rstr_at_ty       CONSTANT
110                                    IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE := 'RSTR_AT_TY';
111        cst_all              CONSTANT      VARCHAR2(10) := 'ALL';
112        cst_person    CONSTANT      VARCHAR2(10) := 'PERSON';
113        cst_course    CONSTANT      VARCHAR2(10) := 'COURSE';
114        cst_enrolment CONSTANT      VARCHAR2(10) := 'ENROLMENT';
115        cst_unitset   CONSTANT      VARCHAR2(10) := 'UNITSET';
116        cst_unit      CONSTANT      VARCHAR2(10) := 'UNIT';
117        v_dummy                            VARCHAR2(1);
118        v_person_exists                    BOOLEAN;
119        v_enrol_academic_exists            BOOLEAN;
120        v_enrol_admin_exists        BOOLEAN;
121        v_course_academic_exists    BOOLEAN;
122        v_course_academic_direct    BOOLEAN;
123        v_course_admin_exists              BOOLEAN;
124        v_course_admin_direct              BOOLEAN;
125        v_unitset_academic_exists   BOOLEAN;
126        v_unitset_admin_exists             BOOLEAN;
127        v_unit_academic_exists             BOOLEAN;
128        v_unit_admin_exists         BOOLEAN;
129        v_academic_ind                     VARCHAR2(1);
130        v_administrative_ind        VARCHAR2(1);
131        CURSOR c_pen_et IS
132               SELECT pen.person_id,
133                      pen.encumbrance_type,
134                      pen.start_dt,
135                      et.s_encumbrance_cat
136               FROM   IGS_PE_PERS_ENCUMB   pen,
137                      IGS_FI_ENCMB_TYPE    et
138               WHERE  pen.person_id        = p_person_id AND
139                      pen.start_dt         <= p_effective_dt AND
140                      (pen.expiry_dt              IS NULL OR
141                      pen.expiry_dt        > p_effective_dt) AND
142                      et.encumbrance_type  = pen.encumbrance_type;
143        CURSOR c_pee (
144               cp_person_id         IGS_PE_PERS_ENCUMB.person_id%TYPE,
145               cp_encumbrance_type  IGS_PE_PERS_ENCUMB.encumbrance_type%TYPE,
146               cp_start_dt          IGS_PE_PERS_ENCUMB.start_dt%TYPE) IS
147               SELECT pee.course_cd,
148                      pee.person_id,
149                      pee.encumbrance_type,
150                      pee.pen_start_dt,
151                      pee.s_encmb_effect_type,
152                      pee.pee_start_dt,
153                      pee.sequence_number
154               FROM   IGS_PE_PERSENC_EFFCT pee
155               WHERE  -- child of current pen record
156                      pee.person_id        = cp_person_id AND
157                      pee.encumbrance_type = cp_encumbrance_type AND
158                      pee.pen_start_dt     = cp_start_dt AND
159                      pee.pee_start_dt     <= p_effective_dt AND
160                      (pee.expiry_dt              IS NULL OR
161                      pee.expiry_dt        > p_effective_dt) AND
162                      (p_course_cd         IS NULL OR
163                      pee.course_cd        IS NULL OR
164                      pee.course_cd        = p_course_cd);
165        CURSOR c_pce (
166               cp_person_id         IGS_PE_PERSENC_EFFCT.person_id%TYPE,
167               cp_encumbrance_type  IGS_PE_PERSENC_EFFCT.encumbrance_type%TYPE,
168               cp_pen_start_dt             IGS_PE_PERSENC_EFFCT.pen_start_dt%TYPE,
169               cp_s_encmb_effect_type      IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE,
170               cp_pee_start_dt             IGS_PE_PERSENC_EFFCT.pee_start_dt%TYPE,
171               cp_sequence_number   IGS_PE_PERSENC_EFFCT.sequence_number%TYPE) IS
172               SELECT 'X'
173               FROM   IGS_PE_COURSE_EXCL   pce
174               WHERE  -- child of current pee record
175                      pce.person_id        = cp_person_id AND
176                      pce.encumbrance_type = cp_encumbrance_type AND
177                      pce.pen_start_dt     = cp_pen_start_dt AND
178                      pce.s_encmb_effect_type     = cp_s_encmb_effect_type AND
179                      pce.pee_start_dt     = cp_pee_start_dt AND
180                      pce.pee_sequence_number     = cp_sequence_number AND
181                      pce.pce_start_dt     <= p_effective_dt AND
182                      (pce.expiry_dt              IS NULL OR
183                      pce.expiry_dt        > p_effective_dt) AND
184                      pce.course_cd        = p_course_cd;
185        CURSOR c_pcge (
186               cp_person_id         IGS_PE_PERSENC_EFFCT.person_id%TYPE,
187               cp_encumbrance_type  IGS_PE_PERSENC_EFFCT.encumbrance_type%TYPE,
188               cp_pen_start_dt             IGS_PE_PERSENC_EFFCT.pen_start_dt%TYPE,
189               cp_s_encmb_effect_type      IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE,
190               cp_pee_start_dt             IGS_PE_PERSENC_EFFCT.pee_start_dt%TYPE,
191               cp_sequence_number   IGS_PE_PERSENC_EFFCT.sequence_number%TYPE) IS
192               SELECT 'X'
193               FROM   IGS_PE_CRS_GRP_EXCL  pcge
194               WHERE  -- child of current pee record
195                      pcge.person_id                     = cp_person_id AND
196                      pcge.encumbrance_type              = cp_encumbrance_type AND
197                      pcge.pen_start_dt           = cp_pen_start_dt AND
198                      pcge.s_encmb_effect_type    = cp_s_encmb_effect_type AND
199                      pcge.pee_start_dt           = cp_pee_start_dt AND
200                      pcge.pee_sequence_number    = cp_sequence_number AND
201                      pcge.pcge_start_dt   <= p_effective_dt AND
202                      (pcge.expiry_dt             IS NULL OR
203                      pcge.expiry_dt              > p_effective_dt) AND
204                      EXISTS (
205                             SELECT 'X'
206                             FROM   IGS_PS_GRP_MBR       cgm
207                             WHERE  cgm.course_group_cd  = pcge.course_group_cd AND
208                                    cgm.course_cd        = p_course_cd);
209        CURSOR c_pue (
210               cp_person_id         IGS_PE_PERSENC_EFFCT.person_id%TYPE,
211               cp_encumbrance_type  IGS_PE_PERSENC_EFFCT.encumbrance_type%TYPE,
212               cp_pen_start_dt             IGS_PE_PERSENC_EFFCT.pen_start_dt%TYPE,
213               cp_s_encmb_effect_type      IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE,
214               cp_pee_start_dt             IGS_PE_PERSENC_EFFCT.pee_start_dt%TYPE,
215               cp_sequence_number   IGS_PE_PERSENC_EFFCT.sequence_number%TYPE) IS
216               SELECT 'X'
217               FROM   IGS_PE_PERS_UNT_EXCL pue
218               WHERE  -- child of current pee record
219                      pue.person_id        = cp_person_id AND
220                      pue.encumbrance_type = cp_encumbrance_type AND
221                      pue.pen_start_dt     = cp_pen_start_dt AND
222                      pue.s_encmb_effect_type     = cp_s_encmb_effect_type AND
223                      pue.pee_start_dt     = cp_pee_start_dt AND
224                      pue.pee_sequence_number     = cp_sequence_number AND
225                      pue.pue_start_dt     <= p_effective_dt AND
226                      (pue.expiry_dt              IS NULL OR
227                      pue.expiry_dt        > p_effective_dt);
228        CURSOR c_pur (
229               cp_person_id         IGS_PE_PERSENC_EFFCT.person_id%TYPE,
230               cp_encumbrance_type  IGS_PE_PERSENC_EFFCT.encumbrance_type%TYPE,
231               cp_pen_start_dt             IGS_PE_PERSENC_EFFCT.pen_start_dt%TYPE,
232               cp_s_encmb_effect_type      IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE,
233               cp_pee_start_dt             IGS_PE_PERSENC_EFFCT.pee_start_dt%TYPE,
234               cp_sequence_number   IGS_PE_PERSENC_EFFCT.sequence_number%TYPE) IS
235               SELECT 'X'
236               FROM   IGS_PE_UNT_REQUIRMNT pur
237               WHERE  -- child of current pee record
238                      pur.person_id        = cp_person_id AND
239                      pur.encumbrance_type = cp_encumbrance_type AND
240                      pur.pen_start_dt     = cp_pen_start_dt AND
241                      pur.s_encmb_effect_type     = cp_s_encmb_effect_type AND
242                      pur.pee_start_dt     = cp_pee_start_dt AND
243                      pur.pee_sequence_number     = cp_sequence_number AND
244                      pur.pur_start_dt     <= p_effective_dt AND
245                      (pur.expiry_dt              IS NULL OR
246                      pur.expiry_dt        > p_effective_dt);
247        CURSOR c_puse (
248               cp_person_id         IGS_PE_PERSENC_EFFCT.person_id%TYPE,
249               cp_encumbrance_type  IGS_PE_PERSENC_EFFCT.encumbrance_type%TYPE,
250               cp_pen_start_dt             IGS_PE_PERSENC_EFFCT.pen_start_dt%TYPE,
251               cp_s_encmb_effect_type      IGS_PE_PERSENC_EFFCT.s_encmb_effect_type%TYPE,
252               cp_pee_start_dt             IGS_PE_PERSENC_EFFCT.pee_start_dt%TYPE,
253               cp_sequence_number   IGS_PE_PERSENC_EFFCT.sequence_number%TYPE) IS
254               SELECT 'X'
255               FROM   IGS_PE_UNT_SET_EXCL  puse
256               WHERE  -- child of current pee record
257                      puse.person_id                     = cp_person_id AND
258                      puse.encumbrance_type              = cp_encumbrance_type AND
259                      puse.pen_start_dt           = cp_pen_start_dt AND
260                      puse.s_encmb_effect_type    = cp_s_encmb_effect_type AND
261                      puse.pee_start_dt           = cp_pee_start_dt AND
262                      puse.pee_sequence_number    = cp_sequence_number AND
263                      puse.puse_start_dt   <= p_effective_dt AND
264                      (puse.expiry_dt             IS NULL OR
265                      puse.expiry_dt              > p_effective_dt);
266 BEGIN
267        -- Set the varaibles, not the OUT NOCOPY parameters because we want to
268        -- read these values and OUT NOCOPY values cannot be read
269        v_administrative_ind := 'N';
270        v_academic_ind := 'N';
271        v_person_exists := FALSE;
272        v_enrol_academic_exists := FALSE;
273        v_enrol_admin_exists := FALSE;
274        v_course_academic_exists := FALSE;
275        v_course_academic_direct := FALSE;
276        v_course_admin_exists := FALSE;
277        v_course_admin_direct := FALSE;
278        v_unitset_academic_exists := FALSE;
279        v_unitset_admin_exists := FALSE;
280        v_unit_academic_exists := FALSE;
281        v_unit_admin_exists := FALSE;
282        FOR v_pen_et_rec IN c_pen_et LOOP
283               FOR v_pee_rec IN c_pee(
284                                    v_pen_et_rec.person_id,
285                                    v_pen_et_rec.encumbrance_type,
286                                    v_pen_et_rec.start_dt) LOOP
287                      IF v_pee_rec.course_cd IS NULL THEN
288                             -- Person based encumbrance exists
289                             IF p_serious_only_ind = 'N' OR
290                                           (v_pee_rec.s_encmb_effect_type IN (
291                                                                       cst_sus_srvc,
292                                                                       cst_rvk_srvc)) THEN
293                                    v_person_exists := TRUE;
294                             END IF;
295                             -- Check for person encumbrances which affect courses
296                             IF v_pee_rec.s_encmb_effect_type IN (
297                                                         cst_sus_srvc,
298                                                         cst_rvk_srvc) THEN
299                                    IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
300                                           v_course_academic_exists := TRUE;
301                                           v_course_academic_direct := TRUE;
302                                           v_unitset_academic_exists := TRUE;
303                                           v_unit_academic_exists := TRUE;
304                                    ELSE
305                                           v_course_admin_exists := TRUE;
306                                           v_course_admin_direct := TRUE;
307                                           v_unitset_admin_exists := TRUE;
308                                           v_unit_admin_exists := TRUE;
309                                    END IF;
310                             END IF;
311                             IF v_pee_rec.s_encmb_effect_type IN (
312                                                         cst_exc_course,
313                                                         cst_sus_course,
314                                                         cst_exc_crs_gp) THEN
315                                    IF p_course_cd IS NULL THEN
316                                           -- Any course exclusion/suspension affects if no
317                                           -- course code parameter specified
318                                           IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
319                                                  v_course_academic_exists := TRUE;
320                                           ELSE
321                                                  v_course_admin_exists := TRUE;
322                                           END IF;
323                                    ELSE
324                                           -- Check that the context course (parameter) is in the
325                                           -- exclusion set; only if it does the encumbrance apply
326                                           OPEN c_pce(
327                                                  v_pee_rec.person_id,
328                                                  v_pee_rec.encumbrance_type,
329                                                  v_pee_rec.pen_start_dt,
330                                                  v_pee_rec.s_encmb_effect_type,
331                                                  v_pee_rec.pee_start_dt,
332                                                  v_pee_rec.sequence_number);
333                                           FETCH c_pce INTO v_dummy;
334                                           IF c_pce%FOUND THEN
335                                                  IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
336                                                         v_course_academic_exists := TRUE;
337                                                         v_course_academic_direct := TRUE;
338                                                  ELSE
339                                                         v_course_admin_exists := TRUE;
340                                                         v_course_admin_direct := TRUE;
341                                                  END IF;
342                                           ELSE
343                                                  OPEN c_pcge (
344                                                         v_pee_rec.person_id,
345                                                         v_pee_rec.encumbrance_type,
346                                                         v_pee_rec.pen_start_dt,
347                                                         v_pee_rec.s_encmb_effect_type,
348                                                         v_pee_rec.pee_start_dt,
349                                                         v_pee_rec.sequence_number);
350                                                  FETCH c_pcge INTO v_dummy;
351                                                  IF c_pcge%FOUND THEN
352                                                         IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
353                                                                v_course_academic_exists := TRUE;
354                                                                v_course_academic_direct := TRUE;
355                                                         ELSE
356                                                                v_course_admin_exists := TRUE;
357                                                                v_course_admin_direct := TRUE;
358                                                         END IF;
359                                                  END IF;
360                                                  CLOSE c_pcge;
361                                           END IF;
362                                           CLOSE c_pce;
363                                    END IF;
364                             END IF;
365                      ELSE -- pee.course_cd is not null
366                             -- Course Based Encumbrance
367                             IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
368                                    -- Ignore detail exclusions - these are picked up below
369                                    IF v_pee_rec.s_encmb_effect_type NOT IN (
370                                                                cst_exc_crs_u,
371                                                                cst_rqrd_crs_u,
372                                                                cst_exc_crs_us) THEN
373                                           v_course_academic_exists := TRUE;
374                                    END IF;
375                                    -- Encumbrance directly affecting the course atempt
376                                    IF v_pee_rec.s_encmb_effect_type IN (
377                                                                cst_sus_srvc,
378                                                                cst_rvk_srvc,
379                                                                cst_exc_course,
380                                                                cst_sus_course,
381                                                                cst_exc_crs_gp,
382                                                                cst_rstr_ge_cp,
383                                                                cst_rstr_le_cp,
384                                                                cst_rstr_at_ty) THEN
385                                           v_course_academic_direct := TRUE;
386                                    END IF;
387                             ELSE
388                                    -- Ignore detail exclusions - these are picked up below
389                                    IF v_pee_rec.s_encmb_effect_type NOT IN (
390                                                                cst_exc_crs_u,
391                                                                cst_rqrd_crs_u,
392                                                                cst_exc_crs_us) THEN
393                                           v_course_admin_exists := TRUE;
394                                    END IF;
395                                    -- Encumbrance directly affecting the course attempt
396                                    IF v_pee_rec.s_encmb_effect_type IN (
397                                                                cst_sus_srvc,
398                                                                cst_rvk_srvc,
399                                                                cst_exc_course,
400                                                                cst_sus_course,
401                                                                cst_exc_crs_gp,
402                                                                cst_rstr_ge_cp,
403                                                                cst_rstr_le_cp,
404                                                                cst_rstr_le_cp,
405                                                                cst_rstr_at_ty) THEN
406                                           v_course_admin_direct := TRUE;
407                                    END IF;
408                             END IF;
409                      END IF;
410                      IF v_pee_rec.s_encmb_effect_type = cst_exc_crs_u THEN
411                             -- Check for unit exclusions
412                             OPEN c_pue (
413                                    v_pee_rec.person_id,
414                                    v_pee_rec.encumbrance_type,
415                                    v_pee_rec.pen_start_dt,
416                                    v_pee_rec.s_encmb_effect_type,
417                                    v_pee_rec.pee_start_dt,
418                                    v_pee_rec.sequence_number);
419                             FETCH c_pue INTO v_dummy;
420                             IF c_pue%FOUND THEN
421                                    IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
422                                           v_unit_academic_exists := TRUE;
423                                           v_course_academic_exists := TRUE;
424                                    ELSE
425                                           v_unit_admin_exists := TRUE;
426                                           v_course_admin_exists := TRUE;
427                                    END IF;
428                             END IF;
429                             CLOSE c_pue;
430                      END IF;
431                      IF v_pee_rec.s_encmb_effect_type = cst_rqrd_crs_u THEN
432                             -- Check for required units
433                             OPEN c_pur (
434                                    v_pee_rec.person_id,
435                                    v_pee_rec.encumbrance_type,
436                                    v_pee_rec.pen_start_dt,
437                                    v_pee_rec.s_encmb_effect_type,
438                                    v_pee_rec.pee_start_dt,
439                                    v_pee_rec.sequence_number);
440                             FETCH c_pur INTO v_dummy;
441                             IF c_pur%FOUND THEN
442                                    IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
443                                           v_unit_academic_exists := TRUE;
444                                           v_course_academic_exists := TRUE;
445                                    ELSE
446                                           v_unit_admin_exists := TRUE;
447                                           v_course_admin_exists := TRUE;
448                                    END IF;
449                             END IF;
450                             CLOSE c_pur;
451                      END IF;
452                      IF v_pee_rec.s_encmb_effect_type = cst_exc_crs_us THEN
453                             -- Check for unit set exclusions
454                             OPEN c_puse (
455                                    v_pee_rec.person_id,
456                                    v_pee_rec.encumbrance_type,
457                                    v_pee_rec.pen_start_dt,
458                                    v_pee_rec.s_encmb_effect_type,
459                                    v_pee_rec.pee_start_dt,
460                                    v_pee_rec.sequence_number);
461                             FETCH c_puse INTO v_dummy;
462                             IF c_puse%FOUND THEN
463                                    IF v_pen_et_rec.s_encumbrance_cat = cst_academic THEN
464                                           v_unitset_academic_exists := TRUE;
465                                           v_course_academic_exists := TRUE;
466                                    ELSE
467                                           v_unitset_admin_exists := TRUE;
468                                           v_course_admin_exists := TRUE;
469                                    END IF;
470                             END IF;
471                             CLOSE c_puse;
472                      END IF;
473               END LOOP;
474        END LOOP;
475        -- Set the appropriate flags depending on the
476        -- level of checking which is being performed
477        IF p_level = cst_all THEN
478               IF v_person_exists = TRUE THEN
479                      v_administrative_ind := 'Y';
480               END IF;
481               IF (v_course_academic_exists = TRUE OR
482                             v_unitset_academic_exists = TRUE OR
483                             v_unit_academic_exists = TRUE) THEN
484                      v_academic_ind := 'Y';
485               END IF;
486               IF (v_course_admin_exists = TRUE OR
487                             v_unitset_admin_exists = TRUE OR
488                             v_unit_admin_exists = TRUE) THEN
489                      v_administrative_ind := 'Y';
490               END IF;
491        ELSIF p_level = cst_person THEN
492               IF v_person_exists = TRUE THEN
493                      v_administrative_ind := 'Y';
494               END IF;
495        ELSIF p_level = cst_course THEN
496               IF p_include_all_course_ind = 'Y' THEN
497                      IF v_course_academic_exists = TRUE THEN
498                             v_academic_ind := 'Y';
499                      END IF;
500                      IF v_course_admin_exists = TRUE THEN
501                             v_administrative_ind := 'Y';
502                      END IF;
503               ELSE
504                      IF v_course_academic_direct = TRUE THEN
505                             v_academic_ind := 'Y';
506                      END IF;
507                      IF v_course_admin_direct = TRUE THEN
508                             v_administrative_ind := 'Y';
509                      END IF;
510               END IF;
511        ELSIF p_level = cst_enrolment THEN
512               IF (v_course_academic_exists = TRUE OR
513                             v_unitset_academic_exists = TRUE OR
514                             v_unit_academic_exists = TRUE) THEN
515                      v_academic_ind := 'Y';
516               END IF;
517               IF (v_course_admin_exists = TRUE OR
518                             v_unitset_admin_exists = TRUE OR
519                             v_unit_admin_exists = TRUE) THEN
520                      v_administrative_ind := 'Y';
521               END IF;
522        ELSIF p_level = cst_unitset THEN
523               IF v_unitset_academic_exists = TRUE THEN
524                      v_academic_ind := 'Y';
525               END IF;
526               IF v_unitset_admin_exists = TRUE THEN
527                      v_administrative_ind := 'Y';
528               END IF;
529        ELSIF p_level = cst_unit THEN
530               IF v_unit_academic_exists = TRUE THEN
531                      v_academic_ind := 'Y';
532               END IF;
533               IF v_unit_admin_exists = TRUE THEN
534                      v_administrative_ind := 'Y';
535               END IF;
536        END IF;
537        p_academic_ind := v_academic_ind;
538        p_admin_ind := v_administrative_ind;
539        -- If either admin or academic encumbrances exist then the routine
540        -- returns true to signify that an applicable encumbrance exists.
541        IF v_academic_ind = 'Y' OR
542                      v_administrative_ind = 'Y' THEN
543               RETURN TRUE;
544        ELSE
545               RETURN FALSE;
546        END IF;
547 EXCEPTION
548        WHEN OTHERS THEN
549               IF (c_pen_et%ISOPEN) THEN
550                      CLOSE c_pen_et;
551               END IF;
552               IF (c_pee%ISOPEN) THEN
553                      CLOSE c_pee;
554               END IF;
555               IF (c_pce%ISOPEN) THEN
556                      CLOSE c_pce;
557               END IF;
558               IF (c_pcge%ISOPEN) THEN
559                      CLOSE c_pcge;
560               END IF;
561               IF (c_pue%ISOPEN) THEN
562                      CLOSE c_pue;
563               END IF;
564               IF (c_pur%ISOPEN) THEN
565                      CLOSE c_pur;
566               END IF;
567               IF (c_puse%ISOPEN) THEN
568                      CLOSE c_puse;
569               END IF;
570               RAISE;
571 END;
572 EXCEPTION
573        WHEN OTHERS THEN
574               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
575               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 2');
576               IGS_GE_MSG_STACK.ADD;
577        App_Exception.Raise_Exception;
578 END inqp_get_encmb;
579 
580 
581 PROCEDURE inqp_get_enr_cat(
582   p_person_id IN NUMBER ,
583   p_course_cd IN VARCHAR2 ,
584   p_enrolment_cat OUT NOCOPY VARCHAR2 ,
585   p_description OUT NOCOPY VARCHAR2 )
586 AS
587        gv_other_detail             VARCHAR2(255);
588 BEGIN  -- inqp_get_enr_cat
589 DECLARE
590        v_enrolment_cat             IGS_AS_SC_ATMPT_ENR.enrolment_cat%TYPE;
591        v_description        IGS_EN_ENROLMENT_CAT.description%TYPE;
592        CURSOR c_scae IS
593               SELECT scae.enrolment_cat,
594                      ec.description
595               FROM   IGS_AS_SC_ATMPT_ENR scae,
596                      IGS_CA_INST ci,
597                      IGS_EN_ENROLMENT_CAT ec
598               WHERE  scae.person_id              = p_person_id AND
599                      scae.course_cd              =p_course_cd AND
600                      ci.cal_type          = scae.cal_type AND
601                      ci.sequence_number   =ci_sequence_number AND
602                      ec.enrolment_cat     = scae.enrolment_cat
603               ORDER BY ci.end_dt DESC;
604 BEGIN
605        -- Cursor handling
606        OPEN c_scae;
607        FETCH c_scae INTO    v_enrolment_cat,
608                             v_description;
609        IF c_scae%FOUND THEN
610               CLOSE c_scae;
611               --Note: use only the first record found (and the latest calendar end date)
612               p_enrolment_cat      := v_enrolment_cat;
613               p_description := v_description;
614        ELSE
615               CLOSE c_scae;
616               p_enrolment_cat      := NULL;
617               p_description := NULL;
618        END IF;
619 EXCEPTION
620        WHEN OTHERS THEN
621               IF c_scae%ISOPEN THEN
622                      CLOSE c_scae;
623               END IF;
624               RAISE;
625 END;
626 EXCEPTION
627        WHEN OTHERS THEN
628               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
629               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 3');
630               IGS_GE_MSG_STACK.ADD;
631        App_Exception.Raise_Exception;
632 END inqp_get_enr_cat;
633 
634 
635 PROCEDURE inqp_get_prg_cp(
636   p_person_id IN NUMBER ,
637   p_course_cd IN VARCHAR2 ,
638   p_version_number IN NUMBER ,
639   p_cp_required OUT NOCOPY NUMBER ,
640   p_cp_passed OUT NOCOPY NUMBER ,
641   p_adv_granted OUT NOCOPY NUMBER ,
642   p_enrolled_cp OUT NOCOPY NUMBER ,
643   p_cp_remaining OUT NOCOPY NUMBER )
644 AS
645        gv_other_detail             VARCHAR2(255);
646 BEGIN  -- func_module
647 DECLARE
648        cst_enrolled  CONSTANT
649                      IGS_EN_SU_ATTEMPT.unit_attempt_status%TYPE := 'ENROLLED';
650        v_crv_credit_points_required       IGS_PS_VER.credit_points_required%TYPE;
651        v_enrolled_total            NUMBER;
652        v_cp_required               IGS_PS_VER.credit_points_required%TYPE;
653        v_cp_passed                 NUMBER;
654        v_adv_granted               NUMBER;
655        v_cp_remaining                     NUMBER;
656        CURSOR c_crv IS
657               SELECT crv.credit_points_required
658               FROM   IGS_PS_VER crv
659               WHERE  crv.course_cd        = p_course_cd AND
660                      crv.version_number   = p_version_number;
661 
662 
663        --Who             When             What
664        --jbegum          25-Jun-2003      BUG#2930935 - Modified cursor c_sua_uv.
665 
666        CURSOR c_sua_uv IS
667               SELECT SUM( NVL(sua.override_achievable_cp,
668                               NVL( NVL(cps.achievable_credit_points,uv.achievable_credit_points),
669                                    NVL(cps.enrolled_credit_points,uv.enrolled_credit_points)
670                                  )
671                              )
672                         )
673               FROM   IGS_EN_SU_ATTEMPT sua,
674                      IGS_PS_UNIT_VER uv ,
675                      IGS_PS_USEC_CPS cps
676               WHERE  sua.person_id        = p_person_id        AND
677                      sua.course_cd        = p_course_cd               AND
678                      sua.unit_attempt_status     = cst_enrolled              AND
679                      sua.ci_start_dt             <= TRUNC(SYSDATE)    AND
680                      sua.uoo_id = cps.uoo_id (+) AND
681                      uv.unit_cd           = sua.unit_cd        AND
682                      uv.version_number           = sua.version_number;
683 BEGIN
684        --Select the required credit points from the students course version
685        OPEN c_crv;
686        FETCH c_crv INTO v_crv_credit_points_required;
687        IF c_crv%FOUND THEN
688               v_cp_required := v_crv_credit_points_required;
689        ELSE
690               v_cp_required := 0;
691        END IF;
692        CLOSE c_crv;
693        --Total the advanced standing for a student
694        v_adv_granted := IGS_AV_GEN_001.ADVP_GET_AS_TOTAL(      p_person_id,
695                                           p_course_cd,
696                                           TRUNC(SYSDATE));
697        --Call routine to derive the credit points passed by the student
698        v_cp_passed := (IGS_EN_GEN_001.ENRP_CLC_SCA_PASS_CP(    p_person_id,
699                                           p_course_cd,
700                                           TRUNC(SYSDATE)) - v_adv_granted);
701        --Derived the number of credit points in which the student is currently
702        -- enrolled
703        OPEN c_sua_uv;
704        FETCH c_sua_uv INTO v_enrolled_total;
705        IF c_sua_uv%FOUND AND v_enrolled_total IS NOT NULL THEN
706               p_enrolled_cp := v_enrolled_total;
707        ELSE
708               p_enrolled_cp := 0;
709        END IF;
710        CLOSE c_sua_uv;
711        --Calculate the credit points remaining based on the above figures.
712        v_cp_remaining := (v_cp_required -
713                      v_cp_passed -
714                      v_adv_granted);
715        IF v_cp_remaining < 0 THEN
716               p_cp_remaining := 0;
717        ELSE
718               p_cp_remaining := v_cp_remaining;
719        END IF;
720        p_cp_required := v_cp_required;
721        p_cp_passed   := v_cp_passed;
722        p_adv_granted := v_adv_granted;
723 EXCEPTION
724        WHEN OTHERS THEN
725               IF c_crv%ISOPEN THEN
726                      CLOSE c_crv;
727               END IF;
728               IF c_sua_uv%ISOPEN THEN
729                      CLOSE c_sua_uv;
730               END IF;
731               RAISE;
732 END;
733 EXCEPTION
734        WHEN OTHERS THEN
735               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
736               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 4');
737               IGS_GE_MSG_STACK.ADD;
738        App_Exception.Raise_Exception;
739 END inqp_get_prg_cp;
740 
741 
742 PROCEDURE inqp_get_sca_status(
743   p_person_id IN NUMBER ,
744   p_course_cd IN VARCHAR2 ,
745   p_course_attempt_status IN VARCHAR2 ,
746   p_commencement_dt IN DATE ,
747   p_discontinued_dt IN DATE ,
748   p_discontinuation_reason_cd IN VARCHAR2 ,
749   p_lapsed_dt IN DATE ,
750   p_status_dt OUT NOCOPY DATE ,
751   p_reason_cd OUT NOCOPY VARCHAR2 ,
752   p_description OUT NOCOPY VARCHAR2 )
753 AS
754        gv_other_detail                    VARCHAR2(255);
755 BEGIN  -- inqp_get_sca_status
756 DECLARE
757        cst_unconfirm CONSTANT      VARCHAR2(9) := 'UNCONFIRM';
758        cst_enrolled  CONSTANT      VARCHAR2(8) := 'ENROLLED';
759        cst_inactive  CONSTANT      VARCHAR2(8) := 'INACTIVE';
760        cst_discontin CONSTANT      VARCHAR2(9) := 'DISCONTIN';
761        cst_lapsed    CONSTANT      VARCHAR2(6) := 'LAPSED';
762        cst_intermit  CONSTANT      VARCHAR2(8) := 'INTERMIT';
763        cst_completed CONSTANT      VARCHAR2(9) := 'COMPLETED';
764        v_drc_description                  IGS_EN_DCNT_REASONCD.description%TYPE;
765        v_sci_start_dt                     IGS_EN_STDNT_PS_INTM.start_dt%TYPE;
766        v_scah_hist_end_dt                 IGS_AS_SC_ATTEMPT_H.hist_end_dt%TYPE;
767        CURSOR c_drc IS
768               SELECT drc.description
769               FROM   IGS_EN_DCNT_REASONCD drc
770               WHERE  drc.discontinuation_reason_cd = p_discontinuation_reason_cd;
771        CURSOR c_sci IS
772               SELECT sci.start_dt
773               FROM   IGS_EN_STDNT_PS_INTM sci,
774                      IGS_EN_INTM_TYPES eit
775               WHERE  sci.person_id               = p_person_id AND
776                      sci.course_cd               = p_course_cd AND
777                      sci.start_dt         <= TRUNC(SYSDATE) AND
778                      sci.end_dt           >= TRUNC(SYSDATE) AND
779 		     sci.approved  = eit.appr_reqd_ind AND
780                      eit.intermission_type = sci.intermission_type AND
781                      sci.logical_delete_date = TO_DATE('31-12-4712','DD-MM-YYYY');
782        CURSOR c_scah IS
783               SELECT scah.hist_end_dt
784               FROM   IGS_AS_SC_ATTEMPT_H scah
785               WHERE  person_id            = p_person_id AND
786                      course_cd            = p_course_cd AND
787                      course_attempt_status       IS NOT NULL
788               ORDER BY hist_end_dt DESC;  --(use the first record)
789 BEGIN
790        IF p_course_attempt_status = cst_unconfirm THEN
791               p_status_dt := NULL;
792        ELSIF p_course_attempt_status = cst_enrolled THEN
793               p_status_dt := p_commencement_dt;
794        ELSIF p_course_attempt_status = cst_inactive THEN
795               p_status_dt := p_commencement_dt;
796        ELSIF p_course_attempt_status = cst_discontin THEN
797               p_status_dt := p_discontinued_dt;
798               p_reason_cd := p_discontinuation_reason_cd;
799               OPEN c_drc;
800               FETCH c_drc INTO v_drc_description;
801               IF c_drc%FOUND THEN
802                      p_description := v_drc_description;
803               END IF;
804               CLOSE c_drc;
805        ELSIF p_course_attempt_status = cst_lapsed THEN
806               p_status_dt := p_lapsed_dt;
807        ELSIF p_course_attempt_status = cst_intermit THEN
808               OPEN c_sci;
809               FETCH c_sci INTO v_sci_start_dt;
810               IF c_sci%FOUND THEN
811                      p_status_dt := v_sci_start_dt;
812               END IF;
813               CLOSE c_sci;
814        ELSIF p_course_attempt_status = cst_completed THEN
815               OPEN c_scah;
816               FETCH c_scah INTO v_scah_hist_end_dt;
817               IF c_scah %FOUND THEN
818                      p_status_dt := v_scah_hist_end_dt;
819               ELSE
820                      p_status_dt := NULL;
821               END IF;
822               CLOSE c_scah;
823        END IF;
824 EXCEPTION
825        WHEN OTHERS THEN
826               IF c_drc %ISOPEN THEN
827                      CLOSE c_drc;
828               END IF;
829               IF c_sci %ISOPEN THEN
830                      CLOSE c_sci;
831               END IF;
832               IF c_scah %ISOPEN THEN
833                      CLOSE c_scah;
834               END IF;
835               RAISE;
836 END;
837 EXCEPTION
838        WHEN OTHERS THEN
839               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
840               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 5');
841               IGS_GE_MSG_STACK.ADD;
842        App_Exception.Raise_Exception;
843 END inqp_get_sca_status;
844 
845 
846 PROCEDURE inqp_get_scho(
847   p_person_id IN NUMBER ,
848   p_course_cd IN VARCHAR2 ,
849   p_hecs_payment_option OUT NOCOPY VARCHAR2 ,
850   p_tax_file_number_ind OUT NOCOPY VARCHAR2 ,
851   p_start_dt OUT NOCOPY DATE ,
852   p_end_dt OUT NOCOPY DATE )
853 AS
854        gv_other_detail             VARCHAR2(255);
855 BEGIN  -- inqp_get_scho
856 DECLARE
857        v_scho_hecs_payment_option  IGS_EN_STDNTPSHECSOP.hecs_payment_option%TYPE;
858        v_scho_tax_file_number      VARCHAR2(10);
859        v_scho_start_dt             IGS_EN_STDNTPSHECSOP.start_dt%TYPE;
860        v_scho_end_dt        IGS_EN_STDNTPSHECSOP.end_dt%TYPE;
861        CURSOR c_scho IS
862               SELECT scho.hecs_payment_option,
863                      scho.tax_file_number,
864                      scho.start_dt,
865                      scho.end_dt
866               FROM   IGS_EN_STDNTPSHECSOP scho
867               WHERE  scho.person_id                     = p_person_id AND
868                      scho.course_cd                     = p_course_cd AND
869                      scho.start_dt                      <= SYSDATE AND
870                      (scho.end_dt                IS NULL OR
871                      scho.end_dt                 >= SYSDATE)
872               ORDER BY start_dt ASC;             --(only use the first and earliest record);
873 BEGIN
874        -- Cursor handling
875        OPEN c_scho;
876        FETCH c_scho INTO    v_scho_hecs_payment_option,
877                             v_scho_tax_file_number,
878                             v_scho_start_dt,
879                             v_scho_end_dt;
880        IF c_scho%FOUND THEN
881               CLOSE c_scho;
882               p_hecs_payment_option       := v_scho_hecs_payment_option;
883               p_start_dt           := v_scho_start_dt;
884               p_end_dt             := v_scho_end_dt;
885               IF  v_scho_tax_file_number IS NOT NULL THEN
886                      p_tax_file_number_ind := 'Y';
887               ELSE
888                      p_tax_file_number_ind := 'N';
889               END IF;
890        ELSE
891               CLOSE c_scho;
892               p_hecs_payment_option       := NULL;
893               p_tax_file_number_ind       := 'N';
894               p_end_dt             := NULL;
895               p_start_dt           := NULL;
896        END IF;
897 EXCEPTION
898        WHEN OTHERS THEN
899               IF c_scho%ISOPEN THEN
900                      CLOSE c_scho;
901               END IF;
902               RAISE;
903 END;
904 EXCEPTION
905        WHEN OTHERS THEN
906               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
907               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 6');
908               IGS_GE_MSG_STACK.ADD;
909        App_Exception.Raise_Exception;
910 END inqp_get_scho;
911 
912 
913 PROCEDURE inqp_get_sci(
914   p_person_id IN NUMBER ,
915   p_course_cd IN VARCHAR2 ,
916   p_start_dt OUT NOCOPY DATE ,
917   p_end_dt OUT NOCOPY DATE ,
918   p_voluntary_ind OUT NOCOPY VARCHAR2 )
919 AS
920        gv_other_detail             VARCHAR2(255);
921 BEGIN  -- inqp_get_sci
922 DECLARE
923        v_sci_start_dt              IGS_EN_STDNT_PS_INTM.start_dt%TYPE;
924        v_sci_end_dt         IGS_EN_STDNT_PS_INTM.end_dt%TYPE;
925        v_sci_voluntary_ind         IGS_EN_STDNT_PS_INTM.voluntary_ind%TYPE;
926        CURSOR c_sci IS
927               SELECT sci.start_dt,
928                      sci.end_dt,
929                      sci.voluntary_ind
930               FROM   IGS_EN_STDNT_PS_INTM sci,
931 		     IGS_EN_INTM_TYPES eit
932               WHERE  sci.person_id = p_person_id and
933                      sci.course_cd = p_course_cd and
934                      sci.end_dt    >= TRUNC(SYSDATE) AND
935 		     sci.approved  = eit.appr_reqd_ind AND
936                      eit.intermission_type = sci.intermission_type AND
937                      sci.logical_delete_date = TO_DATE('31-12-4712','DD-MM-YYYY')
938               ORDER BY start_dt;   --(use the first record)
939 BEGIN
940        -- Cursor handling
941        OPEN c_sci;
942        FETCH c_sci INTO     v_sci_start_dt,
943                             v_sci_end_dt,
944                             v_sci_voluntary_ind;
945        IF c_sci%FOUND THEN
946               CLOSE c_sci;
947               p_start_dt := v_sci_start_dt;
948               p_end_dt := v_sci_end_dt;
949               p_voluntary_ind := v_sci_voluntary_ind;
950        ELSE
951               CLOSE c_sci ;
952               p_start_dt := NULL;
953               p_end_dt := NULL;
954               p_voluntary_ind := NULL;
955        END IF;
956 EXCEPTION
957        WHEN OTHERS THEN
958               IF c_sci%ISOPEN THEN
959                      CLOSE c_sci;
960               END IF;
961               RAISE;
962 END;
963 EXCEPTION
964        WHEN OTHERS THEN
965               FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
966               FND_MESSAGE.SET_TOKEN('NAME','IGS_IN_GEN_001. 7');
967               IGS_GE_MSG_STACK.ADD;
968        App_Exception.Raise_Exception;
969 END inqp_get_sci;
970 
971 
972 FUNCTION inqp_get_sua_achvd(
973   p_person_id IN NUMBER ,
974   p_course_cd IN VARCHAR2 ,
975   p_unit_cd IN VARCHAR2 ,
976   p_cal_type IN VARCHAR2 ,
977   p_ci_sequence_number IN NUMBER ,
978   p_version_number IN NUMBER ,
979   p_ci_end_dt IN DATE ,
980   p_unit_attempt_status IN VARCHAR2 ,
981   p_override_achievable_cp IN NUMBER ,
982   p_s_result_type IN VARCHAR2 ,
983   p_repeatable_ind IN VARCHAR2 ,
984   p_achievable_credit_points IN NUMBER ,
985   p_enrolled_credit_points IN NUMBER,
986   p_uoo_id IN igs_en_su_attempt.uoo_id%TYPE)
987 RETURN NUMBER AS
988 /*
989 | Who         When            What
990 |
991 | knaraset  09-May-03   Modified cursors c_sua and c_sua1 and passed uoo_id in call IGS_AS_GEN_003.ASSP_GET_SUA_OUTCOME,
992 |                       as part of MUS build bug 2829262
993 | rvivekan   09-sep-2003   Modified the behaviour of repeatable_ind column in igs_ps_unit_ver table. PSP integration build #3052433
994 |
995 */
996        gv_other_detail             VARCHAR2(255);
997 BEGIN  -- inqp_get_sua_achvd
998        -- Get the acheived credit points for a nominated student unit attempt,
999        -- allowing for:
1000        --     * Checking whether the student has passed.
1001        --     * Repeating of units which are either allowed or disallowed
1002        --       as repeatable units.
1003 DECLARE
1004        cst_completed CONSTANT      VARCHAR2(12) := 'COMPLETED';
1005        cst_duplicate CONSTANT      VARCHAR2(12) := 'DUPLICATE';
1006        cst_pass      CONSTANT      VARCHAR2(7) := 'PASS';
1007        v_override_achievable_cp    IGS_EN_SU_ATTEMPT.override_achievable_cp%TYPE;
1008        v_result_type               IGS_AS_GRD_SCH_GRADE.s_result_type%TYPE;
1009        v_repeatable_ind            IGS_PS_UNIT_VER.repeatable_ind%TYPE;
1010        v_achievable_credit_points  IGS_PS_UNIT_VER.achievable_credit_points%TYPE;
1011        v_enrolled_credit_points    IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
1012        v_result_found                     BOOLEAN DEFAULT FALSE;
1013        v_outcome_dt                DATE;
1014        v_grading_schema_cd         IGS_AS_GRD_SCH_GRADE.grading_schema_cd%TYPE;
1015        v_gs_version_number         IGS_AS_GRD_SCH_GRADE.version_number%TYPE;
1016        v_grade                            IGS_AS_GRD_SCH_GRADE.grade%TYPE;
1017        v_mark                      IGS_AS_SU_STMPTOUT.mark%TYPE;
1018        v_origin_course_cd          IGS_AS_SU_STMPTOUT.course_cd%TYPE;
1019 
1020        CURSOR c_sua(cp_person_id igs_en_su_attempt.person_id%TYPE,
1021                  cp_course_cd igs_en_su_attempt.course_cd%TYPE,
1022                  cp_uoo_id igs_en_su_attempt.uoo_id%TYPE) IS
1023               SELECT sua.version_number,
1024                      sua.ci_end_dt,
1025                      sua.unit_attempt_status,
1026             sua.location_cd,
1027             sua.unit_class
1028               FROM   IGS_EN_SU_ATTEMPT    sua
1029               WHERE  sua.person_id        = cp_person_id AND
1030                      sua.course_cd        = cp_course_cd AND
1031                      sua.uoo_id           = cp_uoo_id;
1032        v_sua_rec                   c_sua%ROWTYPE;
1033        CURSOR c_sua1 (cp_ci_end_dt igs_en_su_attempt.ci_end_dt%TYPE,
1034                    cp_location_cd igs_en_su_attempt.location_cd%TYPE,
1035                    cp_unit_class igs_en_su_attempt.unit_class%TYPE) IS
1036               SELECT sua.cal_type,
1037                      sua.ci_sequence_number,
1038                      sua.unit_attempt_status,
1039             sua.uoo_id
1040               FROM   IGS_EN_SU_ATTEMPT    sua
1041               WHERE  sua.person_id        = p_person_id AND
1042                      sua.course_cd        = p_course_cd AND
1043                      sua.unit_cd          = p_unit_cd AND
1044             sua.location_cd = cp_location_cd AND
1045             sua.unit_class = cp_unit_class AND
1046                      sua.unit_attempt_status     IN (
1047                                           cst_completed,
1048                                           cst_duplicate) AND
1049                      TRUNC(sua.ci_end_dt) < TRUNC(cp_ci_end_dt);
1050        CURSOR c_uv IS
1051               SELECT uv.repeatable_ind
1052               FROM   IGS_PS_UNIT_VER      uv
1053               WHERE  uv.unit_cd           = p_unit_cd AND
1054                      uv.version_number    = p_version_number;
1055 BEGIN
1056        -- If any of the unit atempt details are null then select from the
1057        -- student unit attempt.
1058        IF p_version_number IS NULL OR
1059                      p_ci_end_dt IS NULL OR
1060                      p_unit_attempt_status IS NULL THEN
1061               OPEN c_sua(p_person_id,p_course_cd,p_uoo_id);
1062               FETCH c_sua INTO v_sua_rec;
1063               IF c_sua%NOTFOUND THEN
1064                      CLOSE c_sua;
1065                      RETURN NULL;
1066               END IF;
1067               CLOSE c_sua;
1068        ELSE
1069               v_sua_rec.version_number := p_version_number;
1070               v_sua_rec.ci_end_dt := p_ci_end_dt;
1071               v_sua_rec.unit_attempt_status := p_unit_attempt_status;
1072        END IF;
1073        -- If not completed, no credit points could have been achieved.
1074        IF v_sua_rec.unit_attempt_status NOT IN (
1075                                           cst_completed,
1076                                           cst_duplicate) THEN
1077               RETURN 0;
1078        END IF;
1079        -- If the result type has no been specified, then call routine to\n   -- retrieve it.
1080        IF p_s_result_type IS NULL THEN
1081               v_result_type := IGS_AS_GEN_003.ASSP_GET_SUA_OUTCOME(
1082                                    p_person_id,
1083                                    p_course_cd,
1084                                    p_unit_cd,
1085                                    p_cal_type,
1086                                    p_ci_sequence_number,
1087                                    v_sua_rec.unit_attempt_status,
1088                                    'Y',
1089                                    v_outcome_dt,
1090                                    v_grading_schema_cd,
1091                                    v_gs_version_number,
1092                                    v_grade,
1093                                    v_mark,
1094                                    v_origin_course_cd,
1095                                    p_uoo_id,
1096 --added by LKAKI----
1097 		                   'N');
1098        ELSE
1099               v_result_type := p_s_result_type;
1100        END IF;
1101        -- If the result is not a pass then acheived credit is always zero.
1102        IF v_result_type <> cst_pass THEN
1103               RETURN 0;
1104        END IF;
1105        IF p_repeatable_ind IS NULL THEN
1106               OPEN c_uv;
1107               FETCH c_uv INTO v_repeatable_ind;
1108               IF c_uv%NOTFOUND THEN
1109                      CLOSE c_uv;
1110                      RETURN NULL;
1111               END IF;
1112               CLOSE c_uv;
1113        ELSE
1114               v_repeatable_ind := p_repeatable_ind;
1115        END IF;
1116        IF v_repeatable_ind <> 'X' THEN
1117               -- If the unit is repeatable then full credit is always granted.
1118               RETURN NVL(p_override_achievable_cp,
1119                             NVL(p_achievable_credit_points,
1120                                    p_enrolled_credit_points));
1121        ELSE
1122               -- If the unit isn't repeatable, only the first pass counts;
1123               -- ensure that this is the first pass.
1124               FOR v_sua1_rec IN c_sua1(v_sua_rec.ci_end_dt,v_sua_rec.location_cd,v_sua_rec.unit_class) LOOP
1125                      v_result_type := IGS_AS_GEN_003.ASSP_GET_SUA_OUTCOME(
1126                                    p_person_id,
1127                                    p_course_cd,
1128                                    p_unit_cd,
1129                                    v_sua1_rec.cal_type,
1130                                    v_sua1_rec.ci_sequence_number,
1131                                    v_sua1_rec.unit_attempt_status,
1132                                    'Y',
1133                                    v_outcome_dt,
1134                                    v_grading_schema_cd,
1135                                    v_gs_version_number,
1136                                    v_grade,
1137                                    v_mark,
1138                                    v_origin_course_cd,
1139                                    v_sua1_rec.uoo_id,
1140 --added by LKAKI---
1141 		                   'N');
1142                      IF v_result_type = cst_pass THEN
1143                             v_result_found := TRUE;
1144                             EXIT;
1145                      END IF;
1146               END LOOP;
1147               IF v_result_found THEN
1148                      -- Earlier pass found; no achievement.
1149                      RETURN 0;
1150               ELSE
1151                      RETURN NVL(p_override_achievable_cp,
1152                             NVL(p_achievable_credit_points,
1153                                    p_enrolled_credit_points));
1154               END IF;
1155        END IF;
1156 EXCEPTION
1157        WHEN OTHERS THEN
1158               IF c_sua%ISOPEN THEN
1159                      CLOSE c_sua;
1160               END IF;
1161               IF c_uv%ISOPEN THEN
1162                      CLOSE c_uv;
1163               END IF;
1164               IF c_sua1%ISOPEN THEN
1165                      CLOSE c_sua1;
1166               END IF;
1167               RAISE;
1168 END;
1169 END inqp_get_sua_achvd;
1170 
1171 
1172 END IGS_IN_GEN_001 ;