DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_EN_GEN_015

Source


1 PACKAGE BODY igs_en_gen_015 AS
2 /* $Header: IGSEN81B.pls 120.13 2006/03/14 00:43:32 smaddali ship $ */
3   --
4   --
5   --  This function is used to get the effective census date which will be used
6   --  to check the effectiveness of the hold.
7   --
8   --
9   FUNCTION get_effective_census_date
10   (
11     p_load_cal_type                IN     VARCHAR2,
12     p_load_cal_seq_number          IN     NUMBER,
13     p_teach_cal_type               IN     VARCHAR2,
14     p_teach_cal_seq_number         IN     NUMBER
15   ) RETURN DATE IS
16   --
17   --  Parameters Description:
18   --
19   --  p_load_cal_type              -> Term or Load Calendar Type
20   --  p_load_cal_seq_number        -> Term or Load Calendar Type Sequence Number
21   --  p_teach_cal_type             -> Teaching Calendar Type
22   --  p_teach_cal_seq_number       -> Teaching Calendar Type Sequence Number
23   --
24   --
25   --  Cursor to find Census Date Alias for the Term (Load)
26   --
27   CURSOR cur_census_date (
28            cp_cal_type              IN VARCHAR2,
29            cp_cal_seq_number        IN NUMBER
30          ) IS
31     SELECT   NVL (absolute_val,
32                     igs_ca_gen_001.calp_get_alias_val (
33                       dai.dt_alias,
34                       dai.sequence_number,
35                       dai.cal_type,
36                       dai.ci_sequence_number
37                     )
38                  ) AS term_census_date
39     FROM     igs_ge_s_gen_cal_con sgcc,
40              igs_ca_da_inst dai
41     WHERE    sgcc.s_control_num = 1
42     AND      dai.dt_alias = sgcc.census_dt_alias
43     AND      dai.cal_type = cp_cal_type
44     AND      dai.ci_sequence_number = cp_cal_seq_number
45     ORDER BY 1 ASC; -- Order by the census_date to use the earliest value.
46   CURSOR cur_teach_period_start_date IS
47     SELECT   start_dt
48     FROM     igs_ca_inst
49     WHERE    cal_type = p_teach_cal_type
50     AND      sequence_number = p_teach_cal_seq_number;
51   --
52   --  Local Variables for the function get_effective_census_date:
53   --
54   lv_census_date DATE;
55   --
56   BEGIN
57     --
58     --  The logic for calculating the Census Date is as follows:
59     --    1) Get the CENSUS-DATE alias value for the Term or Load Calendar.
60     --       If the CENSUS-DATE alias value is null or not defined then,
61     --       1.1) Get the CENSUS-DATE alias value for the Teaching Period.
62     --            If the the CENSUS-DATE value is null or not defined then,
63     --            1.1.1) Get the Start Date of Teaching Period.
64     --
65     --
66     --  Get the Census date of the Load or Term.
67     --
68     OPEN cur_census_date (p_load_cal_type, p_load_cal_seq_number);
69     FETCH cur_census_date INTO lv_census_date;
70     --
71     --  If the CENSUS-DATE alias value for the Term is null or not defined.
72     --
73     IF ((lv_census_date IS NULL) OR (cur_census_date%NOTFOUND)) THEN
74       CLOSE cur_census_date;
75       --
76       --  Get the Census date of the Teaching Period.
77       --
78       OPEN cur_census_date (p_teach_cal_type, p_teach_cal_seq_number);
79       FETCH cur_census_date INTO lv_census_date;
80       --
81       --  If the CENSUS-DATE alias value for the Teaching Period is null or not defined.
82       --
83       IF ((lv_census_date IS NULL) OR (cur_census_date%NOTFOUND)) THEN
84         CLOSE cur_census_date;
85         --
86         --  Get the Start date of Teaching Period instance as Census Date.
87         --
88         OPEN cur_teach_period_start_date;
89         FETCH cur_teach_period_start_date INTO lv_census_date;
90         CLOSE cur_teach_period_start_date;
91       END IF;
92     END IF;
93     --
94     IF (cur_census_date%ISOPEN) THEN
95       CLOSE cur_census_date;
96     END IF;
97     --
98     RETURN (lv_census_date);
99     --
100   END get_effective_census_date;
101   --
102   --
103   --  Function validation_step_overridden is used to check if the given
104   --  Eligibility Step Type is overridden or not and also returns the
105   --  overridden credit point limit if any. (The overridden credit point limit
106   --  will not be present for all the steps. It will be applicable only
107   --  for "Minimum Credit Point Limit", "Maximum Credit Point Limit" and
108   --  "Variable Credit Point Limit" steps.
109   --
110   --
111   FUNCTION val_step_is_ovr_non_stud
112   (
113     p_eligibility_step_type        IN     VARCHAR2
114   ) RETURN BOOLEAN AS
115 
116   l_person_type             igs_pe_person_types.person_type_code%TYPE;
117 
118   CURSOR cur_person_types (cp_person_type igs_pe_person_types.person_type_code%TYPE)IS
119     SELECT system_type
120     FROM   igs_pe_person_types
121     WHERE  person_type_code = cp_person_type;
122 
123   l_cur_person_types        cur_person_types%ROWTYPE;
124   l_system_person_type igs_pe_person_types.system_type%TYPE;
125 
126   CURSOR c_step_overridden (cp_validation  igs_pe_usr_aval.validation%TYPE,
127                             cp_person_type igs_pe_person_types.person_type_code%TYPE) IS
128     SELECT override_ind
129     FROM   igs_pe_usr_aval
130     WHERE  validation = cp_validation
131     AND    override_ind = 'Y'
132     AND    person_type = cp_person_type;
133 
134   l_step_overridden    igs_pe_usr_aval.override_ind%TYPE;
135 
136   BEGIN
137 
138     l_step_overridden := 'N';
139     l_person_type     := Igs_En_Gen_008.enrp_get_person_type(p_course_cd =>NULL);
140 
141     OPEN  cur_person_types(l_person_type);
142     FETCH cur_person_types INTO l_cur_person_types;
143     CLOSE cur_person_types;
144 
145     l_system_person_type := l_cur_person_types.system_type;
146 
147     IF l_system_person_type <> 'STUDENT' THEN
148 
149        -- check whether l_step is overridden or not for non student
150        OPEN c_step_overridden (p_eligibility_step_type,l_person_type );
151        FETCH c_step_overridden INTO l_step_overridden;
152        -- if the step is overridden, return true else continue the rest of validation
153        IF c_step_overridden%FOUND THEN
154           CLOSE c_step_overridden;
155           RETURN TRUE;
156        END IF;
157        CLOSE c_step_overridden;
158 
159     END IF; -- check for person type
160     RETURN FALSE;
161 
162   END val_step_is_ovr_non_stud;
163 
164 
165   FUNCTION validation_step_is_overridden
166   (
167     p_eligibility_step_type        IN     VARCHAR2,
168     p_load_cal_type                IN     VARCHAR2,
169     p_load_cal_seq_number          IN     NUMBER,
170     p_person_id                    IN     NUMBER,
171     p_uoo_id                       IN     NUMBER,
172     p_step_override_limit          OUT    NOCOPY    NUMBER
173   ) RETURN BOOLEAN IS
174   --
175   -- History :
176   -- svenkata   6-Jun-2003      Modified the routine to check for Unit level Overrides at the Unit section level. If overrides do not exist at Unit
177   --                            section level , check if one exists at Unit level. Deny / Warn build - Bug : 2829272.
178   --  Parameters Description:
179   --
180   --  p_eligibility_step_type      -> Enrollment Eligibility Step Type
181   --  p_load_cal_type              -> Term or Load Calendar Type
182   --  p_load_cal_seq_number        -> Term or Load Calendar Type Sequence Number
183   --  p_person_id                  -> Person ID of the Student who wants to enroll
184   --                                  or administrator is enrolling the Students.
185   --  p_uoo_id                     -> Unit Section Identifier to get the Teaching Calendar
186   --                                  Instance against which the override will be checked
187   --                                  in case it is not overridden at the Load Calendar level.
188   --  p_step_override_limit        -> This will return the overridden limit for example
189   --                                  Maximum Credit point limit.
190   --
191   --
192   --  Cursor to check if the Step is overridden for a given Load or Teaching Calendar.
193   --
194   CURSOR cur_check_override (
195            cp_cal_type              IN VARCHAR2,
196            cp_cal_seq_number        IN NUMBER
197          ) IS
198     SELECT   step_override_limit,
199              step_override_type
200     FROM     igs_en_elgb_ovr_step eos,
201              igs_en_elgb_ovr eoa
202     WHERE    eoa.elgb_override_id = eos.elgb_override_id
203     AND      eoa.cal_type = cp_cal_type
204     AND      eoa.ci_sequence_number = cp_cal_seq_number
205     AND      eoa.person_id = p_person_id
206     AND      eos.step_override_type = p_eligibility_step_type;
207   --
208   --  Cursor to check if the Step is overridden for a given Load or Teaching Calendar
209   --  and Unit Section.
210   --
211   CURSOR cur_check_override_uoo_id (
212            cp_cal_type              IN VARCHAR2,
213            cp_cal_seq_number        IN NUMBER,
214            cp_uoo_id                IN NUMBER
215          ) IS
216     SELECT   eou.step_override_limit,
217              step_override_type
218     FROM     igs_en_elgb_ovr_step eos,
219              igs_en_elgb_ovr eoa ,
220              igs_en_elgb_ovr_uoo eou
221     WHERE    eoa.elgb_override_id = eos.elgb_override_id
222     AND      eoa.cal_type = cp_cal_type
223     AND      eoa.ci_sequence_number = cp_cal_seq_number
224     AND      eoa.person_id = p_person_id
225     AND      eos.step_override_type = p_eligibility_step_type
226     AND      eos.elgb_ovr_step_id = eou.elgb_ovr_step_id
227     AND      eou.uoo_id = cp_uoo_id;
228   --
229   --  Cursor to check if the Step is overridden for a given Load or Teaching Calendar
230   --  and Unit Code and Version Number of the Unit Section ID.
231   --
232   CURSOR cur_check_override_unit (
233            cp_cal_type              IN VARCHAR2,
234            cp_cal_seq_number        IN NUMBER,
235            cp_unit_cd               IN VARCHAR2,
236            cp_version_number        IN NUMBER
237          ) IS
238     SELECT   eou.step_override_limit,
239              step_override_type
240     FROM     igs_en_elgb_ovr_step eos,
241              igs_en_elgb_ovr eoa ,
242              igs_en_elgb_ovr_uoo eou
243     WHERE    eoa.elgb_override_id = eos.elgb_override_id
244     AND      eoa.cal_type = cp_cal_type
245     AND      eoa.ci_sequence_number = cp_cal_seq_number
246     AND      eoa.person_id = p_person_id
247     AND      eos.step_override_type = p_eligibility_step_type
248     AND      eos.elgb_ovr_step_id = eou.elgb_ovr_step_id
249     AND      eou.unit_cd = cp_unit_cd
250     AND      eou.version_number = cp_version_number
251     AND      ( eou.uoo_id = -1 OR eou.uoo_id  IS NULL) ;
252   --
253   --  Cursor to check if the Step is overridden for a given Load or Teaching Calendar
254   --  for the Unit Step.
255   --
256   CURSOR cur_check_override_ustep (
257            cp_cal_type              IN VARCHAR2,
258            cp_cal_seq_number        IN NUMBER
259          ) IS
260     SELECT   step_override_limit,
261              step_override_type
262     FROM     igs_en_elgb_ovr_step eos,
263              igs_en_elgb_ovr eoa
264     WHERE    eoa.elgb_override_id = eos.elgb_override_id
265     AND      eoa.cal_type = cp_cal_type
266     AND      eoa.ci_sequence_number = cp_cal_seq_number
267     AND      eoa.person_id = p_person_id
268     AND      eos.step_override_type = p_eligibility_step_type
269     AND  NOT EXISTS (   SELECT 'X'
270                         FROM igs_en_elgb_ovr_uoo eou
271                         WHERE eos.elgb_ovr_step_id = eou.elgb_ovr_step_id );
272   --
273   --  Cursor to finds the Teaching Calendar for a Unit Section.
274   --
275   CURSOR cur_teach_period_of_uoo_id IS
276     SELECT   unit_cd,
277              version_number,
278              cal_type,
279              ci_sequence_number
280     FROM     igs_ps_unit_ofr_opt
281     WHERE    uoo_id = p_uoo_id;
282   --
283   --  Local Variables for the function validation_step_is_overridden:
284   --
285   rec_cur_check_override cur_check_override%ROWTYPE;
286   rec_cur_check_override_uoo_id cur_check_override_uoo_id%ROWTYPE;
287   rec_cur_check_override_unit cur_check_override_unit%ROWTYPE;
288   rec_cur_check_override_ustep cur_check_override_ustep%ROWTYPE;
289   rec_cur_teach_period_of_uoo_id cur_teach_period_of_uoo_id%ROWTYPE;
290   --
291 
292   BEGIN
293 
294     --
295     --  If the Unit Section ID is NULL then process the overridden logic using
296     --  the Calendar passed.
297     --
298     IF (p_uoo_id IS NULL) THEN
299       --
300       --  Check if the Step is Overridden irrespective of the Unit Section ID
301       --  and Unit Code, Unit Version. The step is overridden if the cursor
302       --  fetches atleast one record.
303       --
304       OPEN cur_check_override (p_load_cal_type, p_load_cal_seq_number);
305       FETCH cur_check_override INTO rec_cur_check_override;
306       IF (cur_check_override%FOUND) THEN --  Step is Overridden
307         CLOSE cur_check_override;
308         p_step_override_limit := rec_cur_check_override.step_override_limit;
309 
310         RETURN TRUE;
311 
312       ELSE --  Step is not Overridden
313         CLOSE cur_check_override;
314 
315         RETURN FALSE;
316       END IF;
317 
318     ELSE --  If Unit Section is not NULL
319 
320       --
321       --  Check if the Step is Overridden for the passed Unit Section ID. The step
322       --  is overridden if the cursor fetches atleast one record.
323       --
324       OPEN cur_check_override_uoo_id (
325              p_load_cal_type,
326              p_load_cal_seq_number,
327              p_uoo_id           );
328       FETCH cur_check_override_uoo_id INTO rec_cur_check_override_uoo_id;
329       IF (cur_check_override_uoo_id%FOUND) THEN
330         CLOSE cur_check_override_uoo_id;
331         p_step_override_limit := rec_cur_check_override_uoo_id.step_override_limit;
332 
333         RETURN TRUE;
334 
335       ELSE --  If the Step is not overridden for the Unit Section.
336         CLOSE cur_check_override_uoo_id;
337         --
338         --  Get the Unit Code and Version Number for the passed Unit Section ID.
339         --
340         OPEN cur_teach_period_of_uoo_id;
341         FETCH cur_teach_period_of_uoo_id INTO rec_cur_teach_period_of_uoo_id;
342         CLOSE cur_teach_period_of_uoo_id;
343         --
344         --  If the step is not overridden for the passed Unit Section ID then
345         --  check if the step is Overridden for the Unit Code and Version Number
346         --  of the passed Unit Section ID. The step is overridden if the cursor
347         --  fetches atleast one record.
348         --
349         OPEN cur_check_override_unit (
350                p_load_cal_type,
351                p_load_cal_seq_number,
352                rec_cur_teach_period_of_uoo_id.unit_cd,
353                rec_cur_teach_period_of_uoo_id.version_number
354              );
355         FETCH cur_check_override_unit INTO rec_cur_check_override_unit;
356         IF (cur_check_override_unit%FOUND) THEN --  Step is Overridden for the Unit
357           CLOSE cur_check_override_unit;
358           p_step_override_limit := rec_cur_check_override_unit.step_override_limit;
359 
360           RETURN TRUE;
361         ELSE --  If Step is not Overridden for the Unit
362           CLOSE cur_check_override_unit;
363           --
364           --  Check if the Step is Overridden. The step is overridden if the cursor
365           --  fetches atleast one record.
366           --
367           OPEN cur_check_override_ustep (
368                  p_load_cal_type,
369                  p_load_cal_seq_number
370                );
371           FETCH cur_check_override_ustep INTO rec_cur_check_override_ustep;
372           IF (cur_check_override_ustep%FOUND) THEN --  Step is Overridden
373             CLOSE cur_check_override_ustep;
374             p_step_override_limit := rec_cur_check_override_ustep.step_override_limit;
375             RETURN TRUE;
376           ELSE --  If Step is not Overridden
377             CLOSE cur_check_override_ustep;
378             --
379             -- Checking any overrides exists at unit and unit section level in teaching period, added the below code as part of bug 2366438, pmarada
380             -- Check any overrides at unit section level in the Teaching calender
381                -- Passing teaching cal type, and seq number to the uoo_id cursor, and
382                -- checking any override exists at Unit section level in the teach period.
383                OPEN cur_check_override_uoo_id (
384                     rec_cur_teach_period_of_uoo_id.cal_type,
385                     rec_cur_teach_period_of_uoo_id.ci_sequence_number,
386                     p_uoo_id  );
387                FETCH cur_check_override_uoo_id INTO rec_cur_check_override_uoo_id;
388                  IF (cur_check_override_uoo_id%FOUND) THEN
389                    CLOSE cur_check_override_uoo_id;
390                    p_step_override_limit := rec_cur_check_override_uoo_id.step_override_limit;
391 
392                    RETURN TRUE;
393                  ELSE
394                    CLOSE cur_check_override_uoo_id;
395                     -- Check any overrides exists at unit level in Teaching Period.
396                     -- Passing teaching cal type,seq number,and unit_cd, version to the unit cursor
397                    OPEN cur_check_override_unit (
398                         rec_cur_teach_period_of_uoo_id.cal_type,
399                         rec_cur_teach_period_of_uoo_id.ci_sequence_number,
400                         rec_cur_teach_period_of_uoo_id.unit_cd,
401                         rec_cur_teach_period_of_uoo_id.version_number );
402                    FETCH cur_check_override_unit INTO rec_cur_check_override_unit;
403                    IF (cur_check_override_unit%FOUND) THEN --  Step is Overridden for the Unit
404                      CLOSE cur_check_override_unit;
405                      p_step_override_limit := rec_cur_check_override_unit.step_override_limit;
406 
407                      RETURN TRUE;
408                   ELSE --  If Step is not Overridden for the Unit
409                     CLOSE cur_check_override_unit;
410                     -- end of the code added as part of bug 2366438, pmarada
411                     --  Check if the Step is Overridden for the Teaching Calendar Instance.
412                     --  The step is overridden if the cursor fetches atleast one record.
413                     --
414                     OPEN cur_check_override_ustep (
415                         rec_cur_teach_period_of_uoo_id.cal_type,
416                         rec_cur_teach_period_of_uoo_id.ci_sequence_number
417                         );
418                     FETCH cur_check_override_ustep INTO rec_cur_check_override_ustep;
419                     IF (cur_check_override_ustep%FOUND) THEN --  Step is Overridden
420                       CLOSE cur_check_override_ustep;
421                       p_step_override_limit := rec_cur_check_override_ustep.step_override_limit;
422                       RETURN TRUE;
423                     ELSE --  If Step is not Overridden, There is no override at any of level in load and teach periods.
424                      CLOSE cur_check_override_ustep;
425                     END IF;  -- cur_check_override_ustep teaching cal type
426                 END IF;   -- cur_check_override_unit for teaching period at unit level
427             END IF;      -- cur_check_override_uoo_id for teaching period at unit section level
428           END IF;       -- cur_check_override_ustep load cal
429         END IF;       -- cur_check_override_unit load at unit
430       END IF;       -- cur_check_override_uoo_id for load at unit section level
431     END IF;     -- Uoo_id is not null
432 
433     -- If the override is not set up and any of the obove level
434     -- check for the override at the user activity level
435     IF val_step_is_ovr_non_stud(p_eligibility_step_type) THEN
436       -- set the limit value as null, since this cannot be setup
437       -- in the user activity form
438       p_step_override_limit := NULL;
439       RETURN TRUE;
440     END IF;
441 
442     --
443     --  If the Step is not overridden at any level then return FALSE.
444     --
445     RETURN FALSE;
446     --
447   END validation_step_is_overridden;
448   --
449   --
450   --  Function seats_in_unreserved_category is used to check if there are seats
451   --  available in Unreserved Category.
452   --
453   --
454   FUNCTION seats_in_unreserved_category
455   (
456     p_uoo_id                       IN     NUMBER,
457     p_level                        IN     VARCHAR2
458   )
459   RETURN NUMBER IS
460   --
461   -- History :
462   -- stutta 27-Jul-2004  Removed logic to return(0) if enrollment max is null.
463   --                     This return is stopping enrollment into unreserved seats
464   --                     when reserve seating is set to <100% and enr max is null.
465   --                     Hence, Considered enr max as 999999 if null instead. This
466   --                     logic also takes care of stopping enrollment to unreserved
467   --                     seats if 100% seats are set for reserve seating.Bug #3452321
468 
469   --
470   --  Cursor to find Maximum Enrolllment for the Unit Section if available;
471   --  otherwise get the Maximum Enrolllment for the Unit.
472   --
473   CURSOR cur_maximum_enrollment IS
474     SELECT   NVL (usec.enrollment_maximum, uv.enrollment_maximum) enrollment_maximum,
475              uoo.enrollment_actual enrollment_actual
476     FROM     igs_ps_usec_lim_wlst usec,
477              igs_ps_unit_ver uv,
478              igs_ps_unit_ofr_opt uoo
479     WHERE    uoo.unit_cd = uv.unit_cd
480     AND      uoo.version_number = uv.version_number
481     AND      uoo.uoo_id = usec.uoo_id (+)
482     AND      uoo.uoo_id = p_uoo_id;
483   --
484   --  Cursor to find all the Organization Priorities for the Unit Section Organization.
485   --
486   CURSOR cur_org_priorities IS
487     SELECT   rsv_org_unit_pri_id
488     FROM     igs_ps_rsv_ogpri
489     WHERE    org_unit_cd = (SELECT   owner_org_unit_cd
490                             FROM     igs_ps_unit_ofr_opt
491                             WHERE    uoo_id = p_uoo_id);
492   --
493   --  Cursor to find all the Organization Preferences for the passed Organization Priority.
494   --
495   CURSOR cur_org_preferences (
496            cp_org_unit_priority_id  IN NUMBER
497          ) IS
498     SELECT   rsv_org_unit_pri_id,
499              rsv_org_unit_prf_id,
500              percentage_reserved
501     FROM     igs_ps_rsv_orgun_prf
502     WHERE    rsv_org_unit_pri_id = cp_org_unit_priority_id;
503   --
504   --  Cursor to find all the Unit Offering Pattern Priorities for the Unit Offering Pattern.
505   --
506   CURSOR cur_uop_priorities IS
507     SELECT   rsv_uop_pri_id
508     FROM     igs_ps_rsv_uop_pri
509     WHERE    (unit_cd,
510               version_number,
511               calender_type,
512               ci_sequence_number) = (SELECT   unit_cd,
513                                               version_number,
514                                               cal_type,
515                                               ci_sequence_number
516                                      FROM     igs_ps_unit_ofr_opt
517                                      WHERE    uoo_id = p_uoo_id);
518   --
519   --  Cursor to find all the Unit Offering Pattern Preferences for the passed Unit Offering
520   --  Pattern Priority.
521   --
522   CURSOR cur_uop_preferences (
523            cp_uop_priority_id       IN NUMBER
524          ) IS
525     SELECT   rsv_uop_pri_id,
526              rsv_uop_prf_id,
527              percentage_reserved
528     FROM     igs_ps_rsv_uop_prf
529     WHERE    rsv_uop_pri_id = cp_uop_priority_id;
530   --
531   --  Cursor to find all the Unit Section Priorities for the Unit Section.
532   --
533   CURSOR cur_usec_priorities IS
534     SELECT   rsv_usec_pri_id
535     FROM     igs_ps_rsv_usec_pri
536     WHERE    uoo_id = p_uoo_id;
537   --
538   --  Cursor to find all the Unit Section Preferences for the passed Unit Section Priority.
539   --
540   CURSOR cur_usec_preferences (
541            cp_usec_priority_id       IN NUMBER
542          ) IS
543     SELECT   rsv_usec_pri_id,
544              rsv_usec_prf_id,
545              percentage_reserved
546     FROM     igs_ps_rsv_usec_prf
547     WHERE    rsv_usec_pri_id = cp_usec_priority_id;
548   --
549   --  Cursor to find Actual seats enrolled for the passed Level, Unit Section, and the
550   --  Priorities and Preferences selected for the Level.
551   --
552   CURSOR cur_actual_seats (
553            cp_uoo_id                IN NUMBER,
554            cp_priority_id           IN NUMBER,
555            cp_preference_id         IN NUMBER,
556            cp_level                 IN VARCHAR2
557          ) IS
558     SELECT   actual_seat_enrolled
559     FROM     igs_ps_rsv_ext
560     WHERE    uoo_id = cp_uoo_id
561     AND      priority_id = cp_priority_id
562     AND      preference_id = cp_preference_id
563     AND      rsv_level = cp_level;
564   --
565   --  Local Variables for the function seats_in_unreserved_category:
566   --
567   rec_cur_maximum_enrollment cur_maximum_enrollment%ROWTYPE;
568   lv_total_reserved_seats NUMBER;
569   lv_actual_enrolled_seats NUMBER;
570   lv_seats_available NUMBER;
571   --
572   BEGIN
573     --
574     --  Get the Maximum Enrolllment for the Unit Section if available;
575     --  otherwise get the Maximum Enrolllment for the Unit.
576     --
577     OPEN cur_maximum_enrollment;
578     FETCH cur_maximum_enrollment INTO rec_cur_maximum_enrollment;
579     IF ((cur_maximum_enrollment%NOTFOUND) OR (rec_cur_maximum_enrollment.enrollment_maximum IS NULL)) THEN
580       rec_cur_maximum_enrollment.enrollment_maximum := 999999;
581     END IF;
582     CLOSE cur_maximum_enrollment;
583     --
584     --  Check the type of level for which the seats have to be calculated.
585     --
586     lv_total_reserved_seats := 0;
587     lv_actual_enrolled_seats := 0;
588     IF (p_level = 'UNIT_SEC') THEN
589       FOR rec_cur_usec_priorities IN cur_usec_priorities LOOP
590         FOR rec_cur_usec_preferences IN cur_usec_preferences (rec_cur_usec_priorities.rsv_usec_pri_id) LOOP
591           lv_total_reserved_seats := NVL (lv_total_reserved_seats, 0) +
592                                      ((rec_cur_maximum_enrollment.enrollment_maximum * NVL (rec_cur_usec_preferences.percentage_reserved, 0)) / 100);
593           FOR rec_cur_actual_seats IN cur_actual_seats (
594                                         p_uoo_id,
595                                         rec_cur_usec_preferences.rsv_usec_pri_id,
596                                         rec_cur_usec_preferences.rsv_usec_prf_id,
597                                         p_level
598                                       ) LOOP
599             lv_actual_enrolled_seats := NVL (lv_actual_enrolled_seats, 0) + NVL (rec_cur_actual_seats.actual_seat_enrolled, 0);
600           END LOOP;
601         END LOOP;
602       END LOOP;
603       lv_seats_available := (rec_cur_maximum_enrollment.enrollment_maximum - FLOOR (NVL (lv_total_reserved_seats, 0)))
604                               - (NVL (rec_cur_maximum_enrollment.enrollment_actual, 0) - NVL (lv_actual_enrolled_seats, 0));
605       RETURN (lv_seats_available);
606     ELSIF (p_level = 'UNIT_PAT') THEN
607       FOR rec_cur_uop_priorities IN cur_uop_priorities LOOP
608         FOR rec_cur_uop_preferences IN cur_uop_preferences (rec_cur_uop_priorities.rsv_uop_pri_id) LOOP
609           lv_total_reserved_seats := NVL (lv_total_reserved_seats, 0) +
610                                      ((rec_cur_maximum_enrollment.enrollment_maximum * NVL (rec_cur_uop_preferences.percentage_reserved, 0)) / 100);
611           FOR rec_cur_actual_seats IN cur_actual_seats (
612                                         p_uoo_id,
613                                         rec_cur_uop_preferences.rsv_uop_pri_id,
614                                         rec_cur_uop_preferences.rsv_uop_prf_id,
615                                         p_level
616                                       ) LOOP
617             lv_actual_enrolled_seats := NVL (lv_actual_enrolled_seats, 0) + NVL (rec_cur_actual_seats.actual_seat_enrolled, 0);
618           END LOOP;
619         END LOOP;
620       END LOOP;
621       lv_seats_available := (rec_cur_maximum_enrollment.enrollment_maximum - FLOOR (NVL (lv_total_reserved_seats, 0)))
622                             - (NVL (rec_cur_maximum_enrollment.enrollment_actual, 0) - NVL (lv_actual_enrolled_seats, 0));
623       RETURN (lv_seats_available);
624     ELSIF (p_level = 'ORG_UNIT') THEN
625       FOR rec_cur_org_priorities IN cur_org_priorities LOOP
626         FOR rec_cur_org_preferences IN cur_org_preferences (rec_cur_org_priorities.rsv_org_unit_pri_id) LOOP
627           lv_total_reserved_seats := NVL (lv_total_reserved_seats, 0) +
628                                      ((rec_cur_maximum_enrollment.enrollment_maximum * NVL (rec_cur_org_preferences.percentage_reserved, 0)) / 100);
629           FOR rec_cur_actual_seats IN cur_actual_seats (
630                                         p_uoo_id,
631                                         rec_cur_org_preferences.rsv_org_unit_pri_id,
632                                         rec_cur_org_preferences.rsv_org_unit_prf_id,
633                                         p_level
634                                       ) LOOP
635             lv_actual_enrolled_seats := NVL (lv_actual_enrolled_seats, 0) + NVL (rec_cur_actual_seats.actual_seat_enrolled, 0);
636           END LOOP;
637         END LOOP;
638       END LOOP;
639       lv_seats_available := (rec_cur_maximum_enrollment.enrollment_maximum - FLOOR (NVL (lv_total_reserved_seats, 0)))
640                             - (NVL (rec_cur_maximum_enrollment.enrollment_actual, 0) - NVL (lv_actual_enrolled_seats, 0));
641       RETURN (lv_seats_available);
642     END IF;
643     -- Incase if none of the conditions are satisfied then it is returning 0.
644     -- Added as part of bug# 2396138.
645     RETURN 0;
646   --
647   END seats_in_unreserved_category;
648 
649   PROCEDURE get_usec_status
650   (
651     p_uoo_id               IN NUMBER,
652     p_person_id            IN NUMBER,
653     p_unit_section_status  OUT NOCOPY VARCHAR2,
654     p_waitlist_ind         OUT NOCOPY VARCHAR2,
655     p_load_cal_type        IN VARCHAR2 ,
656     p_load_ci_sequence_number IN NUMBER,
657     p_course_cd            IN VARCHAR2
658   ) AS
659   /*--------------------------------------------------------------------------------------------------------------
660   ||  Created By :
661   ||  Created On :
662   ||  Purpose :This procedure is used to get the status of the Unit Section and Waitlist Indicator,
663   ||           which determine whether student can Enroll, Waitlist or will be shown error message.
664   ||           p_waitlist_ind -> N, means Student can enroll into the unit section
665   ||                          -> Y, means Student can waitlist into the unit section
666   ||                          -> NULL, means Student can neither Enroll nor waitlist, message will be shown.
667   ||           If seats are available and reserved seat is allowed then student enrollment is subject to whether
668   ||           student satisfying the reserved seat step.
669   ||           If student has got Closed section override, he/she will be Enrolled subject to Override max limit
670   ||           , otherwise student will be wiatlisted subject to waitlist setup.
671   || HISTORY
672   || WHO         WHEN          WHAT
673   || smanglm     22-Jan-2003   call igs_en_gen_017.enrp_get_enr_method to decide enrollment method type
674   || knaraset    17-Jul-2002   modified the entire logic which consider only Actual Enrollment and
675   ||                           Max. enrollment limit And other overrides and waitlist setup,
676   ||                           as part fo the bug fix:2417240
677   || pradhakr    24-Oct-2002   Modified the code to get the enrollment maximum, override max from
678   ||                           Cross listed group / Meet with classes. If setup is not done in the
679   ||                           above mentioned groups then it picks up from Unit Section / Unit level.
680   ||                           Changes as per Cross Listed / Meet With DLD. Bug# 2599929.
681   || kkillams    18-12-2002    Checking the student unit attempt table for reserve seating identifier before
682   ||                           calling the  Igs_En_Elgbl_Unit.eval_rsv_seat function w.r.t. bug no :2643207
683   || ptandon     02-09-2003    Modified the local function check_overrides_waitlist to check whether waitlisting
684   ||                           is allowed at Institution/Term Calendar Level also as part of Waitlist
685   ||                           Enhancements Build - Bug# 3052426
686   ------------------------------------------------------------------------------------------------------------------*/
687   --
688   --  Cursor to find the Unit Section Status,Actual Enrollment,Actual Waitlist and Reserve seating allowed indicator
689   --
690   CURSOR c_unit_section_status  (cp_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
691   SELECT unit_section_status,enrollment_actual, waitlist_actual,reserved_seating_allowed
692   FROM   igs_ps_unit_ofr_opt
693   WHERE  uoo_id = cp_uoo_id;
694 
695   -- cursor to fetch the override enrollment maximum value defined at unit level
696   CURSOR cur_unit_enr_max( p_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
697   SELECT override_enrollment_max, enrollment_maximum
698   FROM   igs_ps_unit_ver
699   WHERE  (unit_cd , version_number ) IN (SELECT unit_cd , version_number
700                                          FROM   igs_ps_unit_ofr_opt
701                                          WHERE  uoo_id = p_uoo_id);
702 
703   -- Cursor to fetch the Override enrollment Maximum value defined at Unit Section level
704   CURSOR cur_usec_enr_max( p_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
705   SELECT override_enrollment_max, enrollment_maximum
706   FROM igs_ps_usec_lim_wlst
707   WHERE uoo_id = p_uoo_id;
708 
709   CURSOR c_prg_ver IS
710   SELECT version_number
711   FROM igs_en_stdnt_ps_att
712   WHERE person_id= p_person_id AND
713         course_cd = p_course_cd;
714 
715 
716   -- Cursor to get the enrollment maximum in cross listed group
717   CURSOR  c_cross_listed (l_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
718   SELECT  grp.max_enr_group, grp.max_ovr_group, grpmem.usec_x_listed_group_id
719   FROM    igs_ps_usec_x_grpmem grpmem,
720           igs_ps_usec_x_grp grp
721   WHERE   grp.usec_x_listed_group_id = grpmem.usec_x_listed_group_id
722   AND     grpmem.uoo_id = l_uoo_id;
723 
724 
725   -- Cursor to get the enrollment maximum in Meet with class group
726   CURSOR  c_meet_with_cls (l_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
727   SELECT  grp.max_enr_group, grp.max_ovr_group, ucm.class_meet_group_id
728   FROM    igs_ps_uso_clas_meet ucm,
729           igs_ps_uso_cm_grp grp
730   WHERE   grp.class_meet_group_id = ucm.class_meet_group_id
731   AND     ucm.uoo_id = l_uoo_id;
732 
733 
734    -- Cursor to get the actual enrollment of all the unit sections that belong
735    -- to this class listed group.
736   CURSOR c_actual_enr_crs_lst(l_usec_x_listed_group_id igs_ps_usec_x_grpmem.usec_x_listed_group_id%TYPE) IS
737   SELECT SUM(enrollment_actual)
738   FROM   igs_ps_unit_ofr_opt uoo,
739          igs_ps_usec_x_grpmem ugrp
740   WHERE  uoo.uoo_id = ugrp.uoo_id
741   AND    ugrp.usec_x_listed_group_id = l_usec_x_listed_group_id;
742 
743 
744   -- Cursor to get the actual enrollment of all the unit sections that belong
745   -- to this meet with class group.
746   CURSOR c_actual_enr_meet_cls(l_class_meet_group_id igs_ps_uso_clas_meet.class_meet_group_id%TYPE) IS
747   SELECT SUM(enrollment_actual)
748   FROM   igs_ps_unit_ofr_opt uoo,
749          igs_ps_uso_clas_meet ucls
750   WHERE  uoo.uoo_id = ucls.uoo_id
751   AND    ucls.class_meet_group_id = l_class_meet_group_id;
752 
753   --Cursor to get the reserve seat id at unit section attempt level
754   CURSOR c_sua_rs (p_person_id IGS_EN_SU_ATTEMPT.PERSON_ID%TYPE,
755                    p_course_cd IGS_EN_SU_ATTEMPT.COURSE_CD%TYPE,
756                    p_uoo_id    IGS_EN_SU_ATTEMPT.UOO_ID%TYPE) IS
757   SELECT rsv_seat_ext_id FROM igs_en_su_attempt
758                          WHERE person_id = p_person_id
759                          AND   course_cd = p_course_cd
760                          AND   p_uoo_id  = p_uoo_id
761                          AND   rsv_seat_ext_id IS NOT NULL;
762 
763   l_rsv_seat_ext_id         igs_en_su_attempt.rsv_seat_ext_id%TYPE;
764   l_version_number          igs_ps_ver.version_number%TYPE;
765   l_enrollment_maximum      igs_ps_unit_ver.enrollment_maximum%TYPE;
766   l_override_enrollment_max igs_ps_unit_ver.override_enrollment_max%TYPE;
767   l_enrollment_actual       igs_ps_unit_ofr_opt.enrollment_actual%TYPE;
768   l_waitlist_actual         igs_ps_unit_ofr_opt.waitlist_actual%TYPE;
769   l_rsv_allowed             VARCHAR2(10);
770   l_enr_meth_type           igs_en_method_type.enr_method_type%TYPE;
771   l_enr_cal_type            VARCHAR2(20);
772   l_enr_ci_seq              NUMBER(20);
773   l_enr_cat                 VARCHAR2(20);
774   l_enr_comm                VARCHAR2(2000);
775   l_return_val              BOOLEAN;
776   l_acad_cal_type           igs_ca_inst.cal_type%TYPE;
777   l_acad_ci_sequence_number igs_ca_inst.sequence_number%TYPE;
778   l_acad_start_dt           igs_ca_inst.start_dt%TYPE;
779   l_acad_end_dt             igs_ca_inst.end_dt%TYPE;
780   l_alternate_code          igs_ca_inst.alternate_code%TYPE;
781   l_message                 VARCHAR2(100);
782   l_person_type             igs_pe_person_types.person_type_code%TYPE;
783   l_notification_flag       VARCHAR2(10);
784   l_ret_status              VARCHAR2(10);
785 
786   l_cross_listed_row        c_cross_listed%ROWTYPE;
787   l_meet_with_cls_row       c_meet_with_cls%ROWTYPE;
788   l_unit_section_status     c_unit_section_status%ROWTYPE;
789   l_usec_partof_group       BOOLEAN;
790   l_dummy                   VARCHAR2(200);
791   l_deny_enrollment         VARCHAR2(1);
792 
793 --
794 -- Local Function to check Overrides and waitlist then return appropriate value.
795 --  N - Can Enroll into the unit section
796 --  Y - Can waitlist into the unit section
797 --  NULL - Cant Enroll/Waitlist, Error message should be shown to user
798 --
799 FUNCTION check_overrides_waitlist RETURN VARCHAR2 IS
800  --
801  -- Cursor to Check if Waitlisting is allowed at the institution level .
802  --
803   CURSOR c_wait_allow_inst_level IS
804   SELECT waitlist_allowed_flag
805   FROM igs_en_inst_wl_stps;
806  --
807  -- Cursor to Check if Waitlisting is allowed at the term calendar level .
808  --
809   CURSOR c_wait_allow_term_cal(cp_cal_type igs_en_inst_wlst_opt.cal_type%TYPE) IS
810   SELECT waitlist_alwd
811   FROM igs_en_inst_wlst_opt
812   WHERE cal_type = cp_cal_type;
813  --
814  -- Cursor to Check if Waitlisting is allowed at the unit section level .
815  --
816   CURSOR c_wait_allow_unit_section ( cp_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
817   SELECT  waitlist_allowed , max_students_per_waitlist
818   FROM igs_ps_usec_lim_wlst
819   WHERE uoo_id = cp_uoo_id ;
820  --
821  -- cursor check if waitlisting is allowed at the unit offering level .
822  --
823   CURSOR c_wait_allow_unit_offering ( cp_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
824   SELECT  uop.waitlist_allowed, uop.max_students_per_waitlist
825   FROM igs_ps_unit_ofr_pat uop,
826        igs_ps_unit_ofr_opt uoo
827   WHERE uop.unit_cd            = uoo.unit_cd
828          AND   uop.version_number     = uoo.version_number
829          AND   uop.cal_type           = uoo.cal_type
830          AND   uop.ci_sequence_number = uoo.ci_sequence_number
831          AND   uoo.uoo_id             = cp_uoo_id
832          AND   uop.delete_flag        ='N';
833 
834 
835   l_step_override_limit     igs_en_elgb_ovr_step.step_override_limit%TYPE;
836   l_wlst_max_ovr            BOOLEAN;
837   l_closed_section_ovr      BOOLEAN;
838   l_waitlist_allowed        igs_ps_unit_ofr_pat.waitlist_allowed%TYPE ;
839   l_waitlist_max            igs_ps_usec_lim_wlst.max_students_per_waitlist%TYPE;
840 
841 BEGIN
842 
843     --
844     -- Check whether permission to override enrollment maximum is Y or not
845     -- CLOSED_SECTION_OVR
846 
847     l_closed_section_ovr := validation_step_is_overridden (
848                               p_eligibility_step_type        => 'CLOSED_SECTION_OVR',
849                               p_load_cal_type                => p_load_cal_type,
850                               p_load_cal_seq_number          => p_load_ci_sequence_number,
851                               p_person_id                    => p_person_id,
852                               p_uoo_id                       => p_uoo_id,
853                               p_step_override_limit          => l_step_override_limit
854                             );
855     --
856     -- Check whether permission to override enrollment maximum is Y or not
857     -- WLST_MAX_OVR
858     --
859     l_wlst_max_ovr := validation_step_is_overridden (
860                         p_eligibility_step_type        => 'WLST_MAX_OVR',
861                         p_load_cal_type                => p_load_cal_type,
862                         p_load_cal_seq_number          => p_load_ci_sequence_number,
863                         p_person_id                    => p_person_id,
864                         p_uoo_id                       => p_uoo_id,
865                         p_step_override_limit          => l_step_override_limit
866                       );
867 
868     --
869     -- At the lowest level , waitlist allowed can be set at the Unit Section level . First check if waitlist has been
870     -- allowed at Unit Section Level . If waitlisting is not allowed , then check at the next level - Unit Offering.
871     -- If waitlisting is permitted at the Unit Offering level , return p_waitlist_ind = 'Y'
872     -- We are not checking the waitlist Allowed Indicator at Organization Unit level because this item is mandatory
873     -- at unit offering pattern level so no need to check beyond unit offering pattern level.
874 
875     -- As part of Waitlist Enhancements Build first we'll be checking whether waitlist is allowed at Institution
876     -- and Term Calender level. Check will be performed at Unit Section/Unit Offering level only if waitlist is
877     -- allowed at Institution and Term Calender level.
878 
879     l_waitlist_max := NULL;
880 
881     IF l_usec_partof_group = FALSE THEN
882       -- Check whether waitlisting is allowed at institution level - Bug# 3052426
883       OPEN c_wait_allow_inst_level;
884       FETCH c_wait_allow_inst_level INTO l_waitlist_allowed;
885       IF l_waitlist_allowed = 'Y' THEN
886          -- If allowed at institution level, check whether it is allowed at term calendar level - Bug# 3052426
887          OPEN c_wait_allow_term_cal(p_load_cal_type);
888          FETCH c_wait_allow_term_cal INTO l_waitlist_allowed;
889          IF l_waitlist_allowed = 'N' THEN
890             l_waitlist_allowed := 'N';
891          ELSE
892             -- Check at unit secion/unit offering level.
893             OPEN c_wait_allow_unit_section(p_uoo_id) ;
894             FETCH c_wait_allow_unit_section INTO   l_waitlist_allowed, l_waitlist_max ;
895             IF c_wait_allow_unit_section%NOTFOUND THEN
896                OPEN c_wait_allow_unit_offering(p_uoo_id) ;
897                FETCH c_wait_allow_unit_offering INTO   l_waitlist_allowed, l_waitlist_max ;
898                CLOSE c_wait_allow_unit_offering;
899             END IF;
900             CLOSE c_wait_allow_unit_section;
901          END IF;
902       ELSE
903          l_waitlist_allowed := 'N';
904       END IF;
905     ELSE
906       l_waitlist_allowed := 'N';
907     END IF;
908 
909     --
910     -- If it is determined that waitlist is not allowed at the Unit section and Unit offering level , then
911     -- no further validations need to be carried out NOCOPY . Else based on Waitlist limits it determines student can be waitlisted or not
912     --
913     IF l_waitlist_allowed ='N' THEN
914 
915         IF l_closed_section_ovr  THEN
916            -- Check actual enrollment value is less than the Enrollment Override Maximum
917                    -- If yes, user can Enroll into unit section
918           IF l_enrollment_actual < NVL(l_override_enrollment_max,999999)THEN
919              -- Student will be able to enroll since he/she has closed
920              -- section override and the override seats are still available
921             RETURN 'N';
922           END IF;
923         END IF;
924                 -- Student cannot Enroll,error message will be shown to the user
925         RETURN NULL;
926     ELSE -- Waitlist is allowed
927         IF l_closed_section_ovr  THEN
928             IF l_enrollment_actual < NVL(l_override_enrollment_max,999999)THEN
929                -- Student will be able to enroll since he/she has closed
930                -- section override and the override seats are still available
931                RETURN 'N';
932              END IF;
933         END IF;
934 
935         IF l_waitlist_actual >= NVL(l_waitlist_max,999999) THEN
936           IF l_wlst_max_ovr THEN
937             RETURN 'Y';
938           ELSE
939             -- Student cannot Enroll,error message will be shown to the user
940             RETURN NULL;
941           END IF;
942         ELSE
943           RETURN 'Y';
944         END IF;
945     END IF;     -- Waitlist allowed?.
946 END check_overrides_waitlist;
947 
948 BEGIN   -- get_usec_status
949 
950    l_usec_partof_group := FALSE;
951     --
952     -- Get the Program version
953     --
954     OPEN c_prg_ver;
955     FETCH c_prg_ver INTO l_version_number;
956     CLOSE c_prg_ver;
957 
958     -- Check whether the unit section belongs to any cross-listed group or not.
959     OPEN c_cross_listed(p_uoo_id);
960     FETCH c_cross_listed INTO l_cross_listed_row ;
961 
962     IF c_cross_listed%FOUND THEN
963          -- Get the maximum enrollment limit from the group level.
964         IF l_cross_listed_row.max_enr_group IS NULL THEN
965            l_usec_partof_group := FALSE;
966         ELSE
967           l_usec_partof_group := TRUE;
968           l_enrollment_maximum := l_cross_listed_row.max_enr_group;
969           l_override_enrollment_max := l_cross_listed_row.max_ovr_group;
970           -- Get the actual enrollment count of all the unit sections that belongs to the cross listed group.
971           OPEN c_actual_enr_crs_lst(l_cross_listed_row.usec_x_listed_group_id);
972           FETCH c_actual_enr_crs_lst INTO l_enrollment_actual;
973           CLOSE c_actual_enr_crs_lst;
974         END IF;
975 
976      ELSE
977 
978        OPEN c_meet_with_cls(p_uoo_id);
979        FETCH c_meet_with_cls INTO l_meet_with_cls_row ;
980 
981        IF c_meet_with_cls%FOUND THEN
982          -- Get the maximum enrollment limit from the group level.
983          IF l_meet_with_cls_row.max_enr_group IS NULL THEN
984            l_usec_partof_group := FALSE;
985          ELSE
986            l_usec_partof_group := TRUE;
987            l_enrollment_maximum := l_meet_with_cls_row.max_enr_group;
988            l_override_enrollment_max := l_meet_with_cls_row.max_ovr_group;
989            -- Get the actual enrollment count of all the unit sections that belongs to
990            -- the meet with class group.
991            OPEN c_actual_enr_meet_cls(l_meet_with_cls_row.class_meet_group_id);
992            FETCH c_actual_enr_meet_cls INTO l_enrollment_actual;
993            CLOSE c_actual_enr_meet_cls;
994          END IF;
995 
996        ELSE
997          l_usec_partof_group := FALSE;
998        END IF;
999        CLOSE c_meet_with_cls;
1000 
1001      END IF;
1002      CLOSE c_cross_listed;
1003 
1004      IF l_usec_partof_group = FALSE THEN
1005         -- If setup is not defined in the group level then get the maximum enrollment limit
1006         -- from the Unit Section level.
1007 
1008         OPEN c_unit_section_status (p_uoo_id);
1009         FETCH c_unit_section_status INTO p_unit_section_status,l_enrollment_actual, l_waitlist_actual,l_rsv_allowed;
1010         CLOSE c_unit_section_status;
1011         l_override_enrollment_max := NULL;
1012         l_enrollment_maximum      := NULL;
1013 
1014         -- Find the Override Enrollment Maximum at Unit Section Level.
1015         OPEN cur_usec_enr_max(p_uoo_id);
1016         FETCH cur_usec_enr_max INTO l_override_enrollment_max, l_enrollment_maximum;
1017         CLOSE cur_usec_enr_max;
1018 
1019         -- If not defined at Unit Section, then Fetch at Unit Level
1020         IF l_enrollment_maximum IS NULL THEN
1021           OPEN cur_unit_enr_max(p_uoo_id);
1022           FETCH cur_unit_enr_max INTO l_override_enrollment_max, l_enrollment_maximum;
1023           CLOSE cur_unit_enr_max;
1024         END IF;
1025 
1026      ELSE
1027 
1028        -- If setup is done in group level then get the unit section status and set
1029        -- the reserve allowed indicator to 'N'.
1030 
1031          l_rsv_allowed := 'N';
1032          OPEN c_unit_section_status (p_uoo_id);
1033          FETCH c_unit_section_status INTO l_unit_section_status;
1034          CLOSE c_unit_section_status;
1035              p_unit_section_status := l_unit_section_status.unit_section_status;
1036 
1037     END IF;
1038 
1039     -- Moved NVL check here as part of Bug# 2674875
1040     l_enrollment_actual := NVL(l_enrollment_actual,0) ;
1041     l_waitlist_actual   := NVL(l_waitlist_actual,0) ;
1042 
1043     -- Check whether seats are available in the unit section, if available then student can enroll into it
1044     -- subject to Reserved seating setup.
1045     --
1046 
1047        IF l_rsv_allowed = 'Y' THEN
1048            -- Before calling the Igs_En_Elgbl_Unit.eval_rsv_seat function,
1049            -- Check reserve seating validation is already done for this student unit attempt or not.
1050            -- If done then set p_waitlist_ind to 'N' else do the reserve seating validation.
1051            OPEN c_sua_rs(p_person_id,
1052                          p_course_cd,
1053                          p_uoo_id);
1054            FETCH c_sua_rs INTO l_rsv_seat_ext_id;
1055            IF c_sua_rs%FOUND THEN
1056               CLOSE c_sua_rs;
1057               p_waitlist_ind := 'N';
1058            ELSE
1059                    CLOSE c_sua_rs;
1060                    -- Get the Self service enrollment menthod type
1061                    -- call igs_en_gen_017.enrp_get_enr_method to decide enrollment method type
1062                    igs_en_gen_017.enrp_get_enr_method(
1063                        p_enr_method_type => l_enr_meth_type,
1064                        p_error_message   => l_message,
1065                        p_ret_status      => l_ret_status);
1066 
1067                    --
1068                    -- get the academic calendar of the given Load Calendar
1069                    --
1070                    l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
1071                                                                            p_cal_type                => p_load_cal_type,
1072                                                                            p_ci_sequence_number      => p_load_ci_sequence_number,
1073                                                                            p_acad_cal_type           => l_acad_cal_type,
1074                                                                            p_acad_ci_sequence_number => l_acad_ci_sequence_number,
1075                                                                            p_acad_ci_start_dt        => l_acad_start_dt,
1076                                                                            p_acad_ci_end_dt          => l_acad_end_dt,
1077                                                                            p_message_name            => l_message );
1078                    IF l_message IS NOT NULL THEN
1079                            -- As cannot show appropriate error message, just stopping to enroll/waitlist
1080                         p_waitlist_ind := NULL;
1081                         RETURN;
1082                    END IF;
1083                    l_enr_cat := Igs_En_Gen_003.enrp_get_enr_cat(
1084                                                                p_person_id,
1085                                                                p_course_cd,
1086                                                                l_acad_cal_type,
1087                                                                l_acad_ci_sequence_number,
1088                                                                NULL,
1089                                                                l_enr_cal_type,
1090                                                                l_enr_ci_seq,
1091                                                                l_enr_comm,
1092                                                                l_dummy);
1093                    IF l_enr_comm = 'BOTH' THEN
1094                       l_enr_comm :='ALL';
1095                    END IF;
1096                    -- getting the person type of logged in person
1097                    l_person_type := Igs_En_Gen_008.enrp_get_person_type(p_course_cd =>NULL);
1098                    -- getting the notification flag of reserve seat step
1099                    l_message := NULL;
1100                    l_notification_flag  := Igs_Ss_Enr_Details.get_notification(
1101                                                                                 p_person_type         => l_person_type,
1102                                                                                 p_enrollment_category => l_enr_cat,
1103                                                                                 p_comm_type           => l_enr_comm,
1104                                                                                 p_enr_method_type     => l_enr_meth_type,
1105                                                                                 p_step_group_type     => 'UNIT',
1106                                                                                 p_step_type           => 'RSV_SEAT',
1107                                                                                 p_person_id           => p_person_id,
1108                                                                                 p_message             => l_message
1109                                                                                );
1110                    -- modified the call to get_notification as part of SEVIS build.
1111                    -- if the get notification returns a message then stop the processing
1112                    IF l_message IS NOT NULL THEN
1113                       p_waitlist_ind := NULL;
1114                       RETURN;
1115                    END IF;
1116                    --
1117                    -- Check whether Reserve seating is allowed and Reserve seat Step is defined as DENY, If defined as WARN
1118                    -- no validation required, as Student can still enroll into the unit section.
1119                    --
1120                    IF NVL(l_notification_flag,'NULL') = 'DENY' THEN
1121 
1122                      -- setting save point to roll back any changes done by reserve seat validation function
1123                      -- i.e it increments the Actual Enrollment under reserve category if student satisfies any Priority/preference
1124                      -- this needs to be rolled back, as the same action will be done when reserve seating is validated in
1125                      -- Unit Step Evaluation.
1126                      SAVEPOINT rsv_check_start;
1127                      l_dummy := NULL;
1128                      l_return_val := Igs_En_Elgbl_Unit.eval_rsv_seat(
1129                                                                      p_person_id                => p_person_id,
1130                                                                      p_load_cal_type            => p_load_cal_type,
1131                                                                      p_load_sequence_number     => p_load_ci_sequence_number,
1132                                                                      p_uoo_id                   => p_uoo_id,
1133                                                                      p_course_cd                => p_course_cd,
1134                                                                      p_course_version           => l_version_number,
1135                                                                      p_message                  => l_dummy,
1136                                                                      p_deny_warn                => l_notification_flag,
1137                                                                      p_calling_obj              => 'JOB',
1138                                                                      p_deny_enrollment          => l_deny_enrollment
1139                                                                      );
1140                            -- Roll back all changes done by reserve seat validation function
1141                            ROLLBACK TO rsv_check_start;
1142                            IF l_return_val = FALSE THEN
1143                               -- check whether student has any Overrides, based on this determine whether
1144                               -- student can be enrolled,waitlisted or cant do both.
1145                               p_waitlist_ind := check_overrides_waitlist();
1146                               --check if seat is 100% reserved and student belongs to unreserved category
1147                               IF NVL(l_deny_enrollment,'N') = 'Y' THEN
1148                                      p_waitlist_ind := NULL;
1149                                      RETURN ;
1150                               END IF;
1151                             -- check whether student has any Overrides, based on this determine whether
1152                             -- student can be enrolled,waitlisted or cant do both.
1153                             p_waitlist_ind := check_overrides_waitlist();
1154 
1155 
1156                            ELSE
1157                               -- Student Can Enroll into the unit section
1158                               p_waitlist_ind := 'N';
1159                            END IF;
1160                    ELSE
1161                      -- either Step is not defined or notification flag is not DENY.So Student Can Enroll into the unit section
1162                      p_waitlist_ind := 'N';
1163                    END IF; -- l_notification_flag
1164            END IF; --c_sua_rs%FOUND
1165        ELSE -- Reserve seat is not allowed
1166          p_waitlist_ind := 'N';
1167        END IF; --l_rsv_allowed
1168     IF l_enrollment_actual >= NVL(l_enrollment_maximum,999999) THEN
1169 
1170 
1171                 -- check whether student has any Overrides, based on this determine whether
1172                 -- student can be enrolled,waitlisted or cant do both.
1173                 p_waitlist_ind := check_overrides_waitlist();
1174 
1175    END IF; -- l_enrollment_actual >= l_enrollment_maximum
1176 
1177 
1178   END get_usec_status;
1179   --
1180   --
1181   --  Procedure to get the Academic Calendar and Academic Calenar Sequence Number.
1182   --
1183   --
1184   PROCEDURE get_academic_cal
1185   (
1186     p_person_id                       IN     NUMBER,
1187     p_course_cd                       IN     VARCHAR2,
1188     p_acad_cal_type                  OUT NOCOPY     VARCHAR2,
1189     p_acad_ci_sequence_number        OUT NOCOPY     NUMBER,
1190     p_message                        OUT NOCOPY     VARCHAR2,
1191     p_effective_dt                   IN      DATE
1192   ) AS
1193     --
1194     --  Parameters Description:
1195     --
1196     --  p_person_id                     -> Person Identifier
1197     --  p_course_cd                     -> Program code
1198     --  p_acad_cal_type                 -> Out NOCOPY parameter carrying the academic calendar type
1199     --  p_acad_ci_sequence_number       -> Out NOCOPY parameter carrying academic calendar sequence number
1200     --
1201     --
1202     --  local variable used in the program unit
1203     --
1204     NO_SECC_RECORD_FOUND              EXCEPTION;
1205     cst_active                        CONSTANT VARCHAR2(10) := 'ACTIVE';
1206     cst_load                          CONSTANT VARCHAR2(10) := 'LOAD';
1207     cst_academic                      CONSTANT VARCHAR2(10) := 'ACADEMIC';
1208     l_daiv_rec_found                  BOOLEAN;
1209     l_cal_type                        igs_en_stdnt_ps_att.cal_type%TYPE;
1210     l_load_effect_dt_alias            igs_en_cal_conf.load_effect_dt_alias%TYPE;
1211     l_current_load_cal_type           igs_ca_inst.cal_type%TYPE;
1212     l_current_load_sequence_number    igs_ca_inst.sequence_number%TYPE;
1213     l_current_acad_cal_type           igs_ca_inst.cal_type%TYPE;
1214     l_current_acad_sequence_number    igs_ca_inst.sequence_number%TYPE;
1215     l_other_detail                    VARCHAR2(255);
1216     l_effective_dt                    DATE;
1217     --
1218     --  Cursor to fetch student course attempt calendar type
1219     --
1220     CURSOR c_stu_crs_atmpt (cp_person_id     igs_en_stdnt_ps_att.person_id%TYPE,
1221                             cp_course_cd     igs_en_stdnt_ps_att.course_cd%TYPE) IS
1222       SELECT  sca.cal_type
1223       FROM    igs_en_stdnt_ps_att sca
1224       WHERE   sca.person_id = cp_person_id
1225       AND     sca.course_cd = cp_course_cd;
1226     --
1227     --  Cursor to fetch load effective date alias.
1228     --
1229     CURSOR c_s_enr_cal_conf IS
1230       SELECT  secc.load_effect_dt_alias
1231       FROM    igs_en_cal_conf secc
1232       WHERE   secc.s_control_num = 1;
1233     --
1234     --  Cursor to fetch calendar instances
1235     --
1236     CURSOR c_cal_instance (cp_cal_type      igs_ca_inst.cal_type%TYPE,
1237                            cp_effective_dt  igs_ca_inst.start_dt%TYPE) IS
1238       SELECT   ci.cal_type,
1239                ci.sequence_number
1240       FROM     igs_ca_inst ci,
1241                igs_ca_stat cs
1242       WHERE    ci.cal_type = cp_cal_type
1243       AND      ci.start_dt <= cp_effective_dt
1244       AND      ci.end_dt >= cp_effective_dt
1245       AND      cs.cal_status = ci.cal_status
1246       AND      cs.s_cal_status = cst_active
1247       ORDER BY ci.start_dt DESC;
1248     --
1249     --  Cursor to fetch calendar type instances
1250     --
1251     CURSOR c_cal_type_instance (cp_cal_type         igs_ca_inst.cal_type%TYPE,
1252                                 cp_sequence_number  igs_ca_inst.sequence_number%TYPE) IS
1253       SELECT   ci.cal_type,
1254                ci.sequence_number,
1255                ci.start_dt,
1256                ci.end_dt
1257       FROM     igs_ca_type ct,
1258                igs_ca_inst ci,
1259                igs_ca_stat cs,
1260                igs_ca_inst_rel cir
1261       WHERE    ct.closed_ind = 'N'
1262       AND      cs.s_cal_status = cst_active
1263       AND      ci.cal_status = cs.cal_status
1264       AND      ct.s_cal_cat = cst_load
1265       AND      ci.cal_type = ct.cal_type
1266       AND      cir.sub_cal_type = ci.cal_type
1267       AND      cir.sub_ci_sequence_number =ci.sequence_number
1268       AND      cir.sup_cal_type = cp_cal_type
1269       AND      cir.sup_ci_sequence_number = cp_sequence_number
1270       AND EXISTS ( SELECT   1     FROM     igs_ca_inst_rel cir,
1271                                                 igs_ca_type ct
1272                                        WHERE    cir.sup_cal_type = cp_cal_type
1273                                        AND      cir.sup_ci_sequence_number = cp_sequence_number
1274                                        AND      cir.sub_cal_type = ci.cal_type
1275                                        AND      cir.sub_ci_sequence_number = ci.sequence_number
1276                                        AND      ct.cal_type = cir.sup_cal_type
1277                                        AND      ct.s_cal_cat = cst_academic)
1278      ORDER BY ci.start_dt DESC;
1279     --
1280     --  Cursor to fetch the date alias
1281     --
1282     CURSOR c_dai_v (cp_cal_type             igs_ca_da_inst_v.cal_type%TYPE,
1283                     cp_ci_sequence_number   igs_ca_da_inst_v.ci_sequence_number%TYPE,
1284                     cp_load_effect_dt_alias igs_en_cal_conf.load_effect_dt_alias%TYPE) IS
1285       SELECT   daiv.alias_val
1286       FROM     igs_ca_da_inst_v daiv
1287       WHERE    daiv.cal_type = cp_cal_type
1288       AND      daiv.ci_sequence_number = cp_ci_sequence_number
1289       AND      daiv.dt_alias = cp_load_effect_dt_alias;
1290   --
1291   BEGIN
1292 
1293     -- This statement is added in ENCR015 build ( Bug ID : 2158654)
1294     -- Initialize the l_effective_date with the Effective Date Value passed to this Procedure as Parameter
1295     l_effective_dt := p_effective_dt;
1296 
1297     --
1298     --  The attendance type is derived based on the load calendar instances, using
1299     --  the load effective date alias as the reference point for determining
1300     --  which calendar is the current load_calendar.
1301     --  Load the student IGS_PS_COURSE attempt details.
1302     --
1303     OPEN c_stu_crs_atmpt (p_person_id,
1304                           p_course_cd);
1305     FETCH c_stu_crs_atmpt INTO l_cal_type;
1306     IF (c_stu_crs_atmpt%NOTFOUND) THEN
1307        --
1308        -- if not data found return from the program unit
1309        --
1310        CLOSE c_stu_crs_atmpt;
1311        p_message := 'IGS_EN_NO_CRS_ATMPT';
1312        RETURN;
1313     END IF;
1314     CLOSE c_stu_crs_atmpt;
1315     --
1316     -- Cetermine the 'current' load calendar instance based on the load effective
1317     -- date alias from the enrolment calendar configuration. If this date alias
1318     -- can't be located then the latest calendar instance where start_dt/end_dt
1319     -- encompass the effective dt is deemed current
1320     --
1321     OPEN c_s_enr_cal_conf;
1322     FETCH c_s_enr_cal_conf INTO l_load_effect_dt_alias;
1323     IF c_s_enr_cal_conf%NOTFOUND THEN
1324        CLOSE c_s_enr_cal_conf;
1325        p_message := 'IGS_EN_NO_SECC_REC_FOUND';
1326        RETURN;
1327     END IF;
1328     CLOSE c_s_enr_cal_conf;
1329     --
1330     -- initialise the local variables
1331     --
1332     l_current_load_cal_type := NULL;
1333     l_current_load_sequence_number := NULL;
1334     l_current_acad_cal_type := NULL;
1335     l_current_acad_sequence_number := NULL;
1336     --
1337     -- loop through the records fetched for calendar instances
1338     --
1339     FOR rec_cal_instance IN c_cal_instance (l_cal_type, l_effective_dt)
1340     LOOP
1341         --
1342         -- now loop through the cal type instance records
1343         --
1344         FOR rec_cal_type_instance IN c_cal_type_instance (rec_cal_instance.cal_type,
1345                                                           rec_cal_instance.sequence_number)
1346         LOOP
1347             --
1348             -- Attempt to find load effective date alias against the cale
1349             --
1350             l_daiv_rec_found := FALSE;
1351             FOR rec_dai_v IN c_dai_v (rec_cal_type_instance.cal_type,
1352                                       rec_cal_type_instance.sequence_number,
1353                                       l_load_effect_dt_alias)
1354             LOOP
1355                 l_daiv_rec_found := TRUE;
1356                 IF (l_effective_dt >= rec_dai_v.alias_val) THEN
1357                     l_current_load_cal_type := rec_cal_type_instance.cal_type ;
1358                     l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
1359                     l_current_acad_cal_type := rec_cal_instance.cal_type;
1360                     l_current_acad_sequence_number := rec_cal_instance.sequence_number;
1361                 END IF;
1362             END LOOP;
1363             IF NOT l_daiv_rec_found  THEN
1364                IF (l_effective_dt >= rec_cal_type_instance.start_dt) AND
1365                    (l_effective_dt <= rec_cal_type_instance.end_dt) THEN
1366                     l_current_load_cal_type := rec_cal_type_instance.cal_type ;
1367                     l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
1368                     l_current_acad_cal_type := rec_cal_instance.cal_type;
1369                     l_current_acad_sequence_number := rec_cal_instance.sequence_number;
1370                END IF;
1371             END IF;
1372         END LOOP;
1373         IF l_current_load_cal_type IS NOT NULL THEN
1374            EXIT;
1375         END IF;
1376     END LOOP;
1377     IF l_current_load_cal_type IS NULL THEN
1378        p_acad_cal_type := NULL;
1379     END IF;
1380     p_acad_cal_type := l_current_acad_cal_type;
1381     p_acad_ci_sequence_number := l_current_acad_sequence_number;
1382     p_message := NULL;
1383   END get_academic_cal;
1384   --
1385   --
1386   -- This Function Validate whether given student completed the specified Program Stage
1387   -- by calling the function igs_pr_clc_stdnt_comp, which will insert the result rule status
1388   -- into the table igs_pr_s_scratch_pad.
1389   -- based on the rule status this function will return TRUE or FALSE
1390   --
1391   --
1392   FUNCTION enrp_val_ps_stage (
1393     p_person_id IGS_EN_SU_ATTEMPT.person_id%TYPE,
1394     p_course_cd IGS_EN_SU_ATTEMPT.course_cd%TYPE,
1395     p_version_number NUMBER,
1396     p_preference_code VARCHAR2
1397   ) RETURN BOOLEAN AS
1398     --
1399     CURSOR cur_seq_num IS
1400     SELECT sequence_number
1401     FROM  igs_ps_stage
1402     WHERE course_cd = p_course_cd AND
1403           version_number = p_version_number AND
1404           course_stage_type = p_preference_code
1405     ORDER BY sequence_number;
1406     --
1407     CURSOR cur_crs_stg_result (cp_creation_dt DATE,cp_key_1 VARCHAR2,cp_key_2 VARCHAR2,cp_key_3 VARCHAR2,
1408                                         cp_key_4 VARCHAR2,cp_key_5 VARCHAR2,cp_key_6 VARCHAR2) IS
1409      SELECT     text_1
1410      FROM       igs_pr_s_scratch_pad_v
1411      WHERE      creation_dt     = cp_creation_dt AND
1412             (cp_key_1   IS NULL OR
1413             key_1               = cp_key_1)     AND
1414             (cp_key_2   IS NULL OR
1415             key_2               = cp_key_2)     AND
1416             (cp_key_3   IS NULL OR
1417             key_3               = cp_key_3)     AND
1418            (cp_key_4    IS NULL OR
1419            key_4                = cp_key_4)     AND
1420            (cp_key_5    IS NULL OR
1421            key_5                = cp_key_5)     AND
1422            (cp_key_6    IS NULL OR
1423            key_6                = cp_key_6);
1424     --
1425     l_cur_seq_num igs_ps_stage.sequence_number%TYPE;
1426     lv_message_name VARCHAR2(30);
1427     l_crs_stg_result_rec igs_pr_s_scratch_pad_v.text_1%TYPE;
1428     lv_log_dt DATE;
1429     --
1430   BEGIN
1431     OPEN cur_seq_num;
1432     FETCH cur_seq_num INTO l_cur_seq_num;
1433     IF cur_seq_num%FOUND THEN
1434            --
1435            -- validate the completion of given Program stage for the given student.
1436            -- this function will create a record in igs_pr_s_scratch_pad with the rule status
1437          IF igs_pr_gen_005.igs_pr_clc_stdnt_comp(p_person_id,
1438                                                p_course_cd,
1439                                                p_version_number,
1440                                                p_course_cd,
1441                                                p_version_number,
1442                                                NULL,
1443                                                NULL,
1444                                                l_cur_seq_num,
1445                                                'N',
1446                                                'STG-COMP',
1447                                                'PRGF9030'||'|'||p_person_id||'|'||p_course_cd||'|'||l_cur_seq_num,
1448                                                'Y',
1449                                                lv_log_dt,
1450                                                lv_message_name
1451                                               ) THEN
1452                         --
1453                         -- check the rule status created by the above function, whether the given Program stage is completed..
1454                         OPEN cur_crs_stg_result(lv_log_dt,'PRGF9030',p_person_id,p_course_cd,l_cur_seq_num,'STG-COMP','RULE_STATUS');
1455                         FETCH cur_crs_stg_result INTO l_crs_stg_result_rec;
1456                         CLOSE cur_crs_stg_result;
1457               --
1458               IF l_crs_stg_result_rec = 'COURSE STAGE COMPLETION RULES SATISFIED' THEN
1459                           -- Student satisfied/completed the given program stage.
1460                 RETURN TRUE;
1461               ELSE
1462                 RETURN FALSE;
1463               END IF;
1464          END IF;
1465    END IF;
1466    CLOSE cur_seq_num;
1467    RETURN FALSE;
1468   END enrp_val_ps_stage;
1469   --
1470 --
1471 -- Added as part of ENCR013
1472 FUNCTION enrp_get_appr_cr_pt(
1473     p_person_id IN IGS_EN_SU_ATTEMPT.person_id%TYPE,
1474     p_uoo_id IN IGS_EN_SU_ATTEMPT.uoo_id%TYPE
1475 ) RETURN NUMBER AS
1476  /******************************************************************
1477   Created By        : knaraset
1478   Date Created By   : 12-Nov-2001
1479   Purpose           : This Function returns Approved Credit Points if exists for student in override table
1480   Known limitations,
1481   enhancements,
1482   remarks            : As part of ENCR013
1483   Change History
1484   Who         When        What
1485   knaraset   04-Feb-03   Modified the cursors cur_unit_appr_cp and cur_term_appr_cp to add extra condition
1486                          of checking NULL for Unit Section , Unit version, so that when the override is
1487                          created for a particular Unit version it won't consider for other units.bug 2783365
1488  svenkata    6-Jun-2003  Modified the routine to check for Approved Credit points at the Unit section level. If overrides do not exist at Unit
1489                          section level , check if one exists at Unit level - First for Teach and then for Load Cal.Deny / Warn build - Bug : 2829272.
1490   ******************************************************************/
1491 -- cursor to get Unit details for the Uoo_Id passed as parameter
1492   CURSOR cur_unit_dtl IS
1493   SELECT unit_cd,
1494          version_number,
1495                  cal_type,
1496                  ci_sequence_number
1497   FROM IGS_PS_UNIT_OFR_OPT
1498   WHERE uoo_id = p_uoo_id;
1499 
1500 -- Cursor to get the Load Calendar of the given Teach Calendar.
1501   CURSOR cur_load_dtl_of_uoo_id (p_cal_type IGS_CA_TYPE.cal_type%TYPE , p_ci_sequence_number IGS_CA_INST.sequence_number%TYPE ) IS
1502     SELECT   load_cal_type,
1503              load_ci_sequence_number
1504     FROM     igs_ca_teach_to_load_v
1505     WHERE    teach_cal_type = p_cal_type
1506     AND      teach_ci_Sequence_number = p_ci_sequence_number ;
1507 
1508 
1509   --
1510   -- cursor to get the Approved credit points defined at Unit Section level for the given Calendar.
1511   --
1512    CURSOR cur_uoo_appr_cp (cp_cal_type VARCHAR2, cp_sequence_number NUMBER) IS
1513    SELECT eou.step_override_limit
1514    FROM igs_en_elgb_ovr_step eos,
1515         igs_en_elgb_ovr eo ,
1516         igs_en_elgb_ovr_uoo eou
1517    WHERE eos.step_override_type = 'VAR_CREDIT_APPROVAL' AND
1518          eos.elgb_override_id = eo.elgb_override_id AND
1519          eo.person_id = p_person_id AND
1520          eo.cal_type = cp_cal_type AND
1521          eo.ci_sequence_number = cp_sequence_number AND
1522          eos.elgb_ovr_step_id = eou.elgb_ovr_step_id AND
1523          eou.uoo_id = p_uoo_id ;
1524 
1525   --
1526   -- cursor to get the Approved credit points defined at Unit level.
1527   --
1528    CURSOR cur_unit_appr_cp(cp_unit_cd VARCHAR2, cp_version_number NUMBER, cp_cal_type VARCHAR2, cp_sequence_number NUMBER , cp_uoo_id NUMBER) IS
1529    SELECT eou.step_override_limit
1530    FROM igs_en_elgb_ovr_step eos,
1531         igs_en_elgb_ovr eo ,
1532         igs_en_elgb_ovr_uoo eou
1533    WHERE eos.step_override_type = 'VAR_CREDIT_APPROVAL' AND
1534          eos.ELGB_OVERRIDE_ID = eo.ELGB_OVERRIDE_ID AND
1535          eo.person_id = p_person_id AND
1536          eou.unit_cd = cp_unit_cd AND
1537          eou.version_number = cp_version_number AND
1538          ( eou.uoo_id IS NULL OR eou.uoo_id = -1 ) AND
1539          eos.elgb_ovr_step_id = eou.elgb_ovr_step_id AND
1540          eo.CAL_TYPE = cp_cal_type AND
1541          eo.CI_SEQUENCE_NUMBER = cp_sequence_number ;
1542 
1543    l_unit_dtl cur_unit_dtl%ROWTYPE;
1544    l_appr_cp igs_en_elgb_ovr_step.step_override_limit%TYPE := NULL;
1545    l_load_dtl_of_uoo_id cur_load_dtl_of_uoo_id%ROWTYPE;
1546 
1547 BEGIN
1548 
1549   --
1550   -- Get the Unit Details
1551   OPEN cur_unit_dtl;
1552   FETCH cur_unit_dtl INTO l_unit_dtl;
1553   CLOSE cur_unit_dtl;
1554 
1555   --
1556   -- Get Approved Credit points defined at Unit Section level for Teach Calendar
1557   OPEN cur_uoo_appr_cp(l_unit_dtl.cal_type ,l_unit_dtl.ci_sequence_number);
1558   FETCH cur_uoo_appr_cp INTO l_appr_cp;
1559   IF cur_uoo_appr_cp%FOUND THEN
1560         CLOSE cur_uoo_appr_cp;
1561         RETURN l_appr_cp;
1562   END IF ;
1563   CLOSE cur_uoo_appr_cp;
1564 
1565   --
1566   -- Get Approved Credit points defined at Unit level for Teach Calendar
1567   OPEN cur_unit_appr_cp(l_unit_dtl.unit_cd, l_unit_dtl.version_number ,l_unit_dtl.cal_type ,l_unit_dtl.ci_sequence_number , p_uoo_id );
1568   FETCH cur_unit_appr_cp INTO l_appr_cp;
1569   IF cur_unit_appr_cp%FOUND THEN
1570         CLOSE cur_unit_appr_cp;
1571         RETURN l_appr_cp;
1572   END IF;
1573   CLOSE cur_unit_appr_cp;
1574 
1575   --Get the Load Calendar Details if the Override is not defined at the Load Calendar level.
1576     FOR l_load_dtl_of_uoo_id IN cur_load_dtl_of_uoo_id( l_unit_dtl.cal_type ,l_unit_dtl.ci_sequence_number)
1577   LOOP
1578   --
1579   -- Get Approved Credit points defined at Unit Section level for load Calendar
1580   OPEN cur_uoo_appr_cp(l_load_dtl_of_uoo_id.load_cal_type ,l_load_dtl_of_uoo_id.load_ci_sequence_number);
1581   FETCH cur_uoo_appr_cp INTO l_appr_cp;
1582   IF cur_uoo_appr_cp%FOUND THEN
1583         CLOSE cur_uoo_appr_cp;
1584         RETURN l_appr_cp;
1585   END IF ;
1586   CLOSE cur_uoo_appr_cp;
1587 
1588   END LOOP;
1589 
1590   --
1591   -- Get Approved Credit points defined at Unit level for Load Calendar
1592   OPEN cur_unit_appr_cp(l_unit_dtl.unit_cd, l_unit_dtl.version_number ,l_load_dtl_of_uoo_id.load_cal_type ,l_load_dtl_of_uoo_id.load_ci_sequence_number , p_uoo_id);
1593   FETCH cur_unit_appr_cp INTO l_appr_cp;
1594   IF cur_unit_appr_cp%FOUND THEN
1595         CLOSE cur_unit_appr_cp;
1596         RETURN l_appr_cp;
1597   END IF ;
1598 
1599   CLOSE cur_unit_appr_cp;
1600   RETURN l_appr_cp;
1601 
1602   END enrp_get_appr_cr_pt;
1603 
1604   FUNCTION enrf_drv_cmpl_dt (
1605     p_person_id         IN      NUMBER,
1606     p_course_cd         IN      VARCHAR2,
1607     p_achieved_cp       IN      NUMBER      ,
1608     p_attendance_type   IN      VARCHAR2    ,
1609     p_load_cal_type     IN      VARCHAR2    ,
1610     p_load_ci_seq_num   IN      NUMBER      ,
1611     p_load_ci_alt_code  IN      VARCHAR2    ,
1612     p_load_ci_start_dt  IN      DATE        ,
1613     p_load_ci_end_dt    IN      DATE        ,
1614     p_message_name      OUT NOCOPY     VARCHAR2
1615     )  RETURN DATE AS
1616   /*
1617   ||  Created By : ayedubat(Anji Babu)
1618   ||  Created On : 20-DEC-2001 ( As part of ENCR015 DLD)
1619   ||  Purpose : To Caluculate the Derived Completion Date of a Student Program Attempt
1620   ||  Known limitations, enhancements or remarks :
1621   ||  Change History :
1622   ||  Who             When            What
1623   ||  svanukur         10-MAY-2004    added the check to call igs_en_gen_015.enrp_get_eff_load_ci only if
1624   ||                                   a history record is found. BUG 3597429
1625   ||  (reverse chronological order - newest change first)
1626   */
1627 
1628   -- Local Variables
1629 
1630   l_achieved_cp      NUMBER;
1631   l_attendance_type      igs_en_stdnt_ps_att_all.attendance_type%TYPE;
1632   l_load_cal_type          igs_ca_inst.cal_type%TYPE;
1633   l_load_ci_seq_num      igs_ca_inst.sequence_number%TYPE;
1634   l_load_ci_alt_code igs_ca_inst.alternate_code%TYPE;
1635   l_load_ci_start_dt igs_ca_inst.start_dt%TYPE;
1636   l_load_ci_end_dt   igs_ca_inst.end_dt%TYPE;
1637   l_acad_cal_type    igs_ca_inst.cal_type%TYPE;
1638   l_acad_ci_seq_num      igs_ca_inst.sequence_number%TYPE;
1639   l_cmpl_dt          igs_en_stdnt_ps_att_all.override_cmpl_dt%TYPE;
1640   l_init_dt          DATE := NULL;
1641   l_init_load_cal_type     igs_ca_inst.cal_type%TYPE;
1642   l_init_load_ci_seq_num         igs_ca_inst.sequence_number%TYPE;
1643   l_init_load_ci_alt_code  igs_ca_inst.alternate_code%TYPE;
1644   l_init_load_ci_start_dt  igs_ca_inst.start_dt%TYPE;
1645   l_init_load_ci_end_dt    igs_ca_inst.end_dt%TYPE;
1646   l_message_name     VARCHAR2(30) := NULL;
1647   l_cst_enrolled VARCHAR2(10) ;
1648 
1649 
1650   -- Cursor to find the Start Date and End Date of a Calendar Instance
1651   CURSOR cur_ca_inst ( p_load_cal_type   igs_ca_inst.cal_type%TYPE,
1652                        p_load_ci_seq_num igs_ca_inst.sequence_number%TYPE) IS
1653     SELECT alternate_code, start_dt, end_dt
1654     FROM   IGS_CA_INST
1655     WHERE  cal_type        = p_load_cal_type
1656     AND    sequence_number = p_load_ci_seq_num ;
1657   cur_ca_inst_rec cur_ca_inst%ROWTYPE;
1658 
1659 
1660   -- Cursor find the Date at which the Student Program Attempt became 'ACTIVE'
1661   CURSOR cur_sca_active_dt( p_person_id igs_as_sc_attempt_h_all.person_id%TYPE,
1662                             p_course_cd igs_as_sc_attempt_h_all.course_cd%TYPE ) IS
1663     SELECT NVL(SCAH1.hist_start_dt,SCA1.last_update_date)  hist_start_dt
1664     FROM IGS_AS_SC_ATTEMPT_H scah1,  IGS_EN_STDNT_PS_ATT_ALL SCA1
1665    WHERE SCA1.person_id = SCAH1.person_id(+)
1666     AND  SCA1.course_cd =  SCAH1.course_cd(+)
1667     AND  SCA1.person_id = p_person_id
1668     AND  SCA1.course_cd = p_course_cd
1669     AND  SUBSTR( NVL(SCAH1.course_attempt_status, NVL(IGS_AU_GEN_003.audp_get_scah_col('COURSE_ATTEMPT_STATUS',SCAH1.person_id,
1670      SCAH1.course_cd,SCAH1.hist_end_dt), SCA1.course_attempt_status)),1,10) = l_cst_enrolled
1671     ORDER BY NVL(SCAH1.hist_start_dt,SCA1.last_update_date);
1672 
1673 
1674   --  Cursor to fetch student course attempt calendar type
1675   CURSOR cur_stu_crs_atmpt (cp_person_id     igs_en_stdnt_ps_att.person_id%TYPE,
1676                             cp_course_cd     igs_en_stdnt_ps_att.course_cd%TYPE) IS
1677     SELECT  sca.cal_type
1678     FROM    igs_en_stdnt_ps_att sca
1679     WHERE   sca.person_id = cp_person_id
1680     AND     sca.course_cd = cp_course_cd;
1681   l_cal_type igs_ca_inst.cal_type%TYPE;
1682 
1683   BEGIN
1684     --Assigning due to gscc warnings
1685     l_cst_enrolled := 'ENROLLED';
1686 
1687     -- Assign the parameter values to local variables
1688 
1689     l_achieved_cp        :=  p_achieved_cp;
1690     l_attendance_type    :=  p_attendance_type;
1691     l_load_cal_type      :=  p_load_cal_type;
1692     l_load_ci_seq_num    :=  p_load_ci_seq_num;
1693     l_load_ci_alt_code   :=  p_load_ci_alt_code;
1694     l_load_ci_start_dt   :=  p_load_ci_start_dt;
1695     l_load_ci_end_dt     :=  p_load_ci_end_dt;
1696 
1697     -- Check , weather the Student Program Attempt exists or not
1698     OPEN cur_stu_crs_atmpt (p_person_id,
1699                             p_course_cd);
1700     FETCH cur_stu_crs_atmpt INTO l_cal_type;
1701     IF (cur_stu_crs_atmpt%NOTFOUND) THEN
1702       --
1703       -- if nt data found return from the program unit
1704       --
1705       CLOSE cur_stu_crs_atmpt;
1706       p_message_name := 'IGS_EN_NO_CRS_ATMPT';
1707       RETURN NULL;
1708 
1709     END IF;
1710     CLOSE cur_stu_crs_atmpt;
1711 
1712     --
1713     -- If the Load Cal Type Passed to the function is Null,
1714     -- Then Caluculate Load Calendar Instance for the current Acdemic Calendar of the Student Program Attempt
1715     --
1716 
1717     IF l_load_cal_type IS NULL OR l_load_ci_seq_num IS NULL THEN
1718 
1719       igs_en_gen_015.enrp_get_eff_load_ci (
1720         p_person_id,
1721         p_course_cd,
1722         SYSDATE,
1723         l_acad_cal_type,        -- value returned by GET_ACADEMIC_CAL
1724         l_acad_ci_seq_num,      -- value returned by GET_ACADEMIC_CAL
1725         l_load_cal_type,        -- OUT NOCOPY parameter
1726         l_load_ci_seq_num,      -- OUT NOCOPY Parameter
1727         l_load_ci_alt_code,     -- OUT NOCOPY Parameter
1728         l_load_ci_start_dt,     -- OUT NOCOPY Parameter
1729         l_load_ci_end_dt,       -- OUT NOCOPY Parameter
1730         l_message_name          -- OUT NOCOPY Parameter
1731       );
1732 
1733       -- If the load calendar returned is null then return the function with NULL after assigning
1734       -- IGS_EN_LOAD_CAL_NOT_FOUND to p_message_name
1735 
1736       IF l_load_cal_type IS NULL OR l_load_ci_seq_num IS NULL THEN
1737 
1738          p_message_name := 'IGS_EN_LOAD_CAL_NOT_FOUND' ;
1739          RETURN NULL;
1740 
1741       END IF;
1742 
1743     END IF;
1744 
1745     --
1746     -- If the Achieved Credit Points is passed as NULL
1747     -- Then call the API IGS_EN_GEN_001.ENRP_CLC_SCA_PASS_CP to get the Credit Points
1748     --
1749 
1750     IF l_achieved_cp IS NULL THEN
1751 
1752       l_achieved_cp := igs_en_gen_001.enrp_clc_sca_pass_cp (
1753                          p_person_id,
1754                          p_course_cd,
1755                          SYSDATE
1756                        );
1757     END IF;
1758 
1759     --
1760     -- If the Attendance Type is passed as NULL
1761     -- Then call IGS_EN_GEN_006.ENRP_GET_SCA_LATT as follows
1762     --
1763 
1764     IF l_attendance_type IS NULL THEN
1765 
1766     -- Changed the call to the procedure from IGS_EN_GEN_006.ENRP_GET_SCA_ATT to
1767     -- IGS_EN_GEN_006.ENRP_GET_SCA_LATT. Changes as per bug# 2370100
1768 
1769        l_attendance_type  := igs_en_gen_006.enrp_get_sca_latt(
1770                               p_person_id,
1771                               p_course_cd,
1772                               p_load_cal_type ,
1773                               p_load_ci_seq_num
1774                              );
1775 
1776     END IF;
1777 
1778     /***   Find the initial term of enrollment, i.e. the Term Calendar during which the program attempt became 'ACTIVE'  ***/
1779 
1780     --  First find out NOCOPY when the program attempt became ACTIVE.
1781     --  To do this look at the history table, order the records starting with the oldest history and
1782     --  see when (the last update date column) the status changed to 'ENROLLED' from something else.
1783     --  Let as call the date found in this step as L_INIT_DT
1784 
1785     OPEN cur_sca_active_dt ( p_person_id, p_course_cd );
1786     FETCH cur_sca_active_dt INTO l_init_dt;
1787     CLOSE cur_sca_active_dt;
1788 
1789    --fetch the load calendar details only if a history record is found
1790 
1791      IF l_init_dt IS NOT NULL THEN
1792        igs_en_gen_015.enrp_get_eff_load_ci (
1793         p_person_id,
1794         p_course_cd,
1795         l_init_dt,
1796         l_acad_cal_type,        -- value returned by GET_ACADEMIC_CAL
1797         l_acad_ci_seq_num,      -- value returned by GET_ACADEMIC_CAL
1798         l_init_load_cal_type,        -- OUT NOCOPY parameter
1799         l_init_load_ci_seq_num,      -- OUT NOCOPY Parameter
1800         l_init_load_ci_alt_code,     -- OUT NOCOPY Parameter
1801         l_init_load_ci_start_dt,     -- OUT NOCOPY Parameter
1802         l_init_load_ci_end_dt,       -- OUT NOCOPY Parameter
1803         l_message_name               -- OUT NOCOPY Parameter
1804       );
1805 
1806 
1807     -- If the load calendar returned is null then return the function with NULL after assigning
1808     -- IGS_EN_LOAD_CAL_NOT_FOUND to p_message_name
1809 
1810      IF l_init_load_cal_type IS NULL OR l_init_load_ci_seq_num IS NULL THEN
1811        p_message_name := 'IGS_EN_LOAD_CAL_NOT_FOUND' ;
1812        RETURN NULL;
1813 
1814      END IF;
1815 
1816      -- Find the start date and end date for the INIT load calendar
1817 
1818      OPEN cur_ca_inst( l_init_load_cal_type , l_init_load_ci_seq_num);
1819      FETCH cur_ca_inst INTO cur_ca_inst_rec;
1820      CLOSE cur_ca_inst;
1821 
1822      l_init_load_ci_start_dt := cur_ca_inst_rec.start_dt;
1823      l_init_load_ci_end_dt   := cur_ca_inst_rec.end_dt;
1824 
1825     -- Call the User Hook IGS_EN_RPT_PRC_UHK.ENRF_DRV_CMPL_DT_UHK. The call to the function should be as follows
1826 
1827     l_cmpl_dt := igs_en_rpt_prc_uhk.enrf_drv_cmpl_dt_uhk (
1828                    p_person_id,
1829                    p_course_cd,
1830                    l_achieved_cp,
1831                    l_attendance_type,
1832                    l_load_cal_type,
1833                    l_load_ci_seq_num,
1834                    l_load_ci_alt_code,
1835                    l_load_ci_start_dt,
1836                    l_load_ci_end_dt,
1837                    l_init_load_cal_type,
1838                    l_init_load_ci_seq_num,
1839                    l_init_load_ci_alt_code,
1840                    l_init_load_ci_start_dt,
1841                    l_init_load_ci_end_dt
1842                  );
1843 
1844     RETURN l_cmpl_dt;
1845   END IF;
1846    RETURN NULL;
1847 
1848   EXCEPTION
1849     WHEN OTHERS THEN
1850         fnd_message.Set_Name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1851         fnd_message.Set_Token('NAME','IGS_EN_GEN_015.enrf_drv_cmpl_dt');
1852         IGS_GE_MSG_STACK.ADD;
1853         App_Exception.Raise_Exception;
1854 
1855   END enrf_drv_cmpl_dt;
1856 
1857   PROCEDURE enrp_get_eff_load_ci (
1858     p_person_id           IN    NUMBER,
1859     p_course_cd           IN    VARCHAR2,
1860     p_effective_dt        IN    DATE,
1861     p_acad_cal_type       OUT NOCOPY   VARCHAR2,
1862     p_acad_ci_seq_num     OUT NOCOPY   NUMBER,
1863     p_load_cal_type       OUT NOCOPY   VARCHAR2,
1864     p_load_ci_seq_num     OUT NOCOPY   NUMBER,
1865     p_load_ci_alt_code    OUT NOCOPY   VARCHAR2,
1866     p_load_ci_start_dt    OUT NOCOPY   DATE,
1867     p_load_ci_end_dt      OUT NOCOPY   DATE,
1868     p_message_name        OUT NOCOPY   VARCHAR2) AS
1869 
1870   /*
1871   ||  Created By : ayedubat(Anji Babu)
1872   ||  Created On : 19-DEC-2001 ( As part of ENCR015 DLD)
1873   ||  Purpose : To find the Effective Load Calendar Instance in a given Academic Calendar Instance
1874   ||  Known limitations, enhancements or remarks :
1875   ||  Change History :
1876   ||  Who             When            What
1877   ||  stutta	    20-NOV-2003	    Removed code to find the effective load calendar and replaced it
1878   ||				    with a call to get_curr_acad_term_cal. As part of Term Records Build.
1879   ||  (reverse chronological order - newest change first)
1880   */
1881 
1882     --
1883     --  Cursor to fetch student course attempt calendar type
1884     --
1885     CURSOR c_stu_crs_atmpt (cp_person_id     igs_en_stdnt_ps_att.person_id%TYPE,
1886                             cp_course_cd     igs_en_stdnt_ps_att.course_cd%TYPE) IS
1887       SELECT  sca.cal_type
1888       FROM    igs_en_stdnt_ps_att sca
1889       WHERE   sca.person_id = cp_person_id
1890       AND     sca.course_cd = cp_course_cd;
1891 
1892    -- Local Variables
1893    l_cal_type                        igs_en_stdnt_ps_att.cal_type%TYPE;
1894    l_message VARCHAR2(100);
1895 
1896    BEGIN
1897 
1898     --
1899     --  The attendance type is derived based on the load calendar instances, using
1900     --  the load effective date alias as the reference point for determining
1901     --  which calendar is the current load_calendar.
1902     --  Load the student IGS_PS_COURSE attempt details.
1903     --
1904 
1905     OPEN c_stu_crs_atmpt (p_person_id,
1906                           p_course_cd);
1907     FETCH c_stu_crs_atmpt INTO l_cal_type;
1908     IF (c_stu_crs_atmpt%NOTFOUND) THEN
1909        --
1910        -- if not data found return from the program unit
1911        --
1912        CLOSE c_stu_crs_atmpt;
1913        p_message_name := 'IGS_EN_NO_CRS_ATMPT';
1914        RETURN;
1915     END IF;
1916     CLOSE c_stu_crs_atmpt;
1917 
1918     --
1919     -- Get the current Academic Calendar
1920     --
1921     get_academic_cal
1922       (
1923         p_person_id                => p_person_id,
1924         p_course_cd                => p_course_cd ,
1925         p_acad_cal_type            => p_acad_cal_type,
1926         p_acad_ci_sequence_number  => p_acad_ci_seq_num,
1927         p_message                  => l_message,
1928         p_effective_dt             => p_effective_dt
1929       );
1930 
1931     IF l_message IS NOT NULL THEN
1932       p_message_name := l_message;
1933       RETURN;
1934     END IF;
1935 
1936     --
1937     -- determine the 'current' load calendar instance based on the load effective
1938     -- date alias from the enrolment calendar configuration. If this date alias
1939     -- can't be located then the latest calendar instance where start_dt/end_dt
1940     -- encompass the effective dt is deemed current
1941     --
1942     get_curr_acad_term_cal (
1943             l_cal_type,
1944             p_effective_dt,
1945             p_load_cal_type,
1946             p_load_ci_seq_num,
1947             p_load_ci_alt_code,
1948             p_load_ci_start_dt,
1949             p_load_ci_end_dt,
1950             p_message_name);
1951 
1952   EXCEPTION
1953     WHEN OTHERS THEN
1954         fnd_message.Set_Name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
1955         fnd_message.Set_Token('NAME','IGS_EN_GEN_015.enrp_get_eff_load_ci');
1956         IGS_GE_MSG_STACK.ADD;
1957         App_Exception.Raise_Exception;
1958 
1959   END enrp_get_eff_load_ci;
1960 
1961   PROCEDURE check_spl_perm_exists(
1962                                  p_cal_type             IN VARCHAR2,
1963                                  p_ci_sequence_number   IN NUMBER,
1964                                  p_person_id            IN  NUMBER,
1965                                  p_uoo_id               IN  NUMBER,
1966                                  p_person_type          IN VARCHAR2,
1967                                  p_program_cd           IN VARCHAR2,
1968                                  p_message_name         OUT NOCOPY VARCHAR2,
1969                                  p_return_status        OUT NOCOPY VARCHAR2,
1970                                  p_check_audit      IN VARCHAR2,
1971                                  p_audit_status     OUT NOCOPY VARCHAR2,
1972                                  p_audit_msg_name   OUT NOCOPY VARCHAR2
1973                                 ) AS
1974    ------------------------------------------------------------------------------------
1975     --Created by  : brajendr ( Oracle IDC)
1976     --Date created: 08-OCT-2001
1977     --
1978     --Purpose:
1979     --
1980     --Known limitations/enhancements and/or remarks:
1981     --
1982     --Change History:
1983     --Who         When            What
1984     --ayedubat   07-JUN-2002    The function call,Igs_En_Gen_015.get_academic_cal is replaced with
1985     --                         Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd to get the academic calendar of the
1986     --                         given load calendar rather than current academic calendar for the bug fix:2381603
1987     -- knaraset 27-Feb-2002 Bug- 2245062. This procedure was not considering whether the step is defined or not
1988     --                      Modified the procedure to consider Approval status and step defined or not etc.
1989     --nalkumar  14-May-2002 Modified the query stored in the l_step_def_query variable as per the bug# 2364461.
1990     --Nishikant    01NOV2002      SEVIS Build. Enh Bug#2641905. notification flag was
1991     --                            being fetched from cursor, now modified to get it by
1992     --                            calling the function igs_ss_enr_details.get_notification.
1993     --svanukur    04-jun-03       changed the declaration of the variable  l_step_override_limit
1994     --                           to refer to igs_en_elgb_ovr_uoo as part of deny/warn behaviour build #2829272
1995     -- smaddali  8-mar-06       Modified for bug#5091847
1996     -------------------------------------------------------------------------------------
1997     CURSOR cur_chk_sp_allowed( p_uoo_id NUMBER) IS
1998       SELECT special_permission_ind, cal_type, ci_sequence_number
1999       FROM igs_ps_unit_ofr_opt
2000       WHERE uoo_id = p_uoo_id;
2001 
2002     CURSOR cur_sp_exists( p_person_id NUMBER, p_uoo_id NUMBER) IS
2003       SELECT approval_status, Transaction_type
2004       FROM igs_en_spl_perm
2005       WHERE student_person_id = p_person_id
2006         AND uoo_id =p_uoo_id
2007         AND REQUEST_TYPE = 'SPL_PERM'
2008         AND transaction_type <> 'WITHDRAWN';
2009 
2010     CURSOR cur_sys_pers_type IS
2011     SELECT system_type
2012     FROM igs_pe_person_types
2013     WHERE person_type_code = p_person_type;
2014 
2015     TYPE step_rec IS RECORD(
2016       s_enrolment_step_type  igs_en_cpd_ext.s_enrolment_step_type%TYPE ,
2017       enrolment_cat       igs_en_cpd_ext.enrolment_cat%TYPE,
2018       s_student_comm_type igs_en_cpd_ext.s_student_comm_type%TYPE,
2019       enr_method_type     igs_en_cpd_ext.enr_method_type%TYPE,
2020       step_group_type     igs_lookups_view.step_group_type%TYPE);
2021 
2022     TYPE cur_step_def IS REF CURSOR;
2023 
2024     cur_step_def_var cur_step_def; -- REF cursor variable
2025     cur_step_def_var_rec step_rec;
2026     l_step_def_query VARCHAR2(2000);
2027 
2028 
2029     l_step_override_limit       igs_en_elgb_ovr_uoo.step_override_limit%TYPE;
2030     l_spl_perm_rec              cur_sp_exists%ROWTYPE;
2031     l_sp_allowed                igs_ps_unit_ofr_opt.special_permission_ind%TYPE;
2032     l_teach_cal_type            igs_ps_unit_ofr_opt.cal_type%TYPE;
2033     l_teach_ci_sequence_number  igs_ps_unit_ofr_opt.ci_sequence_number%TYPE;
2034     l_commencement_type         igs_en_cat_prc_dtl.S_STUDENT_COMM_TYPE%TYPE;
2035     l_enr_method                IGS_EN_METHOD_TYPE.enr_method_type%TYPE;
2036     l_enrollment_category       igs_en_cat_prc_dtl.enrolment_cat%TYPE;
2037     l_enrol_cal_type            igs_ca_type.cal_type%TYPE;
2038     l_enrol_sequence_number     igs_ca_inst_all.sequence_number%TYPE;
2039     l_system_type               igs_pe_person_types.system_type%TYPE;
2040     l_acad_cal_type             igs_ca_inst.cal_type%TYPE;
2041     l_acad_ci_sequence_number   igs_ca_inst.sequence_number%TYPE;
2042     lv_message                  fnd_new_messages.message_name%TYPE;
2043           l_acad_start_dt   IGS_CA_INST.start_dt%TYPE;
2044     l_acad_end_dt     IGS_CA_INST.end_dt%TYPE;
2045     l_alternate_code    IGS_CA_INST.alternate_code%TYPE;
2046     l_notification_flag       igs_en_cpd_ext.notification_flag%TYPE;
2047     l_message                 VARCHAR2(2000);
2048     l_return_status           VARCHAR2(10);
2049     l_dummy                   VARCHAR2(200);
2050         PROCEDURE l_call_audit_proc AS
2051         BEGIN
2052       IF p_check_audit = 'Y' THEN
2053         igs_en_gen_015.check_audit_perm_exists(p_cal_type           =>  p_cal_type           ,
2054                                                p_ci_sequence_number =>  p_ci_sequence_number ,
2055                                                p_person_id          =>  p_person_id          ,
2056                                                p_program_cd         =>  p_program_cd         ,
2057                                                p_uoo_id             =>  p_uoo_id             ,
2058                                                p_person_type        =>  p_person_type        ,
2059                                                p_enr_cat            =>  l_enrollment_category,
2060                                                p_enr_method         =>  l_enr_method         ,
2061                                                p_comm_type          =>  l_commencement_type  ,
2062                                                p_return_status      =>  p_audit_status       ,
2063                                                p_message_name       =>  p_audit_msg_name);
2064       END IF;
2065         END;
2066 
2067   BEGIN
2068     p_message_name := NULL;
2069     p_audit_msg_name := NULL;
2070     p_audit_status := 'AUDIT_NREQ';
2071 
2072     OPEN cur_chk_sp_allowed(p_uoo_id);
2073     FETCH cur_chk_sp_allowed INTO l_sp_allowed, l_teach_cal_type, l_teach_ci_sequence_number;
2074     CLOSE cur_chk_sp_allowed;
2075 
2076 
2077     -- check if the unit is being added in the intermission period.
2078     IF NOT IGS_EN_VAL_SUA.ENRP_VAL_SUA_INTRMT(
2079              p_person_id => p_person_id,
2080              p_course_cd => p_program_cd ,
2081              p_cal_type => l_teach_cal_type,
2082              p_ci_sequence_number =>  l_teach_ci_sequence_number,
2083              p_message_name => lv_message) THEN
2084       p_message_name := lv_message;
2085       p_return_status := 'SPL_ERR';
2086       RETURN;
2087     END IF;
2088 
2089     -- call igs_en_gen_017.enrp_get_enr_method to decide enrollment method type
2090     igs_en_gen_017.enrp_get_enr_method(
2091        p_enr_method_type => l_enr_method,
2092        p_error_message   => l_message,
2093        p_ret_status      => l_return_status);
2094 
2095    IF l_return_status = 'FALSE' THEN
2096         p_message_name := 'IGS_SS_EN_NOENR_METHOD' ;
2097         p_return_status := 'SPL_ERR';
2098         RETURN;
2099    ELSE
2100 
2101       l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
2102                             p_cal_type                => p_cal_type,
2103                             p_ci_sequence_number      => p_ci_sequence_number,
2104                             p_acad_cal_type           => l_acad_cal_type,
2105                             p_acad_ci_sequence_number => l_acad_ci_sequence_number,
2106                             p_acad_ci_start_dt        => l_acad_start_dt,
2107                             p_acad_ci_end_dt          => l_acad_end_dt,
2108                             p_message_name            => lv_message );
2109 
2110 
2111 
2112       IF lv_message IS NOT NULL THEN
2113         p_message_name := lv_message;
2114         p_return_status := 'SPL_ERR';
2115         RETURN;
2116       END IF;
2117 
2118 
2119       /* get the enrollment category and commencement type */
2120       l_enrollment_category := igs_en_gen_003.enrp_get_enr_cat
2121                                   ( p_person_id => p_person_id,
2122                                     p_course_cd => p_program_cd,
2123                                     p_cal_type => l_acad_cal_type, -- Acad cal type
2124                                     p_ci_sequence_number => l_acad_ci_sequence_number, --Acad sequence number
2125                                     p_session_enrolment_cat =>NULL,
2126                                     p_enrol_cal_type => l_enrol_cal_type        ,
2127                                     p_enrol_ci_sequence_number => l_enrol_sequence_number,
2128                                     p_commencement_type => l_commencement_type,
2129                                     p_enr_categories  => l_dummy );
2130 
2131       IF l_commencement_type = 'BOTH' THEN
2132      /* if both is returned we have to treat it as all */
2133           l_commencement_type := 'ALL';
2134       END IF;
2135    END IF; -- end if get_enr_method
2136 
2137 
2138     -- check whether special permission functionality is allowed for the given unit section
2139     -- i.e. special permission allowed check box is checked/unchecked..
2140     IF l_sp_allowed = 'N' THEN
2141       -- Special Permission is not required
2142       p_return_status :=  'SPL_NREQ';
2143           l_call_audit_proc;
2144           RETURN;
2145     END IF;
2146 
2147 
2148 
2149 
2150   -- get the System Type for the given Person Type.
2151    OPEN cur_sys_pers_type;
2152    FETCH cur_sys_pers_type INTO l_system_type;
2153    CLOSE cur_sys_pers_type;
2154 
2155    -- if the user log on is a student
2156    IF l_system_type = 'STUDENT' THEN
2157       l_step_def_query := 'SELECT eru.s_enrolment_step_type, eru.enrolment_cat, eru.s_student_comm_type, eru.enr_method_type, lkv.step_group_type
2158                              FROM igs_en_cpd_ext eru, igs_lookups_view lkv
2159                                                  WHERE eru.s_enrolment_step_type = ''SPL_PERM'' AND
2160                                                  eru.s_enrolment_step_type =lkv.lookup_code AND
2161                                                  lkv.lookup_type = ''ENROLMENT_STEP_TYPE_EXT'' AND lkv.step_group_type =
2162                                                  ''UNIT'' AND eru.enrolment_cat = :1  AND eru.enr_method_type = :2
2163                                                  AND (eru.s_student_comm_type = :3  OR eru.s_student_comm_type = ''ALL'')
2164                                                  ORDER BY eru.step_order_num';
2165    OPEN cur_step_def_var FOR l_step_def_query USING l_enrollment_category, l_enr_method, l_commencement_type;
2166 
2167    ELSE
2168    --IF l_system_type = 'SS_ENROLL_STAFF' THEN -- if the log on user is self service enrollment staff
2169    -- removed the check so as to prepare the query for person type other than STUDENT and SS_ENROLL_STAFF also
2170 
2171       l_step_def_query := 'SELECT eru.s_enrolment_step_type, eru.enrolment_cat, eru.s_student_comm_type, eru.enr_method_type, lkv.step_group_type
2172                              FROM igs_en_cpd_ext eru, igs_pe_usr_aval_all uact, igs_lookups_view lkv
2173                                                  WHERE eru.s_enrolment_step_type = ''SPL_PERM'' AND
2174                                                  eru.s_enrolment_step_type =lkv.lookup_code AND
2175                                                  lkv.lookup_type = ''ENROLMENT_STEP_TYPE_EXT'' AND lkv.step_group_type = ''UNIT'' AND
2176                                                  eru.s_enrolment_step_type = uact.validation(+) AND
2177                                                  uact.person_type(+) = :1  AND
2178                                                  NVL(uact.override_ind,''N'') = ''N'' AND
2179                                                  eru.enrolment_cat = :2  AND
2180                                                  eru.enr_method_type = :3
2181                                                  AND ( eru.s_student_comm_type = :4 OR eru.s_student_comm_type = ''ALL'' )
2182                                                  ORDER BY eru.step_order_num';
2183    OPEN cur_step_def_var FOR l_step_def_query USING p_person_type, l_enrollment_category, l_enr_method, l_commencement_type;
2184 
2185    END IF;
2186    --
2187    -- open the REF cursor for the sql query defined above.
2188    FETCH cur_step_def_var INTO cur_step_def_var_rec;
2189    IF cur_step_def_var%NOTFOUND THEN
2190      -- If Special Permission Step is not defined,
2191       p_return_status :=  'SPL_NREQ';
2192           l_call_audit_proc;
2193           RETURN;
2194    END IF;
2195            lv_message := NULL;
2196            l_notification_flag := igs_ss_enr_details.get_notification(
2197                                    p_person_type         => p_person_type,
2198                                    p_enrollment_category => cur_step_def_var_rec.enrolment_cat,
2199                                    p_comm_type           => cur_step_def_var_rec.s_student_comm_type,
2200                                    p_enr_method_type     => cur_step_def_var_rec.enr_method_type,
2201                                    p_step_group_type     => cur_step_def_var_rec.step_group_type,
2202                                    p_step_type           => cur_step_def_var_rec.s_enrolment_step_type,
2203                                    p_person_id           => p_person_id,
2204                                    p_message             => lv_message);
2205    IF lv_message IS NOT NULL THEN
2206       p_return_status :=  'SPL_ERR';
2207       p_message_name  := lv_message;
2208       RETURN;
2209    END IF;
2210    -- even though the step is defined If the notification is WARN
2211    -- no need to get the special permission from the instructor
2212    IF l_notification_flag = 'WARN' THEN
2213       p_return_status :=  'SPL_NREQ';
2214           l_call_audit_proc;
2215           RETURN;
2216    END IF;
2217    -- check whether the Step is overriden or not
2218    -- if step is overriden then no need to get the special permission from the instructor
2219    IF Igs_En_Gen_015.validation_step_is_overridden ('SPL_PERM',
2220                                                      p_cal_type,
2221                                                      p_ci_sequence_number ,
2222                                                      p_person_id ,
2223                                                      p_uoo_id ,
2224                                                      l_step_override_limit) THEN
2225       -- Step is overridden, no special permission is required
2226       p_return_status :=  'SPL_NREQ';
2227           l_call_audit_proc;
2228           RETURN;
2229    END IF;
2230 
2231     -- check whether student has entered special permission data already
2232     OPEN cur_sp_exists( p_person_id, p_uoo_id);
2233     FETCH cur_sp_exists INTO l_spl_perm_rec;
2234     IF cur_sp_exists%NOTFOUND THEN
2235       -- Special permission is required
2236       p_return_status :=  'SPL_REQ';
2237       CLOSE cur_sp_exists;
2238           l_call_audit_proc;
2239           RETURN;
2240     ELSE
2241           CLOSE cur_sp_exists;
2242       IF l_spl_perm_rec.approval_status = 'A' THEN
2243         p_return_status :=  'SPL_NREQ';
2244             l_call_audit_proc;
2245             RETURN;
2246       ELSIF ( l_spl_perm_rec.transaction_type = 'INS_MI') THEN
2247           l_call_audit_proc;
2248           p_return_status :=  'SPL_ERR';
2249           p_message_name := 'IGS_SS_EN_INS_MORE_INFO' ;
2250           RETURN;
2251       ELSIF (l_spl_perm_rec.approval_status = 'I' OR
2252            l_spl_perm_rec.transaction_type = 'STD_MI' ) THEN
2253           l_call_audit_proc;
2254           p_return_status :=  'SPL_ERR';
2255           p_message_name := 'IGS_SS_EN_STD_MORE_INFO' ;
2256           RETURN;
2257       ELSIF l_spl_perm_rec.approval_status = 'D' THEN
2258         p_return_status :=  'SPL_ERR';
2259         p_message_name := 'IGS_SS_EN_INS_DENY' ;
2260             l_call_audit_proc;
2261             RETURN;
2262       ELSE
2263         p_message_name := 'IGS_SS_DENY_SPL_PERMIT';
2264         p_return_status :=  'SPL_ERR';
2265             l_call_audit_proc;
2266             RETURN;
2267       END IF;
2268     END IF;
2269 
2270   END check_spl_perm_exists;
2271 
2272   PROCEDURE check_audit_perm_exists(
2273                                  p_cal_type             IN VARCHAR2,
2274                                  p_ci_sequence_number   IN NUMBER,
2275                                  p_person_id            IN  NUMBER,
2276                                  p_program_cd           IN VARCHAR2,
2277                                  p_uoo_id               IN  NUMBER,
2278                                  p_person_type          IN VARCHAR2,
2279                                                                  p_enr_cat          IN VARCHAR2,
2280                                                                  p_enr_method       IN VARCHAR2,
2281                                                                  p_comm_type        IN VARCHAR2,
2282                                  p_return_status     OUT NOCOPY VARCHAR2,
2283                                  p_message_name   OUT NOCOPY VARCHAR2
2284   ) AS
2285    ------------------------------------------------------------------------------------
2286     --Created by  : Annamalai (Oracle, IDC)
2287     --Date created: 28-OCT-2002
2288     --
2289     --Purpose: To check for Audit Permissons
2290     --
2291     --Known limitations/enhancements and/or remarks:
2292     --
2293     --Change History:
2294     --Who         When            What
2295     --Nishikant    01NOV2002      SEVIS Build. Enh Bug#2641905. notification flag was
2296     --                            being fetched from cursor, now modified to get it by
2297     --                            calling the function igs_ss_enr_details.get_notification.
2298     -- smaddali  8-mar-06       Modified for bug#5091847
2299     -------------------------------------------------------------------------------------
2300     CURSOR c_chk_audit_allowed( p_uoo_id NUMBER) IS
2301       SELECT NVL(auditable_ind, 'N'), NVL(audit_permission_ind, 'N')
2302       FROM igs_ps_unit_ofr_opt
2303       WHERE uoo_id = p_uoo_id;
2304 
2305 
2306     CURSOR c_audit_perm_exists( p_person_id NUMBER, p_uoo_id NUMBER) IS
2307       SELECT approval_status, transaction_type
2308       FROM igs_en_spl_perm
2309       WHERE student_person_id = p_person_id
2310         AND uoo_id =p_uoo_id
2311         AND REQUEST_TYPE = 'AUDIT_PERM'
2312         AND transaction_type <> 'WITHDRAWN';
2313 
2314 
2315     CURSOR c_sys_pers_type (cp_person_type igs_pe_person_types.person_type_code%TYPE) IS
2316     SELECT system_type
2317     FROM igs_pe_person_types
2318     WHERE person_type_code = cp_person_type;
2319 
2320 
2321         CURSOR c_stud_step_def(cp_step IGS_LOOKUPS_VIEW.LOOKUP_CODE%TYPE,
2322                           cp_enrollment_Category IGS_EN_CAT_PRC_DTL.enrolment_cat%TYPE,
2323                                           cp_enr_method IGS_EN_CAT_PRC_DTL.ENR_METHOD_TYPE%TYPE,
2324                                           cp_commencement_type  IGS_EN_CAT_PRC_DTL.S_STUDENT_COMM_TYPE%TYPE
2325                                           ) IS
2326         SELECT
2327           eru.s_enrolment_step_type, eru.enrolment_cat, eru.s_student_comm_type, eru.enr_method_type, lkv.step_group_type --modified by nishikant
2328         FROM
2329           igs_en_cpd_ext eru,
2330           igs_lookups_view lkv
2331         WHERE
2332           eru.s_enrolment_step_type = cp_step AND
2333           eru.s_enrolment_step_type =lkv.lookup_code AND
2334           lkv.lookup_type = 'ENROLMENT_STEP_TYPE_EXT' AND
2335           lkv.step_group_type ='UNIT' AND
2336           eru.enrolment_cat = cp_enrollment_category AND
2337           eru.enr_method_type = cp_enr_method AND
2338           (eru.s_student_comm_type = cp_commencement_type OR eru.s_student_comm_type = 'ALL')
2339         ORDER BY eru.step_order_num;
2340 
2341         CURSOR c_staff_step_def(cp_step IGS_LOOKUPS_VIEW.LOOKUP_CODE%TYPE,
2342                           cp_person_type igs_pe_person_types.PERSON_TYPE_CODE%TYPE,
2343                           cp_enrollment_Category IGS_EN_CAT_PRC_DTL.enrolment_cat%TYPE,
2344                                           cp_enr_method IGS_EN_CAT_PRC_DTL.ENR_METHOD_TYPE%TYPE,
2345                                           cp_commencement_type  IGS_EN_CAT_PRC_DTL.S_STUDENT_COMM_TYPE%TYPE
2346                                           ) IS
2347         SELECT
2348           eru.s_enrolment_step_type, eru.enrolment_cat, eru.s_student_comm_type, eru.enr_method_type, lkv.step_group_type --modified by nishikant
2349         FROM
2350           igs_en_cpd_ext eru,
2351           igs_pe_usr_aval_all uact,
2352           igs_lookups_view lkv
2353         WHERE
2354           eru.s_enrolment_step_type = cp_step AND
2355           eru.s_enrolment_step_type =lkv.lookup_code AND
2356           lkv.lookup_type = 'ENROLMENT_STEP_TYPE_EXT' AND
2357           lkv.step_group_type = 'UNIT' AND
2358           eru.s_enrolment_step_type = uact.validation(+) AND
2359           uact.person_type(+) = cp_person_type AND
2360           NVL(uact.override_ind,'N') = 'N' AND
2361           eru.enrolment_cat = cp_enrollment_category AND
2362           eru.enr_method_type = cp_enr_method                                                    AND
2363           ( eru.s_student_comm_type = cp_commencement_type OR eru.s_student_comm_type = 'ALL' )
2364         ORDER BY eru.step_order_num;
2365 
2366         v_ap_allowed  igs_ps_unit_ofr_opt.AUDITABLE_IND%TYPE;
2367         v_ap_required igs_ps_unit_ofr_opt.AUDIT_PERMISSION_IND%TYPE;
2368         v_staff_step_def_rec c_staff_step_def%ROWTYPE;
2369         v_stud_step_def_rec      c_stud_step_def%ROWTYPE;
2370         v_system_type  igs_pe_person_types.SYSTEM_TYPE%TYPE;
2371         v_step_override_limit   igs_en_elgb_ovr_step.step_override_limit%TYPE;
2372         v_audit_perm_rec  c_audit_perm_exists%ROWTYPE;
2373         l_notification_flag       igs_en_cpd_ext.notification_flag%TYPE;
2374 
2375   BEGIN
2376     p_message_name := NULL;
2377     -- check whether Audit special permission functionality is allowed for the given unit section
2378     -- i.e. Audit allowed check box is checked/unchecked..
2379     OPEN c_chk_audit_allowed(p_uoo_id);
2380     FETCH c_chk_audit_allowed INTO v_ap_allowed,v_ap_required;
2381     CLOSE c_chk_audit_allowed;
2382 
2383         IF v_ap_allowed = 'N' THEN
2384       -- The unit is not auditable hence show an error message
2385       p_return_status :=  'AUDIT_ERR';
2386           p_message_name := 'IGS_EN_CANNOT_AUDIT';
2387           RETURN;
2388     END IF;
2389 
2390         IF  v_ap_allowed = 'Y' AND v_ap_required = 'N' THEN
2391       p_return_status :=  'AUDIT_NREQ';
2392           RETURN;
2393         END IF;
2394 
2395 
2396 
2397   -- get the System Type for the given Person Type.
2398    OPEN c_sys_pers_type(p_person_type);
2399    FETCH c_sys_pers_type INTO v_system_type;
2400    CLOSE c_sys_pers_type;
2401 
2402    -- if the user log on is a student
2403    IF v_system_type = 'STUDENT' THEN
2404 
2405            OPEN c_stud_step_def('AUDIT_PERM',
2406                                  p_enr_cat     ,
2407                                                          p_enr_method,
2408                                                          p_comm_type );
2409            FETCH c_stud_step_def INTO v_stud_step_def_rec;
2410            IF c_stud_step_def%NOTFOUND THEN
2411              -- If Special Permission Step is not defined,
2412                 p_return_status :=  'AUDIT_NREQ';
2413                 RETURN;
2414            END IF;
2415            p_message_name := NULL;
2416            l_notification_flag := NULL;
2417            l_notification_flag := igs_ss_enr_details.get_notification(
2418                                    p_person_type         => p_person_type,
2419                                    p_enrollment_category => v_stud_step_def_rec.enrolment_cat,
2420                                    p_comm_type           => v_stud_step_def_rec.s_student_comm_type,
2421                                    p_enr_method_type     => v_stud_step_def_rec.enr_method_type,
2422                                    p_step_group_type     => v_stud_step_def_rec.step_group_type,
2423                                    p_step_type           => v_stud_step_def_rec.s_enrolment_step_type,
2424                                    p_person_id           => p_person_id ,
2425                                    p_message             => p_message_name);
2426            IF p_message_name IS NOT NULL THEN
2427                  p_return_status := 'AUDIT_ERR';
2428                  RETURN;
2429            END IF;
2430            -- even though the step is defined If the notification is WARN
2431            -- no need to get the special permission from the instructor
2432            IF l_notification_flag = 'WARN' THEN
2433               p_return_status :=  'AUDIT_NREQ';
2434                   RETURN;
2435            END IF;
2436 
2437    ELSE
2438 
2439    --IF l_system_type = 'SS_ENROLL_STAFF' THEN -- if the log on user is self service enrollment staff
2440    -- removed the check so as to prepare the query for person type other than STUDENT and SS_ENROLL_STAFF also
2441    -- open the cursor for the sql query defined above.
2442 
2443            -- open the REF cursor for the sql query defined above.
2444            OPEN c_staff_step_def('AUDIT_PERM',
2445                                  p_person_type,
2446                                  p_enr_cat     ,
2447                                                          p_enr_method,
2448                                                          p_comm_type );
2449            FETCH c_staff_step_def INTO v_staff_step_def_rec;
2450            IF c_staff_step_def%NOTFOUND THEN
2451              -- If Special Permission Step is not defined,
2452               p_return_status :=  'AUDIT_NREQ';
2453                   RETURN;
2454            END IF;
2455 
2456            p_message_name := NULL;
2457            l_notification_flag := NULL;
2458            l_notification_flag := igs_ss_enr_details.get_notification(
2459                                    p_person_type         => p_person_type,
2460                                    p_enrollment_category => v_staff_step_def_rec.enrolment_cat,
2461                                    p_comm_type           => v_staff_step_def_rec.s_student_comm_type,
2462                                    p_enr_method_type     => v_staff_step_def_rec.enr_method_type,
2463                                    p_step_group_type     => v_staff_step_def_rec.step_group_type,
2464                                    p_step_type           => v_staff_step_def_rec.s_enrolment_step_type,
2465                                    p_person_id           => p_person_id ,
2466                                    p_message             => p_message_name);
2467            IF p_message_name IS NOT NULL THEN
2468                  p_return_status := 'AUDIT_ERR';
2469                  RETURN;
2470            END IF;
2471            -- even though the step is defined If the notification is WARN
2472            -- no need to get the special permission from the instructor
2473            IF l_notification_flag = 'WARN' THEN
2474               p_return_status :=  'AUDIT_NREQ';
2475                   RETURN;
2476            END IF;
2477 
2478    END IF;
2479    --
2480 
2481    -- check whether the Step is overriden or not
2482    -- if step is overriden then no need to get the special permission from the instructor
2483    IF Igs_En_Gen_015.validation_step_is_overridden ('AUDIT_PERM',
2484                                                      p_cal_type,
2485                                                      p_ci_sequence_number ,
2486                                                      p_person_id ,
2487                                                      p_uoo_id ,
2488                                                      v_step_override_limit) THEN
2489       -- Step is overridden, no special permission is required
2490       p_return_status :=  'AUDIT_NREQ';
2491           RETURN;
2492    END IF;
2493 
2494     -- check whether student has entered special permission data already
2495     OPEN c_audit_perm_exists( p_person_id, p_uoo_id);
2496     FETCH c_audit_perm_exists INTO v_audit_perm_rec;
2497     IF c_audit_perm_exists%NOTFOUND THEN
2498       -- Special permission is required
2499       p_return_status :=  'AUDIT_REQ';
2500       CLOSE c_audit_perm_exists;
2501           RETURN;
2502     ELSE
2503           CLOSE c_audit_perm_exists;
2504       IF v_audit_perm_rec.approval_status = 'A' THEN
2505         p_return_status :=  'AUDIT_NREQ';
2506             RETURN;
2507       ELSIF ( v_audit_perm_rec.transaction_type = 'INS_MI' ) THEN
2508         p_return_status :=  'AUDIT_ERR';
2509         p_message_name := 'IGS_EN_AU_INS_MORE_INFO' ;
2510             RETURN;
2511       ELSIF (v_audit_perm_rec.approval_status = 'I' OR
2512              v_audit_perm_rec.transaction_type = 'STD_MI' ) THEN
2513         p_return_status :=  'AUDIT_ERR';
2514         p_message_name := 'IGS_EN_AU_STD_MORE_INFO' ;
2515             RETURN;
2516       ELSIF v_audit_perm_rec.approval_status = 'D' THEN
2517         p_return_status :=  'AUDIT_ERR';
2518         p_message_name := 'IGS_EN_AU_INS_DENY' ;
2519             RETURN;
2520       END IF;
2521     END IF;
2522 
2523   END check_audit_perm_exists;
2524 
2525   FUNCTION eval_core_unit_drop
2526   (
2527     p_person_id                    IN     NUMBER,
2528     p_course_cd                    IN     VARCHAR2,
2529     p_uoo_id                       IN     NUMBER,
2530     p_step_type                    IN     VARCHAR2,
2531     p_term_cal                     IN     VARCHAR2,
2532     p_term_sequence_number         IN     NUMBER,
2533     p_deny_warn                    OUT NOCOPY VARCHAR2,
2534     p_enr_method                 IN VARCHAR2
2535   )
2536   ------------------------------------------------------------------
2537   --Created by  : Parul Tandon, Oracle IDC
2538   --Date created: 01-OCT-2003
2539   --
2540   --Purpose: This function checks whether the core unit attempt can
2541   --be dropped.
2542   --
2543   --
2544   --Known limitations/enhancements and/or remarks:
2545   --
2546   --Change History:
2547   --Who         When            What
2548   -------------------------------------------------------------------
2549 
2550   RETURN VARCHAR2 IS
2551 
2552   --
2553   --  Cursor to find the Core Indicator associated with a Unit Attempt
2554   --
2555   CURSOR cur_get_core_ind(cp_person_id          igs_en_su_attempt.person_id%TYPE,
2556                           cp_course_cd          igs_en_su_attempt.course_cd%TYPE,
2557                           cp_uoo_id             igs_en_su_attempt.uoo_id%TYPE)
2558   IS
2559     SELECT   core_indicator_code
2560     FROM     igs_en_su_attempt
2561     WHERE    person_id = cp_person_id
2562     AND      course_cd = cp_course_cd
2563     AND      uoo_id    = cp_uoo_id;
2564 
2565   l_core_indicator_code         igs_en_su_attempt.core_indicator_code%TYPE;
2566   l_person_type                 igs_pe_person_types.person_type_code%TYPE;
2567   l_enrollment_category         igs_en_cat_prc_step.enrolment_cat%TYPE;
2568   l_comm_type                   igs_en_cat_prc_step.s_student_comm_type%TYPE;
2569   l_enr_method_type             igs_en_cat_prc_step.enr_method_type%TYPE;
2570   l_acad_cal_type               igs_ca_inst.cal_type%TYPE;
2571   l_acad_ci_sequence_number     igs_ca_inst.sequence_number%TYPE;
2572   l_step_override_limit         NUMBER;
2573   l_message                     VARCHAR2(100);
2574   l_ret_status                  VARCHAR2(10);
2575   l_en_cal_type                 igs_ca_inst.cal_type%TYPE;
2576   l_en_ci_seq_num               igs_ca_inst.sequence_number%TYPE;
2577   l_dummy                       VARCHAR2(200);
2578 
2579   BEGIN
2580 
2581     --  Check whether the profile is set or not
2582     IF NVL(fnd_profile.value('IGS_EN_CORE_VAL'),'N') = 'N' THEN
2583        RETURN 'TRUE';
2584     END IF;
2585 
2586     --  Get the person type
2587     l_person_type := igs_en_gen_008.enrp_get_person_type(p_course_cd);
2588 
2589     --  Get the superior academic calendar instance
2590     igs_en_gen_015.get_academic_cal
2591     (
2592      p_person_id,
2593      p_course_cd,
2594      l_acad_cal_type,
2595      l_acad_ci_sequence_number,
2596      l_message,
2597      SYSDATE
2598     );
2599 
2600     --  Get the enrollment category and commencement type
2601     l_enrollment_category:=igs_en_gen_003.enrp_get_enr_cat(
2602                                                           p_person_id,
2603                                                           p_course_cd,
2604                                                           l_acad_cal_type,
2605                                                           l_acad_ci_sequence_number,
2606                                                           NULL,
2607                                                           l_en_cal_type,
2608                                                           l_en_ci_seq_num,
2609                                                           l_comm_type,
2610                                                           l_dummy);
2611 
2612     IF p_enr_method IS NULL THEN
2613 	--- Get the enrollment method
2614 	igs_en_gen_017.enrp_get_enr_method(l_enr_method_type,l_message,l_ret_status);
2615     ELSE
2616 	l_enr_method_type := p_enr_method;
2617     END IF;
2618     -- Get the value of Deny/Warn Flag for unit step 'DROP_CORE'
2619     p_deny_warn := igs_ss_enr_details.get_notification(
2620                         p_person_type            => l_person_type,
2621                         p_enrollment_category    => l_enrollment_category,
2622                         p_comm_type              => l_comm_type,
2623                         p_enr_method_type        => l_enr_method_type,
2624                         p_step_group_type        => 'UNIT',
2625                         p_step_type              => 'DROP_CORE',
2626                         p_person_id              => p_person_id,
2627                         p_message                => l_message
2628                         ) ;
2629 
2630     -- If the unit step is not defined return TRUE
2631     IF p_deny_warn IS NULL THEN
2632           RETURN 'TRUE';
2633     END IF;
2634 
2635     -- Get the value of core indicator for unit attempt
2636     OPEN cur_get_core_ind(p_person_id,p_course_cd,p_uoo_id);
2637     FETCH cur_get_core_ind INTO l_core_indicator_code;
2638     CLOSE cur_get_core_ind;
2639 
2640     --  If the unit is not a Core Unit, return TRUE. If the unit is a
2641     --  core unit and the unit step DROP_CORE is overridden for the
2642     --  student in context, return TRUE else return FALSE.
2643     IF l_core_indicator_code = 'CORE' THEN
2644       IF igs_en_gen_015.validation_step_is_overridden
2645                        (
2646                         'DROP_CORE',
2647                         p_term_cal,
2648                         p_term_sequence_number,
2649                         p_person_id,
2650                         p_uoo_id,
2651                         l_step_override_limit
2652                         )
2653       THEN
2654         RETURN 'TRUE';
2655       ELSE
2656         RETURN 'FALSE';
2657       END IF;
2658     ELSE
2659       RETURN 'TRUE';
2660     END IF;
2661 
2662   END eval_core_unit_drop;
2663 
2664 PROCEDURE  get_curr_acad_term_cal (
2665     p_acad_cal_type       IN VARCHAR,
2666     p_effective_dt        IN    DATE,
2667     p_load_cal_type       OUT NOCOPY   VARCHAR2,
2668     p_load_ci_seq_num     OUT NOCOPY   NUMBER,
2669     p_load_ci_alt_code    OUT NOCOPY   VARCHAR2,
2670     p_load_ci_start_dt    OUT NOCOPY   DATE,
2671     p_load_ci_end_dt      OUT NOCOPY   DATE,
2672     p_message_name        OUT NOCOPY   VARCHAR2) AS
2673 ------------------------------------------------------------------
2674   --Created by  : Susmitha Tutta, Oracle IDC
2675   --Date created: 19-NOV-2003
2676   --
2677   --Purpose:  To find the Effective Load Calendar Instance given a Academic Calendar Type and effective date
2678   --
2679   --
2680   --
2681   --Known limitations/enhancements and/or remarks:
2682   --
2683   --Change History:
2684   --Who         When            What
2685   -------------------------------------------------------------------
2686 
2687   -- LOCAL VARIABLES
2688   cst_active                        CONSTANT VARCHAR2(10) := 'ACTIVE';
2689   cst_load                          CONSTANT VARCHAR2(10) := 'LOAD';
2690   l_daiv_rec_found                  BOOLEAN;
2691   l_cal_type                        IGS_EN_STDNT_PS_ATT.CAL_TYPE%TYPE;
2692   l_current_load_ci_alt_code IGS_CA_INST.ALTERNATE_CODE%TYPE;
2693   l_current_load_ci_start_dt IGS_CA_INST.START_DT%TYPE;
2694   l_current_load_ci_end_dt   IGS_CA_INST.END_DT%TYPE;
2695   l_current_load_cal_type           IGS_CA_INST.CAL_TYPE%TYPE;
2696   l_current_load_sequence_number    IGS_CA_INST.SEQUENCE_NUMBER%TYPE;
2697   l_other_detail                    VARCHAR2(255);
2698   l_effective_dt                    DATE;
2699 
2700     --
2701     --  CURSOR TO FETCH LOAD EFFECTIVE DATE ALIAS.
2702     --
2703     CURSOR
2704     c_s_enr_cal_conf IS
2705       SELECT  secc.load_effect_dt_alias
2706       FROM    igs_en_cal_conf secc
2707       WHERE   secc.s_control_num = 1;
2708 
2709     L_LOAD_EFFECT_DT_ALIAS IGS_EN_CAL_CONF.LOAD_EFFECT_DT_ALIAS%TYPE;
2710 
2711     --
2712     --  CURSOR TO FETCH CALENDAR TYPE INSTANCES
2713     --
2714     CURSOR c_cal_type_instance (cp_cal_type         igs_ca_inst.cal_type%TYPE) is
2715       SELECT   ci.cal_type,
2716                ci.sequence_number,
2717 	       ci.alternate_code,
2718                ci.start_dt,
2719                ci.end_dt
2720       FROM     igs_ca_type ct,
2721                igs_ca_inst ci,
2722                igs_ca_stat cs,
2723                igs_ca_inst_rel cir
2724       WHERE    cs.s_cal_status = cst_active
2725       AND      ci.cal_status = cs.cal_status
2726       AND      ct.s_cal_cat = cst_load
2727       AND      ci.cal_type = ct.cal_type
2728       AND      CIR.SUB_CAL_TYPE = CI.CAL_TYPE
2729       AND      cir.sub_ci_sequence_number =ci.sequence_number
2730       AND      cir.sup_cal_type = cp_cal_type
2731       ORDER BY ci.start_dt DESC;
2732 
2733     --
2734     --  CURSOR TO FETCH THE DATE ALIAS
2735     --
2736     CURSOR c_dai_v (cp_cal_type             igs_ca_da_inst_v.cal_type%TYPE,
2737                     cp_ci_sequence_number   igs_ca_da_inst_v.ci_sequence_number%TYPE,
2738                     cp_load_effect_dt_alias igs_en_cal_conf.load_effect_dt_alias%TYPE) IS
2739       SELECT   daiv.alias_val
2740       FROM     igs_ca_da_inst_v daiv
2741       WHERE    daiv.cal_type = cp_cal_type
2742       AND      daiv.ci_sequence_number = cp_ci_sequence_number
2743       AND      daiv.dt_alias = cp_load_effect_dt_alias;
2744 
2745   l_load_alias_value igs_ca_da_inst.absolute_val%TYPE;
2746 
2747 
2748   BEGIN
2749 
2750     --
2751     -- DETERMINE THE 'CURRENT' LOAD CALENDAR INSTANCE BASED ON THE LOAD EFFECTIVE
2752     -- DATE ALIAS FROM THE ENROLMENT CALENDAR CONFIGURATION. IF THIS DATE ALIAS
2753     -- CAN'T BE LOCATED THEN THE LATEST CALENDAR INSTANCE WHERE START_DT/END_DT
2754     -- ENCOMPASS THE EFFECTIVE DT IS DEEMED CURRENT
2755     --
2756     OPEN c_s_enr_cal_conf;
2757     FETCH c_s_enr_cal_conf INTO l_load_effect_dt_alias;
2758     IF c_s_enr_cal_conf%NOTFOUND THEN
2759        CLOSE c_s_enr_cal_conf;
2760        p_message_name := 'IGS_EN_NO_SECC_REC_FOUND';
2761        RETURN;
2762     END IF;
2763     CLOSE c_s_enr_cal_conf;
2764     --
2765     -- INITIALISE THE LOCAL VARIABLES
2766     --
2767     l_current_load_cal_type := NULL;
2768     l_current_load_sequence_number := NULL;
2769     l_current_load_ci_start_dt := NULL;
2770     l_current_load_ci_end_dt := NULL;
2771     l_current_load_ci_alt_code := NULL;
2772 
2773     --
2774     -- NOW LOOP THROUGH THE CAL TYPE INSTANCE RECORDS
2775     --
2776     FOR rec_cal_type_instance IN c_cal_type_instance (p_acad_cal_type)
2777     LOOP
2778         --
2779         -- ATTEMPT TO FIND LOAD EFFECTIVE DATE ALIAS AGAINST THE CALE
2780         --
2781         l_daiv_rec_found := FALSE;
2782         FOR rec_dai_v IN c_dai_v (rec_cal_type_instance.cal_type,
2783                                   rec_cal_type_instance.sequence_number,
2784                                   l_load_effect_dt_alias)
2785         LOOP
2786             l_daiv_rec_found := TRUE;
2787             IF (p_effective_dt >= rec_dai_v.alias_val) THEN
2788                 l_current_load_cal_type := rec_cal_type_instance.cal_type ;
2789                 l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
2790                 l_current_load_ci_start_dt := rec_cal_type_instance.start_dt;
2791                 l_current_load_ci_end_dt := rec_cal_type_instance.end_dt;
2792                 l_current_load_ci_alt_code := rec_cal_type_instance.alternate_code;
2793             END IF;
2794         END LOOP;
2795         IF NOT l_daiv_rec_found  THEN
2796            IF (p_effective_dt >= rec_cal_type_instance.start_dt) AND
2797               (p_effective_dt <= rec_cal_type_instance.end_dt) THEN
2798                   l_current_load_cal_type := rec_cal_type_instance.cal_type ;
2799                   l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
2800                   l_current_load_ci_start_dt := rec_cal_type_instance.start_dt;
2801                   l_current_load_ci_end_dt := rec_cal_type_instance.end_dt;
2802                   l_current_load_ci_alt_code := rec_cal_type_instance.alternate_code;
2803             END IF;
2804         END IF;
2805         IF l_current_load_cal_type IS NOT NULL THEN
2806            EXIT;
2807         END IF;
2808     END LOOP;
2809 
2810     IF l_current_load_cal_type IS NULL THEN
2811        p_load_cal_type    := NULL;
2812        p_load_ci_seq_num  := NULL;
2813        p_load_ci_alt_code   := NULL ;
2814        p_load_ci_start_dt   := NULL;
2815        p_load_ci_end_dt     := NULL;
2816        p_message_name := 'IGS_EN_LOAD_CAL_NOT_FOUND';
2817     ELSE
2818       p_load_cal_type     := l_current_load_cal_type;
2819       p_load_ci_seq_num   := l_current_load_sequence_number;
2820       p_load_ci_alt_code   := l_current_load_ci_alt_code ;
2821       p_load_ci_start_dt   := l_current_load_ci_start_dt;
2822       p_load_ci_end_dt     := l_current_load_ci_end_dt  ;
2823     END IF;
2824 
2825 
2826   EXCEPTION
2827     WHEN OTHERS THEN
2828         FND_MESSAGE.SET_NAME('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
2829         FND_MESSAGE.SET_TOKEN('NAME','IGS_EN_GEN_015.GET_CURR_ACAD_TERM_CAL');
2830         IGS_GE_MSG_STACK.ADD;
2831         APP_EXCEPTION.RAISE_EXCEPTION;
2832 
2833   END get_curr_acad_term_cal;
2834 
2835     PROCEDURE  get_curr_term_for_schedule(
2836     p_acad_cal_type       IN VARCHAR,
2837     p_effective_dt        IN    DATE,
2838     p_load_cal_type       OUT NOCOPY   VARCHAR2,
2839     p_load_ci_seq_num     OUT NOCOPY   NUMBER,
2840     p_load_ci_alt_code    OUT NOCOPY   VARCHAR2,
2841     p_load_ci_start_dt    OUT NOCOPY   DATE,
2842     p_load_ci_end_dt      OUT NOCOPY   DATE,
2843     p_message_name        OUT NOCOPY   VARCHAR2) AS
2844 ------------------------------------------------------------------
2845   --Created by  : RVANGALA, Oracle IDC
2846   --Date created: 16-JUL-2004
2847   --
2848   --Purpose:  To find the current Term Calendar for display of terms
2849   -- on the Schedule page
2850   --
2851   --
2852   --Known limitations/enhancements and/or remarks:
2853   --
2854   --Change History:
2855   --Who         When            What
2856   -------------------------------------------------------------------
2857 
2858   -- LOCAL VARIABLES
2859   cst_active                        CONSTANT VARCHAR2(10) := 'ACTIVE';
2860   cst_load                          CONSTANT VARCHAR2(10) := 'LOAD';
2861   l_cal_type                        IGS_EN_STDNT_PS_ATT.CAL_TYPE%TYPE;
2862   l_current_load_ci_alt_code IGS_CA_INST.ALTERNATE_CODE%TYPE;
2863   l_current_load_ci_start_dt IGS_CA_INST.START_DT%TYPE;
2864   l_current_load_ci_end_dt   IGS_CA_INST.END_DT%TYPE;
2865   l_current_load_cal_type           IGS_CA_INST.CAL_TYPE%TYPE;
2866   l_current_load_sequence_number    IGS_CA_INST.SEQUENCE_NUMBER%TYPE;
2867   l_other_detail                    VARCHAR2(255);
2868   l_effective_dt                    DATE;
2869 
2870     --
2871     --  CURSOR TO FETCH LOAD EFFECTIVE DATE ALIAS.
2872     --
2873     CURSOR
2874     c_s_enr_cal_conf IS
2875       SELECT  secc.load_effect_dt_alias
2876       FROM    igs_en_cal_conf secc
2877       WHERE   secc.s_control_num = 1;
2878 
2879     L_LOAD_EFFECT_DT_ALIAS IGS_EN_CAL_CONF.LOAD_EFFECT_DT_ALIAS%TYPE;
2880 
2881 	CURSOR c_acad_cal_instances (cp_acad_cal_type         igs_ca_inst.cal_type%TYPE) IS
2882 	SELECT cal_type, sequence_number
2883 	FROM IGS_CA_INST
2884 	WHERE CAL_TYPE = cp_acad_cal_type
2885 	ORDER BY start_dt DESC;
2886 
2887 	lb_found_load_rec Boolean;
2888 
2889     --
2890     --  CURSOR TO FETCH CALENDAR TYPE INSTANCES
2891     --
2892     CURSOR c_cal_type_instance (cp_acad_cal_type         igs_ca_inst.cal_type%TYPE,
2893 	                            cp_acad_ci_sequence_number igs_ca_inst.sequence_number%TYPE) IS
2894       SELECT   ci.cal_type,
2895                ci.sequence_number,
2896 	       ci.alternate_code,
2897                ci.start_dt,
2898                ci.end_dt
2899       FROM     igs_ca_type ct,
2900                igs_ca_inst ci,
2901                igs_ca_stat cs,
2902                igs_ca_inst_rel cir
2903       WHERE    cs.s_cal_status = cst_active
2904       AND      ci.cal_status = cs.cal_status
2905       AND      ct.s_cal_cat = cst_load
2906       AND      ci.cal_type = ct.cal_type
2907       AND      CIR.SUB_CAL_TYPE = CI.CAL_TYPE
2908       AND      cir.sub_ci_sequence_number =ci.sequence_number
2909       AND      cir.sup_cal_type = cp_acad_cal_type
2910 	  AND      cir.sup_ci_sequence_number = cp_acad_ci_sequence_number
2911       ORDER BY ci.start_dt DESC;
2912 
2913     --
2914     --  CURSOR TO FETCH THE DATE ALIAS
2915     --
2916     CURSOR c_dai_v (cp_cal_type             igs_ca_da_inst_v.cal_type%TYPE,
2917                     cp_ci_sequence_number   igs_ca_da_inst_v.ci_sequence_number%TYPE,
2918                     cp_load_effect_dt_alias igs_en_cal_conf.load_effect_dt_alias%TYPE) IS
2919       SELECT   daiv.alias_val
2920       FROM     igs_ca_da_inst_v daiv
2921       WHERE    daiv.cal_type = cp_cal_type
2922       AND      daiv.ci_sequence_number = cp_ci_sequence_number
2923       AND      daiv.dt_alias = cp_load_effect_dt_alias;
2924 
2925    -- Cursor to fetch load calendar with earliest start date
2926    -- and whose start_date and end_date encompass the SYSDATE
2927     CURSOR c_first_cal_instance (cp_cal_type         igs_ca_inst.cal_type%TYPE) IS
2928       SELECT   ci.cal_type,
2929                ci.sequence_number,
2930 	       ci.alternate_code,
2931                ci.start_dt,
2932                ci.end_dt
2933       FROM     igs_ca_type ct,
2934                igs_ca_inst ci,
2935                igs_ca_stat cs,
2936                igs_ca_inst_rel cir
2937       WHERE    cs.s_cal_status = cst_active
2938       AND      ci.cal_status = cs.cal_status
2939       AND      ct.s_cal_cat = cst_load
2940       AND      ci.cal_type = ct.cal_type
2941       AND      CIR.SUB_CAL_TYPE = CI.CAL_TYPE
2942       AND      cir.sub_ci_sequence_number =ci.sequence_number
2943       AND      cir.sup_cal_type = cp_cal_type
2944       AND      ci.start_dt <= SYSDATE
2945 	  AND      ci.end_dt   >= SYSDATE
2946   	  ORDER BY ci.start_dt;
2947 
2948   l_load_alias_value igs_ca_da_inst.absolute_val%TYPE;
2949 
2950   BEGIN
2951 
2952     --fetch load effective date alias from enrollment calendar configuration
2953     OPEN c_s_enr_cal_conf;
2954     FETCH c_s_enr_cal_conf INTO l_load_effect_dt_alias;
2955     IF c_s_enr_cal_conf%NOTFOUND THEN
2956        CLOSE c_s_enr_cal_conf;
2957        p_message_name := 'IGS_EN_NO_SECC_REC_FOUND';
2958        RETURN;
2959     END IF;
2960     CLOSE c_s_enr_cal_conf;
2961     --
2962     -- initialise the local variables
2963     --
2964     l_current_load_cal_type := NULL;
2965     l_current_load_sequence_number := NULL;
2966     l_current_load_ci_start_dt := NULL;
2967     l_current_load_ci_end_dt := NULL;
2968     l_current_load_ci_alt_code := NULL;
2969 
2970     lb_found_load_rec := FALSE;
2971 
2972 
2973 	FOR rec_acad_cal_instances in c_acad_cal_instances( p_acad_cal_type)
2974 	LOOP
2975              --
2976              -- now loop through the cal type instance records
2977              -- starting the load calendar instances with the latest start date
2978              FOR rec_cal_type_instance IN c_cal_type_instance (rec_acad_cal_instances.cal_type, rec_acad_cal_instances.sequence_number)
2979              LOOP
2980                  --
2981                  -- attempt to find load effective date alias against the load cal isntance
2982                  --
2983 
2984                  FOR rec_dai_v IN c_dai_v (rec_cal_type_instance.cal_type,
2985                                            rec_cal_type_instance.sequence_number,
2986                                            l_load_effect_dt_alias)
2987                  LOOP
2988 
2989                      IF (p_effective_dt >= rec_dai_v.alias_val) THEN
2990                          l_current_load_cal_type := rec_cal_type_instance.cal_type ;
2991                          l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
2992                          l_current_load_ci_start_dt := rec_cal_type_instance.start_dt;
2993                          l_current_load_ci_end_dt := rec_cal_type_instance.end_dt;
2994                          l_current_load_ci_alt_code := rec_cal_type_instance.alternate_code;
2995                      END IF;
2996                  END LOOP;
2997 
2998                  --if a load calendar instance with satisfying date alias value is found
2999                  IF l_current_load_cal_type IS NOT NULL THEN
3000                       lb_found_load_rec := TRUE;
3001                       EXIT;
3002                  END IF;
3003              END LOOP;
3004 
3005         -- if the term calendar has been determined in the inner loop then
3006 	-- exit out of the this loop as well.
3007 	IF lb_found_load_rec THEN
3008 	     EXIT;
3009 	END IF;
3010 
3011     END LOOP;
3012 
3013     IF l_current_load_cal_type IS NULL THEN
3014       --new logic goes in here
3015       --fetch the load calendar instance with the earliest start date and
3016       --whose start_date<SYSDATE and end_date>SYSDATE
3017       OPEN c_first_cal_instance(p_acad_cal_type);
3018       FETCH c_first_cal_instance INTO  p_load_cal_type,p_load_ci_seq_num,
3019                                        p_load_ci_alt_code,
3020                                        p_load_ci_start_dt,p_load_ci_end_dt;
3021 
3022        --if no load calendar is found whose start_date<SYSDATE
3023        --and end_date>SYSDATE
3024        IF c_first_cal_instance%NOTFOUND THEN
3025            p_load_cal_type    := NULL;
3026            p_load_ci_seq_num  := NULL;
3027            p_load_ci_alt_code   := NULL ;
3028            p_load_ci_start_dt   := NULL;
3029            p_load_ci_end_dt     := NULL;
3030            p_message_name := 'IGS_EN_LOAD_CAL_NOT_FOUND';
3031        END IF;
3032        CLOSE c_first_cal_instance;
3033 
3034     ELSE
3035       p_load_cal_type     := l_current_load_cal_type;
3036       p_load_ci_seq_num   := l_current_load_sequence_number;
3037       p_load_ci_alt_code   := l_current_load_ci_alt_code ;
3038       p_load_ci_start_dt   := l_current_load_ci_start_dt;
3039       p_load_ci_end_dt     := l_current_load_ci_end_dt  ;
3040     END IF;
3041 
3042   EXCEPTION
3043     WHEN OTHERS THEN
3044         FND_MESSAGE.SET_NAME('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
3045         FND_MESSAGE.SET_TOKEN('NAME','IGS_EN_GEN_015.GET_CURR_ACAD_TERM_CAL');
3046         IGS_GE_MSG_STACK.ADD;
3047         APP_EXCEPTION.RAISE_EXCEPTION;
3048 
3049   END get_curr_term_for_schedule;
3050 
3051   PROCEDURE get_academic_cal_poo_chg
3052   (
3053     p_person_id                       IN     NUMBER,
3054     p_course_cd                       IN     VARCHAR2,
3055     p_acad_cal_type                  IN OUT NOCOPY     VARCHAR2,
3056     p_acad_ci_sequence_number        OUT NOCOPY     NUMBER,
3057     p_message                        OUT NOCOPY     VARCHAR2,
3058     p_effective_dt                   IN      DATE
3059   ) AS
3060     -- Determine the academic calendar instance based on parameter p_acad_cal_type.
3061     --
3062     --  Parameters Description:
3063     --
3064     --  p_person_id                     -> Person Identifier
3065     --  p_course_cd                     -> Program code
3066     --  p_acad_cal_type                 -> IN Out NOCOPY parameter carrying the academic calendar type
3067     --  p_acad_ci_sequence_number       -> Out NOCOPY parameter carrying academic calendar sequence number
3068     --
3069     --
3070     --  local variable used in the program unit
3071     --
3072     NO_SECC_RECORD_FOUND              EXCEPTION;
3073     cst_active                        CONSTANT VARCHAR2(10) := 'ACTIVE';
3074     cst_load                          CONSTANT VARCHAR2(10) := 'LOAD';
3075     cst_academic                      CONSTANT VARCHAR2(10) := 'ACADEMIC';
3076     l_daiv_rec_found                  BOOLEAN;
3077     l_cal_type                        igs_en_stdnt_ps_att.cal_type%TYPE;
3078     l_load_effect_dt_alias            igs_en_cal_conf.load_effect_dt_alias%TYPE;
3079     l_current_load_cal_type           igs_ca_inst.cal_type%TYPE;
3080     l_current_load_sequence_number    igs_ca_inst.sequence_number%TYPE;
3081     l_current_acad_cal_type           igs_ca_inst.cal_type%TYPE;
3082     l_current_acad_sequence_number    igs_ca_inst.sequence_number%TYPE;
3083     l_other_detail                    VARCHAR2(255);
3084     l_effective_dt                    DATE;
3085     --
3086     --  Cursor to fetch student course attempt calendar type
3087     --
3088     CURSOR c_stu_crs_atmpt (cp_person_id     igs_en_stdnt_ps_att.person_id%TYPE,
3089                             cp_course_cd     igs_en_stdnt_ps_att.course_cd%TYPE) IS
3090       SELECT  sca.cal_type
3091       FROM    igs_en_stdnt_ps_att sca
3092       WHERE   sca.person_id = cp_person_id
3093       AND     sca.course_cd = cp_course_cd;
3094     --
3095     --  Cursor to fetch load effective date alias.
3096     --
3097     CURSOR c_s_enr_cal_conf IS
3098       SELECT  secc.load_effect_dt_alias
3099       FROM    igs_en_cal_conf secc
3100       WHERE   secc.s_control_num = 1;
3101     --
3102     --  Cursor to fetch calendar instances
3103     --
3104     CURSOR c_cal_instance (cp_cal_type      igs_ca_inst.cal_type%TYPE,
3105                            cp_effective_dt  igs_ca_inst.start_dt%TYPE) IS
3106       SELECT   ci.cal_type,
3107                ci.sequence_number
3108       FROM     igs_ca_inst ci,
3109                igs_ca_stat cs
3110       WHERE    ci.cal_type = cp_cal_type
3111       AND      ci.start_dt <= cp_effective_dt
3112       AND      ci.end_dt >= cp_effective_dt
3113       AND      cs.cal_status = ci.cal_status
3114       AND      cs.s_cal_status = cst_active
3115       ORDER BY ci.start_dt DESC;
3116     --
3117     --  Cursor to fetch calendar type instances
3118     --
3119     CURSOR c_cal_type_instance (cp_cal_type         igs_ca_inst.cal_type%TYPE,
3120                                 cp_sequence_number  igs_ca_inst.sequence_number%TYPE) IS
3121       SELECT   ci.cal_type,
3122                ci.sequence_number,
3123                ci.start_dt,
3124                ci.end_dt
3125       FROM     igs_ca_type ct,
3126                igs_ca_inst ci,
3127                igs_ca_stat cs,
3128                igs_ca_inst_rel cir
3129       WHERE    ct.closed_ind = 'N'
3130       AND      cs.s_cal_status = cst_active
3131       AND      ci.cal_status = cs.cal_status
3132       AND      ct.s_cal_cat = cst_load
3133       AND      ci.cal_type = ct.cal_type
3134       AND      cir.sub_cal_type = ci.cal_type
3135       AND      cir.sub_ci_sequence_number =ci.sequence_number
3136       AND      cir.sup_cal_type = cp_cal_type
3137       AND      cir.sup_ci_sequence_number = cp_sequence_number
3138       AND EXISTS ( SELECT   1     FROM     igs_ca_inst_rel cir,
3139                                                 igs_ca_type ct
3140                                        WHERE    cir.sup_cal_type = cp_cal_type
3141                                        AND      cir.sup_ci_sequence_number = cp_sequence_number
3142                                        AND      cir.sub_cal_type = ci.cal_type
3143                                        AND      cir.sub_ci_sequence_number = ci.sequence_number
3144                                        AND      ct.cal_type = cir.sup_cal_type
3145                                        AND      ct.s_cal_cat = cst_academic)
3146      ORDER BY ci.start_dt DESC;
3147     --
3148     --  Cursor to fetch the date alias
3149     --
3150     CURSOR c_dai_v (cp_cal_type             igs_ca_da_inst_v.cal_type%TYPE,
3151                     cp_ci_sequence_number   igs_ca_da_inst_v.ci_sequence_number%TYPE,
3152                     cp_load_effect_dt_alias igs_en_cal_conf.load_effect_dt_alias%TYPE) IS
3153       SELECT   daiv.alias_val
3154       FROM     igs_ca_da_inst_v daiv
3155       WHERE    daiv.cal_type = cp_cal_type
3156       AND      daiv.ci_sequence_number = cp_ci_sequence_number
3157       AND      daiv.dt_alias = cp_load_effect_dt_alias;
3158   --
3159   BEGIN
3160 
3161     -- This statement is added in ENCR015 build ( Bug ID : 2158654)
3162     -- Initialize the l_effective_date with the Effective Date Value passed to this Procedure as Parameter
3163     l_effective_dt := p_effective_dt;
3164 
3165 	--
3166     --  The attendance type is derived based on the load calendar instances, using
3167     --  the load effective date alias as the reference point for determining
3168     --  which calendar is the current load_calendar.
3169     --  Load the student IGS_PS_COURSE attempt details.
3170     --
3171     OPEN c_stu_crs_atmpt (p_person_id,
3172                           p_course_cd);
3173     FETCH c_stu_crs_atmpt INTO l_cal_type;
3174     IF (c_stu_crs_atmpt%NOTFOUND) THEN
3175        --
3176        -- if not data found return from the program unit
3177        --
3178        CLOSE c_stu_crs_atmpt;
3179        p_message := 'IGS_EN_NO_CRS_ATMPT';
3180        RETURN;
3181     END IF;
3182     CLOSE c_stu_crs_atmpt;
3183 
3184 	IF (p_acad_cal_type IS NOT NULL) THEN
3185 		l_cal_type := p_acad_cal_type;
3186 	END IF;
3187     --
3188     -- Cetermine the 'current' load calendar instance based on the load effective
3189     -- date alias from the enrolment calendar configuration. If this date alias
3190     -- can't be located then the latest calendar instance where start_dt/end_dt
3191     -- encompass the effective dt is deemed current
3192     --
3193     OPEN c_s_enr_cal_conf;
3194     FETCH c_s_enr_cal_conf INTO l_load_effect_dt_alias;
3195     IF c_s_enr_cal_conf%NOTFOUND THEN
3196        CLOSE c_s_enr_cal_conf;
3197        p_message := 'IGS_EN_NO_SECC_REC_FOUND';
3198        RETURN;
3199     END IF;
3200     CLOSE c_s_enr_cal_conf;
3201     --
3202     -- initialise the local variables
3203     --
3204     l_current_load_cal_type := NULL;
3205     l_current_load_sequence_number := NULL;
3206     l_current_acad_cal_type := NULL;
3207     l_current_acad_sequence_number := NULL;
3208     --
3209     -- loop through the records fetched for calendar instances
3210     --
3211     FOR rec_cal_instance IN c_cal_instance (l_cal_type, l_effective_dt)
3212     LOOP
3213         --
3214         -- now loop through the cal type instance records
3215         --
3216         FOR rec_cal_type_instance IN c_cal_type_instance (rec_cal_instance.cal_type,
3217                                                           rec_cal_instance.sequence_number)
3218         LOOP
3219             --
3220             -- Attempt to find load effective date alias against the cale
3221             --
3222             l_daiv_rec_found := FALSE;
3223             FOR rec_dai_v IN c_dai_v (rec_cal_type_instance.cal_type,
3224                                       rec_cal_type_instance.sequence_number,
3225                                       l_load_effect_dt_alias)
3226             LOOP
3227                 l_daiv_rec_found := TRUE;
3228                 IF (l_effective_dt >= rec_dai_v.alias_val) THEN
3229                     l_current_load_cal_type := rec_cal_type_instance.cal_type ;
3230                     l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
3231                     l_current_acad_cal_type := rec_cal_instance.cal_type;
3232                     l_current_acad_sequence_number := rec_cal_instance.sequence_number;
3233                 END IF;
3234             END LOOP;
3235             IF NOT l_daiv_rec_found  THEN
3236                IF (l_effective_dt >= rec_cal_type_instance.start_dt) AND
3237                    (l_effective_dt <= rec_cal_type_instance.end_dt) THEN
3238                     l_current_load_cal_type := rec_cal_type_instance.cal_type ;
3239                     l_current_load_sequence_number := rec_cal_type_instance.sequence_number;
3240                     l_current_acad_cal_type := rec_cal_instance.cal_type;
3241                     l_current_acad_sequence_number := rec_cal_instance.sequence_number;
3242                END IF;
3243             END IF;
3244         END LOOP;
3245         IF l_current_load_cal_type IS NOT NULL THEN
3246            EXIT;
3247         END IF;
3248     END LOOP;
3249     IF l_current_load_cal_type IS NULL THEN
3250        p_acad_cal_type := NULL;
3251     END IF;
3252     p_acad_cal_type := l_current_acad_cal_type;
3253     p_acad_ci_sequence_number := l_current_acad_sequence_number;
3254     p_message := NULL;
3255   END get_academic_cal_poo_chg;
3256 PROCEDURE enrp_get_eff_load_ci_poo_chg (
3257     p_person_id           IN    NUMBER,
3258     p_course_cd           IN    VARCHAR2,
3259     p_effective_dt        IN    DATE,
3260     p_acad_cal_type       IN OUT NOCOPY  VARCHAR2,
3261     p_acad_ci_seq_num     OUT NOCOPY   NUMBER,
3262     p_load_cal_type       OUT NOCOPY   VARCHAR2,
3263     p_load_ci_seq_num     OUT NOCOPY   NUMBER,
3264     p_load_ci_alt_code    OUT NOCOPY   VARCHAR2,
3265     p_load_ci_start_dt    OUT NOCOPY   DATE,
3266     p_load_ci_end_dt      OUT NOCOPY   DATE,
3267     p_message_name        OUT NOCOPY   VARCHAR2) AS
3268 
3269   /*
3270   ||  Created By : Susmitha Tutta
3271   ||  Created On : 27-JUL-2005
3272   ||  Purpose : To find the Effective Load Calendar Instance for a passed in academic calendar type
3273   ||  Known limitations, enhancements or remarks :
3274   ||  Change History :
3275   ||  Who             When            What
3276   ||  (reverse chronological order - newest change first)
3277   */
3278 
3279     --
3280     --  Cursor to fetch student course attempt calendar type
3281     --
3282     CURSOR c_stu_crs_atmpt (cp_person_id     igs_en_stdnt_ps_att.person_id%TYPE,
3283                             cp_course_cd     igs_en_stdnt_ps_att.course_cd%TYPE) IS
3284       SELECT  sca.cal_type
3285       FROM    igs_en_stdnt_ps_att sca
3286       WHERE   sca.person_id = cp_person_id
3287       AND     sca.course_cd = cp_course_cd;
3288 
3289    -- Local Variables
3290    l_cal_type                        igs_en_stdnt_ps_att.cal_type%TYPE;
3291    l_message VARCHAR2(100);
3292 
3293    BEGIN
3294 
3295     --
3296     --  The attendance type is derived based on the load calendar instances, using
3297     --  the load effective date alias as the reference point for determining
3298     --  which calendar is the current load_calendar.
3299     --  Load the student IGS_PS_COURSE attempt details.
3300     --
3301 
3302     OPEN c_stu_crs_atmpt (p_person_id,
3303                           p_course_cd);
3304     FETCH c_stu_crs_atmpt INTO l_cal_type;
3305     IF (c_stu_crs_atmpt%NOTFOUND) THEN
3306        --
3307        -- if not data found return from the program unit
3308        --
3309        CLOSE c_stu_crs_atmpt;
3310        p_message_name := 'IGS_EN_NO_CRS_ATMPT';
3311        RETURN;
3312     END IF;
3313     CLOSE c_stu_crs_atmpt;
3314 	IF (p_acad_cal_type IS NOT NULL) THEN
3315 		l_cal_type := p_acad_cal_type;
3316 	END IF;
3317     --
3318     -- Get the current Academic Calendar instance for the academic cal type passed in.
3319     --
3320     get_academic_cal_poo_chg
3321       (
3322         p_person_id                => p_person_id,
3323         p_course_cd                => p_course_cd ,
3324         p_acad_cal_type            => p_acad_cal_type,
3325         p_acad_ci_sequence_number  => p_acad_ci_seq_num,
3326         p_message                  => l_message,
3327         p_effective_dt             => p_effective_dt
3328       );
3329 
3330     IF l_message IS NOT NULL THEN
3331       p_message_name := l_message;
3332       RETURN;
3333     END IF;
3334 
3335     --
3336     -- determine the 'current' load calendar instance based on the load effective
3337     -- date alias from the enrolment calendar configuration. If this date alias
3338     -- can't be located then the latest calendar instance where start_dt/end_dt
3339     -- encompass the effective dt is deemed current
3340     --
3341     get_curr_acad_term_cal (
3342             l_cal_type,
3343             p_effective_dt,
3344             p_load_cal_type,
3345             p_load_ci_seq_num,
3346             p_load_ci_alt_code,
3347             p_load_ci_start_dt,
3348             p_load_ci_end_dt,
3349             p_message_name);
3350 
3351   EXCEPTION
3352     WHEN OTHERS THEN
3353         fnd_message.Set_Name('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
3354         fnd_message.Set_Token('NAME','IGS_EN_GEN_015.enrp_get_eff_load_ci_poo_chg');
3355         IGS_GE_MSG_STACK.ADD;
3356         App_Exception.Raise_Exception;
3357 
3358   END enrp_get_eff_load_ci_poo_chg;
3359 
3360 
3361 
3362 END igs_en_gen_015;