DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_EN_ELGBL_PROGRAM

Source


1 PACKAGE BODY igs_en_elgbl_program AS
2 /* $Header: IGSEN79B.pls 120.7 2006/05/02 23:58:10 ckasu ship $ */
3 
4   -------------------------------------------------------------------------------------------
5   --Change History:
6   --Who         When            What
7   -- ckasu       15-Jul-2005     Modified this function inorder to log warning records in to a warnings Table
8   --                             when called from selefservice pages as a part of EN317 SS UI Build bug#4377985
9 
10   --ayedubat   6-JUN-2002       Changed the functions eval_max_cp,eval_min_cp and eval_unit_forced_type
11   --                            to replace the function call Igs_En_Gen_015.get_academic_cal with
12   --                            Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd for the bug Fix: 2381603
13   --svenkata   4-Jun-02         The Attendance Type validation shows message for Attendance Mode .The message
14   --                                          returned by the function eval_unit_forced_type has been modified . Bug # 2396126
15   --prchandr    08-Jan-01       Enh Bug No: 2174101, As the Part of Change in IGSEN18B
16   --                            Passing NULL as parameters  to ENRP_CLC_SUA_EFTSU
17   --                            ENRP_CLC_EFTSU_TOTAL for Key course cd and version number
18   --knaraset 14-May-02          Modified CO_REQ to COREQ in eval_program_steps and also the
19   --                            cursor cur_coo_id in eval_unit_forced_type to include course_cd
20   --                            in WHERE clause.
21   -------------------------------------------------------------------------------------------
22 /******************************************************************
23 Created By        : Vinay Chappidi
24 Date Created By   : 19-Jun-2001
25 Purpose           : When the user tries to finalize the units he has selected
26                     for enrolment, program level validations have to be carried
27                     on before the user is actuall enroled. These function's are
28                     meant for calling from the Self-Service applications
29 Known limitations,
30 enhancements,
31 remarks            :
32 Change History
33 Who      When        What
34 ******************************************************************/
35   -- Declare global variables
36   g_person_type            igs_pe_usr_arg.person_type%TYPE;
37   g_enrollment_category    igs_en_cpd_ext.enrolment_cat%TYPE;
38   g_comm_type              igs_en_cpd_ext.s_student_comm_type%TYPE;
39   g_method_type            igs_en_cpd_ext.enr_method_type%TYPE;
40   g_system_person_type     igs_pe_person_types.system_type%TYPE;
41 
42 FUNCTION eval_program_steps( p_person_id                        NUMBER,
43                              p_person_type                      VARCHAR2,
44                              p_load_calendar_type               VARCHAR2,
45                              p_load_cal_sequence_number         NUMBER,
46                              p_uoo_id                           NUMBER,
47                              p_program_cd                       VARCHAR2,
48                              p_program_version                  VARCHAR2,
49                              p_enrollment_category              VARCHAR2,
50                              p_comm_type                        VARCHAR2,
51                              p_method_type                      VARCHAR2,
52                              p_message                      OUT NOCOPY VARCHAR2,
53                              p_deny_warn                    OUT NOCOPY VARCHAR2,
54                              p_calling_obj                      IN VARCHAR2) RETURN BOOLEAN
55   IS
56   /******************************************************************
57   Created By        : Vinay Chappidi
58   Date Created By   : 19-Jun-2001
59   Purpose           : This function is a wrapper function which inturn calls the other
60                       functions depending on the enrolment step type defined
61   Known limitations,
62   enhancements,
63   remarks            :
64   Change History
65   Who          When          What
66   Nishikant    17OCT2002     the call to the function eval_unit_forced_type has got modified
67                              as part of Enrl Elgbl and Validation Build. Bug#2616692
68  amuthu      27 -MAY-2002   Commented the eval_max_cp and eval_min_Cp and retuning TRUE value (bug 2389462)
69  ayedubat    11-APR-2002    Changed the OPEN cursor statement of cur_program_steps to add an extra 'OR'
70                             condition(eru.s_student_comm_type = 'ALL') for s_student_comm_type as part of the bug fix: 2315245
71   ******************************************************************/
72 
73   -- Ref Cursor is used since the select statement is dependent on the type of the person parameter passed to the function
74   -- Record Type is defined so that the cursor Return Type is of this Record Type
75   TYPE l_program_steps_rec IS RECORD ( s_enrolment_step_type   igs_en_cpd_ext.s_enrolment_step_type%TYPE,
76                                        notification_flag       igs_en_cpd_ext.notification_flag%TYPE,
77                                        s_rule_call_cd          igs_en_cpd_ext.s_rule_call_cd%TYPE,
78                                        rul_sequence_number     igs_en_cpd_ext.rul_sequence_number%TYPE
79                                      );
80   TYPE cur_ref_program_steps IS REF CURSOR  RETURN l_program_steps_rec;
81   cur_program_steps    cur_ref_program_steps;
82   l_cur_program_steps  cur_program_steps%ROWTYPE;
83 
84   -- Cursor for getting the actual system person type for the person type that is passed
85   CURSOR cur_person_types
86   IS
87   SELECT system_type
88   FROM   igs_pe_person_types
89   WHERE  person_type_code = p_person_type;
90 
91   -- cursor rowtype variable
92   l_cur_person_types        cur_person_types%ROWTYPE;
93   l_cur_notification_flag   igs_en_cpd_ext.notification_flag%TYPE;
94 
95   -- variables
96   l_deny_warn    l_cur_program_steps.notification_flag%TYPE;
97   l_return_val   BOOLEAN;
98   l_message      VARCHAR2(2000);
99   l_upd_cp               IGS_PS_UNIT_VER.POINTS_MAX%TYPE;
100 
101   l_deny_prg_steps BOOLEAN;
102   l_warn_prg_steps BOOLEAN;
103   l_calling_obj      VARCHAR2(2000);
104 BEGIN
105   -- Fetch the system person type for the person type passed
106   OPEN  cur_person_types;
107   FETCH cur_person_types INTO l_cur_person_types;
108   CLOSE cur_person_types;
109   -- Assign the package body global variables
110   g_person_type          := p_person_type;
111   g_system_person_type   := l_cur_person_types.system_type;
112   g_enrollment_category  := p_enrollment_category;
113   g_comm_type            := p_comm_type;
114   g_method_type          := p_method_type;
115 
116   IF p_calling_obj = 'REINSTATE' THEN
117    l_calling_obj := 'JOB'; --l_calling_obj is used to pass to the validation procedures as the job
118                            --validations and reinstate validation is same.
119   ELSE
120    l_calling_obj := p_calling_obj;
121   END IF;
122 
123   -- Depending on the person type who has tried to register frame the select statement
124   IF g_system_person_type = 'STUDENT' THEN
125     OPEN cur_program_steps FOR SELECT eru.s_enrolment_step_type,
126                                       eru.notification_flag notification_flag,
127                                       eru.s_rule_call_cd,
128                                       eru.rul_sequence_number
129                                FROM   igs_en_cpd_ext  eru,
130                                       igs_lookups_view lkup
131                                WHERE  eru.s_enrolment_step_type    =  lkup.lookup_code           AND
132                                       eru.enrolment_cat            =  p_enrollment_category      AND
133                                      (eru.s_student_comm_type      =  p_comm_type  OR
134                                       eru.s_student_comm_type      = 'ALL'           )           AND
135                                       eru.enr_method_type          =  p_method_type              AND
136                                       lkup.lookup_type             =  'ENROLMENT_STEP_TYPE_EXT'  AND
137                                       lkup.step_group_type         =  'PROGRAM'
138                                ORDER BY eru.step_order_num;
139   ELSE
140     OPEN cur_program_steps FOR SELECT eru.s_enrolment_step_type,
141                                       DECODE(uact.deny_warn,'WARN','WARN',eru.notification_flag) notification_flag,
142                                       eru.s_rule_call_cd,
143                                       eru.rul_sequence_number
144                                FROM   igs_en_cpd_ext  eru,
145                                       igs_pe_usr_aval_all uact,
146                                       igs_lookups_view lkup
147                                WHERE  eru.s_enrolment_step_type    =  lkup.lookup_code          AND
148                                       eru.enrolment_cat            =  p_enrollment_category     AND
149                                       eru.enr_method_type          =  p_method_type             AND
150                                      (eru.s_student_comm_type      =  p_comm_type OR
151                                       eru.s_student_comm_type      = 'ALL'          )           AND
152                                       lkup.lookup_type             = 'ENROLMENT_STEP_TYPE_EXT'  AND
153                                       lkup.step_group_type         = 'PROGRAM'                  AND
154                                       eru.s_enrolment_step_type    =  uact.validation(+)        AND
155                                       uact.person_type  (+)        =  p_person_type             AND
156                                       NVL(uact. override_ind,'N')  = 'N'
157                                ORDER BY eru.step_order_num;
158   END IF;
159 
160   -- Loop through the records that are fetched into the cursor and do the validations
161   LOOP
162   l_return_val := NULL;
163   l_message := NULL;
164   FETCH cur_program_steps INTO l_cur_program_steps;
165   EXIT WHEN cur_program_steps%NOTFOUND;
166 
167      l_cur_program_steps.notification_flag  := igs_ss_enr_details.get_notification(
168             p_person_type               => p_person_type,
169             p_enrollment_category       => p_enrollment_category ,
170             p_comm_type                 => p_comm_type ,
171             p_enr_method_type           => p_method_type ,
172             p_step_group_type           => 'PROGRAM',
173             p_step_type                 => l_cur_program_steps.s_enrolment_step_type,
174             p_person_id                 => p_person_id,
175             p_message                   => l_message) ;
176 
177     IF l_cur_program_steps.s_enrolment_step_type = 'FMAX_CRDT' THEN
178 
179           l_return_val := TRUE;
180 
181 /*         The max cp validation has to be done before each unit is enrolled
182            where as the co-req validation will have to be done for each unit that
183            was enrolled once after enrolling all the units in the cart.
184            The min cp validationa agian has to be done once for each unit after
185            the units have been enrolled  and the changes posted to the database,
186            but the difference   for min cp valiudation would be that the credit point value parameter
187            must be passed explicitly as 0(ZERO) ( not has null, it must be 0)
188            Hence the call the function eval_max_cp has been removed*/
189 
190     ELSIF l_cur_program_steps.s_enrolment_step_type = 'FMIN_CRDT' THEN
191 
192           l_return_val := TRUE;
193 
194 /*         The min cp validation has to be done before each unit is enrolled
195            where as the co-req validation will have to be done for each unit that
196            was enrolled once after enrolling all the units in the cart.
197            The min cp validationa agian has to be done once for each unit after
198            the units have been enrolled  and the changes posted to the database,
199            but the difference   for min cp valiudation would be that the credit point value parameter
200            must be passed explicitly as 0(ZERO) ( not has null, it must be 0)
201             Hence the call the function eval_min_cp has been removed*/
202 
203     ELSIF l_cur_program_steps.s_enrolment_step_type = 'FATD_TYPE' THEN
204        -- Call the Forced Attendance credit points validations
205 
206          -- Below signature of the call to the function has been modified
207          -- as part of Enrl Elgbl and Validation Build. Bug#2616692
208        l_return_val := igs_en_elgbl_program.eval_unit_forced_type( p_person_id,
209                                                                    p_load_calendar_type,
210                                                                    p_load_cal_sequence_number,
211                                                                    p_uoo_id,
212                                                                    p_program_cd,
213                                                                    p_program_version,
214                                                                    l_message,
215                                                                    l_cur_program_steps.notification_flag,
216                                                                    p_enrollment_category,
217                                                                    p_comm_type,
218                                                                    p_method_type,
219                                                                    l_calling_obj
220                                                                  );
221     ELSIF l_cur_program_steps.s_enrolment_step_type = 'TIME_CFTP' THEN
222        -- Call the Time Conflict validations
223        l_return_val := igs_en_elgbl_unit.eval_time_conflict( p_person_id,
224                                                              p_load_calendar_type,
225                                                              p_load_cal_sequence_number,
226                                                              p_uoo_id,
227                                                              p_program_cd,
228                                                              p_program_version,
229                                                              l_message,
230                                                              l_cur_program_steps.notification_flag,
231                                                              l_calling_obj
232                                                            );
233    ELSIF l_cur_program_steps.s_enrolment_step_type = 'CROSS_LOC' THEN
234        l_return_val :=   igs_en_elgbl_program.EVAL_CROSS_VALIDATION(
235                                           p_person_id                   => p_person_id,
236                                           p_course_cd                   =>  p_program_cd,
237                                           p_program_version             => p_program_version,
238                                           p_uoo_id                      => p_uoo_id,
239                                           p_load_cal_type               =>  p_load_calendar_type,
240                                           p_load_ci_sequence_number     => p_load_cal_sequence_number,
241                                           p_deny_warn                   => l_cur_program_steps.notification_flag ,
242                                           p_upd_cp                      => l_upd_cp ,
243                                           p_eligibility_step_type       => 'CROSS_LOC' ,
244                                           p_message                     => l_message,
245                                           p_calling_obj                 => l_calling_obj);
246 
247    ELSIF l_cur_program_steps.s_enrolment_step_type = 'CROSS_FAC' THEN
248        l_return_val :=   igs_en_elgbl_program.EVAL_CROSS_VALIDATION(
249                                           p_person_id                   => p_person_id,
250                                           p_course_cd                   =>  p_program_cd,
251                                           p_program_version             => p_program_version,
252                                           p_uoo_id                      => p_uoo_id,
253                                           p_load_cal_type               =>  p_load_calendar_type,
254                                           p_load_ci_sequence_number     => p_load_cal_sequence_number,
255                                           p_deny_warn                   => l_cur_program_steps.notification_flag ,
256                                           p_upd_cp                      => l_upd_cp ,
257                                           p_eligibility_step_type       => 'CROSS_FAC' ,
258                                           p_message                     => l_message,
259                                           p_calling_obj                 => l_calling_obj);
260 
261    ELSIF l_cur_program_steps.s_enrolment_step_type = 'CROSS_MOD' THEN
262 
263        l_return_val :=   igs_en_elgbl_program.EVAL_CROSS_VALIDATION(
264                                           p_person_id                   => p_person_id,
265                                           p_course_cd                   =>  p_program_cd,
266                                           p_program_version             => p_program_version,
267                                           p_uoo_id                      => p_uoo_id,
268                                           p_load_cal_type               =>  p_load_calendar_type,
269                                           p_load_ci_sequence_number     => p_load_cal_sequence_number,
270                                           p_deny_warn                   => l_cur_program_steps.notification_flag ,
271                                           p_upd_cp                      => l_upd_cp ,
272                                           p_eligibility_step_type       => 'CROSS_MOD' ,
273                                           p_message                     => l_message ,
274                                           p_calling_obj                 => l_calling_obj);
275 
276     END IF;
277 
278     -- code added to handle the system errors for self service pages
279     IF l_message IS NOT NULL AND p_calling_obj NOT IN ('JOB', 'REINSTATE') THEN
280        p_message := l_message;
281        p_deny_warn := 'DENY';
282        CLOSE cur_program_steps; -- close the cursor before returning FALSE from the function
283        RETURN FALSE;
284     END IF;
285 
286     -- if the function returns FALSE and the notification flag is DENY then the function returns FALSE
287     -- if the function returns FALSE and the notification flag is WARN then the function should continue validating
288     IF (l_return_val = FALSE AND l_cur_program_steps.notification_flag='DENY') THEN
289       l_deny_prg_steps := TRUE;
290       -- set the deny_warn variable value
291       p_deny_warn := l_cur_program_steps.notification_flag;
292       IF l_message IS NOT NULL AND p_calling_obj IN ('JOB', 'REINSTATE') THEN
293         IF p_message IS NULL THEN
294           p_message := l_message;
295         ELSE
296           p_message := p_message||';'||l_message;
297         END IF;
298         CLOSE cur_program_steps; -- close the cursor before returning FALSE from the function
299         RETURN FALSE;
300       END IF;
301     ELSIF ((l_return_val = FALSE AND l_cur_program_steps.notification_flag='WARN') OR l_return_val = TRUE) THEN
302 
303       IF NOT l_return_val THEN
304         p_deny_warn := l_cur_program_steps.notification_flag;
305         l_warn_prg_steps := TRUE;
306       END IF;
307        --If calling object is reinstate and any warnings occured in the validation then reintialising the
308        --the message string so that only errors will be displayed in the schedule page.
309       IF p_calling_obj IN ('REINSTATE') AND p_message IS NOT NULL  THEN
310       p_message:= NULL;
311       END IF;
312 
313       -- Continue Validating without returning from the function
314       IF l_message IS NOT NULL AND p_calling_obj IN ('JOB') THEN
315         -- for avoiding ';' when the p_message parameter is NULL
316         IF p_message IS NULL THEN
317           p_message := l_message;
318         ELSE
319           p_message := p_message||';'||l_message;
320         END IF;
321       END IF;
322     END IF;
323 
324   END LOOP;
325   CLOSE cur_program_steps;
326 
327 
328 
329   l_message := NULL;
330   l_cur_notification_flag := NULL;
331           -- for getting the notification_flag value for step type 'CO_REQ'
332           l_cur_notification_flag  := igs_ss_enr_details.get_notification(
333                     p_person_type               => p_person_type,
334                     p_enrollment_category       => p_enrollment_category ,
335                     p_comm_type                 => p_comm_type ,
336                     p_enr_method_type           => p_method_type ,
337                     p_step_group_type           => 'UNIT',
338                     p_step_type                 => 'COREQ',
339                     p_person_id                 => p_person_id,
340                     p_message                   => l_message) ;
341 
342           IF l_cur_notification_flag IS NOT NULL THEN
343             -- Call the Unit credit points co-requisite validations
344             l_return_val := igs_en_elgbl_unit.eval_coreq( p_person_id,
345                                                           p_load_calendar_type,
346                                                           p_load_cal_sequence_number,
347                                                           p_uoo_id,
348                                                           p_program_cd,
349                                                           p_program_version,
350                                                           l_message, --(In/Out Parameter)
351                                                           l_cur_notification_flag,
352                                                           l_calling_obj
353                                                         );
354 
355                -- code added to handle the system errors for self service pages
356              IF l_message IS NOT NULL AND p_calling_obj NOT IN ('JOB','REINSTATE') THEN
357                p_message := l_message;
358                p_deny_warn := 'DENY';
359                RETURN FALSE;
360              END IF;
361 
362            IF NOT l_return_val THEN
363 
364               IF l_message IS NOT NULL AND p_calling_obj IN ('JOB','REINSTATE') THEN
365                       -- for avoiding ';' when the p_message parameter is NULL
366                       IF p_message IS NULL THEN
367                             p_message := l_message;
368                       ELSE
369                             p_message := p_message||';'||l_message;
370                       END IF;
371               END IF;-- end of l_message IS NOT NULL AND p_calling_obj = 'JOB'
372               p_deny_warn := l_cur_notification_flag;
373 
374               IF p_deny_warn = 'DENY'  THEN
375                  l_deny_prg_steps := TRUE;
376                      IF p_calling_obj IN ('JOB','REINSTATE') THEN
377                         RETURN FALSE;
378                  END IF;
379               ELSE
380                     l_warn_prg_steps := TRUE;
381               END IF;-- end of p_deny_warn = 'DENY' case
382            END IF; -- end of NOT l_return_val if case
383 
384           END IF; -- end of l_cur_notification_flag IS NOT NULL
385 
386 
387   -- evaluate prereq and incompatible unit steps when called from self service pages
388 
389   IF p_calling_obj NOT IN ('JOB','REINSTATE') THEN
390 
391             /*********** prereq check ***********/
392                   l_cur_notification_flag := NULL;
393                   -- for getting the notification_flag value for step type 'CO_REQ'
394                   l_cur_notification_flag  := igs_ss_enr_details.get_notification(
395                             p_person_type               => p_person_type,
396                             p_enrollment_category       => p_enrollment_category ,
397                             p_comm_type                 => p_comm_type ,
398                             p_enr_method_type           => p_method_type ,
399                             p_step_group_type           => 'UNIT',
400                             p_step_type                 => 'PREREQ',
401                             p_person_id                 => p_person_id,
402                             p_message                   => l_message) ;
403 
404                   IF l_cur_notification_flag IS NOT NULL THEN
405                             -- Call the Unit pre-requisite validation
406                             l_message := NULL;
407                             l_return_val := igs_en_elgbl_unit.eval_prereq( p_person_id => p_person_id,
408                                                                         p_load_cal_type=>  p_load_calendar_type,
409                                                                         p_load_sequence_number=>  p_load_cal_sequence_number,
410                                                                         p_uoo_id=>  p_uoo_id,
411                                                                         p_course_cd=>  p_program_cd,
412                                                                         p_course_version=>  p_program_version,
413                                                                         p_message=>  l_message, --(In/Out Parameter)
414                                                                         p_deny_warn=>  l_cur_notification_flag,
415                                                                         p_calling_obj => p_calling_obj
416                                                                         );
417                                 -- system error raised
418                             IF l_message IS NOT NULL  THEN
419                                     p_message := l_message;
420                     p_deny_warn := 'DENY';
421                                 RETURN FALSE;
422                             END IF;
423 
424                             IF NOT l_return_val THEN
425                                     IF l_cur_notification_flag = 'DENY'  THEN
426                                             l_deny_prg_steps := TRUE;
427                                     ELSE
428                                             l_warn_prg_steps := TRUE;
429                                     END IF;
430                              END IF;
431 
432                   END IF;
433 
434          /*********** incompatible check ***********/
435                   l_cur_notification_flag := NULL;
436           l_message := NULL;
437                   -- for getting the notification_flag value for step type 'CO_REQ'
438                   l_cur_notification_flag  := igs_ss_enr_details.get_notification(
439                             p_person_type               => p_person_type,
440                             p_enrollment_category       => p_enrollment_category ,
441                             p_comm_type                 => p_comm_type ,
442                             p_enr_method_type           => p_method_type ,
443                             p_step_group_type           => 'UNIT',
444                             p_step_type                 => 'INCMPT_UNT',
445                             p_person_id                 => p_person_id,
446                             p_message                   => l_message) ;
447 
448                   IF l_cur_notification_flag IS NOT NULL THEN
449                             -- Call the Unit  incompatible validations
450                             l_message := NULL;
451                             l_return_val := igs_en_elgbl_unit.eval_incompatible( p_person_id => p_person_id,
452                                                                          p_load_cal_type =>   p_load_calendar_type,
453                                                                          p_load_sequence_number =>  p_load_cal_sequence_number,
454                                                                          p_uoo_id  =>   p_uoo_id,
455                                                                          p_course_cd =>  p_program_cd,
456                                                                          p_course_version =>   p_program_version,
457                                                                          p_message =>  l_message, --(In/Out Parameter)
458                                                                          p_deny_warn =>  l_cur_notification_flag,
459                                                                          p_calling_obj => p_calling_obj
460                                                                         );
461                                 -- system error raised
462                             IF l_message IS NOT NULL  THEN
463                                   p_message := l_message;
464                   p_deny_warn := 'DENY';
465                               RETURN FALSE;
466                             END IF;
467 
468                             IF NOT l_return_val THEN
469                                     p_deny_warn := l_cur_notification_flag;
470                                     IF p_deny_warn = 'DENY'  THEN
471                                             l_deny_prg_steps := TRUE;
472                                     ELSE
473                                             l_warn_prg_steps := TRUE;
474                                     END IF;
475                              END IF;
476                   END IF;
477 
478   END IF;-- end of p_calling_obj NOT IN ('JOB', 'REINSTATE')
479 
480   -- If any of the validations had failed with a deny,
481 
482   IF l_deny_prg_steps THEN
483      p_deny_warn:= 'DENY';
484      RETURN FALSE;
485   ELSIF l_warn_prg_steps THEN
486      p_deny_warn := 'WARN' ;
487      RETURN TRUE;
488   END IF;-- end of  l_deny_prg_steps IF
489 
490   -- no errors/warnings
491   p_deny_warn := NULL;
492   RETURN TRUE;
493 
494 END eval_program_steps;
495 
496 
497 FUNCTION eval_max_cp ( p_person_id                            NUMBER,
498                        p_load_calendar_type                   VARCHAR2,
499                        p_load_cal_sequence_number             NUMBER,
500                        p_uoo_id                               NUMBER,
501                        p_program_cd                           VARCHAR2,
502                        p_program_version                      VARCHAR2,
503                        p_message                          OUT NOCOPY VARCHAR2,
504                        p_deny_warn                            VARCHAR2,
505                        p_upd_cp                           IN  NUMBER,
506                        p_calling_obj                      IN VARCHAR2
507                      ) RETURN BOOLEAN
508   IS
509   /******************************************************************
510   Created By        : Vinay Chappidi
511   Date Created By   : 19-Jun-2001
512   Purpose           : All the validations for the maximum credit points limit
513                       will be done in this funtion
514   Known limitations,
515   enhancements,
516   remarks            :
517   Change History
518   Who        When         What
519   ckasu       15-Jul-2005     Modified this function inorder to log warning records in to a warnings Table
520                               when called from selefservice pages as a part of EN317 SS UI Build bug#4377985
521 
522   smanglm    03-02-2003   call igs_en_gen_017.enrp_get_enr_method to decide enrollment method type
523   kkillams   05-11-2002   As part of sevis build, Minimum credit point could be defined at person id group level also.
524                           If minimum credit points are not set progression level then check at person id group level,
525                           then check it at term/load level. Bug#2641905
526   Nishikant  17OCT2002    Enrl Elgbl and Validation Build. Bug#2616692
527                           The logic of the code modified such that if the Restricted Enrollment Credit Point is not
528                           defined in Progression then check the Maximum CP is overriden at the load calendar level
529                           If yes then proceed with the value, If not then proceed to check out NOCOPY whether provided at Program level.
530   ayedubat   13-JUN-2002  Added the code to find the enrollment category, commencement type and method type
531                           if the eval_max_cp function is directly called from any other package for the bug:2142663
532   ayedubat   6-JUN-2002   The function call,Igs_En_Gen_015.get_academic_cal is replaced with
533                           Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd to get the academic calendar of the given
534                           load calendar rather than current academic calendar for the bug fix: 2381603
535   knaraset    As part of ENCR013-modified the calculation of Unit Attempts CP
536   myoganat 16-JUN-2003    Bug#  2855870 - Added code to return true in case of an audit attempt. Removed the check before the call to
537                                                  IGS_EN_PRC_LOAD.ENRP_CLC_SUA_LOAD.
538   vkarthik              22-Jul-2004     Added three dummy variables l_audit_cp, l_billing_cp, l_enrolled_cp for all the calls to
539                                                 igs_en_prc_load.enrp_clc_sua_load towards EN308 Billable credit points build Enh#3782329
540   ******************************************************************/
541 
542   -- Ref Cursor is used since the select statement is dependent on the type of the person parameter passed to the function
543   -- Record Type is defined so that the cursor Return Type is of this Record Type
544   TYPE l_program_steps_rec IS RECORD (rul_sequence_number     igs_en_cpd_ext.rul_sequence_number%TYPE);
545   TYPE cur_ref_program_steps IS REF CURSOR  RETURN l_program_steps_rec;   -- Defining the Ref Cursor
546   cur_program_steps    cur_ref_program_steps;
547   l_cur_program_steps  cur_program_steps%ROWTYPE;   -- cursor Row Type variable
548 
549   -- Cursor for getting the Teaching Calendar Type and its Sequence number for the UOO_ID passed
550   CURSOR cur_uoo_id
551   IS
552   SELECT unit_cd, version_number, cal_type, ci_sequence_number
553   FROM   igs_ps_unit_ofr_opt
554   WHERE  uoo_id = p_uoo_id;
555 
556   -- added by ckasu as a part EN317 SS UI  bug#4377985
557 
558   CURSOR c_get_override_enr_cp
559   IS
560   SELECT OVERRIDE_ENROLLED_CP
561   FROM IGS_EN_SU_ATTEMPT
562   WHERE person_id = p_person_id
563   AND   course_cd = p_program_cd
564   AND   uoo_id = p_uoo_id;
565   -- Cursor Row Type Variables
566   l_cur_uoo_id              cur_uoo_id%ROWTYPE;
567 
568   -- Table.Column Type Variables
569   l_override_limit          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
570   l_max_cp_allowed          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
571   l_acad_cal_type           igs_ca_inst.cal_type%TYPE;
572   l_acad_ci_sequence_number igs_ca_inst.sequence_number%TYPE;
573   l_unit_cp                 igs_ps_unit_ver.enrolled_credit_points%TYPE;
574   l_rule_message            igs_ru_item.value%TYPE;
575   l_acad_message            VARCHAR2(30);
576   l_dummy_c                 VARCHAR2(200);
577 
578   -- Variables
579   l_return_value            BOOLEAN;
580   l_total_exist_cp          NUMBER; -- NUMBER as returned from the function
581   l_total_eftsu_cp          NUMBER; -- NUMBER as returned from the function
582   l_credit_points           NUMBER;
583   l_exclude_cp              NUMBER;
584   l_rule_return_value       VARCHAR2(30); -- as returned from Rules function
585   l_acad_start_dt           IGS_CA_INST.start_dt%TYPE;
586   l_acad_end_dt             IGS_CA_INST.end_dt%TYPE;
587   l_alternate_code          IGS_CA_INST.alternate_code%TYPE;
588   l_dummy                   NUMBER;
589   l_unit_incurred_cp        NUMBER;
590   l_effective_date          DATE;
591   l_message                 VARCHAR2(2000);
592   l_return_status           VARCHAR2(10);
593  --dummy variable to pick up audit, billing, enrolled credit points
594  --due to signature change by EN308 Billing credit hours Bug 3782329
595  l_audit_cp             IGS_PS_USEC_CPS.billing_credit_points%TYPE;
596  l_billing_cp           IGS_PS_USEC_CPS.billing_hrs%TYPE;
597  l_enrolled_cp  IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
598 
599  l_message_text            VARCHAR2(2000);
600  l_message_icon            VARCHAR2(1);
601 
602   -- Cursor to get the assessment indicator value.
603   CURSOR c_assessment IS
604     SELECT no_assessment_ind
605      FROM  igs_en_su_attempt
606     WHERE  person_id = p_person_id
607       AND  course_cd = p_program_cd
608       AND  uoo_id = p_uoo_id;
609 
610   l_enrol_cal_type              igs_ca_type.cal_type%TYPE;
611   l_enrol_sequence_number   igs_ca_inst_all.sequence_number%TYPE;
612   l_no_assessment_ind       igs_en_su_attempt.no_assessment_ind%TYPE;
613 
614 
615 BEGIN
616 
617   OPEN c_assessment;
618   FETCH c_assessment INTO l_no_assessment_ind;
619   CLOSE c_assessment;
620 
621     -- Checking if the unit section attempt is an audit attempt, if it is then the function will return TRUE
622   IF l_no_assessment_ind = 'Y' THEN
623        RETURN TRUE;
624  END IF;
625 
626   l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'FMAX_CRDT',
627                                                                    p_load_cal_type         => p_load_calendar_type,
628                                                                    p_load_cal_seq_number   => p_load_cal_sequence_number,
629                                                                    p_person_id             => p_person_id,
630                                                                    p_uoo_id                => p_uoo_id,
631                                                                    p_step_override_limit   => l_override_limit
632                                                                  );
633   IF l_return_value = TRUE THEN
634     IF l_override_limit IS NOT NULL THEN
635       l_max_cp_allowed := l_override_limit;
636     ELSE
637       -- If the override limit is not specified, then the function returns TRUE
638       RETURN TRUE;
639     END IF;
640   END IF;
641 
642   -- get the teaching calendar type and its sequence number for the uoo_id that is passed into the function
643   -- unit code and its version number is also captured
644   OPEN  cur_uoo_id;
645   FETCH cur_uoo_id INTO l_cur_uoo_id;
646   CLOSE cur_uoo_id;
647 
648 
649   l_max_cp_allowed := calc_max_cp (
650                     p_person_id                    => p_person_id ,
651                     p_load_calendar_type           => p_load_calendar_type,
652                     p_load_cal_sequence_number     => p_load_cal_sequence_number,
653                     p_uoo_id                       => p_uoo_id,
654                     p_program_cd                   => p_program_cd,
655                     p_program_version              => p_program_version ,
656                     p_message                      => p_message  ) ;
657 
658   IF l_max_cp_allowed IS NULL AND p_message IS NOT NULL THEN
659     RETURN FALSE ;
660   ELSIF l_max_cp_allowed IS NULL AND p_message IS NULL THEN
661      RETURN TRUE;
662   END IF;
663 
664   -- get the academic calendar of the given Load Calendar
665   --
666   l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
667                         p_cal_type                => p_load_calendar_type,
668                         p_ci_sequence_number      => p_load_cal_sequence_number,
669                         p_acad_cal_type           => l_acad_cal_type,
670                         p_acad_ci_sequence_number => l_acad_ci_sequence_number,
671                         p_acad_ci_start_dt        => l_acad_start_dt,
672                         p_acad_ci_end_dt          => l_acad_end_dt,
673                         p_message_name            => l_acad_message );
674 
675   -- this code handle  the system errors
676   IF l_acad_message IS NOT NULL THEN
677      p_message  := l_acad_message;
678      RETURN  FALSE;
679   END IF; -- end of l_message_name IS NOT NULL THEN
680 
681 
682   -- if no academic calendar is defined for the program,person then the function
683   -- should return FALSE with the message that was thrown from the above procedure
684   IF ( l_acad_cal_type IS NOT NULL AND l_acad_ci_sequence_number IS NOT NULL) THEN
685 
686     -- Get the total existing credit points for the Units he has already enrolled for the same academic period
687     l_total_eftsu_cp := igs_en_prc_load.enrp_clc_eftsu_total( p_person_id             => p_person_id,
688                                                               p_course_cd             => p_program_cd,
689                                                               p_acad_cal_type         => l_acad_cal_type,
690                                                               p_acad_sequence_number  => l_acad_ci_sequence_number,
691                                                               p_load_cal_type         => p_load_calendar_type,
692                                                               p_load_sequence_number  => p_load_cal_sequence_number,
693                                                               p_truncate_ind          => 'N',
694                                                               p_include_research_ind  => 'Y',
695                                                               p_key_course_cd         => NULL,
696                                                               p_key_version_number    => NULL,
697                                                               p_credit_points         => l_total_exist_cp);
698 
699     -- If the function returns 'FALSE' then check if Unit Exclusion Step is defined at the enrolment validation form
700     -- If it is defined as a step then get the rule sequence id associated for the step type 'UNIT_EXCL'
701     -- depending on the person type
702     -- removes IF NOT l_return_value THEN as apart of EN317 SS UI Build
703 
704       -- Findout the enrollment category of enrollment category is not set
705       IF g_enrollment_category IS NULL THEN
706 
707          g_enrollment_category := Igs_En_Gen_003.enrp_get_enr_cat(
708                                     p_person_id             => p_person_id,
709                                     p_course_cd             => p_program_cd,
710                                     p_cal_type              => l_acad_cal_type,
711                                     p_ci_sequence_number    => l_acad_ci_sequence_number,
712                                     p_session_enrolment_cat => NULL,
713                                     p_enrol_cal_type        => l_enrol_cal_type ,
714                                     p_enrol_ci_sequence_number => l_enrol_sequence_number,
715                                     p_commencement_type        => g_comm_type,
716                                     p_enr_categories        => l_dummy_c
717                                    );
718 
719            IF g_comm_type = 'BOTH' THEN
720              /* if both is returned we have to treat it as all */
721              g_comm_type := 'ALL';
722            END IF;
723 
724       END IF;
725 
726       -- Findout the enrollment method type  of enrollment method type is not set
727       IF g_method_type IS NULL THEN
728 
729         -- call igs_en_gen_017.enrp_get_enr_method to decide enrollment method type
730         igs_en_gen_017.enrp_get_enr_method(
731           p_enr_method_type => g_method_type,
732           p_error_message   => l_message,
733           p_ret_status      => l_return_status);
734 
735         -- code added to handle the system errors
736         IF l_return_status = 'FALSE' OR l_message IS NOT NULL THEN
737            p_message  := l_message;
738            RETURN FALSE;
739         END IF; -- l_return_status = 'FALSE' OR l_message_name IS NOT NULL THEN
740 
741       END IF;
742 
743       IF g_system_person_type = 'STUDENT' THEN
744         OPEN cur_program_steps FOR SELECT eru.rul_sequence_number rul_sequence_number
745                                    FROM   igs_en_cpd_ext  eru,
746                                           igs_lookups_view lkup
747                                    WHERE  eru.s_enrolment_step_type    =  lkup.lookup_code          AND
748                                           eru.s_enrolment_step_type    = 'UNIT_EXCL'                AND
749                                           eru.enrolment_cat            =  g_enrollment_category     AND
750                                           (eru.s_student_comm_type      =  g_comm_type
751                                            OR eru.s_student_comm_type   =  'ALL' )                  AND
752                                           eru.enr_method_type          =  g_method_type         AND
753                                           lkup.lookup_type             = 'ENROLMENT_STEP_TYPE_EXT'  AND
754                                           lkup.step_group_type         = 'PROGRAM'
755                                    ORDER BY eru.step_order_num;
756       ELSE
757         OPEN cur_program_steps FOR SELECT eru.rul_sequence_number rul_sequence_number
758                                    FROM   igs_en_cpd_ext  eru,
759                                           igs_pe_usr_aval_all uact,
760                                           igs_lookups_view lkup
761                                    WHERE  eru.s_enrolment_step_type    = lkup.lookup_code AND
762                                           lkup.lookup_type             = 'ENROLMENT_STEP_TYPE_EXT'  AND
763                                           eru.s_enrolment_step_type    = 'UNIT_EXCL'                AND
764                                           eru.enrolment_cat            =  g_enrollment_category     AND
765                                           eru.enr_method_type          =  g_method_type         AND
766                                           (eru.s_student_comm_type      = g_comm_type
767                                           OR eru.s_student_comm_type   =  'ALL' )                   AND
768                                           lkup.step_group_type         = 'PROGRAM'                  AND
769                                           eru.s_enrolment_step_type    =  uact.validation(+)              AND
770                                           uact.person_type  (+)        =  g_person_type             AND
771                                           NVL(uact. override_ind,'N')  = 'N'
772                                    ORDER BY eru.step_order_num;
773       END IF;
774       FETCH cur_program_steps INTO l_cur_program_steps;
775       CLOSE cur_program_steps;
776 
777       -- If there is a rule sequence id associated for the step type 'UNIT_EXCL' then get the total excluded credit points
778       IF l_cur_program_steps.rul_sequence_number IS NOT NULL THEN
779         BEGIN
780           l_rule_return_value := igs_ru_gen_001.rulp_val_senna( p_rule_call_name     => 'UNIT_EXCL',
781                                                                 p_rule_number        => l_cur_program_steps.rul_sequence_number,
782                                                                 p_person_id          => p_person_id,
783                                                                 p_course_cd          => p_program_cd,
784                                                                 p_course_version     => p_program_version,
785                                                                 p_unit_cd            => l_cur_uoo_id.unit_cd,
786                                                                 p_unit_version       => l_cur_uoo_id.version_number,
787                                                                 p_cal_type           => l_cur_uoo_id.cal_type,
788                                                                 p_ci_sequence_number => l_cur_uoo_id.ci_sequence_number,
789                                                                 p_message            => l_rule_message ,
790                                                                 p_param_1            => p_program_cd,
791                                                                 p_param_2            => p_program_version
792                                                               );
793           -- If the function returns 'true' then OUT NOCOPY parameter p_message will have the total exclusion credit points
794           IF l_rule_return_value = 'true' THEN
795             l_exclude_cp := TO_NUMBER(l_rule_message);
796           ELSE
797             l_exclude_cp := 0;
798           END IF;
799         EXCEPTION
800           WHEN OTHERS THEN
801             l_exclude_cp := 0;
802         END;
803       END IF;
804 
805   -- added by ckasu as a part of EN317 SS UI changes
806   IF p_calling_obj <> 'JOB' THEN
807       OPEN  c_get_override_enr_cp;
808       FETCH c_get_override_enr_cp INTO l_unit_cp;
809       CLOSE c_get_override_enr_cp;
810   END IF;
811 -- Added as part of ENCR013
812 -- Get the Approved credit points defined in Override Steps Table for the Unit Enrolling.
813   l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'VAR_CREDIT_APPROVAL',
814                                                                    p_load_cal_type         => p_load_calendar_type,
815                                                                    p_load_cal_seq_number   => p_load_cal_sequence_number,
816                                                                    p_person_id             => p_person_id,
817                                                                    p_uoo_id                => p_uoo_id,
818                                                                    p_step_override_limit   => l_override_limit
819                                                                  );
820 
821   IF l_return_value = TRUE THEN
822     IF l_override_limit IS NOT NULL THEN
823       l_unit_cp := l_override_limit;
824     END IF;
825   END IF;
826 
827 
828       -- Calling below method to get Incurred CP for the Unit, from Override Limit If defined, otherwise from Enrolled CP of Unit.
829       -- Added this code as part of bug 2401891
830       l_unit_incurred_cp := Igs_En_Prc_Load.enrp_clc_sua_load(
831                                                       p_unit_cd => l_cur_uoo_id.unit_cd,
832                                                       p_version_number => l_cur_uoo_id.version_number,
833                                                       p_cal_type => l_cur_uoo_id.cal_type,
834                                                       p_ci_sequence_number => l_cur_uoo_id.ci_sequence_number,
835                                                       p_load_cal_type => p_load_calendar_type,
836                                                       p_load_ci_sequence_number => p_load_cal_sequence_number,
837                                                       p_override_enrolled_cp => l_unit_cp,
838                                                       p_override_eftsu => NULL,
839                                                       p_return_eftsu => l_dummy,
840                                                       p_uoo_id =>p_uoo_id,
841                                                       -- anilk, Audit special fee build
842                                                       p_include_as_audit => 'N',
843                                                       p_audit_cp => l_audit_cp,
844                                                       p_billing_cp => l_billing_cp,
845                                                       p_enrolled_cp => l_enrolled_cp);
846 
847 
848     -- Calculate the total credit points
849     l_credit_points := NVL(l_total_exist_cp,0) + NVL(p_upd_cp,NVL(l_unit_incurred_cp,0)) - NVL(l_exclude_cp,0);
850     -- If the total credit points calculated are less than or equal to the maximum credit points allowed
851     -- then the function returns TRUE
852 
853     IF l_credit_points <=  l_max_cp_allowed THEN
854       RETURN TRUE;
855 --added by ckasu as a part of EN317 build
856     ELSE
857       IF p_deny_warn = 'WARN' THEN
858              l_message := 'IGS_SS_WARN_MAX_CP_REACHED';
859       ELSE
860 
861              IF p_calling_obj = 'SCH_UPD' THEN
862                 l_message := 'IGS_EN_MAXCP_UPD_DENY'||'*'||l_max_cp_allowed;
863              ELSE
864                 l_message := 'IGS_SS_DENY_MAX_CP_REACHED';
865              END IF;-- end of p_calling_obj = 'SCH_UPD'  if then
866 
867       END IF; -- end of p_deny_warn = 'WARN' if then
868 
869       IF p_calling_obj NOT IN ('JOB','SCH_UPD') THEN
870 
871           IF p_deny_warn = 'WARN' THEN
872              l_message := 'IGS_EN_MAXCP_TAB_WARN';
873           ELSE
874              l_message := 'IGS_EN_MAXCP_TAB_DENY';
875           END IF; -- end of p_deny_warn = 'WARN' THEN
876 
877           -- create a warnings record
878           l_message_icon := substr(p_deny_warn,1,1);
879           IGS_EN_DROP_UNITS_API.create_ss_warning(p_person_id                    => p_person_id,
880                                                   p_course_cd                    => p_program_cd,
881                                                   p_term_cal_type                => p_load_calendar_type,
882                                                   p_term_ci_sequence_number      => p_load_cal_sequence_number,
883                                                   p_uoo_id                       => p_uoo_id,
884                                                   p_message_for                  => igs_ss_enroll_pkg.enrf_get_lookup_meaning('FMAX_CRDT','ENROLMENT_STEP_TYPE_EXT'),
885                                                   p_message_icon                 => l_message_icon,
886                                                   p_message_name                 => l_message,
887                                                   p_message_rule_text            => NULL,
888                                                   p_message_tokens               => 'UNIT_CD:'||l_max_cp_allowed||';',
889                                                   p_message_action               => NULL,
890                                                   p_destination                  => NULL,
891                                                   p_parameters                   => NULL,
892                                                   p_step_type                    => 'PROGRAM');
893       ELSE
894          p_message :=  l_message;
895       END IF; -- end of p_calling_obj NOT IN ('JOB','SCH_UPD') if then
896 
897     END IF; -- end of l_credit_points <=  l_max_cp_allowed
898 
899   END IF; -- end of ( l_acad_cal_type IS NOT NULL AND l_acad_ci_sequence_number IS NOT NULL)  if then
900 
901   IF l_acad_message IS NOT NULL THEN
902      p_message := l_acad_message;
903   END IF; -- end of l_acad_message IS NOTNULL THEN
904   RETURN FALSE;
905 
906 END eval_max_cp;
907 
908 FUNCTION eval_min_cp( p_person_id                             NUMBER,
909                        p_load_calendar_type                   VARCHAR2,
910                        p_load_cal_sequence_number             NUMBER,
911                        p_uoo_id                               NUMBER,
912                        p_program_cd                           VARCHAR2,
913                        p_program_version                      VARCHAR2,
914                        p_message                          OUT NOCOPY VARCHAR2,
915                        p_deny_warn                            VARCHAR2,
916                        p_credit_points                 IN OUT NOCOPY NUMBER,
917                        p_enrollment_category           IN     VARCHAR2,
918                        p_comm_type                     IN     VARCHAR2,
919                        p_method_type                   IN     VARCHAR2,
920                        p_min_credit_point              IN OUT NOCOPY NUMBER,
921                        p_calling_obj                      IN VARCHAR2
922                      ) RETURN BOOLEAN
923   IS
924   /******************************************************************
925   Created By        : Vinay Chappidi
926   Date Created By   : 19-Jun-2001
927   Purpose           : All the validations for the minimum credit points limit
928                       will be done in this funtion
929   Known limitations,
930   enhancements,
931   remarks           :
932   Change History
933   Who        When        What
934   ckasu       15-Jul-2005     Modified this function inorder to log warning records in to a warnings Table
935                               when called from selefservice pages as a part of EN317 SS UI Build bug#4377985
936 
937   kkillams   05-11-2002  As part of sevis build, Minimum credit point could be defined at person id group level also.
938                          If minimum credit points are not set progression level then check at person id group level,
939                          then check it at term/load level. Bug#2641905
940   Nishikant  17OCT2002   Enrl Elgbl and Validation Build. Bug#2616692
941                          The logic of the code modified such that if the Restricted Enrollment Credit Point is not
942                          defined in Progression then check the Minimum CP is overriden at the load calendar level
943                          If yes then proceed with the value, If not then proceed to check out NOCOPY whether provided at
944                          Program level. Also the l_deny_warn variable has been set to DENY or WARN according to the
945                          setup of The Minimum Credit Point Validation in the Enrollment Catagory Validation Setup form.
946   ayedubat   6-JUN-2002  Replaced the function call,Igs_En_Gen_015.get_academic_cal with
947                          Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd to get the academic calendar of the given
948                          load calendar rather than current academic calendar for the bug fix: 2381603
949   msrinivi    removed the Exclusion functionality in eval_min_cp
950   knaraset    As part of ENCR013-modified the calculation of Unit Attempts CP
951   myoganat 16-JUN-2003   Bug#  2855870 - Added code to return TRUE incase of an Audit Attempt. Removed the check before the call to
952                                                  IGS_EN_PRC_LOAD.ENRP_CLC_SUA_LOAD.
953   vkarthik              22-Jul-2004     Added three dummy variables l_audit_cp, l_billing_cp, l_enrolled_cp for all the calls to
954                                                 igs_en_prc_load.enrp_clc_sua_load towards EN308 Billable credit points build Enh#3782329
955   ******************************************************************/
956 
957   -- Cursor for getting the Teaching Calendar Type and its Sequence number for the UOO_ID passed
958   CURSOR cur_uoo_id
959   IS
960   SELECT unit_cd, version_number, cal_type, ci_sequence_number
961   FROM   igs_ps_unit_ofr_opt
962   WHERE  uoo_id = p_uoo_id;
963 
964   CURSOR cur_min_cp_config IS
965   SELECT ecpd.config_min_cp_valdn, ecpd.enforce_date_alias
966   FROM   igs_en_cat_prc_dtl ecpd, igs_en_cpd_ext ecpe
967   WHERE  ecpe.s_enrolment_step_type IN ( 'FATD_TYPE' ,  'FMIN_CRDT' ) AND
968          ecpe.enrolment_cat         = p_enrollment_category AND
969          ecpe.enr_method_type       = p_method_type AND
970          (ecpe.s_student_comm_type   = p_comm_type
971          OR ecpe.s_student_comm_type   =  'ALL' ) AND
972          ecpd.enrolment_cat         = ecpe.enrolment_cat       AND
973          ecpd.enr_method_type       = ecpe.enr_method_type     AND
974          ecpd.s_student_comm_type   = ecpe.s_student_comm_type AND
975          ecpd.config_min_cp_valdn   <> 'NONE';
976 
977   CURSOR cur_get_alias_val( l_p_date_alias igs_ca_da_inst_v.dt_alias%TYPE ) IS
978   SELECT MIN(di.alias_val)
979   FROM   igs_ca_da_inst_v di
980   WHERE  di.cal_type           = p_load_calendar_type AND
981          di.ci_sequence_number = p_load_cal_sequence_number AND
982          di.dt_alias           = l_p_date_alias ;
983 
984   -- Cursor to get the assessment indicator value.
985   CURSOR c_assessment IS
986     SELECT no_assessment_ind
987      FROM  igs_en_su_attempt
988     WHERE  person_id = p_person_id
989       AND  course_cd = p_program_cd
990       AND  uoo_id = p_uoo_id;
991 
992 
993   -- Cursor Row Type Variables
994   l_cur_uoo_id              cur_uoo_id%ROWTYPE;
995 
996 
997   -- Below local variable added as part of Enrl Elgbl and Validation Build. Bug#2616692
998   l_min_cp_config           cur_min_cp_config%ROWTYPE;
999 
1000   -- Table.Column Type Variables
1001   l_override_limit          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
1002   l_min_cp_allowed          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
1003   l_acad_cal_type           igs_ca_inst.cal_type%TYPE;
1004   l_acad_ci_sequence_number igs_ca_inst.sequence_number%TYPE;
1005   l_unit_cp                 igs_ps_unit_ver.enrolled_credit_points%TYPE;
1006   l_rule_message            igs_ru_item.value%TYPE;
1007   -- Below two local variables added as part of Enrl Elgbl and Validation Build. Bug#2616692
1008 
1009   l_get_alias_val           igs_ca_da_inst_v.alias_val%TYPE;
1010 
1011   -- Variables
1012   l_return_value            BOOLEAN;
1013   l_effective_date          DATE;
1014   l_total_exist_cp          NUMBER; -- As defined in the function
1015   l_total_eftsu_cp          NUMBER; -- As defined in the function
1016   l_credit_points           NUMBER; -- clarify
1017   l_rule_return_value       VARCHAR2(30); -- as returned from Rules function
1018   l_acad_message            VARCHAR2(30); -- as returned from Get Academic Calendar procedure
1019   l_acad_start_dt           IGS_CA_INST.start_dt%TYPE;
1020   l_acad_end_dt             IGS_CA_INST.end_dt%TYPE;
1021   l_alternate_code          IGS_CA_INST.alternate_code%TYPE;
1022   l_dummy                   NUMBER;
1023   l_unit_incurred_cp        NUMBER;
1024   -- Below local variable added as part of Enrl Elgbl and Validation Build. Bug#2616692
1025   l_deny_warn               igs_en_cpd_ext_v.notification_flag%TYPE;
1026   l_no_assessment_ind       igs_en_su_attempt.no_assessment_ind%TYPE;
1027   --dummy variable to pick up audit, billing, enrolled credit points
1028   --due to signature change by EN308 Billing credit hours Bug 3782329
1029   l_audit_cp            IGS_PS_USEC_CPS.billing_credit_points%TYPE;
1030   l_billing_cp          IGS_PS_USEC_CPS.billing_hrs%TYPE;
1031   l_enrolled_cp IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
1032 
1033   l_message                 VARCHAR2(2000);
1034   l_message_text            VARCHAR2(2000);
1035   l_message_icon            VARCHAR2(1);
1036 
1037 BEGIN
1038 
1039   OPEN c_assessment;
1040   FETCH c_assessment INTO l_no_assessment_ind;
1041   CLOSE c_assessment;
1042 
1043     -- Checking if the unit section attempt is an audit attempt, if it is then the function will return TRUE
1044   IF l_no_assessment_ind = 'Y' THEN
1045       RETURN TRUE;
1046   END IF;
1047 
1048   l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'FMIN_CRDT',
1049                                                                    p_load_cal_type         => p_load_calendar_type,
1050                                                                    p_load_cal_seq_number   => p_load_cal_sequence_number,
1051                                                                    p_person_id             => p_person_id,
1052                                                                    p_uoo_id                => p_uoo_id,
1053                                                                    p_step_override_limit   => l_override_limit
1054                                                                  );
1055 
1056   IF l_return_value = TRUE THEN
1057     IF l_override_limit IS NOT NULL THEN
1058       l_min_cp_allowed := l_override_limit;
1059     ELSE
1060        RETURN TRUE;
1061     END IF;
1062   END IF;
1063 
1064 
1065   -- get the teaching calendar type and its sequence number for the uoo_id that is passed into the function
1066   -- unit code and its version number is also captured
1067   OPEN  cur_uoo_id;
1068   FETCH cur_uoo_id INTO l_cur_uoo_id;
1069   CLOSE cur_uoo_id;
1070 
1071   l_min_cp_allowed := calc_min_cp (
1072                     p_person_id                    => p_person_id ,
1073                     p_load_calendar_type           => p_load_calendar_type,
1074                     p_load_cal_sequence_number     => p_load_cal_sequence_number,
1075                     p_uoo_id                       => p_uoo_id,
1076                     p_program_cd                   => p_program_cd,
1077                     p_program_version              => p_program_version ,
1078                     p_message                      => p_message  ) ;
1079 
1080   IF l_min_cp_allowed IS NULL AND p_message IS NOT NULL THEN
1081     RETURN FALSE ;
1082   ELSIF l_min_cp_allowed IS NULL AND p_message IS NULL THEN
1083      RETURN TRUE;
1084   END IF;
1085 
1086      -- get the academic calendar of the gievn load calendar
1087      -- clarify if this function returns a value ,
1088      -- if not there is a place in the function which returns a value, confirm the function name
1089      l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
1090                            p_cal_type                => p_load_calendar_type,
1091                            p_ci_sequence_number      => p_load_cal_sequence_number,
1092                            p_acad_cal_type           => l_acad_cal_type,
1093                            p_acad_ci_sequence_number => l_acad_ci_sequence_number,
1094                            p_acad_ci_start_dt        => l_acad_start_dt,
1095                            p_acad_ci_end_dt          => l_acad_end_dt,
1096                            p_message_name            => l_acad_message );
1097 
1098       -- this code handle  the system errors
1099       IF l_acad_message IS NOT NULL THEN
1100          p_message  := l_acad_message;
1101          RETURN  FALSE;
1102       END IF; -- end of l_message_name IS NOT NULL THEN
1103 
1104 
1105      -- if no academic calendar is defined for the program,person then the function
1106      -- should return FALSE
1107      IF ( l_acad_cal_type IS NOT NULL AND l_acad_ci_sequence_number IS NOT NULL) THEN
1108          -- Get the total existing credit points for the Units he has already enrolled for the same academic period
1109          l_total_eftsu_cp := igs_en_prc_load.enrp_clc_eftsu_total( p_person_id             => p_person_id,
1110                                                                  p_course_cd             => p_program_cd,
1111                                                                  p_acad_cal_type         => l_acad_cal_type,
1112                                                                  p_acad_sequence_number  => l_acad_ci_sequence_number,
1113                                                                  p_load_cal_type         => p_load_calendar_type,
1114                                                                  p_load_sequence_number  => p_load_cal_sequence_number,
1115                                                                  p_truncate_ind          => 'N',
1116                                                                  p_include_research_ind  => 'Y',
1117                                                                  p_key_course_cd         => NULL,
1118                                                                  p_key_version_number    => NULL,
1119                                                                  p_credit_points         => l_total_exist_cp
1120                                                                );
1121 
1122          -- Added As part of ENCR013
1123          -- Get the Approved credit points defined in Override Steps Table for the Unit Enrolling.
1124          l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'VAR_CREDIT_APPROVAL',
1125                                                                       p_load_cal_type         => p_load_calendar_type,
1126                                                                       p_load_cal_seq_number   => p_load_cal_sequence_number,
1127                                                                       p_person_id             => p_person_id,
1128                                                                       p_uoo_id                => p_uoo_id,
1129                                                                       p_step_override_limit   => l_override_limit
1130                                                                     );
1131 
1132          IF l_return_value = TRUE THEN
1133             IF l_override_limit IS NOT NULL THEN
1134                l_unit_cp := l_override_limit;
1135             END IF;
1136          END IF;
1137 
1138 
1139              -- Calling below method to get Incurred CP for the Unit, from Override Limit If defined, otherwise from Enrolled CP of Unit.
1140              -- Added this code as part of bug 2401891
1141              l_unit_incurred_cp := Igs_En_Prc_Load.enrp_clc_sua_load(
1142                                                          p_unit_cd => l_cur_uoo_id.unit_cd,
1143                                                          p_version_number => l_cur_uoo_id.version_number,
1144                                                          p_cal_type => l_cur_uoo_id.cal_type,
1145                                                          p_ci_sequence_number => l_cur_uoo_id.ci_sequence_number,
1146                                                          p_load_cal_type => p_load_calendar_type,
1147                                                          p_load_ci_sequence_number => p_load_cal_sequence_number,
1148                                                          p_override_enrolled_cp => l_unit_cp,
1149                                                          p_override_eftsu => NULL,
1150                                                          p_return_eftsu => l_dummy,
1151                                                          p_uoo_id=>p_uoo_id,
1152                                                          -- anilk, Audit special fee build
1153                                                          p_include_as_audit => 'N',
1154                                                          p_audit_cp => l_audit_cp,
1155                                                          p_billing_cp => l_billing_cp,
1156                                                          p_enrolled_cp => l_enrolled_cp);
1157 
1158          -- Calculate the total credit points
1159          -- msrinivi Added this chnge to check if cp parameter is null,else take l_unit_cp
1160          l_credit_points := NVL(l_total_exist_cp,0) + NVL(p_credit_points,NVL(l_unit_incurred_cp,0)) ;
1161 
1162          -- If the total credit points calculated are greater than the minimum credit points allowed
1163          -- and its not called from the eval_unit_forced_type function then the function returns TRUE
1164 
1165          IF l_credit_points >=  l_min_cp_allowed THEN
1166              p_credit_points := l_credit_points;
1167              p_min_credit_point := l_min_cp_allowed;
1168              RETURN TRUE;
1169          END IF;
1170 
1171      END IF;   -- IF ( l_acad_cal_type IS NOT NULL AND l_acad_ci_sequence_number IS NOT NULL) THEN
1172 
1173      l_deny_warn := p_deny_warn ;
1174     --Open the cursor defined to find out NOCOPY whether Minimum CP overriden at term level
1175     OPEN cur_min_cp_config;
1176     FETCH cur_min_cp_config INTO l_min_cp_config;
1177     -- If the Min CP is not Overriden at Load Calendar level OR
1178     -- The Minimum Credit Point Validation is set as the default value 'Every Time' in the Enrollment Catagory
1179     -- Validation Setup form OR p_deny_warm parameter contains the value DENY_QUERY or WARN_QUERY, which means
1180     -- the function has been invoked from the form 'Minimum Credit Point Query' then proceed
1181 
1182     IF cur_min_cp_config%NOTFOUND
1183        OR p_deny_warn IN ('DENY_QUERY', 'WARN_QUERY') THEN --(proceed with the existing functionality)
1184         CLOSE cur_min_cp_config;
1185         -- As the parameter p_credit_points made as IN/OUT to have the value of the valriable l_credit_points
1186         p_credit_points := l_credit_points; -- Totall enrolled Credit Points are returned.
1187         -- If p_deny_warn is DENY_QUERY then make it DENY and If it is WARN_QUERY make it WARN.
1188         IF p_deny_warn IN ('DENY_QUERY', 'WARN_QUERY') THEN
1189             l_deny_warn := SUBSTR(p_deny_warn, 1, 4);
1190         END IF;
1191 
1192     ELSE  -- Else part of IF cur_min_cp_config%NOTFOUND OR l_min_cp_config.config_min_cp_valdn = 'NONE'.
1193         CLOSE cur_min_cp_config;
1194        -- If the Minimum Credit Point has been overirden at Load calendar level AND the The Minimum Credit
1195        -- Point Validation is set as the other than default value 'Every Time' in the Enrollment Catagory Validation Setup form
1196        -- AND this function is not invoked from the form 'Minimum Credit Point Query' then Proceed
1197 
1198        -- If the Minimum Credit Point Validation is configured as 'Enforce When First Reached Minimum Credit Point'
1199        IF l_min_cp_config.config_min_cp_valdn = 'MINCPREACH' THEN
1200           IF p_min_credit_point IS NOT NULL THEN
1201              l_credit_points := p_min_credit_point;
1202           END IF;
1203           IF l_credit_points >= l_min_cp_allowed THEN
1204              l_deny_warn := 'DENY';
1205           ELSE
1206              l_deny_warn := 'WARN';
1207           END IF;
1208 
1209        -- If the Minimum Credit Point Validation is set as 'Enforce by Date Only'
1210        ELSIF l_min_cp_config.config_min_cp_valdn = 'DTALIASRCH' THEN  --Else part of 'IF l_min_cp_config.config_min_cp_valdn = 'MINCPREACH' THEN'
1211 
1212           --open the cursor cur_get_alias_val which will fetch the minimum of the Alias value for the date alias provided
1213           OPEN cur_get_alias_val( l_min_cp_config.enforce_date_alias);
1214           FETCH cur_get_alias_val INTO l_get_alias_val;
1215           CLOSE cur_get_alias_val;
1216 
1217           --If the date alias defined for the Calendar Instance then
1218           IF l_get_alias_val IS NOT NULL THEN
1219              --If the alias value has been reached then p_deny_warn is DENY else WARN
1220              IF TRUNC(l_get_alias_val) <= TRUNC(SYSDATE) THEN
1221                 l_deny_warn := 'DENY';
1222              ELSE
1223                 l_deny_warn := 'WARN';
1224              END IF;
1225           -- If the Date alias is not defined for the Calendar Instance then p_deny_wan is WARN
1226           ELSE
1227              RETURN TRUE;
1228           END IF;
1229 
1230        END IF;   --  IF l_min_cp_config.config_min_cp_valdn = 'MINCPREACH' THEN
1231     END IF;   --cur_min_cp_config%NOTFOUND OR l_min_cp_config.config_min_cp_valdn = 'NONE'
1232 
1233  IF l_deny_warn = 'WARN' THEN
1234 
1235     IF p_calling_obj = 'DROP' THEN
1236        l_message := 'IGS_SS_EN_MINIMUM_CP_WARN';
1237     ELSIF p_calling_obj = 'JOB' THEN
1238        l_message := 'IGS_SS_WARN_MIN_CP_REACHED';
1239     END IF; -- end of p_calling_obj = 'SCH_UPD'
1240 
1241  ELSE
1242 
1243     IF p_calling_obj = 'SCH_UPD' THEN
1244        l_message := 'IGS_EN_MINCP_UPD_DENY'||'*'||l_min_cp_allowed;
1245     ELSIF p_calling_obj = 'DROP' THEN
1246        l_message := 'IGS_SS_EN_MINIMUM_CP_DENY';
1247     ELSIF p_calling_obj = 'JOB' THEN
1248        l_message := 'IGS_SS_DENY_MIN_CP_REACHED';
1249     END IF; -- end of p_calling_obj = 'SCH_UPD'
1250 
1251 
1252  END IF; -- end of l_deny_warn = 'WARN' IF THEN
1253 
1254  IF p_calling_obj NOT IN ('JOB','DROP','SCH_UPD') THEN
1255 
1256      IF p_deny_warn = 'WARN' THEN
1257         l_message := 'IGS_EN_MINCP_TAB_WARN';
1258      ELSE
1259         l_message := 'IGS_EN_MINCP_TAB_DENY';
1260      END IF; -- end of p_deny_warn = 'WARN' THEN
1261 
1262      l_message_icon := substr(l_deny_warn,1,1);
1263       -- create a warnings record
1264       IGS_EN_DROP_UNITS_API.create_ss_warning(p_person_id                => p_person_id,
1265                                               p_course_cd                => p_program_cd,
1266                                               p_term_cal_type            => p_load_calendar_type,
1267                                               p_term_ci_sequence_number  => p_load_cal_sequence_number,
1268                                               p_uoo_id                   => p_uoo_id,
1269                                               p_message_for              => igs_ss_enroll_pkg.enrf_get_lookup_meaning('FMIN_CRDT','ENROLMENT_STEP_TYPE_EXT'),
1270                                               p_message_icon             => l_message_icon,
1271                                               p_message_name             => l_message,
1272                                               p_message_rule_text        => NULL,
1273                                               p_message_tokens           => 'UNIT_CD:'||l_min_cp_allowed||';',
1274                                               p_message_action           => NULL,
1275                                               p_destination              => NULL,
1276                                               p_parameters               => NULL,
1277                                               p_step_type                => 'PROGRAM');
1278  ELSE
1279      p_message :=  l_message;
1280  END IF; -- end of p_calling_obj NOT IN ('JOB','SCH_UPD') if then
1281 
1282 
1283   p_credit_points := l_credit_points;
1284   p_min_credit_point := l_min_cp_allowed;
1285   RETURN FALSE;
1286 
1287 END eval_min_cp;
1288 
1289 FUNCTION eval_unit_forced_type( p_person_id                 NUMBER,
1290                                 p_load_calendar_type        VARCHAR2,
1291                                 p_load_cal_sequence_number  VARCHAR2,
1292                                 p_uoo_id                    NUMBER,
1293                                 p_course_cd                 VARCHAR2,
1294                                 p_course_version            VARCHAR2,
1295                                 p_message               OUT NOCOPY VARCHAR2,
1296                                 p_deny_warn                 VARCHAR2,
1297                                 p_enrollment_category   IN  VARCHAR2,
1298                                 p_comm_type             IN  VARCHAR2,
1299                                 p_method_type           IN  VARCHAR2,
1300                                 p_calling_obj           IN VARCHAR2
1301                               ) RETURN BOOLEAN
1302 AS
1303   /******************************************************************
1304   Created By        : Vinay Chappidi
1305   Date Created By   : 19-Jun-2001
1306   Purpose           : This function validates the program attempt mode against
1307                       program offering option restriction
1308   Known limitations,
1309   enhancements,
1310   remarks            :
1311   Change History
1312   Who        When            What
1313   ckasu       15-Jul-2005     Modified this function inorder to log warning records in to a warnings Table
1314                               when called from selefservice pages as a part of EN317 SS UI Build bug#4377985
1315 
1316   stutta    18-NOV-2003  Replaced the cursor, which retrieves coo_id from program attempt table, with a call to
1317                          terms api function to return coo_id. Done as part of Term Records Build.
1318   svenkata    21-Jan-03  Modified the routine as part of Bug# 2750538 to validate Attendance Type when Min CP Configuration does not exist.
1319   svenkata    7-Jan-03   Incorporated the logic for 'When first Reach Attendance Type'. The value of p_deny_warn has a value of AttTypReached / AttTypNotReached
1320                          if called from Drop Unit section / Update Unit section CP / Transfer unit section.-Bug#2737263.If this parameter has a value and a Min CP
1321                          config exists for 'When First Reach Min CP' , then DENY/WARN is determined programatically based on whether the Att Typ has already been rchd.
1322   Nishikant  17OCT2002   Enrl Elgbl and Validation Build. Bug#2616692.
1323                          The Logic modified to check first whether Min CP is Overriden at Load Calendar level
1324                          then call eval_min_cp and set DENY or WARN messages accordingly.
1325   ayedubat  6-JUN-2002   Replaced the function call,Igs_En_Gen_015.get_academic_cal with
1326                        Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd to get the academic calendar of the given
1327                        load calendar rather than current academic calendar for the bug fix: 2381603
1328 myoganat 16-JUN-2003    Bug# 2855870 Added cursor c_assessment to check for an audit attempt and if it is, the function
1329                                                    will return TRUE.
1330   ******************************************************************/
1331 
1332   -- cursor for getting all the program offering option of all the active program attempts
1333   -- modified the WHERE clause to add condition course_cd = p_course_cd and removed course_attempt_status condition.
1334 
1335   -- Cursor to fetch the Date Alias value.
1336   CURSOR cur_get_alias_val( l_p_date_alias igs_ca_da_inst_v.dt_alias%TYPE ) IS
1337   SELECT MIN(di.alias_val)
1338   FROM   igs_ca_da_inst_v di
1339   WHERE  di.cal_type           = p_load_calendar_type AND
1340          di.ci_sequence_number = p_load_cal_sequence_number AND
1341          di.dt_alias           = l_p_date_alias ;
1342 
1343   -- Below cursor added as part of Enrl Elgbl and Validation Build. Bug#2616692
1344   CURSOR cur_min_cp_config IS
1345   SELECT ecpd.config_min_cp_valdn, ecpd.enforce_date_alias
1346   FROM   igs_en_cat_prc_dtl ecpd, igs_en_cpd_ext ecpe
1347   WHERE  ecpe.s_enrolment_step_type IN  ( 'FATD_TYPE' ,  'FMIN_CRDT' ) AND
1348          ecpe.enrolment_cat         = p_enrollment_category AND
1349          ecpe.enr_method_type       = p_method_type AND
1350          (ecpe.s_student_comm_type   = p_comm_type
1351          OR ecpe.s_student_comm_type   =  'ALL' ) AND
1352          ecpd.enrolment_cat         = ecpe.enrolment_cat       AND
1353          ecpd.enr_method_type       = ecpe.enr_method_type     AND
1354          ecpd.s_student_comm_type   = ecpe.s_student_comm_type AND
1355          ecpd.config_min_cp_valdn   <> 'NONE';
1356 
1357 
1358  -- Cursor to get the assessment indicator value.
1359   CURSOR c_assessment IS
1360      SELECT no_assessment_ind
1361      FROM  igs_en_su_attempt
1362      WHERE  person_id = p_person_id
1363       AND  course_cd = p_course_cd
1364       AND  uoo_id = p_uoo_id;
1365 
1366   -- added by ckasu as a part of EN317 SS UI Build bug#4377985
1367    CURSOR c_get_att_type(p_coo_id IGS_PS_OFR_OPT.coo_id%TYPE) IS
1368       SELECT attendance_type
1369       FROM IGS_PS_OFR_OPT
1370       WHERE coo_id = p_coo_id;
1371 
1372 
1373 
1374   -- Cursor ROWTYPE variables
1375   l_min_cp_config  cur_min_cp_config%ROWTYPE;
1376   l_person_type igs_pe_typ_instances.person_type_code%TYPE;
1377    l_no_assessment_ind       igs_en_su_attempt.no_assessment_ind%TYPE;
1378 
1379   -- Table.Column Type Variables
1380   l_coo_id  igs_en_stdnt_ps_att.coo_id%TYPE;
1381   l_override_limit          igs_en_elgb_ovr_step.step_override_limit%TYPE; -- should be NUMBER(6,3) Instead of NUMBER(5,3)
1382   l_acad_cal_type           igs_ca_inst.cal_type%TYPE;
1383   l_acad_ci_sequence_number igs_ca_inst.sequence_number%TYPE;
1384   l_get_alias_val           igs_ca_da_inst_v.alias_val%TYPE;
1385 
1386   -- Variables
1387   l_return_value            BOOLEAN;
1388   l_message_name            VARCHAR2(30);  -- As returned from the function igs_en_val_sca.enrp_val_coo_att
1389   l_attendance_types        VARCHAR2(100); -- As returned from the function igs_en_val_sca.enrp_val_coo_att
1390   l_acad_message            VARCHAR2(30);  -- as reutrned from the procedure Get Academic Calendar
1391   l_acad_start_dt           IGS_CA_INST.start_dt%TYPE;
1392   l_acad_end_dt             IGS_CA_INST.end_dt%TYPE;
1393   l_alternate_code          IGS_CA_INST.alternate_code%TYPE;
1394   --Below Three variables added as part of Enrl Elgbl and Validation Build. Bug#2616692
1395   l_credit_points           igs_en_config_enr_cp.min_cp_per_term%TYPE;
1396   l_min_credit_point        igs_en_config_enr_cp.min_cp_per_term%TYPE;
1397   l_deny_warn               VARCHAR2(20);
1398 
1399   l_att_type                IGS_PS_OFR_OPT.ATTENDANCE_TYPE%TYPE;
1400 
1401   l_message                 VARCHAR2(2000);
1402   l_message_icon            VARCHAR2(1);
1403 
1404 BEGIN
1405 
1406   OPEN c_assessment;
1407   FETCH c_assessment INTO l_no_assessment_ind;
1408   CLOSE c_assessment;
1409 
1410     -- Checking if the unit section attempt is an audit attempt, if it is then the function will return TRUE
1411   IF l_no_assessment_ind = 'Y' THEN
1412       RETURN TRUE;
1413   END IF;
1414 
1415   -- Checking if the step is overriden, if it is overriden then the function will return TRUE
1416   l_return_value :=igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'FATD_TYPE',
1417                                                                   p_load_cal_type         => p_load_calendar_type,
1418                                                                   p_load_cal_seq_number   => p_load_cal_sequence_number,
1419                                                                   p_person_id             => p_person_id,
1420                                                                   p_uoo_id                => p_uoo_id,
1421                                                                   p_step_override_limit   => l_override_limit
1422                                                                  );
1423   IF l_return_value THEN
1424     RETURN TRUE;
1425   END IF;
1426 
1427   -- get the academic calendar of the given Load Calendar
1428   -- clarify if this function returns a value , if not there is a place in the function which returns a value, confirm the function name
1429       l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
1430                         p_cal_type                => p_load_calendar_type,
1431                         p_ci_sequence_number      => p_load_cal_sequence_number,
1432                         p_acad_cal_type           => l_acad_cal_type,
1433                         p_acad_ci_sequence_number => l_acad_ci_sequence_number,
1434                         p_acad_ci_start_dt        => l_acad_start_dt,
1435                         p_acad_ci_end_dt          => l_acad_end_dt,
1436                         p_message_name            => l_acad_message );
1437 
1438   -- if no academic calendar is defined for the program,person then the function
1439   -- should return FALSE with the message that was thrown from the above procedure
1440       IF ( l_acad_cal_type IS NOT NULL AND l_acad_ci_sequence_number IS NOT NULL) THEN
1441     -- validate the attendance type of the program offering option of the active program attempts
1442 
1443         l_coo_id := igs_en_spa_terms_api.get_spat_coo_id( p_person_id => p_person_id,
1444                                 p_program_cd => p_course_cd,
1445                                 p_term_cal_type => p_load_calendar_type,
1446                                 p_term_sequence_number => p_load_cal_sequence_number);
1447         l_return_value := igs_en_val_sca.enrp_val_coo_att(p_person_id          => p_person_id,
1448                                                       p_coo_id             => l_coo_id,
1449                                                       p_cal_type           => l_acad_cal_type,
1450                                                       p_ci_sequence_number => l_acad_ci_sequence_number,
1451                                                       p_message_name       => l_message_name,
1452                                                       p_attendance_types   => l_attendance_types,
1453                                                       p_load_or_teach_cal_type => p_load_calendar_type,
1454                                                       p_load_or_teach_seq_number => p_load_cal_sequence_number
1455                                                      );
1456         IF l_return_value THEN
1457            RETURN TRUE;
1458         END IF;
1459 
1460       END IF;
1461 
1462   l_deny_warn := p_deny_warn;
1463   OPEN cur_min_cp_config;
1464   FETCH cur_min_cp_config INTO l_min_cp_config;
1465 
1466   IF cur_min_cp_config%FOUND THEN
1467 
1468         CLOSE cur_min_cp_config;
1469 
1470         -- The MIn CP is configured for Date Alias,then call eval_min_cp to check if the Date Alias has already been reached.
1471         IF l_min_cp_config.config_min_cp_valdn = 'DTALIASRCH' THEN
1472           OPEN cur_get_alias_val( l_min_cp_config.enforce_date_alias);
1473           FETCH cur_get_alias_val INTO l_get_alias_val;
1474           CLOSE cur_get_alias_val;
1475 
1476           --If the date alias defined for the Calendar Instance then
1477           IF l_get_alias_val IS NOT NULL THEN
1478              --If the alias value has been reached then p_deny_warn is DENY else WARN
1479              IF TRUNC(l_get_alias_val) <= TRUNC(SYSDATE) THEN
1480                 l_deny_warn := 'DENY';
1481              ELSE
1482                 l_deny_warn := 'WARN';
1483              END IF;
1484 
1485           -- If the Date alias is not defined for the Calendar Instance then return TRUE.
1486           ELSE
1487              RETURN TRUE;
1488           END IF;
1489 
1490         ELSIF l_min_cp_config.config_min_cp_valdn = 'MINCPREACH' THEN
1491 
1492             -- If Min CP is configured for 'When First Reach Min CP', check if the student has already reached the Attendance Type of the Program.If the Attendance Type
1493             -- has already reached, DENY the user from dropping below the Forced Attendance Type.The parameter p_deny_warn can have these values only when it is being called
1494             -- from Transfer section workflow/Update CP/Drop Units.
1495             IF p_deny_warn = 'AttTypReached' THEN
1496                 l_deny_warn := 'DENY' ;
1497             ELSIF  p_deny_warn = 'AttTypNotReached' THEN
1498                 l_deny_warn := 'WARN' ;
1499             END IF ;
1500 
1501         END IF ;
1502     ELSE
1503         l_person_type := igs_en_gen_008.enrp_get_person_type(p_course_cd => NULL );
1504 
1505         l_deny_warn  := igs_ss_enr_details.get_notification(
1506             p_person_type               => l_person_type,
1507             p_enrollment_category       => p_enrollment_category ,
1508             p_comm_type                 => p_comm_type ,
1509             p_enr_method_type           => p_method_type ,
1510             p_step_group_type           => 'PROGRAM',
1511             p_step_type                 => 'FATD_TYPE',
1515     END IF ;
1512             p_person_id                 => p_person_id,
1513             p_message                   => l_message_name) ;
1514 
1516 
1517   -- code added by ckasu as a part of EN317 SS Build bug# 4377985
1518   OPEN c_get_att_type(l_coo_id);
1519   FETCH c_get_att_type INTO l_att_type;
1520   CLOSE c_get_att_type;
1521 
1522   IF l_deny_warn ='WARN' THEN
1523 
1524     IF p_calling_obj = 'DROP' THEN
1525        l_message := 'IGS_SS_EN_ATT_TYP_WARN';
1526     ELSIF p_calling_obj = 'JOB' THEN
1527        l_message := 'IGS_SS_WARN_ATTYPE_CHK';
1528     END IF; -- end of p_calling_obj = 'SCH_UPD'
1529 
1530   ELSE
1531 
1532     IF p_calling_obj = 'SCH_UPD' THEN
1533        l_message := 'IGS_EN_ATTYPE_UPD_DENY' ||'*'||l_att_type;
1534     ELSIF p_calling_obj = 'DROP' THEN
1535        l_message := 'IGS_SS_EN_ATT_TYP_DENY';
1536     ELSIF p_calling_obj = 'JOB' THEN
1537        l_message := 'IGS_SS_DENY_ATTYPE_CHK';
1538     END IF; -- end of p_calling_obj = 'SCH_UPD'
1539 
1540   END IF; -- end of l_deny_warn ='WARN' IF THEN
1541 
1542   IF p_calling_obj NOT IN ('JOB','DROP','SCH_UPD') THEN
1543 
1544      IF p_deny_warn = 'WARN' THEN
1545         l_message := 'IGS_EN_ATTYPE_TAB_WARN';
1546      ELSE
1547         l_message := 'IGS_EN_ATTYPE_TAB_DENY';
1548      END IF; -- end of p_deny_warn = 'WARN' THEN
1549 
1550      l_message_icon := substr(l_deny_warn,1,1);
1551      -- create a warnings record
1552      IGS_EN_DROP_UNITS_API.create_ss_warning(p_person_id                 => p_person_id,
1553                                              p_course_cd                 => p_course_cd,
1554                                              p_term_cal_type             => p_load_calendar_type,
1555                                              p_term_ci_sequence_number   => p_load_cal_sequence_number,
1556                                              p_uoo_id                    => p_uoo_id,
1557                                              p_message_for               => igs_ss_enroll_pkg.enrf_get_lookup_meaning('FATD_TYPE','ENROLMENT_STEP_TYPE_EXT'),
1558                                              p_message_icon              => l_message_icon,
1559                                              p_message_name              => l_message,
1560                                              p_message_rule_text         => NULL,
1561                                              p_message_tokens            => 'UNIT_CD:'||l_att_type||';',
1562                                              p_message_action            => NULL,
1563                                              p_destination               => NULL,
1564                                              p_parameters                => NULL,
1565                                              p_step_type                 => 'PROGRAM');
1566   ELSE
1567      p_message :=  l_message;
1568   END IF; -- end of p_calling_obj NOT IN ('JOB','SCH_UPD') if then
1569 
1570   -- end of code adde dby ckasu as a part of bug# 4377985
1571 
1572  RETURN FALSE;
1573 
1574 END eval_unit_forced_type;
1575 
1576 FUNCTION eval_fail_min_cp(
1577      p_person_id                NUMBER,
1578      p_course_cd                VARCHAR2,
1579      p_version_number           NUMBER,
1580      p_acad_cal                 VARCHAR2,
1581      p_load_cal                 VARCHAR2,
1582      p_load_ci_sequence_number  NUMBER,
1583      p_method                   VARCHAR2) RETURN VARCHAR2
1584 AS
1585   /******************************************************************
1586   Created By        : Nishikant
1587   Date Created By   : 21OCT2002
1588   Purpose           : This function is introduced in Enrollment Eligibility
1589              and Validation Build. Bug#2616692. This function is being used
1590              in a cursor in the form IGSEN076. This function calls the function
1591              eval_min_cp for each ACTIVE unit attempt of the student and
1592              returns TRUE or FALSE.
1593   Known limitations,
1594   enhancements,
1595   remarks            :
1596   Change History
1597   Who             When        What
1598   ckasu       15-Jul-2005     Modified this function inorder to add new parameter p_calling_obj
1599                               as a part of EN317 SS UI Build bug#4377985
1600   ******************************************************************/
1601 
1602   CURSOR c_acad_cal IS
1603   SELECT sup_ci_sequence_number
1604   FROM   igs_ca_inst_rel
1605   WHERE  sub_cal_type = p_load_cal AND
1606          sub_ci_sequence_number = p_load_ci_sequence_number AND
1607          sup_cal_type = p_acad_cal;
1608 
1609   CURSOR c_chk_min_cp_valdn( p_enrl_cat  igs_en_cat_prc_dtl.enrolment_cat%TYPE,
1610                              p_enr_meth_type  igs_en_method_type.enr_method_type%TYPE,
1611                              p_s_stdnt_comm_type  VARCHAR2) IS
1612   SELECT notification_flag
1613   FROM   igs_en_cpd_ext
1614   WHERE  enrolment_cat = p_enrl_cat
1615   AND    enr_method_type = p_enr_meth_type
1616   AND    s_enrolment_step_type = 'FMIN_CRDT'
1617   AND    (s_student_comm_type = p_s_stdnt_comm_type OR
1618           s_student_comm_type = 'ALL');
1619 
1620   CURSOR c_get_unit_attmpt IS
1621   SELECT DISTINCT uoo_id
1622   FROM   igs_en_su_attempt sua,
1623          igs_ca_load_to_teach_v ltt
1624   WHERE  sua.person_id = p_person_id
1625   AND    sua.course_cd = p_course_cd
1626   AND    sua.unit_attempt_status = 'ENROLLED'
1627   AND    sua.cal_type = ltt.teach_cal_type
1628   AND    sua.ci_sequence_number = ltt.teach_ci_sequence_number
1629   AND    ltt.load_cal_type = p_load_cal
1630   AND    ltt.load_ci_sequence_number = p_load_ci_sequence_number ;
1634   l_enrollment_cat        igs_en_cat_prc_dtl.enrolment_cat%TYPE;
1631 
1632   l_acad_ci_seq_number    igs_ca_inst_rel.sup_ci_sequence_number%TYPE;
1633   l_commencement_type     VARCHAR2(10);
1635   l_enrol_cal_type        igs_ca_inst_all.cal_type%TYPE;
1636   l_enrol_sequence_number igs_ca_inst_all.sequence_number%TYPE;
1637   l_notification_flag     igs_en_cpd_ext.notification_flag%TYPE;
1638   l_message               fnd_new_messages.message_name%TYPE;
1639   l_credit_points         igs_en_config_enr_cp.min_cp_per_term%TYPE;
1640   l_min_credit_point      igs_en_config_enr_cp.min_cp_per_term%TYPE;
1641   l_ret_value             BOOLEAN;
1642   l_dummy                 VARCHAR2(200);
1643 
1644 BEGIN
1645    --Getting the sequence number of the passed parameter Acad Calendar Type.
1646    OPEN c_acad_cal;
1647    FETCH c_acad_cal INTO l_acad_ci_seq_number;
1648    CLOSE c_acad_cal;
1649 
1650    --Calling the below function to get the values Enrollment Category, Commencement Type
1651    l_enrollment_cat := igs_en_gen_003.enrp_get_enr_cat
1652                          ( p_person_id => p_person_id,
1653                            p_course_cd => p_course_cd,
1654                            p_cal_type => p_acad_cal,
1655                            p_ci_sequence_number => l_acad_ci_seq_number,
1656                            p_session_enrolment_cat =>NULL,
1657                            p_enrol_cal_type => l_enrol_cal_type,
1658                            p_enrol_ci_sequence_number => l_enrol_sequence_number,
1659                            p_commencement_type => l_commencement_type,
1660                            p_enr_categories  => l_dummy
1661                           );
1662    --If Commencement Type is BOTH is returned we have to treat it as ALL
1663    IF l_commencement_type = 'BOTH' THEN
1664           l_commencement_type := 'ALL';
1665    END IF;
1666 
1667    OPEN c_chk_min_cp_valdn(l_enrollment_cat, p_method, l_commencement_type);
1668    FETCH c_chk_min_cp_valdn INTO l_notification_flag;
1669    -- If Min CP validation is defined as a step in the Enrollment Category of the Student then
1670    -- Proceed inside the If Block.
1671    IF c_chk_min_cp_valdn%FOUND THEN
1672       -- We have to pass the value of the variable l_notificetion_flag as either DENY_QUERY or WARN_QUERY
1673       -- to the function call eval_min_cp.
1674       IF l_notification_flag = 'DENY' THEN
1675           l_notification_flag := 'DENY_QUERY';
1676       ELSIF l_notification_flag = 'WARN' THEN
1677           l_notification_flag := 'WARN_QUERY';
1678       END IF;
1679 
1680       -- For each ACTIVE Unit Attempted by the student loop through the block untill the function call
1681       -- eval_min_cp returns TRUE
1682       FOR l_cur_uoo_id IN c_get_unit_attmpt
1683       LOOP
1684           l_credit_points := NULL;
1685           l_min_credit_point := NULL;
1686           -- Call eval_min_cp function for each unit attempt, if it returns FALSE then no need to proceed
1687           -- further for the rest of the units. Return FALSE.
1688           l_ret_value := eval_min_cp(
1689                        p_person_id                =>  p_person_id,
1690                        p_load_calendar_type       =>  p_load_cal,
1691                        p_load_cal_sequence_number =>  p_load_ci_sequence_number,
1692                        p_uoo_id                   =>  l_cur_uoo_id.uoo_id,
1693                        p_program_cd               =>  p_course_cd,
1694                        p_program_version          =>  TO_CHAR(p_version_number),
1695                        p_message                  =>  l_message,
1696                        p_deny_warn                =>  l_notification_flag,
1697                        p_credit_points            =>  l_credit_points,
1698                        p_enrollment_category      =>  l_enrollment_cat,
1699                        p_comm_type                =>  l_commencement_type,
1700                        p_method_type              =>  p_method,
1701                        p_min_credit_point         =>  l_min_credit_point,
1702                        p_calling_obj              =>  'JOB');
1703           IF l_ret_value = FALSE AND l_message = 'IGS_SS_DENY_MIN_CP_REACHED' THEN
1704               RETURN 'FALSE';
1705           END IF;
1706       END LOOP;
1707    END IF;
1708    RETURN 'TRUE';
1709 END eval_fail_min_cp;
1710 
1711 PROCEDURE stdnt_crd_pnt_enrl_workflow(
1712                             p_user_name             IN VARCHAR2,
1713                             p_course_cd             IN VARCHAR2,
1714                             p_version_number        IN NUMBER,
1715                             p_enrolled_cp           IN NUMBER,
1716                             p_min_cp                IN NUMBER
1717                             )AS
1718   -----------------------------------------------------------------------------
1719   -- Created by  : Nishikant
1720   -- Date created: 22OCT2002
1721   --
1722   -- Purpose: This procedure introduced to raise a bussiness event to notify the
1723   --       student that he/she has failed the Min CP Validation.
1724   --
1725   -- Known limitations/enhancements and/or remarks:
1726   --
1727   -- Change History:
1728   -- Who         When            What
1729   --
1730   ------------------------------------------------------------------------------
1731   CURSOR cur_seq_val  IS
1732   SELECT IGS_EN_WF_BE002_S.nextval seq_val
1733   FROM   DUAL;
1734 
1735   l_cur_seq_val         cur_seq_val%ROWTYPE;
1736   l_wf_parameter_list_t WF_PARAMETER_LIST_T:=wf_parameter_list_t();
1737   l_wf_installed        fnd_lookups.lookup_code%TYPE;
1738 
1739 BEGIN
1740 
1744   -- if workflow is installed then carry on with the raising an event
1741   -- get the profile value that is set for checking if workflow is installed
1742   fnd_profile.get('IGS_WF_ENABLE',l_wf_installed);
1743 
1745   IF (RTRIM(l_wf_installed) = 'Y' ) THEN
1746 
1747      OPEN cur_seq_val;
1748      FETCH cur_seq_val INTO l_cur_seq_val;
1749      CLOSE cur_seq_val;
1750 
1751      -- set the event parameters
1752      wf_event.addparametertolist(p_Name=>'USER_NAME',      p_Value=>p_user_name      ,p_Parameterlist =>l_wf_parameter_list_t);
1753      wf_event.addparametertolist(p_Name=>'COURSE_CD',      p_Value=>p_course_cd      ,p_Parameterlist =>l_wf_parameter_list_t);
1754      wf_event.addparametertolist(p_Name=>'VERSION_NUMBER', p_Value=>p_version_number ,p_Parameterlist =>l_wf_parameter_list_t);
1755      wf_event.addparametertolist(p_Name=>'ENROLLED_CP',    p_Value=>p_enrolled_cp    ,p_Parameterlist =>l_wf_parameter_list_t);
1756      wf_event.addparametertolist(p_Name=>'MIN_CP',         p_Value=>p_min_cp         ,p_Parameterlist =>l_wf_parameter_list_t);
1757 
1758      -- raise the event
1759      WF_EVENT.RAISE(p_event_name=>'oracle.apps.igs.en.be_en002',
1760                     p_event_key =>'oracle.apps.igs.en.be_en002'||l_cur_seq_val.seq_val,
1761                     p_event_data=>NULL,
1762                     p_parameters=>l_wf_parameter_list_t);
1763     --As part of the bug 2840171 fix, issuing commit after workflow event is raised.
1764     --Reason, workflow event would successfully complete only after commit(transaction is complete),
1765     --but there is no explicit commit call in the Minimum Credit point Query form(IGSEN076.fmb) form
1766     --while calling the this workflow procedure.
1767     COMMIT;
1768   END IF;
1769 
1770 END stdnt_crd_pnt_enrl_workflow;
1771 
1772 
1773 FUNCTION calc_min_cp (
1774  p_person_id                             NUMBER,
1775  p_load_calendar_type                   VARCHAR2,
1776  p_load_cal_sequence_number             NUMBER,
1777  p_uoo_id                               NUMBER,
1778  p_program_cd                           VARCHAR2,
1779  p_program_version                      VARCHAR2,
1780  p_message                      OUT NOCOPY VARCHAR2
1781 ) RETURN NUMBER IS
1782  -----------------------------------------------------------------------------
1783   -- Created by  : svenkata
1784   -- Date created: 23-Jan-2003
1785   --
1786   -- Purpose: The routine has been created by moving the code from the routine eval_min_cp.This function calculates the Min CP as
1787   -- defined at any one of the following levels in that order :Override, Holds,Person ID group,Term or Program.
1788   --
1789   -- Known limitations/enhancements and/or remarks:
1790   --
1791   -- Change History:
1792   -- Who         When            What
1793   --
1794   ----------------------------------------------------------------------------
1795   -- Cursor for getting the Teaching Calendar Type and its Sequence number for the UOO_ID passed
1796   CURSOR cur_uoo_id
1797   IS
1798   SELECT unit_cd, version_number, cal_type, ci_sequence_number
1799   FROM   igs_ps_unit_ofr_opt
1800   WHERE  uoo_id = p_uoo_id;
1801 
1802   -- Cursor for getting the minimum progression credit points that are defined
1803   CURSOR cur_min_progression_cp(cp_effective_date DATE)
1804   IS
1805   SELECT MIN(restricted_enrolment_cp) restricted_enrolment_cp
1806   FROM   igs_pe_persenc_effct
1807   WHERE  person_id            = p_person_id
1808   AND    s_encmb_effect_type  = 'RSTR_GE_CP'
1809   AND    pee_start_dt        <= cp_effective_date
1810   AND    (expiry_dt IS NULL OR expiry_dt >= cp_effective_date);
1811 
1812   -- Cursor for getting the minimum primary program credit points that are defined
1813   CURSOR cur_min_primary_cp(cp_primary_cd     igs_ps_ver.course_cd%TYPE,
1814                             cp_version_number igs_ps_ver.version_number%TYPE)
1815   IS
1816   SELECT min_cp_per_calendar
1817   FROM   igs_ps_ver
1818   WHERE  course_cd      = cp_primary_cd
1819   AND    version_number = cp_version_number;
1820 
1821   -- Below three cursors added as part of Enrl Elgbl and Validation Build. Bug#2616692
1822   CURSOR cur_get_min_cp_ovr IS
1823   SELECT min_cp_per_term
1824   FROM   igs_en_config_enr_cp
1825   WHERE  course_cd      = p_program_cd      AND
1826          version_number = p_program_version AND
1827          cal_type       = p_load_calendar_type;
1828 
1829   -- Cursor to get the Load Calendar Start Date when the uoo_id is not mentioned.
1830   CURSOR get_load_cal_st_dt IS
1831   SELECT start_dt
1832   FROM igs_ca_inst
1833   WHERE cal_type = p_load_calendar_type  AND
1834   sequence_number =  p_load_cal_sequence_number ;
1835 
1836   -- Cursor Row Type Variables
1837   l_cur_uoo_id              cur_uoo_id%ROWTYPE;
1838   l_cur_min_progression_cp  cur_min_progression_cp%ROWTYPE;
1839   l_cur_min_primary_cp      cur_min_primary_cp%ROWTYPE;
1840   l_message                 VARCHAR2(30) := NULL ;
1841 
1842   -- Table.Column Type Variables
1843   l_override_limit          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
1844   l_min_cp_allowed          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE := NULL ;
1845 
1846   l_get_min_cp_ovr          igs_en_config_enr_cp.min_cp_per_term%TYPE;
1847   l_return_value            BOOLEAN;
1848   l_effective_date          igs_ca_inst.start_dt%TYPE;
1849   l_prsid_min_cp            igs_en_pig_cp_setup.prsid_min_cp%TYPE;
1850 
1851 BEGIN
1852   l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'FMIN_CRDT',
1856                                                                    p_uoo_id                => p_uoo_id,
1853                                                                    p_load_cal_type         => p_load_calendar_type,
1854                                                                    p_load_cal_seq_number   => p_load_cal_sequence_number,
1855                                                                    p_person_id             => p_person_id,
1857                                                                    p_step_override_limit   => l_override_limit
1858                                                                  );
1859   IF l_return_value = TRUE THEN
1860     IF l_override_limit IS NOT NULL THEN
1861       l_min_cp_allowed := l_override_limit;
1862       RETURN l_min_cp_allowed;
1863     ELSE
1864        RETURN NULL;
1865     END IF;
1866   END IF;
1867 
1868 
1869   -- get the teaching calendar type and its sequence number for the uoo_id that is passed into the function
1870   -- unit code and its version number is also captured
1871   OPEN  cur_uoo_id;
1872   FETCH cur_uoo_id INTO l_cur_uoo_id;
1873   CLOSE cur_uoo_id;
1874 
1875   -- Once the teaching calendar and its sequence number is found , get the census date as a return value (effective date)
1876   l_effective_date := igs_en_gen_015.get_effective_census_date( p_load_cal_type        => p_load_calendar_type,
1877                                                                 p_load_cal_seq_number  => p_load_cal_sequence_number,
1878                                                                 p_teach_cal_type       => l_cur_uoo_id.cal_type,
1879                                                                 p_teach_cal_seq_number => l_cur_uoo_id.ci_sequence_number
1880                                                               );
1881   --
1882   -- The Effective Date is the Census Date alias value that is queried at the following levels : Term Cal , Teach Cal. If not defined,
1883   -- Teach Cal Start date is taken. When called from SS , Teach Cal details are not available.Hence the function
1884   --igs_en_gen_015.get_effective_census_date may return NULL. So Load Cal start Date is assigned to l_effective_date.
1885   IF l_effective_date IS NULL THEN
1886     OPEN get_load_cal_st_dt  ;
1887     FETCH get_load_cal_st_dt  INTO l_effective_date ;
1888     CLOSE get_load_cal_st_dt ;
1889   END IF ;
1890 
1891   -- if the minimum credit points are not fetched till this point,
1892   -- get the minimum credit points from the progression prespective
1893   IF l_min_cp_allowed IS NULL THEN
1894     -- opening the cursor with the effective date fetched, start and expiry date should be between the census date
1895     OPEN  cur_min_progression_cp (l_effective_date);
1896     FETCH cur_min_progression_cp INTO l_cur_min_progression_cp;
1897     CLOSE cur_min_progression_cp;
1898 
1899     -- If the credit points fetched is not null then assign it to the minimum cp allowed variable
1900     IF l_cur_min_progression_cp.restricted_enrolment_cp IS NOT NULL THEN
1901       RETURN l_cur_min_progression_cp.restricted_enrolment_cp;
1902     ELSE
1903 
1904        --If the Restricted Enrollment Credit Point is not defined in Progression then check the Minimum CP then
1905        --check at person id group level.
1906        l_prsid_min_cp := igs_en_val_pig.enrf_get_pig_cp(p_person_id,'MIN_CP',l_message);
1907        IF l_message IS NOT NULL THEN
1908            --If a person belongs to more than one person grop and
1909            --Override steps were defined at more than one person id group level.
1910             p_message := l_message ;
1911             RETURN NULL  ;
1912        ELSIF l_prsid_min_cp IS NOT NULL THEN
1913             RETURN l_prsid_min_cp;
1914        ELSE
1915             -- Code added by Nishikant as part of Enrollment Eligibility and Validation Build - Bug#2616692
1916             -- If the Restricted Enrollment Credit Point is not defined in person id group then check the Minimum CP
1917             -- is overriden at the load calendar level. If yes then proceed with the value, If not then proceed to
1918             -- check out NOCOPY whether provided at Program level.
1919             OPEN cur_get_min_cp_ovr;
1920             FETCH cur_get_min_cp_ovr INTO l_get_min_cp_ovr;
1921             CLOSE cur_get_min_cp_ovr;
1922             IF l_get_min_cp_ovr IS NOT NULL THEN
1923                    RETURN l_get_min_cp_ovr;
1924             ELSE
1925                   OPEN  cur_min_primary_cp (p_program_cd, p_program_version);
1926                   FETCH cur_min_primary_cp INTO l_cur_min_primary_cp;
1927                   CLOSE cur_min_primary_cp;
1928                   -- If the credit points fetched for the primary program is not null
1929                   -- then assign it to the minimum cp allowed variable
1930                   IF l_cur_min_primary_cp.min_cp_per_calendar IS NOT NULL THEN
1931                      RETURN l_cur_min_primary_cp.min_cp_per_calendar;
1932                   ELSE
1933                          RETURN NULL ;
1934                   END IF;
1935               END IF; --IF cur_get_min_cp_ovr%FOUND AND l_get_min_cp_ovr.min_cp_per_term IS NOT NULL THEN
1936        END IF;  --If l_message is not null
1937     END IF;--IF l_cur_min_progression_cp.restricted_enrolment_cp IS NOT NULL THEN
1938   END IF;--IF l_min_cp_allowed IS NULL THEN
1939 
1940   RETURN NULL ;
1941 END calc_min_cp ;
1942 
1943 FUNCTION calc_max_cp (
1944                        p_person_id                             NUMBER,
1945                        p_load_calendar_type                   VARCHAR2,
1946                        p_load_cal_sequence_number             NUMBER,
1947                        p_uoo_id                               NUMBER,
1948                        p_program_cd                           VARCHAR2,
1952  -----------------------------------------------------------------------------
1949                        p_program_version                      VARCHAR2,
1950                        p_message                      OUT NOCOPY VARCHAR2
1951                     ) RETURN NUMBER IS
1953   -- Created by  : svenkata
1954   -- Date created: 23-Jan-2003
1955   --
1956   -- Purpose: The routine has been created by moving the code from the routine eval_max_cp.This function calculates the Max CP as
1957   -- defined at any one of the following levels in that order :Override, Holds,Person ID group,Term or Program.
1958   --
1959   -- Known limitations/enhancements and/or remarks:
1960   --
1961   -- Change History:
1962   -- Who         When            What
1963   --
1964   ----------------------------------------------------------------------------
1965 
1966   -- Cursor for getting the Teaching Calendar Type and its Sequence number for the UOO_ID passed
1967   CURSOR cur_uoo_id
1968   IS
1969   SELECT unit_cd, version_number, cal_type, ci_sequence_number
1970   FROM   igs_ps_unit_ofr_opt
1971   WHERE  uoo_id = p_uoo_id;
1972 
1973   -- Cursor for getting the maximum progression credit points that are defined
1974   CURSOR cur_max_progression_cp(cp_effective_date DATE)
1975   IS
1976   SELECT MAX(restricted_enrolment_cp) restricted_enrolment_cp
1977   FROM   igs_pe_persenc_effct
1978   WHERE  person_id            = p_person_id
1979   AND    s_encmb_effect_type  = 'RSTR_LE_CP'
1980   AND    pee_start_dt        <= cp_effective_date
1981   AND    (expiry_dt IS NULL OR expiry_dt >= cp_effective_date);
1982 
1983   -- Cursor for getting the maximum primary program credit points that are defined
1984   CURSOR cur_max_primary_cp(cp_primary_cd     igs_ps_ver.course_cd%TYPE,
1985                             cp_version_number igs_ps_ver.version_number%TYPE)
1986   IS
1987   SELECT max_cp_per_teaching_period
1988   FROM   igs_ps_ver
1989   WHERE  course_cd      = cp_primary_cd
1990   AND    version_number = cp_version_number;
1991 
1992   -- Below cursor added as part of Enrl Elgbl and Validation Build. Bug#2616692
1993   CURSOR cur_get_max_cp_ovr IS
1994   SELECT max_cp_per_term
1995   FROM   igs_en_config_enr_cp
1996   WHERE  course_cd      = p_program_cd      AND
1997          version_number = p_program_version AND
1998          cal_type       = p_load_calendar_type;
1999 
2000   -- Cursor to get the Load Calendar Start Date when the uoo_id is not mentioned.
2001   CURSOR get_load_cal_st_dt IS
2002   SELECT start_dt
2003   FROM igs_ca_inst
2004   WHERE cal_type = p_load_calendar_type  AND
2005   sequence_number =  p_load_cal_sequence_number ;
2006 
2007   l_cur_uoo_id              cur_uoo_id%ROWTYPE;
2008   l_cur_max_progression_cp  cur_max_progression_cp%ROWTYPE;
2009   l_cur_max_primary_cp      cur_max_primary_cp%ROWTYPE;
2010   l_get_max_cp_ovr          cur_get_max_cp_ovr%ROWTYPE;
2011   l_override_limit          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
2012   l_return_value            BOOLEAN;
2013   l_effective_date          DATE;
2014   l_prsid_max_cp            igs_en_pig_cp_setup.prsid_max_cp%TYPE;
2015   l_message                 VARCHAR2(30);
2016   l_max_cp_allowed          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
2017 
2018   l_enrol_cal_type              igs_ca_type.cal_type%TYPE;
2019   l_enrol_sequence_number   igs_ca_inst_all.sequence_number%TYPE;
2020 
2021 BEGIN
2022 
2023   l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => 'FMAX_CRDT',
2024                                                                    p_load_cal_type         => p_load_calendar_type,
2025                                                                    p_load_cal_seq_number   => p_load_cal_sequence_number,
2026                                                                    p_person_id             => p_person_id,
2027                                                                    p_uoo_id                => p_uoo_id,
2028                                                                    p_step_override_limit   => l_override_limit
2029                                                                  );
2030   IF l_return_value = TRUE THEN
2031     IF l_override_limit IS NOT NULL THEN
2032       l_max_cp_allowed :=  l_override_limit;
2033       RETURN l_override_limit;
2034     ELSE
2035       -- If the override limit is not specified, then the function returns NULL
2036       RETURN NULL ;
2037     END IF;
2038   END IF;
2039 
2040   -- get the teaching calendar type and its sequence number for the uoo_id that is passed into the function
2041   -- unit code and its version number is also captured
2042   OPEN  cur_uoo_id;
2043   FETCH cur_uoo_id INTO l_cur_uoo_id;
2044   CLOSE cur_uoo_id;
2045 
2046   -- Once the teaching calendar and its sequence number is found , get the census date as a return value (effective date)
2047   l_effective_date := igs_en_gen_015.get_effective_census_date( p_load_cal_type        => p_load_calendar_type,
2048                                                                 p_load_cal_seq_number  => p_load_cal_sequence_number,
2049                                                                 p_teach_cal_type       => l_cur_uoo_id.cal_type,
2050                                                                 p_teach_cal_seq_number => l_cur_uoo_id.ci_sequence_number
2051                                                               );
2052 
2053   --
2054   -- The Effective Date is the Census Date alias value that is queried at the following levels : Term Cal , Teach Cal. If not defined,
2055   -- Teach Cal Start date is taken. When called from SS , Teach Cal details are not available.Hence the function
2059     FETCH get_load_cal_st_dt  INTO l_effective_date ;
2056   --igs_en_gen_015.get_effective_census_date may return NULL. So Load Cal start Date is assigned to l_effective_date.
2057   IF l_effective_date IS NULL THEN
2058     OPEN get_load_cal_st_dt  ;
2060     CLOSE get_load_cal_st_dt ;
2061   END IF ;
2062 
2063   -- if the maximum credit points are not fetched till this point,
2064   -- get the maximum credit points from the progression prespective
2065   IF l_max_cp_allowed IS NULL THEN
2066     -- opening the cursor with the effective date fetched, start and expiry date should be between the census date
2067     OPEN  cur_max_progression_cp (l_effective_date);
2068     FETCH cur_max_progression_cp INTO l_cur_max_progression_cp;
2069     CLOSE cur_max_progression_cp;
2070 
2071     -- If the credit points fetched is not null then assign it to the maximum cp allowed variable
2072     IF l_cur_max_progression_cp.restricted_enrolment_cp IS NOT NULL THEN
2073       RETURN l_cur_max_progression_cp.restricted_enrolment_cp;
2074     ELSE
2075 
2076        --If the Restricted Enrollment Credit Point is not defined in Progression then check the Maximum CP then
2077        --check at person id group level.
2078        l_prsid_max_cp := igs_en_val_pig.enrf_get_pig_cp(p_person_id,'MAX_CP',l_message);
2079 
2080        IF l_message IS NOT NULL THEN
2081 
2082            --If a person belongs to more than one person grop and Override steps were defined at more than one person id group level.
2083            p_message := l_message ;
2084             RETURN NULL ;
2085        ELSIF l_prsid_max_cp IS NOT NULL THEN
2086             RETURN l_prsid_max_cp;
2087        ELSE
2088 
2089            --
2090            -- Enrollment Eligibility and Validation Build - Bug#2616692 .If the Restricted Enrollment Credit Point is not defined in person id group level then check the Maximum CP
2091            -- is overriden at the load calendar level. If yes then proceed with the value, If not then proceed to check out NOCOPY whether provided at Program level.
2092 
2093            OPEN cur_get_max_cp_ovr;
2094            FETCH cur_get_max_cp_ovr INTO l_get_max_cp_ovr;
2095            CLOSE cur_get_max_cp_ovr;
2096 
2097            IF l_get_max_cp_ovr.max_cp_per_term IS NOT NULL THEN
2098                RETURN  l_get_max_cp_ovr.max_cp_per_term;
2099            ELSE
2100            -- If the credit points are not specified then fecth the credit points defined at the program level
2101               OPEN  cur_max_primary_cp (p_program_cd, p_program_version);
2102               FETCH cur_max_primary_cp INTO l_cur_max_primary_cp;
2103               CLOSE cur_max_primary_cp;
2104 
2105               -- If the credit points fetched for the primary program is not null
2106               -- then assign it to the maximum cp allowed variable
2107               IF l_cur_max_primary_cp.max_cp_per_teaching_period IS NOT NULL THEN
2108                 RETURN l_cur_max_primary_cp.max_cp_per_teaching_period;
2109               ELSE
2110                 -- If no credit points are defined at the program level, function should return 'TRUE'
2111                 RETURN NULL ;
2112               END IF;
2113 
2114            END IF; -- max_cp_per_term
2115         END IF; -- l_prsid_max_cp
2116     END IF; -- restricted_enrolment_cp
2117   END IF; -- l_max_cp_allowed
2118 
2119   RETURN NULL;
2120 END calc_max_cp ;
2121 
2122 PROCEDURE get_per_min_max_cp (
2123  p_person_id                            NUMBER,
2124  p_load_calendar_type                   VARCHAR2,
2125  p_load_cal_sequence_number             NUMBER,
2126  p_program_cd                           VARCHAR2,
2127  p_program_version                      VARCHAR2,
2128  p_min_cp                       OUT     NOCOPY VARCHAR2 ,
2129  p_max_cp                       OUT     NOCOPY VARCHAR2 ,
2130  p_message                      OUT     NOCOPY VARCHAR2 ) IS
2131  -----------------------------------------------------------------------------
2132   -- Created by  : svenkata
2133   -- Date created: 23-Jan-2003
2134   --
2135   -- Purpose: This routine is a wrapper that is being called from SS pages to get the Min and Max Credit points.
2136   --
2137   -- Known limitations/enhancements and/or remarks:
2138   --
2139   -- Change History:
2140   -- Who         When            What
2141   --
2142   -----------------------------------------------------------------------------
2143   l_min_message VARCHAR2(30) := NULL;
2144   l_max_message VARCHAR2(30) := NULL;
2145 
2146 BEGIN
2147     p_min_cp := calc_min_cp (
2148          p_person_id                =>  p_person_id   ,
2149          p_load_calendar_type       =>  p_load_calendar_type ,
2150          p_load_cal_sequence_number =>  p_load_cal_sequence_number ,
2151          p_uoo_id                   =>  NULL ,
2152          p_program_cd               =>  p_program_cd ,
2153          p_program_version          =>  p_program_version,
2154          p_message                  =>  l_min_message  );
2155 
2156     -- If the value of Min CP returned by the routine is NULL , a hyphen is returned to SS. This is done
2157     -- deliberately to indicate to the user that the values of Min/Max CP is not defined.
2158     IF p_min_cp IS NULL THEN
2159        p_min_cp := '-' ;
2160     END IF ;
2161 
2162     p_max_cp := calc_max_cp (
2163          p_person_id                =>  p_person_id   ,
2164          p_load_calendar_type       =>  p_load_calendar_type ,
2165          p_load_cal_sequence_number =>  p_load_cal_sequence_number ,
2166          p_uoo_id                   =>  NULL ,
2167          p_program_cd               =>  p_program_cd ,
2168          p_program_version          =>  p_program_version,
2169          p_message                  =>  l_max_message );
2170 
2171     -- Though the messages are being passed as OUT parameters, these messages are currently not being shown to the user,
2172     -- as the routine is expected to calculate only the Min and Max CP values.
2173     IF l_max_message IS NOT NULL THEN
2174          p_message := l_max_message ;
2175     ELSIF l_min_message IS NOT NULL THEN
2176          p_message := l_min_message ;
2177     END IF ;
2178 
2179     -- If the value of Max CP returned by the routine is NULL , a hyphen is returned to SS. This is done
2180     -- deliberately to indicate to the user that the values of Min/Max CP is not defined.
2181     IF p_max_cp IS NULL THEN
2182        p_max_cp := '-' ;
2183     END IF ;
2184 
2185 END get_per_min_max_cp;
2186 
2187 FUNCTION EVAL_CROSS_VALIDATION(
2188   p_person_id                   IN NUMBER ,
2189   p_course_cd                   IN VARCHAR2 ,
2190   p_program_version             IN VARCHAR2,
2191   p_uoo_id                      IN NUMBER,
2192   p_load_cal_type               IN VARCHAR2 ,
2193   p_load_ci_sequence_number     IN NUMBER ,
2194   p_deny_warn                   IN VARCHAR2,
2195   p_upd_cp                      IN  NUMBER ,
2196   p_eligibility_step_type       IN VARCHAR2 ,
2197   p_message                     IN OUT NOCOPY VARCHAR2,
2198   p_calling_obj                 IN VARCHAR2 )
2199   RETURN boolean AS
2200   /******************************************************************
2201   Created By        : svenkata
2202   Date Created By   : 12-May-2003
2203   Purpose           : This function would validate the Cross element restriction (cross location / faculty / mode ) Credit points
2204                       based on the Eligibility Step Type parameter passed to it . It is a generic function that behaves differently
2205                       according to the value of parameter p_eligibility_step_type.
2206   Known limitations,
2207   enhancements,
2208   remarks           :
2209   Change History
2210   Who          When          What
2211   ckasu       15-Jul-2005     Modified this function inorder to log warning records in to a warnings Table
2212                               when called from selefservice pages as a part of EN317 SS UI Build bug#4377985
2213 
2214   stutta    18-NOV-2003  Replaced cursor to program attempt table with calls to terms api functions.
2215                          Done as part of Term Records Build.
2216 
2217    myoganat 16-JUN-2003    Added cursor c_assessment to check for an audit attempt and if it is, the function
2218                                                    will return TRUE
2219   vkarthik              22-Jul-2004     Added three dummy variables l_audit_cp, l_billing_cp, l_enrolled_cp for all the calls to
2220                                                 igs_en_prc_load.enrp_clc_sua_load towards EN308 Billable credit points build Enh#3782329
2221 ******************************************************************/
2222 
2223 --
2224 -- Cursor to fetch the Unit Offering Details
2225         CURSOR cur_uoo_id IS
2226         SELECT unit_cd, version_number, cal_type, ci_sequence_number
2227         FROM   igs_ps_unit_ofr_opt
2228         WHERE  uoo_id = p_uoo_id;
2229 
2230 
2231 -- Cursor to fetch the Cross faculty Element restrictions
2232         CURSOR c_cop (
2233                 cp_sca_coo_id           IGS_EN_STDNT_PS_ATT.coo_id%TYPE,
2234                 cp_cal_type             IGS_EN_STDNT_PS_ATT.cal_type%TYPE,
2235                 cp_ci_sequence_number   IGS_CA_INST.sequence_number%TYPE) IS
2236                 SELECT  cop.max_cross_faculty_cp,
2237                         cop.max_cross_mode_cp,
2238                         cop.max_cross_location_cp
2239                 FROM    IGS_PS_OFR_PAT  cop
2240                 WHERE   cop.coo_id = cp_sca_coo_id AND
2241                         cop.cal_type = cp_cal_type AND
2242                         cop.ci_sequence_number = cp_ci_sequence_number;
2243 
2244 -- Cursor to fetch the Student Unit Attempt Details. The cursor  queries all the Units that are attempted by the student
2245 -- in all the Teaching Calendars that are subordinate to the given Academic Calendar The cursor also selects only Unit Attempts
2246 -- that incur a Load in the given Load Calendar. IGS_EN_PRC_LOAD.ENRP_GET_LOAD_INCUR determines whether a nominated student unit
2247 -- attempt incurs load for a nominated load calendar.
2248 
2249   -- modified this cursor as a part of EN317 Build bug#4377985
2250   -- CURSOR c_sua_uv was modified to remove academic calendar instance relationship.
2251   -- Instead fetch all unit attempts which belong to the passed load calendar.
2252 
2253         CURSOR c_sua_uv (
2254                 cp_person_id                    IGS_EN_STDNT_PS_ATT.person_id%TYPE,
2255                 cp_course_cd                    IGS_EN_STDNT_PS_ATT.course_cd%TYPE,
2256                 cp_load_cal_type                  IGS_CA_INST.cal_type%TYPE, -- Load Cal
2257                 cp_load_ci_sequence_number           IGS_CA_INST.sequence_number%TYPE) IS-- Load Cal
2258                 SELECT DISTINCT  sua.unit_cd,
2259                         sua.version_number,
2260                         sua.cal_type,
2261                         sua.ci_sequence_number,
2262                         sua.uoo_id,
2263                         sua.administrative_unit_status,
2264                         sua.unit_attempt_status,
2265                         sua.override_enrolled_cp,
2266                         sua.override_eftsu,
2267                         sua.location_cd,
2268                         sua.unit_class,
2269                         sua.no_assessment_ind
2270                 FROM    igs_en_su_attempt       sua,
2271                         igs_ca_load_to_teach_v ltt
2272                 WHERE   sua.person_id = cp_person_id AND
2273                         sua.course_cd = cp_course_cd AND
2274                         sua.cal_type = ltt.teach_cal_type AND
2275                         sua.ci_sequence_number = ltt.teach_ci_sequence_number AND
2276                         ltt.load_cal_type = cp_load_cal_type  AND
2277                         ltt.load_ci_sequence_number = cp_load_ci_sequence_number AND
2278                          ((IGS_EN_PRC_LOAD.ENRP_GET_LOAD_INCUR(
2279                                                                 sua.cal_type,
2280                                                                 sua.ci_sequence_number,
2281                                                                 sua.discontinued_dt,
2282                                                                 sua.administrative_unit_status,
2283                                                                 sua.unit_attempt_status,
2284                                                                 sua.no_assessment_ind,
2285                                                                 cp_load_cal_type,
2286                                                                 cp_load_ci_sequence_number,
2287                                                                 -- anilk, Audit special fee build
2288                                                                 NULL, -- for p_uoo_id
2289                                                                 'N') = 'Y') OR
2290 /* added this for bug 3037043, as unit status would still waitlist when called from auto enroll process*/
2291                       (sua.uoo_id = p_uoo_id AND
2292                        sua.unit_attempt_status = 'WAITLISTED') ) AND
2293                         NVL(sua.no_assessment_ind ,'N') = 'N' ;
2294 
2295         CURSOR c_org_unit (cp_uoo_id igs_en_su_attempt_all.uoo_id%TYPE) IS
2296         SELECT  uop.owner_org_unit_cd,
2297                 ou.start_dt
2298         FROM   igs_ps_unit_ofr_opt_all   uop,
2299                igs_or_inst_org_base_v ou
2300         WHERE uop.uoo_id  = cp_uoo_id AND
2301                 uop.owner_org_unit_cd = ou.party_number AND
2302                 ou.inst_org_ind = 'O' ;
2303         c_org_unit_rec  c_org_unit%ROWTYPE;
2304 
2305 --
2306 -- Cursor to fetch the system Unit mode once the Unit class is provided.
2307         CURSOR c_um_ucl (
2308                 cp_sua_unit_class       IGS_EN_SU_ATTEMPT.unit_class%TYPE) IS
2309                 SELECT  um.s_unit_mode
2310                         FROM    IGS_AS_UNIT_MODE        um,
2311                         IGS_AS_UNIT_CLASS       ucl
2312                 WHERE   ucl.unit_class = cp_sua_unit_class AND
2313                         ucl.closed_ind = 'N'               AND
2314                         ucl.unit_mode = um.unit_mode;
2315 
2316 --
2317 -- Cursor to fetch the govt. Attendance mode from the user defined Attendance Mode. Government Attendance Mode of 1
2318 -- means ON CAMPUS , 2 means OFF CAMPUS and 3 means MIXED CAMPUS.
2319         CURSOR c_am ( cp_sca_attendance_mode    IGS_EN_STDNT_PS_ATT.attendance_mode%TYPE) IS
2320                 SELECT  am.govt_attendance_mode
2321                 FROM    IGS_EN_ATD_MODE am
2322                 WHERE   am.attendance_mode = cp_sca_attendance_mode;
2323 --
2324 -- Cursor to check if the Organization Unit associated with the Course is the same as the Organization associated with the Unit.
2325         CURSOR c_cow (cp_sca_course_cd          IGS_EN_STDNT_PS_ATT.course_cd%TYPE,
2326                 cp_sca_version_number           IGS_EN_STDNT_PS_ATT.version_number%TYPE,
2327                 cp_uv_owner_org_unit_cd         IGS_PS_UNIT_VER.owner_org_unit_cd%TYPE,
2328                 cp_uv_owner_ou_start_dt         IGS_PS_UNIT_VER.owner_ou_start_dt%TYPE) IS
2329                 SELECT  cow.course_cd,
2330                         cow.version_number,
2331                         cow.org_unit_cd,
2332                         cow.ou_start_dt
2333                 FROM    IGS_PS_OWN cow
2334                 WHERE   cow.course_cd = cp_sca_course_cd AND
2335                         cow.version_number = cp_sca_version_number AND
2336                         ((cow.org_unit_cd = cp_uv_owner_org_unit_cd AND
2337                         cow.ou_start_dt = cp_uv_owner_ou_start_dt) OR
2338                         (IGS_OR_GEN_001.ORGP_GET_WITHIN_OU(
2339                                         cow.org_unit_cd,
2340                                         cow.ou_start_dt,
2341                                         cp_uv_owner_org_unit_cd,
2342                                         cp_uv_owner_ou_start_dt,
2343                                         'N') = 'Y'));
2344 
2345  -- Cursor to get the assessment indicator value.
2346   CURSOR c_assessment IS
2347     SELECT no_assessment_ind
2348      FROM  igs_en_su_attempt
2349     WHERE  person_id = p_person_id
2350       AND  course_cd = p_course_cd
2351       AND  uoo_id = p_uoo_id;
2352  --
2353  -- Variables
2354  l_cop_cross_faculty_cp    IGS_PS_OFR_PAT.max_cross_faculty_cp%TYPE;
2355  l_cross_faculty_cp        IGS_PS_OFR_PAT.max_cross_faculty_cp%TYPE := 0;
2356  l_cop_cross_mode_cp       IGS_PS_OFR_PAT.max_cross_mode_cp%TYPE;
2357  l_cross_mode_cp           IGS_PS_OFR_PAT.max_cross_mode_cp%TYPE := 0 ;
2358  l_cop_cross_location_cp   IGS_PS_OFR_PAT.max_cross_location_cp%TYPE;
2359  l_cross_location_cp       IGS_PS_OFR_PAT.max_cross_location_cp%TYPE := 0;
2360  l_no_assessment_ind       igs_en_su_attempt.no_assessment_ind%TYPE;
2361 
2362  l_sua_cp                  IGS_PS_UNIT_VER.POINTS_MAX%TYPE;
2363  l_return_value            BOOLEAN;
2364  l_alternate_code          IGS_CA_INST.alternate_code%TYPE;
2365  l_override_limit          igs_pe_persenc_effct.restricted_enrolment_cp%TYPE;
2366  l_return_eftsu            NUMBER := 0;
2367  v_um_s_unit_mode          IGS_AS_UNIT_MODE.s_unit_mode%TYPE;
2368  v_am_govt_attendance_mode IGS_EN_ATD_MODE.govt_attendance_mode%TYPE;
2369 
2370  l_sca_course_cd          IGS_EN_STDNT_PS_ATT.course_cd%TYPE;
2371  l_sca_version_number     IGS_EN_STDNT_PS_ATT.version_number%TYPE;
2372  l_sca_location_cd        IGS_EN_STDNT_PS_ATT.location_cd%TYPE;
2373  l_sca_attendance_mode    IGS_EN_STDNT_PS_ATT.attendance_mode%TYPE;
2374  l_sca_coo_id             IGS_EN_STDNT_PS_ATT.coo_id%TYPE;
2375 
2376  l_cow_course_cd        IGS_PS_OWN.course_cd%TYPE;
2377  l_cow_version_number   IGS_PS_OWN.version_number%TYPE;
2378  l_cow_org_unit_cd      IGS_PS_OWN.org_unit_cd%TYPE;
2379  v_cow_ou_start_dt      IGS_PS_OWN.ou_start_dt%TYPE;
2380 
2381  l_acad_cal_type          IGS_CA_TYPE.CAL_TYPE%TYPE;
2382  l_acad_ci_sequence_number IGS_CA_INST.SEQUENCE_NUMBER%TYPE;
2383  l_acad_start_dt          IGS_CA_INST.START_DT%TYPE;
2384  l_acad_end_dt            IGS_CA_INST.END_DT%TYPE;
2385  l_acad_message           VARCHAR2(30);
2386  l_temp NUMBER := 0 ;
2387 --dummy variable to pick up audit, billing, enrolled credit points
2388 --due to signature change by EN308 Billing credit hours Bug 3782329
2389 l_audit_cp              IGS_PS_USEC_CPS.billing_credit_points%TYPE;
2390 l_billing_cp            IGS_PS_USEC_CPS.billing_hrs%TYPE;
2391 l_enrolled_cp   IGS_PS_UNIT_VER.enrolled_credit_points%TYPE;
2392 
2393 l_message            VARCHAR2(2000);
2394 l_message_text       VARCHAR2(2000);
2395 l_message_icon       VARCHAR2(1);
2396 l_token_value        IGS_PS_OFR_PAT.max_cross_location_cp%TYPE;
2397 BEGIN
2398 
2399 -- This module validates that the student hasn't breached any of  the cross-element restrictions held against the
2400 -- course-offering pattern for the specified academic period.
2401 
2402 --
2403 -- Set the default message number
2404 p_message := null;
2405 
2406   OPEN c_assessment;
2407   FETCH c_assessment INTO l_no_assessment_ind;
2408   CLOSE c_assessment;
2409 
2410     -- Checking if the unit section attempt is an audit attempt, if it is then the function will return TRUE
2411   IF l_no_assessment_ind = 'Y' THEN
2412       RETURN TRUE;
2413   END IF;
2414 
2415 -- Check if the step is overridden
2416   l_return_value := igs_en_gen_015.validation_step_is_overridden ( p_eligibility_step_type => p_eligibility_step_type  ,
2417                                                                    p_load_cal_type         => p_load_cal_type,
2421                                                                    p_step_override_limit   => l_override_limit
2418                                                                    p_load_cal_seq_number   => p_load_ci_sequence_number,
2419                                                                    p_person_id             => p_person_id,
2420                                                                    p_uoo_id                => p_uoo_id,
2422                                                                  );
2423   IF l_return_value = TRUE THEN
2424       RETURN TRUE;
2425   END IF;
2426 
2427   -- Get student course attempt detail
2428 
2429   l_sca_coo_id := igs_en_spa_terms_api.get_spat_coo_id( p_person_id => p_person_id,
2430                         p_program_cd => p_course_cd,
2431                         p_term_cal_type => p_load_cal_type,
2432                         p_term_sequence_number => p_load_ci_sequence_number);
2433   l_sca_location_cd := igs_en_spa_terms_api.get_spat_location( p_person_id => p_person_id,
2434                                 p_program_cd => p_course_cd,
2435                                 p_term_cal_type => p_load_cal_type,
2436                                 p_term_sequence_number => p_load_ci_sequence_number);
2437   l_sca_attendance_mode := igs_en_spa_terms_api.get_spat_att_mode( p_person_id => p_person_id,
2438                                 p_program_cd => p_course_cd,
2439                                 p_term_cal_type => p_load_cal_type,
2440                                 p_term_sequence_number => p_load_ci_sequence_number);
2441   l_sca_version_number := igs_en_spa_terms_api.get_spat_program_version( p_person_id => p_person_id,
2442                                 p_program_cd => p_course_cd,
2443                                 p_term_cal_type => p_load_cal_type,
2444                                 p_term_sequence_number => p_load_ci_sequence_number);
2445   IF (l_sca_coo_id IS NULL AND l_sca_location_cd IS NULL
2446       AND l_sca_attendance_mode IS NULL AND l_sca_version_number IS NULL) THEN
2447         RETURN TRUE;
2448   ELSE
2449         l_sca_course_cd := p_course_cd;
2450   END IF;
2451   -- Get the academic calendar of the given Load Calendar
2452   l_alternate_code := Igs_En_Gen_002.Enrp_Get_Acad_Alt_Cd(
2453                         p_cal_type                => p_load_cal_type,
2454                         p_ci_sequence_number      => p_load_ci_sequence_number,
2455                         p_acad_cal_type           => l_acad_cal_type,
2456                         p_acad_ci_sequence_number => l_acad_ci_sequence_number,
2457                         p_acad_ci_start_dt        => l_acad_start_dt,
2458                         p_acad_ci_end_dt          => l_acad_end_dt,
2459                         p_message_name            => l_acad_message );
2460 
2461 
2462   -- Get the course offering pattern detail for the specified  academic period.
2463   --
2464   OPEN  c_cop(l_sca_coo_id, L_acad_cal_type, l_acad_ci_sequence_number);
2465   FETCH c_cop   INTO    l_cop_cross_faculty_cp,
2466                         l_cop_cross_mode_cp,
2467                         l_cop_cross_location_cp;
2468   IF (c_cop%NOTFOUND) THEN
2469         -- no IGS_PS_OFR_PAT records found
2470         CLOSE   c_cop;
2471         RETURN TRUE;
2472   END IF;
2473   CLOSE c_cop;
2474 
2475   --If Cross Location /Faculty  / Mode Credit points are mentioned as zero , it means that Cross Credit points are not allowed totally.
2476   -- The function should not return True in this scenario.
2477 
2478   IF ((l_cop_cross_location_cp IS NULL)) AND p_eligibility_step_type = 'CROSS_LOC'  THEN
2479         RETURN TRUE;
2480   ELSIF ((l_cop_cross_mode_cp IS NULL)) AND p_eligibility_step_type = 'CROSS_MOD'  THEN
2481         RETURN TRUE;
2482   ELSIF ((l_cop_cross_faculty_cp IS NULL)) AND  p_eligibility_step_type = 'CROSS_FAC'  THEN
2483         RETURN TRUE;
2484   END IF;
2485 
2486 -- removed by ckasu as apart of bug#4377985   IF ( l_acad_cal_type IS NOT NULL AND l_acad_ci_sequence_number IS NOT NULL) THEN
2487                 FOR v_sua_uv_row IN c_sua_uv(
2488                                 p_person_id,
2489                                 p_course_cd,
2490                                 p_load_cal_type,
2491                                 p_load_ci_sequence_number) LOOP
2492 
2493                         -- Call routine to get the load for the SUA within the 'working' load calendar instance.
2494                         l_sua_cp := IGS_EN_PRC_LOAD.enrp_clc_sua_load(
2495                                         v_sua_uv_row.unit_cd,
2496                                         v_sua_uv_row.version_number,
2497                                         v_sua_uv_row.cal_type,
2498                                         v_sua_uv_row.ci_sequence_number,
2499                                         p_load_cal_type,
2500                                         p_load_ci_sequence_number,
2501                                         v_sua_uv_row.override_enrolled_cp,
2502                                         v_sua_uv_row.override_eftsu,
2503                                         l_return_eftsu,
2504                                         p_uoo_id,
2505                                         -- anilk, Audit special fee build
2506                                         'N',
2507                                         p_audit_cp => l_audit_cp,
2508                                         p_billing_cp => l_billing_cp,
2509                                         p_enrolled_cp => l_enrolled_cp);
2510 
2511                         IF p_eligibility_step_type = 'CROSS_LOC' THEN
2512                                 --
2513                                 -- If the UA is cross location then add to cross location CP total.
2514                                 IF (v_sua_uv_row.location_cd <> l_sca_location_cd) THEN
2515 
2516                                         IF p_uoo_id = v_sua_uv_row.uoo_id and p_upd_cp IS NOT NULL THEN
2520                                         END IF;
2517                                                 l_cross_location_cp := l_cross_location_cp + NVL(p_upd_cp ,NVL( l_sua_cp,0)) ;
2518                                         ELSE
2519                                                 l_cross_location_cp := l_cross_location_cp + l_sua_cp;
2521 
2522                                 END IF;
2523 
2524                         ELSIF p_eligibility_step_type = 'CROSS_MOD' THEN
2525 
2526                                 OPEN    c_um_ucl(v_sua_uv_row.unit_class);
2527                                 FETCH   c_um_ucl        INTO    v_um_s_unit_mode;
2528                                 CLOSE   c_um_ucl;
2529 
2530                                 OPEN    c_am(l_sca_attendance_mode);
2531                                 FETCH   c_am            INTO    v_am_govt_attendance_mode;
2532                                 CLOSE   c_am;
2533 
2534                                 IF ((v_um_s_unit_mode = 'ON' AND
2535                                                 v_am_govt_attendance_mode <> '1' AND
2536                                                 v_am_govt_attendance_mode <> '3') OR
2537                                                 (v_um_s_unit_mode = 'OFF' AND
2538                                                 v_am_govt_attendance_mode <> '2' AND
2539                                                 v_am_govt_attendance_mode <> '3')) THEN
2540 
2541                                         IF p_uoo_id = v_sua_uv_row.uoo_id and p_upd_cp IS NOT NULL THEN
2542 
2543                                                 l_cross_mode_cp := l_cross_mode_cp +  NVL(p_upd_cp ,NVL( l_sua_cp,0)) ;
2544                                         ELSE
2545 
2546                                                 l_cross_mode_cp := l_cross_mode_cp + l_sua_cp ;
2547                                         END IF;
2548                                 END IF;
2549 
2550                         ELSIF p_eligibility_step_type = 'CROSS_FAC' THEN
2551 
2552                                 -- If the UA is cross faculty then add to cross faculty CP total.
2553                                 -- This is dome by checking whether the unit version ownership
2554                                 -- is within any of the course ownership OUs.
2555                                 c_org_unit_rec := NULL;
2556                                 OPEN c_org_unit (v_sua_uv_row.uoo_id);
2557                                 FETCH c_org_unit INTO c_org_unit_rec;
2558                                 CLOSE c_org_unit;
2559 
2560                                 OPEN    c_cow(
2561                                                 l_sca_course_cd,
2562                                                 l_sca_version_number,
2563                                                 c_org_unit_rec.owner_org_unit_cd,
2564                                                 c_org_unit_rec.start_dt);
2565                                 FETCH   c_cow   INTO    l_cow_course_cd,
2566                                                         l_cow_version_number,
2567                                                         l_cow_org_unit_cd,
2568                                                         v_cow_ou_start_dt;
2569                                 IF (c_cow%NOTFOUND) THEN
2570                                         IF p_uoo_id = v_sua_uv_row.uoo_id and p_upd_cp IS NOT NULL THEN
2571 
2572                                                 l_cross_faculty_cp := l_cross_faculty_cp + NVL(p_upd_cp ,NVL( l_sua_cp,0)) ;
2573                                         ELSE
2574                                                 l_cross_faculty_cp := l_cross_faculty_cp + l_sua_cp;
2575 
2576                                         END IF;
2577                                 END IF;
2578                                 CLOSE   c_cow;
2579                         END IF;
2580                 END LOOP;
2581 
2582 
2583     IF p_eligibility_step_type = 'CROSS_LOC' AND l_cross_location_cp  <=  l_cop_cross_location_cp THEN
2584       RETURN TRUE;
2585     ELSIF p_eligibility_step_type = 'CROSS_MOD' AND l_cross_mode_cp  <=  l_cop_cross_mode_cp THEN
2586       RETURN TRUE;
2587     ELSIF p_eligibility_step_type = 'CROSS_FAC' AND l_cross_faculty_cp  <=  l_cop_cross_faculty_cp THEN
2588       RETURN TRUE;
2589     END IF;
2590 
2591     -- code modfied by ckasu as a part of EN317 SS UI Build bug#4377985
2592 
2593     IF p_deny_warn = 'WARN' AND p_eligibility_step_type = 'CROSS_LOC' THEN
2594           IF p_calling_obj = 'JOB' THEN
2595                     l_message := 'IGS_EN_CROSS_LOC_WARN';
2596           ELSE
2597                     l_message := 'IGS_EN_CRSLOC_TAB_WARN';
2598                     l_token_value := l_cop_cross_location_cp;
2599           END IF;
2600 
2601     ELSIF p_deny_warn = 'DENY' AND p_eligibility_step_type = 'CROSS_LOC' THEN
2602 
2603       IF p_calling_obj = 'SCH_UPD' THEN
2604                     l_message := 'IGS_EN_CRSLOC_UPD_DENY'  ||'*'||l_cop_cross_location_cp;
2605        ELSIF p_calling_obj = 'JOB' THEN
2606                     l_message := 'IGS_EN_STUD_MNY_CRS_LOCCRDPNT';
2607        ELSE
2608                     l_message := 'IGS_EN_CRSLOC_TAB_DENY';
2609                     l_token_value := l_cop_cross_location_cp;
2610        END IF; -- end of p_calling_obj = 'SCH_UPD'
2611 
2612     ELSIF p_deny_warn = 'WARN' AND p_eligibility_step_type = 'CROSS_MOD' THEN
2613          IF p_calling_obj = 'JOB' THEN
2614                     l_message := 'IGS_EN_CROSS_MOD_WARN';
2615          ELSE
2616                     l_message := 'IGS_EN_CRSMOD_TAB_WARN';
2617                     l_token_value := l_cop_cross_mode_cp;
2618          END IF;
2619     ELSIF p_deny_warn = 'DENY' AND p_eligibility_step_type = 'CROSS_MOD' THEN
2620 
2621        IF p_calling_obj = 'SCH_UPD' THEN
2622                     l_message := 'IGS_EN_CRSMOD_UPD_DENY'  ||'*'||l_cop_cross_mode_cp;
2623        ELSIF p_calling_obj = 'JOB' THEN
2624                     l_message := 'IGS_EN_STUD_MNY_CRS_MODECRDPN';
2625         ELSE
2626                     l_message := 'IGS_EN_CRSMOD_TAB_DENY';
2627                     l_token_value := l_cop_cross_mode_cp;
2628        END IF; -- end of p_calling_obj = 'SCH_UPD'
2629 
2630 
2631     ELSIF p_deny_warn = 'WARN' AND p_eligibility_step_type = 'CROSS_FAC' THEN
2632         IF p_calling_obj = 'JOB' THEN
2633                     l_message := 'IGS_EN_CROSS_FAC_WARN';
2634         ELSE
2635                     l_message := 'IGS_EN_CRSFAC_TAB_WARN';
2636                     l_token_value := l_cop_cross_faculty_cp;
2637         END IF;
2638     ELSIF p_deny_warn = 'DENY' AND p_eligibility_step_type = 'CROSS_FAC' THEN
2639 
2640        IF p_calling_obj = 'SCH_UPD' THEN
2641                     l_message := 'IGS_EN_CRSFAC_UPD_DENY' ||'*'||l_cop_cross_faculty_cp;
2642        ELSIF p_calling_obj = 'JOB' THEN
2643                     l_message := 'IGS_EN_STUD_MNY_CRSFACCRDPNT';
2644        ELSE
2645                     l_message := 'IGS_EN_CRSFAC_TAB_DENY';
2646                     l_token_value := l_cop_cross_faculty_cp;
2647        END IF; -- end of p_calling_obj = 'SCH_UPD'
2648 
2649     END IF; -- end of p_deny_warn = 'WARN' AND p_eligibility_step_type = 'CROSS_LOC' IF THEN
2650 
2651     IF p_calling_obj NOT IN ('JOB','SCH_UPD') THEN
2652 
2653        l_message_icon := substr(p_deny_warn,1,1);
2654        -- create a warnings record
2655        IGS_EN_DROP_UNITS_API.create_ss_warning(p_person_id               => p_person_id,
2656                                              p_course_cd                        => p_course_cd,
2657                                              p_term_cal_type                => p_load_cal_type,
2658                                              p_term_ci_sequence_number      => p_load_ci_sequence_number,
2659                                              p_uoo_id                               => p_uoo_id,
2660                                              p_message_for                      => igs_ss_enroll_pkg.enrf_get_lookup_meaning(p_eligibility_step_type,'ENROLMENT_STEP_TYPE_EXT'),
2661                                              p_message_icon                         => l_message_icon,
2662                                              p_message_name                         => l_message,
2663                                              p_message_rule_text                => NULL,
2664                                              p_message_tokens                   => 'UNIT_CD:'||l_token_value||';',
2665                                              p_message_action                   => NULL,
2666                                              p_destination                          => NULL,
2667                                              p_parameters                           => NULL,
2668                                              p_step_type                            => 'PROGRAM');
2669 
2670     ELSE
2671        p_message :=  l_message;
2672     END IF; -- end of p_calling_obj NOT IN ('JOB','SCH_UPD') if then
2673 
2674 
2675 
2676     RETURN FALSE;
2677 
2678   END eval_cross_validation;
2679 
2680 FUNCTION get_applied_min_cp (
2681                        p_person_id            IN NUMBER,
2682                        p_term_cal_type        IN VARCHAR2,
2683                        p_term_sequence_number IN NUMBER,
2684                        p_program_cd           IN VARCHAR2,
2685                        p_program_version      IN VARCHAR2
2686                     ) RETURN NUMBER AS
2687   l_message VARCHAR2(300);
2688   l_min_cp_allowed NUMBER;
2689 BEGIN
2690   l_min_cp_allowed := calc_min_cp (
2691                             p_person_id                    => p_person_id ,
2692                             p_load_calendar_type           => p_term_cal_type,
2693                             p_load_cal_sequence_number     => p_term_sequence_number,
2694                             p_uoo_id                       => NULL,
2695                             p_program_cd                   => p_program_cd,
2696                             p_program_version              => p_program_version ,
2697                             p_message                      => l_message);
2698   RETURN l_min_cp_allowed;
2699 
2700 END get_applied_min_cp;
2701 
2702 FUNCTION get_applied_max_cp (
2703                        p_person_id            IN NUMBER,
2704                        p_term_cal_type        IN VARCHAR2,
2705                        p_term_sequence_number IN NUMBER,
2706                        p_program_cd           IN VARCHAR2,
2707                        p_program_version      IN VARCHAR2
2708                     ) RETURN NUMBER AS
2709   l_message VARCHAR2(300);
2710   l_max_cp_allowed NUMBER;
2711 BEGIN
2712   l_max_cp_allowed := calc_max_cp (
2713                             p_person_id                    => p_person_id ,
2714                             p_load_calendar_type           => p_term_cal_type,
2715                             p_load_cal_sequence_number     => p_term_sequence_number,
2716                             p_uoo_id                       => NULL,
2717                             p_program_cd                   => p_program_cd,
2718                             p_program_version              => p_program_version ,
2719                             p_message                      => l_message);
2720   RETURN l_max_cp_allowed;
2721 
2722 END get_applied_max_cp;
2723 
2724 
2725 -- end of package
2726 END igs_en_elgbl_program ;