DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_EN_ELGBL_UNIT

Source


1 PACKAGE BODY IGS_EN_ELGBL_UNIT AS
2 /* $Header: IGSEN80B.pls 120.23 2006/08/24 07:31:50 bdeviset ship $ */
3 
4 --  This function gets the coreq units for the passsed uoo_id
5 -- and add quotes so that the string containing units can be used in
6 -- sql statement
7 FUNCTION  get_coreq_units(p_uoo_id IN NUMBER)
8 RETURN VARCHAR2 AS
9 
10 l_unit_cds VARCHAR2(500);
11 l_unit_cd VARCHAR2(12);
12 l_ret_unit_cds VARCHAR2(500);
13 
14 BEGIN
15 
16 l_unit_cds := igs_ss_enr_details.Get_coreq_units(p_uoo_id);
17 
18 WHILE l_unit_cds IS NOT NULL LOOP
19 
20   IF (instr(l_unit_cds,',',1)) = 0 THEN
21     l_unit_cd := l_unit_cds;
22     l_unit_cds := NULL;
23   ELSE
24      -- get the unit cd for formatting
25     l_unit_cd := substr(l_unit_cds,1,instr(l_unit_cds,',')-1);
26       -- remove the unit cd from the string
27     l_unit_cds := substr(l_unit_cds,instr(l_unit_cds,',')+1);
28 
29   END IF;
30 
31   -- add auotes to unit cd for it to be used in sql statement
32   l_unit_cd := ''''||l_unit_cd||'''';
33 
34   IF l_ret_unit_cds IS NULL THEN
35     l_ret_unit_cds := l_unit_cd;
36   ELSE
37     l_ret_unit_cds := l_ret_unit_cds||','||l_unit_cd;
38   END IF;
39 
40 END LOOP;
41 
42 RETURN   l_ret_unit_cds;
43 
44 END get_coreq_units;
45 
46 FUNCTION eval_unit_steps(
47 p_person_id IN NUMBER,
48 p_person_type IN VARCHAR2,
49 p_load_cal_type IN VARCHAR2,
50 p_load_sequence_number IN VARCHAR2,
51 p_uoo_id  IN NUMBER,
52 p_course_cd IN VARCHAR2,
53 p_course_version IN NUMBER,
54 p_enrollment_category IN VARCHAR2,
55 p_enr_method_type IN VARCHAR2,
56 p_comm_type IN VARCHAR2,
57 p_message OUT NOCOPY VARCHAR2,
58 p_deny_warn OUT NOCOPY VARCHAR2,
59 p_calling_obj IN      VARCHAR2
60 ) RETURN BOOLEAN AS
61 
62 --------------------------------------------------------------------------------
63   --Created by  : knaraset ( Oracle IDC)
64   --Date created: 21-JUN-2001
65   --
66   --Purpose: This function will validate all the unit steps defined for the given combination of
67   --         Enrollment Category, Enrollment Method and Commencement Type against the given Student
68   --         Unit Attempt. If any unit step validation fails and if notification flag is DENY
69   --         then stop validation of further unit steps(exception for Co-Req) and
70   --             return FALSE with notification flag and message(s)
71   --
72   --Known limitations/enhancements and/or remarks:
73   --
74   --Change History:
75   --Who         When            What
76   --jbegum      25-jun-03       BUG#2930935
77   --                            Modified the cursor c_unit_aud_att.
78   --ayedubat    11-APR-2002    Changed the Dynamic SQL Statement storing in l_step_def_query variable to add an extra 'OR'
79   --                           condition(eru.s_student_comm_type = 'ALL') for s_student_comm_type as part of the bug fix: 2315245
80   -- smanglm   14/08/2001    removed the check for system_type = SS_ENROLL_STAFF so
81   --                         that query can be made for all possible person type
82   -- pradhakr   27-Oct-2002  Added logic to check whether the Unit Section exists in Cross Listed /
83   --                         Meet With classes group. If it exists then by pass the reserve seating
84   --                         validation. Added as part of En Cross List / Meet With build.
85   --                         Bug# 2599929.
86   --Nishikant    01NOV2002   SEVIS Build. Enh Bug#2641905. notification flag was
87   --                         being fetched from REF cursor, now modified to get it by
88   --                         calling the function igs_ss_enr_details.get_notification.
89   --myoganat   12-JUN-2003  Modified the cursor c_audit_sua by adding a clause to check for the statuses of the unit section attempts
90   --                                          As part of Bug#  2855870 (ENCR032 Build)
91   --bdeviset   20-JUL-2006  While calling eval_intmsn_unit_lvl and eval_visa_unit_lvl in eval_units_steps
92   --                        passed l_calling_obj instead of p_calling_obj inorder to avoid logging
93   --                        warning msg when called from 'REINSTATE' and instead return a message
94   --                        Bug# 5306874
95   ------------------------------------------------------------------------------
96 
97   CURSOR cur_sys_pers_type(p_person_type_code VARCHAR2) IS
98   SELECT system_type
99   FROM igs_pe_person_types
100   WHERE person_type_code = p_person_type_code;
101 
102   -- Cursor to check whether unit is attempted for audit
103   CURSOR c_unit_aud_att IS
104   SELECT sua.no_assessment_ind,
105          sua.unit_attempt_status,
106          NVL(sua.override_enrolled_cp,NVL(cps.enrolled_credit_points,uv.enrolled_credit_points)) credit_points
107   FROM igs_en_su_attempt sua,
108        igs_ps_unit_ver uv ,
109        igs_ps_usec_cps cps
110   WHERE sua.person_id   = p_person_id
111   AND   sua.course_cd   = p_course_cd
112   AND   sua.uoo_id      = p_uoo_id
113   AND   sua.unit_cd     = uv.unit_cd
114   AND   sua.version_number = uv.version_number
115   AND   sua.uoo_id         = cps.uoo_id(+);
116 
117 
118   --  Cursor to select the number of auditors for the given unit
119   CURSOR   c_usec_audit_lim IS
120   SELECT   NVL (usec.max_auditors_allowed, NVL(uv.max_auditors_allowed,999999) )
121   FROM     igs_ps_usec_lim_wlst usec,
122            igs_ps_unit_ver uv,
123            igs_ps_unit_ofr_opt uoo
124   WHERE    uoo.unit_cd          = uv.unit_cd
125   AND      uoo.version_number   = uv.version_number
126   AND      uoo.uoo_id           = usec.uoo_id (+)
127   AND      uoo.uoo_id           = p_uoo_id;
128 
129   CURSOR c_audit_sua IS
130   SELECT COUNT(*)
131   FROM igs_en_su_attempt
132   WHERE uoo_id=p_uoo_id
133   AND  no_assessment_ind = 'Y' -- For Audit TD Bug 2641864
134   AND (( p_calling_obj <> 'PLAN' AND unit_attempt_status IN ('ENROLLED', 'COMPLETED','INVALID','UNCONFIRM')  ) OR
135              (p_calling_obj = 'PLAN' AND unit_attempt_status IN ('ENROLLED', 'COMPLETED','INVALID','UNCONFIRM','PLANNED') )
136   OR (unit_attempt_status = 'WAITLISTED' AND FND_PROFILE.VALUE('IGS_EN_VAL_WLST')  ='Y'));
137 
138 
139 
140   TYPE step_rec IS RECORD(
141     s_enrolment_step_type  igs_en_cpd_ext.s_enrolment_step_type%TYPE ,
142     enrolment_cat          igs_en_cpd_ext.enrolment_cat%TYPE,
143     s_student_comm_type    igs_en_cpd_ext.s_student_comm_type%TYPE,
144     enr_method_type        igs_en_cpd_ext.enr_method_type%TYPE,
145     step_group_type        igs_lookups_view.step_group_type%TYPE,
146     s_rule_call_cd         igs_en_cpd_ext.s_rule_call_cd%TYPE,
147     rul_sequence_number    igs_en_cpd_ext.rul_sequence_number%TYPE,
148     stud_audit_lim         igs_en_cpd_ext.stud_audit_lim%TYPE); -- added for Audit build
149 
150   TYPE cur_step_def IS REF CURSOR;
151 
152   cur_step_def_var cur_step_def; -- REF cursor variable
153   cur_step_def_var_rec step_rec;
154 
155   l_system_type         igs_pe_person_types.system_type%TYPE;
156   l_message             VARCHAR2(30);
157   l_usec_status         igs_ps_unit_ofr_opt.unit_section_status%TYPE;
158   l_waitlist_ind        VARCHAR2(1);
159   l_step_def_query      VARCHAR2(2000);
160   l_repeat_tag          VARCHAR2(1);
161   l_assessment_ind      VARCHAR2(1);
162   l_usec_audit_lim      NUMBER;
163   l_audit_sua           NUMBER;
164   -- Cursor to check whether the unit section belongs to any cross-listed group or not.
165   CURSOR c_cross_list(l_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
166   SELECT 'x'
167   FROM igs_ps_usec_x_grpmem
168   WHERE uoo_id = l_uoo_id;
169 
170   -- Cursor to check whether the unit section belongs to any Meet with class group.
171   CURSOR c_class_meet (l_uoo_id igs_ps_unit_ofr_opt.uoo_id%TYPE) IS
172   SELECT 'x'
173   FROM igs_ps_uso_clas_meet
174   WHERE uoo_id = l_uoo_id;
175 
176   l_cross_list c_cross_list%ROWTYPE;
177   l_class_meet c_class_meet%ROWTYPE;
178   l_usec_partof_group BOOLEAN;
179   l_notification_flag       igs_en_cpd_ext.notification_flag%TYPE; --added by nishikant
180   l_unit_attempt_status igs_en_su_attempt_all.unit_attempt_status%TYPE;
181   l_credit_points  igs_ps_unit_ver.enrolled_credit_points%type;
182   l_deny_unit_steps BOOLEAN;
183   l_warn_unit_steps BOOLEAN;
184   l_message_icon    VARCHAR2(1);
185   l_unit_sec        VARCHAR2(100);
186   l_calling_obj      VARCHAR2(2000);
187   l_deny_enrollment         VARCHAR2(1);
188 BEGIN
189 
190   l_usec_partof_group := FALSE;
191 
192   OPEN cur_sys_pers_type(p_person_type);
193   FETCH cur_sys_pers_type INTO l_system_type;
194   CLOSE cur_sys_pers_type;
195 
196     IF p_calling_obj IN ('REINSTATE','JOB_FROM_WAITLIST') THEN
197    l_calling_obj := 'JOB'; --l_calling_obj is used to pass to the validation procedures as the job
198                            --validations and reinstate validation is same.
199   ELSE
200    l_calling_obj := p_calling_obj;
201   END IF;
202 
203   -- Check whether the unit section belongs to any cross listed group /  Meet With Class group.
204   -- if it is a part of these group then set the variable l_usec_partof_group to TRUE.
205   --
206   OPEN c_cross_list(p_uoo_id);
207   FETCH c_cross_list INTO l_cross_list;
208 
209   IF c_cross_list%FOUND THEN
210      l_usec_partof_group := TRUE;
211 
212   ELSE
213     OPEN c_class_meet(p_uoo_id);
214     FETCH c_class_meet INTO l_class_meet;
215 
216     IF c_class_meet%FOUND THEN
217        l_usec_partof_group := TRUE;
218     END IF;
219     CLOSE c_class_meet;
220 
221   END IF;
222   CLOSE c_cross_list;
223 
224 
225   -- if the user log on is a student
226   IF l_system_type = 'STUDENT' THEN
227 
228      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,
229                               eru.s_rule_call_cd,eru.rul_sequence_number,eru.stud_audit_lim
230                              FROM igs_en_cpd_ext eru, igs_lookups_view lkv
231                                                  WHERE eru.s_enrolment_step_type =lkv.lookup_code AND
232                                                  lkv.lookup_type = ''ENROLMENT_STEP_TYPE_EXT'' AND lkv.step_group_type =
233                                                  ''UNIT'' AND eru.enrolment_cat = :1 AND eru.enr_method_type = :2
234                                                  AND ( eru.s_student_comm_type = :3 OR eru.s_student_comm_type = ''ALL'')
235                                                  ORDER BY eru.step_order_num';
236 
237   OPEN cur_step_def_var FOR l_step_def_query USING p_enrollment_category, p_enr_method_type, p_comm_type;
238 
239   ELSE
240   --IF l_system_type = 'SS_ENROLL_STAFF' THEN -- if the log on user is self service enrollment staff
241   -- removed the check so as to prepare the query for person type other than STUDENT and SS_ENROLL_STAFF also
242 
243      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,
244                               eru.s_rule_call_cd,eru.rul_sequence_number,eru.stud_audit_lim
245                              FROM igs_en_cpd_ext eru, igs_pe_usr_aval uact, igs_lookups_view lkv
246                                                  WHERE eru.s_enrolment_step_type =lkv.lookup_code AND
247                                                  lkv.lookup_type = ''ENROLMENT_STEP_TYPE_EXT'' AND lkv.step_group_type = ''UNIT'' AND
248                                                  eru.s_enrolment_step_type = uact.validation(+) AND
249                                                  uact.person_type(+) = :1 AND NVL(uact.override_ind,''N'') = ''N'' AND
250                                                  eru.enrolment_cat = :2 AND eru.enr_method_type = :3
251                                                  AND ( eru.s_student_comm_type = :4 OR eru.s_student_comm_type = ''ALL'')
252                                                  ORDER BY eru.step_order_num';
253 
254   OPEN cur_step_def_var FOR l_step_def_query USING p_person_type, p_enrollment_category, p_enr_method_type, p_comm_type;
255 
256   END IF;
257 
258   -- Check whether the student attempted the unit for Audit
259   OPEN c_unit_aud_att;
260   FETCH c_unit_aud_att INTO l_assessment_ind , l_unit_attempt_status ,l_credit_points;
261   CLOSE c_unit_aud_att;
262 
263   <<loop_unit_steps >> -- loop lable
264   LOOP
265      FETCH cur_step_def_var INTO cur_step_def_var_rec;
266 
267         EXIT WHEN cur_step_def_var%NOTFOUND;
268              l_message := NULL;
269              l_notification_flag := NULL;
270              l_notification_flag  :=  igs_ss_enr_details.get_notification(
271                                        p_person_type         => p_person_type,
272                                        p_enrollment_category => cur_step_def_var_rec.enrolment_cat,
273                                        p_comm_type           => cur_step_def_var_rec.s_student_comm_type,
274                                        p_enr_method_type     => cur_step_def_var_rec.enr_method_type,
275                                        p_step_group_type     => cur_step_def_var_rec.step_group_type,
276                                        p_step_type           => cur_step_def_var_rec.s_enrolment_step_type,
277                                        p_person_id           => p_person_id,
278                                        p_message             => l_message);
279              IF l_message IS NOT NULL THEN
280                 p_deny_warn := 'DENY';
281                 IF p_message IS NULL THEN
282                     p_message := l_message;
283                 ELSE
284                     p_message := p_message ||';'||l_message;
285                 END IF;
286                 RETURN FALSE;
287              END IF;
288 
289 --
290 -- validate the Enrollment Method Step
291 --This will not be called while reinstating the units from the schedule page.
292 --This method will be skipped while rinstating the unit.
293          IF cur_step_def_var_rec.s_enrolment_step_type = 'ENR_MTHD' AND p_calling_obj NOT IN('ENROLPEND', 'REINSTATE','JOB_FROM_WAITLIST')  THEN
294 
295             IF NOT eval_unit_ss_allowed (
296                      p_person_id                    => p_person_id,
297                      p_course_cd                    => p_course_cd,
298                      p_person_type                  => p_person_type,
299                      p_load_cal_type                => p_load_cal_type,
300                      p_load_sequence_number         => p_load_sequence_number,
301                      p_uoo_id                       => p_uoo_id,
302                      p_message                      => p_message,
303                      p_deny_warn                    => l_notification_flag,
304                      p_calling_obj                  => p_calling_obj
305                     ) THEN
306 
307                   IF l_notification_flag = 'DENY' THEN
308 
309                     l_deny_unit_steps := TRUE;
310 
311                     IF p_calling_obj = 'JOB' THEN
312                       p_deny_warn := l_notification_flag;
313                       RETURN FALSE;
314                     END IF;
315 
316                   ELSE
317                     l_warn_unit_steps := TRUE;
318                   END IF; -- IF l_notification_flag = 'DENY' THEN
319 
320             END IF; -- IF NOT eval_unit_ss_allowed
321 
322 --  validate the Program Check
323 --
324          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'PROG_CHK' THEN
325             IF NOT eval_program_check(
326                      p_person_id                    => p_person_id,
327                      p_load_cal_type                => p_load_cal_type,
328                      p_load_sequence_number         => p_load_sequence_number,
329                      p_uoo_id                       => p_uoo_id,
330                      p_course_cd                    => p_course_cd,
331                      p_course_version               => p_course_version,
332                      p_message                      => p_message,
333                      p_deny_warn                    => l_notification_flag,
334                      p_rule_seq_number              => cur_step_def_var_rec.rul_sequence_number,
335                      p_calling_obj                  => l_calling_obj
336                     ) THEN
337                 IF l_notification_flag = 'DENY' THEN
338 
339                   l_deny_unit_steps := TRUE;
340 
341                   IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
342                     p_deny_warn := l_notification_flag;
343                     RETURN FALSE;
344                   END IF;
345 
346                 ELSE
347                   l_warn_unit_steps := TRUE;
348                 END IF; -- IF l_notification_flag = 'DENY' THEN
349 
350              END IF;
351 --
352 -- validate the unit step Forced Location
353 --
354          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'FLOC_CHK' THEN
355             IF NOT eval_unit_forced_location(
356                      p_person_id                    => p_person_id,
357                      p_load_cal_type                => p_load_cal_type,
358                      p_load_sequence_number         => p_load_sequence_number,
359                      p_uoo_id                       => p_uoo_id,
360                      p_course_cd                    => p_course_cd,
361                      p_course_version               => p_course_version,
362                      p_message                      => p_message,
363                      p_deny_warn                    => l_notification_flag,
364                      p_calling_obj                  => l_calling_obj
365                     ) THEN
366                 IF l_notification_flag = 'DENY' THEN
367 
368                   l_deny_unit_steps := TRUE;
369 
370                   IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
371                     p_deny_warn := l_notification_flag;
372                     RETURN FALSE;
373                   END IF;
374 
375                 ELSE
376                   l_warn_unit_steps := TRUE;
377                 END IF; -- IF l_notification_flag = 'DENY' THEN
378 
379             END IF;
380 --
381 -- validate the unit step Forced Attendance Mode
382 --
383          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'FATD_MODE' THEN
384             IF NOT eval_unit_forced_mode(
385                      p_person_id                    => p_person_id,
386                      p_load_cal_type                => p_load_cal_type,
387                      p_load_sequence_number         => p_load_sequence_number,
388                      p_uoo_id                       => p_uoo_id,
389                      p_course_cd                    => p_course_cd,
390                      p_course_version               => p_course_version,
391                      p_message                      => p_message,
392                      p_deny_warn                    => l_notification_flag,
393                      p_calling_obj                  => l_calling_obj
394                     ) THEN
395                 IF l_notification_flag = 'DENY' THEN
396 
397                   l_deny_unit_steps := TRUE;
398 
399                   IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
400                     p_deny_warn := l_notification_flag;
401                     RETURN FALSE;
402                   END IF;
403 
404                 ELSE
405                   l_warn_unit_steps := TRUE;
406                 END IF; -- IF l_notification_flag = 'DENY' THEN
407 
408             END IF;
409 --
410 -- validate the unit step Unit Repeat
411 ----This will not be called while reinstating the units from the schedule page.
412 
413          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'REENROLL' AND p_calling_obj <> 'REINSTATE'  THEN
414             IF NOT eval_unit_reenroll (
415                  p_person_id                    => p_person_id,
416                      p_load_cal_type                => p_load_cal_type,
417                      p_load_cal_seq_number          => p_load_sequence_number,
418                      p_uoo_id                       => p_uoo_id,
419                      p_program_cd                   => p_course_cd,
420                      p_program_version              => p_course_version,
421                      p_message                      => p_message,
422                      p_deny_warn                    => l_notification_flag,
423                      p_upd_cp                      => l_credit_points,
424                      p_val_level               =>'ALL',
425                      p_calling_obj                  => l_calling_obj
426                     ) THEN
427                   IF l_notification_flag = 'DENY' THEN
428 
429                     l_deny_unit_steps := TRUE;
430 
431                     IF p_calling_obj IN ('JOB','JOB_FROM_WAITLIST') THEN
432                       p_deny_warn := l_notification_flag;
433                       RETURN FALSE;
434                     END IF;
435 
436                   ELSE
437                     l_warn_unit_steps := TRUE;
438                   END IF; -- IF l_notification_flag = 'DENY' THEN
439             END IF;
440 
441 --Unit repeat validation
442 --This will not be called while reinstating the units from the schedule page.
443 
444          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'UNIT_RPT' AND p_calling_obj <> 'REINSTATE' THEN
445             IF NOT eval_unit_repeat (
446                      p_person_id                    => p_person_id,
447                      p_load_cal_type                => p_load_cal_type,
448                      p_load_cal_seq_number          => p_load_sequence_number,
449                      p_uoo_id                       => p_uoo_id,
450                      p_program_cd                   => p_course_cd,
451                      p_program_version              => p_course_version,
452                      p_message                      => p_message,
453                      p_deny_warn                    => l_notification_flag,
454                      p_repeat_tag                   => l_repeat_tag,
455                      p_calling_obj                  => l_calling_obj
456                     ) THEN
457 
458                   IF l_notification_flag = 'DENY' THEN
459 
460                     l_deny_unit_steps := TRUE;
461 
462                     IF p_calling_obj IN ('JOB','JOB_FROM_WAITLIST') THEN
463                       p_deny_warn := l_notification_flag;
464                       RETURN FALSE;
465                     END IF;
466 
467                   ELSE
468                     l_warn_unit_steps := TRUE;
469                   END IF; -- IF l_notification_flag = 'DENY' THEN
470 
471             END IF;
472 --
473 -- validate the unit step Time Conflict
474 --
475          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'TIME_CNFLT' THEN
476             IF NOT eval_time_conflict(
477                      p_person_id                    => p_person_id,
478                      p_load_cal_type                => p_load_cal_type,
479                      p_load_cal_seq_number          => p_load_sequence_number,
480                      p_uoo_id                       => p_uoo_id,
481                      p_program_cd                   => p_course_cd,
482                      p_program_version              => p_course_version,
483                      p_message                      => p_message,
484                      p_deny_warn                    => l_notification_flag,
485                      p_calling_obj                  => l_calling_obj
486                     ) THEN
487                   IF l_notification_flag = 'DENY' THEN
488 
489                     l_deny_unit_steps := TRUE;
490 
491                     IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
492                       p_deny_warn := l_notification_flag;
493                       RETURN FALSE;
494                     END IF;
495 
496                   ELSE
497                     l_warn_unit_steps := TRUE;
498                   END IF; -- IF l_notification_flag = 'DENY' THEN
499 
500             END IF;
501 --
502 -- validate the unit step Pre-Requisite rule
503 --
504          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'PREREQ' THEN
505            -- for self service pages this step will be evaluated along with the program steps
506             IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
507 
508               IF NOT eval_prereq (
509                              p_person_id => p_person_id,
510                              p_load_cal_type => p_load_cal_type,
511                              p_load_sequence_number => p_load_sequence_number,
512                              p_uoo_id  => p_uoo_id,
513                              p_course_cd => p_course_cd,
514                              p_course_version => p_course_version,
515                              p_message => p_message,
516                              p_deny_warn => l_notification_flag,
517                              p_calling_obj => l_calling_obj
518                       ) THEN
519                  IF l_notification_flag = 'DENY' THEN
520                    l_deny_unit_steps := TRUE;
521                    p_deny_warn := l_notification_flag;
522                    RETURN FALSE;
523                  ELSE
524                    l_warn_unit_steps := TRUE;
525                  END IF;
526 
527               END IF; -- IF p_calling_obj = 'JOB' THEN
528 
529             END IF;
530 
531 --
532 -- validate the unit step incompatibility rule
533 --
534          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'INCMPT_UNT' THEN
535            -- for self service pages this step will be evaluated along with the program steps
536             IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
537 
538               IF NOT eval_incompatible(
539                                      p_person_id => p_person_id,
540                              p_load_cal_type => p_load_cal_type,
541                              p_load_sequence_number => p_load_sequence_number,
542                              p_uoo_id  => p_uoo_id,
543                              p_course_cd => p_course_cd,
544                              p_course_version => p_course_version,
545                              p_message => p_message,
546                              p_deny_warn => l_notification_flag,
547                              p_calling_obj => l_calling_obj
548                              ) THEN
549 
550                  IF l_notification_flag = 'DENY' THEN
551                    l_deny_unit_steps := TRUE;
552                    p_deny_warn := l_notification_flag;
553                    RETURN FALSE;
554                  ELSE
555                    l_warn_unit_steps := TRUE;
556                  END IF;
557 
558               END IF; -- IF p_calling_obj = 'JOB' THEN
559 
560             END IF;
561 
562 
563 --
564 -- validate the unit step special permission
565 --
566          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'SPL_PERM' AND p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
567          -- spl per  is evaluated in add units api
568             IF NOT eval_spl_permission(
569                                    p_person_id => p_person_id,
570                            p_load_cal_type => p_load_cal_type,
571                            p_load_sequence_number => p_load_sequence_number,
572                            p_uoo_id  => p_uoo_id,
573                            p_course_cd => p_course_cd,
574                            p_course_version => p_course_version,
575                            p_message => p_message,
576                            p_deny_warn => l_notification_flag
577                     ) THEN
578                 IF l_notification_flag = 'DENY' THEN
579                   l_deny_unit_steps := TRUE;
580                    p_deny_warn := l_notification_flag;
581                   RETURN FALSE;
582                 ELSE
583                  l_warn_unit_steps := TRUE;
584                 END IF;
585             END IF;
586 
587         --
588         -- validate the unit step reserve seating
589         -- Call the reserve seating validation only if the unit section is not a part of any group.
590         -- Modified as part of Bug# 2599929'
591         --
592          ELSIF l_usec_partof_group = FALSE AND cur_step_def_var_rec.s_enrolment_step_type = 'RSV_SEAT' THEN
593 
594             IF p_calling_obj <> 'PLAN' THEN
595             -- for plannig waitlisting is not allowed
596                 --
597                 -- If the student is already WAITLISTED then the Unit section status need not be verified when the student is
598                 -- ENROLLED- beacuse the procedure validate_unit_steps itself would be called only when it is determined that there are
599                 -- seats avaliavle for the student to move from waitlist to enroll.
600                 --
601               IF l_unit_attempt_status <> 'WAITLISTED' THEN
602                   --
603                   -- Check whether the student is going to be waitlisted or not
604                   -- Added four more parameters as per bug 2417240.
605                   Igs_En_Gen_015.get_usec_status( p_uoo_id              => p_uoo_id,
606                                       p_person_id               => p_person_id,
607                                       p_unit_section_status     => l_usec_status,
608                                       p_waitlist_ind            => l_waitlist_ind,
609                                       p_load_cal_type           => p_load_cal_type,
610                                       p_load_ci_sequence_number => p_load_sequence_number,
611                                       p_course_cd               => p_course_cd);
612               END IF ;
613 
614                 --
615                 -- if student is not going to be waitlisted OR if it is determined that the student is already WAITLISTED , but wants to
616                 -- ENROL now , then only call the reserve seat validation.
617               IF l_unit_attempt_status = 'WAITLISTED' OR l_waitlist_ind = 'N' THEN
618 
619                 IF NOT eval_rsv_seat(
620                                p_person_id => p_person_id,
621                                p_load_cal_type => p_load_cal_type,
622                                p_load_sequence_number => p_load_sequence_number,
623                                p_uoo_id  => p_uoo_id,
624                                p_course_cd => p_course_cd,
625                                p_course_version => p_course_version,
626                                p_message => p_message,
627                                p_deny_warn => l_notification_flag,
628                                p_calling_obj => l_calling_obj,
629                                p_deny_enrollment  => l_deny_enrollment
630                                ) THEN
631 
632                            IF l_notification_flag = 'DENY' THEN
633 
634                               l_deny_unit_steps := TRUE;
635 
636                               IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
637                                 p_deny_warn := l_notification_flag;
638                                 RETURN FALSE;
639                               END IF;
640 
641                             ELSE
642                               l_warn_unit_steps := TRUE;
643                             END IF; -- IF l_notification_flag = 'DENY' THEN
644 
645                  END IF; -- IF NOT eval_unit_ss_allowed
646 
647               END IF;  -- l_waitlist_ind
648 
649           END IF; -- IF p_calling_obj <> 'PLAN' THEN
650 --
651 -- cart maximum step is validated in add_units_api
652 --
653 --
654 -- validate the unit step
655 --
656 
657          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'INT_STSU' THEN
658             IF NOT eval_intmsn_unit_lvl(
659                      p_person_id                    => p_person_id,
660                      p_load_cal_type                => p_load_cal_type,
661                      p_load_cal_seq_number          => p_load_sequence_number,
662                      p_uoo_id                       => p_uoo_id,
663                      p_program_cd                   => p_course_cd,
664                      p_program_version              => p_course_version,
665                      p_message                      => p_message,
666                      p_deny_warn                    => l_notification_flag,
667                      p_rule_seq_number              => cur_step_def_var_rec.rul_sequence_number,
668                      p_calling_obj                  => l_calling_obj
669                     ) THEN
670                   IF l_notification_flag = 'DENY' THEN
671 
672                     l_deny_unit_steps := TRUE;
673 
674                     IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
675                       p_deny_warn := l_notification_flag;
676                       RETURN FALSE;
677                     END IF;
678 
679                   ELSE
680                     l_warn_unit_steps := TRUE;
681                   END IF; -- IF l_notification_flag = 'DENY' THEN
682             END IF;
683 --
684 -- validate the unit step
685 --
686          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'VISA_STSU' THEN
687             IF NOT eval_visa_unit_lvl(
688                      p_person_id                    => p_person_id,
689                      p_load_cal_type                => p_load_cal_type,
690                      p_load_cal_seq_number          => p_load_sequence_number,
691                      p_uoo_id                       => p_uoo_id,
692                      p_program_cd                   => p_course_cd,
693                      p_program_version              => p_course_version,
694                      p_message                      => p_message,
695                      p_deny_warn                    => l_notification_flag,
696                      p_rule_seq_number              => cur_step_def_var_rec.rul_sequence_number,
697                      p_calling_obj                  => l_calling_obj
698                     ) THEN
699                   IF l_notification_flag = 'DENY' THEN
700 
701                     l_deny_unit_steps := TRUE;
702 
703                     IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
704                       p_deny_warn := l_notification_flag;
705                       RETURN FALSE;
706                     END IF;
707 
708                   ELSE
709                     l_warn_unit_steps := TRUE;
710                   END IF; -- IF l_notification_flag = 'DENY' THEN
711             END IF;
712 
713            -- new code added ----------
714           ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'AUDIT_PERM' AND l_assessment_ind = 'Y'  THEN
715             -- audit per  is evaluated in add units api
716             IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
717               IF NOT eval_audit_permission (p_person_id            => p_person_id,
718                                         p_load_cal_type        => p_load_cal_type,
719                                         p_load_sequence_number => p_load_sequence_number,
720                                         p_uoo_id               => p_uoo_id,
721                                         p_course_cd            => p_course_cd,
722                                         p_course_version       => p_course_version,
723                                         p_message              => p_message,
724                                         p_deny_warn            => l_notification_flag
725                                                 ) THEN
726                     IF l_notification_flag = 'DENY' THEN
727                         l_deny_unit_steps := TRUE;
728                         p_deny_warn := l_notification_flag;
729                         RETURN FALSE;
730                     ELSE
731                       l_warn_unit_steps := TRUE;
732                     END IF; -- IF l_notification_flag = 'DENY' THEN
733               END IF;
734             END IF; -- p_calling_obj = 'JOB'
735 
736           ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'AUDIT_LIM'  AND l_assessment_ind = 'Y' THEN
737               IF NOT eval_student_audit_limit (p_person_id            => p_person_id,
738                                          p_load_cal_type        => p_load_cal_type,
739                                          p_load_sequence_number => p_load_sequence_number,
740                                          p_uoo_id               => p_uoo_id,
741                                          p_course_cd            => p_course_cd,
742                                          p_course_version       => p_course_version,
743                                          p_message              => p_message,
744                                          p_deny_warn            => l_notification_flag,
745                                          p_stud_audit_lim       => cur_step_def_var_rec.stud_audit_lim,
746                                          p_calling_obj          => l_calling_obj
747                                               ) THEN
748                   IF l_notification_flag = 'DENY' THEN
749 
750                     l_deny_unit_steps := TRUE;
751 
752                     IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
753                       p_deny_warn := l_notification_flag;
754                       RETURN FALSE;
755                     END IF;
756 
757                   ELSE
758                     l_warn_unit_steps := TRUE;
759                   END IF; -- IF l_notification_flag = 'DENY' THEN
760               END IF;
761 
762          ELSIF cur_step_def_var_rec.s_enrolment_step_type = 'CHK_TIME_UNIT' THEN
763 
764             IF p_calling_obj NOT IN  ('PLAN','JOB','ENROLPEND','REINSTATE','JOB_FROM_WAITLIST') THEN
765             -- When planning, donot need to validate this step. When submiting plan need to validate this step
766 
767                 l_message := NULL;
768                IF NOT igs_en_elgbl_person.eval_timeslot(
769                                                    p_person_id => p_person_id,
770                                                    p_person_type => p_person_type,
771                                                    p_load_calendar_type => p_load_cal_type,
772                                                    p_load_cal_sequence_number => p_load_sequence_number,
773                                                    p_uoo_id  => p_uoo_id,
774                                                    p_enrollment_category => p_enrollment_category,
775                                                    p_comm_type  => p_comm_type,
776                                                    p_enrl_method => p_enr_method_type,
777                                                    p_message => l_message,
778                                               p_notification_flag =>l_notification_flag
779                ) THEN
780                    IF l_message IS NOT NULL THEN
781 
782                         -- if calling object is from self service create a warning/deny record
783                         l_unit_sec := igs_en_add_units_api.get_unit_sec(p_uoo_id);
784                         l_message_icon := substr(l_notification_flag,1,1);
785 
786                         igs_en_drop_units_api.create_ss_warning (
787                              p_person_id => p_person_id,
788                              p_course_cd => p_course_cd,
789                              p_term_cal_type=> p_load_cal_type,
790                              p_term_ci_sequence_number => p_load_sequence_number,
791                              p_uoo_id => p_uoo_id,
792                              p_message_for => l_unit_sec,
793                              p_message_icon=> l_message_icon,
794                              p_message_name => l_message,
795                              p_message_rule_text => NULL,
796                              p_message_tokens => NULL,
797                              p_message_action=> NULL,
798                              p_destination =>NULL,
799                              p_parameters => NULL,
800                              p_step_type => 'UNIT');
801 
802 
803                    END IF; -- IF l_message IS NOT NULL THEN
804 
805                    IF l_notification_flag = 'DENY' THEN
806 
807                       l_deny_unit_steps := TRUE;
808 
809                       IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
810                         p_deny_warn := l_notification_flag;
811                         RETURN FALSE;
812                       END IF;
813 
814                    ELSE
815                       l_warn_unit_steps := TRUE;
816                    END IF; -- IF l_notification_flag = 'DENY' THEN
817 
818               END IF; -- IF NOT igs_en_elgbl_person.eval_timeslot
819 
820            END IF; -- IF p_calling_obj <> ('PLAN','JOB','ENROLPEND') THEN
821 
822         END IF;  -- cur_step_def_var_rec.s_enrolment_step_type
823 
824         -- if p_message is not null means it is a system error
825         -- so we should stop processing
826         IF p_calling_obj NOT IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') AND p_message IS NOT NULL THEN
827           p_deny_warn := 'DENY';
828           RETURN FALSE;
829         END IF;
830 
831        --If calling object is reinstate and any warnings occured in the validation then reintialising the
832        --the message string so that only errors will be displayed in the schedule page.
833 
834         IF p_calling_obj IN ('REINSTATE') AND p_message IS NOT NULL AND l_warn_unit_steps THEN
835            p_message:= NULL;
836         END IF;
837 
838   END LOOP loop_unit_steps;
839 
840   l_message := NULL;
841   IF NOT eval_award_prog_only(
842                      p_person_id                    => p_person_id,
843                      p_person_type                  => p_person_type,
844                      p_load_cal_type                => p_load_cal_type,
845                      p_load_sequence_number         => p_load_sequence_number,
846                      p_uoo_id                       => p_uoo_id,
847                      p_course_cd                    => p_course_cd,
848                      p_course_version               => p_course_version,
849                      p_message                      => l_message,
850                      p_calling_obj                  => l_calling_obj
851        ) THEN
852             p_deny_warn := 'DENY';
853 
854             IF p_calling_obj NOT IN  ('JOB','SCH_UPD', 'REINSTATE','JOB_FROM_WAITLIST') THEN
855                       -- if calling object is from self service create a warning/deny record
856                       l_unit_sec := igs_en_add_units_api.get_unit_sec(p_uoo_id);
857                       l_message_icon := substr(p_deny_warn,1,1);
858 
859                       igs_en_drop_units_api.create_ss_warning (
860                            p_person_id => p_person_id,
861                            p_course_cd => p_course_cd,
862                            p_term_cal_type=> p_load_cal_type,
863                            p_term_ci_sequence_number => p_load_sequence_number,
864                            p_uoo_id => p_uoo_id,
865                            p_message_for => l_unit_sec,
866                            p_message_icon=> l_message_icon,
867                            p_message_name => l_message,
868                            p_message_rule_text => NULL,
869                            p_message_tokens => NULL,
870                            p_message_action=> NULL,
871                            p_destination =>NULL,
872                            p_parameters => NULL,
873                            p_step_type => 'UNIT');
874 
875 
876             ELSE
877 
878               IF p_message IS NULL THEN
879                       p_message := l_message;
880                   ELSE
881                       p_message := p_message ||';'||l_message;
882               END IF;
883 
884             END IF; -- IF p_calling_obj <> 'JOB'
885 
886             RETURN FALSE;
887 
888          END IF;
889 
890      l_message := NULL;
891      IF l_assessment_ind = 'Y' THEN
892         OPEN c_usec_audit_lim;
893             FETCH c_usec_audit_lim INTO l_usec_audit_lim;
894         CLOSE c_usec_audit_lim;
895         OPEN c_audit_sua;
896             FETCH c_audit_sua INTO l_audit_sua;
897         CLOSE c_audit_sua;
898          IF l_audit_sua  > l_usec_audit_lim THEN
899 
900             IF p_calling_obj IN ('JOB','REINSTATE','JOB_FROM_WAITLIST') THEN
901               l_message := 'IGS_EN_AU_LIM_UNIT_CROSS';
902             ELSE
903               l_message := 'IGS_EN_NOOFAUD_TAB_DENY';
904             END IF;
905             p_deny_warn := 'DENY';
906 
907             IF p_calling_obj NOT IN  ('JOB','SCH_UPD', 'REINSTATE','JOB_FROM_WAITLIST') THEN
908                       -- if calling object is from self service create a warning/deny record
909                       l_unit_sec := igs_en_add_units_api.get_unit_sec(p_uoo_id);
910                       l_message_icon := substr(p_deny_warn,1,1);
911 
912                       igs_en_drop_units_api.create_ss_warning (
913                            p_person_id => p_person_id,
914                            p_course_cd => p_course_cd,
915                            p_term_cal_type=> p_load_cal_type,
916                            p_term_ci_sequence_number => p_load_sequence_number,
917                            p_uoo_id => p_uoo_id,
918                            p_message_for => l_unit_sec,
919                            p_message_icon=> l_message_icon,
920                            p_message_name => l_message,
921                            p_message_rule_text => NULL,
922                            p_message_tokens => NULL,
923                            p_message_action=> NULL,
924                            p_destination =>NULL,
925                            p_parameters => NULL,
926                            p_step_type => 'UNIT');
927 
928 
929             ELSE
930 
931               IF p_message IS NULL THEN
932                       p_message := l_message;
933                   ELSE
934                       p_message := p_message ||';'||l_message;
935               END IF;
936 
937             END IF; -- IF p_calling_obj <> 'JOB'
938 
939             RETURN FALSE;
940 
941          END IF; -- IF l_audit_sua  > l_usec_audit_lim THEN
942 
943      END IF; -- IF l_assessment_ind = 'Y' THEN
944 
945     -- If any of the validations had failed with a deny, i.e.
946     -- depending on the return value of l_vald_person_steps, return from the main function
947     IF l_deny_unit_steps THEN
948        --
949        -- validation of person steps returns TRUE
950        --
951        IF p_message IS NOT NULL THEN
952 
953           --
954           -- remove ; from beginning
955           --
956           IF substr(p_message,1,1) = ';' THEN
957              p_message := substr(p_message,2);
958           END IF;
959           --
960           -- remove ; from end
961           --
962           IF substr(p_message,-1,1) = ';' THEN
963              p_message := substr(p_message,1,length(p_message)-1);
964           END IF;
965        END IF;
966        p_deny_warn:= 'DENY';
967        RETURN FALSE;
968     ELSIF l_warn_unit_steps THEN
969 
970        IF p_message IS NOT NULL THEN
971           -- remove ; from beginning
972           --
973           IF substr(p_message,1,1) = ';' THEN
974              p_message := substr(p_message,2);
975           END IF;
976           --
977           -- remove ; from end
978           --
979           IF substr(p_message,-1,1) = ';' THEN
980              p_message := substr(p_message,1,length(p_message)-1);
981           END IF;
982         END IF;
983         p_deny_warn := 'WARN' ;
984         RETURN TRUE;
985     END IF;
986     -- no errors/warnings
987     p_deny_warn := NULL;
988     RETURN TRUE;
989 
990 RETURN TRUE;
991 
992 END eval_unit_steps;
993   --
994   --
995   --  This function is used to get the effective census date which will be used
996   --  to check the effectiveness of the hold.
997   --
998   --
999   FUNCTION eval_unit_ss_allowed
1000   (
1001     p_person_id                    IN     NUMBER,
1002     p_course_cd                    IN     VARCHAR2,
1003     p_person_type                  IN     VARCHAR2,
1004     p_load_cal_type                IN     VARCHAR2,
1005     p_load_sequence_number         IN     VARCHAR2,
1006     p_uoo_id                       IN     NUMBER,
1007     p_message                      IN OUT NOCOPY VARCHAR2,
1008     p_deny_warn                    IN     VARCHAR2,
1009     p_calling_obj                  IN     VARCHAR2
1010   ) RETURN BOOLEAN AS
1011     ------------------------------------------------------------------------------------
1012     --Created by  : knaraset ( Oracle IDC)
1013     --Date created: 21-JUN-2001
1014     --
1015     --Purpose: this function returns whether a student unit attempt can be enrolled or not based on the value of ss_enrol_indicator
1016     --         but for self service staff can perform enrollment in any case, i.e. even value of ss_enrol_indicator is 'NO'
1017     --
1018     --Known limitations/enhancements and/or remarks:
1019     --
1020     --Change History:
1021     --Who         When            What
1022     -------------------------------------------------------------------------------------
1023     --
1024     CURSOR cur_pers_sys_type(p_person_type_code IN VARCHAR2) IS
1025     SELECT system_type
1026     FROM igs_pe_person_types
1027     WHERE person_type_code = p_person_type_code;
1028   --
1029     CURSOR cur_ss_enrol_ind(p_uoo_id NUMBER) IS
1030     SELECT ss_enrol_ind,unit_class,unit_cd
1031     FROM igs_ps_unit_ofr_opt
1032     WHERE uoo_id = p_uoo_id;
1033   --
1034     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
1035     l_system_type igs_pe_person_types.system_type%TYPE ;
1036     l_ss_enrol_rec cur_ss_enrol_ind%ROWTYPE ;
1037 
1038     l_message VARCHAR2(30);
1039     l_message_icon VARCHAR2(1);
1040   --
1041   -- begin of the function eval_unit_ss_allowed
1042   --
1043   BEGIN
1044   --
1045   --  Fetch the system type corresponding to the person Type of logged on user
1046   --
1047   OPEN cur_pers_sys_type(p_person_type);
1048   FETCH cur_pers_sys_type INTO l_system_type;
1049   CLOSE cur_pers_sys_type;
1050   --
1051   -- check whether logged on user is self service staff
1052   --
1053   IF l_system_type <> 'STUDENT' THEN
1054     RETURN TRUE;
1055   END IF;
1056   --
1057   --  Check whether Enrollment Method step has been overridden
1058   --
1059   IF Igs_En_Gen_015.validation_step_is_overridden (
1060        'ENR_MTHD',
1061        p_load_cal_type,
1062        p_load_sequence_number ,
1063        p_person_id ,
1064        p_uoo_id ,
1065        l_step_override_limit
1066      ) THEN
1067       RETURN TRUE;
1068   END IF;
1069   --
1070   -- fetch ss_enrol_ind for the given unit section
1071   --
1072   OPEN cur_ss_enrol_ind (p_uoo_id);
1073   FETCH cur_ss_enrol_ind INTO l_ss_enrol_rec;
1074   CLOSE cur_ss_enrol_ind;
1075   --
1076   -- Check whether ss_enrol_ind is checked for the given unit section
1077   --
1078   IF l_ss_enrol_rec.ss_enrol_ind = 'Y' THEN
1079     RETURN TRUE;
1080   END IF;
1081   --
1082   IF p_deny_warn = 'WARN' THEN
1083         l_message := 'IGS_SS_WARN_ENR_METHOD';
1084   ELSE
1085         l_message := 'IGS_SS_DENY_ENR_METHOD';
1086   END IF;
1087 
1088   IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
1089 
1090     l_message_icon := substr(p_deny_warn,1,1);
1091     igs_en_drop_units_api.create_ss_warning (
1092              p_person_id => p_person_id,
1093              p_course_cd => p_course_cd,
1094              p_term_cal_type=> p_load_cal_type,
1095              p_term_ci_sequence_number => p_load_sequence_number,
1096              p_uoo_id => p_uoo_id,
1097              p_message_for => l_ss_enrol_rec.unit_cd||'/'||l_ss_enrol_rec.unit_class,
1098              p_message_icon=> l_message_icon,
1099              p_message_name => l_message,
1100              p_message_rule_text => NULL,
1101              p_message_tokens => NULL,
1102              p_message_action=> NULL,
1103              p_destination =>NULL,
1104              p_parameters => NULL,
1105              p_step_type => 'UNIT');
1106 
1107   ELSE
1108     IF p_message IS NULL THEN
1109        p_message := l_message;
1110     ELSE
1111        p_message := p_message ||';'||l_message;
1112     END IF;
1113   END IF;
1114   --
1115   RETURN FALSE;
1116   --
1117   END eval_unit_ss_allowed;
1118   --
1119   --
1120   --
1121   FUNCTION  eval_program_check (
1122   p_person_id IN NUMBER,
1123   p_load_cal_type IN VARCHAR2,
1124   p_load_sequence_number IN VARCHAR2,
1125   p_uoo_id  IN NUMBER,
1126   p_course_cd IN VARCHAR2,
1127   p_course_version IN NUMBER,
1128   p_message IN OUT NOCOPY VARCHAR2,
1129   p_deny_warn  IN VARCHAR2,
1130   p_rule_seq_number IN NUMBER,
1131   p_calling_obj IN  VARCHAR2
1132   ) RETURN BOOLEAN AS
1133 
1134   ------------------------------------------------------------------------------------
1135     --Created by  : knaraset ( Oracle IDC)
1136     --Date created: 21-JUN-2001
1137     --
1138     --Purpose:  this function checks whether the student is eligible for enrolling in the given unit
1139     --          based on the program type of the student.
1140     --Known limitations/enhancements and/or remarks:
1141     --
1142     --Change History:
1143     --Who         When            What
1144     -------------------------------------------------------------------------------------
1145     CURSOR cur_uoo_dtl(p_uoo_id NUMBER) IS
1146     SELECT unit_cd,version_number, unit_class
1147     FROM igs_ps_unit_ofr_opt
1148     WHERE uoo_id = p_uoo_id;
1149   --
1150     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
1151     l_uoo_dtl_rec cur_uoo_dtl%ROWTYPE;
1152     l_message VARCHAR2(30);
1153     l_message_icon VARCHAR2(1);
1154     l_rule_text VARCHAR2(1000);
1155   --
1156   -- begin of the function eval_program_check
1157   --
1158   BEGIN
1159   --
1160   --  No Program Type Check rule defined.
1161   --
1162   IF p_rule_seq_number IS NULL THEN
1163     RETURN TRUE;
1164   END IF;
1165   --
1166   --  Check whether Program Type Check rule has been overriden for the given student.
1167   --
1168   IF Igs_En_Gen_015.validation_step_is_overridden (
1169        'PROG_CHK',
1170        p_load_cal_type,
1171        p_load_sequence_number ,
1172        p_person_id ,
1173        p_uoo_id ,
1174        l_step_override_limit
1175      ) THEN
1176     RETURN TRUE;
1177   END IF;
1178   --
1179   --  get the unit section details
1180   --
1181   OPEN cur_uoo_dtl(p_uoo_id);
1182   FETCH cur_uoo_dtl INTO l_uoo_dtl_rec;
1183   CLOSE cur_uoo_dtl;
1184   --
1185   --  check whether student has satisfied the Program Type Check rule by invoking the rule engine.
1186   --
1187     IF igs_ru_gen_001.rulp_val_senna (
1188          p_rule_call_name => 'PROG_CHK',
1189          p_rule_number => p_rule_seq_number,
1190          p_person_id => p_person_id,
1191          p_param_1 => p_course_cd,
1192          p_param_2 => p_course_version,
1193          p_param_3 => l_uoo_dtl_rec.unit_cd,
1194          p_param_4 => l_uoo_dtl_rec.version_number,
1195          p_message => l_message
1196        ) = 'true' THEN
1197        RETURN TRUE;
1198     END IF;
1199 
1200    IF p_deny_warn = 'WARN' THEN
1201         IF p_calling_obj = 'JOB' THEN
1202           l_message := 'IGS_SS_WARN_PRG_CHK';
1203         ELSE
1204           l_message := 'IGS_EN_PRGCHK_TAB_WARN';
1205         END IF;
1206      ELSE
1207         IF p_calling_obj = 'JOB' THEN
1208           l_message := 'IGS_SS_DENY_PRG_CHK';
1209         ELSE
1210           l_message := 'IGS_EN_PRGCHK_TAB_DENY';
1211         END IF;
1212    END IF;
1213 
1214   l_rule_text := NULL;
1215   IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
1216 
1217     IF  (NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
1218       l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(p_rule_seq_number);
1219     END IF;
1220     l_message_icon := substr(p_deny_warn,1,1);
1221     igs_en_drop_units_api.create_ss_warning (
1222            p_person_id => p_person_id,
1223            p_course_cd => p_course_cd,
1224            p_term_cal_type=> p_load_cal_type,
1225            p_term_ci_sequence_number => p_load_sequence_number,
1226            p_uoo_id => p_uoo_id,
1227            p_message_for => l_uoo_dtl_rec.unit_cd||'/'||l_uoo_dtl_rec.unit_class,
1228            p_message_icon=> l_message_icon,
1229            p_message_name => l_message,
1230            p_message_rule_text => l_rule_text,
1231            p_message_tokens => NULL,
1232            p_message_action=> NULL,
1233            p_destination =>NULL,
1234            p_parameters => NULL,
1235            p_step_type => 'UNIT');
1236 
1237 
1238 
1239   ELSE
1240 
1241       IF p_message IS NULL THEN
1242         p_message := l_message;
1243       ELSE
1244         p_message := p_message || ';' || l_message;
1245       END IF;
1246 
1247   END IF;
1248   RETURN FALSE;
1249 
1250   END eval_program_check;
1251   --
1252   --
1253   --
1254  FUNCTION eval_unit_forced_location(
1255   p_person_id IN NUMBER,
1256   p_load_cal_type IN VARCHAR2,
1257   p_load_sequence_number IN VARCHAR2,
1258   p_uoo_id  IN NUMBER,
1259   p_course_cd IN VARCHAR2,
1260   p_course_version IN NUMBER,
1261   p_message IN OUT NOCOPY VARCHAR2,
1262   p_deny_warn  IN VARCHAR2,
1263   p_calling_obj  IN VARCHAR2
1264   ) RETURN BOOLEAN AS
1265     ------------------------------------------------------------------------------------
1266     --Created by  : knaraset ( Oracle IDC)
1267     --Date created: 21-JUN-2001
1268     --
1269     --Purpose:  this function returns TRUE for a given student and unit attempt
1270     --          when the Unit attempt's location code AND the Primary program location code are same
1271     --
1272     --Known limitations/enhancements and/or remarks:
1273     --
1274     --Change History:
1275     --Who         When            What
1276     -- pradhakr   23-Dec-2002     Added a call to the function IGS_EN_VAL_SUA.enrp_val_coo_loc.
1277     --                            This function call validates unit location code against
1278     --                            course_offering_option location code for the enrolled course.
1279     --                            Bug# 2689233.
1280     -- stutta     19-NOV-2003     Replaced a cursor to return coo_id from program attempt table
1281     --                            with a terms api function call. Term Records Build. Bug 2829263
1282     -------------------------------------------------------------------------------------
1283     --
1284     CURSOR cur_chk_floc(p_coo_id NUMBER, p_uoo_id NUMBER) IS
1285     SELECT uoo.location_cd
1286     FROM  igs_ps_ofr_opt coo,
1287           igs_ps_unit_ofr_opt uoo
1288     WHERE coo.coo_id = p_coo_id AND
1289           uoo.uoo_id = p_uoo_id AND
1290           uoo.location_cd = coo.location_cd;
1291 
1292 
1293     CURSOR cur_get_floc(p_coo_id NUMBER) IS
1294     SELECT location_cd
1295     FROM igs_ps_ofr_opt
1296     WHERE coo_id = p_coo_id;
1297 
1298 
1299       -- Cursor to get the unit location code
1300     CURSOR c_location IS
1301       SELECT location_cd, unit_cd, unit_class
1302       FROM igs_ps_unit_ofr_opt
1303       WHERE uoo_id = p_uoo_id;
1304     l_location_rec c_location%ROWTYPE;
1305 
1306     l_coo_id                    IGS_EN_STDNT_PS_ATT.coo_id%TYPE;
1307     v_message_name              fnd_new_messages.message_name%TYPE;
1308     l_step_override_limit       igs_en_elgb_ovr_step.step_override_limit%TYPE;
1309     l_chk_floc                  igs_ps_unit_ofr_opt.location_cd%TYPE ;
1310     l_message                   VARCHAR2(30);
1311     l_message_icon              VARCHAR2(1);
1312     l_message_token             VARCHAR2(100);
1313 
1314   --
1315   -- begin of the function eval_unit_forced_location
1316   --
1317   BEGIN
1318   --
1319   -- check whether the Forced location step is overridden
1320   --
1321   IF Igs_En_Gen_015.validation_step_is_overridden (
1322        'FLOC_CHK',
1323        p_load_cal_type,
1324        p_load_sequence_number ,
1325        p_person_id ,
1326        p_uoo_id ,
1327        l_step_override_limit
1328      ) THEN
1329       RETURN TRUE;
1330   END IF;
1331   --
1332   -- Check whether the Location code of Unit section and of Primary program attempt are same.
1333   --
1334   l_coo_id := igs_en_spa_terms_api.get_spat_coo_id(   p_person_id => p_person_id,
1335                                 p_program_cd => p_course_cd,
1336                                 p_term_cal_type => p_load_cal_type,
1337                                 p_term_sequence_number => p_load_sequence_number );
1338   OPEN cur_chk_floc(l_coo_id,p_uoo_id);
1339   FETCH cur_chk_floc INTO l_chk_floc;
1340   IF cur_chk_floc%FOUND THEN
1341     CLOSE cur_chk_floc;
1342     RETURN TRUE;
1343   END IF;
1344   CLOSE cur_chk_floc;
1345   -- Cursor to get the unit location code
1346   OPEN c_location;
1347   FETCH c_location INTO l_location_rec;
1348   CLOSE c_location;
1349 
1350   -- The following call validates unit location code against
1351   -- course_offering_option location code for the enrolled course
1352   IF IGS_EN_VAL_SUA.enrp_val_coo_loc(
1353                     l_coo_id,
1354                     l_location_rec.location_cd,
1355                     v_message_name) THEN
1356         RETURN TRUE;
1357   END IF;
1358   --
1359   OPEN cur_get_floc(l_coo_id);
1360   FETCH cur_get_floc INTO l_chk_floc;
1361   CLOSE cur_get_floc;
1362 
1363   IF p_deny_warn = 'WARN' THEN
1364         IF p_calling_obj = 'JOB' THEN
1365           l_message := 'IGS_SS_WARN_LOC_CHK';
1366         ELSE
1367           l_message := 'IGS_EN_FLOC_TAB_WARN';
1368         END IF;
1369   ELSE
1370         IF p_calling_obj = 'JOB' THEN
1371           l_message := 'IGS_SS_DENY_LOC_CHK';
1372         ELSE
1373           l_message := 'IGS_EN_FLOC_TAB_DENY';
1374         END IF;
1375 
1376   END IF;
1377   IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
1378 
1379       l_message_token := 'UNIT_CD'||':'||l_chk_floc||';';
1380       l_message_icon := substr(p_deny_warn,1,1);
1381       igs_en_drop_units_api.create_ss_warning (
1382              p_person_id => p_person_id,
1383              p_course_cd => p_course_cd,
1384              p_term_cal_type=> p_load_cal_type,
1385              p_term_ci_sequence_number => p_load_sequence_number,
1386              p_uoo_id => p_uoo_id,
1387              p_message_for => l_location_rec.unit_cd||'/'||l_location_rec.unit_class,
1388              p_message_icon=> l_message_icon,
1389              p_message_name => l_message,
1390              p_message_rule_text => NULL,
1391              p_message_tokens => l_message_token,
1392              p_message_action=> NULL,
1393              p_destination =>NULL,
1394              p_parameters => NULL,
1395              p_step_type => 'UNIT');
1396   ELSE
1397 
1398     IF p_message IS NULL THEN
1399          p_message := l_message;
1400     ELSE
1401          p_message := p_message ||';'||l_message;
1402     END IF;
1403 
1404   END IF; -- IF p_calling_obj <> 'JOB'
1405   --
1406   RETURN FALSE;
1407   --
1408   END eval_unit_forced_location;
1409   -- =================================================================================
1410   FUNCTION eval_unit_forced_mode (
1411   p_person_id IN NUMBER,
1412   p_load_cal_type IN VARCHAR2,
1413   p_load_sequence_number IN VARCHAR2,
1414   p_uoo_id  IN NUMBER,
1415   p_course_cd IN VARCHAR2,
1416   p_course_version IN NUMBER,
1417   p_message IN OUT NOCOPY VARCHAR2,
1418   p_deny_warn  IN VARCHAR2,
1419   p_calling_obj  IN VARCHAR2
1420   ) RETURN BOOLEAN AS
1421   ------------------------------------------------------------------------------------
1422     --Created by  : knaraset ( Oracle IDC)
1423     --Date created: 21-JUN-2001
1424     --
1425     --Purpose:  this function returns TRUE for a given student and unit attempt
1426     --          if the unit attempt is in line with students forced
1427     --         mode (if applicable).
1428     --          This module validates the nominated unit class against
1429     --          course_offering_option attandance mode for the Primary Program
1430     --
1431     --Known limitations/enhancements and/or remarks:
1432     --
1433     --Change History:
1434     --Who         When            What
1435     --stutta      19-NOV-2003     Replaced a cursor to return coo_id from program attempt table
1436     --                            with a terms api function call. Term Records Build. Bug 2829263
1437     -------------------------------------------------------------------------------------
1438     CURSOR cur_unit_class(p_uoo_id NUMBER) IS
1439     SELECT unit_class,unit_cd
1440     FROM igs_ps_unit_ofr_opt
1441     WHERE uoo_id = p_uoo_id;
1442 
1443     CURSOR cur_get_fatt(p_coo_id NUMBER) IS
1444     SELECT attendance_mode
1445     FROM igs_ps_ofr_opt
1446     WHERE coo_id = p_coo_id;
1447 
1448 
1449   --
1450     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
1451     l_unit_class_rec cur_unit_class%ROWTYPE ;
1452     l_coo_id igs_en_stdnt_ps_att.coo_id%TYPE;
1453     l_forced_att_mode igs_ps_ofr_opt.attendance_mode%TYPE;
1454     l_message VARCHAR2(30);
1455     l_message_icon VARCHAR2(1);
1456     l_message_token   VARCHAR2(100);
1457   --
1458   -- begin of the function eval_unit_forced_location
1459   --
1460   BEGIN
1461   --
1462   -- check whether forced attendance mode step has been overridden.
1463   --
1464   IF Igs_En_Gen_015.validation_step_is_overridden (
1465        'FATD_MODE',
1466        p_load_cal_type,
1467        p_load_sequence_number ,
1468        p_person_id ,
1469        p_uoo_id ,
1470        l_step_override_limit
1471      ) THEN
1472       RETURN TRUE;
1473   END IF;
1474   --
1475   -- Get the unit class of Unit section
1476   --
1477   OPEN cur_unit_class(p_uoo_id);
1478   FETCH cur_unit_class INTO l_unit_class_rec;
1479   CLOSE cur_unit_class;
1480   --
1481   -- get the coo_id of the primary program
1482   --
1483   l_coo_id := igs_en_spa_terms_api.get_spat_coo_id(   p_person_id => p_person_id,
1484                                 p_program_cd => p_course_cd,
1485                                 p_term_cal_type => p_load_cal_type,
1486                                 p_term_sequence_number => p_load_sequence_number );
1487   --
1488   --   determine if the unit attempt is in line with students forced
1489   --   mode (if applicable).
1490   --
1491   IF igs_en_val_sua.enrp_val_coo_mode (
1492        p_coo_id => l_coo_id,
1493        p_unit_class => l_unit_class_rec.unit_class,
1494        p_message_name => l_message
1495      ) THEN
1496          RETURN TRUE;
1497   END IF;
1498   --
1499   OPEN cur_get_fatt(l_coo_id);
1500   FETCH cur_get_fatt INTO l_forced_att_mode;
1501   CLOSE cur_get_fatt;
1502 
1503   IF p_deny_warn = 'WARN' THEN
1504     IF p_calling_obj  = 'JOB' THEN
1505         l_message := 'IGS_SS_WARN_ATMODE_CHK';
1506     ELSE
1507         l_message := 'IGS_EN_ATMOD_TAB_WARN';
1508     END IF;
1509   ELSE
1510     IF p_calling_obj  = 'JOB' THEN
1511         l_message := 'IGS_SS_DENY_ATMODE_CHK';
1512     ELSE
1513         l_message := 'IGS_EN_ATMOD_TAB_DENY';
1514     END IF;
1515   END IF;
1516 
1517   IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
1518 
1519       l_message_token := 'UNIT_CD'||':'||l_forced_att_mode||';';
1520       l_message_icon := substr(p_deny_warn,1,1);
1521       igs_en_drop_units_api.create_ss_warning (
1522              p_person_id => p_person_id,
1523              p_course_cd => p_course_cd,
1524              p_term_cal_type=> p_load_cal_type,
1525              p_term_ci_sequence_number => p_load_sequence_number,
1526              p_uoo_id => p_uoo_id,
1527              p_message_for => l_unit_class_rec.unit_cd||'/'||l_unit_class_rec.unit_class,
1528              p_message_icon=> l_message_icon,
1529              p_message_name => l_message,
1530              p_message_rule_text => NULL,
1531              p_message_tokens => l_message_token,
1532              p_message_action=> NULL,
1533              p_destination =>NULL,
1534              p_parameters => NULL,
1535              p_step_type => 'UNIT');
1536   ELSE
1537     IF p_message IS NULL THEN
1538        p_message := l_message;
1539     ELSE
1540        p_message := p_message ||';'||l_message;
1541     END IF;
1542   END IF;
1543   --
1544   RETURN FALSE;
1545   --
1546 END eval_unit_forced_mode;
1547 
1548 FUNCTION eval_unit_repeat (
1549     p_person_id                    IN     NUMBER,
1550     p_load_cal_type                IN     VARCHAR2,
1551     p_load_cal_seq_number          IN     NUMBER,
1552     p_uoo_id                       IN     NUMBER,
1553     p_program_cd                   IN     VARCHAR2,
1554     p_program_version              IN     NUMBER,
1555     p_message                      IN OUT NOCOPY VARCHAR2,
1556     p_deny_warn                    IN     VARCHAR2,
1557     p_repeat_tag                   OUT NOCOPY    VARCHAR2 ,
1558     p_unit_cd                      IN     VARCHAR2  ,
1559     p_unit_version                 IN     NUMBER,
1560     p_calling_obj                  IN VARCHAR2
1561   ) RETURN BOOLEAN AS
1562   --------------------------------------------------------------------------------
1563   --Created by  : pradhakr ( Oracle IDC)
1564   --Date created: 21-JUN-2001
1565   --
1566   --Purpose:This function is used to evaluate if a student is eligible for Unit Repeat.
1567   --  Parameters Description:
1568   --
1569   --  p_person_id                  -> Person ID of the student who wants to enroll or administrator is enrolling.
1570   --  p_load_cal_type              -> Load (Term) or Teaching Calendar Type.
1571   --  p_load_cal_seq_number        -> Load Calendar or Teaching Calendar instance sequence number.
1572   --  p_uoo_id                     -> Unit Section Identifier.
1573   --  p_program_cd                 -> The Primary Program Code or the Program code selected by the student.
1574   --  p_program_version            -> The Primary Program version number or the Program version number selected by the student.
1575   --  p_message                    -> Message from the validation.
1576   --  p_deny_warn                  -> Deny or Warn Indicator based on the setup.
1577   --  p_repeat_tag                 -> Indicates whether Unit Section is considered as Repeat or Not.
1578   -- if p_uoo_id is null then these two parameters are not null and vice versa
1579   --  p_unit_cd                    -> Indicates the unit being enrolled/advanced standing being granted for
1580   --  p_unit_version             -> Indicates the version of the unit being attempted for
1581   --  smaddali removed all the institution logic. When this function is called from advanced standing details(IGSAV003)
1582   --  form then since there is no uoo_id we pass the new parameters of unit version . So the code has been modified to
1583   --  consider the new unit version being passed when uoo_id is null.
1584   --  Modified Cursor to select all the Unit attempts.
1585   --
1586   --Known limitations/enhancements and/or remarks:
1587   --
1588   --Change History:
1589   --Who         When            What
1590   --smaddali                    added two new parameters p_unit_cd,p_version_number for ccr PSCR014 (bug1960126)
1591   --kkillams    26-12-2002      Added NVL to the l_user_hook_successful column in the if clause, after
1592   --                            igs_en_rpt_prc_uhk.repeat_allowed function call w.r.t. bug no# 2692012.
1593   -- rvivekan 18-Jun-2003   modified as per Reenrollment and repeat processing enh#2881363
1594   -- rvivekan    9-Sep-2003     PSP integration build 3052433. modified type of
1595   --                            local variable l_repeat_allowed
1596   -- stutta     05-Aug-2004     Added call to user hook depending on profile value IGS_EN_REP_REN.
1597   --                            As per repeat reenrollment user hook Build # 3807707
1598 
1599   ------------------------------------------------------------------------------
1600 
1601 
1602     CURSOR cur_unit_details IS
1603       SELECT   unit_cd,
1604                unit_class,
1605                version_number,
1606                cal_type,
1607                ci_sequence_number
1608       FROM     igs_ps_unit_ofr_opt
1609       WHERE    uoo_id = p_uoo_id;
1610     --
1611     --  Cursor to check if the Organization Unit has "Include Advanced Standing Units" set to Yes.
1612     --  and also get the max repeats allowed
1613     --
1614     CURSOR cur_org_incl_adv_stand (
1615              cp_org_unit_cd           IN VARCHAR2
1616            ) IS
1617       SELECT   include_adv_standing_units,max_repeats_for_credit,max_repeats_for_funding,rp.org_unit_id
1618       FROM     igs_en_rep_process  rp , igs_or_unit ou
1619       WHERE    ou.org_unit_cd = cp_org_unit_cd
1620       AND      ou.party_id = rp.org_unit_id
1621       AND      rp.org_unit_id IS NOT NULL
1622       UNION
1623       SELECT  include_adv_standing_units,max_repeats_for_credit,max_repeats_for_funding,org_unit_id
1624       FROM igs_en_rep_process
1625       WHERE org_unit_id IS NULL
1626       ORDER BY org_unit_id;
1627     --
1628     --  Cursor to select all the Unit Attempts of the Student.
1629       CURSOR cur_student_attempts (
1630              cp_include_in_adv_stand  IN VARCHAR2 ,
1631              cp_unit_cd   igs_ps_unit_ver.unit_cd%TYPE,
1632              cp_version_number igs_ps_unit_ver.version_number%TYPE
1633            ) IS
1634       SELECT  sua.unit_cd,
1635               sua.version_number,
1636               sua.cal_type,
1637               sua.ci_sequence_number,
1638               sua.uoo_id,
1639               sua.override_enrolled_cp  ,
1640               sua.course_cd
1641       FROM     igs_en_su_attempt sua, igs_ps_unit_ver psv
1642       WHERE    sua.person_id = p_person_id
1643       AND     ( sua.cart IS NOT NULL AND ( p_calling_obj <> 'SWAP'  OR  (p_calling_obj = 'SWAP' AND sua.uoo_id <> p_uoo_id) ) )
1644       AND     ((p_calling_obj <> 'PLAN' AND sua.unit_attempt_status IN ('ENROLLED', 'DISCONTIN','COMPLETED','INVALID','UNCONFIRM')  )
1645               OR (p_calling_obj = 'PLAN' AND sua.unit_attempt_status IN ('ENROLLED', 'DISCONTIN','COMPLETED','INVALID','UNCONFIRM','PLANNED') )
1646               OR (sua.unit_attempt_status = 'WAITLISTED' AND FND_PROFILE.VALUE('IGS_EN_VAL_WLST')  ='Y'))
1647       AND      sua.unit_cd = psv.unit_cd
1648       AND      sua.version_number = psv.version_number
1649       AND      ( ( sua.unit_cd = cp_unit_cd AND sua.version_number =  cp_version_number)
1650                 OR  psv.rpt_fmly_id = ( SELECT   psu.rpt_fmly_id
1651                                       FROM igs_ps_unit_ver psu,
1652                                            igs_ps_rpt_fmly rep
1653                                       WHERE psu.unit_cd                 = cp_unit_cd
1654                                       AND   psu.version_number          = cp_version_number
1655                                       AND   psu.rpt_fmly_id             = rep.rpt_fmly_id
1656                                       AND   NVL(rep.closed_ind,'N')     = 'N' )
1657                 )
1658       UNION
1659       SELECT  adv.unit_cd,
1660               adv.version_number,
1661               NULL cal_type,
1662               TO_NUMBER(NULL) ci_sequence_number,
1663               TO_NUMBER(NULL) uoo_id,
1664               adv.achievable_credit_points  override_enrolled_cp  ,
1665               adv.as_course_cd  course_cd
1666       FROM     igs_av_stnd_unit adv, igs_ps_unit_ver psv
1667       WHERE   adv.person_id = p_person_id
1668       AND     adv.s_adv_stnd_granting_status = 'GRANTED'
1669       AND    (adv.s_adv_stnd_recognition_type = 'CREDIT'
1670               AND igs_av_val_asu.granted_adv_standing(adv.person_id,adv.as_course_cd,adv.as_version_number,adv.unit_cd,adv.version_number,'GRANTED',NULL) ='TRUE' )
1671       AND      cp_include_in_adv_stand = 'Y'
1672       AND    adv.unit_cd = psv.unit_cd
1673        AND   adv.version_number = psv.version_number
1674        AND  (  ( adv.unit_cd = cp_unit_cd AND adv.version_number = cp_version_number )
1675              OR  psv.rpt_fmly_id = (SELECT   psu.rpt_fmly_id
1676                                      FROM igs_ps_unit_ver psu,
1677                                           igs_ps_rpt_fmly rep
1678                                      WHERE psu.unit_cd                 = cp_unit_cd
1679                                      AND   psu.version_number          = cp_version_number
1680                                      AND   psu.rpt_fmly_id             = rep.rpt_fmly_id
1681                                      AND   NVL(rep.closed_ind,'N')     = 'N')
1682              );
1683     --
1684     -- Cursor to find if the unit version is repeatable and Maximum Repeats for credit
1685     --
1686     CURSOR  cur_unit_repeat_for_cp(cp_unit_cd   igs_ps_unit_ver.unit_cd%TYPE,
1687              cp_version_number igs_ps_unit_ver.version_number%TYPE)  IS
1688       SELECT  repeatable_ind,max_repeats_for_credit, max_repeats_for_funding
1689       FROM  igs_ps_unit_ver
1690       WHERE  unit_cd = cp_unit_cd
1691       AND  version_number = cp_version_number;
1692 
1693     --  Cursor to find the Organization Unit Code.
1694     --  Organization Unit Code defined at Unit level is taken if it is not defined at Unit Section level.
1695     --
1696     CURSOR cur_organization_unit IS
1697       SELECT   NVL (usec.owner_org_unit_cd, uv.owner_org_unit_cd) owner_org_unit_cd
1698       FROM     igs_ps_unit_ofr_opt usec,
1699                igs_ps_unit_ver uv
1700       WHERE    usec.uoo_id = p_uoo_id
1701       AND      usec.unit_cd = uv.unit_cd
1702       AND      usec.version_number = uv.version_number
1703       AND p_uoo_id  IS NOT NULL
1704       UNION
1705       SELECT uv.owner_org_unit_cd
1706       FROM igs_ps_unit_ver uv
1707       WHERE uv.unit_cd = p_unit_cd
1708       AND   uv.version_number = p_unit_version
1709       AND  p_uoo_id IS NULL;
1710 
1711     rec_cur_unit_details cur_unit_details%ROWTYPE;
1712     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
1713     l_number_of_repeats NUMBER := 0 ;
1714     l_include_in_advanced_standing igs_en_rep_process.include_adv_standing_units%TYPE := 'N';
1715     l_repeat_allowed igs_ps_unit_ver.repeatable_ind%TYPE ;
1716     l_max_repeats NUMBER;
1717     l_unit_max_repeats NUMBER;
1718     l_org_max_repeats NUMBER;
1719     l_owner_org_unit_cd igs_ps_unit_ver.owner_org_unit_cd%TYPE;
1720     l_user_hook_successful BOOLEAN;
1721     l_message         VARCHAR2(100);
1722     l_org_unit_id    NUMBER;
1723     l_unit_max_repeats_funding NUMBER;
1724     l_org_max_repeats_funding NUMBER;
1725     l_max_repeat_funding NUMBER;
1726     l_message_icon VARCHAR2(1);
1727     l_message_token VARCHAR2(100);
1728   BEGIN
1729 
1730     -- check if all the parameters uoo_id,unit_cd , unit_version are null show a message
1731      IF p_uoo_id IS NULL AND ( p_unit_cd IS NULL OR p_unit_version IS NULL) THEN
1732         IF (p_message IS NULL) THEN
1733            p_message := 'IGS_EN_NO_REPEAT_PAR';
1734          ELSE
1735            p_message := p_message || ';' || 'IGS_EN_NO_REPEAT_PAR';
1736          END IF;
1737         RETURN FALSE;
1738      END IF;
1739     --
1740     --  Check whether Unit Level Repeat step has been overridden.
1741     -- this check is performed only when uoo_id is passed
1742     IF p_uoo_id IS NOT NULL THEN
1743       IF Igs_En_Gen_015.validation_step_is_overridden (
1744          'UNIT_RPT',
1745          p_load_cal_type,
1746          p_load_cal_seq_number,
1747          p_person_id,
1748          p_uoo_id,
1749          l_step_override_limit
1750        ) THEN
1751          RETURN TRUE;
1752       END IF;
1753       --
1754       --  Get the Unit Details for the passed Unit Section.
1755       --
1756       OPEN cur_unit_details;
1757       FETCH cur_unit_details INTO rec_cur_unit_details;
1758       CLOSE cur_unit_details;
1759     ELSE --if uoo_id is null use the parameters for unit_cd,version passed to this function
1760       rec_cur_unit_details.unit_cd := p_unit_cd;
1761       rec_cur_unit_details.version_number := p_unit_version;
1762       rec_cur_unit_details.cal_type := NULL;
1763       rec_cur_unit_details.ci_sequence_number  :=  NULL;
1764     END IF;
1765 
1766         --
1767     --  Check if the Unit Section is Repeatable.
1768     --  at unit level
1769      OPEN cur_unit_repeat_for_cp(rec_cur_unit_details.unit_cd,
1770          rec_cur_unit_details.version_number) ;
1771      FETCH cur_unit_repeat_for_cp INTO l_repeat_allowed,l_unit_max_repeats,l_unit_max_repeats_funding ;
1772      IF cur_unit_repeat_for_cp%NOTFOUND OR l_repeat_allowed IS NULL THEN
1773        l_repeat_allowed := 'N';
1774      END IF;
1775      CLOSE cur_unit_repeat_for_cp ;
1776 
1777     --If repeatable indicator is 'Y' means unit is setup for reenrollment
1778     IF (l_repeat_allowed = 'Y' OR l_repeat_allowed = 'X') THEN
1779        -- Repeat is not allowed, unit is set for Reenrollment.
1780        RETURN  TRUE;
1781     END IF;
1782 
1783     --
1784     --  Check if the "Include Advanced Standing Units" value is 'Y'es for the
1785     --  Organizaion Unit of the Unit Code (of the passed Unit Section).
1786     --
1787     OPEN cur_organization_unit;
1788     FETCH cur_organization_unit INTO l_owner_org_unit_cd;
1789     CLOSE cur_organization_unit;
1790     --
1791     OPEN cur_org_incl_adv_stand (l_owner_org_unit_cd);
1792     FETCH cur_org_incl_adv_stand INTO l_include_in_advanced_standing,l_org_max_repeats,l_org_max_repeats_funding,l_org_unit_id;
1793     IF (cur_org_incl_adv_stand%NOTFOUND) THEN
1794       l_include_in_advanced_standing := 'N';
1795     END IF;
1796     CLOSE cur_org_incl_adv_stand;
1797 
1798     -- if the limit defined at unit level consider the same otherwise take the limit defined at org unit level
1799     l_max_repeats := NVL(l_unit_max_repeats,l_org_max_repeats);
1800     l_max_repeat_funding := NVL(l_unit_max_repeats_funding,l_org_max_repeats_funding);
1801 
1802 
1803     --  Calculate the Repeat Credit Points and Number of Repeats.
1804     --  Check if the Unit can be repeated in the same Teaching Period in the "Unit Section" level.
1805     --  If so calculate the total repats and repeat credit points within the same teach period also
1806     --
1807    FOR rec_cur_student_attempts IN cur_student_attempts (
1808              l_include_in_advanced_standing,
1809              rec_cur_unit_details.unit_cd,
1810              rec_cur_unit_details.version_number
1811            )
1812    LOOP
1813        l_number_of_repeats := l_number_of_repeats + 1;
1814     END LOOP;
1815 
1816 
1817     IF  (l_repeat_allowed = 'N') THEN
1818 
1819          IF NVL(FND_PROFILE.VALUE('IGS_EN_REP_REN'),'NONE') = 'BOTH'
1820          OR NVL(FND_PROFILE.VALUE('IGS_EN_REP_REN'),'NONE') = 'REPEAT_EXTERNAL' THEN
1821                 --
1822                 --  Call User Hook.
1823                 --
1824                 l_user_hook_successful := NULL;
1825                 l_user_hook_successful := IGS_EN_RPT_PRC_UHK.repeat_reenroll_allowed(
1826                                             p_person_id => p_person_id,
1827                                             p_program_cd => p_program_cd,
1828                                             p_unit_cd => rec_cur_unit_details.unit_cd,
1829                                             P_uoo_id => p_uoo_id,
1830                                             p_repeat_reenroll => 'REPEAT', -- repeat
1831                                             p_load_cal_type => p_load_cal_type,
1832                                             p_load_ci_seq_number => p_load_cal_seq_number,
1833                                             p_repeat_max => l_max_repeats,
1834                                             p_repeat_funding => l_max_repeat_funding,
1835                                             p_mus_ind => NULL,
1836                                             p_reenroll_max => NULL,
1837                                             p_reenroll_max_cp => NULL,
1838                                             p_same_tch_reenroll_max => NULL,
1839                                             p_same_tch_reenroll_max_cp => NULL,
1840                                             p_message => l_message);
1841                 IF NVL(l_user_hook_successful,FALSE) THEN
1842                     p_repeat_tag := 'Y';
1843                      RETURN TRUE;
1844                 ELSE
1845 
1846                     IF l_message IS NULL THEN
1847                       l_message_token := 'UNIT_CD:'||l_max_repeats||';';
1848                     END IF;
1849                     p_repeat_tag := 'Y';
1850 
1851                     IF p_deny_warn = 'DENY' THEN
1852 
1853                       IF p_calling_obj = 'JOB' THEN
1854                         l_message := NVL(l_message,'IGS_SS_DENY_REPEAT_CHK');
1855                       ELSE
1856                         l_message := NVL(l_message,'IGS_EN_REPEAT_TAB_DENY');
1857                       END IF;
1858                     ELSE
1859                       IF p_calling_obj = 'JOB' THEN
1860                         l_message :=  NVL(l_message,'IGS_SS_WARN_REPEAT_CHK');
1861                       ELSE
1862                         l_message := NVL(l_message,'IGS_EN_REPEAT_TAB_WARN');
1863                       END IF;
1864                     END IF;
1865 
1866                     IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
1867 
1868                       l_message_icon := substr(p_deny_warn,1,1);
1869                         igs_en_drop_units_api.create_ss_warning (
1870                                p_person_id => p_person_id,
1871                                p_course_cd => p_program_cd,
1872                                p_term_cal_type=> p_load_cal_type,
1873                                p_term_ci_sequence_number => p_load_cal_seq_number,
1874                                p_uoo_id => p_uoo_id,
1875                                p_message_for => rec_cur_unit_details.unit_cd||'/'||rec_cur_unit_details.unit_class,
1876                                p_message_icon=> l_message_icon,
1877                                p_message_name => l_message,
1878                                p_message_rule_text => NULL,
1879                                p_message_tokens => l_message_token,
1880                                p_message_action=> NULL,
1881                                p_destination =>NULL,
1882                                p_parameters => NULL,
1883                                p_step_type => 'UNIT');
1884 
1885                     ELSE
1886                         IF (p_message IS NULL) THEN
1887                           p_message := l_message;
1888                         ELSE
1889                           p_message := p_message || ';' || l_message;
1890                         END IF;
1891                     END IF; --IF p_calling_obj <> 'JOB'
1892 
1893                   RETURN FALSE;
1894                 END IF; -- user hook successful
1895 
1896          END IF; -- FND_PROFILE.VALUE
1897 
1898     END IF; -- l_repeat_allowed
1899 
1900      --  If there is no student unit attempt then the Unit is not considered as repeat.
1901     --  So return TRUE.
1902     IF l_number_of_repeats = 0 THEN
1903          p_repeat_tag := 'N';
1904          RETURN TRUE;
1905     END IF;
1906 
1907     IF l_max_repeats IS NULL THEN
1908        -- no limits defined means unlimited repeats allowed
1909        RETURN TRUE;
1910     END IF;
1911 
1912       IF (l_number_of_repeats <= l_max_repeats)  THEN
1913             p_repeat_tag := 'Y' ;
1914             RETURN  TRUE;
1915       END IF;
1916 
1917        IF p_deny_warn = 'DENY' THEN
1918            IF p_calling_obj = 'JOB' THEN
1919             l_message := NVL(l_message,'IGS_SS_DENY_REPEAT_CHK');
1920           ELSE
1921             l_message := NVL(l_message,'IGS_EN_REPEAT_TAB_DENY');
1922             l_message_token := 'UNIT_CD:'||l_max_repeats||';';
1923           END IF;
1924         ELSE
1925           IF p_calling_obj = 'JOB' THEN
1926             l_message :=  NVL(l_message,'IGS_SS_WARN_REPEAT_CHK');
1927           ELSE
1928             l_message := NVL(l_message,'IGS_EN_REPEAT_TAB_WARN');
1929             l_message_token := 'UNIT_CD:'||l_max_repeats||';';
1930           END IF;
1931         END IF;
1932 
1933        IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
1934 
1935           l_message_icon := substr(p_deny_warn,1,1);
1936           igs_en_drop_units_api.create_ss_warning (
1937                  p_person_id => p_person_id,
1938                  p_course_cd => p_program_cd,
1939                  p_term_cal_type=> p_load_cal_type,
1940                  p_term_ci_sequence_number => p_load_cal_seq_number,
1941                  p_uoo_id => p_uoo_id,
1942                  p_message_for => rec_cur_unit_details.unit_cd||'/'||rec_cur_unit_details.unit_class,
1943                  p_message_icon=> l_message_icon,
1944                  p_message_name => l_message,
1945                  p_message_rule_text => NULL,
1946                  p_message_tokens => l_message_token,
1947                  p_message_action=> NULL,
1948                  p_destination =>NULL,
1949                  p_parameters => NULL,
1950                  p_step_type => 'UNIT');
1951 
1952       ELSE
1953           IF (p_message IS NULL) THEN
1954             p_message := l_message;
1955           ELSE
1956             p_message := p_message || ';' || l_message;
1957           END IF;
1958       END IF; --IF p_calling_obj <> 'JOB'
1959 
1960        p_repeat_tag := 'Y';
1961        RETURN FALSE;
1962 
1963   END eval_unit_repeat;
1964 
1965 
1966 
1967 
1968 
1969 
1970 
1971 FUNCTION eval_unit_reenroll (
1972     p_person_id                    IN     NUMBER,
1973     p_load_cal_type                IN     VARCHAR2,
1974     p_load_cal_seq_number          IN     NUMBER,
1975     p_uoo_id                       IN     NUMBER,
1976     p_program_cd                   IN     VARCHAR2,
1977     p_program_version              IN     NUMBER,
1978     p_deny_warn                    IN     VARCHAR2,
1979     p_upd_cp                       IN     NUMBER,
1980     p_message                      IN OUT NOCOPY VARCHAR2,
1981     p_val_level                    IN     VARCHAR2,
1982     p_calling_obj                  IN     VARCHAR2
1983   ) RETURN BOOLEAN AS
1984   ------------------------------------------------------------------------------------
1985     --Created by  : rvivekan ( Oracle IDC)
1986     --Date created: 18-JUN-2003
1987     --
1988     --Purpose:  this function returns TRUE for a given student and unit attempt
1989     --          if the unit attempt is in line with reenroll validation
1990     --         (if applicable).Introduced as a prt of reenrollment and repeat build #2881363
1991     --
1992     --Known limitations/enhancements and/or remarks:
1993     --
1994     --Change History:
1995     --Who         When            What
1996     --jbegum      25-jun-03       BUG#2930935
1997     --                            Modified the cursor cur_student_attempts.
1998     --rvivekan    9-sep-03        modified column name in cur_reenroll_in_same_tp_usec
1999     --                            definitions of l_reenroll_in_same_tp and l_reenroll_allowed #3052433
2000     -- svanukur   14-jan-2004     Cahnged the condition that checks for l_reenroll_in_same_tp to 'N'
2001     --                              bug 3368048
2002     --stutta      05-Aug-2004     Added call to user hook depending on profile value IGS_EN_REP_REN.
2003     --                            Build # 3807707
2004     -- smaddali  29-mar-05   Modified this procedure for bug#4262571
2005     -------------------------------------------------------------------------------------
2006 
2007    -- Cursor to get the unit section details
2008     CURSOR cur_unit_details IS
2009       SELECT   unit_cd,
2010                unit_class,
2011                version_number,
2012                cal_type,
2013                ci_sequence_number
2014       FROM     igs_ps_unit_ofr_opt
2015       WHERE    uoo_id = p_uoo_id;
2016 
2017     -- smaddali modified this cursor to add advance standing units also, bug#4262571
2018     --  Cursor to select all the reenrolled Unit Attempts of the Student.
2019       CURSOR cur_student_attempts (
2020              cp_unit_cd   igs_ps_unit_ver.unit_cd%TYPE,
2021              cp_version_number igs_ps_unit_ver.version_number%TYPE
2022            ) IS
2023       SELECT  sua.unit_cd,
2024               sua.version_number,
2025               sua.cal_type,
2026               sua.ci_sequence_number,
2027               sua.uoo_id,
2028               NVL(sua.override_enrolled_cp,NVL(cps.enrolled_credit_points,uv.enrolled_credit_points))  override_enrolled_cp ,
2029               sua.course_cd
2030       FROM     igs_en_su_attempt sua,
2031                igs_ps_unit_ver uv,
2032                igs_ps_usec_cps cps
2033       WHERE    sua.person_id = p_person_id
2034       AND      sua.unit_cd = uv.unit_cd
2035       AND      sua.version_number = uv.version_number
2036       AND      sua.unit_cd = cp_unit_cd
2037       AND      sua.version_number = cp_version_number
2038       AND      sua.uoo_id = cps.uoo_id(+)
2039       AND      ((p_calling_obj <> 'PLAN' AND unit_attempt_status IN ('ENROLLED', 'DISCONTIN','COMPLETED','INVALID','UNCONFIRM')  )
2040                OR (p_calling_obj = 'PLAN' AND unit_attempt_status IN ('ENROLLED', 'DISCONTIN','COMPLETED','INVALID','UNCONFIRM','PLANNED') )
2041                OR (unit_attempt_status = 'WAITLISTED' AND FND_PROFILE.VALUE('IGS_EN_VAL_WLST')  ='Y'))
2042       AND      ( sua.cart IS NOT NULL AND ( p_calling_obj <> 'SWAP' OR (p_calling_obj = 'SWAP' AND sua.uoo_id <> p_uoo_id) ) )
2043       UNION
2044       SELECT  adv.unit_cd,
2045               adv.version_number,
2046               NULL cal_type,
2047               TO_NUMBER(NULL) ci_sequence_number,
2048               TO_NUMBER(NULL) uoo_id,
2049               adv.achievable_credit_points  override_enrolled_cp  ,
2050               adv.as_course_cd  course_cd
2051       FROM     igs_av_stnd_unit adv
2052       WHERE   adv.person_id = p_person_id
2053       AND     adv.s_adv_stnd_granting_status = 'GRANTED'
2054       AND    (adv.s_adv_stnd_recognition_type = 'CREDIT'
2055               AND igs_av_val_asu.granted_adv_standing(adv.person_id,adv.as_course_cd,adv.as_version_number,adv.unit_cd,adv.version_number,'GRANTED',NULL) ='TRUE' )
2056       AND      adv.unit_cd = cp_unit_cd
2057       AND     adv.version_number = cp_version_number;
2058 
2059     --
2060     --  Cursor to get the same Teaching Period indicator  at Unit Section  level.
2061     --
2062     CURSOR cur_reenroll_in_same_tp_usec IS
2063       SELECT   not_multiple_section_flag
2064       FROM     igs_ps_unit_ofr_opt
2065       WHERE    uoo_id = p_uoo_id;
2066 
2067     --
2068     -- Cursor to get the reenroll allowed indicator and the reenrollment limits
2069     --
2070     CURSOR  cur_unit_reenroll_details(cp_unit_cd   igs_ps_unit_ver.unit_cd%TYPE,
2071              cp_version_number igs_ps_unit_ver.version_number%TYPE)  IS
2072       SELECT  repeatable_ind,same_teach_period_repeats,same_teach_period_repeats_cp,
2073               max_repeats_for_credit,max_repeat_credit_points, same_teaching_period
2074       FROM  igs_ps_unit_ver
2075       WHERE  unit_cd = cp_unit_cd
2076       AND  version_number = cp_version_number;
2077 
2078     --
2079     rec_cur_unit_details cur_unit_details%ROWTYPE;
2080     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
2081     l_no_of_reenrollments NUMBER := 0 ;
2082     l_total_reenroll_credit_points NUMBER := 0 ;
2083     l_reenroll_in_same_tp  igs_ps_unit_ofr_opt.not_multiple_section_flag%TYPE;
2084     l_reenroll_allowed igs_ps_unit_ver.repeatable_ind%TYPE ;
2085     l_max_reenrollments_for_credit NUMBER ;
2086     l_max_renroll_credit_points NUMBER  ;
2087     l_count  NUMBER := 0;
2088     l_same_tp_reenrollments NUMBER := 0 ;
2089     l_same_tp_cp NUMBER := 0;
2090     l_max_same_tp_reenrollments  NUMBER ;
2091     l_max_same_tp_cp  NUMBER;
2092     l_message         VARCHAR2(100);
2093     l_reenroll_fail BOOLEAN DEFAULT FALSE;
2094     l_reenroll_cp_fail BOOLEAN DEFAULT FALSE;
2095     l_reenroll_same_tp_fail BOOLEAN DEFAULT FALSE;
2096     l_reenroll_same_tp_cp_fail BOOLEAN DEFAULT FALSE;
2097     l_user_hook_successful BOOLEAN;
2098     l_unit_mus VARCHAR2(1);
2099     l_mus_ind VARCHAR2(1);
2100     l_message_icon VARCHAR2(1);
2101     l_message_token VARCHAR2(100);
2102   BEGIN
2103 
2104   --
2105   --  Check whether Unit Level Reenroll step has been overridden.
2106   -- this check is performed only when uoo_id is passed
2107   IF p_uoo_id IS NOT NULL THEN
2108     IF Igs_En_Gen_015.validation_step_is_overridden (
2109        'REENROLL',
2110        p_load_cal_type,
2111        p_load_cal_seq_number,
2112        p_person_id,
2113        p_uoo_id,
2114        l_step_override_limit
2115      ) THEN
2116 
2117        RETURN TRUE;
2118     END IF;
2119    END IF;
2120     --
2121     --  Get the Unit Details for the passed Unit Section.
2122     --
2123     OPEN cur_unit_details;
2124     FETCH cur_unit_details INTO rec_cur_unit_details;
2125     CLOSE cur_unit_details;
2126 
2127   --  Check if the Unit Section is Reenrollment allowed.
2128    OPEN cur_unit_reenroll_details(rec_cur_unit_details.unit_cd,
2129                              rec_cur_unit_details.version_number) ;
2130    FETCH cur_unit_reenroll_details INTO l_reenroll_allowed,l_max_same_tp_reenrollments,l_max_same_tp_cp,
2131                   l_max_reenrollments_for_credit, l_max_renroll_credit_points, l_unit_mus;
2132 
2133 
2134    IF cur_unit_reenroll_details%NOTFOUND OR l_reenroll_allowed IS NULL THEN
2135       l_reenroll_allowed := 'N';
2136    END IF;
2137    CLOSE cur_unit_reenroll_details ;
2138 
2139      --If repeatable indicator is 'N' means the unit is set for reenroll processing
2140     IF (l_reenroll_allowed IN ('N','X') ) THEN
2141       RETURN  TRUE;
2142     END IF;
2143     --  Calculate the Reenrollment Credit Points and Number of Reenrollments.
2144     --
2145    FOR rec_cur_student_attempts IN cur_student_attempts (
2146              rec_cur_unit_details.unit_cd,
2147              rec_cur_unit_details.version_number
2148            )
2149    LOOP
2150        l_count := l_count + 1;
2151 
2152           l_total_reenroll_credit_points := l_total_reenroll_credit_points + rec_cur_student_attempts.override_enrolled_cp;
2153           l_no_of_reenrollments := l_no_of_reenrollments + 1;
2154           --
2155           --  Check whether this Unit has already been taken in the Same Teaching Period selected for Enrollment.
2156           --
2157           IF (( rec_cur_unit_details.cal_type = rec_cur_student_attempts.cal_type AND
2158                rec_cur_unit_details.ci_sequence_number = rec_cur_student_attempts.ci_sequence_number
2159          ) OR
2160          ( rec_cur_student_attempts.cal_type IS NULL AND
2161             rec_cur_student_attempts.ci_sequence_number IS NULL
2162     )
2163         ) THEN
2164              l_same_tp_cp := l_same_tp_cp +  rec_cur_student_attempts.override_enrolled_cp;
2165              l_same_tp_reenrollments  := l_same_tp_reenrollments + 1 ;
2166           END IF;
2167 
2168     END LOOP;
2169 
2170     --
2171     --  get the same Teaching Period indicator  at the  Unit section level.
2172     -- setting the null value to be 'Y' since a value of 'N' implies unit is
2173     -- part of MUS.
2174     OPEN cur_reenroll_in_same_tp_usec;
2175     FETCH cur_reenroll_in_same_tp_usec INTO l_reenroll_in_same_tp;
2176     IF  cur_reenroll_in_same_tp_usec%NOTFOUND  OR l_reenroll_in_same_tp IS NULL  THEN
2177            l_reenroll_in_same_tp := 'Y';
2178     END IF;
2179     CLOSE cur_reenroll_in_same_tp_usec;
2180 
2181     IF  (l_reenroll_allowed = 'Y') THEN
2182 
2183          IF NVL(FND_PROFILE.VALUE('IGS_EN_REP_REN'),'NONE') = 'BOTH'
2184          OR NVL(FND_PROFILE.VALUE('IGS_EN_REP_REN'),'NONE') = 'REENROLL_EXTERNAL' THEN
2185                 --
2186                 --  Call User Hook.
2187                 --
2188                 IF l_unit_mus = 'N' OR l_reenroll_in_same_tp = 'Y' THEN
2189                   -- if MUS not selected at unit level or Excluded at unit section level
2190                     l_mus_ind := 'N';
2191                 ELSE
2192                   --
2193                     l_mus_ind := 'Y';
2194                 END IF;
2195 
2196                 l_user_hook_successful := NULL;
2197                 l_user_hook_successful := IGS_EN_RPT_PRC_UHK.repeat_reenroll_allowed(
2198                                             p_person_id => p_person_id,
2199                                             p_program_cd => p_program_cd,
2200                                             p_unit_cd => rec_cur_unit_details.unit_cd,
2201                                             P_uoo_id => p_uoo_id,
2202                                             p_repeat_reenroll => 'REENROLL',
2203                                             p_load_cal_type => p_load_cal_type,
2204                                             p_load_ci_seq_number => p_load_cal_seq_number,
2205                                             p_repeat_max => NULL,
2206                                             p_repeat_funding => NULL,
2207                                             p_mus_ind => l_mus_ind,
2208                                             p_reenroll_max => l_max_reenrollments_for_credit,
2209                                             p_reenroll_max_cp => l_max_renroll_credit_points,
2210                                             p_same_tch_reenroll_max => l_max_same_tp_reenrollments,
2211                                             p_same_tch_reenroll_max_cp => l_max_same_tp_cp,
2212                                             p_message => l_message);
2213                 IF NVL(l_user_hook_successful,FALSE) THEN
2214                      RETURN TRUE;
2215                 ELSE
2216                   -- set the token only when l_message is null
2217                   IF l_message IS NULL THEN
2218                     l_message_token := 'UNIT_CD'||':'||l_max_reenrollments_for_credit||';';
2219                   END IF;
2220                     -- Check if message is returned from user hook
2221                   IF p_deny_warn = 'DENY' THEN
2222                     IF p_calling_obj IN ('JOB','SCH_UPD') THEN
2223                       l_message := NVL(l_message,'IGS_SS_DENY_REENR_CHK');
2224                     ELSE
2225                       l_message := NVL(l_message,'IGS_EN_REENRL_TAB_DENY');
2226                     END IF;
2227                   ELSE
2228                     IF p_calling_obj = 'JOB' THEN
2229                       l_message := NVL(l_message,'IGS_SS_WARN_REENR_CHK');
2230                     ELSIF p_calling_obj <> 'SCH_UPD' THEN
2231                       l_message := NVL(l_message,'IGS_EN_REENRL_TAB_WARN');
2232                     END IF;
2233 
2234                   END IF; -- p_message = 'DENY'
2235 
2236                   IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
2237 
2238                     l_message_icon := substr(p_deny_warn,1,1);
2239                     igs_en_drop_units_api.create_ss_warning (
2240                            p_person_id => p_person_id,
2241                            p_course_cd => p_program_cd,
2242                            p_term_cal_type=> p_load_cal_type,
2243                            p_term_ci_sequence_number => p_load_cal_seq_number,
2244                            p_uoo_id => p_uoo_id,
2245                            p_message_for => rec_cur_unit_details.unit_cd||'/'||rec_cur_unit_details.unit_class,
2246                            p_message_icon=> l_message_icon,
2247                            p_message_name => l_message,
2248                            p_message_rule_text => NULL,
2249                            p_message_tokens => l_message_token,
2250                            p_message_action=> NULL,
2251                            p_destination =>NULL,
2252                            p_parameters => NULL,
2253                            p_step_type => 'UNIT');
2254 
2255                   ELSE
2256                       IF (p_message IS NULL) THEN
2257                         p_message := l_message;
2258                       ELSE
2259                         p_message := p_message || ';' || l_message;
2260                       END IF;
2261                 END IF; --IF p_calling_obj <> 'JOB'
2262                   RETURN FALSE;
2263                 END IF; -- user hook successful
2264          END IF; -- FND_PROFILE.VALUE
2265     END IF; -- l_reenroll_allowed
2266 
2267   --  There are no reenrolled unit attempts or advance standing for this unit
2268   --  So return TRUE.
2269   -- smaddali moved this code from before calling the user hook, for bug#4262571
2270     IF l_count = 0 THEN
2271          RETURN TRUE;
2272     END IF;
2273 
2274     -- If limit is NUll  then it means no limit is set
2275     l_max_reenrollments_for_credit := NVL (l_max_reenrollments_for_credit, 999999);
2276     l_max_renroll_credit_points := NVL (l_max_renroll_credit_points, 999.999);
2277     l_max_same_tp_reenrollments := NVL(l_max_same_tp_reenrollments,999999) ;
2278     l_max_same_tp_cp  :=  NVL(l_max_same_tp_cp,999.999) ;
2279 
2280     -- If the procedure called when user has overriden the unit attempt credit points
2281     -- then the difference would be passed in to the parameter p_upd_cp
2282     -- Add this cp to the total credit points
2283        l_total_reenroll_credit_points := l_total_reenroll_credit_points + NVL(p_upd_cp,0);
2284        l_same_tp_cp := l_same_tp_cp +  NVL(p_upd_cp,0);
2285 
2286       IF (l_no_of_reenrollments > l_max_reenrollments_for_credit) THEN
2287         l_reenroll_fail := TRUE;
2288       END IF;
2289 
2290       IF NOT(p_deny_warn = 'DENY' AND l_reenroll_fail) THEN
2291           IF (l_total_reenroll_credit_points > l_max_renroll_credit_points) THEN
2292             l_reenroll_cp_fail := TRUE;
2293           END IF;
2294       END IF;
2295    --check if l_reenroll_in_same_tp is 'N' since this means the unit is partof MUS
2296       IF l_reenroll_in_same_tp = 'N' THEN
2297          IF NOT(p_deny_warn = 'DENY' AND (l_reenroll_fail OR l_reenroll_cp_fail)) THEN
2298               IF (l_same_tp_reenrollments > l_max_same_tp_reenrollments) THEN
2299                 l_reenroll_same_tp_fail := TRUE;
2300               END IF;
2301 
2302               IF NOT(p_deny_warn = 'DENY' AND l_reenroll_same_tp_fail) THEN
2303                   IF (l_same_tp_cp > l_max_same_tp_cp) THEN
2304                     l_reenroll_same_tp_cp_fail := TRUE;
2305                   END IF;
2306               END IF;
2307          END IF;
2308       END IF;
2309 
2310    IF NOT l_reenroll_fail AND NOT l_reenroll_cp_fail AND NOT l_reenroll_same_tp_fail AND NOT l_reenroll_same_tp_cp_fail THEN
2311      -- No limit is breached.
2312 
2313      RETURN TRUE;
2314    END IF;
2315 
2316    IF p_deny_warn = 'WARN' THEN
2317 
2318       -- no warning messages for sch_upd
2319       IF p_calling_obj <> 'SCH_UPD' THEN
2320 
2321          IF l_reenroll_cp_fail THEN
2322             IF p_calling_obj = 'JOB' THEN
2323               l_message := 'IGS_SS_WARN_REENR_CP_CHK';
2324             ELSIF p_calling_obj <> 'SCH_UPD' THEN
2325               l_message := 'IGS_EN_REENCP_TAB_WARN';
2326               l_message_token := 'UNIT_CD'||':'||l_max_renroll_credit_points||';';
2327             END IF;
2328          END IF;
2329 
2330          IF l_reenroll_fail AND p_val_level='ALL' THEN
2331             IF p_calling_obj = 'JOB' THEN
2332               l_message := 'IGS_SS_WARN_REENR_CHK';
2333             ELSIF p_calling_obj <> 'SCH_UPD' THEN
2334               l_message := 'IGS_EN_REENRL_TAB_WARN';
2335               l_message_token := 'UNIT_CD'||':'||l_max_reenrollments_for_credit||';';
2336             END IF;
2337          END IF;
2338 
2339          IF l_reenroll_same_tp_cp_fail THEN
2340             IF p_calling_obj IN ('JOB','SCH_UPD') THEN
2341               l_message := 'IGS_SS_WARN_REENR_STP_CP_CHK';
2342             ELSE
2343               l_message := 'IGS_EN_REENCP_STP_TAB_WARN';
2344               l_message_token := 'UNIT_CD'||':'||l_max_same_tp_cp||';';
2345             END IF;
2346          END IF;
2347 
2348          IF l_reenroll_same_tp_fail AND p_val_level='ALL' THEN
2349             IF p_calling_obj IN ('JOB','SCH_UPD') THEN
2350               l_message := 'IGS_SS_WARN_REENR_STP_CHK';
2351             ELSE
2352               l_message := 'IGS_EN_REENR_STP_TAB_WARN';
2353               l_message_token := 'UNIT_CD'||':'||l_max_same_tp_reenrollments||';';
2354             END IF;
2355          END IF;
2356 
2357       END IF; -- IF p_calling_obj <> 'SCH_UPD'
2358 
2359    ELSE
2360        IF l_reenroll_cp_fail THEN
2361           IF p_calling_obj = 'SCH_UPD' THEN
2362             l_message  :=  'IGS_EN_REENR_UPD_DENY'  || '*' || l_max_renroll_credit_points ;
2363           ELSIF p_calling_obj = 'JOB' THEN
2364             l_message := 'IGS_SS_DENY_REENR_CP_CHK';
2365           ELSE
2366             l_message := 'IGS_EN_REENCP_TAB_DENY';
2367             l_message_token := 'UNIT_CD'||':'||l_max_renroll_credit_points||';';
2368           END IF;
2369        END IF;
2370 
2371        IF l_reenroll_fail AND p_val_level='ALL' THEN
2372           IF p_calling_obj IN ('JOB','SCH_UPD') THEN
2373             l_message := 'IGS_SS_DENY_REENR_CHK';
2374           ELSE
2375             l_message := 'IGS_EN_REENRL_TAB_DENY';
2376             l_message_token := 'UNIT_CD'||':'||l_max_reenrollments_for_credit||';';
2377           END IF;
2378        END IF;
2379 
2380        IF l_reenroll_same_tp_cp_fail THEN
2381           IF p_calling_obj = 'SCH_UPD' THEN
2382             l_message  :=  'IGS_EN_REENSTP_UPD_DENY' || '*' || l_max_same_tp_cp ;
2383           ELSIF p_calling_obj = 'JOB' THEN
2384             l_message := 'IGS_SS_DENY_REENR_STP_CP_CHK';
2385           ELSE
2386             l_message := 'IGS_EN_REENCP_STP_TAB_DENY';
2387             l_message_token := 'UNIT_CD'||':'||l_max_same_tp_cp||';';
2388           END IF;
2389        END IF;
2390 
2391        IF l_reenroll_same_tp_fail AND p_val_level='ALL' THEN
2392           IF p_calling_obj IN ('JOB','SCH_UPD') THEN
2393             l_message := 'IGS_SS_DENY_REENR_STP_CHK';
2394           ELSE
2395             l_message := 'IGS_EN_REENR_STP_TAB_DENY';
2396             l_message_token := 'UNIT_CD'||':'||l_max_same_tp_reenrollments||';';
2397           END IF;
2398        END IF;
2399    END IF;
2400 
2401    IF p_calling_obj NOT IN ('JOB','SCH_UPD') THEN
2402 
2403           l_message_icon := substr(p_deny_warn,1,1);
2404           igs_en_drop_units_api.create_ss_warning (
2405                  p_person_id => p_person_id,
2406                  p_course_cd => p_program_cd,
2407                  p_term_cal_type=> p_load_cal_type,
2408                  p_term_ci_sequence_number => p_load_cal_seq_number,
2409                  p_uoo_id => p_uoo_id,
2410                  p_message_for => rec_cur_unit_details.unit_cd||'/'||rec_cur_unit_details.unit_class,
2411                  p_message_icon=> l_message_icon,
2412                  p_message_name => l_message,
2413                  p_message_rule_text => NULL,
2414                  p_message_tokens => l_message_token,
2415                  p_message_action=> NULL,
2416                  p_destination =>NULL,
2417                  p_parameters => NULL,
2418                  p_step_type => 'UNIT');
2419 
2420     ELSE
2421             IF (p_message IS NULL) THEN
2422               p_message := l_message;
2423             ELSE
2424               p_message := p_message || ';' || l_message;
2425             END IF;
2426     END IF; --IF p_calling_obj <> 'JOB'
2427 
2428    RETURN FALSE;
2429     --
2430   END eval_unit_reenroll;
2431 
2432   --
2433   --
2434   --  This function is used to evaluate the Time Conflict for the Student's Unit Section Occurrences.
2435   --
2436   -- smaddali modified this function for PSP004 bug#2191501
2437   -- smaddali modified the two cursors ,to remove the NVL( day,'N') for all the days
2438   -- being selected .Since here the two occurrences conflict only if both have monday = 'Y'
2439   -- or tuesday = 'Y so on ... By selecting NVL(monday,'N') even though both are not  ='Y'
2440   -- they are equal to each other because of the NVL and hence is being considered as conflicting
2441   FUNCTION eval_time_conflict
2442   (
2443     p_person_id                    IN     NUMBER,
2444     p_load_cal_type                IN     VARCHAR2,
2445     p_load_cal_seq_number          IN     NUMBER,
2446     p_uoo_id                       IN     NUMBER,
2447     p_program_cd                   IN     VARCHAR2,
2448     p_program_version              IN     VARCHAR2,
2449     p_message                      IN OUT NOCOPY VARCHAR2,
2450     p_deny_warn                    IN     VARCHAR2,
2451     p_calling_obj                  IN     VARCHAR2
2452   ) RETURN BOOLEAN AS
2453 
2454 /*--------------------------------------------------------------------------------+
2455  | HISTORY                                                                        |
2456  | Who         When           What                                                |
2457  |ptandon     1-Sep-2003     Modified the cursor cur_usec_occurs_existing         |
2458  |                           to consider waitlisted students based on the value   |
2459  |                           of checkbox 'Waitlist Allowed with Time Conflict'    |
2460  |                           in institutional waitlist options form and the       |
2461  |                           profile has been obsolete as part of Waitlist        |
2462  |                           Enhancements Build - Bug# 3052426                    |
2463  |ptandon    14-Jan-2004     Modified the cursor cur_usec_occurs_existing to      |
2464  |                           change the unit attempt status from WAITLIST to      |
2465  |                           WAITLISTED. Bug# 3371080.                            |
2466  +-------------------------------------------------------------------------------*/
2467     --
2468     --  Parameters Description:
2469     --
2470     --  p_person_id                  -> Person ID of the student who wants to enroll or administrator is enrolling.
2471     --  p_load_cal_type              -> Load (Term) or Teaching Calendar Type.
2472     --  p_load_cal_seq_number        -> Load Calendar or Teaching Calendar instance sequence number.
2473     --  p_uoo_id                     -> Unit Section Identifier.
2474     --  p_program_cd                 -> The Primary Program Code or the Program code selected by the student.
2475     --  p_program_version            -> The Primary Program version number or the Program version number selected by the student.
2476     --  p_message                    -> Message from the validation.
2477     --  p_deny_warn                  -> Deny or Warn Indicator based on the setup.
2478     --
2479     --
2480     --  Cursor to find Unit Section Occurrences for the passed Unit Section.
2481     --
2482     CURSOR cur_usec_occurs_new (
2483              cp_uoo_id                IN NUMBER
2484            ) IS
2485     SELECT   uocr.monday ,
2486              uocr.tuesday ,
2487              uocr.wednesday,
2488              uocr.thursday,
2489              uocr.friday ,
2490              uocr.saturday ,
2491              uocr.sunday ,
2492              uocr.start_time start_time,
2493              uocr.end_time end_time,
2494              uoo.unit_cd,
2495              uoo.unit_class,
2496              NVL (uocr.start_date, NVL (uoo.unit_section_start_date, ci.start_dt)) start_date,
2497              NVL (uocr.end_date, NVL (uoo.unit_section_end_date, ci.end_dt)) end_date
2498     FROM     igs_ps_usec_occurs uocr,
2499              igs_ps_unit_ofr_opt uoo,
2500              igs_ca_inst ci
2501     WHERE    uoo.uoo_id = cp_uoo_id
2502     AND      uoo.uoo_id = uocr.uoo_id
2503     AND      uoo.cal_type = ci.cal_type
2504     AND      uoo.ci_sequence_number = ci.sequence_number;
2505     --
2506     --  Cursor to find existing Unit Section Occurrences that the Student has already attempted.
2507     --
2508     CURSOR cur_usec_occurs_existing IS
2509     SELECT   uocur.uoo_id,
2510              uocur.monday,
2511              uocur.tuesday,
2512              uocur.wednesday,
2513              uocur.thursday,
2514              uocur.friday,
2515              uocur.saturday,
2516              uocur.sunday,
2517              uocur.start_time,
2518              uocur.end_time,
2519              uoo.unit_cd,
2520              uoo.unit_class,
2521              NVL (uocur.start_date, NVL (uoo.unit_section_start_date, lt.start_dt)) start_date,
2522              NVL (uocur.end_date, NVL (uoo.unit_section_end_date, lt.end_dt)) end_date
2523     FROM     igs_ps_usec_occurs uocur,
2524              igs_en_su_attempt_all ua,
2525              igs_ca_inst lt,
2526              igs_ps_unit_ofr_opt_all uoo
2527     WHERE    uocur.uoo_id = ua.uoo_id
2528     AND      uoo.uoo_id = ua.uoo_id
2529     AND      ua.uoo_id <> p_uoo_id
2530     AND      ua.cal_type = lt.cal_type
2531     AND      ua.ci_sequence_number = lt.sequence_number
2532     AND      ua.person_id = p_person_id
2533     AND     (
2534               (  p_calling_obj <>'PLAN' AND
2535                   ( ua.unit_attempt_status IN ( 'ENROLLED','INVALID') OR
2536                         ( ua.unit_attempt_status = 'WAITLISTED' AND
2537                               ( EXISTS(SELECT 'X' FROM IGS_EN_INST_WL_STPS  WHERE TIME_CONFL_ALWD_WLST_FLAG = 'N' ) OR
2538                                   ( NOT EXISTS(SELECT 'X' FROM IGS_EN_INST_WL_STPS  )  AND FND_PROFILE.VALUE('IGS_EN_VAL_WLST')  ='Y' )
2539                                )
2540                          )
2541                    )
2542                )
2543               OR
2544               ( p_calling_obj ='PLAN' AND
2545                      (ua.unit_attempt_status IN ( 'ENROLLED','INVALID','PLANNED') OR
2546                            (ua.unit_attempt_status = 'WAITLISTED' AND (EXISTS(SELECT 'X' FROM IGS_EN_INST_WL_STPS WHERE TIME_CONFL_ALWD_WLST_FLAG = 'N')  )  OR
2547                                 ( NOT EXISTS(SELECT 'X' FROM IGS_EN_INST_WL_STPS  )  AND FND_PROFILE.VALUE('IGS_EN_VAL_WLST')  ='Y' )
2548                             )
2549                       )
2550                )
2551 
2552             );
2553 
2554      --
2555     rec_cur_usec_occurs_new     cur_usec_occurs_new%ROWTYPE;
2556     l_step_override_limit       igs_en_elgb_ovr_step.step_override_limit%TYPE;
2557     d_new_start_time            DATE;
2558     d_new_end_time              DATE;
2559     d_existing_start_time       DATE;
2560     d_existing_end_time         DATE;
2561     l_time_conflict_found       BOOLEAN := FALSE;
2562     l_message                   VARCHAR2(30);
2563     l_message_icon              VARCHAR2(30);
2564     l_message_token             VARCHAR2(100);
2565 
2566   BEGIN
2567     --
2568     --  Check whether Unit Level Time Conflict step has been overridden.
2569     --
2570     IF Igs_En_Gen_015.validation_step_is_overridden (
2571          'TIME_CNFLT',
2572          p_load_cal_type,
2573          p_load_cal_seq_number,
2574          p_person_id,
2575          p_uoo_id,
2576          l_step_override_limit
2577        ) THEN
2578       RETURN TRUE;
2579     END IF;
2580     --
2581     OPEN cur_usec_occurs_new (p_uoo_id);
2582     LOOP
2583       FETCH cur_usec_occurs_new INTO rec_cur_usec_occurs_new;
2584       IF ((cur_usec_occurs_new%NOTFOUND) AND (cur_usec_occurs_new%ROWCOUNT = 0)) THEN
2585         CLOSE cur_usec_occurs_new;
2586         RETURN TRUE;
2587       ELSIF (cur_usec_occurs_new%NOTFOUND) THEN
2588         CLOSE cur_usec_occurs_new;
2589         EXIT;
2590       END IF;
2591 
2592       --
2593       --  Loop through all the Unit Section Occurrences that the student attempted,
2594       --  and check for time conflict.
2595       --
2596       FOR rec_cur_usec_occurs_existing IN cur_usec_occurs_existing LOOP
2597         --
2598         --  Check if Effective dates of the occurrences for the new and existing Unit Section Occurrences overlap.
2599         --     S2         E2 S1                  E1 S2        E2
2600         --      |----------|  |-------------------| |----------|
2601         --         S2         E2         S2         E2
2602         --          |----------|          |----------|
2603         --         S2                               E2
2604         --          |--------------------------------|
2605         --
2606         IF ((rec_cur_usec_occurs_new.start_date BETWEEN rec_cur_usec_occurs_existing.start_date AND rec_cur_usec_occurs_existing.end_date) OR
2607             (rec_cur_usec_occurs_new.end_date BETWEEN rec_cur_usec_occurs_existing.start_date AND rec_cur_usec_occurs_existing.end_date) OR
2608             (rec_cur_usec_occurs_existing.start_date BETWEEN rec_cur_usec_occurs_new.start_date AND rec_cur_usec_occurs_new.end_date) OR
2609             (rec_cur_usec_occurs_existing.end_date BETWEEN rec_cur_usec_occurs_new.start_date AND rec_cur_usec_occurs_new.end_date)) THEN
2610           --
2611           --  Check if the same day (MONDAY..SUNDAY) is selected for meetings.
2612           --
2613           IF ((rec_cur_usec_occurs_new.monday = 'Y' AND  rec_cur_usec_occurs_existing.monday='Y') OR
2614               (rec_cur_usec_occurs_new.tuesday = 'Y' AND rec_cur_usec_occurs_existing.tuesday='Y') OR
2615               (rec_cur_usec_occurs_new.wednesday ='Y' AND  rec_cur_usec_occurs_existing.wednesday='Y') OR
2616               (rec_cur_usec_occurs_new.thursday ='Y' AND rec_cur_usec_occurs_existing.thursday='Y') OR
2617               (rec_cur_usec_occurs_new.friday ='Y' AND rec_cur_usec_occurs_existing.friday='Y') OR
2618               (rec_cur_usec_occurs_new.saturday ='Y' AND rec_cur_usec_occurs_existing.saturday='Y') OR
2619               (rec_cur_usec_occurs_new.sunday ='Y' AND rec_cur_usec_occurs_existing.sunday='Y')) THEN
2620 
2621             --  Check if Start Time and End Time for the new and existing Unit Section Occurrences overlap.
2622             --
2623             -- Extracting the time component alone to create new date-time values
2624             -- as the date component is not needed
2625             d_new_start_time        := TO_DATE ('1000/01/01 ' || TO_CHAR (rec_cur_usec_occurs_new.start_time, 'HH24:MI:SS'), 'YYYY/MM/DD HH24:MI:SS');
2626             d_new_end_time          := TO_DATE ('1000/01/01 ' || TO_CHAR (rec_cur_usec_occurs_new.end_time, 'HH24:MI:SS'), 'YYYY/MM/DD HH24:MI:SS');
2627             d_existing_start_time   := TO_DATE ('1000/01/01 ' || TO_CHAR (rec_cur_usec_occurs_existing.start_time, 'HH24:MI:SS'), 'YYYY/MM/DD HH24:MI:SS');
2628             d_existing_end_time     := TO_DATE ('1000/01/01 ' || TO_CHAR (rec_cur_usec_occurs_existing.end_time, 'HH24:MI:SS'), 'YYYY/MM/DD HH24:MI:SS');
2629 
2630             IF ( (d_new_start_time BETWEEN d_existing_start_time AND d_existing_end_time) OR
2631                  (d_new_end_time BETWEEN d_existing_start_time AND d_existing_end_time) OR
2632                  (d_existing_start_time BETWEEN d_new_start_time AND d_new_end_time) OR
2633                  (d_existing_end_time BETWEEN d_new_start_time AND d_new_end_time) ) THEN
2634               --
2635               --  Boundary conditions should be treated as no overlap.
2636               --  For example a class ending at 9 a.m. is not in conflict with another class starting at 9 a.m.
2637               --
2638               IF ((d_new_start_time = d_existing_end_time) OR
2639                   (d_existing_start_time = d_new_end_time)) THEN
2640                 NULL;
2641               ELSE
2642                 -- smaddali added this new If condition call for Instructor information dld PSP004
2643                 --bug#2191501 to check if there is any time conflict at the date instance level
2644                 IF NOT igs_ps_rlovr_fac_tsk.crsp_chk_inst_time_conft( rec_cur_usec_occurs_existing.start_date ,
2645                   rec_cur_usec_occurs_existing.end_date,rec_cur_usec_occurs_existing.monday,
2646                   rec_cur_usec_occurs_existing.tuesday, rec_cur_usec_occurs_existing.wednesday,
2647                   rec_cur_usec_occurs_existing.thursday, rec_cur_usec_occurs_existing.friday,
2648                   rec_cur_usec_occurs_existing.saturday, rec_cur_usec_occurs_existing.sunday ,
2649                   rec_cur_usec_occurs_new.start_date,   rec_cur_usec_occurs_new.end_date ,
2650                   rec_cur_usec_occurs_new.monday,rec_cur_usec_occurs_new.tuesday,
2651                   rec_cur_usec_occurs_new.wednesday,rec_cur_usec_occurs_new.thursday,
2652                   rec_cur_usec_occurs_new.friday,rec_cur_usec_occurs_new.saturday,rec_cur_usec_occurs_new.sunday) THEN
2653                     NULL ;
2654                 ELSE
2655                     l_time_conflict_found := TRUE;
2656                    --
2657                    --  If the student has satisfied the Time Conflict then return FALSE with a warning/deny message.
2658                    --
2659                    IF (p_deny_warn = 'WARN') THEN
2660                      IF p_calling_obj = 'JOB' THEN
2661                         l_message := 'IGS_SS_WARN_TCONFLICT_CHK';
2662                      ELSE
2663                         l_message := 'IGS_EN_TCONFLICT_TAB_WARN';
2664                      END IF;
2665                    ELSE
2666                      IF p_calling_obj = 'JOB' THEN
2667                         l_message := 'IGS_SS_DENY_TCONFLICT_CHK';
2668                      ELSE
2669                        l_message := 'IGS_EN_TCONFLICT_TAB_DENY';
2670                      END IF;
2671                    END IF;
2672 
2673                    IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
2674 
2675                     l_message_token := 'UNIT_CD'||':'||rec_cur_usec_occurs_existing.unit_cd||'/'||rec_cur_usec_occurs_existing.unit_class||';';
2676 
2677                     l_message_icon := substr(p_deny_warn,1,1);
2678                     igs_en_drop_units_api.create_ss_warning (
2679                            p_person_id => p_person_id,
2680                            p_course_cd => p_program_cd,
2681                            p_term_cal_type=> p_load_cal_type,
2682                            p_term_ci_sequence_number => p_load_cal_seq_number,
2683                            p_uoo_id => p_uoo_id,
2684                            p_message_for => rec_cur_usec_occurs_new.unit_cd||'/'||rec_cur_usec_occurs_new.unit_class,
2685                            p_message_icon=> l_message_icon,
2686                            p_message_name => l_message,
2687                            p_message_rule_text => NULL,
2688                            p_message_tokens => l_message_token,
2689                            p_message_action=> NULL,
2690                            p_destination =>NULL,
2691                            p_parameters => NULL,
2692                            p_step_type => 'UNIT');
2693 
2694                    ELSE
2695                      IF (p_message IS NULL) THEN
2696                        p_message := l_message;
2697                      ELSE
2698                        p_message := p_message || ';' || l_message;
2699                      END IF;
2700                    END IF;  -- warn level
2701                    RETURN FALSE;
2702                 END IF ;  -- conflict exists at date instance level
2703               END IF;
2704             END IF;
2705           END IF;
2706         END IF;
2707       END LOOP;
2708     END LOOP;
2709 
2710     IF cur_usec_occurs_new%ISOPEN THEN
2711        CLOSE cur_usec_occurs_new;
2712     END IF;
2713 
2714     --
2715     --  Return TRUE if no Time Conflict is found.
2716     --
2717     IF (NOT l_time_conflict_found) THEN
2718       RETURN TRUE;
2719     END IF;
2720     --
2721   END eval_time_conflict;
2722 --
2723 -- ================================================================================
2724 FUNCTION eval_prereq (
2725 p_person_id IN NUMBER,
2726 p_load_cal_type IN VARCHAR2,
2727 p_load_sequence_number IN VARCHAR2,
2728 p_uoo_id  IN NUMBER,
2729 p_course_cd IN VARCHAR2,
2730 p_course_version IN NUMBER,
2731 p_message IN OUT NOCOPY VARCHAR2,
2732 p_deny_warn  IN VARCHAR2,
2733 p_calling_obj IN VARCHAR2
2734 ) RETURN BOOLEAN AS
2735 
2736 --------------------------------------------------------------------------------
2737   --Created by  : knaraset ( Oracle IDC)
2738   --Date created: 21-JUN-2001
2739   --
2740   --Purpose:
2741   --
2742   --Known limitations/enhancements and/or remarks:
2743   --
2744   --Change History:
2745   --Who         When            What
2746   --stutta    21-Sep-2004    Passing p_parm_5 as 'Y' in rules engine call. This value
2747   --                         is expected by rule componenet PREDICTED_ENROLLED.Bug#3902375
2748   --bdeviset  12-DEC-2005    Passing extra parameter p_param_8 ( in which the uoo_is is passed)
2749   --                         while calling rules engine for Bug# 4304688
2750   ------------------------------------------------------------------------------
2751   CURSOR cur_uoo_prereq(p_uoo_id NUMBER) IS
2752   SELECT rul_sequence_number
2753   FROM igs_ps_usec_ru
2754   WHERE uoo_id = p_uoo_id AND
2755         s_rule_call_cd = 'USECPREREQ';
2756 
2757   CURSOR cur_unit_prereq(p_uoo_id NUMBER) IS
2758   SELECT rul_sequence_number
2759   FROM igs_ps_unit_ver_ru uvr,
2760        igs_ps_unit_ofr_opt uoo
2761   WHERE uvr.unit_cd = uoo.unit_cd AND
2762         uvr.version_number = uoo.version_number AND
2763                 uoo_id = p_uoo_id AND
2764                 uvr.s_rule_call_cd = 'PREREQ';
2765 
2766   CURSOR cur_usec_dtl(p_uoo_id NUMBER) IS
2767   SELECT unit_cd,unit_class,version_number,cal_type,ci_sequence_number
2768   FROM igs_ps_unit_ofr_opt
2769   WHERE uoo_id = p_uoo_id;
2770 
2771   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
2772   l_rul_sequence_number igs_ps_unit_ver_ru.rul_sequence_number%TYPE;
2773   l_unit_dtls_rec cur_usec_dtl%ROWTYPE;
2774   l_version_number igs_ps_unit_ofr_opt.version_number%TYPE;
2775   l_cal_type igs_ps_unit_ofr_opt.cal_type%TYPE;
2776   l_ci_sequence_number igs_ps_unit_ofr_opt.ci_sequence_number%TYPE;
2777   l_message VARCHAR2(30);
2778   l_rule_text igs_ps_unit_ver_ru_v.rule_text%TYPE;
2779   l_message_icon VARCHAR2(1);
2780 
2781 --
2782 -- begin of the function eval_prereq
2783 --
2784 BEGIN
2785 l_rule_text := NULL;
2786 IF Igs_En_Gen_015.validation_step_is_overridden ('PREREQ',
2787                                                 p_load_cal_type,
2788                                                 p_load_sequence_number ,
2789                                                 p_person_id ,
2790                                                 p_uoo_id ,
2791                                                 l_step_override_limit) THEN
2792     RETURN TRUE;
2793 END IF;
2794 
2795 -- check whether pre-requisite rule are defined at unit section level
2796 OPEN cur_uoo_prereq (p_uoo_id);
2797 FETCH cur_uoo_prereq INTO l_rul_sequence_number;
2798 CLOSE cur_uoo_prereq;
2799 
2800 -- if no pre-requisite rule defined at unit section level, check whether defined at Unit level
2801 IF l_rul_sequence_number IS NULL THEN
2802   OPEN cur_unit_prereq (p_uoo_id);
2803   FETCH cur_unit_prereq INTO l_rul_sequence_number;
2804   CLOSE cur_unit_prereq;
2805 END IF;
2806 
2807 -- if no pre-requisite rule defined at either levels,
2808 IF l_rul_sequence_number IS NULL THEN
2809   RETURN TRUE;
2810 END IF;
2811 
2812 -- get the details of unit section
2813 OPEN cur_usec_dtl(p_uoo_id);
2814 FETCH  cur_usec_dtl INTO l_unit_dtls_rec;
2815 CLOSE cur_usec_dtl;
2816 
2817 --
2818 -- check whether student has satisfied the pre-requisite rule by invoking the rule engine
2819 --
2820 IF igs_ru_gen_001.rulp_val_senna(p_rule_call_name => 'PREREQ',
2821                                  p_person_id => p_person_id,
2822                                  p_course_cd => p_course_cd,
2823                                  p_course_version => p_course_version ,
2824                                  p_unit_cd => l_unit_dtls_rec.unit_cd,
2825                                  p_unit_version => l_unit_dtls_rec.version_number,
2826                                  p_cal_type => l_unit_dtls_rec.cal_type,
2827                                  p_ci_sequence_number => l_unit_dtls_rec.ci_sequence_number,
2828                                  p_message => l_message,
2829                                  p_rule_number => l_rul_sequence_number,
2830                                  p_param_5 => 'Y',
2831                                  p_param_8 => p_uoo_id
2832                                 ) = 'true' THEN
2833    RETURN TRUE;
2834 END IF;
2835 
2836 IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
2837     l_rule_text :=igs_ru_gen_003.Rulp_Get_Rule(l_rul_sequence_number);
2838 END IF;
2839 IF p_deny_warn = 'WARN' THEN
2840   IF p_calling_obj = 'JOB' THEN
2841      l_message := 'IGS_SS_WARN_PREREQ' || '*' || l_unit_dtls_rec.unit_cd;
2842   ELSE
2843      l_message := 'IGS_EN_PREREQ_TAB_WARN';
2844   END IF;
2845 ELSE
2846   IF p_calling_obj = 'JOB' THEN
2847      l_message := 'IGS_SS_DENY_PREREQ' || '*' || l_unit_dtls_rec.unit_cd;
2848   ELSE
2849      l_message := 'IGS_EN_PREREQ_TAB_DENY';
2850   END IF;
2851 END IF;
2852 
2853 
2854 IF p_calling_obj NOT IN  ('JOB','SCH_UPD','DROP') THEN
2855 
2856   l_message_icon := substr(p_deny_warn,1,1);
2857   igs_en_drop_units_api.create_ss_warning (
2858          p_person_id => p_person_id,
2859          p_course_cd => p_course_cd,
2860          p_term_cal_type=> p_load_cal_type,
2861          p_term_ci_sequence_number => p_load_sequence_number,
2862          p_uoo_id => p_uoo_id,
2863          p_message_for => l_unit_dtls_rec.unit_cd||'/'||l_unit_dtls_rec.unit_class,
2864          p_message_icon=> l_message_icon,
2865          p_message_name => l_message,
2866          p_message_rule_text => l_rule_text,
2867          p_message_tokens => NULL,
2868          p_message_action=> NULL,
2869          p_destination =>NULL,
2870          p_parameters => NULL,
2871          p_step_type => 'UNIT');
2872 
2873  -- Incase of DROP only rule text is passed
2874  -- as the message is set in the drop units api depending on
2875  -- whether TRUE or FALSE is returned
2876 ELSIF p_calling_obj = 'DROP' THEN
2877       p_message := l_rule_text;
2878 ELSE
2879 
2880    IF (p_message IS NULL) THEN
2881      p_message := l_message;
2882    ELSE
2883      p_message := p_message || ';' || l_message;
2884    END IF;
2885 
2886      IF l_rule_text IS NOT NULL THEN
2887          p_message :=p_message ||';'||'IGS_EN_RULE_TEXT' || '*' || l_rule_text;
2888     END IF;
2889 
2890 END IF;
2891 
2892 RETURN FALSE;
2893 
2894 END eval_prereq;
2895 
2896 -- =================================================================================
2897 
2898 FUNCTION eval_coreq(
2899 p_person_id IN NUMBER,
2900 p_load_cal_type IN VARCHAR2,
2901 p_load_sequence_number IN VARCHAR2,
2902 p_uoo_id  IN NUMBER,
2903 p_course_cd IN VARCHAR2,
2904 p_course_version IN NUMBER,
2905 p_message IN OUT NOCOPY VARCHAR2,
2906 p_deny_warn  IN VARCHAR2,
2907 p_calling_obj IN VARCHAR2
2908 ) RETURN BOOLEAN AS
2909 
2910 ------------------------------------------------------------------------------------
2911   --Created by  : knaraset ( Oracle IDC)
2912   --Date created: 21-JUN-2001
2913   --
2914   --Purpose:
2915   --
2916   --Known limitations/enhancements and/or remarks:
2917   --
2918   --Change History:
2919   --Who         When            What
2920   --bdeviset  12-DEC-2005    Passing extra parameter p_param_8 ( in which the uoo_is is passed)
2921   --                         while calling rules engine for Bug# 4304688
2922   -------------------------------------------------------------------------------------
2923   CURSOR cur_uoo_coreq(p_uoo_id NUMBER) IS
2924   SELECT rul_sequence_number
2925   FROM igs_ps_usec_ru
2926   WHERE uoo_id = p_uoo_id AND
2927         s_rule_call_cd = 'USECCOREQ';
2928 
2929   CURSOR cur_unit_coreq(p_uoo_id NUMBER) IS
2930   SELECT rul_sequence_number
2931   FROM igs_ps_unit_ver_ru uvr,
2932        igs_ps_unit_ofr_opt uoo
2933   WHERE uvr.unit_cd = uoo.unit_cd AND
2934         uvr.version_number = uoo.version_number AND
2935                 uoo_id = p_uoo_id AND
2936                 uvr.s_rule_call_cd = 'COREQ';
2937 
2938   CURSOR cur_usec_dtl(p_uoo_id NUMBER) IS
2939   SELECT unit_cd,unit_class,version_number,cal_type,ci_sequence_number
2940   FROM igs_ps_unit_ofr_opt
2941   WHERE uoo_id = p_uoo_id;
2942 
2943   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
2944   l_rul_sequence_number igs_ps_unit_ver_ru.rul_sequence_number%TYPE;
2945   l_unit_dtls_rec cur_usec_dtl%ROWTYPE;
2946   l_message VARCHAR2(30);
2947   l_message_icon VARCHAR2(1);
2948   l_rule_text igs_ps_unit_ver_ru_v.rule_text%TYPE;
2949   l_coreq_string VARCHAR2(1000);
2950   l_destination VARCHAR2(100);
2951   l_message_action VARCHAR2(100);
2952 --
2953 -- begin of the function eval_coreq
2954 --
2955 BEGIN
2956 l_rule_text := NULL;
2957 IF Igs_En_Gen_015.validation_step_is_overridden ('COREQ',
2958                                                 p_load_cal_type,
2959                                                 p_load_sequence_number ,
2960                                                 p_person_id ,
2961                                                 p_uoo_id ,
2962                                                 l_step_override_limit) THEN
2963     RETURN TRUE;
2964 END IF;
2965 
2966 -- check whether co-requisite rule are defined at unit section level
2967 OPEN cur_uoo_coreq (p_uoo_id);
2968 FETCH cur_uoo_coreq INTO l_rul_sequence_number;
2969 CLOSE cur_uoo_coreq;
2970 
2971 -- if no co-requisite rule defined at unit section level, check whether defined at Unit level
2972 IF l_rul_sequence_number IS NULL THEN
2973   OPEN cur_unit_coreq (p_uoo_id);
2974   FETCH cur_unit_coreq INTO l_rul_sequence_number;
2975   CLOSE cur_unit_coreq;
2976 END IF;
2977 
2978 -- if no co-requisite rule defined at either levels,
2979 IF l_rul_sequence_number IS NULL THEN
2980   RETURN TRUE;
2981 END IF;
2982 
2983 -- get the details of unit section
2984 OPEN cur_usec_dtl(p_uoo_id);
2985 FETCH  cur_usec_dtl INTO l_unit_dtls_rec;
2986 CLOSE cur_usec_dtl;
2987 
2988 --
2989 -- check whether student has satisfied the co-requisite rule by invoking the rule engine
2990 
2991 IF igs_ru_gen_001.rulp_val_senna(p_rule_call_name => 'COREQ',
2992                                  p_person_id => p_person_id,
2993                                  p_course_cd => p_course_cd,
2994                                  p_course_version => p_course_version ,
2995                                  p_unit_cd => l_unit_dtls_rec.unit_cd,
2996                                  p_unit_version => l_unit_dtls_rec.version_number,
2997                                  p_cal_type => l_unit_dtls_rec.cal_type,
2998                                  p_ci_sequence_number => l_unit_dtls_rec.ci_sequence_number,
2999                                  p_message => l_message,
3000                                  p_rule_number => l_rul_sequence_number,
3001                                  p_param_8 => p_uoo_id
3002    ) = 'true' THEN
3003    RETURN TRUE;
3004 END IF;
3005 
3006 IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y')  THEN
3007     l_rule_text :=igs_ru_gen_003.Rulp_Get_Rule(l_rul_sequence_number);
3008 END IF;
3009 
3010 IF p_deny_warn = 'WARN' THEN
3011   IF p_calling_obj = 'JOB' THEN
3012      l_message := 'IGS_SS_WARN_COREQ' || '*' || l_unit_dtls_rec.unit_cd;
3013   ELSE
3014      l_message := 'IGS_EN_COREQ_TAB_WARN';
3015   END IF;
3016 ELSE
3017   IF p_calling_obj = 'JOB' THEN
3018      l_message := 'IGS_SS_DENY_COREQ' || '*' || l_unit_dtls_rec.unit_cd;
3019   ELSE
3020      l_message := 'IGS_EN_COREQ_TAB_DENY';
3021   END IF;
3022 END IF;
3023 
3024 IF p_calling_obj NOT IN  ('JOB','SCH_UPD','DROP') THEN
3025 
3026   l_coreq_string := get_coreq_units(p_uoo_id);
3027   l_message_icon := substr(p_deny_warn,1,1);
3028 
3029   IF  p_calling_obj IN ('PLAN', 'SUBMITPLAN') THEN
3030     l_destination := 'IGS_EN_PLAN_COREQ_SUB';
3031   ELSIF p_calling_obj IN ('CART', 'SUBMITCART','SCHEDULE','ENROLPEND')  THEN
3032     l_destination :=  'IGS_EN_CART_COREQ_SUB';
3033   ELSIF p_calling_obj IN ('SWAP','SUBMITSWAP' ) THEN
3034     l_destination := 'IGS_EN_SCH_COREQ_SUB';
3035   END IF;
3036 
3037   l_message_action := igs_ss_enroll_pkg.enrf_get_lookup_meaning (
3038                                                                   p_lookup_code => 'ADD_COREQ',
3039                                                                   p_lookup_type => 'IGS_EN_WARN_LINKS');
3040   igs_en_drop_units_api.create_ss_warning (
3041          p_person_id => p_person_id,
3042          p_course_cd => p_course_cd,
3043          p_term_cal_type=> p_load_cal_type,
3044          p_term_ci_sequence_number => p_load_sequence_number,
3045          p_uoo_id => p_uoo_id,
3046          p_message_for => l_unit_dtls_rec.unit_cd||'/'||l_unit_dtls_rec.unit_class,
3047          p_message_icon=> l_message_icon,
3048          p_message_name => l_message,
3049          p_message_rule_text => l_rule_text,
3050          p_message_tokens => NULL,
3051          p_message_action=> l_message_action,
3052          p_destination => l_destination,
3053          p_parameters => l_coreq_string,
3054          p_step_type => 'UNIT');
3055 
3056 
3057  -- Incase of DROP only rule text is passed
3058  -- as the message is set in the drop units api depending on
3059  -- whether TRUE or FALSE is returned
3060 ELSIF p_calling_obj = 'DROP' THEN
3061       p_message := l_rule_text;
3062 ELSE
3063    IF (p_message IS NULL) THEN
3064      p_message := l_message;
3065    ELSE
3066      p_message := p_message || ';' || l_message;
3067    END IF;
3068  END IF;
3069 
3070 RETURN FALSE;
3071 
3072 END eval_coreq;
3073 
3074 -- =================================================================================
3075 
3076 FUNCTION eval_incompatible(
3077 p_person_id IN NUMBER,
3078 p_load_cal_type IN VARCHAR2,
3079 p_load_sequence_number IN VARCHAR2,
3080 p_uoo_id  IN NUMBER,
3081 p_course_cd IN VARCHAR2,
3082 p_course_version IN NUMBER,
3083 p_message IN OUT NOCOPY VARCHAR2,
3084 p_deny_warn  IN VARCHAR2,
3085 p_calling_obj IN VARCHAR2
3086 ) RETURN BOOLEAN AS
3087 
3088 ------------------------------------------------------------------------------------
3089   --Created by  : knaraset ( Oracle IDC)
3090   --Date created: 21-JUN-2001
3091   --
3092   --Purpose:
3093   --
3094   --Known limitations/enhancements and/or remarks:
3095   --
3096   --Change History:
3097   --Who         When            What
3098   -------------------------------------------------------------------------------------
3099 
3100   CURSOR cur_unit_incomp(p_uoo_id NUMBER) IS
3101   SELECT rul_sequence_number
3102   FROM igs_ps_unit_ver_ru uvr,
3103        igs_ps_unit_ofr_opt uoo
3104   WHERE uvr.unit_cd = uoo.unit_cd AND
3105         uvr.version_number = uoo.version_number AND
3106                 uoo_id = p_uoo_id AND
3107                 uvr.s_rule_call_cd = 'INCOMP';
3108 
3109   CURSOR cur_usec_dtl(p_uoo_id NUMBER) IS
3110   SELECT unit_cd,unit_class,version_number,cal_type,ci_sequence_number
3111   FROM igs_ps_unit_ofr_opt
3112   WHERE uoo_id = p_uoo_id;
3113 
3114   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
3115   l_rul_sequence_number igs_ps_unit_ver_ru.rul_sequence_number%TYPE;
3116   l_unit_dtls_rec   cur_usec_dtl%ROWTYPE;
3117   l_message VARCHAR2(30);
3118   l_message_icon VARCHAR2(1);
3119   l_rule_text igs_ps_unit_ver_ru_v.rule_text%TYPE;
3120 
3121 --
3122 -- begin of the function eval_incompatible
3123 --
3124 BEGIN
3125 IF Igs_En_Gen_015.validation_step_is_overridden ('INCMPT_UNT',
3126                                                 p_load_cal_type,
3127                                                 p_load_sequence_number ,
3128                                                 p_person_id ,
3129                                                 p_uoo_id ,
3130                                                 l_step_override_limit) THEN
3131     RETURN TRUE;
3132 END IF;
3133 
3134 -- Check whether incompatibility rule defined at Unit level
3135   OPEN cur_unit_incomp (p_uoo_id);
3136   FETCH cur_unit_incomp INTO l_rul_sequence_number;
3137   CLOSE cur_unit_incomp;
3138 
3139 -- if no incompatibility rule defined at unit level,
3140 IF l_rul_sequence_number IS NULL THEN
3141   RETURN TRUE;
3142 END IF;
3143 
3144 -- get the details of unit section
3145 OPEN cur_usec_dtl(p_uoo_id);
3146 FETCH  cur_usec_dtl INTO l_unit_dtls_rec;
3147 CLOSE cur_usec_dtl;
3148 
3149 --
3150 -- check whether student has satisfied the incompatibility rule by invoking the rule engine
3151 
3152 IF igs_ru_gen_001.rulp_val_senna(p_rule_call_name => 'INCOMP',
3153                                  p_person_id => p_person_id,
3154                                  p_course_cd => p_course_cd,
3155                                  p_course_version => p_course_version ,
3156                                  p_unit_cd => l_unit_dtls_rec.unit_cd,
3157                                  p_unit_version => l_unit_dtls_rec.version_number,
3158                                  p_cal_type => l_unit_dtls_rec.cal_type,
3159                                  p_ci_sequence_number => l_unit_dtls_rec.ci_sequence_number,
3160                                  p_message => l_message,
3161                                  p_rule_number => l_rul_sequence_number
3162    ) = 'true' THEN
3163    RETURN TRUE;
3164 END IF;
3165 
3166 IF p_deny_warn = 'WARN' THEN
3167   IF p_calling_obj = 'JOB' THEN
3168      l_message := 'IGS_SS_WARN_INCOMP' || '*' || l_unit_dtls_rec.unit_cd;
3169   ELSE
3170      l_message := 'IGS_EN_INCOMP_TAB_WARN';
3171   END IF;
3172 ELSE
3173   IF p_calling_obj = 'JOB' THEN
3174      l_message := 'IGS_SS_DENY_INCOMP' || '*' || l_unit_dtls_rec.unit_cd;
3175   ELSE
3176      l_message := 'IGS_EN_INCOMP_TAB_DENY';
3177   END IF;
3178 END IF;
3179 
3180 IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
3181 
3182   IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y')  THEN
3183     l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(l_rul_sequence_number);
3184   END IF;
3185   l_message_icon := substr(p_deny_warn,1,1);
3186   igs_en_drop_units_api.create_ss_warning (
3187          p_person_id => p_person_id,
3188          p_course_cd => p_course_cd,
3189          p_term_cal_type=> p_load_cal_type,
3190          p_term_ci_sequence_number => p_load_sequence_number,
3191          p_uoo_id => p_uoo_id,
3192          p_message_for => l_unit_dtls_rec.unit_cd||'/'||l_unit_dtls_rec.unit_class,
3193          p_message_icon=> l_message_icon,
3194          p_message_name => l_message,
3195          p_message_rule_text => l_rule_text,
3196          p_message_tokens => NULL,
3197          p_message_action=> NULL,
3198          p_destination =>NULL,
3199          p_parameters => NULL,
3200          p_step_type => 'UNIT');
3201 
3202  ELSE
3203    IF (p_message IS NULL) THEN
3204      p_message := l_message;
3205    ELSE
3206      p_message := p_message || ';' || l_message;
3207    END IF;
3208  END IF;
3209 
3210 RETURN FALSE;
3211 
3212 END eval_incompatible;
3213 
3214 -- =================================================================================
3215 
3216 FUNCTION eval_spl_permission(
3217 p_person_id IN NUMBER,
3218 p_load_cal_type IN VARCHAR2,
3219 p_load_sequence_number IN VARCHAR2,
3220 p_uoo_id  IN NUMBER,
3221 p_course_cd IN VARCHAR2,
3222 p_course_version IN NUMBER,
3223 p_message IN OUT NOCOPY VARCHAR2,
3224 p_deny_warn  IN VARCHAR2
3225 ) RETURN BOOLEAN AS
3226 
3227 ------------------------------------------------------------------------------------
3228   --Created by  : knaraset ( Oracle IDC)
3229   --Date created: 21-JUN-2001
3230   --
3231   --Purpose:  this function returns TRUE for a given student and unit attempt
3232   --          if the student has got special permission override,special permission approval or
3233   --          special permission functionality is not allowed.Otherwise it returns FALSE with message
3234   --
3235   --Known limitations/enhancements and/or remarks:
3236   --
3237   --Change History:
3238   --Who         When            What
3239   -------------------------------------------------------------------------------------
3240   CURSOR cur_chk_sp_allowed(p_uoo_id NUMBER) IS
3241   SELECT special_permission_ind
3242   FROM igs_ps_unit_ofr_opt
3243   WHERE uoo_id = p_uoo_id;
3244 
3245   CURSOR cur_sp_approve(p_person_id NUMBER,p_uoo_id NUMBER) IS
3246   SELECT approval_status
3247   FROM igs_en_spl_perm
3248   WHERE student_person_id = p_person_id AND
3249         uoo_id =p_uoo_id AND
3250         request_type    = 'SPL_PERM' AND
3251         approval_status = 'A';
3252 
3253   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
3254   l_sp_approve igs_en_spl_perm.approval_status%TYPE ;
3255   l_sp_allowed igs_ps_unit_ofr_opt.special_permission_ind%TYPE;
3256 
3257 --
3258 -- begin of the function eval_spl_permission
3259 --
3260 BEGIN
3261 IF Igs_En_Gen_015.validation_step_is_overridden ('SPL_PERM',
3262                                                 p_load_cal_type,
3263                                                 p_load_sequence_number ,
3264                                                 p_person_id ,
3265                                                 p_uoo_id ,
3266                                                 l_step_override_limit) THEN
3267     RETURN TRUE;
3268 END IF;
3269 
3270 -- check whether special permission functionality is allowed for the given unit section
3271 -- i.e. special permission allowed check box is checked/unchecked..
3272 OPEN cur_chk_sp_allowed(p_uoo_id);
3273 FETCH cur_chk_sp_allowed INTO l_sp_allowed;
3274 CLOSE cur_chk_sp_allowed;
3275 IF l_sp_allowed = 'N' THEN
3276   RETURN TRUE;
3277 END IF;
3278 
3279 --
3280 -- check whether student got special permission approved
3281 OPEN cur_sp_approve(p_person_id,p_uoo_id);
3282 FETCH cur_sp_approve INTO l_sp_approve;
3283 CLOSE cur_sp_approve;
3284 
3285 IF l_sp_approve = 'A' THEN
3286   RETURN TRUE;
3287 END IF;
3288 
3289 IF p_deny_warn = 'WARN' THEN
3290   IF p_message IS NULL THEN
3291       p_message := 'IGS_SS_WARN_SPL_PERMIT';
3292   ELSE
3293       p_message := p_message ||';'||'IGS_SS_WARN_SPL_PERMIT';
3294   END IF;
3295 ELSE
3296   IF p_message IS NULL THEN
3297      p_message := 'IGS_SS_DENY_SPL_PERMIT';
3298   ELSE
3299      p_message := p_message ||';'||'IGS_SS_DENY_SPL_PERMIT';
3300   END IF;
3301 END IF;
3302 
3303 RETURN FALSE;
3304 
3305 END eval_spl_permission;
3306 
3307 -- ================================================================================
3308 
3309 FUNCTION eval_rsv_seat(
3310 p_person_id IN NUMBER,
3311 p_load_cal_type IN VARCHAR2,
3312 p_load_sequence_number IN VARCHAR2,
3313 p_uoo_id  IN NUMBER,
3314 p_course_cd IN VARCHAR2,
3315 p_course_version IN NUMBER,
3316 p_message IN OUT NOCOPY VARCHAR2,
3317 p_deny_warn  IN VARCHAR2,
3318 p_calling_obj IN VARCHAR2,
3319 p_deny_enrollment OUT NOCOPY VARCHAR2
3320 ) RETURN BOOLEAN AS
3321 
3322 ------------------------------------------------------------------------------------
3323   --Created by  : knaraset ( Oracle IDC)
3324   --Date created: 21-JUN-2001
3325   --
3326   --Purpose:
3327   --
3328   --
3329   --Known limitations/enhancements and/or remarks:
3330   --
3331   --Change History:
3332   --Who         When            What
3333   --smadathi    30-JUL-2001     Changes Made as per enhancement Bug No.1869767
3334   -- svenkata   19-Feb-2003     Merged 2 cursors that were based on the same table.Bug 2749605
3335   -- stutta     27-Jul-2004     Added a missing join condition sus.person_id = spa.person_id
3336   --                            in cursor cur_unit_set. Bug #3452321
3337   -- stutta     23-Aug-2004     Added validation for Class standing(CLASS_STD) priority
3338   --                            at all three levels. Bug#3803790
3339   -------------------------------------------------------------------------------------
3340 
3341 -- cursor to select the Unit section details
3342   CURSOR cur_usec_dtl(p_uoo_id NUMBER) IS
3343   SELECT unit_cd,unit_class,version_number,cal_type,ci_sequence_number,owner_org_unit_cd , reserved_seating_allowed
3344   FROM igs_ps_unit_ofr_opt
3345   WHERE uoo_id = p_uoo_id;
3346 
3347 -- cursor to fetch priorities defined at unit section level
3348 CURSOR cur_rsv_uoo_pri(p_uoo_id NUMBER) IS
3349 SELECT priority_value, rsv_usec_pri_id priority_id
3350 FROM igs_ps_rsv_usec_pri
3351 WHERE uoo_id = p_uoo_id
3352 ORDER BY priority_order;
3353 
3354 -- cursor to fetch preferences defined at unit section level
3355 CURSOR cur_rsv_uoo_prf(p_rsv_usec_pri_id NUMBER) IS
3356 SELECT preference_code,preference_version,group_id,percentage_reserved, rsv_usec_prf_id preference_id
3357 FROM igs_ps_rsv_usec_prf
3358 WHERE rsv_usec_pri_id = p_rsv_usec_pri_id
3359 ORDER BY preference_order;
3360 
3361 -- cursor to fetch priorities defined at unit offering pattern level
3362 CURSOR cur_rsv_uop_pri(p_unit_cd VARCHAR2 ,p_version_number NUMBER ,p_cal_type VARCHAR2 ,p_ci_sequence_number NUMBER) IS
3363 SELECT priority_value, rsv_uop_pri_id priority_id
3364 FROM igs_ps_rsv_uop_pri
3365 WHERE unit_cd = p_unit_cd AND
3366       version_number = p_version_number AND
3367           calender_type  = p_cal_type AND
3368           ci_sequence_number = p_ci_sequence_number
3369 ORDER BY priority_order;
3370 
3371 -- cursor to fetch preferences defined at unit offering pattern level
3372 CURSOR cur_rsv_uop_prf(p_rsv_uop_pri_id NUMBER) IS
3373 SELECT preference_code,preference_version,group_id,percentage_reserved, rsv_uop_prf_id preference_id
3374 FROM igs_ps_rsv_uop_prf
3375 WHERE rsv_uop_pri_id = p_rsv_uop_pri_id
3376 ORDER BY preference_order;
3377 
3378 -- cursor to fetch priorities defined at owner Organizational Unit level
3379 CURSOR cur_rsv_org_pri(p_org_unit_cd varchar2) IS
3380 SELECT priority_value, rsv_org_unit_pri_id priority_id
3381 FROM igs_ps_rsv_ogpri
3382 WHERE org_unit_cd = p_org_unit_cd
3383 ORDER BY priority_order;
3384 
3385 -- cursor to fetch preferences defined at owner Organizational Unit level
3386 CURSOR cur_rsv_org_prf(p_rsv_org_unit_pri_id NUMBER) IS
3387 SELECT preference_code,preference_version,group_id,percentage_reserved, rsv_org_unit_prf_id preference_id
3388 FROM igs_ps_rsv_orgun_prf
3389 WHERE rsv_org_unit_pri_id = p_rsv_org_unit_pri_id
3390 ORDER BY preference_order;
3391 
3392 CURSOR cur_program(p_person_id NUMBER , p_course_cd VARCHAR2 ,p_version_number NUMBER) IS
3393 SELECT 'X'
3394 FROM igs_en_stdnt_ps_att
3395 WHERE person_id = p_person_id AND
3396       course_cd = p_course_cd AND
3397           version_number = p_version_number;
3398 
3399 CURSOR cur_org(p_person_id NUMBER , p_org_unit_cd VARCHAR2) IS
3400 SELECT 'X'
3401 FROM igs_en_stdnt_ps_att sca,
3402        igs_ps_ver pv
3403 WHERE sca.person_id = p_person_id AND
3404         sca.course_cd = pv.course_cd AND
3405             sca.version_number = pv.version_number AND
3406             pv.responsible_org_unit_cd = p_org_unit_cd;
3407 
3408 CURSOR cur_unit_set(p_person_id NUMBER , p_unit_set_cd VARCHAR2 ,p_us_version_number NUMBER) IS
3409 SELECT 'X'
3410 FROM igs_en_stdnt_ps_att spa,
3411      igs_as_su_setatmpt sus
3412 WHERE spa.person_id = p_person_id AND
3413       sus.person_id = spa.person_id AND
3414       spa.course_cd = sus.course_cd AND
3415           sus.unit_set_cd = p_unit_set_cd AND
3416           sus.us_version_number = p_us_version_number;
3417 
3418 CURSOR cur_person_grp(p_person_id NUMBER , p_group_id VARCHAR2) IS
3419 SELECT 'X'
3420 FROM igs_pe_prsid_grp_mem pgm
3421 WHERE pgm.person_id = p_person_id AND
3422       pgm.group_id = p_group_id ;
3423 
3424 
3425   l_unit_cd igs_ps_unit_ofr_opt.unit_cd%TYPE;
3426   l_unit_class  igs_ps_unit_ofr_opt.unit_class%TYPE;
3427   l_version_number igs_ps_unit_ofr_opt.version_number%TYPE;
3428   l_cal_type igs_ps_unit_ofr_opt.cal_type%TYPE;
3429   l_ci_sequence_number igs_ps_unit_ofr_opt.ci_sequence_number%TYPE;
3430   l_owner_org_unit_cd  igs_ps_unit_ofr_opt.owner_org_unit_cd%TYPE;
3431 
3432   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
3433   l_rsv_allowed igs_ps_unit_ofr_opt.reserved_seating_allowed%TYPE;
3434   l_pri_satisfied VARCHAR2(1);
3435   l_unreserved_seats NUMBER;
3436 
3437 -- flag variable which stores in which level reserved seat setup found in the hierarchy
3438    l_rsv_level igs_ps_rsv_ext.rsv_level%TYPE;
3439 
3440    l_message               VARCHAR2(30);
3441    l_message_icon        VARCHAR2(1);
3442 -- variable which stores the total reserved percentage found in the hierarchy
3443    l_total_percentage NUMBER;
3444 
3445 -- ================================================================================
3446 -- function which validate whether the syudent can enroll under the
3447 -- given priority/preference which student satisfied.
3448 --
3449 FUNCTION enrf_val_reserve_seat(p_priority_id IN VARCHAR2,
3450                                p_preference_id IN VARCHAR2,
3451                                p_percentage_reserved IN NUMBER,
3452                                p_rsv_level IN VARCHAR2)
3453 RETURN BOOLEAN AS
3454 /*----------------------------------------------------------------------------------+
3455  | HISTORY                                                                          |
3456  | Who         When           What                                                  |
3457  |ptandon     1-Sep-2003     Added two new parameters WLST_PRIORITY_WEIGHT_NUM      |
3458  |                           and WLST_PREFERENCE_WEIGHT_NUM in calls to             |
3459  |                           igs_en_sua_api.update_unit_attempt as part of Waitlist |
3460  |                           Enhancements Build - Bug# 3052426
3461  |rvangala    07-OCT-2003    Value for CORE_INDICATOR_CODE passed to IGS_EN_SUA_API.UPDATE_UNIT_ATTEMPT
3462  |                          added as part of Prevent Dropping Core Units. Enh Bug# 3052432
3463  +---------------------------------------------------------------------------------*/
3464 
3465 -- cursor to get the enrollment maximum defined at unit section level
3466 CURSOR cur_usec_enr_max IS
3467 SELECT enrollment_maximum
3468 FROM igs_ps_usec_lim_wlst
3469 WHERE uoo_id = p_uoo_id;
3470 
3471 -- cursor to get the enrollment maximum defined at unit level
3472 CURSOR cur_unit_enr_max IS
3473 SELECT enrollment_maximum
3474 FROM igs_ps_unit_ver uv,
3475      igs_ps_unit_ofr_opt uoo
3476 WHERE uoo.uoo_id = p_uoo_id AND -- p_uoo_id is parameter of container function
3477       uv.unit_cd = uoo.unit_cd AND
3478           uv.version_number = uoo.version_number;
3479 --
3480 -- cursor to check/get the details of reserve seats utilization against given priority/preference
3481 -- defined at given level.
3482 CURSOR cur_rsv_ext(p_priority_id VARCHAR2, p_preference_id VARCHAR2,
3483                                    p_rsv_level VARCHAR2)IS
3484 SELECT rsve.ROWID, rsve.*
3485 FROM igs_ps_rsv_ext rsve
3486 WHERE rsve.priority_id = p_priority_id AND
3487       rsve.preference_id = p_preference_id AND
3488           rsve.rsv_level = p_rsv_level AND
3489           rsve.uoo_id = p_uoo_id
3490           FOR UPDATE ; -- p_uoo_id is parameter of container function
3491 
3492 cur_rsv_ext_rec cur_rsv_ext%ROWTYPE;
3493 
3494 l_enrollment_max igs_ps_usec_lim_wlst.enrollment_maximum%TYPE;
3495 l_resereved_max NUMBER;
3496 l_rowid VARCHAR2(25);
3497 l_rsv_ext_id NUMBER;
3498 l_rsv_temp_id NUMBER;
3499 
3500 CURSOR  c_igs_en_su_attempt (cp_person_id igs_pe_person.person_id%TYPE,
3501                              cp_uoo_id    igs_ps_unit_ofr_opt.uoo_id%TYPE,
3502                              cp_course_cd igs_en_su_attempt.course_cd%TYPE
3503                              ) IS
3504 SELECT   *
3505 FROM     igs_en_su_attempt
3506 WHERE    person_id = cp_person_id
3507 AND      uoo_id    = cp_uoo_id
3508 AND      course_cd = cp_course_cd ;
3509 
3510 l_c_igs_en_su_attempt  c_igs_en_su_attempt%ROWTYPE ;
3511 
3512 
3513 BEGIN
3514 -- fetching the enrollment maximum defined at unit section level
3515 OPEN cur_usec_enr_max;
3516 FETCH cur_usec_enr_max INTO l_enrollment_max;
3517 CLOSE cur_usec_enr_max;
3518 
3519 -- if enroolment maximum is not defined at unit section level, check at unit level
3520 IF l_enrollment_max IS NULL THEN
3521    OPEN cur_unit_enr_max;
3522    FETCH cur_unit_enr_max INTO l_enrollment_max;
3523    CLOSE cur_unit_enr_max;
3524 END IF;
3525 
3526 --
3527 -- if enrollment maximum is not defined at either levels
3528 IF l_enrollment_max IS NULL THEN
3529    OPEN cur_rsv_ext(p_priority_id,
3530                             p_preference_id,
3531                                     p_rsv_level);
3532    FETCH cur_rsv_ext INTO cur_rsv_ext_rec;
3533 -- record already exist against given priority/preference
3534    IF cur_rsv_ext%FOUND THEN
3535      l_rsv_ext_id := cur_rsv_ext_rec.rsv_ext_id;
3536      igs_ps_rsv_ext_pkg.update_row(x_rowid => cur_rsv_ext_rec.ROWID,
3537                                        x_rsv_ext_id => cur_rsv_ext_rec.rsv_ext_id,
3538                                        x_uoo_id => cur_rsv_ext_rec.uoo_id,
3539                                                                    x_priority_id => cur_rsv_ext_rec.priority_id,
3540                                                                    x_preference_id => cur_rsv_ext_rec.preference_id ,
3541                                                                    x_rsv_level => cur_rsv_ext_rec.rsv_level ,
3542                                                                    x_actual_seat_enrolled => cur_rsv_ext_rec.actual_seat_enrolled + 1,
3543                                                                    x_mode => 'R' );
3544    ELSE -- record is not exist against given priority/preference, so inserting a new record
3545      igs_ps_rsv_ext_pkg.insert_row(x_rowid => l_rowid,
3546                                        x_rsv_ext_id => l_rsv_ext_id,
3547                                        x_uoo_id => p_uoo_id,
3548                                                                    x_priority_id => p_priority_id,
3549                                                                    x_preference_id => p_preference_id ,
3550                                                                    x_rsv_level => p_rsv_level ,
3551                                                                    x_actual_seat_enrolled => 1,
3552                                                                    x_mode => 'R');
3553    END IF; -- cur_rsv_ext
3554    CLOSE cur_rsv_ext;
3555 
3556    FOR l_c_igs_en_su_attempt IN c_igs_en_su_attempt (cp_person_id  => p_person_id,
3557                                                      cp_uoo_id     => p_uoo_id,
3558                                                      cp_course_cd  => p_course_cd)
3559     LOOP
3560       IGS_EN_SU_ATTEMPT_PKG.UPDATE_ROW (
3561                                         X_ROWID                        =>     l_c_igs_en_su_attempt.row_id                         ,
3562                                         X_PERSON_ID                    =>     l_c_igs_en_su_attempt.person_id                      ,
3563                                         X_COURSE_CD                    =>     l_c_igs_en_su_attempt.course_cd                      ,
3564                                         X_UNIT_CD                      =>     l_c_igs_en_su_attempt.unit_cd                        ,
3565                                         X_CAL_TYPE                     =>     l_c_igs_en_su_attempt.cal_type                       ,
3566                                         X_CI_SEQUENCE_NUMBER           =>     l_c_igs_en_su_attempt.ci_sequence_number             ,
3567                                         X_VERSION_NUMBER               =>     l_c_igs_en_su_attempt.version_number                 ,
3568                                         X_LOCATION_CD                  =>     l_c_igs_en_su_attempt.location_cd                    ,
3569                                         X_UNIT_CLASS                   =>     l_c_igs_en_su_attempt.unit_class                     ,
3570                                         X_CI_START_DT                  =>     l_c_igs_en_su_attempt.ci_start_dt                    ,
3571                                         X_CI_END_DT                    =>     l_c_igs_en_su_attempt.ci_end_dt                      ,
3572                                         X_UOO_ID                       =>     l_c_igs_en_su_attempt.uoo_id                         ,
3573                                         X_ENROLLED_DT                  =>     l_c_igs_en_su_attempt.enrolled_dt                    ,
3574                                         X_UNIT_ATTEMPT_STATUS          =>     l_c_igs_en_su_attempt.unit_attempt_status            ,
3575                                         X_ADMINISTRATIVE_UNIT_STATUS   =>     l_c_igs_en_su_attempt.administrative_unit_status     ,
3576                                         X_DISCONTINUED_DT              =>     l_c_igs_en_su_attempt.discontinued_dt                ,
3577                                         X_RULE_WAIVED_DT               =>     l_c_igs_en_su_attempt.rule_waived_dt                 ,
3578                                         X_RULE_WAIVED_PERSON_ID        =>     l_c_igs_en_su_attempt.rule_waived_person_id          ,
3579                                         X_NO_ASSESSMENT_IND            =>     l_c_igs_en_su_attempt.no_assessment_ind              ,
3580                                         X_SUP_UNIT_CD                  =>     l_c_igs_en_su_attempt.sup_unit_cd                    ,
3581                                         X_SUP_VERSION_NUMBER           =>     l_c_igs_en_su_attempt.sup_version_number             ,
3582                                         X_EXAM_LOCATION_CD             =>     l_c_igs_en_su_attempt.exam_location_cd               ,
3583                                         X_ALTERNATIVE_TITLE            =>     l_c_igs_en_su_attempt.alternative_title              ,
3584                                         X_OVERRIDE_ENROLLED_CP         =>     l_c_igs_en_su_attempt.override_enrolled_cp           ,
3585                                         X_OVERRIDE_EFTSU               =>     l_c_igs_en_su_attempt.override_eftsu                 ,
3586                                         X_OVERRIDE_ACHIEVABLE_CP       =>     l_c_igs_en_su_attempt.override_achievable_cp         ,
3587                                         X_OVERRIDE_OUTCOME_DUE_DT      =>     l_c_igs_en_su_attempt.override_outcome_due_dt        ,
3588                                         X_OVERRIDE_CREDIT_REASON       =>     l_c_igs_en_su_attempt.override_credit_reason         ,
3589                                         X_ADMINISTRATIVE_PRIORITY      =>     l_c_igs_en_su_attempt.administrative_priority        ,
3590                                         X_WAITLIST_DT                  =>     l_c_igs_en_su_attempt.waitlist_dt                    ,
3591                                         X_DCNT_REASON_CD               =>     l_c_igs_en_su_attempt.dcnt_reason_cd                 ,
3592                                         X_MODE                         =>     'R'                                                  ,
3593                                         X_GS_VERSION_NUMBER            =>     l_c_igs_en_su_attempt.gs_version_number              ,
3594                                         X_ENR_METHOD_TYPE              =>     l_c_igs_en_su_attempt.enr_method_type                ,
3595                                         X_FAILED_UNIT_RULE             =>     l_c_igs_en_su_attempt.failed_unit_rule               ,
3596                                         X_CART                         =>     l_c_igs_en_su_attempt.cart                           ,
3597                                         X_RSV_SEAT_EXT_ID              =>     l_rsv_ext_id                                         ,
3598                                         X_ORG_UNIT_CD                  =>     l_c_igs_en_su_attempt.org_unit_cd                    ,
3599                                         -- session_id added by Nishikant 28JAN2002 - Enh Bug#2172380.
3600                                         X_SESSION_ID                   =>     l_c_igs_en_su_attempt.session_id,
3601                                         -- Added the column grading schema as a part of the bug 2037897. - aiyer
3602                                         X_GRADING_SCHEMA_CODE          =>     l_c_igs_en_su_attempt.grading_schema_code            ,
3603                                         X_DEG_AUD_DETAIL_ID            =>     l_c_igs_en_su_attempt.deg_aud_detail_id,
3604                                         X_SUBTITLE                     =>     l_c_igs_en_su_attempt.subtitle,
3605                                         X_STUDENT_CAREER_TRANSCRIPT    =>     l_c_igs_en_su_attempt.student_career_transcript       ,
3606                                         X_STUDENT_CAREER_STATISTICS    =>     l_c_igs_en_su_attempt.student_career_statistics,
3607                                         X_ATTRIBUTE_CATEGORY           =>     l_c_igs_en_su_attempt.attribute_category,
3608                                         X_ATTRIBUTE1                   =>     l_c_igs_en_su_attempt.attribute1,
3609                                         X_ATTRIBUTE2                   =>     l_c_igs_en_su_attempt.attribute2,
3610                                         X_ATTRIBUTE3                   =>     l_c_igs_en_su_attempt.attribute3,
3611                                         X_ATTRIBUTE4                   =>     l_c_igs_en_su_attempt.attribute4,
3612                                         X_ATTRIBUTE5                   =>     l_c_igs_en_su_attempt.attribute5,
3613                                         X_ATTRIBUTE6                   =>     l_c_igs_en_su_attempt.attribute6,
3614                                         X_ATTRIBUTE7                   =>     l_c_igs_en_su_attempt.attribute7,
3615                                         X_ATTRIBUTE8                   =>     l_c_igs_en_su_attempt.attribute8,
3616                                         X_ATTRIBUTE9                   =>     l_c_igs_en_su_attempt.attribute9,
3617                                         X_ATTRIBUTE10                  =>     l_c_igs_en_su_attempt.attribute10,
3618                                         X_ATTRIBUTE11                  =>     l_c_igs_en_su_attempt.attribute11,
3619                                         X_ATTRIBUTE12                  =>     l_c_igs_en_su_attempt.attribute12,
3620                                         X_ATTRIBUTE13                  =>     l_c_igs_en_su_attempt.attribute13,
3621                                         X_ATTRIBUTE14                  =>     l_c_igs_en_su_attempt.attribute14,
3622                                         X_ATTRIBUTE15                  =>     l_c_igs_en_su_attempt.attribute15,
3623                                         X_ATTRIBUTE16                  =>     l_c_igs_en_su_attempt.attribute16,
3624                                         X_ATTRIBUTE17                  =>     l_c_igs_en_su_attempt.attribute17,
3625                                         X_ATTRIBUTE18                  =>     l_c_igs_en_su_attempt.attribute18,
3626                                         X_ATTRIBUTE19                  =>     l_c_igs_en_su_attempt.attribute19,
3627                                         X_ATTRIBUTE20                  =>     l_c_igs_en_su_attempt.attribute20,
3628                                         X_WAITLIST_MANUAL_IND          =>     l_c_igs_en_su_attempt.waitlist_manual_ind, --Added by mesriniv for Bug 2554109.
3629                                         X_WLST_PRIORITY_WEIGHT_NUM     =>     l_c_igs_en_su_attempt.wlst_priority_weight_num,
3630                                         X_WLST_PREFERENCE_WEIGHT_NUM   =>     l_c_igs_en_su_attempt.wlst_preference_weight_num,
3631                                         -- CORE_INDICATOR_CODE added by rvangala 07-OCT-2003. Enh Bug# 3052432
3632                                         X_CORE_INDICATOR_CODE          =>     l_c_igs_en_su_attempt.core_indicator_code
3633 
3634                                    ) ;
3635     END LOOP;
3636 -- return TRUE as the given student satisfied some priority/preference and
3637 -- student is eligible to enroll under reserved category
3638    RETURN TRUE;
3639 ELSE -- l_enrollment_max is not null
3640   l_resereved_max := FLOOR((l_enrollment_max * p_percentage_reserved ) / 100);
3641 --
3642 -- get the actual seats enrolled under the give priority/ preference.
3643 --
3644    OPEN cur_rsv_ext(p_priority_id,
3645                     p_preference_id,
3646                     p_rsv_level);
3647    FETCH cur_rsv_ext INTO cur_rsv_ext_rec;
3648 -- record already exist against given priority/preference
3649    IF cur_rsv_ext%FOUND THEN
3650      IF NVL(cur_rsv_ext_rec.actual_seat_enrolled,0) + 1 > l_resereved_max THEN
3651            --
3652            -- no seat available under the given priority/ preference
3653         CLOSE cur_rsv_ext;
3654         RETURN FALSE;
3655      END IF;
3656      l_rsv_ext_id := cur_rsv_ext_rec.rsv_ext_id;
3657      igs_ps_rsv_ext_pkg.update_row(x_rowid => cur_rsv_ext_rec.ROWID,
3658                                        x_rsv_ext_id => cur_rsv_ext_rec.rsv_ext_id,
3659                                        x_uoo_id => cur_rsv_ext_rec.uoo_id,
3660                                        x_priority_id => cur_rsv_ext_rec.priority_id,
3661                                        x_preference_id => cur_rsv_ext_rec.preference_id ,
3662                                        x_rsv_level => cur_rsv_ext_rec.rsv_level ,
3663                                        x_actual_seat_enrolled => cur_rsv_ext_rec.actual_seat_enrolled + 1,
3664                                        x_mode => 'R' );
3665    ELSE -- record is not exist against given priority/preference, so inserting a new record
3666      IF 1 > l_resereved_max THEN
3667            --
3668            -- no seat available under the given priority/ preference
3669         CLOSE cur_rsv_ext;
3670         RETURN FALSE;
3671      END IF;
3672      igs_ps_rsv_ext_pkg.insert_row(x_rowid => l_rowid,
3673                                    x_rsv_ext_id => l_rsv_ext_id,
3674                                    x_uoo_id => p_uoo_id,
3675                                    x_priority_id => p_priority_id,
3676                                    x_preference_id => p_preference_id ,
3677                                    x_rsv_level => p_rsv_level ,
3678                                    x_actual_seat_enrolled => 1,
3679                                    x_mode => 'R');
3680    END IF; -- cur_rsv_ext
3681    IF  cur_rsv_ext%ISOPEN THEN
3682      CLOSE cur_rsv_ext;
3683    END IF;
3684 
3685    FOR l_c_igs_en_su_attempt IN c_igs_en_su_attempt (cp_person_id  => p_person_id,
3686                                                      cp_uoo_id     => p_uoo_id,
3687                                                      cp_course_cd  => p_course_cd)
3688     LOOP
3689       IGS_EN_SU_ATTEMPT_PKG.UPDATE_ROW (
3690                                         X_ROWID                        =>     l_c_igs_en_su_attempt.row_id                         ,
3691                                         X_PERSON_ID                    =>     l_c_igs_en_su_attempt.person_id                      ,
3692                                         X_COURSE_CD                    =>     l_c_igs_en_su_attempt.course_cd                      ,
3693                                         X_UNIT_CD                      =>     l_c_igs_en_su_attempt.unit_cd                        ,
3694                                         X_CAL_TYPE                     =>     l_c_igs_en_su_attempt.cal_type                       ,
3695                                         X_CI_SEQUENCE_NUMBER           =>     l_c_igs_en_su_attempt.ci_sequence_number             ,
3696                                         X_VERSION_NUMBER               =>     l_c_igs_en_su_attempt.version_number                 ,
3697                                         X_LOCATION_CD                  =>     l_c_igs_en_su_attempt.location_cd                    ,
3698                                         X_UNIT_CLASS                   =>     l_c_igs_en_su_attempt.unit_class                     ,
3699                                         X_CI_START_DT                  =>     l_c_igs_en_su_attempt.ci_start_dt                    ,
3700                                         X_CI_END_DT                    =>     l_c_igs_en_su_attempt.ci_end_dt                      ,
3701                                         X_UOO_ID                       =>     l_c_igs_en_su_attempt.uoo_id                         ,
3702                                         X_ENROLLED_DT                  =>     l_c_igs_en_su_attempt.enrolled_dt                    ,
3703                                         X_UNIT_ATTEMPT_STATUS          =>     l_c_igs_en_su_attempt.unit_attempt_status            ,
3704                                         X_ADMINISTRATIVE_UNIT_STATUS   =>     l_c_igs_en_su_attempt.administrative_unit_status     ,
3705                                         X_DISCONTINUED_DT              =>     l_c_igs_en_su_attempt.discontinued_dt                ,
3706                                         X_RULE_WAIVED_DT               =>     l_c_igs_en_su_attempt.rule_waived_dt                 ,
3707                                         X_RULE_WAIVED_PERSON_ID        =>     l_c_igs_en_su_attempt.rule_waived_person_id          ,
3708                                         X_NO_ASSESSMENT_IND            =>     l_c_igs_en_su_attempt.no_assessment_ind              ,
3709                                         X_SUP_UNIT_CD                  =>     l_c_igs_en_su_attempt.sup_unit_cd                    ,
3710                                         X_SUP_VERSION_NUMBER           =>     l_c_igs_en_su_attempt.sup_version_number             ,
3711                                         X_EXAM_LOCATION_CD             =>     l_c_igs_en_su_attempt.exam_location_cd               ,
3712                                         X_ALTERNATIVE_TITLE            =>     l_c_igs_en_su_attempt.alternative_title              ,
3713                                         X_OVERRIDE_ENROLLED_CP         =>     l_c_igs_en_su_attempt.override_enrolled_cp           ,
3714                                         X_OVERRIDE_EFTSU               =>     l_c_igs_en_su_attempt.override_eftsu                 ,
3715                                         X_OVERRIDE_ACHIEVABLE_CP       =>     l_c_igs_en_su_attempt.override_achievable_cp         ,
3716                                         X_OVERRIDE_OUTCOME_DUE_DT      =>     l_c_igs_en_su_attempt.override_outcome_due_dt        ,
3717                                         X_OVERRIDE_CREDIT_REASON       =>     l_c_igs_en_su_attempt.override_credit_reason         ,
3718                                         X_ADMINISTRATIVE_PRIORITY      =>     l_c_igs_en_su_attempt.administrative_priority        ,
3719                                         X_WAITLIST_DT                  =>     l_c_igs_en_su_attempt.waitlist_dt                    ,
3720                                         X_DCNT_REASON_CD               =>     l_c_igs_en_su_attempt.dcnt_reason_cd                 ,
3721                                         X_MODE                         =>     'R'                                                  ,
3722                                         X_GS_VERSION_NUMBER            =>     l_c_igs_en_su_attempt.gs_version_number              ,
3723                                         X_ENR_METHOD_TYPE              =>     l_c_igs_en_su_attempt.enr_method_type                ,
3724                                         X_FAILED_UNIT_RULE             =>     l_c_igs_en_su_attempt.failed_unit_rule               ,
3725                                         X_CART                         =>     l_c_igs_en_su_attempt.cart                           ,
3726                                         X_RSV_SEAT_EXT_ID              =>     l_rsv_ext_id ,
3727                                         X_ORG_UNIT_CD                  =>     l_c_igs_en_su_attempt.org_unit_cd                    ,
3728                                         -- session_id added by Nishikant 28JAN2002 - Enh Bug#2172380.
3729                                         X_SESSION_ID                   =>     l_c_igs_en_su_attempt.session_id,
3730                                         -- Added the column grading schema as a part of the bug 2037897. - aiyer
3731                                         X_GRADING_SCHEMA_CODE          =>     l_c_igs_en_su_attempt.grading_schema_code            ,
3732                                         X_DEG_AUD_DETAIL_ID            =>     l_c_igs_en_su_attempt.deg_aud_detail_id              ,
3733                                         X_SUBTITLE                     =>     l_c_igs_en_su_attempt.subtitle   ,
3734                                         X_STUDENT_CAREER_TRANSCRIPT    =>     l_c_igs_en_su_attempt.student_career_transcript       ,
3735                                         X_STUDENT_CAREER_STATISTICS    =>     l_c_igs_en_su_attempt.student_career_statistics,
3736                                         X_ATTRIBUTE_CATEGORY           =>     l_c_igs_en_su_attempt.attribute_category,
3737                                         X_ATTRIBUTE1                   =>     l_c_igs_en_su_attempt.attribute1,
3738                                         X_ATTRIBUTE2                   =>     l_c_igs_en_su_attempt.attribute2,
3739                                         X_ATTRIBUTE3                   =>     l_c_igs_en_su_attempt.attribute3,
3740                                         X_ATTRIBUTE4                   =>     l_c_igs_en_su_attempt.attribute4,
3741                                         X_ATTRIBUTE5                   =>     l_c_igs_en_su_attempt.attribute5,
3742                                         X_ATTRIBUTE6                   =>     l_c_igs_en_su_attempt.attribute6,
3743                                         X_ATTRIBUTE7                   =>     l_c_igs_en_su_attempt.attribute7,
3744                                         X_ATTRIBUTE8                   =>     l_c_igs_en_su_attempt.attribute8,
3745                                         X_ATTRIBUTE9                   =>     l_c_igs_en_su_attempt.attribute9,
3746                                         X_ATTRIBUTE10                  =>     l_c_igs_en_su_attempt.attribute10,
3747                                         X_ATTRIBUTE11                  =>     l_c_igs_en_su_attempt.attribute11,
3748                                         X_ATTRIBUTE12                  =>     l_c_igs_en_su_attempt.attribute12,
3749                                         X_ATTRIBUTE13                  =>     l_c_igs_en_su_attempt.attribute13,
3750                                         X_ATTRIBUTE14                  =>     l_c_igs_en_su_attempt.attribute14,
3751                                         X_ATTRIBUTE15                  =>     l_c_igs_en_su_attempt.attribute15,
3752                                         X_ATTRIBUTE16                  =>     l_c_igs_en_su_attempt.attribute16,
3753                                         X_ATTRIBUTE17                  =>     l_c_igs_en_su_attempt.attribute17,
3754                                         X_ATTRIBUTE18                  =>     l_c_igs_en_su_attempt.attribute18,
3755                                         X_ATTRIBUTE19                  =>     l_c_igs_en_su_attempt.attribute19,
3756                                         X_ATTRIBUTE20                  =>     l_c_igs_en_su_attempt.attribute20,
3757                                         X_WAITLIST_MANUAL_IND          =>     l_c_igs_en_su_attempt.waitlist_manual_ind, --Added by mesriniv for Bug 2554109.
3758                                         X_WLST_PRIORITY_WEIGHT_NUM     =>     l_c_igs_en_su_attempt.wlst_priority_weight_num,
3759                                         X_WLST_PREFERENCE_WEIGHT_NUM   =>     l_c_igs_en_su_attempt.wlst_preference_weight_num,
3760                                         -- CORE_INDICATOR_CODE added by rvangala 07-OCT-2003. Enh Bug# 3052432
3761                                         X_CORE_INDICATOR_CODE          =>     l_c_igs_en_su_attempt.core_indicator_code
3762                                    ) ;
3763     END LOOP ;
3764 
3765 -- return TRUE as the given student satisfied some priority/preference and
3766 -- student is eligible to enroll under reserved category
3767    RETURN TRUE;
3768 
3769 END IF; -- l_enrollment_max
3770    RETURN FALSE;
3771 END enrf_val_reserve_seat;
3772 
3773 --
3774 -- begin of the function eval_rsv_seat
3775 --
3776 
3777 BEGIN
3778 IF Igs_En_Gen_015.validation_step_is_overridden ('RSV_SEAT',
3779                                                 p_load_cal_type,
3780                                                 p_load_sequence_number ,
3781                                                 p_person_id ,
3782                                                 p_uoo_id ,
3783                                                 l_step_override_limit) THEN
3784     RETURN TRUE;
3785 END IF;
3786 
3787 -- get the details of unit section and check whether reserved seat functionality is allowed for the given unit section
3788 OPEN cur_usec_dtl(p_uoo_id);
3789 FETCH  cur_usec_dtl INTO l_unit_cd,l_unit_class,l_version_number,l_cal_type,l_ci_sequence_number,l_owner_org_unit_cd,l_rsv_allowed;
3790 CLOSE cur_usec_dtl;
3791 
3792 IF l_rsv_allowed = 'N' THEN
3793   RETURN TRUE;
3794 END IF;
3795 
3796 --
3797 -- check whether the student satisfies any Priority and Preference, if yes then return true.
3798 --
3799 -- check the priority/preferences at Unit section level
3800 --
3801 FOR cur_rsv_uoo_pri_rec IN cur_rsv_uoo_pri(p_uoo_id) LOOP
3802   l_rsv_level := 'UNIT_SEC';
3803   IF cur_rsv_uoo_pri_rec.priority_value = 'PROGRAM' THEN
3804     FOR cur_rsv_uoo_prf_rec IN cur_rsv_uoo_prf(cur_rsv_uoo_pri_rec.priority_id) LOOP
3805           OPEN cur_program(p_person_id,cur_rsv_uoo_prf_rec.preference_code ,cur_rsv_uoo_prf_rec.preference_version );
3806           FETCH cur_program INTO l_pri_satisfied;
3807           IF cur_program%FOUND THEN
3808             IF enrf_val_reserve_seat(cur_rsv_uoo_pri_rec.priority_id,
3809                                      cur_rsv_uoo_prf_rec.preference_id,
3810                                      cur_rsv_uoo_prf_rec.percentage_reserved,
3811                                      l_rsv_level) THEN
3812                CLOSE cur_program;
3813                RETURN TRUE;
3814              END IF;
3815           END IF;
3816           IF cur_program%ISOPEN THEN
3817             CLOSE cur_program;
3818           END IF;
3819         l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uoo_prf_rec.percentage_reserved,0);
3820         END LOOP; -- cur_rsv_uoo_prf_rec
3821 
3822   ELSIF cur_rsv_uoo_pri_rec.priority_value = 'ORG_UNIT' THEN
3823     FOR cur_rsv_uoo_prf_rec IN cur_rsv_uoo_prf(cur_rsv_uoo_pri_rec.priority_id) LOOP
3824           OPEN cur_org(p_person_id,cur_rsv_uoo_prf_rec.preference_code);
3825           FETCH cur_org INTO l_pri_satisfied;
3826           IF cur_org%FOUND THEN
3827             IF enrf_val_reserve_seat(cur_rsv_uoo_pri_rec.priority_id,
3828                                      cur_rsv_uoo_prf_rec.preference_id,
3829                                      cur_rsv_uoo_prf_rec.percentage_reserved,
3830                                      l_rsv_level) THEN
3831               CLOSE cur_org;
3832               RETURN TRUE;
3833             END IF;
3834           END IF;
3835           IF cur_org%ISOPEN THEN
3836              CLOSE cur_org;
3837           END IF;
3838      l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uoo_prf_rec.percentage_reserved,0);
3839      END LOOP; -- cur_rsv_uoo_prf_rec
3840 
3841   ELSIF cur_rsv_uoo_pri_rec.priority_value = 'UNIT_SET' THEN
3842     FOR cur_rsv_uoo_prf_rec IN cur_rsv_uoo_prf(cur_rsv_uoo_pri_rec.priority_id) LOOP
3843           OPEN cur_unit_set(p_person_id,cur_rsv_uoo_prf_rec.preference_code ,cur_rsv_uoo_prf_rec.preference_version );
3844           FETCH cur_unit_set INTO l_pri_satisfied;
3845           IF cur_unit_set%FOUND THEN
3846             IF enrf_val_reserve_seat(cur_rsv_uoo_pri_rec.priority_id,
3847                                          cur_rsv_uoo_prf_rec.preference_id,
3848                                                                  cur_rsv_uoo_prf_rec.percentage_reserved,
3849                                                          l_rsv_level) THEN
3850               CLOSE cur_unit_set;
3851               RETURN TRUE;
3852             END IF;
3853           END IF;
3854           IF cur_unit_set%ISOPEN THEN
3855             CLOSE cur_unit_set;
3856           END IF;
3857         l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uoo_prf_rec.percentage_reserved,0);
3858         END LOOP; -- cur_rsv_uoo_prf_rec
3859 
3860   ELSIF cur_rsv_uoo_pri_rec.priority_value = 'PROGRAM_STAGE' THEN
3861     FOR cur_rsv_uoo_prf_rec IN cur_rsv_uoo_prf(cur_rsv_uoo_pri_rec.priority_id) LOOP
3862       --
3863           -- Call the function to determine whether given student completed the given program stage
3864           --
3865           IF igs_en_gen_015.enrp_val_Ps_Stage(p_person_id,
3866                                               p_course_cd,
3867                                               p_course_version,
3868                                               cur_rsv_uoo_prf_rec.preference_code) THEN
3869 
3870             IF enrf_val_reserve_seat(cur_rsv_uoo_pri_rec.priority_id,
3871                                      cur_rsv_uoo_prf_rec.preference_id,
3872                                      cur_rsv_uoo_prf_rec.percentage_reserved,
3873                                      l_rsv_level) THEN
3874                RETURN TRUE;
3875             END IF;
3876           END IF;
3877      l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uoo_prf_rec.percentage_reserved,0);
3878      END LOOP; -- cur_rsv_uoo_prf_rec
3879 
3880   ELSIF cur_rsv_uoo_pri_rec.priority_value = 'PERSON_GRP' THEN
3881     FOR cur_rsv_uoo_prf_rec IN cur_rsv_uoo_prf(cur_rsv_uoo_pri_rec.priority_id) LOOP
3882           OPEN cur_person_grp(p_person_id,cur_rsv_uoo_prf_rec.group_id);
3883           FETCH cur_person_grp INTO l_pri_satisfied;
3884           IF cur_person_grp%FOUND THEN
3885             IF enrf_val_reserve_seat(cur_rsv_uoo_pri_rec.priority_id,
3886                                      cur_rsv_uoo_prf_rec.preference_id,
3887                                      cur_rsv_uoo_prf_rec.percentage_reserved,
3888                                      l_rsv_level) THEN
3889               CLOSE cur_person_grp;
3890               RETURN TRUE;
3891             END IF;
3892           END IF;
3893           IF cur_person_grp%ISOPEN THEN
3894             CLOSE cur_person_grp;
3895           END IF;
3896         l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uoo_prf_rec.percentage_reserved,0);
3897         END LOOP; -- cur_rsv_uoo_prf_rec
3898    ELSIF cur_rsv_uoo_pri_rec.priority_value = 'CLASS_STD' THEN
3899            FOR cur_rsv_uoo_prf_rec IN cur_rsv_uoo_prf(cur_rsv_uoo_pri_rec.priority_id) LOOP
3900              IF igs_pr_get_class_std.get_class_standing(p_person_id, p_course_cd, 'Y', SYSDATE, NULL, NULL)
3901                                                               = cur_rsv_uoo_prf_rec.preference_code THEN
3902                    IF enrf_val_reserve_seat(cur_rsv_uoo_pri_rec.priority_id,
3903                                           cur_rsv_uoo_prf_rec.preference_id,
3904                                           cur_rsv_uoo_prf_rec.percentage_reserved,
3905                                           l_rsv_level) THEN
3906                         RETURN TRUE;
3907                    END IF;
3908              END IF;
3909            l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uoo_prf_rec.percentage_reserved,0);
3910            END LOOP;
3911    END IF; --cur_rsv_uoo_pri_rec.priority_value
3912 END LOOP; -- cur_rsv_uoo_rec
3913 
3914 --
3915 -- if no priority/preferences defined at Unit section level,
3916 -- check the priority/preferences at Unit offering pattern level
3917 --
3918 IF l_rsv_level IS NULL THEN
3919    FOR cur_rsv_uop_pri_rec IN cur_rsv_uop_pri(l_unit_cd,l_version_number,l_cal_type,l_ci_sequence_number) LOOP
3920      --Assign value changed from 'UNIT_OFR_OPT' TO 'UNIT_PAT', because l_rsv_level variable is stype of IGS_PS_RSV_EXT.RSV_LEVEL
3921      --which is VARCHAR2(10) but 'UNIT_OFR_OPT' size is 12 chars which throws value numberic value error
3922      --w.r.t. bug no 2455245 by kkillams
3923      l_rsv_level := 'UNIT_PAT';
3924      IF cur_rsv_uop_pri_rec.priority_value = 'PROGRAM' THEN
3925        FOR cur_rsv_uop_prf_rec IN cur_rsv_uop_prf(cur_rsv_uop_pri_rec.priority_id) LOOP
3926           OPEN cur_program(p_person_id,cur_rsv_uop_prf_rec.preference_code ,cur_rsv_uop_prf_rec.preference_version );
3927           FETCH cur_program INTO l_pri_satisfied;
3928           IF cur_program%FOUND THEN
3929             IF enrf_val_reserve_seat(cur_rsv_uop_pri_rec.priority_id,
3930                                      cur_rsv_uop_prf_rec.preference_id,
3931                                      cur_rsv_uop_prf_rec.percentage_reserved,
3932                                      l_rsv_level) THEN
3933                CLOSE cur_program;
3934                RETURN TRUE;
3935             END IF;
3936           END IF;
3937           IF cur_program%ISOPEN THEN
3938             CLOSE cur_program;
3939           END IF;
3940        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uop_prf_rec.percentage_reserved,0);
3941        END LOOP; -- cur_rsv_uop_prf_rec
3942 
3943      ELSIF cur_rsv_uop_pri_rec.priority_value = 'ORG_UNIT' THEN
3944        FOR cur_rsv_uop_prf_rec IN cur_rsv_uop_prf(cur_rsv_uop_pri_rec.priority_id) LOOP
3945           OPEN cur_org(p_person_id,cur_rsv_uop_prf_rec.preference_code);
3946           FETCH cur_org INTO l_pri_satisfied;
3947           IF cur_org%FOUND THEN
3948             IF enrf_val_reserve_seat(cur_rsv_uop_pri_rec.priority_id,
3949                                      cur_rsv_uop_prf_rec.preference_id,
3950                                      cur_rsv_uop_prf_rec.percentage_reserved,
3951                                      l_rsv_level) THEN
3952                CLOSE cur_org;
3953                RETURN TRUE;
3954             END IF;
3955           END IF;
3956           IF cur_org%ISOPEN THEN
3957              CLOSE cur_org;
3958           END IF;
3959        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uop_prf_rec.percentage_reserved,0);
3960        END LOOP; -- cur_rsv_uop_prf_rec
3961 
3962      ELSIF cur_rsv_uop_pri_rec.priority_value = 'UNIT_SET' THEN
3963        FOR cur_rsv_uop_prf_rec IN cur_rsv_uop_prf(cur_rsv_uop_pri_rec.priority_id) LOOP
3964           OPEN cur_unit_set(p_person_id,cur_rsv_uop_prf_rec.preference_code ,cur_rsv_uop_prf_rec.preference_version );
3965           FETCH cur_unit_set INTO l_pri_satisfied;
3966           IF cur_unit_set%FOUND THEN
3967             IF enrf_val_reserve_seat(cur_rsv_uop_pri_rec.priority_id,
3968                                      cur_rsv_uop_prf_rec.preference_id,
3969                                      cur_rsv_uop_prf_rec.percentage_reserved,
3970                                      l_rsv_level) THEN
3971                CLOSE cur_unit_set;
3972                RETURN TRUE;
3973             END IF;
3974           END IF;
3975           IF cur_unit_set%ISOPEN THEN
3976             CLOSE cur_unit_set;
3977           END IF;
3978        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uop_prf_rec.percentage_reserved,0);
3979        END LOOP; -- cur_rsv_uop_prf_rec
3980 
3981      ELSIF cur_rsv_uop_pri_rec.priority_value = 'PROGRAM_STAGE' THEN
3982        FOR cur_rsv_uop_prf_rec IN cur_rsv_uop_prf(cur_rsv_uop_pri_rec.priority_id) LOOP
3983           --
3984               -- Call the function to determine whether given student completed the given program stage
3985               --
3986               IF igs_en_gen_015.enrp_val_Ps_Stage(p_person_id,
3987                                           p_course_cd,
3988                                           p_course_version,
3989                                           cur_rsv_uop_prf_rec.preference_code) THEN
3990 
3991              IF enrf_val_reserve_seat(cur_rsv_uop_pri_rec.priority_id,
3992                                       cur_rsv_uop_prf_rec.preference_id,
3993                                       cur_rsv_uop_prf_rec.percentage_reserved,
3994                                       l_rsv_level) THEN
3995                RETURN TRUE;
3996                 END IF;
3997           END IF;
3998         l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uop_prf_rec.percentage_reserved,0);
3999        END LOOP; -- cur_rsv_uop_prf_rec
4000 
4001      ELSIF cur_rsv_uop_pri_rec.priority_value = 'PERSON_GRP' THEN
4002        FOR cur_rsv_uop_prf_rec IN cur_rsv_uop_prf(cur_rsv_uop_pri_rec.priority_id) LOOP
4003           OPEN cur_person_grp(p_person_id,cur_rsv_uop_prf_rec.group_id);
4004           FETCH cur_person_grp INTO l_pri_satisfied;
4005           IF cur_person_grp%FOUND THEN
4006             IF enrf_val_reserve_seat(cur_rsv_uop_pri_rec.priority_id,
4007                                      cur_rsv_uop_prf_rec.preference_id,
4008                                      cur_rsv_uop_prf_rec.percentage_reserved,
4009                                      l_rsv_level) THEN
4010                CLOSE cur_person_grp;
4011                RETURN TRUE;
4012             END IF;
4013           END IF;
4014           IF cur_person_grp%ISOPEN THEN
4015             CLOSE cur_person_grp;
4016           END IF;
4017        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uop_prf_rec.percentage_reserved,0);
4018        END LOOP; -- cur_rsv_uop_prf_rec
4019      ELSIF cur_rsv_uop_pri_rec.priority_value = 'CLASS_STD' THEN
4020        FOR cur_rsv_uop_prf_rec IN cur_rsv_uop_prf(cur_rsv_uop_pri_rec.priority_id) LOOP
4021          IF igs_pr_get_class_std.get_class_standing(p_person_id, p_course_cd, 'Y', SYSDATE, NULL, NULL)
4022                                                           = cur_rsv_uop_prf_rec.preference_code THEN
4023                IF enrf_val_reserve_seat(cur_rsv_uop_pri_rec.priority_id,
4024                                       cur_rsv_uop_prf_rec.preference_id,
4025                                       cur_rsv_uop_prf_rec.percentage_reserved,
4026                                       l_rsv_level) THEN
4027                     RETURN TRUE;
4028                END IF;
4029          END IF;
4030         l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_uop_prf_rec.percentage_reserved,0);
4031        END LOOP;
4032      END IF; --cur_rsv_uop_pri_rec.priority_value
4033    END LOOP; -- cur_rsv_uop_rec
4034 END IF;
4035 
4036 --
4037 -- if no priority/preferences defined at Unit section or Unit offering pattern level,
4038 -- check the priority/preferences at Organizational Unit level
4039 --
4040 IF l_rsv_level IS NULL THEN
4041    FOR cur_rsv_org_pri_rec IN cur_rsv_org_pri(l_owner_org_unit_cd) LOOP
4042      l_rsv_level := 'ORG_UNIT';
4043      IF cur_rsv_org_pri_rec.priority_value = 'PROGRAM' THEN
4044        FOR cur_rsv_org_prf_rec IN cur_rsv_org_prf(cur_rsv_org_pri_rec.priority_id) LOOP
4045              OPEN cur_program(p_person_id,cur_rsv_org_prf_rec.preference_code ,cur_rsv_org_prf_rec.preference_version );
4046              FETCH cur_program INTO l_pri_satisfied;
4047           IF cur_program%FOUND THEN
4048             IF enrf_val_reserve_seat(cur_rsv_org_pri_rec.priority_id,
4049                                      cur_rsv_org_prf_rec.preference_id,
4050                                      cur_rsv_org_prf_rec.percentage_reserved,
4051                                      l_rsv_level) THEN
4052                 CLOSE cur_program;
4053                 RETURN TRUE;
4054              END IF;
4055           END IF;
4056           IF cur_program%ISOPEN THEN
4057             CLOSE cur_program;
4058           END IF;
4059        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_org_prf_rec.percentage_reserved,0);
4060        END LOOP; -- cur_rsv_org_prf_rec
4061 
4062      ELSIF cur_rsv_org_pri_rec.priority_value = 'ORG_UNIT' THEN
4063        FOR cur_rsv_org_prf_rec IN cur_rsv_org_prf(cur_rsv_org_pri_rec.priority_id) LOOP
4064           OPEN cur_org(p_person_id,cur_rsv_org_prf_rec.preference_code);
4065           FETCH cur_org INTO l_pri_satisfied;
4066           IF cur_org%FOUND THEN
4067             IF enrf_val_reserve_seat(cur_rsv_org_pri_rec.priority_id,
4068                                      cur_rsv_org_prf_rec.preference_id,
4069                                      cur_rsv_org_prf_rec.percentage_reserved,
4070                                      l_rsv_level) THEN
4071                CLOSE cur_org;
4072                RETURN TRUE;
4073              END IF;
4074           END IF;
4075           IF cur_org%ISOPEN THEN
4076             CLOSE cur_org;
4077           END IF;
4078        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_org_prf_rec.percentage_reserved,0);
4079        END LOOP; -- cur_rsv_org_prf_rec
4080 
4081      ELSIF cur_rsv_org_pri_rec.priority_value = 'UNIT_SET' THEN
4082        FOR cur_rsv_org_prf_rec IN cur_rsv_org_prf(cur_rsv_org_pri_rec.priority_id) LOOP
4083           OPEN cur_unit_set(p_person_id,cur_rsv_org_prf_rec.preference_code ,cur_rsv_org_prf_rec.preference_version );
4084           FETCH cur_unit_set INTO l_pri_satisfied;
4085           IF cur_unit_set%FOUND THEN
4086             IF enrf_val_reserve_seat(cur_rsv_org_pri_rec.priority_id,
4087                                          cur_rsv_org_prf_rec.preference_id,
4088                                                                  cur_rsv_org_prf_rec.percentage_reserved,
4089                                                          l_rsv_level) THEN
4090                CLOSE cur_unit_set;
4091                RETURN TRUE;
4092             END IF;
4093           END IF;
4094           IF cur_unit_set%ISOPEN THEN
4095             CLOSE cur_unit_set;
4096           END IF;
4097        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_org_prf_rec.percentage_reserved,0);
4098        END LOOP; -- cur_rsv_org_prf_rec
4099 
4100      ELSIF cur_rsv_org_pri_rec.priority_value = 'PROGRAM_STAGE' THEN
4101        FOR cur_rsv_org_prf_rec IN cur_rsv_org_prf(cur_rsv_org_pri_rec.priority_id) LOOP
4102           --
4103               -- Call the function to determine whether given student completed the given program stage
4104               --
4105               IF igs_en_gen_015.enrp_val_Ps_Stage(p_person_id,
4106                                           p_course_cd,
4107                                           p_course_version,
4108                                           cur_rsv_org_prf_rec.preference_code) THEN
4109 
4110             IF enrf_val_reserve_seat(cur_rsv_org_pri_rec.priority_id,
4111                                          cur_rsv_org_prf_rec.preference_id,
4112                                                                  cur_rsv_org_prf_rec.percentage_reserved,
4113                                                          l_rsv_level) THEN
4114                RETURN TRUE;
4115                 END IF;
4116           END IF;
4117        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_org_prf_rec.percentage_reserved,0);
4118        END LOOP; -- cur_rsv_org_prf_rec
4119 
4120      ELSIF cur_rsv_org_pri_rec.priority_value = 'PERSON_GRP' THEN
4121        FOR cur_rsv_org_prf_rec IN cur_rsv_org_prf(cur_rsv_org_pri_rec.priority_id) LOOP
4122           OPEN cur_person_grp(p_person_id,cur_rsv_org_prf_rec.group_id);
4123           FETCH cur_person_grp INTO l_pri_satisfied;
4124           IF cur_person_grp%FOUND THEN
4125             IF enrf_val_reserve_seat(cur_rsv_org_pri_rec.priority_id,
4126                                          cur_rsv_org_prf_rec.preference_id,
4127                                                                  cur_rsv_org_prf_rec.percentage_reserved,
4128                                                          l_rsv_level) THEN
4129                 CLOSE cur_person_grp;
4130                 RETURN TRUE;
4131              END IF;
4132           END IF;
4133           IF cur_person_grp%ISOPEN THEN
4134              CLOSE cur_person_grp;
4135           END IF;
4136        l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_org_prf_rec.percentage_reserved,0);
4137        END LOOP; -- cur_rsv_org_prf_rec
4138     ELSIF cur_rsv_org_pri_rec.priority_value = 'CLASS_STD' THEN
4139        FOR cur_rsv_org_prf_rec IN cur_rsv_org_prf(cur_rsv_org_pri_rec.priority_id) LOOP
4140          IF igs_pr_get_class_std.get_class_standing(p_person_id, p_course_cd, 'Y', SYSDATE, NULL, NULL)
4141                                                           = cur_rsv_org_prf_rec.preference_code THEN
4142                IF enrf_val_reserve_seat(cur_rsv_org_pri_rec.priority_id,
4143                                       cur_rsv_org_prf_rec.preference_id,
4144                                       cur_rsv_org_prf_rec.percentage_reserved,
4145                                       l_rsv_level) THEN
4146                     RETURN TRUE;
4147                END IF;
4148          END IF;
4149         l_total_percentage := NVL(l_total_percentage,0) + NVL(cur_rsv_org_prf_rec.percentage_reserved,0);
4150        END LOOP;
4151      END IF; --cur_rsv_org_pri_rec.priority_value
4152    END LOOP; -- cur_rsv_org_rec
4153 END IF;
4154 
4155 --
4156 -- If no priority/preferences defined at any level
4157 --
4158 IF l_rsv_level IS NULL THEN
4159   RETURN TRUE;
4160 END IF;
4161 
4162 --
4163 -- student hasn't satisfied any priority/preference
4164 -- check whether any seats available in unreserved category.
4165 --
4166  l_unreserved_seats := Igs_En_Gen_015.seats_in_unreserved_category(
4167                                                                    p_uoo_id => p_uoo_id  ,
4168                                                                    p_level => l_rsv_level );
4169 
4170 -- if unreserved seats available return TRUE
4171 IF l_unreserved_seats >= 1 THEN
4172   RETURN TRUE;
4173 END IF;
4174 
4175 IF p_deny_warn = 'WARN' THEN
4176   IF p_calling_obj = 'JOB' THEN
4177      l_message := 'IGS_SS_WARN_RSVSEAT_CHK';
4178   ELSE
4179      l_message := 'IGS_EN_RSVSEAT_TAB_WARN';
4180   END IF;
4181 ELSE
4182   IF p_calling_obj = 'JOB' THEN
4183      l_message := 'IGS_SS_DENY_RSVSEAT_CHK';
4184   ELSE
4185      l_message := 'IGS_EN_RSVSEAT_TAB_DENY';
4186   END IF;
4187   IF l_unreserved_seats < 1 AND NVL(l_total_percentage,-1) >= 100 THEN
4188     p_deny_enrollment := 'Y';
4189   END IF;
4190 END IF;
4191 
4192 IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
4193 
4194       l_message_icon := substr(p_deny_warn,1,1);
4195       igs_en_drop_units_api.create_ss_warning (
4196              p_person_id => p_person_id,
4197              p_course_cd => p_course_cd,
4198              p_term_cal_type=> p_load_cal_type,
4199              p_term_ci_sequence_number => p_load_sequence_number,
4200              p_uoo_id => p_uoo_id,
4201              p_message_for => l_unit_cd||'/'||l_unit_class ,
4202              p_message_icon=> l_message_icon,
4203              p_message_name => l_message,
4204              p_message_rule_text => NULL,
4205              p_message_tokens => NULL,
4206              p_message_action=> NULL,
4207              p_destination =>NULL,
4208              p_parameters => NULL,
4209              p_step_type => 'UNIT');
4210 
4211 ELSE
4212 
4213       IF p_message IS NULL THEN
4214         p_message := l_message;
4215       ELSE
4216         p_message := p_message || ';' || l_message;
4217       END IF;
4218 
4219 END IF;
4220 
4221 
4222 
4223 
4224 RETURN FALSE;
4225 
4226 END eval_rsv_seat;
4227 
4228 -- =================================================================================
4229 
4230 FUNCTION eval_cart_max(
4231 p_person_id IN NUMBER,
4232 p_load_cal_type IN VARCHAR2,
4233 p_load_sequence_number IN VARCHAR2,
4234 p_uoo_id  IN NUMBER,
4235 p_course_cd IN VARCHAR2,
4236 p_course_version IN NUMBER,
4237 p_message IN OUT NOCOPY VARCHAR2,
4238 p_deny_warn  IN VARCHAR2,
4239 p_rule_seq_number IN NUMBER
4240 ) RETURN BOOLEAN AS
4241 
4242 ------------------------------------------------------------------------------------
4243   --Created by  : knaraset ( Oracle IDC)
4244   --Date created: 21-JUN-2001
4245   --
4246   --Purpose:
4247   --
4248   --Known limitations/enhancements and/or remarks:
4249   --
4250   --Change History:
4251   --Who         When            What
4252   -- svenkata                   Call to igs_ru_gen_001.rulp_val_senna has been modified to include 2 new parameters
4253   --                            p_load_cal_type and p_load_sequence_number . The corresponding named rule has also been
4254   --                            modified . Bug # 2338013.
4255   -------------------------------------------------------------------------------------
4256 
4257   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
4258   l_message VARCHAR2(30);
4259 --
4260 -- begin of the function eval_coreq
4261 --
4262 BEGIN
4263 
4264 -- no cart max rule defined
4265 IF p_rule_seq_number IS NULL THEN
4266   RETURN TRUE;
4267 END IF;
4268 
4269 -- check whether cart max rule has been overriden for the given student.
4270 IF Igs_En_Gen_015.validation_step_is_overridden ('CART_MAX',
4271                                                 p_load_cal_type,
4272                                                 p_load_sequence_number ,
4273                                                 p_person_id ,
4274                                                 p_uoo_id ,
4275                                                 l_step_override_limit) THEN
4276     RETURN TRUE;
4277 END IF;
4278 
4279 --
4280 -- check whether student has satisfied the cart max rule by invoking the rule engine
4281 
4282 IF igs_ru_gen_001.rulp_val_senna(p_rule_call_name => 'CART_MAX',
4283                                  p_person_id => p_person_id,
4284                                  p_message => l_message,
4285                                  p_rule_number => p_rule_seq_number,
4286                                  p_param_1 => p_course_cd,
4287                                  p_param_2 => p_course_version,
4288                                  p_param_3 => p_load_cal_type,
4289                                  p_param_4 => p_load_sequence_number
4290    ) = 'false' THEN
4291 
4292    IF p_deny_warn = 'WARN' THEN
4293      IF p_message IS NULL THEN
4294         p_message := 'IGS_SS_WARN_CART_MAX';
4295      ELSE
4296         p_message := p_message ||';'||'IGS_SS_WARN_CART_MAX';
4297      END IF;
4298    ELSE
4299      IF p_message IS NULL THEN
4300         p_message := 'IGS_SS_DENY_CART_MAX';
4301      ELSE
4302         p_message := p_message ||';'||'IGS_SS_DENY_CART_MAX';
4303      END IF;
4304    END IF;
4305    RETURN FALSE;
4306 END IF;
4307 
4308 RETURN TRUE;
4309 
4310 END eval_cart_max;
4311   --
4312   --
4313   --  This function is used to evaluate the Intermission Unit Level Rule Status.
4314   --
4315   --
4316   FUNCTION eval_intmsn_unit_lvl
4317   (
4318     p_person_id                    IN     NUMBER,
4319     p_load_cal_type                IN     VARCHAR2,
4320     p_load_cal_seq_number          IN     NUMBER,
4321     p_uoo_id                       IN     NUMBER,
4322     p_program_cd                   IN     VARCHAR2,
4323     p_program_version              IN     VARCHAR2,
4324     p_message                      IN OUT NOCOPY VARCHAR2,
4325     p_deny_warn                    IN     VARCHAR2,
4326     p_rule_seq_number              IN     NUMBER,
4327     p_calling_obj                  IN     VARCHAR2
4328   ) RETURN BOOLEAN AS
4329   /*  HISTORY
4330     WHO        WHEN         WHAT
4331     ayedubat   07-JUN-2002   Changed the type of cursor parameter,cp_program_cd from NUMBER to
4332                              IGS_PS_VER.course_cd%TYPE of the cursor,cur_intermission_details for the bug:2381603
4333     svenkata   26-JUN-2002   The IF condition for the Intermission records had a logical error . The same has been
4334                              fixed .Bug # 2423604
4335   */
4336     --
4337     --  Parameters Description:
4338     --
4339     --  p_person_id                  -> Person ID of the student who wants to enroll or administrator is enrolling.
4340     --  p_load_cal_type              -> Load (Term) or Teaching Calendar Type.
4341     --  p_load_cal_seq_number        -> Load Calendar or Teaching Calendar instance sequence number.
4342     --  p_uoo_id                     -> Unit Section Identifier.
4343     --  p_program_cd                 -> The Primary Program Code or the Program code selected by the student.
4344     --  p_program_version            -> The Primary Program version number or the Program version number selected by the student.
4345     --  p_message                    -> Message from the validation.
4346     --  p_deny_warn                  -> Deny or Warn Indicator based on the setup.
4347     --  p_rule_seq_number            -> Sequence Number of the Unit level Intermission Rules.
4348     --
4349     --
4350     --  Cursor to find Calendar Type and Calendar Sequence Number for a Unit Section.
4351     --
4352     CURSOR cur_cal_type_seq_num (
4353              cp_uoo_id                IN NUMBER
4354            ) IS
4355     SELECT   cal_type, ci_sequence_number, unit_cd, unit_class
4356     FROM     igs_ps_unit_ofr_opt
4357     WHERE    uoo_id = cp_uoo_id;
4358     --
4359     --  Cursor to find Intermission Type and Start Date for a given Person and Program.
4360     --
4361     CURSOR cur_intermission_details (
4362            cp_person_id   IGS_EN_STDNT_PS_ATT.person_id%TYPE,
4363            cp_program_cd  IGS_PS_VER.course_cd%TYPE
4364     ) IS
4365     SELECT   sci.intermission_type,
4366              sci.start_dt,
4367              sci.approved
4368     FROM     igs_en_stdnt_ps_intm sci,
4369              IGS_EN_INTM_TYPES eit,
4370              igs_en_stdnt_ps_att spa
4371     WHERE    sci.person_id = cp_person_id
4372     AND      sci.course_cd = cp_program_cd
4373     AND      sci.approved  = eit.appr_reqd_ind
4374     AND      eit.intermission_type = sci.intermission_type
4375     AND      sci.logical_delete_date = TO_DATE('31-12-4712','DD-MM-YYYY')
4376     AND      spa.person_id = sci.person_id
4377     AND      spa.course_cd = sci.course_cd
4378     AND      ((trunc(sysdate) between sci.start_dt and sci.end_dt)
4379                OR
4380               ((trunc(sysdate) > sci.end_dt) AND (spa.course_attempt_status = 'INTERMIT'))
4381              );
4382 
4383     --
4384     l_cal_type_rec cur_cal_type_seq_num%ROWTYPE;
4385     rec_cur_intermission_details cur_intermission_details%ROWTYPE;
4386     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
4387     l_message VARCHAR2(30);
4388     l_return_value VARCHAR2(30) := 'true';
4389     l_rule_text VARCHAR2(1000);
4390     l_message_icon VARCHAR2(1);
4391     --
4392 
4393   BEGIN
4394     --
4395     --  Check whether Unit Level Intermission Status step has been overridden.
4396     --
4397     IF Igs_En_Gen_015.validation_step_is_overridden (
4398          'INT_STSU',
4399          p_load_cal_type,
4400          p_load_cal_seq_number,
4401          p_person_id,
4402          p_uoo_id,
4403          l_step_override_limit
4404        ) THEN
4405       RETURN TRUE;
4406     END IF;
4407 
4408     IF p_rule_seq_number IS  NULL THEN
4409       RETURN TRUE;
4410     ELSE
4411 
4412       --
4413       --  If the Rule is defined then get the Teaching Calendar Type and Teaching Calendar Sequence Number.
4414       --
4415       OPEN cur_cal_type_seq_num (p_uoo_id);
4416       FETCH cur_cal_type_seq_num INTO l_cal_type_rec;
4417       CLOSE cur_cal_type_seq_num;
4418       --
4419       --  Select all the intermission records of the program passed and make a call to the rule for all of them.
4420       --
4421       FOR rec_cur_intermission_details IN cur_intermission_details (p_person_id, p_program_cd) LOOP
4422         --
4423         --  Check whether student has satisfied the Intermission Status Step rule by invoking the rule engine.
4424         --
4425         l_return_value := igs_ru_gen_001.rulp_val_senna (
4426               p_rule_call_name             => 'INT_STSU',
4427               p_rule_number                => p_rule_seq_number,
4428               p_person_id                  => p_person_id,
4429               p_param_1                    => p_program_cd,
4430               p_param_2                    => rec_cur_intermission_details.intermission_type,
4431               p_param_3                    => rec_cur_intermission_details.start_dt,
4432               p_param_4                    => p_load_cal_type,
4433               p_param_5                    => p_load_cal_seq_number,
4434               p_param_6                    => l_cal_type_rec.cal_type,
4435               p_param_7                    => l_cal_type_rec.ci_sequence_number,
4436               p_message                    => l_message
4437             ) ;
4438         IF l_return_value = 'false'  THEN
4439           EXIT;
4440         END IF;
4441       END LOOP;
4442       --
4443       --  If the student has not satisfied the Intermission Status Step rule then return FALSE with a warning/deny message.
4444       --
4445       IF l_return_value = 'false'  THEN
4446 
4447 
4448         IF p_deny_warn = 'WARN' THEN
4449              l_message := 'IGS_SS_WARN_INTERMIT_STAT';
4450         ELSE
4451              l_message := 'IGS_SS_DENY_INTERMIT_STAT';
4452         END IF;
4453 
4454         IF p_calling_obj NOT IN  ('JOB','SCH_UPD','JOB_FROM_WAITLIST') THEN
4455 
4456           IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
4457             l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(p_rule_seq_number);
4458           END IF;
4459           l_message_icon := substr(p_deny_warn,1,1);
4460           igs_en_drop_units_api.create_ss_warning (
4461                  p_person_id => p_person_id,
4462                  p_course_cd => p_program_cd,
4463                  p_term_cal_type=> p_load_cal_type,
4464                  p_term_ci_sequence_number => p_load_cal_seq_number,
4465                  p_uoo_id => p_uoo_id,
4466                  p_message_for => l_cal_type_rec.unit_cd||'/'||l_cal_type_rec.unit_class ,
4467                  p_message_icon=> l_message_icon,
4468                  p_message_name => l_message,
4469                  p_message_rule_text => l_rule_text,
4470                  p_message_tokens => NULL,
4471                  p_message_action=> NULL,
4472                  p_destination =>NULL,
4473                  p_parameters => NULL,
4474                  p_step_type => 'UNIT');
4475 
4476       ELSE
4477 
4478         IF p_message IS NULL THEN
4479           p_message := l_message;
4480         ELSE
4481           p_message := p_message || ';' || l_message;
4482         END IF;
4483 
4484       END IF; -- IF p_calling_obj <> 'JOB' THEN
4485 
4486       RETURN FALSE;
4487 
4488     ELSE
4489       RETURN TRUE;
4490     END IF; -- IF l_return_value = 'false'  THEN
4491 
4492   END IF;  --   IF p_rule_seq_number IS  NULL
4493     --
4494   END eval_intmsn_unit_lvl;
4495   --
4496   --
4497   --  This function is used to evaluate the Visa Unit Level Rule Status.
4498   --
4499   --
4500   FUNCTION eval_visa_unit_lvl
4501   (
4502     p_person_id                    IN     NUMBER,
4503     p_load_cal_type                IN     VARCHAR2,
4504     p_load_cal_seq_number          IN     NUMBER,
4505     p_uoo_id                       IN     NUMBER,
4506     p_program_cd                   IN     VARCHAR2,
4507     p_program_version              IN     VARCHAR2,
4508     p_message                      IN OUT NOCOPY VARCHAR2,
4509     p_deny_warn                    IN     VARCHAR2,
4510     p_rule_seq_number              IN     NUMBER,
4511     p_calling_obj                  IN     VARCHAR2
4512   ) RETURN BOOLEAN AS
4513 ------------------------------------------------------------------------------------
4514   --Created by  : knaraset ( Oracle IDC)
4515   --Date created: 21-JUN-2001
4516   --
4517   --Purpose:
4518   --
4519   --Known limitations/enhancements and/or remarks:
4520   --
4521   --Change History:
4522   --Who         When            What
4523   -------------------------------------------------------------------------------------
4524     --
4525     --  Parameters Description:
4526     --
4527     --  p_person_id                  -> Person ID of the student who wants to enroll or administrator is enrolling.
4528     --  p_load_cal_type              -> Load (Term) or Teaching Calendar Type.
4529     --  p_load_cal_seq_number        -> Load Calendar or Teaching Calendar instance sequence number.
4530     --  p_uoo_id                     -> Unit Section Identifier.
4531     --  p_program_cd                 -> The Primary Program Code or the Program code selected by the student.
4532     --  p_program_version            -> The Primary Program version number or the Program version number selected by the student.
4533     --  p_message                    -> Message from the validation.
4534     --  p_deny_warn                  -> Deny or Warn Indicator based on the setup.
4535     --  p_rule_seq_number            -> Sequence Number of  the Unit level Visa Status Rules.
4536     --
4537     --
4538     --  Cursor to find Calendar Type and Calendar Sequence Number for a Unit Section.
4539     --
4540     CURSOR cur_cal_type_seq_num (
4541              cp_uoo_id                IN NUMBER
4542            ) IS
4543     SELECT   cal_type,
4544              ci_sequence_number,unit_cd,unit_class
4545     FROM     igs_ps_unit_ofr_opt
4546     WHERE    uoo_id = cp_uoo_id;
4547     --
4548     --  Cursor to find Visa Type and Visa Number.
4549     --
4550     CURSOR cur_visa_details (
4551              cp_person_id             IN NUMBER
4552            ) IS
4553       SELECT   visa_type,
4554                visa_number
4555       FROM     igs_pe_visa
4556       WHERE    person_id = cp_person_id;
4557     --
4558     l_cal_type_rec cur_cal_type_seq_num%ROWTYPE;
4559     rec_cur_visa_details cur_visa_details%ROWTYPE;
4560     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
4561     l_message VARCHAR2(30);
4562     l_rule_text VARCHAR2(1000);
4563     l_message_icon VARCHAR2(1);
4564     --
4565   BEGIN
4566     --
4567     --  Check whether Unit Level Visa Status step has been overridden.
4568     --
4569     IF Igs_En_Gen_015.validation_step_is_overridden (
4570          'VISA_STSU',
4571          p_load_cal_type,
4572          p_load_cal_seq_number ,
4573          p_person_id ,
4574          p_uoo_id ,
4575          l_step_override_limit
4576        ) THEN
4577       RETURN TRUE;
4578     END IF;
4579     IF (p_rule_seq_number IS NULL) THEN
4580       RETURN TRUE;
4581     ELSE
4582 
4583 
4584       --
4585       --  If the Rule is defined then get the Teaching Calendar Type and Teaching Calendar Sequence Number.
4586       --
4587       OPEN cur_cal_type_seq_num (p_uoo_id);
4588       FETCH cur_cal_type_seq_num INTO l_cal_type_rec;
4589       CLOSE cur_cal_type_seq_num;
4590       --
4591       --  Select all the Visa records of the student and make a call to the rule for all of them.
4592       --
4593       FOR rec_cur_visa_details IN cur_visa_details (p_person_id) LOOP
4594         --
4595         --  Check whether student has satisfied the Visa Status rule by invoking the rule engine.
4596         --
4597         IF (igs_ru_gen_001.rulp_val_senna (
4598               p_rule_call_name             => 'VISA_STSU',
4599               p_rule_number                => p_rule_seq_number,
4600               p_person_id                  => p_person_id,
4601               p_param_1                    => rec_cur_visa_details.visa_type,
4602               p_param_2                    => p_load_cal_type ,
4603               p_param_3                    => p_load_cal_seq_number      ,
4604               p_param_4                    => l_cal_type_rec.cal_type,
4605               p_param_5                    => l_cal_type_rec.ci_sequence_number,
4606               p_param_6                    => rec_cur_visa_details.visa_number,
4607               p_message                    => l_message
4608             ) = 'true' ) THEN
4609           RETURN TRUE;
4610         END IF;
4611       END LOOP;
4612       --
4613       --  If the student has not satisfied the Visa Status Step rule then return FALSE with a warning/deny message.
4614       --
4615       IF p_deny_warn = 'WARN' THEN
4616           l_message := 'IGS_SS_WARN_VISA_STAT';
4617       ELSE
4618           l_message := 'IGS_SS_DENY_VISA_STAT';
4619       END IF;
4620 
4621 
4622       l_rule_text := NULL;
4623 
4624       IF p_calling_obj NOT IN  ('JOB','SCH_UPD','JOB_FROM_WAITLIST') THEN
4625 
4626         IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
4627          l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(p_rule_seq_number);
4628         END IF;
4629         l_message_icon := substr(p_deny_warn,1,1);
4630         igs_en_drop_units_api.create_ss_warning (
4631                p_person_id => p_person_id,
4632                p_course_cd => p_program_cd,
4633                p_term_cal_type=> p_load_cal_type,
4634                p_term_ci_sequence_number => p_load_cal_seq_number,
4635                p_uoo_id => p_uoo_id,
4636                p_message_for => l_cal_type_rec.unit_cd||'/'||l_cal_type_rec.unit_class ,
4637                p_message_icon=> l_message_icon,
4638                p_message_name => l_message,
4639                p_message_rule_text => l_rule_text,
4640                p_message_tokens => NULL,
4641                p_message_action=> NULL,
4642                p_destination =>NULL,
4643                p_parameters => NULL,
4644                p_step_type => 'UNIT');
4645 
4646 
4647 
4648         ELSE
4649           IF p_message IS NULL THEN
4650             p_message := l_message;
4651           ELSE
4652             p_message := p_message || ';' || l_message;
4653           END IF;
4654       END IF; -- IF p_calling_obj <> 'JOB' THEN
4655     END IF; -- IF (p_rule_seq_number IS NULL) THEN
4656     RETURN FALSE;
4657     --
4658   END eval_visa_unit_lvl;
4659 
4660 
4661   FUNCTION eval_audit_permission (p_person_id             IN NUMBER,
4662                                   p_load_cal_type         IN VARCHAR2,
4663                                   p_load_sequence_number  IN VARCHAR2,
4664                                   p_uoo_id                IN NUMBER,
4665                                   p_course_cd             IN VARCHAR2,
4666                                   p_course_version        IN NUMBER,
4667                                   p_message               IN OUT NOCOPY VARCHAR2,
4668                                   p_deny_warn             IN VARCHAR2
4669                                  ) RETURN BOOLEAN AS
4670 --------------------------------------------------------------------------------
4671   --Created by  : prraj ( Oracle IDC)
4672   --Date created: 23-OCT-2002
4673   --
4674   --Purpose: This function will check whether audit permission exist for the
4675   --         given student and unit section
4676   --
4677   --Known limitations/enhancements and/or remarks:
4678   --
4679   -- Change History:
4680   -- Who         When            What
4681   -- prraj       23-Oct          Created
4682 --------------------------------------------------------------------------------
4683 
4684   -- Cursor to check whether the approved audit permission record
4685   -- exists in the table Igs_En_Spl_Perm for the given student and unit section
4686   CURSOR c_approv_perm IS
4687   SELECT 'x'
4688   FROM Igs_En_Spl_Perm
4689   WHERE student_person_id = p_person_id
4690   AND uoo_id            = p_uoo_id
4691   AND request_type      = 'AUDIT_PERM'
4692   AND approval_status = 'A';
4693 
4694  CURSOR cur_chk_au_allowed IS
4695   SELECT NVL(auditable_ind, 'N')
4696   FROM igs_ps_unit_ofr_opt
4697   WHERE uoo_id = p_uoo_id;
4698 
4699   CURSOR cur_chk_au_perm_req IS
4700   SELECT NVL(audit_permission_ind, 'N')
4701   FROM igs_ps_unit_ofr_opt
4702   WHERE uoo_id = p_uoo_id;
4703 
4704   -- Local variables
4705   l_dummy               VARCHAR2(1);
4706   l_audit_allowed   VARCHAR2(1);
4707   l_au_perm_req   VARCHAR2(1);
4708   l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
4709   BEGIN
4710 
4711       -- Check whether the Audit is allowed in the given unit section
4712       -- If audit is not allowed return error message.
4713       OPEN cur_chk_au_allowed;
4714         FETCH cur_chk_au_allowed INTO l_audit_allowed;
4715       CLOSE cur_chk_au_allowed;
4716 
4717       IF l_audit_allowed = 'N' THEN
4718 
4719          IF p_message IS NULL THEN
4720                  p_message := 'IGS_EN_CANNOT_AUDIT';
4721              ELSE
4722                  p_message := p_message ||';'||'IGS_EN_CANNOT_AUDIT';
4723          END IF;
4724          RETURN FALSE;
4725       END IF;
4726 
4727     -- For Audit TD Bug 2641864
4728     --  Check whether Audit Permission step has been overridden.
4729     --
4730     IF Igs_En_Gen_015.validation_step_is_overridden (
4731          'AUDIT_PERM',
4732          p_load_cal_type,
4733          p_load_sequence_number ,
4734          p_person_id ,
4735          p_uoo_id ,
4736          l_step_override_limit
4737        ) THEN
4738       RETURN TRUE;
4739     END IF;
4740 
4741     -- check whether audit permission required for the given unit section
4742     OPEN cur_chk_au_perm_req;
4743     FETCH cur_chk_au_perm_req INTO l_au_perm_req;
4744     CLOSE cur_chk_au_perm_req;
4745     IF l_au_perm_req = 'N' THEN
4746        RETURN TRUE;
4747     END IF;
4748 
4749       OPEN c_approv_perm;
4750         FETCH c_approv_perm INTO l_dummy;
4751 
4752       IF c_approv_perm%FOUND THEN
4753          CLOSE c_approv_perm;
4754                 RETURN TRUE;
4755       ELSE
4756               --  If the student has not satisfied the Audit Permission Step rule
4757               --  then return FALSE with a warning/deny message.
4758               --
4759               IF p_deny_warn = 'WARN' THEN
4760                   IF p_message IS NULL THEN
4761                     p_message := 'IGS_EN_WARN_AUDIT_PERM';
4762                   ELSE
4763                     p_message := p_message || ';' || 'IGS_EN_WARN_AUDIT_PERM';
4764                   END IF;
4765               ELSE
4766                   IF p_message IS NULL THEN
4767                     p_message := 'IGS_EN_DENY_AUDIT_PERM';
4768                   ELSE
4769                     p_message := p_message || ';' || 'IGS_EN_DENY_AUDIT_PERM';
4770                   END IF;
4771               END IF;
4772       END IF;
4773       CLOSE c_approv_perm;
4774 
4775     RETURN FALSE;
4776 
4777   END eval_audit_permission;
4778 
4779 
4780   FUNCTION eval_student_audit_limit(p_person_id             IN NUMBER,
4781                                     p_load_cal_type         IN VARCHAR2,
4782                                     p_load_sequence_number  IN VARCHAR2,
4783                                     p_uoo_id                IN NUMBER,
4784                                     p_course_cd             IN VARCHAR2,
4785                                     p_course_version        IN NUMBER,
4786                                     p_message               IN OUT NOCOPY VARCHAR2,
4787                                     p_deny_warn             IN VARCHAR2,
4788                                     p_stud_audit_lim        IN NUMBER,
4789                                     p_calling_obj           IN VARCHAR2
4790                                    ) RETURN BOOLEAN AS
4791 ----------------------------------------------------------------------------------------------------------------------------------------------------------------
4792   --Created by  : prraj ( Oracle IDC)
4793   --Date created: 23-OCT-2002
4794   --
4795   --Purpose: This function will check whether the number of audit units attempted
4796   --         by the given student is crossing the limit defined
4797   --
4798   --Known limitations/enhancements and/or remarks:
4799   --
4800   --Change History:
4801   -- Who              When                What
4802   -- prraj             23-Oct                    Created
4803   --myoganat     12-Jun-2003     Cursor c_car_audit_units  and its usage was removed as part of Bug# 2855870 (ENCR032 Build)
4804   --                                             The above cursor was used for evaluation of audit points for a student  under career centric approach
4805   --                                             Now c_prg_audit_units  is used for both program centric and career centric approaches.
4806   ----------------------------------------------------------------------------------------------------------------------------------------------------------------
4807 
4808         -- Program centric
4809         -- Cursor to count the number of audit units for the student
4810         -- under all the program attempts
4811     CURSOR c_prg_audit_units IS
4812     SELECT count(*)
4813     FROM igs_en_su_attempt
4814     WHERE person_id = p_person_id
4815     AND no_assessment_ind = 'Y'
4816     AND ((p_calling_obj <> 'PLAN' AND unit_attempt_status IN ('ENROLLED', 'COMPLETED','INVALID','UNCONFIRM')  )
4817         OR (p_calling_obj = 'PLAN' AND unit_attempt_status IN ('ENROLLED', 'COMPLETED','INVALID','UNCONFIRM','PLANNED') )
4818         OR (unit_attempt_status = 'WAITLISTED' AND FND_PROFILE.VALUE('IGS_EN_VAL_WLST')  ='Y'))
4819     AND (cal_type,ci_sequence_number) IN (SELECT teach_cal_type,teach_ci_sequence_number
4820                                           FROM igs_ca_load_to_teach_v
4821                                           WHERE load_cal_type = p_load_cal_type AND
4822                                                 load_ci_sequence_number = p_load_sequence_number);
4823 
4824     -- Local variables
4825     l_audit_count   NUMBER;
4826     l_step_override_limit igs_en_elgb_ovr_step.step_override_limit%TYPE;
4827 
4828     CURSOR cur_usec_dtls IS
4829     SELECT unit_cd,unit_class
4830     FROM igs_ps_unit_ofr_opt
4831     WHERE uoo_id = p_uoo_id;
4832 
4833     l_usec_dtls cur_usec_dtls%ROWTYPE;
4834     l_message VARCHAR2(30);
4835     l_message_icon VARCHAR2(1);
4836 
4837 
4838   BEGIN
4839 
4840     -- For Audit TD Bug 2641864.
4841     --  Check whether Audit Limit for Student step has been overridden.
4842     --
4843     IF Igs_En_Gen_015.validation_step_is_overridden (
4844          'AUDIT_LIM',
4845          p_load_cal_type,
4846          p_load_sequence_number ,
4847          p_person_id ,
4848          p_uoo_id ,
4849          l_step_override_limit
4850        ) THEN
4851       RETURN TRUE;
4852     END IF;
4853 
4854      OPEN c_prg_audit_units;
4855      FETCH c_prg_audit_units INTO l_audit_count;
4856      CLOSE c_prg_audit_units;
4857 
4858       -- If the student has not satisfied the Audit Limit Step rule then
4859       -- return FALSE with a warning/deny message.
4860 
4861       IF l_audit_count > p_stud_audit_lim OR
4862         ( p_calling_obj ='SCH_UPD' AND l_audit_count >= p_stud_audit_lim ) THEN
4863 
4864           IF p_deny_warn = 'WARN' THEN
4865 
4866                   IF  p_calling_obj = 'JOB' THEN
4867                     l_message  :=  'IGS_EN_WARN_AUDIT_LIM';
4868                   ELSIF p_calling_obj = 'CART' THEN
4869                     l_message := 'IGS_EN_EXCAUDS_TAB_WARN';
4870                   ELSIF  p_calling_obj <> 'SCH_UPD' THEN
4871                     l_message := 'IGS_EN_AUDLIM_TAB_WARN';
4872                   END IF;
4873           ELSE
4874                   IF p_calling_obj = 'SCH_UPD' THEN
4875                     l_message  :=  'IGS_EN_AUDLIM_UPD_DENY';
4876                   ELSIF  p_calling_obj = 'JOB' THEN
4877                     l_message  :=  'IGS_EN_DENY_AUDIT_LIM';
4878                   ELSIF p_calling_obj = 'CART' THEN
4879                     l_message := 'IGS_EN_EXCAUDS_TAB_DENY';
4880                   ELSE
4881                     l_message := 'IGS_EN_AUDLIM_TAB_DENY';
4882                   END IF;
4883           END IF;
4884 
4885           IF p_calling_obj NOT IN  ('JOB','SCH_UPD') THEN
4886 
4887             l_message_icon := substr(p_deny_warn,1,1);
4888             OPEN cur_usec_dtls;
4889             FETCH cur_usec_dtls INTO l_usec_dtls;
4890             CLOSE cur_usec_dtls;
4891             igs_en_drop_units_api.create_ss_warning (
4892                    p_person_id => p_person_id,
4893                    p_course_cd => p_course_cd,
4894                    p_term_cal_type=> p_load_cal_type,
4895                    p_term_ci_sequence_number => p_load_sequence_number,
4896                    p_uoo_id => p_uoo_id,
4897                    p_message_for => l_usec_dtls.unit_cd||'/'||l_usec_dtls.unit_class,
4898                    p_message_icon=> l_message_icon,
4899                    p_message_name => l_message,
4900                    p_message_rule_text => NULL,
4901                    p_message_tokens => NULL,
4902                    p_message_action=> NULL,
4903                    p_destination =>NULL,
4904                    p_parameters => NULL,
4905                    p_step_type => 'UNIT');
4906 
4907               IF l_message_icon <> 'D' THEN
4908                 RETURN TRUE;
4909               END  IF;
4910 
4911            ELSE
4912                IF (p_message IS NULL) THEN
4913                  p_message := l_message;
4914                ELSE
4915                  p_message := p_message || ';' || l_message;
4916                END IF;
4917           END IF;
4918 
4919          RETURN FALSE;
4920 
4921       ELSE
4922          RETURN TRUE;
4923       END IF;
4924 
4925   END eval_student_audit_limit;
4926 
4927  FUNCTION eval_award_prog_only(
4928 		p_person_id             IN NUMBER,
4929         p_person_type       IN VARCHAR2,
4930         p_load_cal_type         IN VARCHAR2,
4931 		p_load_sequence_number  IN VARCHAR2,
4932 		p_uoo_id                IN NUMBER,
4933 		p_course_cd             IN VARCHAR2,
4934 		p_course_version        IN NUMBER,
4935 		p_message               OUT NOCOPY VARCHAR2,
4936 		p_calling_obj			IN			VARCHAR2
4937 	 ) RETURN BOOLEAN AS
4938 
4939     CURSOR cur_pers_sys_type(cp_person_type_code IN VARCHAR2) IS
4940     SELECT system_type
4941     FROM igs_pe_person_types
4942     WHERE person_type_code = cp_person_type_code;
4943 
4944     CURSOR c_admin_ovr (cp_person_type_code IN VARCHAR2) IS
4945     SELECT 'X'
4946     FROM IGS_PE_USR_AVAL
4947     WHERE PERSON_TYPE = cp_person_type_code
4948     AND validation = 'AWD_CRS_ONLY'
4949     AND OVERRIDE_IND = 'Y';
4950 
4951     CURSOR c_prog_award IS
4952     select NVL(AWARD_COURSE_IND,'N')
4953     from igs_ps_type ct, igs_ps_ver cv
4954     where cv.course_cd = p_course_Cd
4955     and cv.version_number = p_course_version
4956     and cv.course_type = ct.course_type;
4957 
4958 
4959     CURSOR c_unit_award IS
4960     SELECT NVL(AWARD_COURSE_ONLY_IND,'N')
4961     FROM igs_ps_unit_ver uv, igs_ps_unit_ofr_opt uoo
4962     where uv.unit_cd = uoo.unit_cd
4963     and uv.version_number = uoo.version_number
4964     and uoo.uoo_id = p_uoo_id;
4965 
4966     l_system_type igs_pe_person_types.system_type%TYPE ;
4967     v_prog_award_ind igs_ps_type.AWARD_COURSE_IND%TYPE;
4968     v_unit_award_ind igs_ps_unit_ver.AWARD_COURSE_ONLY_IND%TYPE;
4969     l_step_override_limit number;
4970     l_dummy VARCHAR2(1);
4971 
4972   BEGIN
4973 
4974     IF p_person_type IS NOT NULL THEN
4975       OPEN cur_pers_sys_type(p_person_type);
4976       FETCH cur_pers_sys_type INTO l_system_type;
4977       CLOSE cur_pers_sys_type;
4978 
4979       IF l_system_type <> 'STUDENT' THEN
4980         OPEN c_admin_ovr(p_person_type);
4981         FETCH c_admin_ovr INTO l_dummy;
4982         IF c_admin_ovr%FOUND THEN
4983           CLOSE c_admin_ovr;
4984           RETURN TRUE;
4985         ELSE
4986           CLOSE c_admin_ovr;
4987         END IF;
4988       END IF;
4989     END IF;
4990 
4991 
4992       --
4993       -- check whether the Forced location step is overridden
4994       --
4995       IF Igs_En_Gen_015.validation_step_is_overridden (
4996            'AWD_CRS_ONLY',
4997            p_load_cal_type,
4998            p_load_sequence_number ,
4999            p_person_id ,
5000            p_uoo_id ,
5001            l_step_override_limit
5002          ) THEN
5003           RETURN TRUE;
5004       END IF;
5005 
5006       OPEN c_prog_award;
5007       FETCH c_prog_award INTO v_prog_award_ind;
5008       CLOSE c_prog_award;
5009 
5010       IF v_prog_award_ind = 'N' THEN
5011         OPEN c_unit_award;
5012         FETCH c_unit_award INTO v_unit_award_ind;
5013         CLOSE c_unit_award;
5014 
5015         IF v_unit_award_ind = 'Y' THEN
5016           p_message := 'IGS_AD_UNITVER_AWARD_PRG';
5017           RETURN FALSE;
5018         ELSE
5019           p_message := NULL;
5020         END IF;
5021       END IF;
5022 
5023       RETURN TRUE;
5024 
5025   END eval_award_prog_only;
5026 
5027 
5028 
5029 END igs_en_elgbl_unit;