DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_EN_ELGBL_PERSON

Source


1 PACKAGE BODY IGS_EN_ELGBL_PERSON AS
2 /* $Header: IGSEN78B.pls 120.10 2006/09/19 12:15:35 amuthu ship $ */
3 
4  ------------------------------------------------------------------------------------
5   --Created by  : smanglm ( Oracle IDC)
6   --Date created: 19-JUN-2001
7   --
8   --Purpose:  Created as part of the build for DLD Enrollment Setup : Eligibility and Validation
9   --          This package deals with the holds and person step validation. It has following
10   --          functions:
11   --             i)  eval_deny_all_hold - Validate Deny All Enrollment Hold
12   --                 one local function vald_deny_all_hold
13   --            ii)  eval_person_steps - Validate Person Steps
14   --                 one local function vald_person_steps
15   --           iii)  eval_timeslot - Validate Time Slot - Person Level
16   --                 one local function - vald_timeslot
17   --            iv)  a private function get_sys_pers_type - Returns System Person Type
18   --
19   --Known limitations/enhancements and/or remarks:
20   --
21   --Change History:
22   --Who         When           What
23   --Nishikant   01NOV2002      SEVIS Build. Enh Bug#2641905.
24   --                           The notification flag was being fetched from cursor earlier. now its
25   --                           modified to call the function igs_ss_enr_details.get_notification,
26   --                           to get the value for it and to make the way common across all the packages.
27   --
28   --ayedubat    24-JUN-2002    Modified the function,vald_person_steps for the bug fix: 2427528
29   --Bayadav     23-OCT-2001    Modified eval_timeslot procedure as a part of self service dld-2043044
30   --Nalin Kumar  14-May-2002   Modified the 'get_sys_pers_type' function as per the Bug# 2364461.
31   --                           Removed the code logic to check the whether the
32   --                           passed person type is not a system person type or not.
33   --kkillams    20-01-2003      New procedure eval_ss_deny_all_hold and get_enrl_comm_type are added,
34   --                            eval_ss_deny_all_hold is a wrapper procedure to eval_deny_all_hold function
35   --                            for self service purpose
36   --                            get_enrl_comm_type procedure will derives the enrollment category type and
37   --                            enrollment commencement type  w.r.t bug 2737703
38   --svenkata    19-jun-2003	Changed the refernce to lookup code from CHK_TIME_UNT to CHK_TIME_UNIT. Bug 2829272
39   --vkarthik    1-Jul-2004	Initialized variable l_hold_override to NULL
40   --				inside the loop in the function ald_deny_all_hold local to eval_deny_all_hold
41   --				for Bug 3449582
42   -- smaddali   19-sep-04       Modified procedure eval_deny_all_hold for bug#3930876
43   -- rvangala   16-Jul-2005     Logging error/warnings to warnings table
44   --                            Created private function create_ss_warning, for Build #4377985
45   -- bdeviset   09-SEP-2005     Modified the if condition related census date and hold start/end date in vald_deny_all_hold
46   --                            for bug# 4590555
47   -- ckasu      15-SEP-2005     Modified eval_person_Steps inoder to delete the warnings/error messages indorder to create
48   --                            them during this run as a part  EN318 SS UI Admin Impact Build bug #4402631
49   -- jnalam      15-NOV-2005     Modified c_intmsn_details for 4726839
50   -- amuthu     18-Sep-2006     Added new function eval_rev_sus_all_hold
51   -------------------------------------------------------------------------------------
52 
53 --
54 -- forward declaration for function get_sys_pers_type
55 --
56 FUNCTION get_sys_pers_type (
57                               p_person_type                     IN  VARCHAR2,
58                               p_message                        OUT NOCOPY  VARCHAR2
59                             )
60 RETURN VARCHAR2;
61 
62 FUNCTION eval_deny_all_hold (
63                               p_person_id                       IN  NUMBER,
64                               p_person_type                     IN  VARCHAR2,
65                               p_load_calendar_type              IN  VARCHAR2,
66                               p_load_cal_sequence_number        IN  NUMBER,
67                               p_enrollment_category             IN  VARCHAR2,
68                               p_comm_type                       IN  VARCHAR2,
69                               p_enrl_method                     IN  VARCHAR2,
70                               p_message                        OUT NOCOPY  VARCHAR2
71                             )
72  RETURN BOOLEAN
73  IS
74 
75  ------------------------------------------------------------------------------------
76   --Created by  : smanglm ( Oracle IDC)
77   --Date created: 19-JUN-2001
78   --
79   --Purpose:  Created as part of the build for DLD Enrollment Setup : Eligibility and Validation
80   --          This function will check whether a hold with Deny All Enrollment acticity effect
81   --          exists for the student or not. If yes, whether the hold is overridden or not. If not,
82   --          validates the effective hold dates with the census date of Term/Teaching period.
83   --          If the hold is effective on the census date then it returns False, meaning the
84   --          student has some advising hold in the teaching period or term in which he is going
85   --          to enroll
86   --
87   --
88   --Known limitations/enhancements and/or remarks:
89   --
90   --Change History:
91   --Who         When            What
92   -- smaddali 19-sep-04  For bug#3930876, removed the condition if l_person_type is not NULL and replaced it with p_person_type
93   --                      before deriving the system person type, since this is a local variable
94   -------------------------------------------------------------------------------------
95 
96     l_enr_method_type     igs_en_method_type.enr_method_type%TYPE;
97 
98     --
99     -- cursor to check whether the CHKENCUMB is overridden or not
100     --
101     CURSOR c_chkencumb_override (cp_person_type igs_pe_usr_aval.person_type%TYPE) IS
102            SELECT 'Y'
103            FROM    igs_pe_usr_aval
104            WHERE   validation = 'CHKENCUMB'
105            AND     override_ind = 'Y'
106            AND     person_type = cp_person_type;
107     l_chkencumb_override    VARCHAR2(1) ;
108 
109     l_deny_all_hold   BOOLEAN;
110     l_step_override   BOOLEAN;
111 
112     l_step_override_limit  igs_en_elgb_ovr_step.step_override_limit%TYPE;
113 
114     l_person_type          igs_pe_person_types.person_type_code%TYPE;
115 
116     FUNCTION vald_deny_all_hold
117     RETURN BOOLEAN
118     IS
119 
120     ------------------------------------------------------------------------------------
121     --Created by  : smanglm ( Oracle IDC)
122     --Date created: 19-JUN-2001
123     --
124     --Purpose:  local program unit to function eval_deny_all_hold
125     --          This function will check if deny all hold effect is associated with the Hold or not
126     --          and check if the hold is effective. If any of the hold type with deny all enrollment
127     --          activity is effective return FALSE
128     --
129     --
130     --Known limitations/enhancements and/or remarks:
131     --
132     --Change History:
133     --Who         When            What
134     -------------------------------------------------------------------------------------
135 
136       --
137       -- cursor to fecth all the holds of the student which has the hold effect of Deny all
138       -- enrolment activity
139       --
140       CURSOR c_holds (cp_person_id igs_pe_pers_encumb.person_id%TYPE) IS
141              SELECT   ppe.person_id,
142                       ppe.encumbrance_type,
143                       peff.pee_start_dt hold_start_dt,
144                       peff.expiry_dt
145              FROM     igs_pe_pers_encumb ppe,
146                       igs_pe_persenc_effct peff
147              WHERE    ppe.person_id = peff.person_id
148              AND      ppe.encumbrance_type = peff.encumbrance_type
149              AND      ppe.start_dt=peff.pen_start_dt
150              AND      peff.s_encmb_effect_type = 'DENY_EACT'
151              AND      ppe.person_id = cp_person_id;
152       rec_holds       c_holds%ROWTYPE;
153 
154       --
155       -- cursor to check whether the particular hold type for a person in a given term/teaching period
156       -- is overridden or not
157       --
158       CURSOR c_hold_override (cp_person_id   igs_en_elgb_ovr_all.person_id%TYPE,
159                               cp_hold_type   igs_pe_hold_rel_ovr.hold_type%TYPE) IS
160              SELECT hro.hold_rel_or_ovr
161              FROM   igs_en_elgb_ovr_all eoa,
162                     igs_pe_hold_rel_ovr hro
163              WHERE  eoa.elgb_override_id = hro.elgb_override_id
164              AND    eoa.person_id = cp_person_id
165              AND    eoa.cal_type = p_load_calendar_type
166              AND    eoa.ci_sequence_number = p_load_cal_sequence_number
167              AND    hro.hold_type = cp_hold_type;
168       l_hold_override    igs_pe_hold_rel_ovr.hold_rel_or_ovr%TYPE;
169 
170       l_census_date      DATE;
171 
172     BEGIN
173       --
174       -- open the cursor c_hold to get the holds on a student which deny all enrl activity effect
175       --
176       FOR rec_holds IN c_holds (p_person_id)
177       LOOP
178         --
179         -- check whether the hold is oevrridden for the student in the given load calendar/teaching period
180         --
181 	-- initializing l_hold_override for Bug 3449582
182         l_hold_override := NULL;
183 	OPEN c_hold_override (p_person_id, rec_holds.encumbrance_type);
184         FETCH c_hold_override INTO l_hold_override;
185         CLOSE c_hold_override;
186 
187         --
188         -- if the hold type is not overridden i.e. l_hold_override <> 'O', check whether the sysdate
189         -- is greater then hold start date and  less than hold expiry date or hold expiry date is null
190 
191 	      IF nvl(l_hold_override,'Z') <> 'O' THEN
192                /*    --
193                    -- get the effective date for checking the hold
194                    --
195 
196              l_census_date := igs_en_gen_015.get_effective_census_date
197                                                 (
198                                                   p_load_cal_type                => p_load_calendar_type,
199                                                   p_load_cal_seq_number          => p_load_cal_sequence_number,
200                                                   p_teach_cal_type               => NULL,
201                                                   p_teach_cal_seq_number         => NULL
202                                                 );    */
203 
204            IF  ((SYSDATE >= rec_holds.hold_start_dt)  AND
205                 ( rec_holds.expiry_dt IS NULL OR (SYSDATE < rec_holds.expiry_dt) )) THEN
206                p_message := 'IGS_EN_ADV_HOLD';
207 
208 	          RETURN FALSE;
209            END IF;
210         END IF;
211       END LOOP;
212       --
213       -- the student does not have any hold with the deny all enrollment activity as cursor fetched zero records
214       -- hence return TRUE
215       --
216       RETURN TRUE;
217     END vald_deny_all_hold;
218 
219 
220 
221   --
222   -- main begin for eval_deny_all_hold
223   --
224   BEGIN
225     --
226     -- assign the p_enrl_method to l_enr_method_type
227     --
228     l_enr_method_type := p_enrl_method;
229 
230     -- smaddali For bug#3930876, removed the condition if l_person_type is not NULL
231     --    before deriving the system person type, since this is a local variable which will always be null
232     -- get the system person type
233     --
234     IF p_person_type IS NOT NULL THEN
235           l_person_type := get_sys_pers_type (
236                                         p_person_type => p_person_type,
237                                         p_message     => p_message
238                                       );
239     END IF;
240     IF p_message IS NOT NULL THEN
241        RETURN FALSE;
242     END IF;
243 
244 
245     --
246     -- person type is STUDENT
247     -- make a call to procedure to see whether the step is overriden or not
248     --
249     l_step_override := igs_en_gen_015.validation_step_is_overridden
250                                  (
251                                    p_eligibility_step_type        => 'CHKENCUMB',
252                                    p_load_cal_type                => p_load_calendar_type,
253                                    p_load_cal_seq_number          => p_load_cal_sequence_number,
254                                    p_person_id                    => p_person_id,
255                                    p_uoo_id                       => NULL,
256                                    p_step_override_limit          => l_step_override_limit
257                                 );
258     IF l_step_override THEN
259       --
260       -- return TRUE if the step is overridden for the passed person_type
261       --
262       RETURN TRUE;
263     END IF;
264 
265 
266     --
267     -- check for the person type passed. If it is not student, check whether CHKENCUMB is overridden or not
268     -- for passed person type
269     --
270     IF l_person_type <> 'STUDENT' THEN
271        --
272        -- open cursor c_chkencumb_override and see whether the CHKEMCUMB is oevrriden or not for the passed
273        -- person_type
274        --
275        l_chkencumb_override := 'N';
276        OPEN c_chkencumb_override (p_person_type);
277        FETCH c_chkencumb_override INTO l_chkencumb_override;
278        CLOSE c_chkencumb_override;
279        IF l_chkencumb_override = 'Y' THEN
280           --
281           -- return TRUE if the step is overridden for the passed person_type
282           --
283           RETURN TRUE;
284        END IF;
285     END IF; -- check for person type
286 
287     -- now do validation of Deny All Enrollment Activity Hold
288     -- call the function vald_deny_all_hold
289     --
290     l_deny_all_hold := vald_deny_all_hold;
291 
292     --
293     -- depending on the return value of l_deny_all_hold, return from the main function
294     --
295     IF l_deny_all_hold THEN
296        --
297        -- validation of Deny All Enrollment Activity Hold returns TRUE
298        --
299        RETURN TRUE;
300     ELSIF NOT l_deny_all_hold THEN
301        --
302        -- validation of Deny All Enrollment Activity Hold returns FALSE
303        -- and the p_message has been assigned message in the vald_deny_all_hold
304        -- program unit, hence just return FALSE
305        --
306        RETURN FALSE;
307     END IF;
308     RETURN TRUE;
309   END eval_deny_all_hold;
310 
311 
312 FUNCTION eval_ss_rev_sus_all_hold (
313                               p_person_id                       IN  NUMBER,
314                               p_course_cd                       IN  VARCHAR2,
315                               p_person_type                     IN  VARCHAR2,
316                               p_load_calendar_type              IN  VARCHAR2,
317                               p_load_cal_sequence_number        IN  NUMBER,
318                               p_message                        OUT NOCOPY  VARCHAR2
319                             )
320  RETURN BOOLEAN
321  IS
322 
323  ------------------------------------------------------------------------------------
324   --Created by  : smanglm ( Oracle IDC)
325   --Date created: 19-JUN-2001
326   --
327   --Purpose:  Created as part of the build for DLD Enrollment Setup : Eligibility and Validation
328   --          This function will check whether a hold with revoke/susped all services effect
329   --          exists for the student or not. If yes, whether the hold is overridden or not. If not,
330   --
331   --
332   --Known limitations/enhancements and/or remarks:
333   --
334   --Change History:
335   --Who         When            What
336   -------------------------------------------------------------------------------------
337 
338     l_enr_method_type     igs_en_method_type.enr_method_type%TYPE;
339 
340     CURSOR get_enr_method IS
341     SELECT enr_method_type FROM igs_en_method_type
342     WHERE self_service = 'Y'
343     AND   closed_ind = 'N';
347     --
344 
345     --
346     -- cursor to check whether the CHKENCUMB is overridden or not
348     CURSOR c_chkencumb_override (cp_person_type igs_pe_usr_aval.person_type%TYPE) IS
349            SELECT 'Y'
350            FROM    igs_pe_usr_aval
351            WHERE   validation = 'CHKENCUMB'
352            AND     override_ind = 'Y'
353            AND     person_type = cp_person_type;
354     l_chkencumb_override    VARCHAR2(1) ;
355 
356     l_deny_all_hold   BOOLEAN;
357     l_step_override   BOOLEAN;
358 
359     l_step_override_limit  igs_en_elgb_ovr_step.step_override_limit%TYPE;
360 
361     l_person_type          igs_pe_person_types.person_type_code%TYPE;
362 
363     FUNCTION vald_rev_sus_hold
364     RETURN BOOLEAN
365     IS
366 
367     ------------------------------------------------------------------------------------
368     --Created by  : smanglm ( Oracle IDC)
369     --Date created: 19-JUN-2001
370     --
371     --Purpose:  local program unit to function eval_deny_all_hold
372     --          This function will check if deny all hold effect is associated with the Hold or not
373     --          and check if the hold is effective. If any of the hold type with deny all enrollment
374     --          activity is effective return FALSE
375     --
376     --
377     --Known limitations/enhancements and/or remarks:
378     --
379     --Change History:
380     --Who         When            What
381     -------------------------------------------------------------------------------------
382 
383       --
384       -- cursor to fecth all the holds of the student which has the hold effect of Deny all
385       -- enrolment activity
386       --
387       CURSOR c_holds ( cp_person_id hz_parties.party_id%TYPE ) IS
388                 SELECT  ppe.person_id,
389                         ppe.encumbrance_type,
390                         peff.pee_start_dt hold_start_dt,
391                         peff.expiry_dt
392                 FROM    igs_pe_pers_encumb ppe,
393                         IGS_PE_PERSENC_EFFCT peff
394                 WHERE   ppe.encumbrance_type = peff.encumbrance_type
395                 AND     ppe.start_dt=peff.pen_start_dt
396                 AND     s_encmb_effect_type in ('SUS_SRVC','RVK_SRVC')
397                 AND     ppe.person_id = cp_person_id;
398 
399       --
400       -- cursor to check whether the particular hold type for a person in a given term/teaching period
401       -- is overridden or not
402       --
403       CURSOR c_hold_override (cp_person_id   igs_en_elgb_ovr_all.person_id%TYPE,
404                               cp_hold_type   igs_pe_hold_rel_ovr.hold_type%TYPE) IS
405              SELECT hro.hold_rel_or_ovr
406              FROM   igs_en_elgb_ovr_all eoa,
407                     igs_pe_hold_rel_ovr hro
408              WHERE  eoa.elgb_override_id = hro.elgb_override_id
409              AND    eoa.person_id = cp_person_id
410              AND    eoa.cal_type = p_load_calendar_type
411              AND    eoa.ci_sequence_number = p_load_cal_sequence_number
412              AND    hro.hold_type = cp_hold_type;
413       l_hold_override    igs_pe_hold_rel_ovr.hold_rel_or_ovr%TYPE;
414 
415       l_message_name     VARCHAR2(30);
416 
417     BEGIN
418       --
419       -- open the cursor c_hold to get the holds on a student which deny all enrl activity effect
420       --
421       FOR rec_holds IN c_holds (p_person_id)
422       LOOP
423         --
424         -- check whether the hold is oevrridden for the student in the given load calendar/teaching period
425         --
426 	-- initializing l_hold_override for Bug 3449582
427         l_hold_override := NULL;
428         OPEN c_hold_override (p_person_id, rec_holds.encumbrance_type);
429         FETCH c_hold_override INTO l_hold_override;
430         CLOSE c_hold_override;
431 
432         --
433         -- if the hold type is not overridden i.e. l_hold_override <> 'O', check whether the sysdate
434         -- is greater then hold start date and  less than hold expiry date or hold expiry date is null
435 
436         IF nvl(l_hold_override,'Z') <> 'O' THEN
437 
438           IF NOT IGS_EN_VAL_ENCMB.enrp_val_excld_prsn(
439                                            p_person_id           => p_person_id,
440                                            p_course_cd           => p_course_cd,
441                                            p_effective_dt        => SYSDATE,
442                                            p_message_name        => p_message
443                                           ) THEN
444 
445             RETURN FALSE;
446 
447            END IF;
448         END IF;
449       END LOOP;
450       --
451       -- the student does not have any hold with the deny all enrollment activity as cursor fetched zero records
452       -- hence return TRUE
453       --
454       RETURN TRUE;
455     END vald_rev_sus_hold;
456 
457 
458 
459   --
460   -- main begin for eval_deny_all_hold
461   --
462 BEGIN
463      p_message  := NULL;
464 
465      --Get the enrollment method for the self service responsibility.
466      OPEN get_enr_method;
467      FETCH get_enr_method INTO l_enr_method_type;
468      IF get_enr_method%NOTFOUND THEN
469         CLOSE get_enr_method;
470         p_message := 'IGS_EN_ONE_SS_MTYP';
471         RETURN FALSE;
472      ELSE
476     -- assign the p_enrl_method to l_enr_method_type
473         CLOSE get_enr_method;
474      END IF;
475     --
477     --
478 
479     -- smaddali For bug#3930876, removed the condition if l_person_type is not NULL
480     --    before deriving the system person type, since this is a local variable which will always be null
481     -- get the system person type
482     --
483     IF p_person_type IS NOT NULL THEN
484           l_person_type := get_sys_pers_type (
485                                         p_person_type => p_person_type,
486                                         p_message     => p_message
487                                       );
488     END IF;
489     IF p_message IS NOT NULL THEN
490        RETURN FALSE;
491     END IF;
492 
493 
494     --
495     -- person type is STUDENT
496     -- make a call to procedure to see whether the step is overriden or not
497     --
498     l_step_override := igs_en_gen_015.validation_step_is_overridden
499                                  (
500                                    p_eligibility_step_type        => 'CHKENCUMB',
501                                    p_load_cal_type                => p_load_calendar_type,
502                                    p_load_cal_seq_number          => p_load_cal_sequence_number,
503                                    p_person_id                    => p_person_id,
504                                    p_uoo_id                       => NULL,
505                                    p_step_override_limit          => l_step_override_limit
506                                 );
507     IF l_step_override THEN
508       --
509       -- return TRUE if the step is overridden for the passed person_type
510       --
511       RETURN TRUE;
512     END IF;
513 
514 
515     --
516     -- check for the person type passed. If it is not student, check whether CHKENCUMB is overridden or not
517     -- for passed person type
518     --
519     IF l_person_type <> 'STUDENT' THEN
520        --
521        -- open cursor c_chkencumb_override and see whether the CHKEMCUMB is oevrriden or not for the passed
522        -- person_type
523        --
524        l_chkencumb_override := 'N';
525        OPEN c_chkencumb_override (p_person_type);
526        FETCH c_chkencumb_override INTO l_chkencumb_override;
527        CLOSE c_chkencumb_override;
528        IF l_chkencumb_override = 'Y' THEN
529           --
530           -- return TRUE if the step is overridden for the passed person_type
531           --
532           RETURN TRUE;
533        END IF;
534     END IF; -- check for person type
535 
536     -- now do validation of Deny All Enrollment Activity Hold
537     -- call the function vald_deny_all_hold
538     --
539     l_deny_all_hold := vald_rev_sus_hold;
540 
541     --
542     -- depending on the return value of l_deny_all_hold, return from the main function
543     --
544     IF l_deny_all_hold THEN
545        --
546        -- validation of Deny All Enrollment Activity Hold returns TRUE
547        --
548        RETURN TRUE;
549     ELSIF NOT l_deny_all_hold THEN
550        --
551        -- validation of Deny All Enrollment Activity Hold returns FALSE
552        -- and the p_message has been assigned message in the vald_deny_all_hold
553        -- program unit, hence just return FALSE
554        --
555        RETURN FALSE;
556     END IF;
557     RETURN TRUE;
558   END eval_ss_rev_sus_all_hold;
559 
560 
561 FUNCTION eval_person_steps (
562                               p_person_id                       IN  NUMBER,
563                               p_person_type                     IN  VARCHAR2,
564                               p_load_calendar_type              IN  VARCHAR2,
565                               p_load_cal_sequence_number        IN  NUMBER,
566                               p_program_cd                      IN  VARCHAR2,
567                               p_program_version                 IN  NUMBER,
568                               p_enrollment_category             IN  VARCHAR2,
569                               p_comm_type                       IN  VARCHAR2,
570                               p_enrl_method                     IN  VARCHAR2,
571                               p_message                        OUT NOCOPY  VARCHAR2,
572                               p_deny_warn                      OUT NOCOPY  VARCHAR2,
573                               p_calling_obj                     IN VARCHAR2,
574                               p_create_warning                  IN VARCHAR2
575                             )
576  RETURN BOOLEAN
577  IS
578 
579  ------------------------------------------------------------------------------------
580   --Created by  : smanglm ( Oracle IDC)
581   --Date created: 19-JUN-2001
582   --
583   --Purpose:  Created as part of the build for DLD Enrollment Setup : Eligibility and Validation
584   --          This function will validate all of the selected Person Steps based on the rules
585   --          setup by the institution in the Enrollment Category Validations form and the
586   --          self service user activity set up form.
587   --
588   --Known limitations/enhancements and/or remarks:
589   --
590   --Change History:
591   --Who         When            What
592   --ayedubat    11-APR-2002    Changed the cursors,c_non_stud_vald_steps and c_stud_vald_steps to add an extra 'OR'
596   --                           calling the function igs_ss_enr_details.get_notification.
593   --                           condition(eru.s_student_comm_type = 'ALL') for s_student_comm_type as part of the bug fix: 2315245
594   --Nishikant    01NOV2002     SEVIS Build. Enh Bug#2641905. notification flag was
595   --                           being fetched from cursor, now modified to get it by
597   --
598   -------------------------------------------------------------------------------------
599 
600     l_enr_method_type     igs_en_method_type.enr_method_type%TYPE;
601 
602     --
603     -- cursor to fetch validation steps for the person type not equal to STUDENT
604     --
605     CURSOR c_non_stud_vald_steps (cp_enr_method_type    igs_en_cpd_ext.enr_method_type%TYPE) IS
606            SELECT  eru.s_enrolment_step_type, eru.enrolment_cat, eru.s_student_comm_type, eru.enr_method_type, lkup.step_group_type,
607                    eru.s_rule_call_cd,
608                    eru.rul_sequence_number
609            FROM    igs_en_cpd_ext eru,
610                    igs_pe_usr_aval_all uact,
611                    igs_lookups_view lkup
612            WHERE   eru.s_enrolment_step_type = lkup.lookup_code
613            AND     lkup.lookup_type = 'ENROLMENT_STEP_TYPE_EXT'
614            AND     lkup.step_group_type = 'PERSON'
615            AND     eru.s_enrolment_step_type = uact.validation (+)
616            AND     uact.person_type (+) = p_person_type
617            AND     nvl(uact.override_ind,'N') = 'N'
618                  AND     eru.enrolment_cat = p_enrollment_category
619            AND    (eru.s_student_comm_type = p_comm_type OR eru.s_student_comm_type = 'ALL')
620                  AND     eru.enr_method_type = cp_enr_method_type
621            ORDER BY eru.step_order_num;
622 
623     --
624     -- cursor to fetch validation steps for the person type equal to STUDENT
625     --
626     CURSOR c_stud_vald_steps (cp_enr_method_type    igs_en_cpd_ext.enr_method_type%TYPE) IS
627            SELECT  eru.s_enrolment_step_type, eru.enrolment_cat, eru.s_student_comm_type, eru.enr_method_type, lkup.step_group_type,
628                    eru.s_rule_call_cd,
629                    eru.rul_sequence_number
630            FROM    igs_en_cpd_ext eru,
631                    igs_lookups_view lkup
632            WHERE   eru.s_enrolment_step_type = lkup.lookup_code
633            AND     lkup.lookup_type = 'ENROLMENT_STEP_TYPE_EXT'
634            AND     lkup.step_group_type = 'PERSON'
635                  AND     eru.enrolment_cat = p_enrollment_category
636                  AND    (eru.s_student_comm_type = p_comm_type OR eru.s_student_comm_type = 'ALL')
637                  AND     eru.enr_method_type = cp_enr_method_type
638            ORDER BY eru.step_order_num;
639 
640     rec_vald_steps         c_stud_vald_steps%ROWTYPE;
641 
642     l_vald_person_steps    BOOLEAN;
643     l_step_override_limit  igs_en_elgb_ovr_step.step_override_limit%TYPE;
644     l_person_type          igs_pe_person_types.person_type_code%TYPE;
645     l_notification_flag    igs_en_cpd_ext.notification_flag%TYPE; --added by nishikant
646     l_message              VARCHAR2(2000);
647     l_deny_person_steps BOOLEAN;
648     l_warn_person_steps BOOLEAN;
649     l_steps             VARCHAR2(100);
650    PROCEDURE create_ss_warning(p_message_for	IN IGS_EN_STD_WARNINGS.message_for%TYPE,
651    							   p_message_icon	IN IGS_EN_STD_WARNINGS.message_icon%TYPE,
652 							   p_message_name	IN IGS_EN_STD_WARNINGS.message_name%TYPE,
653                                p_message_rule_text IN IGS_PS_UNIT_VER_RU_V.rule_text%TYPE) IS
654     ------------------------------------------------------------------------------------
655     --Created by  : rvangala
656     --Date created: 16-JUN-2005
657     --
658     --Purpose:  Function to create/update errors/warnings in the warnings table
659     --
660     --
661     ------------------------------------------------------------------------------------
662 
663     BEGIN
664                 IGS_EN_DROP_UNITS_API.create_ss_warning(p_person_id => p_person_id,
665                      p_course_cd   => p_program_cd,
666                      p_term_cal_type => p_load_calendar_type,
667                      p_term_ci_sequence_number => p_load_cal_sequence_number,
668 		             p_uoo_id  => null,
669 		             p_message_for => p_message_for,
670 		             p_message_icon => p_message_icon,
671 		             p_message_name   => p_message_name,
672                      p_message_rule_text => p_message_rule_text,
673                      p_message_tokens	=> null,
674 		             p_message_action => null,
675 		             p_destination    => null,
676 		             p_parameters     => null,
677 		             p_step_type      => 'PERSON');
678 
679     END create_ss_warning;
680 
681 
682     FUNCTION vald_person_steps
683     RETURN BOOLEAN
684     IS
685 
686     ------------------------------------------------------------------------------------
687     --Created by  : smanglm ( Oracle IDC)
688     --Date created: 19-JUN-2001
689     --
690     --Purpose:  local program unit to function eval_person_steps
691     --          This function will validate the person steps
692     --
693     --
694     --Known limitations/enhancements and/or remarks:
695     --
696     --Change History:
697     --Who         When            What
698     --ayedubat    24-JUN-2002    Modified the cursor,c_padm_tr_req in vald_person_steps added to new
699     --                           parameters: cp_person_id and cp_course_cd which retrieves only the
703     -- rnirwani   13-Sep-2004    changed cursor c_intmsn_details  to not consider logically deleted records and
700     --                           records of the student program in context for the bug fix: 2427528
701     --svanukur    31-may-03      Added the validation for PersonLevel Timeslot by invoking eval_timeslot
702     --                            as part of DENY/WARN behaviour build 2829272.
704     --				also to avoid un-approved intermission records. Bug# 3885804
705     -------------------------------------------------------------------------------------
706 
707       l_step_overridden   BOOLEAN;
708       l_return_val        VARCHAR2(10);
709       l_message_text      VARCHAR2(2000);
710       l_message_name      VARCHAR2(2000);
711 
712       --
713       -- cursor to fetch the adm_appl_number and adm_sequence_number
714       --
715       CURSOR c_adm_sts IS
716              SELECT adm_admission_appl_number,
717                     adm_sequence_number
718              FROM   igs_en_stdnt_ps_att
719              WHERE  person_id = p_person_id
720              AND    course_cd = p_program_cd
721              AND    version_number = p_program_version;
722       rec_adm_sts    c_adm_sts%ROWTYPE;
723 
724       --
725       -- cursor to check whether the student has completed some post admission tracking requirements
726       -- As part of Bug 2343417 modified 'POST-ADM' to 'POST_ADMISSION'
727       CURSOR c_padm_tr_req (cp_person_id        igs_en_stdnt_ps_att.person_id%TYPE,
728                             cp_course_cd        igs_en_stdnt_ps_att.course_cd%TYPE,
729                             cp_adm_appl_number  igs_en_stdnt_ps_att.adm_admission_appl_number%TYPE,
730                             cp_adm_seq_number   igs_en_stdnt_ps_att.adm_sequence_number%TYPE) IS
731              SELECT 'TRUE'
732              FROM   igs_tr_item ti,
733                     igs_tr_status ts
734              WHERE  ts.tracking_status = ti.tracking_status
735              AND    ts.s_tracking_status <> 'COMPLETE'
736              AND    ti.tracking_id IN ( SELECT ad.tracking_id
737                                           FROM   igs_tr_type tt,
738                                                  igs_tr_item ti,
739                                                  igs_ad_aplins_admreq ad
740                                           WHERE  tt.s_tracking_type = 'POST_ADMISSION'
741                                           AND    ad.tracking_id = ti.tracking_id
742                                           AND    ti.tracking_type = tt.tracking_type
743                                           AND    ad.person_id = cp_person_id
744                                           AND    ad.course_cd = cp_course_cd
745                                           AND    ad.admission_appl_number = cp_adm_appl_number
746                                           AND    ad.sequence_number = cp_adm_seq_number );
747        rec_padm_tr_req     c_padm_tr_req%ROWTYPE;
748 
749        --
750        -- cursor to fetch the intermission records of the program passed
751        --
752        CURSOR c_intmsn_details IS
753               SELECT sci.intermission_type,
754                      sci.start_dt
755               FROM   igs_en_stdnt_ps_intm sci,
756                      IGS_EN_INTM_TYPES eit,
757                      igs_en_stdnt_ps_att spa
758               WHERE  sci.person_id = p_person_id
759               AND    sci.course_cd = p_program_cd
760               AND    sci.logical_delete_date = TO_DATE('31-12-4712','DD-MM-YYYY')
761               AND    sci.approved  = eit.appr_reqd_ind
762               AND    eit.intermission_type = sci.intermission_type
763               AND    spa.person_id = sci.person_id
764               AND    spa.course_cd = sci.course_cd
765               AND    ((trunc(sysdate) between sci.start_dt and sci.end_dt)
766                      OR
767                      ((trunc(sysdate) > sci.end_dt) AND (spa.course_attempt_status = 'INTERMIT')));
768 
769         --
770         -- cursor to fetch the visa records of the student
771         --
772         CURSOR c_visa_details IS
773                SELECT visa_type,
774                       visa_number
775                FROM   igs_pe_visa
776                WHERE  person_id = p_person_id;
777 
778     --
779     -- begin for local program unit vald_person_steps
780     --
781     l_rule_text VARCHAR2(1000);
782     BEGIN
783       --
784       -- check that the eligibility validation step rec_vald_steps.s_enrolment_step_type is not overridden
785       -- else return TRUE
786       --
787       l_step_overridden := igs_en_gen_015.validation_step_is_overridden
788                                      (
789                                        p_eligibility_step_type        => rec_vald_steps.s_enrolment_step_type,
790                                        p_load_cal_type                => p_load_calendar_type,
791                                        p_load_cal_seq_number          => p_load_cal_sequence_number,
792                                        p_person_id                    => p_person_id,
793                                        p_uoo_id                       => NULL,
794                                        p_step_override_limit          => l_step_override_limit
795                                     );
796       IF l_step_overridden THEN
797          RETURN TRUE;
798       END IF;
799       --
800       -- check the step type to be validated from the record type variable rec_vald_steps
801       -- if any of the validation procedure encounters a warning message asign the warning messages to the
805 
802       -- variable p_message separated by delimiter semicolon (;) and continue validating the other steps
803       -- Only if an Error Condition occurs, return to the calling procedure
804       --
806       IF rec_vald_steps.s_enrolment_step_type = 'ADM_STS' THEN --Admission Status
807          --
808          -- select the application details of the primary program and check whether the adm status rules are
809          -- satisfied by calling the Rules evaluation procedure.
810          --
811          FOR rec_adm_sts IN c_adm_sts
812          LOOP
813              IF rec_vald_steps.rul_sequence_number IS NOT NULL AND
814                 rec_adm_sts.adm_sequence_number IS NOT NULL AND
815                 rec_adm_sts.adm_admission_appl_number IS NOT NULL  THEN
816 
817                 l_return_val := null;
818                 l_message_text := null;
819                 --
820                 -- call the rule function rulp_val_senna
821                 --
822                 l_return_val := igs_ru_gen_001.rulp_val_senna (
823                                                                 p_rule_call_name => 'ADM_STS',
824                                                                 p_rule_number    => rec_vald_steps.rul_sequence_number,
825                                                                 p_person_id      => p_person_id,
826                                                                 p_param_1        => nvl(rec_adm_sts.adm_admission_appl_number,-99),
827                                                                 p_param_2        => p_program_cd,
828                                                                 p_param_3        => nvl(rec_adm_sts.adm_sequence_number,-99),
829                                                                 p_message        => l_message_text
830                                                               );
831                 IF upper(l_return_val) = 'TRUE' THEN
832                    --
833                    -- if any of the application details returns true, no need to check for other records
834                    --
835                    EXIT;
836                 END IF;
837              END IF; -- check for rec_vald_steps.rul_sequence_number
838          END LOOP;
839 
840 
841           IF upper(l_return_val) <> 'TRUE' THEN
842            l_rule_text := null;
843             IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
844               l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(rec_vald_steps.rul_sequence_number );
845             END IF;
846 
847            IF l_notification_flag = 'DENY' THEN
848 	    	-- rule validation failed and notification flag is DENY, return FALSE
849 		   l_deny_person_steps := TRUE;
850 
851            IF p_create_warning = 'Y' THEN
852 		      -- create warning record
853               create_ss_warning( igs_ss_enroll_pkg.enrf_get_lookup_meaning
854                                    (p_lookup_code => 'ADM_STS',
855                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
856                                     'D','IGS_SS_DENY_ADM_STAT',l_rule_text);
857     	   ELSE
858 			  p_message := p_message||';'||'IGS_SS_DENY_ADM_STAT';
859 		   END IF;
860 
861 		  RETURN FALSE;
862          ELSIF  l_notification_flag = 'WARN' THEN
863 		-- rule validation failed and notification flag is WARN, append the message
864 	   	   l_warn_person_steps := TRUE;
865            IF p_create_warning = 'Y' THEN
866 		    -- create warning record
867             create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
868                                    (p_lookup_code => 'ADM_STS',
869                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
870                                     'W','IGS_SS_WARN_ADM_STAT',l_rule_text);
871 		  ELSE
872 			p_message := p_message||';'||'IGS_SS_WARN_ADM_STAT';
873           END IF;
874    		  RETURN TRUE;
875 		 END IF;
876 
877 	    END IF;
878 
879       ELSIF rec_vald_steps.s_enrolment_step_type = 'PADM_STS' THEN  -- Post Admission Status
880          --
881          -- get the student application details
882          --
883          FOR rec_adm_sts IN c_adm_sts
884          LOOP
885             l_return_val := null;
886             --
887             -- select all the tracking type with system defined tracking type = Post Admission Status attached
888             -- to the student from the Admission Application Tracking Details.
889             --
890             -- check whether the student has completed the post admission tracking requirements
891             --
892             OPEN c_padm_tr_req (p_person_id,
893                                 p_program_cd,
894                                 rec_adm_sts.adm_admission_appl_number,
895                                 rec_adm_sts.adm_sequence_number);
896 
897             FETCH c_padm_tr_req INTO l_return_val;
898             CLOSE c_padm_tr_req;
899 
900             IF upper(NVL(l_return_val,'FALSE'))  = 'TRUE' THEN
901                --
902                -- if any of the tracking types for application details returns true, no need to check for other records
903                --
904                EXIT;
905             END IF;
906          END LOOP;
907 
908        IF upper(l_return_val) = 'TRUE' THEN
909            l_rule_text := null;
910            IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
911               l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(rec_vald_steps.rul_sequence_number );
912            END IF;
913 
914            IF l_notification_flag = 'DENY' THEN
918             -- create warning record
915 		-- rule validation failed and notification flag is DENY, return FALSE
916    		  l_deny_person_steps := TRUE;
917 		IF p_create_warning = 'Y' THEN
919             create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
920                                    (p_lookup_code => 'PADM_STS',
921                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
922                                     'D','IGS_SS_DENY_POST_ADM_STAT',l_rule_text);
923 		ELSE
924 			p_message := p_message||';'||'IGS_SS_DENY_POST_ADM_STAT';
925 		END IF;
926 		RETURN FALSE;
927 	    ELSIF  l_notification_flag = 'WARN' THEN
928 		-- rule validation failed and notification flag is WARN, append the message
929 		l_warn_person_steps := TRUE;
930 		IF p_create_warning = 'Y' THEN
931             -- create warning record
932             create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
933                                    (p_lookup_code => 'PADM_STS',
934                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
935                                     'W','IGS_SS_WARN_POST_ADM_STAT',l_rule_text);
936 		 ELSE
937 			p_message := p_message||';'||'IGS_SS_WARN_POST_ADM_STAT';
938 	 	 END IF;
939  		RETURN TRUE;
940 	    END IF;
941 	 END IF;
942 
943 
944       ELSIF rec_vald_steps.s_enrolment_step_type = 'CONTD_STS' THEN -- Continuing Status
945          --
946          -- perform the continuing status validation only if the rule is defined
947          --
948          IF rec_vald_steps.rul_sequence_number IS NOT NULL THEN
949            l_return_val:= null;
950            l_message_text := null;
951                 --
952                 -- call the rule function rulp_val_senna
953                 --
954                 l_return_val := igs_ru_gen_001.rulp_val_senna (
955                                                                 p_rule_call_name => 'CONTD_STS',
956                                                                 p_rule_number    => rec_vald_steps.rul_sequence_number,
957                                                                 p_person_id      => p_person_id,
958                                                                 p_param_1        => p_program_cd,
959                                                                 p_param_2        => p_program_version,
960                                                                 p_message        => l_message_text
961                                                               );
962            IF upper(l_return_val) <> 'TRUE' THEN
963             l_rule_text := null;
964             IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
965               l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(rec_vald_steps.rul_sequence_number );
966             END IF;
967 
968 		     IF l_notification_flag = 'DENY' THEN
969 			-- rule validation failed and notification flag is DENY, return FALSE
970 			  l_deny_person_steps := TRUE;
971 			  IF p_create_warning = 'Y' THEN
972                 -- create warning record
973                 create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
974                                    (p_lookup_code => 'CONTD_STS',
975                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
976                                     'D','IGS_SS_DENY_CONT_ADM_STAT',l_rule_text);
977 			  ELSE
978 				p_message := p_message||';'||'IGS_SS_DENY_CONT_ADM_STAT';
979 			  END IF;
980 			 RETURN FALSE;
981 		    ELSIF  l_notification_flag = 'WARN' THEN
982 			-- rule validation failed and notification flag is WARN, append the message
983 			l_warn_person_steps := TRUE;
984 			IF p_create_warning = 'Y' THEN
985                -- create warning record
986                create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
987                                    (p_lookup_code => 'CONTD_STS',
988                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
989                                     'W','IGS_SS_WARN_CONT_ADM_STAT',l_rule_text);
990 			ELSE
991 				p_message := p_message||';'||'IGS_SS_WARN_CONT_ADM_STAT';
992 			END IF;
993 
994 			RETURN TRUE;
995 		    END IF;
996           END IF;
997          END IF; --end of rec_vald_steps.rul_sequence_number IS NOT NULL
998 
999 
1000       ELSIF rec_vald_steps.s_enrolment_step_type = 'INTMSN_STS' THEN -- Intermission Status
1001          --
1002          -- perform the validation for the intermission status only if the rule is defined.
1003          --
1004          IF rec_vald_steps.rul_sequence_number IS NOT NULL THEN
1005             --
1006             -- fetch the intermission records of the program passed
1007             --
1008             FOR rec_intmsn_details IN c_intmsn_details
1009             LOOP
1010               l_return_val := null;
1011               l_message_text := null;
1012                 --
1013                 -- call the rule function rulp_val_senna
1014                 --
1015                 l_return_val := igs_ru_gen_001.rulp_val_senna (
1016                                                                 p_rule_call_name => 'INTMSN_STS',
1017                                                                 p_rule_number    => rec_vald_steps.rul_sequence_number,
1018                                                                 p_person_id      => p_person_id,
1019                                                                 p_param_1        => p_program_cd,
1023                                                                 p_param_5        => p_load_cal_sequence_number,
1020                                                                 p_param_2        => nvl(rec_intmsn_details.intermission_type,'-99'),
1021                                                                 p_param_3        => rec_intmsn_details.start_dt,
1022                                                                 p_param_4        => p_load_calendar_type,
1024                                                                 p_message        => l_message_text
1025                                                               );
1026 
1027                 IF upper(l_return_val) = 'TRUE' THEN
1028                    --
1029                    -- if the student satisfies the rules for any one of the record, do not check for the remaining records
1030                    --
1031                    EXIT;
1032                 END IF;
1033             END LOOP;
1034 
1035             IF upper(l_return_val) <> 'TRUE' THEN
1036              l_rule_text := null;
1037              IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
1038               l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(rec_vald_steps.rul_sequence_number );
1039              END IF;
1040 
1041   	    	  IF l_notification_flag = 'DENY' THEN
1042 			-- rule validation failed and notification flag is DENY, return FALSE
1043 			l_deny_person_steps := TRUE;
1044   		      IF p_create_warning = 'Y' THEN
1045                -- create warning record
1046                 create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
1047                                    (p_lookup_code => 'INTMSN_STS',
1048                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
1049                                     'D','IGS_SS_DENY_INTERMIT_STAT',l_rule_text);
1050 			  ELSE
1051 				p_message := p_message||';'||'IGS_SS_DENY_INTERMIT_STAT';
1052 			  END IF;
1053 			 RETURN FALSE;
1054 		    ELSIF  l_notification_flag = 'WARN' THEN
1055 			-- rule validation failed and notification flag is WARN, append the message
1056 			l_warn_person_steps := TRUE;
1057 			  IF p_create_warning = 'Y' THEN
1058                 -- create warning record
1059                 create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
1060                                    (p_lookup_code => 'INTMSN_STS',
1061                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
1062                                     'W','IGS_SS_WARN_INTERMIT_STAT',l_rule_text);
1063 			   ELSE
1064 				p_message := p_message||';'||'IGS_SS_WARN_INTERMIT_STAT';
1065 			   END IF;
1066 			  RETURN TRUE;
1067 		      END IF;
1068 	     END IF; -- IF upper(l_return_val) <> 'TRUE'
1069 
1070         END IF;
1071 
1072       ELSIF rec_vald_steps.s_enrolment_step_type = 'VISA_STS' THEN -- Visa Status
1073          --
1074          -- perform the validation for the visa status only if the rule is defined.
1075          --
1076          IF rec_vald_steps.rul_sequence_number IS NOT NULL THEN
1077             --
1078             -- fetch the visa records of the student
1079             --
1080             FOR rec_visa_details IN c_visa_details
1081             LOOP
1082               l_return_val := null;
1083               l_message_text := null;
1084                 --
1085                 -- call the rule function rulp_val_senna
1086                 --
1087                 l_return_val := igs_ru_gen_001.rulp_val_senna (
1088                                                                 p_rule_call_name => 'VISA_STS',
1089                                                                 p_rule_number    => rec_vald_steps.rul_sequence_number,
1090                                                                 p_person_id      => p_person_id,
1091                                                                 p_param_1        => rec_visa_details.visa_type,
1092                                                                 p_param_2        => p_load_calendar_type,
1093                                                                 p_param_3        => p_load_cal_sequence_number,
1094                                                                 p_param_6        => rec_visa_details.visa_number,
1095                                                                 p_message        => l_message_text
1096                                                               );
1097 
1098                 IF upper(l_return_val) = 'TRUE' THEN
1099                    --
1100                    -- if the student satisfies the rules for any one of the record, do not check for the remaining records
1101                    --
1102                    EXIT;
1103                 END IF;
1104             END LOOP;
1105 
1106            IF upper(l_return_val) <> 'TRUE' THEN
1107              l_rule_text := null;
1108              IF(NVL(fnd_profile.value('IGS_EN_CART_RULE_DISPLAY'),'N')='Y') THEN
1109               l_rule_text := igs_ru_gen_003.Rulp_Get_Rule(rec_vald_steps.rul_sequence_number );
1110              END IF;
1111 
1112 	    	IF l_notification_flag = 'DENY' THEN
1113 			-- rule validation failed and notification flag is DENY, return FALSE
1114 			l_deny_person_steps := TRUE;
1115 			 IF p_create_warning = 'Y' THEN
1116    		        -- create warning record
1117                 create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
1118                                    (p_lookup_code => 'VISA_STS',
1119                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
1120                                     'D','IGS_SS_DENY_VISA_STAT',l_rule_text);
1124 			RETURN FALSE;
1121 			ELSE
1122 				p_message := p_message||';'||'IGS_SS_DENY_VISA_STAT';
1123 			END IF;
1125 		    ELSIF  l_notification_flag = 'WARN' THEN
1126 			-- rule validation failed and notification flag is WARN, append the message
1127 			l_warn_person_steps := TRUE;
1128 			IF p_create_warning = 'Y' THEN
1129 				-- create warning record
1130 				create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
1131                                    (p_lookup_code => 'VISA_STS',
1132                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
1133                                     'W','IGS_SS_WARN_VISA_STAT',l_rule_text);
1134 			ELSE
1135 				p_message := p_message||';'||'IGS_SS_WARN_VISA_STAT';
1136 			END IF;
1137 			RETURN TRUE;
1138 		    END IF;
1139   	      END IF;
1140          END IF;
1141 
1142 
1143       ELSIF rec_vald_steps.s_enrolment_step_type = 'CHK_TIME_PER' THEN
1144         IF p_calling_obj IN ('PLAN','ENROLPEND','JOB') THEN
1145           RETURN TRUE;
1146         ELSE
1147 
1148         IF NOT eval_timeslot(
1149                               p_person_id => p_person_id,
1150                               p_person_type => p_person_type,
1151                               p_load_calendar_type => p_load_calendar_type,
1152                               p_load_cal_sequence_number => p_load_cal_sequence_number,
1153                               p_uoo_id  => NULL,
1154                               p_enrollment_category => p_enrollment_category,
1155                               p_comm_type  => p_comm_type,
1156                               p_enrl_method => p_enrl_method,
1157                               p_message => l_message_name,
1158                   p_notification_flag => l_notification_flag
1159           ) THEN
1160 
1161           IF l_message_name NOT IN ('IGS_SS_DENY_TSLOT', 'IGS_SS_WARN_TSLOT') then
1162                p_message := p_message||';'||l_message_name;
1163                p_deny_warn := 'DENY';
1164                RETURN FALSE;
1165           END IF;
1166 
1167 		   IF l_notification_flag = 'DENY' AND l_message_name IS NOT NULL THEN
1168 			-- rule validation failed and notification flag is DENY, return FALSE
1169 			l_deny_person_steps := TRUE;
1170 			IF p_create_warning='Y' THEN
1171               -- create warning record
1172               create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
1173                                    (p_lookup_code => 'CHK_TIME_PER',
1174                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
1175                                     'D',l_message_name,null);
1176 			ELSE
1177 				p_message := p_message||';'||l_message_name;
1178 			END IF;
1179 			RETURN FALSE;
1180 
1181 		    ELSIF  l_notification_flag = 'WARN' AND l_message_name IS NOT NULL THEN
1182 			-- rule validation failed and notification flag is WARN, append the message
1183 			l_warn_person_steps := TRUE;
1184   			 IF p_create_warning = 'Y' THEN
1185 			    -- create warning record
1186                 create_ss_warning(igs_ss_enroll_pkg.enrf_get_lookup_meaning
1187                                    (p_lookup_code => 'CHK_TIME_PER',
1188                                     p_lookup_type => 'ENROLMENT_STEP_TYPE_EXT'),
1189                                     'W',l_message_name,null);
1190 			 ELSE
1191 				p_message := p_message||';'||l_message_name;
1192 			 END IF;
1193 			RETURN TRUE;
1194 
1195            END IF;
1196 	      END IF; --  IF NOT eval_timeslot
1197         END IF; --  P_calling_obj = 'PLAN'
1198 
1199       END IF; -- check for rec_vald_steps.s_enrolment_step_type
1200 
1201       --
1202       -- either the steps have validated or there is some warning message
1203       --
1204       RETURN TRUE;
1205     END vald_person_steps;
1206  --
1207  -- main begin for eval_person_steps
1208  --
1209  BEGIN
1210      l_deny_person_steps := FALSE;
1211      l_warn_person_steps := FALSE;
1212     --
1213     -- assign the p_enrl_method to l_enr_method_type
1214     --
1215     l_enr_method_type := p_enrl_method;
1216     IF p_person_type IS NOT NULL THEN
1217             --
1218             -- get the system person type
1219             --
1220             l_person_type := get_sys_pers_type (
1221                                                  p_person_type => p_person_type,
1222                                                  p_message     => p_message
1223                                                );
1224             IF p_message IS NOT NULL THEN
1225                p_deny_warn := 'DENY';
1226                RETURN FALSE;
1227             END IF;
1228     END IF;
1229     --
1230     -- check for the person type, if not student select only those steps which are not overridden for
1231     -- the given person type
1232     --
1233 
1234     -- added by ckasu as a prt of EN318 SS Admin Impact Build inorder to delete
1235     -- Person step Warning or Error Record when Create warnings is set to 'Y'.
1236 
1237     IF p_create_warning = 'Y' THEN
1238          l_steps := 'PERSON';
1239          igs_en_add_units_api.delete_ss_warnings(p_person_id,
1240                          p_program_cd,
1241                          p_load_calendar_type,
1242                          p_load_cal_sequence_number,
1243                          NULL, -- uoo_id
1244                          NULL, -- message_for
1245                          l_steps);
1246     END IF; -- end of IF p_create_warning = 'N'
1247 
1251        FOR  r_vald_steps IN c_non_stud_vald_steps (l_enr_method_type)
1248 
1249     IF l_person_type <> 'STUDENT' THEN
1250 
1252        LOOP
1253          --
1254          -- make a call to local program unit vald_person_steps
1255          -- also copy the r_vald_steps to global variable rec_vald_steps as r_vald_steps will
1256          -- not be visible outside the FOR LOOP and END LOOP
1257          --
1258          rec_vald_steps := r_vald_steps;
1259          l_notification_flag := igs_ss_enr_details.get_notification(
1260                                    p_person_type         => p_person_type,
1261                                    p_enrollment_category => rec_vald_steps.enrolment_cat,
1262                                    p_comm_type           => rec_vald_steps.s_student_comm_type,
1263                                    p_enr_method_type     => rec_vald_steps.enr_method_type,
1264                                    p_step_group_type     => rec_vald_steps.step_group_type,
1265                                    p_step_type           => rec_vald_steps.s_enrolment_step_type,
1266                                    p_person_id           => p_person_id ,
1267                                    p_message             => l_message);
1268          IF l_message IS NOT NULL THEN
1269             p_message := l_message;
1270             p_deny_warn := 'DENY';
1271 
1272 	    RETURN FALSE;
1273          END IF;
1274 
1275 	 l_vald_person_steps := vald_person_steps;
1276          --
1277          -- if any of the step validation returns FALSE, return FALSE and no need to check further records
1278          --
1279          IF NOT l_vald_person_steps THEN
1280           IF p_calling_obj = 'JOB' OR  p_create_warning = 'N' THEN
1281             EXIT;
1282           END IF;
1283          END IF;
1284        END LOOP;
1285     ELSE
1286        FOR  r_vald_steps IN c_stud_vald_steps (l_enr_method_type)
1287        LOOP
1288          --
1289          -- make a call to local program unit vald_person_steps
1290          -- also copy the r_vald_steps to global variable rec_vald_steps as r_vald_steps will
1291          -- not be visible outside the FOR LOOP and END LOOP
1292          --
1293          rec_vald_steps := r_vald_steps;
1294          l_notification_flag := igs_ss_enr_details.get_notification(
1295                                    p_person_type         => p_person_type,
1296                                    p_enrollment_category => rec_vald_steps.enrolment_cat,
1297                                    p_comm_type           => rec_vald_steps.s_student_comm_type,
1298                                    p_enr_method_type     => rec_vald_steps.enr_method_type,
1299                                    p_step_group_type     => rec_vald_steps.step_group_type,
1300                                    p_step_type           => rec_vald_steps.s_enrolment_step_type,
1301                                    p_person_id           => p_person_id,
1302                                    p_message             => l_message);
1303          IF l_message IS NOT NULL THEN
1304             p_message := l_message;
1305             p_deny_warn := 'DENY';
1306 
1307 	    RETURN FALSE;
1308          END IF;
1309          l_vald_person_steps := vald_person_steps;
1310          --
1311          -- if any of the step validation returns FALSE, return FALSE if called from jobs,and no need to check further records
1312          -- but if called from self service, we need to log all possible failures
1313          IF NOT l_vald_person_steps THEN
1314           IF p_calling_obj = 'JOB' OR  p_create_warning = 'N' THEN
1315             EXIT ;
1316           END IF;
1317          END IF;
1318        END LOOP;
1319     END IF;
1320 
1321     IF l_deny_person_steps THEN
1322        --
1323        -- validation of person steps returns TRUE
1324        --
1325        IF p_message IS NOT NULL THEN
1326           --
1327           -- that is there are few warning messages so assign WARN to p_deny_warn and remove ';'
1328           -- from the beginning and end of p_message
1329           --
1330           --
1331           -- remove ; from beginning
1332           --
1333           IF substr(p_message,1,1) = ';' THEN
1334              p_message := substr(p_message,2);
1335           END IF;
1336           --
1337           -- remove ; from end
1338           --
1339           IF substr(p_message,-1,1) = ';' THEN
1340              p_message := substr(p_message,1,length(p_message)-1);
1341           END IF;
1342        END IF;
1343        p_deny_warn:= 'DENY';
1344        RETURN FALSE;
1345     ELSIF l_warn_person_steps THEN
1346        --
1347        -- validation of person steps returns FALSE
1348        -- and the p_message and p_deny_warn have been assigned value in the vald_person_steps
1349        -- program unit, hence just return FALSE
1350        --
1351        -- As part of Bug 2343417 added below code to remove ';' from p_message
1352        IF p_message IS NOT NULL THEN
1353           -- remove ; from beginning
1354           --
1355           IF substr(p_message,1,1) = ';' THEN
1356              p_message := substr(p_message,2);
1357           END IF;
1358           --
1359           -- remove ; from end
1360           --
1361           IF substr(p_message,-1,1) = ';' THEN
1362              p_message := substr(p_message,1,length(p_message)-1);
1363           END IF;
1364         END IF;
1365        p_deny_warn := 'WARN' ;
1366        RETURN TRUE;
1367     END IF;
1368     RETURN TRUE;
1369 
1370  END eval_person_steps;
1371 
1372 
1373 
1374 
1375  FUNCTION eval_timeslot    (
1376                               p_person_id                       IN  NUMBER,
1377                               p_person_type                     IN  VARCHAR2,
1378                               p_load_calendar_type              IN  VARCHAR2,
1379                               p_load_cal_sequence_number        IN  NUMBER,
1380                               p_uoo_id                          IN  NUMBER,
1381                               p_enrollment_category             IN  VARCHAR2,
1382                               p_comm_type                       IN  VARCHAR2,
1383                               p_enrl_method                     IN  VARCHAR2,
1384                               p_message                          OUT NOCOPY  VARCHAR2,
1385 			      p_notification_flag               IN VARCHAR2
1386                             )
1387  RETURN BOOLEAN
1388  IS
1389 
1390  ------------------------------------------------------------------------------------
1391   --Created by  : smanglm ( Oracle IDC)
1392   --Date created: 19-JUN-2001
1393   --
1394   --Purpose:  Created as part of the build for DLD Enrollment Setup : Eligibility and Validation
1395   --          This function validates the time slot registration times assigned to the student
1396   --          against SYSDATE when the CHK_TIME_PER person step is selected in the Enrollment
1397   --          Category Procedure Details Form. The function returns DENY or WARN messages if
1398   --          the student is not eligible to register. The validation is done for the Term
1399   --          calendar.
1400   --
1401   --Known limitations/enhancements and/or remarks:
1402   --
1403   --Change History:
1404   --Who         When            What
1405   --Bayadav    11-OCt-2001      Modified the validation of timeslots as a part of enh bug:2043044
1406   --Bayadav    30-Oct-2001      Corrected the code comparing date by removing to_char function
1407   --  svanukur     31-may-03     Converted the person?unit step timeslot validation step which can be configured for DENY or WARN
1408   --                           Added a new parameter p_notification_flag and modified p_message to IN OUT as per the Deny/Warn behaviour build # 2829272
1409   -------------------------------------------------------------------------------------------------
1410 
1411     l_enr_method_type     igs_en_method_type.enr_method_type%TYPE;
1412     l_step                igs_en_cat_prc_step.s_enrolment_step_type%TYPE;
1413     l_vald_timeslot       BOOLEAN;
1414     --
1415     -- cursor to check whether the step is oevrridden or not
1416     --
1417 
1418     l_step_override    BOOLEAN;
1419 
1420     l_person_type          igs_pe_person_types.person_type_code%TYPE;
1421     l_step_override_limit  igs_en_elgb_ovr_step.step_override_limit%TYPE;
1422 
1423     FUNCTION vald_timeslot
1424     RETURN BOOLEAN
1425     IS
1426 
1427     ------------------------------------------------------------------------------------
1428     --Created by  : smanglm ( Oracle IDC)
1429     --Date created: 19-JUN-2001
1430     --
1431     --Purpose:  local program unit to function eval_timeslot
1432     --          this function select all timeslots assigned to the student
1433     --          either at term level or at teach level
1434     --
1435     --Known limitations/enhancements and/or remarks:
1436     --
1437     --Change History:
1438     --Who         When            What
1439     --knaraset   20-May-2002    Romoving the validation against census date as per bug 2380758
1440     -------------------------------------------------------------------------------------
1441 
1442       --
1443       -- cursor to fetch the timeslot associated with the student
1444       --
1445       CURSOR c_stud_timeslot (cp_cal_type           igs_en_timeslot_para.cal_type%TYPE,
1446                               cp_sequence_number    igs_en_timeslot_para.sequence_number%TYPE) IS
1447              SELECT tr.start_dt_time,
1448                     tr.end_dt_time
1449              FROM   igs_en_timeslot_rslt tr,
1450                     igs_en_timeslot_para tp
1451              WHERE  tr.person_id = p_person_id
1452              AND    tr.igs_en_timeslot_para_id = tp.igs_en_timeslot_para_id
1453              AND    tp.cal_type = cp_cal_type
1454              AND    tp.sequence_number = cp_sequence_number;
1455       rec_stud_timeslot    c_stud_timeslot%ROWTYPE;
1456 
1457       --
1458       --cursor to fetch cal type and sequnece no when p_uoo_id is not null
1459       --
1460       CURSOR c_calendar IS
1461              SELECT cal_type,
1462                     ci_sequence_number
1463              FROM   igs_ps_unit_ofr_opt
1464              WHERE  uoo_id = p_uoo_id;
1465       l_cal_type    igs_ps_unit_ofr_opt.cal_type%TYPE DEFAULT NULL;
1466       l_seq_number  igs_ps_unit_ofr_opt.ci_sequence_number%TYPE DEFAULT NULL;
1467 
1468       --
1469       -- cursor to fetch load cal type and load seq number based on teach cal type and teach seq number
1470       --
1471       CURSOR c_load_cal (cp_teach_cal_type   igs_ca_teach_to_load_v.teach_cal_type%TYPE,
1472                          cp_teach_ci_seq_no  igs_ca_teach_to_load_v.teach_ci_sequence_number%TYPE) IS
1473              SELECT load_cal_type,
1474                     load_ci_sequence_number
1475              FROM   igs_ca_teach_to_load_v
1476              WHERE  teach_cal_type = cp_teach_cal_type
1477              AND    teach_ci_sequence_number = cp_teach_ci_seq_no;
1478       rec_load_cal   c_load_cal%ROWTYPE;
1479       lv_validate_timeslot   CONSTANT  VARCHAR2(30) :=  FND_PROFILE.VALUE('IGS_EN_VAL_TIMESLOT');
1480       lv_timeslot_rec_found BOOLEAN ;
1481     BEGIN
1482       --
1483       -- get the cal type and seq number if p_uoo_id is not null
1487          OPEN c_calendar;
1484       --
1485 
1486       IF p_uoo_id IS NOT NULL THEN
1488          FETCH c_calendar INTO l_cal_type,l_seq_number;
1489          CLOSE c_calendar;
1490       END IF;
1491       --
1492       -- now fetch the timeslot based on the obtained cal_type and seq number and if the values are null
1493       -- pass p_load_calendar_type and p_load_cal_sequence_number
1494       --
1495       lv_timeslot_rec_found := FALSE;
1496       FOR rec_stud_timeslot IN c_stud_timeslot (nvl(l_cal_type,p_load_calendar_type),
1497                                                 nvl(l_seq_number,p_load_cal_sequence_number))
1498       LOOP
1499         -- check the profile option value .IF profile option 'Validate Timeslots' is 'START_TIME_ONLY' then
1500         -- get the enrolled census date and check if timeslot current date falls b/w timeslot start and enrolled census date
1501         -- else if profile option'Validate timeslots' value is 'START_TO_END_TIME' or not set then check if timeslot
1502         -- current date falls b/w timeslot start and end time.Included code as a part of enhancement bug:2043044
1503 
1504         -- Timeslot record found
1505 
1506         lv_timeslot_rec_found := TRUE;
1507 
1508         IF lv_validate_timeslot = 'START_TIME_ONLY' then
1509           IF (SYSDATE >=  rec_stud_timeslot.start_dt_time) OR  (rec_stud_timeslot.start_dt_time IS NULL ) THEN
1510            --Student is eligible
1511                RETURN TRUE;
1512           END IF;
1513     --  profile value is other than start_time_only
1514       ELSE
1515         IF (
1516            ( (SYSDATE >= rec_stud_timeslot.start_dt_time) OR  rec_stud_timeslot.start_dt_time IS NULL )
1517             AND
1518            ( ( SYSDATE  <= rec_stud_timeslot.end_dt_time) OR  rec_stud_timeslot.end_dt_time IS NULL)
1519            ) THEN
1520               --
1521               -- student has been assigned at least one timeslot at unit level and hence return TRUE
1522               --
1523               RETURN TRUE;
1524         END IF;
1525       END IF;
1526       END LOOP;
1527       --
1528       -- check at the load calendar also if it is not defined at teach level and look at term level for the timeslot assignment
1529       --
1530       FOR rec_load_cal IN c_load_cal (l_cal_type,l_seq_number)
1531       LOOP
1532         FOR rec_stud_timeslot IN c_stud_timeslot (rec_load_cal.load_cal_type,
1533                                                   rec_load_cal.load_ci_sequence_number)
1534         LOOP
1535         -- check the profile option value .IF profile option 'Validate Timeslots' is 'START_TIME_ONLY' then
1536         -- check if timeslot current date is greater than or equal to timeslot start
1537         -- else if profile option'Validate timeslots' value is 'START_TO_END_TIME' or not set then check if timeslot
1538         -- current date falls b/w timeslot start and end time.Included code as a part of enhancement bug:2043044
1539 
1540         -- Timeslot record found
1541 
1542         lv_timeslot_rec_found := TRUE;
1543 
1544          IF lv_validate_timeslot = 'START_TIME_ONLY' then
1545           IF (SYSDATE >= rec_stud_timeslot.start_dt_time) OR (rec_stud_timeslot.start_dt_time IS NULL ) THEN
1546              --Student is eligible
1547                RETURN TRUE;
1548           END IF;
1549         ELSE
1550        -- check if timeslot current date falls b/w timeslot start and end time and profile value is other than start_time_value
1551           --
1552           IF (
1553               ( (SYSDATE >= rec_stud_timeslot.start_dt_time) OR    rec_stud_timeslot.start_dt_time IS NULL ) AND
1554               ( (SYSDATE <= rec_stud_timeslot.end_dt_time) OR    rec_stud_timeslot.end_dt_time IS NULL )
1555              ) THEN
1556                -- student has been assigned at least one timeslot at term level and hence return TRUE
1557                RETURN TRUE;
1558           END IF;
1559         END IF;
1560        END LOOP;
1561       END LOOP;
1562 
1563       IF NOT lv_timeslot_rec_found THEN
1564          --
1565          -- No Timeslot records defined/alloted for the Student
1566          -- Added as part of Bug 2380758
1567         RETURN TRUE;
1568       ELSE
1569         RETURN FALSE;
1570       END IF;
1571 
1572     END vald_timeslot;
1573 
1574   --
1575   -- main begin for eval_timeslot
1576   --
1577   BEGIN
1578     --
1579     -- assign the p_enrl_method to l_enr_method_type
1580     --
1581     l_enr_method_type := p_enrl_method;
1582     --
1583     -- decide the step to be used depending on whether the p_uoo_id is null or not. If null, use
1584     -- CHK_TIME_PER else use CHK_TIME_UNIT
1585     --
1586     IF p_uoo_id IS NOT NULL THEN
1587        l_step := 'CHK_TIME_UNIT';
1588     ELSE
1589        l_step := 'CHK_TIME_PER';
1590     END IF;
1591     IF p_person_type IS NOT NULL THEN
1592             --
1593             -- get the system person type
1594             --
1595             l_person_type := get_sys_pers_type (
1596                                                  p_person_type => p_person_type,
1597                                                  p_message     => p_message
1598                                                );
1599             IF p_message IS NOT NULL THEN
1600                RETURN FALSE;
1601             END IF;
1602     END IF;
1603 
1604     --
1605     -- check the step is overridden for the given load calendar/teaching period or not
1606     -- if yes, return true else carry out NOCOPY the rest of validation for timeslot
1607     --
1608     l_step_override := igs_en_gen_015.validation_step_is_overridden
1609                                  (
1610                                    p_eligibility_step_type        => l_step,
1611                                    p_load_cal_type                => p_load_calendar_type,
1612                                    p_load_cal_seq_number          => p_load_cal_sequence_number,
1613                                    p_person_id                    => p_person_id,
1614                                    p_uoo_id                       => p_uoo_id,
1615                                    p_step_override_limit          => l_step_override_limit
1616                                 );
1617     IF l_step_override THEN
1618       RETURN TRUE;
1619     END IF;
1620 
1621     --
1622     -- depending on the return value of l_vald_timeslot, return from the main function
1623     --
1624     -- call the local program unit vald_timeslot for selecting timeslot
1625     l_vald_timeslot := vald_timeslot;
1626     IF l_vald_timeslot THEN
1627        --
1628        -- validation of timeslots returns TRUE
1629        --
1630        RETURN TRUE;
1631     ELSIF NOT l_vald_timeslot THEN
1632       IF p_notification_flag = 'DENY' THEN
1633         p_message := 'IGS_SS_DENY_TSLOT';
1634       ELSIF p_notification_flag = 'WARN' THEN
1635         p_message := 'IGS_SS_WARN_TSLOT';
1636       END IF;
1637       RETURN FALSE;
1638     END IF;
1639 
1640     RETURN TRUE;
1641 
1642   END eval_timeslot;
1643 
1644  FUNCTION get_sys_pers_type (
1645                               p_person_type                     IN  VARCHAR2,
1646                               p_message                        OUT NOCOPY  VARCHAR2
1647                             )
1648     ------------------------------------------------------------------------------------
1649     --Created by  : smanglm ( Oracle IDC)
1650     --Date created: 19-JUN-2001
1651     --
1652     --Purpose:  private function get_sys_pers_type to get the system person type
1653     --
1654     --Known limitations/enhancements and/or remarks:
1655     --
1656     --Change History:
1657     --Who          When            What
1658     --Nalin Kumar  14-May-2002     Modified this function as per the Bug# 2364461.
1659     --                             Removed the code logic to check the whether the
1660     --                             passed person type is not a system person type or not.
1661     -- knaraset    20-May-2002     Removed the Upper() in the where clause of cursor
1662     --                               c_sys_pers_type as part of Bug 2380758.
1663     -------------------------------------------------------------------------------------
1664  RETURN VARCHAR2 IS
1665    --
1666    -- cursor c_sys_pers_type to fetch the system person type
1667    --
1668    CURSOR c_sys_pers_type (cp_person_type igs_pe_person_types.person_type_code%TYPE) IS
1669           SELECT system_type
1670           FROM   igs_pe_person_types
1671           WHERE  person_type_code = cp_person_type;
1672    l_sys_pers_type  igs_pe_person_types.person_type_code%TYPE;
1673 
1674 
1675  BEGIN
1676    p_message := NULL;
1677    --
1678    -- now get the corresponding system person type, if not found return a error message
1679    --
1680    OPEN c_sys_pers_type (p_person_type);
1681    FETCH c_sys_pers_type INTO l_sys_pers_type;
1682    IF c_sys_pers_type%NOTFOUND THEN
1683       p_message := 'IGS_EN_NO_SYS_PERS_TYPE';
1684       RETURN NULL;
1685    ELSE
1686       RETURN l_sys_pers_type;
1687    END IF;
1688    CLOSE c_sys_pers_type;
1689 
1690  END get_sys_pers_type;
1691 
1692 PROCEDURE eval_ss_deny_all_hold( p_person_id                       IN  NUMBER,
1693                                  p_person_type                     IN  VARCHAR2,
1694                                  p_course_cd                       IN  VARCHAR2,
1695                                  p_load_calendar_type              IN  VARCHAR2,
1696                                  p_load_cal_sequence_number        IN  NUMBER,
1697                                  p_status                          OUT NOCOPY  VARCHAR2,
1698                                  p_message                         OUT NOCOPY  VARCHAR2) AS
1699 ------------------------------------------------------------------------------------
1700 --Created by  : kkillams ( Oracle IDC)
1701 --Date created: 20-JAN-2002
1702 --
1703 --Purpose:procedure is a wrapper eval_deny_all_hold function for Self Service purpose only.
1704 --
1705 --Known limitations/enhancements and/or remarks:
1706 --
1707 --Change History:
1708 --Who          When            What
1709 -------------------------------------------------------------------------------------
1710 
1714 l_comm_type          VARCHAR2(100);
1711 CURSOR get_enr_method IS    SELECT enr_method_type FROM igs_en_method_type
1712                                                    WHERE self_service = 'Y'
1713                                                    AND   closed_ind = 'N';
1715 l_enrolment_cat      VARCHAR2(100);
1716 l_enr_method_type    igs_en_method_type.enr_method_type%TYPE;
1717 BEGIN
1718      p_status := 'S';
1719      p_message  := NULL;
1720      --Get the enrollment category and enrollment commencement type.
1721      igs_en_elgbl_person.get_enrl_comm_type(p_person_id         =>p_person_id,
1722                                             p_course_cd         =>p_course_cd,
1723                                             p_cal_type          =>p_load_calendar_type,
1724                                             p_cal_seq_number    =>p_load_cal_sequence_number,
1725                                             p_enrolment_cat     =>l_enrolment_cat,
1726                                             p_commencement_type =>l_comm_type ,
1727                                             p_message           =>p_message);
1728      --If p_message returns some message means terminate the procedure
1729      IF p_message IS NOT NULL THEN
1730         p_status := 'E';
1731         RETURN;
1732      END IF;
1733 
1734      --Get the enrollment method for the self service responsibility.
1735      OPEN get_enr_method;
1736      FETCH get_enr_method INTO l_enr_method_type;
1737      IF get_enr_method%NOTFOUND THEN
1738         CLOSE get_enr_method;
1739         RETURN;
1740      ELSE
1741         CLOSE get_enr_method;
1742 
1743         IF NOT igs_en_elgbl_person.eval_deny_all_hold(
1744                                                       p_person_id,
1745                                                       p_person_type,
1746                                                       p_load_calendar_type,
1747                                                       p_load_cal_sequence_number,
1748                                                       l_enrolment_cat,
1749                                                       l_comm_type,
1750                                                       l_enr_method_type,
1751                                                       p_message) THEN
1752                p_status := 'E';
1753                RETURN;
1754         END IF;
1755      END IF;
1756 END eval_ss_deny_all_hold;
1757 
1758 PROCEDURE get_enrl_comm_type(p_person_id                       IN  NUMBER,
1759                              p_course_cd                       IN  VARCHAR2,
1760                              p_cal_type                        IN  VARCHAR2,
1761                              p_cal_seq_number                  IN  NUMBER,
1762                              p_enrolment_cat                   OUT NOCOPY  VARCHAR2,
1763                              p_commencement_type               OUT NOCOPY  VARCHAR2,
1764                              p_message                         OUT NOCOPY  VARCHAR2) AS
1765 ------------------------------------------------------------------------------------
1766 --Created by  : kkillams ( Oracle IDC)
1767 --Date created: 20-JAN-2002
1768 --
1769 --Purpose: Procedure derives the Enrollment Category,Commencement Type for
1770 -- a given person, course code and calendar.
1771 --Known limitations/enhancements and/or remarks:
1772 --
1773 --Change History:
1774 --Who          When            What
1775 -------------------------------------------------------------------------------------
1776 l_alt_cd                          igs_ca_inst.alternate_code%TYPE;
1777 l_acad_cal_type                   igs_ca_inst.cal_type%TYPE;
1778 l_acad_ci_sequence_number         igs_ca_inst.sequence_number%TYPE;
1779 l_acad_ci_start_dt                igs_ca_inst.start_dt%TYPE;
1780 l_acad_ci_end_dt                  igs_ca_inst.end_dt%TYPE;
1781 l_en_cal_type                     igs_ca_inst.cal_type%TYPE;
1782 l_en_ci_seq_num                   igs_ca_inst.sequence_number%TYPE;
1783 l_message_name                    VARCHAR2(100);
1784 l_dummy                           VARCHAR2(200);
1785 BEGIN
1786 
1787       --Function gets the academic calendar instance details for a sub ordinate calendar
1788       l_alt_cd := igs_en_gen_002.enrp_get_acad_alt_cd( p_cal_type,
1789                                                        p_cal_seq_number,
1790                                                        l_acad_cal_type,
1791                                                        l_acad_ci_sequence_number,
1792                                                        l_acad_ci_start_dt,
1793                                                        l_acad_ci_end_dt,
1794                                                        l_message_name);
1795       IF l_message_name IS NOT NULL THEN
1796           p_message := l_message_name;
1797           RETURN;
1798       END IF;
1799 
1800         --Function gets the enrollment category and commencement type for a person and course code.
1801         p_enrolment_cat:=igs_en_gen_003.enrp_get_enr_cat(
1802                                                           p_person_id,
1803                                                           p_course_cd,
1804                                                           l_acad_cal_type,
1805                                                           l_acad_ci_sequence_number,
1806                                                           NULL,
1807                                                           l_en_cal_type,
1808                                                           l_en_ci_seq_num,
1809                                                           p_commencement_type,
1810                                                           l_dummy);
1811 END get_enrl_comm_type;
1812 
1813 
1814 END  IGS_EN_ELGBL_PERSON;