DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_PS_VALIDATE_LGCY_PKG

Source


1 PACKAGE BODY igs_ps_validate_lgcy_pkg AS
2 /* $Header: IGSPS86B.pls 120.17 2006/04/10 05:26:28 sommukhe ship $ */
3 
4   /***********************************************************************************************
5     Created By     :  Sanjeeb Rakshit, Shirish Tatiko, Saravana Kumar
6     Date Created By:  11-NOV-2002
7     Purpose        :  This package has validation functions which will be called from sub processes,
8                       in IGS_PS_UNIG_LGCY_PKG package.
9                       This Package also provides few generic utility function like set_msg, get_lkup_meaning.
10 
11     Known limitations,enhancements,remarks:
12     Change History (in reverse chronological order)
13     Who         When            What
14     smvk         28-Jul-2004    Bug # 3793580. Created utility procedure get_uso_id.
15     sarakshi     12-Apr-2004    bug#3555871, Removed the function get_call_number
16     smvk        25-Nov-2003     Bug # 2833971. Modified validate_usec_el procedure.
17     smvk         10-Oct-2003    Bug # 3052445. Added utility function is_waitlist_allowed and modified validate_waitlist_allowed function.
18     smvk         23-Sep-2003    Bug # 3121311, Removed the utility procedures uso_effective_dates, validate_staff_person and validate_instructor.
19     SMVK         27-Jun-2003    Bug # 2999888. Created procedure validate_unit_reference.
20     jbegum      02-June-2003    Bug # 2972950.
21                                 For Legacy Enhancements TD:
22                                 Modified the code to use messages rather than lookup codes mentioned in TD, due to
23                                 Non Backward compatible changes in igslkups.ldt.
24                                 Created procedure validate_usec_el and uso_effective_dates. Functions post_uso_ins_busi
25                                 and validate_instructor. Defined usec_tr_rectype record struture, usec_tr_tbltype table structure and
26                                 v_tab_usec_tr global parameter. Created new procedure validate_enr_lmts. The changes are as mentioned in TD.
27                                 Modified validate_staff_person, get_call_number()
28                                 As a part of Binding issues, modified unit_version procedure and validate_org_unit_cd function.
29                                 For the PSP Scheduling Enhancements TD:
30                                 Modified the procedure validate_usec_occurs.
31                                 For the PSP Enhancements TD:
32                                 Modified the procedure validate_uoo.
33     sarakshi  04-Mar-2003      Bug#2768783,modified get_call_number and validate_uoo procedures
34     smvk      12-Dec-2002      Passing the value TRUE to the newly added parameter p_b_lgcy_validator to the
35                                functions call igs_ps_val_tr.crsp_val_tr_perc,igs_ps_val_ud.crsp_val_ud_perc.
36                                As a part of the Bug # 2696207.
37     smvk       26-Dec-2002     Added a generic procedure (get_party_id) and a function (validate_staff_person)
38                                As a part of Bug # 2721495
39   ********************************************************************************************** */
40 
41   g_n_user_id igs_ps_unit_ver_all.created_by%TYPE := NVL(fnd_global.user_id,-1);
42   g_n_login_id igs_ps_unit_ver_all.last_update_login%TYPE := NVL(fnd_global.login_id,-1);
43 
44   -- for doing certain validation at unit section level while importing unit section occurrence of instructors
45   TYPE usec_tr_rectype IS RECORD( uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
46                                   instr_index NUMBER);
47   TYPE usec_tr_tbltype IS TABLE OF usec_tr_rectype index by binary_integer;
48   v_tab_usec_tr usec_tr_tbltype;
49 
50 
51   PROCEDURE upd_usec_occurs_schd_status ( p_uoo_id IN NUMBER, schd_stat IN VARCHAR2 ) AS
52 
53     --Bug # 2831065. Update the USO which are not in schedule status processing and input schedule status schd_stat.
54     CURSOR c_usec_occurs ( p_uoo_id IN NUMBER, cp_c_schd_stat IN  igs_ps_usec_occurs.schedule_status%TYPE) IS
55       SELECT ROWID, puo.*
56       FROM   igs_ps_usec_occurs puo
57       WHERE  uoo_id = p_uoo_id
58         AND  (schedule_status IS NULL OR schedule_status <> cp_c_schd_stat)
59         AND  NO_SET_DAY_IND ='N'
60       FOR UPDATE NOWAIT;
61 
62     l_c_cancel igs_ps_usec_occurs_all.cancel_flag%TYPE;
63     l_c_schedule_status igs_ps_usec_occurs_all.schedule_status%TYPE;
64 
65   BEGIN
66 
67     FOR c_usec_occurs_rec IN c_usec_occurs(p_uoo_id, schd_stat) LOOP
68 
69       IF schd_stat ='USER_CANCEL' THEN
70          IF c_usec_occurs_rec.schedule_status = 'PROCESSING'  THEN
71             l_c_schedule_status := 'PROCESSING';
72          ELSE
73             l_c_schedule_status := schd_stat;
74          END IF;
75          l_c_cancel := 'Y';
76       ELSE
77          l_c_schedule_status := schd_stat;
78          l_c_cancel := 'N';
79       END IF;
80 
81       IF schd_stat ='USER_CANCEL' OR (schd_stat ='USER_UPDATE' AND (c_usec_occurs_rec.schedule_status IS NOT NULL AND c_usec_occurs_rec.schedule_status <> 'PROCESSING')) THEN
82 
83           igs_ps_usec_occurs_pkg.update_row (
84            x_rowid                             => c_usec_occurs_rec.ROWID,
85            x_unit_section_occurrence_id        => c_usec_occurs_rec.unit_section_occurrence_id,
86            x_uoo_id                            => c_usec_occurs_rec.uoo_id,
87            x_monday                            => c_usec_occurs_rec.monday,
88            x_tuesday                           => c_usec_occurs_rec.tuesday,
89            x_wednesday                         => c_usec_occurs_rec.wednesday,
90            x_thursday                          => c_usec_occurs_rec.thursday,
91            x_friday                            => c_usec_occurs_rec.friday,
92            x_saturday                          => c_usec_occurs_rec.saturday,
93            x_sunday                            => c_usec_occurs_rec.sunday,
94            x_start_time                        => c_usec_occurs_rec.start_time,
95            x_end_time                          => c_usec_occurs_rec.end_time,
96            x_building_code                     => c_usec_occurs_rec.building_code,
97            x_room_code                         => c_usec_occurs_rec.room_code,
98            x_schedule_status                   => l_c_schedule_status,
99            x_status_last_updated               => c_usec_occurs_rec.status_last_updated,
100            x_instructor_id                     => c_usec_occurs_rec.instructor_id,
101            X_attribute_category                => c_usec_occurs_rec.attribute_category,
102            X_attribute1                        => c_usec_occurs_rec.attribute1,
103            X_attribute2                        => c_usec_occurs_rec.attribute2,
104            X_attribute3                        => c_usec_occurs_rec.attribute3,
105            X_attribute4                        => c_usec_occurs_rec.attribute4,
106            X_attribute5                        => c_usec_occurs_rec.attribute5,
107            X_attribute6                        => c_usec_occurs_rec.attribute6,
108            X_attribute7                        => c_usec_occurs_rec.attribute7,
109            X_attribute8                        => c_usec_occurs_rec.attribute8,
110            X_attribute9                        => c_usec_occurs_rec.attribute9,
111            X_attribute10                       => c_usec_occurs_rec.attribute10,
112            X_attribute11                       => c_usec_occurs_rec.attribute11,
113            X_attribute12                       => c_usec_occurs_rec.attribute12,
114            X_attribute13                       => c_usec_occurs_rec.attribute13,
115            X_attribute14                       => c_usec_occurs_rec.attribute14,
116            X_attribute15                       => c_usec_occurs_rec.attribute15,
117            X_attribute16                       => c_usec_occurs_rec.attribute16,
118            X_attribute17                       => c_usec_occurs_rec.attribute17,
119            X_attribute18                       => c_usec_occurs_rec.attribute18,
120            X_attribute19                       => c_usec_occurs_rec.attribute19,
121            X_attribute20                       => c_usec_occurs_rec.attribute20,
122            x_error_text                        => c_usec_occurs_rec.error_text,
123            x_mode                              => 'R',
124            X_start_date                        => c_usec_occurs_rec.start_date,
125            X_end_date                          => c_usec_occurs_rec.end_date,
126            X_to_be_announced                   => c_usec_occurs_rec.to_be_announced,
127            x_dedicated_building_code           => c_usec_occurs_rec.dedicated_building_code,
128            x_dedicated_room_code               => c_usec_occurs_rec.dedicated_room_code,
129            x_preferred_building_code           => c_usec_occurs_rec.preferred_building_code,
130            x_preferred_room_code               => c_usec_occurs_rec.preferred_room_code,
131            x_inst_notify_ind                   => c_usec_occurs_rec.inst_notify_ind,
132            x_notify_status                     => c_usec_occurs_rec.notify_status,
133            x_preferred_region_code             => c_usec_occurs_rec.preferred_region_code,
134            x_no_set_day_ind                    => c_usec_occurs_rec.no_set_day_ind,
135            x_cancel_flag                       => l_c_cancel,
136  	   x_occurrence_identifier             => c_usec_occurs_rec.occurrence_identifier,
137 	   x_abort_flag                        => c_usec_occurs_rec.abort_flag
138          );
139        END IF;
140     END LOOP;
141 
142  END upd_usec_occurs_schd_status;
143 
144   PROCEDURE validate_enr_lmts( p_n_ern_min igs_ps_unit_ver_all.enrollment_minimum%TYPE,
145                                p_n_enr_max igs_ps_unit_ver_all.enrollment_maximum%TYPE,
146                                p_n_ovr_max igs_ps_unit_ver_all.override_enrollment_max%TYPE,
147                                p_n_adv_max igs_ps_unit_ver_all.advance_maximum%TYPE,
148                                p_c_rec_status IN OUT NOCOPY VARCHAR2) ;
149 
150   PROCEDURE unit_version(p_unit_ver_rec    IN OUT NOCOPY  igs_ps_generic_pub.unit_ver_rec_type,
151                          p_coord_person_id IN             igs_ps_unit_ver_all.coord_person_id%TYPE) AS
152   /***********************************************************************************************
153 
154   Created By:         sarakshi
155   Date Created By:    13-Nov-2002
156   Purpose:            This procedure validates legacy data.
157 
158   Known limitations,enhancements,remarks:
159 
160   Change History
161 
162   Who       When          What
163   sommukhe  10-Mar-2006   Bug#5140666,changed the sizse of l_func_name from 10 to 50.
164   sommukhe  16-FEB-2006   Bug#5040156,Description: Change call from GET_WHERE_CLAUSE to GET_WHERE_CLAUSE_API1 as a part of Literal fix
165   sarakshi  04-May-2004   Enh#3568858, added validation related to columns ovrd_wkld_val_flag, workload_val_code
166   sarakshi  10-Nov-2003   Enh#3116171, added business logic related to the newly introduced field BILLING_CREDIT_POINTS
167   sarakshi  22-Aug-2003   Enh#3045069, added validations related to repeatable indicator.
168   sarakshi  04-Jul-2003   Enh#3036221,removed the validation for repeatable checkbox
169   jbegum    02-June-2003  Bug # 2972950.
170                           For the Legacy Enhancements TD:
171                           Add the call to validate_enr_lmts procedure as mentioned in TD.
172                           As a part of Binding issues, using bind variable in the ref cursor.
173   smvk      27-feb-2003  Bug #2770598. Added the validation "re-enrollment for credit('Repeatable_Ind') is not allowed
174                          then the max_repeats_for_credit maximum repeats credit points and max_repeats_for_funding should be null.
175   smvk      26-Dec-2002  Bug # 2721495. Using the function to validate_staff_person instead of igs_en_gen_003.get_staff_ind.
176   ***********************************************************************************************/
177   CURSOR c_subtitle(cp_unit_cd        igs_ps_unit_subtitle.unit_cd%TYPE,
178                       cp_version_number igs_ps_unit_subtitle.version_number%TYPE) IS
179   SELECT 'X'
180   FROM   igs_ps_unit_subtitle
181   WHERE  closed_ind='N'
182   AND    approved_ind='Y'
183   AND    unit_cd=cp_unit_cd
184   AND    version_number=cp_version_number;
185   l_c_var           VARCHAR2(1);
186   l_c_message_name  fnd_new_messages.message_name%TYPE;
187   l_func_name VARCHAR2(50) := 'UNIT_VERSION_LGCY';
188 
189   TYPE c_ref_cur IS REF CURSOR;
190   c_org_cur         c_ref_cur;
191   l_c_where_clause  VARCHAR2(3000);
192   l_c_cur_stat      VARCHAR2(3100);
193   l_c_rec_found       VARCHAR2(1);
194   BEGIN
195     --Validate the start_dt,end_dt and expiry_dt fields,using the generic function
196     IF (NOT igs_ps_val_us.crsp_val_ver_dt(p_unit_ver_rec.start_dt,
197                                           p_unit_ver_rec.end_dt,
198                                           p_unit_ver_rec.expiry_dt,
199                                           l_c_message_name,
200                                           TRUE)) THEN
201       p_unit_ver_rec.status:='E';
202     END IF;
203 
204     --Validate end date cannot be set for non inactive status
205     IF (NOT igs_ps_val_uv.crsp_val_uv_end_sts(p_unit_ver_rec.end_dt,
206                                               p_unit_ver_rec.unit_status,
207                                               l_c_message_name)) THEN
208       igs_ps_validate_lgcy_pkg.set_msg(l_c_message_name,NULL,NULL,FALSE);
209       p_unit_ver_rec.status:='E';
210     END IF;
211 
212     --Removed the validation to check unit coordinator is a staff person.As a part of bug # 3121311
213 
214     --Validate if unit version has the assessable indicator checked then it must have supplementary exam checked
215     IF (NOT igs_ps_val_uv.crsp_val_uv_sup_exam(p_unit_ver_rec.supp_exam_permitted_ind,
216                                                p_unit_ver_rec.assessable_ind,
217                                                l_c_message_name)) THEN
218 
219       igs_ps_validate_lgcy_pkg.set_msg(l_c_message_name,NULL,NULL,FALSE);
220       p_unit_ver_rec.status :='E';
221     END IF;
222 
223     --Validate atleast one unit enrollment method type between interactive Voice response and
224     --self service should be selected
225     IF p_unit_ver_rec.ivr_enrol_ind = 'N' and p_unit_ver_rec.ss_enrol_ind = 'N' THEN
226       igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_ONE_UNIT_ENR_MTHD',NULL,NULL,FALSE);
227       p_unit_ver_rec.status :='E';
228     END IF;
229 
230     --Validate only one version of unit can exist with active status and expiry date not set
231     IF (NOT igs_ps_val_uv.crsp_val_uv_exp_sts(p_unit_ver_rec.unit_cd,
232                                          p_unit_ver_rec.version_number,
233                                          p_unit_ver_rec.expiry_dt,
234                                          p_unit_ver_rec.unit_status,
235                                          l_c_message_name)) THEN
236 
237       igs_ps_validate_lgcy_pkg.set_msg(l_c_message_name,NULL,NULL,FALSE);
238       p_unit_ver_rec.status :='E';
239     END IF;
240 
241     --Validate status with respect to superior and subordinate units
242     IF (NOT igs_ps_val_uv.crsp_val_uv_unit_sts(p_unit_ver_rec.unit_cd,
243                                                p_unit_ver_rec.version_number,
244                                                p_unit_ver_rec.unit_status,
245                                                NULL,
246                                                l_c_message_name,
247                                                TRUE)) THEN
248       p_unit_ver_rec.status :='E';
249     END IF;
250 
251     --Validate if auditable checkbox is checked then only audit_permission_ind and max_auditors_allowed can have values
252     IF p_unit_ver_rec.auditable_ind = 'N' THEN
253       IF p_unit_ver_rec.audit_permission_ind = 'Y' THEN
254         igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_AUDIT_PERMISSION_EXIST',NULL,NULL,FALSE);
255         p_unit_ver_rec.status :='E';
256       END IF;
257       IF p_unit_ver_rec.max_auditors_allowed IS NOT NULL THEN
258         igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_MAX_AUDIT_ALWD_EXIST',NULL,NULL,FALSE);
259         p_unit_ver_rec.status :='E';
260       END IF;
261     END IF;
262 
263     --Validate if credit point indicator is checked and points max,points min,points increment are null
264     IF p_unit_ver_rec.points_override_ind = 'Y' AND (p_unit_ver_rec.points_increment IS NULL OR
265                                                      p_unit_ver_rec.points_max IS NULL OR
266                                                      p_unit_ver_rec.points_min IS NULL) THEN
267 
268       igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_CPS_NULL',NULL,NULL,FALSE);
269       p_unit_ver_rec.status :='E';
270     END IF;
271 
272     --Validate the credit points related validations using generic function
273     IF (NOT igs_ps_val_uv.crsp_val_uv_pnt_ovrd(p_unit_ver_rec.points_override_ind,
274                                                p_unit_ver_rec.points_increment,
275                                                p_unit_ver_rec.points_min,
276                                                p_unit_ver_rec.points_max,
277                                                p_unit_ver_rec.enrolled_credit_points,
278                                                p_unit_ver_rec.achievable_credit_points,
279                                                l_c_message_name,
280                                                TRUE)) THEN
281       p_unit_ver_rec.status :='E';
282     END IF;
283 
284 
285     --Validate if override credit points indicator has been unchecked and points max,points min,
286     --points increment are not null
287     IF p_unit_ver_rec.points_override_ind = 'N' AND (p_unit_ver_rec.points_increment IS NOT NULL OR
288                                                      p_unit_ver_rec.points_max IS NOT NULL OR
289                                                      p_unit_ver_rec.points_min IS NOT NULL) THEN
290       igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_CPS_NOT_NULL',NULL,NULL,FALSE);
291       p_unit_ver_rec.status :='E';
292     END IF;
293 
294     --Validate if approved subtitles exists for a unit version, if then only approved subtitles can only be
295     --used.If approved subtitles does not exits then free format subtitles can be used
296     OPEN c_subtitle(p_unit_ver_rec.unit_cd,p_unit_ver_rec.version_number);
297     FETCH c_subtitle INTO l_c_var;
298     IF c_subtitle%FOUND THEN
299       IF p_unit_ver_rec.subtitle_approved_ind = 'N' AND p_unit_ver_rec.subtitle IS NOT NULL THEN
300         igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_INVALID_SUBTITLE',NULL,NULL,FALSE);
301         p_unit_ver_rec.status :='E';
302       END IF;
303     END IF;
304     CLOSE c_subtitle;
305 
306 
307     --Billing credit Points can be provided only when auditable_ind is set to Y
308     IF p_unit_ver_rec.auditable_ind = 'N' AND p_unit_ver_rec.billing_credit_points IS NOT NULL THEN
309        igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_BILL_CRD_PTS_ERROR',NULL,NULL,FALSE);
310        p_unit_ver_rec.status :='E';
311     END IF;
312 
313    --Added this validation as a part of bug#4199404
314    IF p_unit_ver_rec.approval_date IS NOT NULL AND p_unit_ver_rec.approval_date > p_unit_ver_rec.start_dt THEN
315        igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_VALID_APPRDATE',NULL,NULL,FALSE);
316        p_unit_ver_rec.status :='E';
317    END IF;
318 
319     --validation releted to repeatable indicator columm
320     IF p_unit_ver_rec.repeatable_ind = 'X' THEN
321        IF p_unit_ver_rec.max_repeats_for_credit IS NOT NULL OR p_unit_ver_rec.max_repeats_for_funding IS NOT NULL OR
322           p_unit_ver_rec.max_repeat_credit_points IS NOT NULL OR p_unit_ver_rec.same_teach_period_repeats IS NOT NULL OR
323           p_unit_ver_rec.same_teach_period_repeats_cp IS NOT NULL THEN
324 
325           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_RPT_X',NULL,NULL,FALSE);
326           p_unit_ver_rec.status :='E';
327        END IF;
328        IF p_unit_ver_rec.same_teaching_period = 'Y' THEN
329           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_RPT_X_SAME_TCH_PRD',NULL,NULL,FALSE);
330           p_unit_ver_rec.status :='E';
331        END IF;
332 
333     ELSIF p_unit_ver_rec.repeatable_ind = 'N' THEN
334        IF p_unit_ver_rec.max_repeat_credit_points IS NOT NULL OR p_unit_ver_rec.same_teach_period_repeats IS NOT NULL OR
335           p_unit_ver_rec.same_teach_period_repeats_cp IS NOT NULL THEN
336 
337           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_RPT_N',NULL,NULL,FALSE);
338           p_unit_ver_rec.status :='E';
339        END IF;
340 
341        IF p_unit_ver_rec.same_teaching_period = 'Y' THEN
342           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_RPT_N_SAME_TCH_PRD',NULL,NULL,FALSE);
343           p_unit_ver_rec.status :='E';
344        END IF;
345 
346        IF p_unit_ver_rec.max_repeats_for_funding IS NULL AND p_unit_ver_rec.max_repeats_for_credit IS NOT NULL THEN
347           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_CREDIT_FUNDING',NULL,NULL,FALSE);
348           p_unit_ver_rec.status :='E';
349        END IF;
350 
351        IF p_unit_ver_rec.max_repeats_for_funding > p_unit_ver_rec.max_repeats_for_credit THEN
352           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_MAX_FUN_LE_MA',NULL,NULL,FALSE);
353           p_unit_ver_rec.status :='E';
354        END IF;
355     ELSE
356       IF p_unit_ver_rec.max_repeats_for_funding IS NOT NULL THEN
357          igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_RPT_Y',NULL,NULL,FALSE);
358          p_unit_ver_rec.status :='E';
359       END IF;
360 
361       IF p_unit_ver_rec.max_repeats_for_credit = 0 AND p_unit_ver_rec.max_repeat_credit_points IS NOT NULL  THEN
362          igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_MAX_REP_CRD_PTS',NULL,NULL,FALSE);
363          p_unit_ver_rec.status :='E';
364       END IF;
365 
366       IF  p_unit_ver_rec.same_teaching_period = 'Y' THEN
367          IF p_unit_ver_rec.same_teach_period_repeats > p_unit_ver_rec.max_repeats_for_credit  THEN
368            igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_TPA_LE_MA',NULL,NULL,FALSE);
369            p_unit_ver_rec.status :='E';
370          END IF;
371 
372         IF p_unit_ver_rec.max_repeats_for_credit IS NOT NULL AND p_unit_ver_rec.same_teach_period_repeats IS NULL  THEN
373            igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_MAX_ALWD_SAME_TCH',NULL,NULL,FALSE);
374            p_unit_ver_rec.status :='E';
375         END IF;
376 
377         IF p_unit_ver_rec.same_teach_period_repeats = 0 AND p_unit_ver_rec.same_teach_period_repeats_cp IS NOT NULL THEN
378            igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_TCH_PRD_RPT_CP',NULL,NULL,FALSE);
379            p_unit_ver_rec.status :='E';
380         END IF;
381 
382         IF  p_unit_ver_rec.same_teach_period_repeats_cp > p_unit_ver_rec.max_repeat_credit_points THEN
383            igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_MAX_TCH_PRD_RPT_CP',NULL,NULL,FALSE);
384            p_unit_ver_rec.status :='E';
385         END IF;
386 
387         IF p_unit_ver_rec.max_repeat_credit_points IS NOT NULL AND p_unit_ver_rec.same_teach_period_repeats_cp IS NULL THEN
388            igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_MX_CRD_SAME_TCH_CR',NULL,NULL,FALSE);
389            p_unit_ver_rec.status :='E';
390         END IF;
391 
392       ELSE
393 
394         IF p_unit_ver_rec.same_teach_period_repeats IS NOT NULL OR p_unit_ver_rec.same_teach_period_repeats_cp IS NOT NULL THEN
395            igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_TCH_PRD_RPS_N_NULL',NULL,NULL,FALSE);
396            p_unit_ver_rec.status :='E';
397         END IF;
398 
399       END IF;
400 
401     END IF;
402 
403 
404     --Workload Validation cannot be provided only when Override validation set to N
405     --Workload Validation to be provided  when Override validation set to Y
406     IF (p_unit_ver_rec.ovrd_wkld_val_flag = 'N' AND p_unit_ver_rec.workload_val_code IS NOT NULL) OR
407        (p_unit_ver_rec.ovrd_wkld_val_flag = 'Y' AND p_unit_ver_rec.workload_val_code IS NULL)  THEN
408 
409         igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_WKLD_VALIDATION',NULL,NULL,FALSE);
410         p_unit_ver_rec.status :='E';
411     END IF;
412 
413     --Validate the DFF's
414     IF NOT igs_ad_imp_018.validate_desc_flex(p_unit_ver_rec.attribute_category,
415                                              p_unit_ver_rec.attribute1,
416                                              p_unit_ver_rec.attribute2,
417                                              p_unit_ver_rec.attribute3,
418                                              p_unit_ver_rec.attribute4,
419                                              p_unit_ver_rec.attribute5,
420                                              p_unit_ver_rec.attribute6,
421                                              p_unit_ver_rec.attribute7,
422                                              p_unit_ver_rec.attribute8,
423                                              p_unit_ver_rec.attribute9,
424                                              p_unit_ver_rec.attribute10,
425                                              p_unit_ver_rec.attribute11,
426                                              p_unit_ver_rec.attribute12,
427                                              p_unit_ver_rec.attribute13,
428                                              p_unit_ver_rec.attribute14,
429                                              p_unit_ver_rec.attribute15,
430                                              p_unit_ver_rec.attribute16,
431                                              p_unit_ver_rec.attribute17,
432                                              p_unit_ver_rec.attribute18,
433                                              p_unit_ver_rec.attribute19,
434                                              p_unit_ver_rec.attribute20,
435                                              'IGS_PS_UNIT_VER_FLEX') THEN
436 
437       igs_ps_validate_lgcy_pkg.set_msg('IGS_AD_INVALID_DESC_FLEX',NULL,NULL,FALSE);
438       p_unit_ver_rec.status :='E';
439     END IF;
440 
441     --Validate Org unit filter integration
442     --Bug #2972950. As a part of Binding issues, using bind variable in the ref cursor.Original sql bind fix bug is 2941266
443     igs_or_gen_012_pkg.get_where_clause_api1('UNIT_VERSION_LGCY',l_c_where_clause);
444     IF l_c_where_clause IS NOT NULL THEN
445       l_c_cur_stat  :='SELECT '||''''||'X'||''''||' FROM IGS_OR_INST_ORG_BASE_V WHERE party_number = :p_c_org_unit_cd AND '|| l_c_where_clause;
446       OPEN c_org_cur FOR l_c_cur_stat USING p_unit_ver_rec.owner_org_unit_cd,l_func_name ;
447     ELSE
448       l_c_cur_stat  :='SELECT '||''''||'X'||''''||' FROM IGS_OR_INST_ORG_BASE_V WHERE party_number= :p_c_org_unit_cd ';
449       OPEN c_org_cur FOR l_c_cur_stat USING p_unit_ver_rec.owner_org_unit_cd ;
450     END IF;
451     FETCH c_org_cur INTO l_c_rec_found;
452     IF c_org_cur%NOTFOUND THEN
453       igs_ps_validate_lgcy_pkg.set_msg('IGS_EN_INV','OWNER_ORG_UNIT_CD','LEGACY_TOKENS',FALSE);
454       p_unit_ver_rec.status :='E';
455     END IF;
456     CLOSE c_org_cur;
457 
458     validate_enr_lmts (p_unit_ver_rec.enrollment_minimum, p_unit_ver_rec.enrollment_maximum, p_unit_ver_rec.override_enrollment_max, p_unit_ver_rec.advance_maximum, p_unit_ver_rec.status);
459 
460   END unit_version;
461 
462   FUNCTION post_teach_resp ( p_tab_teach_resp IN OUT NOCOPY igs_ps_generic_pub.unit_tr_tbl_type
463                            ) RETURN BOOLEAN  AS
464 
465   /***********************************************************************************************
466     Created By     :  shtatiko
467     Date Created By:  11-NOV-2002
468     Purpose        :  This procedure will do validations after inserting records of Teaching
469                       Responsibility.
470 
471     Known limitations,enhancements,remarks:
472     Change History (in reverse chronological order)
473     Who         When            What
474     smvk      12-Dec-2002      Added a boolean parameter to the function call igs_ps_val_tr.crsp_val_tr_perc.
475                                As a part of the Bug # 2696207
476   ********************************************************************************************** */
477   l_c_message VARCHAR2(30);
478   l_n_count_msg NUMBER(6);
479 
480   BEGIN
481     -- Check if total percentage for a given unit_cd and version_number is 100. If not, change the status of records accordingly.
482     IF NOT igs_ps_val_tr.crsp_val_tr_perc ( p_tab_teach_resp(p_tab_teach_resp.FIRST).unit_cd, p_tab_teach_resp(p_tab_teach_resp.FIRST).version_number, l_c_message ,TRUE) THEN
483       fnd_message.set_name ( 'IGS', l_c_message );
484       fnd_msg_pub.add;
485 
486       l_n_count_msg := fnd_msg_pub.count_msg;
487       FOR I in 1..p_tab_teach_resp.LAST LOOP
488         IF p_tab_teach_resp.EXISTS(I) THEN
489           IF p_tab_teach_resp(I).status = 'S' THEN
490             p_tab_teach_resp(I).status   := 'E';
491             /* Add Reference to the last added message i.e., l_c_message. */
492             p_tab_teach_resp(I).msg_from := l_n_count_msg;
493             p_tab_teach_resp(I).msg_to   := l_n_count_msg;
494           END IF;
495         END IF;
496       END LOOP;
497       RETURN FALSE;
498     END IF;
499 
500     RETURN TRUE;
501 
502   END post_teach_resp;
503 
504   FUNCTION post_unit_discip ( p_tab_unit_dscp IN OUT NOCOPY igs_ps_generic_pub.unit_dscp_tbl_type
505                             ) RETURN BOOLEAN AS
506 
507   /***********************************************************************************************
508     Created By     :  shtatiko
509     Date Created By:  15-NOV-2002
510     Purpose        :  This procedure will do validations after inserting records of Unit Discipline.
511 
512     Known limitations,enhancements,remarks:
513     Change History (in reverse chronological order)
514     Who         When            What
515     smvk      12-Dec-2002      Added a boolean parameter to the function call igs_ps_val_ud.crsp_val_ud_perc.
516                                As a part of the Bug # 2696207
517   ********************************************************************************************** */
518   l_c_message VARCHAR2(30);
519   l_n_count_msg NUMBER(6);
520 
521   BEGIN
522     -- Check if total percentage for a given unit_cd and version_number is 100. If not, change the status of records accordingly.
523     IF NOT igs_ps_val_ud.crsp_val_ud_perc ( p_tab_unit_dscp(p_tab_unit_dscp.FIRST).unit_cd, p_tab_unit_dscp(p_tab_unit_dscp.FIRST).version_number, l_c_message ,TRUE) THEN
524       fnd_message.set_name ( 'IGS', l_c_message );
525       fnd_msg_pub.add;
526 
527       l_n_count_msg := fnd_msg_pub.count_msg;
528       FOR I in 1..p_tab_unit_dscp.LAST LOOP
529         IF p_tab_unit_dscp.EXISTS(I) THEN
530           IF p_tab_unit_dscp(I).status = 'S' THEN
531             p_tab_unit_dscp(I).status   := 'E';
532             /* Add Reference to the last added message i.e., l_c_message. */
533             p_tab_unit_dscp(I).msg_from := l_n_count_msg;
534             p_tab_unit_dscp(I).msg_to   := l_n_count_msg;
535           END IF;
536         END IF;
537       END LOOP;
538       RETURN FALSE;
539     END IF;
540 
541     RETURN TRUE;
542 
543   END post_unit_discip;
544 
545 PROCEDURE validate_unit_grd_sch ( p_unit_gs_rec IN OUT NOCOPY igs_ps_generic_pub.unit_gs_rec_type )
546   AS
547   /***********************************************************************************************
548     Created By     :  shtatiko
549     Date Created By:  15-NOV-2002
550     Purpose        :  This procedure will do validations before inserting records of Unit Grading Schema.
551                       This is called from sub process of legacy import data, which inserts Unit GS records.
552 
553     Known limitations,enhancements,remarks:
554     Change History (in reverse chronological order)
555     Who         When            What
556   ********************************************************************************************** */
557   BEGIN
558   -- Check if grading schema type is 'UNIT' for a given grading schema.
559     IF NOT validate_gs_type ( p_unit_gs_rec.grading_schema_code, p_unit_gs_rec.grd_schm_version_number ) THEN
560       fnd_message.set_name ( 'IGS', 'IGS_PS_LGCY_INCORRECT_GS_TYPE' );
561       fnd_msg_pub.add;
562       p_unit_gs_rec.status := 'E';
563       RETURN;
564     END IF;
565   END validate_unit_grd_sch;
566 
567   FUNCTION post_unit_grd_sch ( p_tab_grd_sch IN OUT NOCOPY igs_ps_generic_pub.unit_gs_tbl_type ) RETURN BOOLEAN
568   AS
569   /***********************************************************************************************
570     Created By     :  shtatiko
571     Date Created By:  18-NOV-2002
572     Purpose        :  This function will do validations after inserting records of Unit Grading Schema.
573                       This will returns TRUE if all the validations pass and returns FALSE, if fails.
574 
575     Known limitations,enhancements,remarks:
576     Change History (in reverse chronological order)
577     Who         When            What
578   ********************************************************************************************** */
579   CURSOR c_unit_gs_count (
580             cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
581             cp_ver_num igs_ps_unit_ver_all.version_number%TYPE
582   ) IS
583   SELECT COUNT(*) cnt
584   FROM igs_ps_unit_grd_schm
585   WHERE
586     unit_code = cp_unit_cd AND
587     unit_version_number = cp_ver_num AND
588     default_flag = 'Y';
589   rec_unit_gs_count c_unit_gs_count%ROWTYPE;
590   l_n_count_msg NUMBER(6);
591 
592   BEGIN
593 
594   -- Check if atleast and atmost one default flag is set to 'Y' for a given unit code and version number.
595     OPEN c_unit_gs_count (
596             cp_unit_cd => p_tab_grd_sch(p_tab_grd_sch.FIRST).unit_cd,
597             cp_ver_num => p_tab_grd_sch(p_tab_grd_sch.FIRST).version_number
598     );
599     FETCH c_unit_gs_count INTO rec_unit_gs_count;
600     IF rec_unit_gs_count.cnt = 1 THEN
601       CLOSE c_unit_gs_count;
602       RETURN TRUE;
603     ELSE
604       fnd_message.set_name ( 'IGS', 'IGS_PS_ONE_UGSC_DFLT_MARK' );
605       fnd_msg_pub.add;
606 
607       l_n_count_msg := fnd_msg_pub.count_msg;
608       FOR I in 1..p_tab_grd_sch.LAST LOOP
609         IF p_tab_grd_sch.EXISTS(I) THEN
610           IF p_tab_grd_sch(I).status = 'S' THEN
611             p_tab_grd_sch(I).status := 'E';
612             p_tab_grd_sch(I).msg_from := l_n_count_msg;
613             p_tab_grd_sch(I).msg_to := l_n_count_msg;
614           END IF;
615         END IF;
616       END LOOP;
617       CLOSE c_unit_gs_count;
618       RETURN FALSE;
619     END IF;
620 
621   END post_unit_grd_sch;
622 
623 
624   -- Validate Unit Offer Option Records before inserting them
625   PROCEDURE validate_uoo ( p_usec_rec IN OUT NOCOPY igs_ps_generic_pub.usec_rec_type,
626                            p_c_cal_type IN igs_ca_type.cal_type%TYPE,
627                            p_n_seq_num IN igs_ca_inst_all.sequence_number%TYPE,
628                            p_n_sup_uoo_id IN OUT NOCOPY igs_ps_unit_ofr_opt_all.sup_uoo_id%TYPE,
629 			   p_insert_update VARCHAR2,
630 			   p_conc_flag OUT NOCOPY BOOLEAN)
631   AS
632   /***********************************************************************************************
633     Created By     :  shtatiko
634     Date Created By:  22-NOV-2002
635     Purpose        :  This does legacy validations before inserting Unit Offering Option Records.
636 
637     Known limitations,enhancements,remarks:
638     Change History (in reverse chronological order)
639     Who         When            What
640     sommukhe  12-JAN-2006       Bug#4926548, in the cursor user_check changed the table fnd_user_resp_groups to fnd_user_resp_groups_direct
641                                 modified the cursors c_anon_grd_method and c_cal_rel also introduced new cursors c_min_load_start_dt and cur_teach_load.
642     sarakshi  13-Apr-2004       Bug#3555871,added validation of teach calender association with load calender.Also removed the call of get_call_number .
643     sarakshi  21-oct-2003       Bug#3052452,used igs_ps_gen_003.enrollment_for_uoo_check in place of using a local cursor
644     smvk      24-Sep-2003       Bug # 3121311. Removed the validation to check unit contact person is of person type staff member.
645                                 Removed the variable l_n_unit_contact_id and calls to get_party_id and validate_staff_person.
646     sarakshi  11-Sep-2003       Enh#3052452,Added validation related to passed sup_uoo_id
647     sarakshi  22-Aug-2003       Bug#304509, added validation, Not Multiple Unit Section Flag should not be N if it N at Unit level
648     sarakshi  04-Mar-2003       Bug#2768783, addded call number validation for profile option NONE also
649     smvk      26-Dec-2002       Bug # 2721495. Using the newly created function and procedure get_party_id, validate_staff_person.
650   ********************************************************************************************** */
651     l_n_call_number igs_ps_unit_ofr_opt_all.call_number%TYPE;
652     -- Removed l_n_unit_contact_id as a part of bug # 3121311
653     l_c_message VARCHAR2(30);
654 
655     CURSOR c_location_type ( cp_location_cd igs_ad_location_all.location_cd%TYPE ) IS
656     SELECT 'x'
657     FROM   igs_ad_location_all a,
658 	   igs_ad_location_type_all b
659     WHERE  a.location_type = b.location_type
660     AND    b.s_location_type = 'CAMPUS'
661     AND    a.location_cd = cp_location_cd;
662     rec_location_type c_location_type%ROWTYPE;
663 
664     CURSOR c_anon_unit_grading ( cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
665 				 cp_version_number igs_ps_unit_ver_all.version_number%TYPE ) IS
666     SELECT 1
667     FROM   igs_ps_unit_ver
668     WHERE  unit_cd = cp_unit_cd
669     AND    version_number = cp_version_number
670     AND    anon_unit_grading_ind = 'Y' ;
671     rec_anon_unit_grading c_anon_unit_grading%ROWTYPE;
672 
673     CURSOR c_anon_grd_method ( cp_cal_type igs_ps_unit_ofr_opt_all.cal_type%TYPE,
674 			       cp_ci_seq_num igs_ps_unit_ofr_opt_all.ci_sequence_number%TYPE,
675 			       cp_load_start_dt igs_ca_inst_all.start_dt%TYPE) IS
676     SELECT 1
677     FROM   igs_ca_teach_to_load_v a,
678 	   igs_as_anon_method b
679     WHERE  a.teach_cal_type = cp_cal_type
680     AND    a.teach_ci_sequence_number = cp_ci_seq_num
681     AND    a.load_start_dt = cp_load_start_dt
682     AND    a.load_cal_type = b.load_cal_type;
683     rec_anon_grd_method c_anon_grd_method%ROWTYPE;
684 
685     CURSOR c_min_load_start_dt ( cp_cal_type igs_ps_unit_ofr_opt_all.cal_type%TYPE,
686 			       cp_ci_seq_num igs_ps_unit_ofr_opt_all.ci_sequence_number%TYPE ) IS
687     SELECT MIN(c.load_start_dt)
688     FROM   igs_ca_teach_to_load_v c
689     WHERE  c.teach_cal_type = cp_cal_type
690     AND    c.teach_ci_sequence_number = cp_ci_seq_num ;
691 
692     l_load_start_dt igs_ca_inst_all.start_dt%TYPE;
693 
694     CURSOR c_anon_assess_grading ( cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
695 				   cp_version_number igs_ps_unit_ver_all.version_number%TYPE ) IS
696     SELECT 1
697     FROM   igs_ps_unit_ver
698     WHERE  unit_cd = cp_unit_cd
699     AND    version_number = cp_version_number
700     AND    anon_assess_grading_ind = 'Y';
701     rec_anon_assess_grading c_anon_assess_grading%ROWTYPE;
702 
703     --Enh bug#2972950
704     --For PSP Enhancements the following cursor was added
705     CURSOR c_cal_status  ( cp_c_cal_type igs_ca_inst_all.cal_type%TYPE,
706 			   cp_n_ci_seq_num igs_ca_inst_all.sequence_number%TYPE ) IS
707     SELECT B.s_cal_status
708     FROM igs_ca_inst_all A,igs_ca_stat B
709     WHERE A.cal_type = cp_c_cal_type
710     AND   A.sequence_number = cp_n_ci_seq_num
711     AND   A.cal_status = B.cal_status;
712 
713     rec_cal_status c_cal_status%ROWTYPE;
714 
715     CURSOR c_muiltiple_section_flag ( cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
716 				      cp_version_number igs_ps_unit_ver_all.version_number%TYPE )IS
717     SELECT same_teaching_period
718     FROM   igs_ps_unit_ver_all
719     WHERE  unit_cd = cp_unit_cd
720     AND    version_number = cp_version_number;
721 
722     l_same_teaching_period  igs_ps_unit_ver_all.same_teaching_period%TYPE;
723 
724     CURSOR c_crosslist ( cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
725     SELECT 'X'
726     FROM  igs_ps_usec_x_grpmem
727     WHERE uoo_id = cp_uoo_id;
728 
729 
730     CURSOR c_usec_status ( cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
731 			   cp_usec_status igs_ps_unit_ofr_opt_all.unit_section_status%TYPE) IS
732     SELECT 'X'
733     FROM  igs_ps_unit_ofr_opt_all
734     WHERE uoo_id = cp_uoo_id
735     AND   unit_section_status = cp_usec_status;
736 
737     CURSOR c_relation (cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
738 		       cp_relation_type igs_ps_unit_ofr_opt_all.relation_type%TYPE) IS
739     SELECT 'X'
740     FROM  igs_ps_unit_ofr_opt_all
741     WHERE uoo_id = cp_uoo_id
742     AND   relation_type = cp_relation_type;
743 
744     CURSOR c_cal_seq_no(cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE)  IS
745     SELECT uoo.cal_type,uoo.ci_sequence_number
746     FROM   igs_ps_unit_ofr_opt_all uoo
747     WHERE  uoo.uoo_id = cp_uoo_id;
748 
749 
750     TYPE teach_cal_rec IS RECORD(
751 				 cal_type igs_ca_inst_all.cal_type%TYPE,
752 				 sequence_number igs_ca_inst_all.sequence_number%TYPE
753 				 );
754     TYPE teachCalendar IS TABLE OF teach_cal_rec INDEX BY BINARY_INTEGER;
755     teachCalendar_tbl teachCalendar;
756     l_n_counter NUMBER(10);
757     l_c_proceed BOOLEAN ;
758 
759 
760     CURSOR cur_teach_load IS
761     SELECT load_cal_type,load_ci_sequence_number
762     FROM   igs_ca_teach_to_load_v
763     WHERE  teach_cal_type=p_c_cal_type
764     AND    teach_ci_sequence_number=p_n_seq_num;
765 
766     CURSOR c_cal_rel(cp_cal_teach_type           igs_ca_load_to_teach_v.teach_cal_type%TYPE,
767 		     cp_teach_ci_sequence_number igs_ca_load_to_teach_v.teach_ci_sequence_number%TYPE)  IS
768     SELECT load_cal_type,load_ci_sequence_number
769     FROM   igs_ca_load_to_teach_v
770     WHERE  teach_cal_type = cp_cal_teach_type
771     AND    teach_ci_sequence_number = cp_teach_ci_sequence_number;
772 
773     CURSOR c_teach_to_load ( cp_cal_type igs_ca_type.cal_type%TYPE,
774 			     cp_seq_num igs_ca_inst_all.sequence_number%TYPE ) IS
775     SELECT load_cal_type lcal_type, load_ci_sequence_number lseq_num
776     FROM igs_ca_teach_to_load_v
777     WHERE
778       teach_cal_type = cp_cal_type AND
779       teach_ci_sequence_number = cp_seq_num;
780     rec_teach_to_load c_teach_to_load%ROWTYPE;
781 
782     CURSOR c_usec IS
783     SELECT a.*, a.rowid
784     FROM  igs_ps_unit_ofr_opt_all a
785     WHERE unit_cd = p_usec_rec.unit_cd
786     AND version_number =  p_usec_rec.version_number
787     AND ci_sequence_number =p_n_seq_num
788     AND unit_class = p_usec_rec.unit_class
789     AND location_cd = p_usec_rec.location_cd
790     AND cal_type = p_c_cal_type ;
791 
792     c_usec_rec c_usec%ROWTYPE;
793 
794     CURSOR c_uso(cp_n_uoo_id igs_ps_usec_occurs_all.uoo_id%TYPE) IS
795     SELECT uso.rowid, uso.*
796     FROM   igs_ps_usec_occurs_all uso
797     WHERE  uso.uoo_id = cp_n_uoo_id
798     AND    building_code IS NOT NULL;
799 
800     CURSOR cur_unit_audit(cp_uoo_id igs_en_su_attempt.uoo_id%TYPE) IS
801     SELECT 'X'
802     FROM IGS_EN_SU_ATTEMPT
803     WHERE uoo_id = cp_uoo_id
804     AND no_assessment_ind='Y';
805     rec_unit_audit cur_unit_audit%ROWTYPE;
806 
807 
808     CURSOR user_check(cp_user_id IN fnd_user_resp_groups.user_id%TYPE) IS
809     SELECT 'X'
810     FROM fnd_user_resp_groups_direct a,fnd_responsibility_vl b, fnd_user c
811     WHERE a.user_id= cp_user_id
812     AND   a.user_id = c.user_id
813     AND   TRUNC(SYSDATE) BETWEEN TRUNC(c.start_date) AND TRUNC(NVL(c.end_date,SYSDATE))
814     AND   a.responsibility_id= b.responsibility_id
815     AND   b.responsibility_key    ='IGS_SUPER_USER'
816     AND   TRUNC(SYSDATE) BETWEEN TRUNC(a.start_date) AND TRUNC(NVL(a.end_date,SYSDATE));
817 
818 
819     l_v_flag  igs_ps_unit_ver.same_teaching_period%TYPE;
820     l_c_perference_name igs_pe_person.preferred_name%TYPE;
821     v_message_name VARCHAR2(30);
822     v_request_id NUMBER;
823 
824 
825     l_c_cal_seq_no  c_cal_seq_no%ROWTYPE;
826     l_n_sup_uoo_id  igs_ps_unit_ofr_opt_all.sup_uoo_id%TYPE;
827     l_c_valid_fail  BOOLEAN := FALSE;
828     l_c_var         VARCHAR2(1);
829 
830       FUNCTION testCalendar(cp_cal_type igs_ca_inst_all.cal_type%TYPE,
831                           cp_sequence_number igs_ca_inst_all.sequence_number%TYPE)  RETURN BOOLEAN AS
832     BEGIN
833       IF teachCalendar_tbl.EXISTS(1) THEN
834         FOR i IN 1..teachCalendar_tbl.last LOOP
835 	     IF cp_cal_type=teachCalendar_tbl(i).cal_type AND
836 		cp_sequence_number=teachCalendar_tbl(i).sequence_number THEN
837 		RETURN TRUE;
838 	     END IF;
839 	END LOOP;
840       END IF;
841       RETURN FALSE;
842     END testCalendar;
843 
844   BEGIN
845 
846     -- validation to check whehter the unit contact person should be of type staff is removed as a part of Bug # 3121311
847 
848     l_n_counter :=1;
849     FOR cur_teach_load_rec IN cur_teach_load LOOP
850       teachCalendar_tbl(l_n_counter).cal_type :=cur_teach_load_rec.load_cal_type;
851       teachCalendar_tbl(l_n_counter).sequence_number :=cur_teach_load_rec.load_ci_sequence_number;
852       l_n_counter:=l_n_counter+1;
853     END LOOP;
854 
855     --Fetch the minimum load start date
856     OPEN c_min_load_start_dt ( p_c_cal_type, p_n_seq_num );
857     FETCH c_min_load_start_dt INTO l_load_start_dt;
858     CLOSE c_min_load_start_dt;
859 
860     -- Check if the passed location type is of type 'CAMPUS'
861     OPEN c_location_type ( p_usec_rec.location_cd );
862     FETCH c_location_type INTO rec_location_type;
863     IF ( c_location_type%NOTFOUND ) THEN
864       fnd_message.set_name ( 'IGS', 'IGS_PS_UVN_NOTE_FK_C' );
865       fnd_msg_pub.add;
866       p_usec_rec.status := 'E';
867     END IF;
868     CLOSE c_location_type;
869 
870     -- at least one unit enrollment method type between Voice Response and Self Service should be selected
871     IF ( p_usec_rec.IVRS_AVAILABLE_IND = 'N' AND p_usec_rec.ss_enrol_ind ='N' ) THEN
872       fnd_message.set_name ( 'IGS', 'IGS_PS_ONE_UNIT_ENR_MTHD' );
873       fnd_msg_pub.add;
874       p_usec_rec.status := 'E';
875     END IF;
876 
877     -- Check whether the teach calender is associated with a load calender.
878     OPEN c_teach_to_load ( p_c_cal_type, p_n_seq_num );
879     FETCH c_teach_to_load INTO rec_teach_to_load;
880     IF c_teach_to_load%NOTFOUND THEN
881         fnd_message.set_name ( 'IGS', 'IGS_PS_TECH_NO_LOAD_CAL_EXST' );
882         fnd_msg_pub.add;
883         p_usec_rec.status := 'E';
884     END IF;
885     CLOSE c_teach_to_load;
886 
887     IF p_insert_update = 'I' THEN---this validation needs to be done only while insert operation
888       -- Validate Call Number
889       IF (fnd_profile.value('IGS_PS_CALL_NUMBER') = 'AUTO' AND p_usec_rec.call_number IS NOT NULL) THEN
890 
891 	-- Profile is AUTO and values is passed to call_number so raise error
892 	igs_ps_validate_lgcy_pkg.set_msg('IGS_EN_INV', 'CALL_NUMBER', 'LEGACY_TOKENS', FALSE);
893 	p_usec_rec.status := 'E';
894       ELSIF ( fnd_profile.value('IGS_PS_CALL_NUMBER') = 'USER_DEFINED' ) THEN
895 
896 	IF p_usec_rec.call_number IS NOT NULL THEN
897 	  IF NOT igs_ps_unit_ofr_opt_pkg.check_call_number ( p_teach_cal_type     => p_c_cal_type,
898 							     p_teach_sequence_num => p_n_seq_num,
899 							     p_call_number        => p_usec_rec.call_number,
900 							     p_rowid              => null ) THEN
901 	    fnd_message.set_name ( 'IGS', 'IGS_PS_DUPLICATE_CALL_NUMBER' );
902 	    fnd_msg_pub.add;
903 	    p_usec_rec.status := 'E';
904 	  END IF;
905 	END IF;
906       END IF;
907     END IF;
908 
909     IF ( fnd_profile.value('IGS_PS_CALL_NUMBER') = 'NONE' ) THEN
910 
911 	IF p_usec_rec.call_number IS NOT NULL THEN
912 	  -- Profile is NONE and values is passed to call_number so raise error
913 	  igs_ps_validate_lgcy_pkg.set_msg('IGS_EN_INV', 'CALL_NUMBER', 'LEGACY_TOKENS', FALSE);
914 	  p_usec_rec.status := 'E';
915 	END IF;
916 
917     END IF;
918 
919 
920     -- If anonymous grading is set to Yes check whether it is enabled at unit level
921     -- and check if anonymous grading method is done
922     IF ( p_usec_rec.anon_unit_grading_ind = 'Y' ) THEN
923       OPEN c_anon_unit_grading ( p_usec_rec.unit_cd, p_usec_rec.version_number );
924       FETCH c_anon_unit_grading INTO rec_anon_unit_grading;
925       IF ( c_anon_unit_grading%NOTFOUND ) THEN
926         fnd_message.set_name ( 'IGS', 'IGS_AS_ANON_UNT_GRD_DISABLE' );
927         fnd_msg_pub.add;
928         p_usec_rec.status := 'E';
929       END IF;
930       CLOSE c_anon_unit_grading;
931 
932       -- check whether configuration of anonymous grading method is done or not.
933       OPEN c_anon_grd_method ( p_c_cal_type, p_n_seq_num,l_load_start_dt );
934       FETCH c_anon_grd_method INTO rec_anon_grd_method;
935       IF c_anon_grd_method%NOTFOUND THEN
936         fnd_message.set_name ( 'IGS', 'IGS_AS_CON_UN_GRD_DISABLE' );
937         fnd_msg_pub.add;
938         p_usec_rec.status := 'E';
939       END IF;
940       CLOSE c_anon_grd_method;
941     END IF;
942 
943     -- If anonymous assessment grading is set to Yes then check whether it is enabled at unit level
944     IF ( p_usec_rec.anon_assess_grading_ind = 'Y' ) THEN
945       OPEN c_anon_assess_grading ( p_usec_rec.unit_cd, p_usec_rec.version_number );
946       FETCH c_anon_assess_grading INTO rec_anon_assess_grading;
947       IF ( c_anon_assess_grading%NOTFOUND ) THEN
948         fnd_message.set_name ( 'IGS', 'IGS_AS_ANON_ASES_GRD_DISABLE' );
949         fnd_msg_pub.add;
950         p_usec_rec.status := 'E';
951       END IF;
952       CLOSE c_anon_assess_grading;
953 
954       -- check whether configuration of anonymous grading method is done or not.
955       OPEN c_anon_grd_method ( p_c_cal_type, p_n_seq_num,l_load_start_dt );
956       FETCH c_anon_grd_method INTO rec_anon_grd_method;
957       IF c_anon_grd_method%NOTFOUND THEN
958         fnd_message.set_name ( 'IGS', 'IGS_AS_CON_ASS_GRD_DISABLE' );
959         fnd_msg_pub.add;
960         p_usec_rec.status := 'E';
961       END IF;
962       CLOSE c_anon_grd_method;
963 
964     END IF;
965 
966     --Enh Bug#2972950
967     --The following validation added for PSP Enhancements TD
968 
969     OPEN c_cal_status ( p_c_cal_type, p_n_seq_num );
970     FETCH c_cal_status INTO rec_cal_status;
971     CLOSE c_cal_status;
972 
973     --Unit section status should be 'Not Offered' if the corresponding teaching calendar is inactive
974     IF rec_cal_status.s_cal_status = 'INACTIVE' THEN
975        IF p_usec_rec.unit_section_status <> 'NOT_OFFERED' THEN
976           fnd_message.set_name ( 'IGS', 'IGS_PS_NOT_OFR_INACT_CAL' );
977           fnd_msg_pub.add;
978           p_usec_rec.status := 'E';
979        END IF;
980     --Unit section status cannot be 'Not Offered' if the corresponding teaching calendar is not inactive
981     ELSE
982        IF p_usec_rec.unit_section_status = 'NOT_OFFERED' THEN
983           fnd_message.set_name ( 'IGS', 'IGS_PS_INACT_CAL_NOT_OFR' );
984           fnd_msg_pub.add;
985           p_usec_rec.status := 'E';
986        END IF;
987     END IF;
988 
989     --Not Multiple Unit Section Flag should not be N if it N at Unit level
990     IF p_usec_rec.not_multiple_section_flag = 'N' THEN
991        OPEN c_muiltiple_section_flag( p_usec_rec.unit_cd, p_usec_rec.version_number );
992        FETCH c_muiltiple_section_flag INTO l_same_teaching_period;
993        CLOSE c_muiltiple_section_flag;
994        IF l_same_teaching_period = 'N' THEN
995           fnd_message.set_name ( 'IGS', 'IGS_PS_LGCY_US_MULTIPLE_FLAG' );
996           fnd_msg_pub.add;
997           p_usec_rec.status := 'E';
998        END IF;
999     END IF;
1000 
1001     --The validation related to the unit section start and end date is added for the bug#4210597
1002     --Non standard unit section must have unit section start date
1003     IF p_usec_rec.non_std_usec_ind = 'Y' AND p_usec_rec.unit_section_start_date IS NULL THEN
1004        fnd_message.set_name ( 'IGS', 'IGS_EN_OFFSET_DT_NULL' );
1005        fnd_msg_pub.add;
1006        p_usec_rec.status := 'E';
1007     END IF;
1008 
1009 
1010     --Following validation needs to be performed if the sup_uoo_id is provided
1011     IF p_n_sup_uoo_id IS NOT NULL THEN
1012 
1013       l_n_sup_uoo_id:=p_n_sup_uoo_id;
1014 
1015       --Check if the superior unit section belong to a crosslisted group
1016       OPEN c_crosslist(l_n_sup_uoo_id);
1017       FETCH c_crosslist INTO l_c_var;
1018       IF c_crosslist%FOUND THEN
1019         l_c_valid_fail :=TRUE;
1020       END IF;
1021       CLOSE c_crosslist;
1022 
1023       --Check if the superior unit section status is NOT_OFFERED
1024       OPEN c_usec_status(l_n_sup_uoo_id,'NOT_OFFERED');
1025       FETCH c_usec_status INTO l_c_var;
1026       IF c_usec_status%FOUND THEN
1027         l_c_valid_fail :=TRUE;
1028       END IF;
1029       CLOSE c_usec_status;
1030 
1031       --Check if the current unit section status is NOT_OFFERED
1032       IF p_usec_rec.unit_section_status = 'NOT_OFFERED'  THEN
1033         l_c_valid_fail :=TRUE;
1034       END IF;
1035 
1036       IF l_c_valid_fail THEN
1037         p_n_sup_uoo_id:= NULL;
1038         fnd_message.set_name ( 'IGS', 'IGS_PS_US_NOT_OFF_CRS_LISTED' );
1039         fnd_msg_pub.add;
1040         p_usec_rec.status := 'E';
1041       END IF;
1042 
1043 
1044       --Check if the superior unit section is already in a relationship
1045       OPEN c_relation(l_n_sup_uoo_id,'SUBORDINATE');
1046       FETCH c_relation INTO l_c_var;
1047       IF c_relation%FOUND THEN
1048         p_n_sup_uoo_id:= NULL;
1049         fnd_message.set_name ( 'IGS', 'IGS_PS_US_UPLOADED_NORMAL_REL' );
1050         fnd_msg_pub.add;
1051         p_usec_rec.status := 'E';
1052       END IF;
1053       CLOSE c_relation;
1054 
1055       --The unit section must belong to the same load calander as the superior unit section section
1056 
1057       --Fetch the calendar instance for the input uoo_id
1058       OPEN  c_cal_seq_no(l_n_sup_uoo_id);
1059       FETCH c_cal_seq_no INTO l_c_cal_seq_no;
1060       CLOSE c_cal_seq_no ;
1061 
1062       IF teachCalendar_tbl.EXISTS(1) THEN
1063 	l_c_proceed:= TRUE;
1064 	FOR c_cal_rel_rec IN c_cal_rel(l_c_cal_seq_no.cal_type,l_c_cal_seq_no.ci_sequence_number) LOOP
1065 	  IF testCalendar(c_cal_rel_rec.load_cal_type ,c_cal_rel_rec.load_ci_sequence_number ) THEN
1066 	    l_c_proceed:=FALSE;
1067 	    EXIT;
1068 	  END IF;
1069 	END LOOP;
1070 	IF l_c_proceed THEN
1071 	  p_n_sup_uoo_id:= NULL;
1072 	  fnd_message.set_name ( 'IGS', 'IGS_PS_SUP_TERM_STUD_ENROLL' );
1073 	  fnd_msg_pub.add;
1074 	  p_usec_rec.status := 'E';
1075 	END IF;
1076 	teachCalendar_tbl.DELETE;
1077       ELSE
1078          p_n_sup_uoo_id:= NULL;
1079 	 fnd_message.set_name ( 'IGS', 'IGS_PS_SUP_TERM_STUD_ENROLL' );
1080 	 fnd_msg_pub.add;
1081 	 p_usec_rec.status := 'E';
1082       END IF;
1083 
1084       --Check if superior unit section exists in any enrollment activity
1085       IF igs_ps_gen_003.enrollment_for_uoo_check(l_n_sup_uoo_id) THEN
1086         p_n_sup_uoo_id:= NULL;
1087         fnd_message.set_name ( 'IGS', 'IGS_PS_SUP_TERM_STUD_ENROLL' );
1088         fnd_msg_pub.add;
1089         p_usec_rec.status := 'E';
1090       END IF;
1091 
1092     END IF;
1093 
1094     --starts of validations for update
1095     IF p_insert_update = 'U' THEN
1096       OPEN c_usec;
1097       FETCH c_usec INTO c_usec_rec;
1098       CLOSE c_usec;
1099 
1100 
1101       IF ( fnd_profile.value('IGS_PS_CALL_NUMBER') = 'USER_DEFINED' ) THEN
1102 	IF p_usec_rec.call_number IS NOT NULL THEN
1103 	  IF NOT igs_ps_unit_ofr_opt_pkg.check_call_number ( p_teach_cal_type     => p_c_cal_type,
1104 							     p_teach_sequence_num => p_n_seq_num,
1105 							     p_call_number        => p_usec_rec.call_number,
1106 							     p_rowid              => c_usec_rec.rowid ) THEN
1107 	    fnd_message.set_name ( 'IGS', 'IGS_PS_DUPLICATE_CALL_NUMBER' );
1108 	    fnd_msg_pub.add;
1109 	    p_usec_rec.status := 'E';
1110 	  END IF;
1111 	END IF;
1112       END IF;
1113 
1114 
1115       --Unit Section status cant be passed as Not Offered.
1116       IF p_usec_rec.unit_section_status = 'NOT_OFFERED' THEN
1117 	 fnd_message.set_name('IGS','IGS_PS_CNT_UPD_NOT_OFFERED');
1118 	 fnd_msg_pub.add;
1119 	 p_usec_rec.status := 'E';
1120       END IF;
1121 
1122 
1123       OPEN c_muiltiple_section_flag(p_usec_rec.unit_cd,p_usec_rec.version_number);
1124       FETCH c_muiltiple_section_flag INTO l_v_flag;
1125       CLOSE c_muiltiple_section_flag;
1126 
1127       --Enable the checkbox 'Exclude from Multiple Unit Secion', if 'Multiple Unit Section Allowed' checkbox
1128       --in Unit Repeat/Reenroll Condition form is checked.
1129       IF NVL(l_v_flag,'N') = 'N' THEN
1130 	--update of the field NOT_MULTIPLE_SECTION_FLAG is not allowed
1131 	IF p_usec_rec.not_multiple_section_flag <> c_usec_rec.not_multiple_section_flag THEN
1132 	   fnd_message.set_name('IGS','IGS_PS_LGCY_US_MULTIPLE_FLAG');
1133 	   fnd_msg_pub.add;
1134 	   p_usec_rec.status := 'E';
1135 	END IF;
1136       END IF;
1137 
1138       --Not Offered unit section should not be allowed to be updated
1139       IF NOT igs_ps_validate_lgcy_pkg.check_not_offered_usec_status(c_usec_rec.uoo_id) THEN
1140 	fnd_message.set_name ( 'IGS', 'IGS_PS_IMP_NOT_ALD_NOT_OFFERED' );
1141 	fnd_msg_pub.add;
1142 	p_usec_rec.status := 'E';
1143       END IF;
1144 
1145       --If that unit has been used in auditing then do not allow unchecking of auditable_ind
1146       IF p_usec_rec.auditable_ind='N' THEN
1147 	OPEN cur_unit_audit(c_usec_rec.uoo_id);
1148 	FETCH cur_unit_audit INTO rec_unit_audit;
1149 	IF(cur_unit_audit%FOUND) THEN
1150 	  fnd_message.set_name('IGS', 'IGS_PS_AUD_NO_CHK_USEC');
1151 	  fnd_msg_pub.add;
1152 	  p_usec_rec.status := 'E';
1153 	END IF;
1154 	CLOSE cur_unit_audit;
1155 
1156 	IF p_usec_rec.audit_permission_ind ='Y'  THEN
1157 	  fnd_message.set_name('IGS', 'IGS_PS_AUDIT_PERMISSION_EXIST');
1158 	  fnd_msg_pub.add;
1159 	  p_usec_rec.status := 'E';
1160 	ELSE
1161 	  --update of the field AUDIT_PERMISSION_IND is not allowed
1162 	  IF p_usec_rec.audit_permission_ind <>c_usec_rec.audit_permission_ind THEN
1163 	    fnd_message.set_name('IGS', 'IGS_PS_AUDIT_PERMISSION_EXIST');
1164 	    fnd_msg_pub.add;
1165 	    p_usec_rec.status := 'E';
1166 	  END IF;
1167 	END IF;
1168 
1169       END IF;
1170 
1171       IF igs_ps_usec_schedule.prgp_get_schd_status( c_usec_rec.uoo_id,NULL,v_message_name ) = TRUE THEN
1172 	  IF v_message_name IS NULL THEN
1173 	    v_message_name := 'IGS_PS_SCST_PROC';
1174 	  END IF;
1175 	  fnd_message.set_name( 'IGS', v_message_name);
1176 	  fnd_msg_pub.add;
1177 	  p_usec_rec.status := 'E';
1178       ELSIF c_usec_rec.location_cd <> p_usec_rec.location_cd THEN
1179 	 IF igs_ps_usec_schedule.prgp_upd_usec_dtls( c_usec_rec.uoo_id,p_usec_rec.location_cd,Null,Null,Null,Null,
1180 						     v_request_id,
1181 						     v_message_name
1182 						   ) = FALSE THEN
1183 
1184 	    fnd_message.set_name( 'IGS', v_message_name);
1185 	    fnd_msg_pub.add;
1186 	    p_usec_rec.status := 'E';
1187 	  END IF;
1188       END IF;
1189 
1190       --Validate unit section status transition
1191       IF  p_usec_rec.unit_section_status <> c_usec_rec.unit_section_status  THEN
1192 	BEGIN
1193           igs_ps_unit_ofr_opt_pkg.check_status_transition( p_n_uoo_id        => c_usec_rec.uoo_id,
1194                                                            p_c_old_usec_sts  => c_usec_rec.unit_section_status,
1195                                                            p_c_new_usec_sts  => p_usec_rec.unit_section_status);
1196         EXCEPTION WHEN OTHERS THEN
1197 	   p_usec_rec.status := 'E';
1198 	END;
1199 
1200       END IF;
1201 
1202 
1203       --clearing Building code and room code when status is cancelled
1204       IF p_usec_rec.unit_section_status <> c_usec_rec.unit_section_status THEN
1205 	IF p_usec_rec.unit_section_status = 'CANCELLED' THEN
1206 	  IF (NVL(fnd_profile.value('IGS_PS_SCH_SOFT_NOT_INSTLD'),'N')) = 'N' THEN
1207 	    IF p_usec_rec.status <> 'E' THEN
1208 	      FOR rec_uso IN c_uso(c_usec_rec.uoo_id)   LOOP
1209 		igs_ps_usec_occurs_pkg.update_row (
1210 		       X_Mode                              => 'R',
1211 		       X_RowId                             => rec_uso.rowid ,
1212 		       X_unit_section_occurrence_id        => rec_uso.unit_section_occurrence_id,
1213 		       X_uoo_id                            => rec_uso.uoo_id,
1214 		       X_monday                            => rec_uso.monday,
1215 		       X_tuesday                           => rec_uso.tuesday,
1216 		       X_wednesday                         => rec_uso.wednesday,
1217 		       X_thursday                          => rec_uso.thursday,
1218 		       X_friday                            => rec_uso.friday,
1219 		       X_saturday                          => rec_uso.saturday,
1220 		       X_sunday                            => rec_uso.sunday,
1221 		       X_start_time                        => rec_uso.start_time,
1222 		       X_end_time                          => rec_uso.end_time,
1223 		       X_building_code                     => NULL,  -- Clearing the building code
1224 		       X_room_code                         => NULL,  -- Clearing the room code
1225 		       X_schedule_status                   => rec_uso.schedule_status,
1226 		       X_status_last_updated               => SYSDATE,
1227 		       X_instructor_id                     => rec_uso.instructor_id,
1228 		       X_attribute_category                => rec_uso.attribute_category,
1229 		       X_attribute1                        => rec_uso.attribute1,
1230 		       X_attribute2                        => rec_uso.attribute2,
1231 		       X_attribute3                        => rec_uso.attribute3,
1232 		       X_attribute4                        => rec_uso.attribute4,
1233 		       X_attribute5                        => rec_uso.attribute5,
1234 		       X_attribute6                        => rec_uso.attribute6,
1235 		       X_attribute7                        => rec_uso.attribute7,
1236 		       X_attribute8                        => rec_uso.attribute8,
1237 		       X_attribute9                        => rec_uso.attribute9,
1238 		       X_attribute10                       => rec_uso.attribute10,
1239 		       X_attribute11                       => rec_uso.attribute11,
1240 		       X_attribute12                       => rec_uso.attribute12,
1241 		       X_attribute13                       => rec_uso.attribute13,
1242 		       X_attribute14                       => rec_uso.attribute14,
1243 		       X_attribute15                       => rec_uso.attribute15,
1244 		       X_attribute16                       => rec_uso.attribute16,
1245 		       X_attribute17                       => rec_uso.attribute17,
1246 		       X_attribute18                       => rec_uso.attribute18,
1247 		       X_attribute19                       => rec_uso.attribute19,
1248 		       X_attribute20                       => rec_uso.attribute20,
1249 		       X_error_text                        => rec_uso.error_text ,
1250 		       X_start_date                        => rec_uso.start_date,
1251 		       X_end_date                          => rec_uso.end_date,
1252 		       X_to_be_announced                   => rec_uso.to_be_announced,
1253 		       X_inst_notify_ind                   => rec_uso.inst_notify_ind,
1254 		       X_notify_status                     => rec_uso.notify_status,
1255 		       X_preferred_region_code             => rec_uso.preferred_region_code,
1256 		       X_no_set_day_ind                    => rec_uso.no_set_day_ind,
1257 		       X_preferred_building_code           => rec_uso.preferred_building_code,
1258 		       X_preferred_room_code               => rec_uso.preferred_room_code,
1259 		       X_dedicated_building_code           => rec_uso.dedicated_building_code,
1260 		       X_dedicated_room_code               => rec_uso.dedicated_room_code,
1261 		       x_cancel_flag                       => rec_uso.cancel_flag,
1262 		       x_occurrence_identifier             => rec_uso.occurrence_identifier,
1263 		       x_abort_flag                        => rec_uso.abort_flag
1264 		    );
1265 
1266 	      END LOOP;
1267             END IF;
1268 	  ELSE
1269             OPEN user_check(g_n_user_id);
1270 	    FETCH user_check INTO l_c_var;
1271 	    IF user_check%FOUND THEN
1272 	      p_conc_flag:= TRUE;
1273             ELSE
1274 	      --Update the occurrence status
1275 	      upd_usec_occurs_schd_status(c_usec_rec.uoo_id,'USER_CANCEL');
1276             END IF;
1277 	    CLOSE user_check;
1278 
1279 	  END IF; -- end if of checking whether scheduling software is installed or not profile checking.
1280 	END IF;
1281       END IF;
1282 
1283     END IF;--End of  validations for update
1284 
1285   END validate_uoo;
1286 
1287 
1288 
1289   -- Validate Unit Section Credit Points Records before inserting them
1290   PROCEDURE validate_cps ( p_usec_rec IN OUT NOCOPY igs_ps_generic_pub.usec_rec_type,
1291                            p_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
1292 			   p_insert_update VARCHAR2) AS
1293 
1294   /***********************************************************************************************
1295     Created By     :  shtatiko
1296     Date Created By:  23-NOV-2002
1297     Purpose        :  This procedure will validate records before inserting Unit Section Credit Points
1298 
1299     Known limitations,enhancements,remarks:
1300     Change History (in reverse chronological order)
1301     Who         When            What
1302     sommukhe    29-AUG-2005     Bug # 4089179.Included the check for insert condition while recalculating Re-calculating the values in Worload lecture,
1303                                 Laboratory and Other in Teaching Responsibilities
1304     smvk        17-Jun-2004     Bug # 3697443.Added variable increment into the validation for displaying the message IGS_PS_LGCY_CPS_NULL.
1305     sarakshi    10-Nov-2003     Enh#3116171, added business logic related to the newly introduced field BILLING_CREDIT_POINTS
1306     sarakshi    28-Jun-2003     Enh#2930935,modified cursor c_credits such that it no longer selects
1307                                 enrolled and achievable credit points
1308   ********************************************************************************************** */
1309     CURSOR c_credit (cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
1310 		     cp_ver_num igs_ps_unit_ver_all.version_number%TYPE) IS
1311     SELECT points_override_ind
1312     FROM   igs_ps_unit_ver_all
1313     WHERE  unit_cd = cp_unit_cd
1314     AND    version_number = cp_ver_num;
1315 
1316     CURSOR c_teach_resp(p_uoo_id NUMBER) IS
1317     SELECT rowid,iputr.*
1318     FROM   igs_ps_usec_tch_resp iputr
1319     WHERE  iputr.uoo_id = p_uoo_id
1320     AND    iputr.percentage_allocation IS NOT NULL
1321     AND    iputr.instructional_load_lab IS NULL
1322     AND    iputr.instructional_load_lecture IS NULL
1323     AND    iputr.instructional_load IS NULL;
1324 
1325 
1326     CURSOR c_usec_cp(cp_n_uoo_id NUMBER) IS
1327     SELECT *
1328     FROM igs_ps_usec_cps
1329     WHERE uoo_id = cp_n_uoo_id;
1330 
1331     c_usec_cp_rec c_usec_cp%ROWTYPE;
1332     l_new_lab  igs_ps_usec_tch_resp_v.instructional_load_lab%TYPE;
1333     l_new_lecture igs_ps_usec_tch_resp_v.instructional_load_lecture%TYPE;
1334     l_new_other igs_ps_usec_tch_resp_v.instructional_load%TYPE;
1335 
1336     l_c_override_ind igs_ps_unit_ver_all.points_override_ind%TYPE;
1337     l_c_message VARCHAR2(30);
1338 
1339   BEGIN
1340     OPEN c_credit ( p_usec_rec.unit_cd, p_usec_rec.version_number );
1341     FETCH c_credit INTO l_c_override_ind ;
1342     CLOSE c_credit;
1343 
1344     IF l_c_override_ind = 'Y' AND ( p_usec_rec.variable_increment IS NULL OR
1345                                       p_usec_rec.maximum_credit_points IS NULL OR
1346                                       p_usec_rec.minimum_credit_points IS NULL ) THEN
1347       fnd_message.set_name ( 'IGS', 'IGS_PS_LGCY_CPS_NULL' );
1348       fnd_msg_pub.add;
1349       p_usec_rec.status := 'E';
1350     END IF;
1351 
1352     --Billing credit Points can be provided only when auditable_ind is set to Y
1353     IF p_usec_rec.auditable_ind = 'N' AND p_usec_rec.billing_credit_points IS NOT NULL THEN
1354        igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_BILL_CRD_PTS_ERROR',NULL,NULL,FALSE);
1355        p_usec_rec.status :='E';
1356     END IF;
1357 
1358     IF NOT igs_ps_val_uv.crsp_val_uv_pnt_ovrd ( l_c_override_ind,
1359                                                 p_usec_rec.variable_increment,
1360                                                 p_usec_rec.minimum_credit_points,
1361                                                 p_usec_rec.maximum_credit_points,
1362                                                 p_usec_rec.enrolled_credit_points,
1363                                                 p_usec_rec.achievable_credit_points,
1364                                                 l_c_message,TRUE ) THEN
1365         p_usec_rec.status := 'E';
1366     END IF;
1367 
1368     OPEN c_usec_cp(p_n_uoo_id);
1369     FETCH c_usec_cp INTO c_usec_cp_rec;
1370     CLOSE c_usec_cp;
1371     IF (p_insert_update = 'U' AND
1372       ( NVL(p_usec_rec.work_load_other,-1) <> NVL(c_usec_cp_rec.work_load_other,-1) OR
1373        NVL(p_usec_rec.work_load_cp_lecture ,-1) <> NVL(c_usec_cp_rec.work_load_cp_lecture ,-1) OR
1374        NVL(p_usec_rec.work_load_cp_lab,-1) <> NVL(c_usec_cp_rec.work_load_cp_lab,-1))) OR p_insert_update = 'I' THEN
1375          -- Re-calculating the values in Worload lecture,Laboratory and Other in Teaching Responsibilities as these points are modified at Unit Section level
1376 
1377           FOR c_teach_resp_rec in c_teach_resp(p_n_uoo_id)
1378           LOOP
1379                --igs_ps_fac_credt_wrkload.calculate_teach_work_load(c_teach_resp_rec.uoo_id,c_teach_resp_rec.percentage_allocation,l_new_lab,l_new_lecture,l_new_other);
1380 	       l_new_lecture:=((c_teach_resp_rec.percentage_allocation/100)* p_usec_rec.work_load_cp_lecture);
1381 	       l_new_lab:=((c_teach_resp_rec.percentage_allocation/100)* p_usec_rec.work_load_cp_lab);
1382 	       l_new_other:=((c_teach_resp_rec.percentage_allocation/100)* p_usec_rec.work_load_other);
1383 
1384 	       igs_ps_usec_tch_resp_pkg.update_row (
1385                                                   x_mode                       => 'R',
1386                                                   x_rowid                      => c_teach_resp_rec.rowid,
1387                                                   x_unit_section_teach_resp_id => c_teach_resp_rec.unit_section_teach_resp_id,
1388                                                   x_instructor_id              => c_teach_resp_rec.instructor_id,
1389                                                   x_confirmed_flag             => c_teach_resp_rec.confirmed_flag ,
1390                                                   x_percentage_allocation      => c_teach_resp_rec.percentage_allocation,
1391                                                   x_instructional_load         => l_new_other ,
1392                                                   x_lead_instructor_flag       => c_teach_resp_rec.lead_instructor_flag,
1393                                                   x_uoo_id                     => c_teach_resp_rec.uoo_id,
1394                                                   x_instructional_load_lab     => l_new_lab,
1395                                                   x_instructional_load_lecture => l_new_lecture
1396                                                  );
1397           END LOOP;
1398     END IF;
1399 
1400   END validate_cps;
1401 
1402   -- Validate Unit Section Referece Records before inserting them
1403   PROCEDURE validate_ref ( p_usec_rec IN OUT NOCOPY igs_ps_generic_pub.usec_rec_type,
1404                            p_n_subtitle_id OUT NOCOPY igs_ps_unit_subtitle.subtitle_id%TYPE,
1405 			   p_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
1406 			   p_insert_update VARCHAR2)
1407   AS
1408   /***********************************************************************************************
1409     Created By     :  shtatiko
1410     Date Created By:  23-NOV-2002
1411     Purpose        :  This does legacy validations before inserting Unit Section Reference Records.
1412 
1413     Known limitations,enhancements,remarks:
1414     Change History (in reverse chronological order)
1415     Who         When            What
1416   ********************************************************************************************** */
1417     CURSOR c_subtitle ( cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
1418                         cp_ver_num igs_ps_unit_ver_all.version_number%TYPE) IS
1419     SELECT 1
1420     FROM   igs_ps_unit_subtitle
1421     WHERE  closed_ind = 'N'
1422     AND    approved_ind = 'Y'
1423     AND    unit_cd = cp_unit_cd
1424     AND    version_number = cp_ver_num;
1425     rec_subtitle c_subtitle%ROWTYPE;
1426 
1427     CURSOR c_subtitle_id  (
1428             cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
1429             cp_ver_num igs_ps_unit_ver_all.version_number%TYPE,
1430             cp_subtitle igs_ps_unit_subtitle.subtitle%TYPE,
1431             cp_approved_ind igs_ps_unit_subtitle.approved_ind%TYPE) IS
1432     SELECT subtitle_id
1433     FROM   igs_ps_unit_subtitle
1434     WHERE  closed_ind = 'N'
1435     AND    approved_ind = cp_approved_ind
1436     AND    unit_cd = cp_unit_cd
1437     AND    version_number = cp_ver_num
1438     AND    subtitle = cp_subtitle ;
1439     rec_subtitle_id c_subtitle_id%ROWTYPE;
1440 
1441     CURSOR c_unit_ver(cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
1442                     cp_ver_num igs_ps_unit_ver_all.version_number%TYPE) IS
1443     SELECT uv.title_override_ind,
1444            uv.subtitle_modifiable_flag
1445     FROM   igs_ps_unit_ver uv
1446     WHERE  uv.unit_cd = cp_unit_cd
1447     AND    uv.version_number = cp_ver_num;
1448     r_unit_ver c_unit_ver%ROWTYPE;
1449 
1450     CURSOR c_usec_ref(p_n_uoo_id NUMBER) IS
1451     SELECT *
1452     FROM igs_ps_usec_ref
1453     WHERE uoo_id = p_n_uoo_id;
1454 
1455     c_usec_ref_rec c_usec_ref%ROWTYPE;
1456 
1457     CURSOR c_subtitle_closed  (
1458           cp_unit_cd igs_ps_unit_ver_all.unit_cd%TYPE,
1459           cp_ver_num igs_ps_unit_ver_all.version_number%TYPE,
1460           cp_subtitle igs_ps_unit_subtitle.subtitle%TYPE ) IS
1461     SELECT 'X'
1462     FROM   igs_ps_unit_subtitle
1463     WHERE  closed_ind = 'Y'
1464     AND    unit_cd = cp_unit_cd
1465     AND    version_number = cp_ver_num
1466     AND    subtitle = cp_subtitle ;
1467     l_c_var VARCHAR2(1);
1468 
1469   BEGIN
1470 
1471     IF p_usec_rec.reference_subtitle IS NOT NULL THEN
1472 
1473       OPEN c_subtitle ( p_usec_rec.unit_cd, p_usec_rec.version_number );
1474       FETCH c_subtitle INTO rec_subtitle ;
1475       IF c_subtitle%FOUND THEN
1476 	OPEN c_subtitle_id ( p_usec_rec.unit_cd, p_usec_rec.version_number, p_usec_rec.reference_subtitle, 'Y' );
1477 	FETCH c_subtitle_id INTO rec_subtitle_id;
1478 	IF c_subtitle_id%FOUND THEN
1479 	  p_n_subtitle_id := rec_subtitle_id.subtitle_id;
1480 	ELSE
1481 	  fnd_message.set_name ( 'IGS', 'IGS_PS_INVALID_SUBTITLE' );
1482 	  fnd_msg_pub.add;
1483 	  p_usec_rec.status := 'E';
1484 	  p_n_subtitle_id := NULL;
1485 	END IF;
1486 	CLOSE c_subtitle_id;
1487       ELSE
1488 	-- Check if any Un-Approved subtitles exist with given subtitle
1489 	OPEN c_subtitle_id ( p_usec_rec.unit_cd, p_usec_rec.version_number, p_usec_rec.reference_subtitle, 'N' );
1490 	FETCH c_subtitle_id INTO rec_subtitle_id;
1491 
1492 	IF c_subtitle_id%FOUND THEN
1493 	  p_n_subtitle_id := rec_subtitle_id.subtitle_id;
1494 	ELSE
1495 	  --Added this condition as a part of bug#3748341
1496 	  --If the passed subtitle is a closed one then it is an error condition , if it does not exists then insert it
1497 	  OPEN c_subtitle_closed(p_usec_rec.unit_cd, p_usec_rec.version_number, p_usec_rec.reference_subtitle);
1498 	  FETCH c_subtitle_closed INTO l_c_var;
1499 	  IF c_subtitle_closed%NOTFOUND THEN
1500 	    -- Subtitle is not null and there is no approved or un-approved subtitle exist
1501 	    -- then insert the passed subtitle into table
1502 	    INSERT INTO igs_ps_unit_subtitle
1503 	    (subtitle_id,
1504 	     unit_cd,
1505 	     version_number,
1506 	     subtitle,
1507 	     approved_ind,
1508 	     closed_ind,
1509 	     created_by,
1510 	     creation_date,
1511 	     last_updated_by,
1512 	     last_update_date,
1513 	     last_update_login
1514 	    )
1515 	    VALUES
1516 	    (igs_ps_unit_subtitle_s.NEXTVAL,
1517 	     p_usec_rec.unit_cd,
1518 	     p_usec_rec.version_number,
1519 	     p_usec_rec.reference_subtitle,
1520 	     'N',
1521 	     'N',
1522 	     g_n_user_id,
1523 	     SYSDATE,
1524 	     g_n_user_id,
1525 	     SYSDATE,
1526 	     g_n_login_id
1527 	    )RETURNING subtitle_id INTO p_n_subtitle_id;
1528 	  ELSE
1529 	    fnd_message.set_name ( 'IGS', 'IGS_PS_INVALID_SUBTITLE' );
1530 	    fnd_msg_pub.add;
1531 	    p_usec_rec.status := 'E';
1532 	    p_n_subtitle_id := NULL;
1533 	  END IF;
1534 	  CLOSE c_subtitle_closed;
1535 	END IF;
1536 	CLOSE c_subtitle_id;
1537       END IF;
1538       CLOSE c_subtitle;
1539     END IF;
1540 
1541     -- Validate DFF columns
1542     IF NOT igs_ad_imp_018.validate_desc_flex ( p_usec_rec.reference_attribute_category,
1543                                                p_usec_rec.reference_attribute1,
1544                                                p_usec_rec.reference_attribute2,
1545                                                p_usec_rec.reference_attribute3,
1546                                                p_usec_rec.reference_attribute4,
1547                                                p_usec_rec.reference_attribute5,
1548                                                p_usec_rec.reference_attribute6,
1549                                                p_usec_rec.reference_attribute7,
1550                                                p_usec_rec.reference_attribute8,
1551                                                p_usec_rec.reference_attribute9,
1552                                                p_usec_rec.reference_attribute10,
1553                                                p_usec_rec.reference_attribute11,
1554                                                p_usec_rec.reference_attribute12,
1555                                                p_usec_rec.reference_attribute13,
1556                                                p_usec_rec.reference_attribute14,
1557                                                p_usec_rec.reference_attribute15,
1558                                                p_usec_rec.reference_attribute16,
1559                                                p_usec_rec.reference_attribute17,
1560                                                p_usec_rec.reference_attribute18,
1561                                                p_usec_rec.reference_attribute18,
1562                                                p_usec_rec.reference_attribute20,
1563                                                'IGS_PS_USEC_REF_FLEX' ) THEN
1564       fnd_message.set_name ( 'IGS', 'IGS_AD_INVALID_DESC_FLEX' );
1565       fnd_msg_pub.add;
1566       p_usec_rec.status := 'E';
1567     END IF;
1568 
1569     IF p_insert_update ='U' THEN
1570 
1571       OPEN c_unit_ver(p_usec_rec.unit_cd,p_usec_rec.version_number);
1572       FETCH c_unit_ver INTO r_unit_ver;
1573       CLOSE c_unit_ver;
1574 
1575       OPEN c_usec_ref(p_n_uoo_id);
1576       FETCH c_usec_ref INTO c_usec_ref_rec;
1577       CLOSE c_usec_ref;
1578 
1579       -- IF override Title is checked at Unit Level then only  update is allowed.
1580       IF r_unit_ver.title_override_ind = 'N' THEN
1581 	--cannot  update TITLE log error message
1582 	IF p_usec_rec.reference_title <> c_usec_ref_rec.title THEN
1583 	  fnd_message.set_name( 'IGS', 'IGS_PS_CNT_UPD_TITLE');
1584 	  p_usec_rec.status := 'E';
1585 	  fnd_msg_pub.add;
1586 	END IF;
1587 
1588       END IF;
1589 
1590       -- IF subtitle modifiable is checked at Unit Level then only update is allowed .
1591       IF r_unit_ver.subtitle_modifiable_flag = 'N' THEN
1592 	  --cannot  update SUBTITLE log error message
1593 	IF p_usec_rec.reference_subtitle <> c_usec_ref_rec.subtitle THEN
1594 	  fnd_message.set_name( 'IGS', 'IGS_PS_CNT_UPD_SUBTITLE');
1595 	  p_usec_rec.status := 'E';
1596 	  fnd_msg_pub.add;
1597 	END IF;
1598       END IF;
1599     END IF;
1600   END validate_ref;
1601 
1602   PROCEDURE validate_usec_grd_sch ( p_usec_gs_rec IN OUT NOCOPY igs_ps_generic_pub.usec_gs_rec_type,
1603                                     p_n_uoo_id    IN NUMBER)
1604   AS
1605   /***********************************************************************************************
1606     Created By     :  shtatiko
1607     Date Created By:  15-NOV-2002
1608     Purpose        :  This procedure will do validations before inserting records of Unit Section Grading Schema.
1609                       This is called from sub process of legacy import data, which inserts Unit Section GS records.
1610 
1611     Known limitations,enhancements,remarks:
1612     Change History (in reverse chronological order)
1613     Who         When            What
1614   ********************************************************************************************** */
1615   l_c_message  VARCHAR2(30);
1616 
1617   BEGIN
1618     -- Check if grading schema type is 'UNIT' for a given grading schema.
1619     IF NOT validate_gs_type ( p_usec_gs_rec.grading_schema_code, p_usec_gs_rec.grd_schm_version_number ) THEN
1620       fnd_message.set_name ( 'IGS', 'IGS_PS_LGCY_INCORRECT_GS_TYPE' );
1621       fnd_msg_pub.add;
1622       p_usec_gs_rec.status := 'E';
1623     END IF;
1624 
1625     -- Check if unit status is inactive.
1626     IF NOT igs_ps_val_unit.crsp_val_iud_uv_dtl(p_usec_gs_rec.unit_cd,p_usec_gs_rec.version_number,l_c_message) THEN
1627       fnd_message.set_name ( 'IGS', 'IGS_PS_NOCHG_UNITVER_DETAILS' );
1628       fnd_msg_pub.add;
1629       p_usec_gs_rec.status := 'E';
1630     END IF;
1631 
1632     --Check if the unit section is NOT_OFFERED
1633     IF NOT igs_ps_validate_lgcy_pkg.check_not_offered_usec_status(p_n_uoo_id) THEN
1634       fnd_message.set_name ( 'IGS', 'IGS_PS_IMP_NOT_ALD_NOT_OFFERED' );
1635       fnd_msg_pub.add;
1636       p_usec_gs_rec.status := 'E';
1637     END IF;
1638 
1639   END validate_usec_grd_sch;
1640 
1641   FUNCTION post_usec_grd_sch ( p_tab_usec_gs IN OUT NOCOPY igs_ps_generic_pub.usec_gs_tbl_type,
1642                                p_tab_uoo     IN igs_ps_create_generic_pkg.uoo_tbl_type) RETURN BOOLEAN
1643   AS
1644   /***********************************************************************************************
1645     Created By     :  Sommukhe
1646     Date Created By:
1647     Purpose        :  This function will do validations after inserting records of Unit Section Grading Schema.
1648                       This will returns TRUE if all the validations pass and returns FALSE, if fails.
1649 
1650     Known limitations,enhancements,remarks:
1651     Change History (in reverse chronological order)
1652     Who         When            What
1653   ********************************************************************************************** */
1654   CURSOR c_usec_gs_count ( cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE ) IS
1655   SELECT COUNT(*) cnt
1656   FROM   igs_ps_usec_grd_schm
1657   WHERE  uoo_id = cp_uoo_id
1658   AND    default_flag = 'Y';
1659   rec_usec_gs_count c_usec_gs_count%ROWTYPE;
1660 
1661   CURSOR c_uoo_id (cp_usec_gs_rec IN OUT NOCOPY igs_ps_generic_pub.usec_gs_rec_type) IS
1662   SELECT uoo_id
1663   FROM   igs_ps_unit_ofr_opt_all a,igs_ca_inst_all b
1664   WHERE  a.unit_cd = cp_usec_gs_rec.unit_cd
1665   AND a.version_number = cp_usec_gs_rec.version_number
1666   AND a.cal_type = b.cal_type
1667   AND a.ci_sequence_number = b.sequence_number
1668   AND b.alternate_code=cp_usec_gs_rec.teach_cal_alternate_code
1669   AND a.location_cd =cp_usec_gs_rec.location_cd
1670   AND a.unit_class = cp_usec_gs_rec.unit_class;
1671   c_uoo_id_rec c_uoo_id%ROWTYPE;
1672 
1673   l_n_count_msg NUMBER(6);
1674   l_b_status    BOOLEAN;
1675 
1676   BEGIN
1677     l_b_status:= TRUE;
1678     -- Check if atleast and atmost one default flag is set to 'Y' for a given unit code and version number.
1679     FOR i IN 1 ..p_tab_uoo.LAST LOOP
1680 
1681     OPEN c_usec_gs_count (p_tab_uoo(i));
1682     FETCH c_usec_gs_count INTO rec_usec_gs_count;
1683     IF rec_usec_gs_count.cnt <> 1 THEN
1684       l_b_status:= FALSE;
1685       fnd_message.set_name ( 'IGS', 'IGS_PS_GRD_SCHM_CHCK' );
1686       fnd_msg_pub.add;
1687       l_n_count_msg := fnd_msg_pub.count_msg;
1688       FOR j in 1..p_tab_usec_gs.LAST LOOP
1689          OPEN c_uoo_id (p_tab_usec_gs(j));
1690 	 FETCH c_uoo_id INTO c_uoo_id_rec;
1691          CLOSE c_uoo_id;
1692 	IF p_tab_usec_gs.EXISTS(j) THEN
1693           IF p_tab_usec_gs(j).status = 'S' AND p_tab_uoo(i)= c_uoo_id_rec.uoo_id THEN
1694             p_tab_usec_gs(j).status := 'E';
1695             p_tab_usec_gs(j).msg_from := l_n_count_msg;
1696             p_tab_usec_gs(j).msg_to := l_n_count_msg;
1697           END IF;
1698         END IF;
1699       END LOOP;
1700     END IF;
1701     CLOSE c_usec_gs_count;
1702   END LOOP;
1703 
1704   RETURN   l_b_status;
1705 
1706   END post_usec_grd_sch;
1707 
1708   PROCEDURE validate_usec_occurs ( p_uso_rec IN OUT NOCOPY igs_ps_generic_pub.uso_rec_type,
1709                                    p_n_uoo_id IN igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
1710                                    p_d_start_date IN igs_ca_inst_all.start_dt%TYPE,
1711                                    p_d_end_date IN igs_ca_inst_all.end_dt%TYPE,
1712 				   p_n_building_code IN NUMBER,
1713 				   p_n_room_code IN NUMBER,
1714 				   p_n_dedicated_building_code IN NUMBER,
1715 				   p_n_dedicated_room_code IN NUMBER,
1716 				   p_n_preferred_building_code IN NUMBER,
1717 				   p_n_preferred_room_code IN NUMBER,
1718 				   p_n_uso_id IN NUMBER,
1719 				   p_insert IN VARCHAR2,
1720 				   p_calling_context IN VARCHAR2,
1721 				   p_notify_status OUT NOCOPY VARCHAR2,
1722 				   p_schedule_status IN OUT NOCOPY VARCHAR2
1723 				   ) AS
1724 
1725   /***********************************************************************************************
1726     Created By     :  shtatiko
1727     Date Created By:  20-NOV-2002
1728     Purpose        :  This procedure will do validations before inserting record of Unit Section Occurrence.
1729                       This is called from sub process of legacy import data, which inserts USO records.
1730 
1731     Known limitations,enhancements,remarks:
1732     Change History (in reverse chronological order)
1733     Who         When            What
1734     jbegum      3-June-2003     Enh Bug#2972950
1735                                 For the PSP Scheduling Enhancements TD:
1736                                 Added validations given in TD.
1737   ********************************************************************************************** */
1738 
1739   CURSOR c_usec_dates ( cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE ) IS
1740   SELECT unit_section_start_date start_date,
1741          unit_section_end_date end_date
1742   FROM igs_ps_unit_ofr_opt_all
1743   WHERE
1744     uoo_id = cp_uoo_id ;
1745   rec_usec_dates c_usec_dates%ROWTYPE;
1746   l_message_name fnd_new_messages.message_name%TYPE;
1747 --
1748 CURSOR c_room_id(cp_bld_id IN NUMBER, cp_rom_id IN NUMBER) IS
1749 SELECT 'X'
1750 FROM igs_ad_room
1751 WHERE  building_id=cp_bld_id
1752 AND room_id=cp_rom_id;
1753 l_c_var VARCHAR2(1);
1754 
1755 
1756 
1757 CURSOR c_ins(cp_uso_id IN NUMBER) IS
1758 SELECT instructor_id  FROM igs_ps_uso_instrctrs
1759 WHERE unit_section_occurrence_id = cp_uso_id;
1760 
1761 CURSOR cur_occur(cp_uso_id IN NUMBER) IS
1762 SELECT *
1763 FROM igs_ps_usec_occurs_all
1764 WHERE unit_section_occurrence_id = cp_uso_id;
1765 l_cur_occur cur_occur%ROWTYPE;
1766 
1767     CURSOR c_shadow_num(l_unit_sec_occurrence_id IGS_PS_USEC_OCCURS.unit_section_occurrence_id%TYPE) IS
1768 	SELECT count(*)
1769 	FROM IGS_PS_SH_USEC_OCCURS
1770 	WHERE unit_section_occurrence_id= l_unit_sec_occurrence_id;
1771     l_shadow_num number;
1772     l_new_monday IGS_PS_USEC_OCCURS_V.monday%TYPE := '1';
1773     l_new_tuesday IGS_PS_USEC_OCCURS_V.tuesday%TYPE := '1';
1774     l_new_wednesday IGS_PS_USEC_OCCURS_V.wednesday%TYPE := '1';
1775     l_new_thursday IGS_PS_USEC_OCCURS_V.thursday%TYPE:= '1';
1776     l_new_friday IGS_PS_USEC_OCCURS_V.friday%TYPE := '1';
1777     l_new_saturday IGS_PS_USEC_OCCURS_V.saturday%TYPE := '1';
1778     l_new_sunday IGS_PS_USEC_OCCURS_V.sunday%TYPE := '1';
1779     l_new_start_time VARCHAR2(50):='1' ;
1780     l_new_end_time VARCHAR2(50) :='1';
1781     l_new_building_code VARCHAR2(10):='1';
1782     l_new_room_code VARCHAR2(10):='1';
1783 
1784     l_old_monday IGS_PS_USEC_OCCURS_V.monday%TYPE := '1';
1785     l_old_tuesday IGS_PS_USEC_OCCURS_V.tuesday%TYPE := '1';
1786     l_old_wednesday IGS_PS_USEC_OCCURS_V.wednesday%TYPE := '1';
1787     l_old_thursday IGS_PS_USEC_OCCURS_V.thursday%TYPE := '1';
1788     l_old_friday IGS_PS_USEC_OCCURS_V.friday%TYPE := '1';
1789     l_old_saturday IGS_PS_USEC_OCCURS_V.saturday%TYPE := '1';
1790     l_old_sunday IGS_PS_USEC_OCCURS_V.sunday%TYPE := '1';
1791     l_old_start_time VARCHAR2(50):='1' ;
1792     l_old_end_time VARCHAR2(50) :='1';
1793     l_old_building_code VARCHAR2(10):='1';
1794     l_old_room_code VARCHAR2(10):='1';
1795 
1796     i binary_integer:=1;ctr number;
1797    l_new_instructor_id IGS_PS_SH_USEC_OCCURS.instructor_id%TYPE := NULL;
1798    l_old_instructor_id IGS_PS_SH_USEC_OCCURS.instructor_id%TYPE := NULL;
1799    l_new_usecsh_id IGS_PS_SH_USEC_OCCURS.usecsh_id%TYPE;
1800    l_new_unit_section_occur_id IGS_PS_USEC_OCCURS.unit_section_occurrence_id%TYPE;
1801 
1802     CURSOR c_shadow_rec(l_unit_sec_occurrence_id IGS_PS_USEC_OCCURS.unit_section_occurrence_id%TYPE) IS
1803 	SELECT monday,tuesday, wednesday, thursday, friday, saturday,
1804 		sunday, start_time, end_time, building_code, room_code, instructor_id
1805 	FROM IGS_PS_SH_USEC_OCCURS
1806 	WHERE unit_section_occurrence_id= l_unit_sec_occurrence_id;
1807 
1808     l_shd_monday IGS_PS_USEC_OCCURS_V.monday%TYPE:= '1';
1809     l_shd_tuesday IGS_PS_USEC_OCCURS_V.tuesday%TYPE:= '1';
1810     l_shd_wednesday IGS_PS_USEC_OCCURS_V.wednesday%TYPE:= '1';
1811     l_shd_thursday IGS_PS_USEC_OCCURS_V.thursday%TYPE:= '1';
1812     l_shd_friday IGS_PS_USEC_OCCURS_V.friday%TYPE:= '1';
1813     l_shd_saturday IGS_PS_USEC_OCCURS_V.saturday%TYPE:= '1';
1814     l_shd_sunday IGS_PS_USEC_OCCURS_V.sunday%TYPE:= '1';
1815     l_shd_start_time VARCHAR2(50):='1';
1816     l_shd_end_time VARCHAR2(50):='1';
1817     l_shd_building_code VARCHAR2(10):='1';
1818     l_shd_room_code VARCHAR2(10):='1';
1819     l_shd_instructor_id IGS_PS_SH_USEC_OCCURS_V.instructor_id%TYPE:= '1';
1820     lv_usec_occur_id IGS_PS_USEC_OCCURS.unit_section_occurrence_id%TYPE:= 1;
1821     CURSOR c_insv_unit_sec_occur_id(l_unit_occur_id IGS_PS_USEC_OCCURS.unit_section_occurrence_id%TYPE) IS
1822       SELECT instructor_id from IGS_PS_SH_USEC_OCCURS
1823       WHERE unit_section_occurrence_id =l_unit_occur_id;
1824     l_insv_instructor_id IGS_PS_SH_USEC_OCCURS.instructor_id%TYPE;
1825 
1826 CURSOR cur_sch_int(cp_uso_id IN NUMBER) IS
1827 SELECT uso.transaction_type,uso.schedule_status,uso.int_occurs_id,uso.int_usec_id,uso.tba_status, usec.int_pat_id
1828 FROM igs_ps_sch_int_all uso, igs_ps_sch_usec_int_all usec
1829 WHERE uso.unit_section_occurrence_id=cp_uso_id
1830 AND   uso.int_usec_id = usec.int_usec_id
1831 AND   uso.transaction_type IN ('REQUEST','UPDATE' ,'CANCEL')
1832 AND   uso.abort_flag='N';
1833 l_cur_sch_int cur_sch_int%ROWTYPE;
1834 
1835 CURSOR cur_int_usec(cp_uoo_id IN NUMBER) IS
1836 SELECT *
1837 FROM  igs_ps_sch_usec_int_all
1838 WHERE uoo_Id=cp_uoo_id
1839 AND  abort_flag='N';
1840 l_cur_int_usec  cur_int_usec%ROWTYPE;
1841 
1842 l_transaction_type  igs_ps_sch_int_all.transaction_type%TYPE;
1843 
1844 --
1845   BEGIN
1846 
1847 
1848     -- If one building code and room code is passed then other one should be passed.
1849     -- Otherwise, error out with proper message.
1850 
1851     IF p_n_room_code IS NOT NULL AND p_n_building_code IS NULL THEN
1852       igs_ps_validate_lgcy_pkg.set_msg('IGS_EN_INV', 'BUILDING_CODE', 'LEGACY_TOKENS', FALSE);
1853       p_uso_rec.status := 'E';
1854     END IF;
1855 
1856 
1857     IF p_n_dedicated_room_code IS NOT NULL AND p_n_dedicated_building_code IS NULL THEN
1858       igs_ps_validate_lgcy_pkg.set_msg('IGS_EN_INV', igs_ps_validate_lgcy_pkg.get_lkup_meaning('DEDICATED', 'LEGACY_TOKENS') || ' ' ||
1859                                         igs_ps_validate_lgcy_pkg.get_lkup_meaning('BUILDING_CODE', 'LEGACY_TOKENS'), NULL, FALSE);
1860       p_uso_rec.status := 'E';
1861     END IF;
1862 
1863 
1864     IF p_n_preferred_room_code IS NOT NULL AND p_n_preferred_building_code IS NULL THEN
1865       igs_ps_validate_lgcy_pkg.set_msg('IGS_EN_INV', igs_ps_validate_lgcy_pkg.get_lkup_meaning('PREFERRED', 'LEGACY_TOKENS') || ' ' ||
1866                                         igs_ps_validate_lgcy_pkg.get_lkup_meaning('BUILDING_CODE', 'LEGACY_TOKENS'), NULL, FALSE);
1867       p_uso_rec.status := 'E';
1868     END IF;
1869 
1870 
1871     -- Validate Start Date and End Date.
1872     OPEN c_usec_dates ( p_n_uoo_id );
1873     FETCH c_usec_dates INTO rec_usec_dates;
1874 
1875     -- Unit Section Occurrence (USO) start date should be greater than or equal to Unit Section (US) start date
1876     IF ( p_uso_rec.start_date IS NOT NULL ) THEN
1877       -- Check if it is less than start_date
1878       IF ( rec_usec_dates.start_date IS NOT NULL ) THEN
1879         IF ( p_uso_rec.start_date < rec_usec_dates.start_date ) THEN
1880           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_STDT_GE_US_STDT' );
1881           fnd_msg_pub.add;
1882           p_uso_rec.status := 'E';
1883         END IF;
1884       ELSE
1885         IF ( p_uso_rec.start_date < p_d_start_date ) THEN
1886           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_STDT_GE_TP_STDT' );
1887           fnd_msg_pub.add;
1888           p_uso_rec.status := 'E';
1889         END IF;
1890       END IF;
1891 
1892       -- Check if it is greater than end date
1893       IF ( rec_usec_dates.end_date IS NOT NULL ) THEN
1894         IF ( p_uso_rec.start_date > rec_usec_dates.end_date ) THEN
1895           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_ST_DT_UOO_END_DT' );
1896           fnd_msg_pub.add;
1897           p_uso_rec.status := 'E';
1898         END IF;
1899       ELSE
1900         IF ( p_uso_rec.start_date > p_d_end_date ) THEN
1901           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_ST_DT_TP_END_DT' );
1902           fnd_msg_pub.add;
1903           p_uso_rec.status := 'E';
1904         END IF;
1905       END IF;
1906 
1907     END IF;
1908 
1909     -- USO start date should be less than or equal to USO end date
1910     IF ( p_uso_rec.start_date > p_uso_rec.end_date ) THEN
1911       fnd_message.set_name ( 'IGS', 'IGS_PE_EDT_LT_SDT' );
1912       fnd_msg_pub.add;
1913       p_uso_rec.status := 'E';
1914     END IF;
1915 
1916     IF ( p_uso_rec.end_date IS NOT NULL ) THEN
1917       -- Check it against start_date
1918       IF ( rec_usec_dates.start_date IS NOT NULL ) THEN
1919         IF ( p_uso_rec.end_date < rec_usec_dates.start_date ) THEN
1920           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_END_DT_UOO_ST_DT' );
1921           fnd_msg_pub.add;
1922           p_uso_rec.status := 'E';
1923         END IF;
1924       ELSE
1925         IF ( p_uso_rec.end_date < p_d_start_date ) THEN
1926           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_END_DT_TP_ST_DT' );
1927           fnd_msg_pub.add;
1928           p_uso_rec.status := 'E';
1929         END IF;
1930       END IF;
1931 
1932       -- Check it against end_date
1933       IF ( rec_usec_dates.start_date IS NOT NULL ) THEN
1934         IF ( p_uso_rec.end_date > rec_usec_dates.end_date ) THEN
1935           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_ENDT_LE_US_ENDT' );
1936           fnd_msg_pub.add;
1937           p_uso_rec.status := 'E';
1938         END IF;
1939       ELSE
1940         IF ( p_uso_rec.end_date > p_d_end_date ) THEN
1941           fnd_message.set_name ( 'IGS', 'IGS_PS_USO_ENDT_LE_TP_ENDT' );
1942           fnd_msg_pub.add;
1943           p_uso_rec.status := 'E';
1944         END IF;
1945       END IF;
1946 
1947     END IF;
1948     CLOSE c_usec_dates;
1949 
1950 
1951     -- Validated start time and end time. USO start time should be less than USO end time.
1952     -- Compare only time part of date
1953     IF ( to_char(p_uso_rec.start_time,'HH24MI') > to_char(p_uso_rec.end_time,'HH24MI') ) THEN
1954       fnd_message.set_name ( 'IGS', 'IGS_GE_ST_TIME_LT_END_TIME' );
1955       fnd_msg_pub.add;
1956       p_uso_rec.status := 'E';
1957     END IF;
1958 
1959     -- If to_be_announced is 'N' then atleast one of the day must be checked.
1960     IF (p_uso_rec.to_be_announced = 'N' AND p_uso_rec.no_set_day_ind = 'N' AND
1961         p_uso_rec.monday    ='N' AND
1962         p_uso_rec.tuesday   ='N' AND
1963         p_uso_rec.wednesday ='N' AND
1964         p_uso_rec.thursday  ='N' AND
1965         p_uso_rec.friday    ='N' AND
1966         p_uso_rec.saturday  ='N' AND
1967         p_uso_rec.sunday    ='N' ) THEN
1968       fnd_message.set_name ( 'IGS', 'IGS_PS_ATLEAST_ONE_DAY_CHECK' );
1969       fnd_msg_pub.add;
1970       p_uso_rec.status := 'E';
1971     END IF;
1972 
1973     -- IF to_be_announced is 'Y' then no day should have 'Y'
1974     IF (p_uso_rec.to_be_announced = 'Y' AND
1975         ( p_uso_rec.monday    ='Y' OR
1976           p_uso_rec.tuesday   ='Y' OR
1977           p_uso_rec.wednesday ='Y' OR
1978           p_uso_rec.thursday  ='Y' OR
1979           p_uso_rec.friday    ='Y' OR
1980           p_uso_rec.saturday  ='Y' OR
1981           p_uso_rec.sunday    ='Y' OR
1982           p_uso_rec.start_time  IS NOT NULL OR
1983           p_uso_rec.end_time  IS NOT NULL)
1984         ) THEN
1985       fnd_message.set_name ( 'IGS', 'IGS_PS_LGCY_TBA_WITH_DAYS' );
1986       fnd_msg_pub.add;
1987       p_uso_rec.status := 'E';
1988     END IF;
1989 
1990     --Start date and end date should be provided for normal unit section occurrences
1991     IF ( p_uso_rec.monday  ='Y' OR
1992           p_uso_rec.tuesday   ='Y' OR
1993           p_uso_rec.wednesday ='Y' OR
1994           p_uso_rec.thursday  ='Y' OR
1995           p_uso_rec.friday    ='Y' OR
1996           p_uso_rec.saturday  ='Y' OR
1997           p_uso_rec.sunday    ='Y' ) AND
1998           (p_uso_rec.start_date  IS  NULL OR  p_uso_rec.end_date  IS  NULL) AND
1999            p_uso_rec.no_set_day_ind='N'
2000          THEN
2001       fnd_message.set_name ( 'IGS', 'IGS_AS_BOTH_STDT_ENDDT_ENERED' );
2002       fnd_msg_pub.add;
2003       p_uso_rec.status := 'E';
2004     END IF;
2005 
2006     -- Cannot enter Preferred Building/Room if Dedicated Building/Room is entered.
2007     IF ( p_n_dedicated_building_code IS NOT NULL AND
2008          ( p_n_preferred_room_code IS NOT NULL OR
2009            p_n_preferred_building_code IS NOT NULL )
2010        ) THEN
2011       fnd_message.set_name ( 'IGS', 'IGS_PS_ENTER_PREF_DEDICATED' );
2012       fnd_msg_pub.add;
2013       p_uso_rec.status := 'E';
2014     END IF;
2015 
2016     -- Can enter either Other Building Options (Preferred or Dedicated Building/Room) or Scheduled Building
2017     IF ( p_n_building_code IS NOT NULL AND
2018          ( p_n_dedicated_building_code IS NOT NULL OR
2019            p_n_preferred_building_code IS NOT NULL OR
2020            p_n_dedicated_room_code IS NOT NULL OR
2021            p_n_preferred_room_code IS NOT NULL
2022          )
2023        ) THEN
2024       fnd_message.set_name ( 'IGS', 'IGS_PS_SCHD_OR_OTHER' );
2025       fnd_msg_pub.add;
2026       p_uso_rec.status := 'E';
2027     END IF;
2028 
2029     -- Validate DFF columns
2030     IF NOT igs_ad_imp_018.validate_desc_flex ( p_uso_rec.attribute_category,
2031                                                p_uso_rec.attribute1,
2032                                                p_uso_rec.attribute2,
2033                                                p_uso_rec.attribute3,
2034                                                p_uso_rec.attribute4,
2035                                                p_uso_rec.attribute5,
2036                                                p_uso_rec.attribute6,
2037                                                p_uso_rec.attribute7,
2038                                                p_uso_rec.attribute8,
2039                                                p_uso_rec.attribute9,
2040                                                p_uso_rec.attribute10,
2041                                                p_uso_rec.attribute11,
2042                                                p_uso_rec.attribute12,
2043                                                p_uso_rec.attribute13,
2044                                                p_uso_rec.attribute14,
2045                                                p_uso_rec.attribute15,
2046                                                p_uso_rec.attribute16,
2047                                                p_uso_rec.attribute17,
2048                                                p_uso_rec.attribute18,
2049                                                p_uso_rec.attribute18,
2050                                                p_uso_rec.attribute20,
2051                                                'IGS_PS_UNITSEC_OCCUR' ) THEN
2052       fnd_message.set_name ( 'IGS', 'IGS_AD_INVALID_DESC_FLEX' );
2053       fnd_msg_pub.add;
2054       p_uso_rec.status := 'E';
2055     END IF;
2056 
2057 
2058     -- Following validation added as part of enh bug#2972950 for the PSP Scheduling Enhancements
2059     --  Unit Section Occurrence should not have both the No Set Day Indicator and To Be Announced Indicator
2060     -- set to 'Y'.
2061 
2062     IF p_uso_rec.no_set_day_ind = 'Y' AND
2063        p_uso_rec.to_be_announced = 'Y' THEN
2064 
2065          fnd_message.set_name ( 'IGS', 'IGS_PS_NSD_OR_TBA' );
2066          fnd_msg_pub.add;
2067          p_uso_rec.status := 'E';
2068 
2069     END IF;
2070 
2071     -- Following validation added as part of enh bug#2972950 for the PSP Scheduling Enhancements
2072     --  User can enter either preferred region code or other scheduling options
2073     -- (ie. preferred or dedicated or scheduled building/room)
2074 
2075     IF p_uso_rec.preferred_region_code IS NOT NULL THEN
2076        IF p_n_building_code IS NOT NULL OR
2077           p_n_room_code IS NOT NULL OR
2078           p_n_dedicated_building_code IS NOT NULL OR
2079           p_n_dedicated_room_code IS NOT NULL OR
2080           p_n_preferred_building_code IS NOT NULL OR
2081           p_n_preferred_room_code IS NOT NULL THEN
2082 
2083             fnd_message.set_name ( 'IGS', 'IGS_PS_PRF_REG_BLD_ROM_EXIST' );
2084             fnd_msg_pub.add;
2085             p_uso_rec.status := 'E';
2086 
2087        END IF;
2088     END IF;
2089 
2090 ----
2091 
2092     --Check if the unit is INACTIVE, then do not allow to insert/update
2093     IF igs_ps_val_unit.crsp_val_iud_uv_dtl(p_uso_rec.unit_cd, p_uso_rec.version_number,l_message_name)=FALSE THEN
2094           fnd_message.set_name ( 'IGS', 'IGS_PS_NOCHG_UNITVER_DETAILS' );
2095           fnd_msg_pub.add;
2096           p_uso_rec.status := 'E';
2097     END IF;
2098 
2099     --Check if the unit section is NOT_OFFERED
2100     IF NOT igs_ps_validate_lgcy_pkg.check_not_offered_usec_status(p_n_uoo_id) THEN
2101       fnd_message.set_name ( 'IGS', 'IGS_PS_IMP_NOT_ALD_NOT_OFFERED' );
2102       fnd_msg_pub.add;
2103       p_uso_rec.status := 'E';
2104     END IF;
2105 
2106     -- Room should belong to a valid building
2107     IF p_n_building_code IS NOT NULL AND p_n_room_code IS NOT NULL THEN
2108 	OPEN c_room_id ( p_n_building_code, p_n_room_code );
2109 	FETCH c_room_id INTO l_c_var;
2110 	IF ( c_room_id%NOTFOUND ) THEN
2111           fnd_message.set_name ( 'IGS', 'IGS_PS_ROOM_INV_FOR_BLD' );
2112           fnd_msg_pub.add;
2113           p_uso_rec.status := 'E';
2114 	END IF;
2115 	CLOSE c_room_id;
2116     END IF;
2117 
2118     -- Dedicated Room should belong to a valid building
2119     IF p_n_dedicated_building_code IS NOT NULL AND p_n_dedicated_room_code IS NOT NULL THEN
2120 	OPEN c_room_id ( p_n_dedicated_building_code, p_n_dedicated_room_code );
2121 	FETCH c_room_id INTO l_c_var;
2122 	IF ( c_room_id%NOTFOUND ) THEN
2123           fnd_message.set_name ( 'IGS', 'IGS_PS_D_ROOM_INV_FOR_BLD' );
2124           fnd_msg_pub.add;
2125           p_uso_rec.status := 'E';
2126 	END IF;
2127 	CLOSE c_room_id;
2128     END IF;
2129 
2130     -- Preferred Room should belong to a valid building
2131     IF p_n_preferred_building_code IS NOT NULL AND p_n_preferred_room_code IS NOT NULL THEN
2132 	OPEN c_room_id ( p_n_preferred_building_code, p_n_preferred_room_code );
2133 	FETCH c_room_id INTO l_c_var;
2134 	IF ( c_room_id%NOTFOUND ) THEN
2135           fnd_message.set_name ( 'IGS', 'IGS_PS_P_ROOM_INV_FOR_BLD' );
2136           fnd_msg_pub.add;
2137           p_uso_rec.status := 'E';
2138 	END IF;
2139 	CLOSE c_room_id;
2140     END IF;
2141 
2142     --If time is provided then days are mandatory
2143     IF p_uso_rec.start_time IS NOT NULL OR  p_uso_rec.end_time IS NOT NULL THEN
2144       IF p_uso_rec.monday = 'N' AND p_uso_rec.tuesday = 'N' AND p_uso_rec.wednesday = 'N' AND
2145 	 p_uso_rec.thursday = 'N' AND p_uso_rec.friday = 'N' AND p_uso_rec.saturday = 'N' AND
2146 	 p_uso_rec.sunday = 'N' THEN
2147 
2148           fnd_message.set_name ( 'IGS', 'IGS_PS_DAYS_REQD_TIME_THERE' );
2149           fnd_msg_pub.add;
2150           p_uso_rec.status := 'E';
2151       END IF;
2152     END IF;
2153 
2154     IF p_insert = 'U' THEN
2155 
2156      OPEN cur_occur(p_n_uso_id);
2157      FETCH cur_occur INTO l_cur_occur;
2158      CLOSE cur_occur;
2159 
2160      --If schedule status is SCHEDULED and TBA is Y then it is error condition
2161      IF p_uso_rec.to_be_announced = 'Y' AND l_cur_occur.schedule_status='SCHEDULED' THEN
2162           fnd_message.set_name ( 'IGS', 'IGS_PS_SCHD_CANT_CHANGE_TBA' );
2163           fnd_msg_pub.add;
2164           p_uso_rec.status := 'E';
2165      END IF;
2166 
2167      --If schedule status is SCHEDULED and No_set_day is Y then it is error condition
2168      IF p_uso_rec.no_set_day_ind = 'Y' AND l_cur_occur.schedule_status='SCHEDULED' THEN
2169           fnd_message.set_name ( 'IGS', 'IGS_PS_CANT_NSD_USO' );
2170           fnd_msg_pub.add;
2171           p_uso_rec.status := 'E';
2172      END IF;
2173 
2174 
2175      --Cannot import scheduling information for already scheduled occurrence
2176      IF (p_n_building_code IS NOT NULL AND p_n_building_code <> l_cur_occur.building_code OR
2177          p_n_room_code IS NOT NULL AND p_n_room_code <> l_cur_occur.room_code ) AND l_cur_occur.schedule_status='SCHEDULED' THEN
2178           fnd_message.set_name ( 'IGS', 'IGS_PS_SCH_INFO_NOT_IMPORT' );
2179           fnd_msg_pub.add;
2180           p_uso_rec.status := 'E';
2181      END IF;
2182 
2183      --Cannot update occurrence for in progress occurrence when the calling context is not 'S'-scheduling
2184      IF  l_cur_occur.schedule_status='PROCESSING' AND p_calling_context <> 'S' THEN
2185           fnd_message.set_name ( 'IGS', 'IGS_PS_UPD_IN_PRG_OCR' );
2186           fnd_msg_pub.add;
2187           p_uso_rec.status := 'E';
2188      END IF;
2189 
2190       --If TBA is N then need to check if there is any instructors for the occurrences having time conflict, if yes then warning
2191       IF p_uso_rec.to_be_announced = 'N' THEN
2192         FOR c_ins_rec IN c_ins(p_n_uso_id) LOOP
2193            IF igs_ps_rlovr_fac_tsk.crsp_instrct_time_conflct (
2194 	            p_person_id=>c_ins_rec.instructor_id,
2195 		    p_unit_section_occurrence_id=>p_n_uso_id,
2196 		    p_monday=>p_uso_rec.monday,
2197 		    p_tuesday=>p_uso_rec.tuesday,
2198 		    p_wednesday=>p_uso_rec.wednesday,
2199 		    p_thursday=>p_uso_rec.thursday,
2200 		    p_friday=>p_uso_rec.friday,
2201 		    p_saturday=>p_uso_rec.saturday,
2202 		    p_sunday=>p_uso_rec.sunday,
2203 		    p_start_time=>p_uso_rec.start_time,
2204 		    p_end_time=>p_uso_rec.end_time,
2205 		    p_start_date=>p_uso_rec.start_date,
2206 		    p_end_date=>p_uso_rec.end_date,
2207 		    p_calling_module=>'FORM',
2208 		    p_message_name => l_message_name)= FALSE THEN
2209 
2210 		fnd_message.set_name ( 'IGS', l_message_name );
2211 		fnd_msg_pub.add;
2212 		p_uso_rec.status := 'W';
2213                 EXIT;
2214            END IF;
2215 	END LOOP;
2216       END IF;
2217 
2218 
2219      IF   p_calling_context = 'S' THEN
2220 
2221        OPEN cur_sch_int(p_n_uso_id);
2222        FETCH cur_sch_int INTO l_cur_sch_int;
2223        IF cur_sch_int%FOUND THEN
2224 
2225          -- TBA occurrences when imported should have building/days/dates
2226 
2227          IF (p_uso_rec.monday='N' AND  p_uso_rec.tuesday='N' AND
2228 	   p_uso_rec.wednesday='N' AND  p_uso_rec.thursday='N' AND
2229 	   p_uso_rec.friday='N' AND  p_uso_rec.saturday='N' AND
2230 	   p_uso_rec.sunday='N') OR  p_uso_rec.start_date IS NULL OR p_uso_rec.end_date IS NULL OR
2231 	   p_n_building_code IS NULL THEN
2232 
2233 	   IF l_cur_sch_int.tba_status='Y' THEN
2234 	     fnd_message.set_name ( 'IGS', 'IGS_PS_USO_TBA_STATUS' );
2235 	     fnd_msg_pub.add;
2236  	     p_uso_rec.status := 'E';
2237            ELSIF l_cur_sch_int.transaction_type IN ('REQUEST','UPDATE') THEN
2238 	     --For normal occurrences shoud have
2239              fnd_message.set_name ( 'IGS', 'IGS_PS_VALUES_NULL' );
2240              fnd_msg_pub.add;
2241  	     p_uso_rec.status := 'E';
2242            END IF;
2243 	 END IF;
2244 
2245 	 IF l_cur_sch_int.transaction_type = 'CANCEL' THEN
2246            p_schedule_status := 'CANCELLED' ;
2247 	 END IF;
2248 
2249          --if the record exists in the interface table and TRANSACTION_TYPE as either 'REQUEST' / 'UPDATE' then BUILDING_CODE is must
2250 	 IF l_cur_sch_int.transaction_type IN ('REQUEST','UPDATE')  AND p_n_building_code IS NULL THEN
2251 	    fnd_message.set_name ( 'IGS', 'IGS_PS_SCH_BLDIS_MUST' );
2252 	    fnd_msg_pub.add;
2253 	    p_uso_rec.status := 'E';
2254          END IF;
2255          --if the record exists in the interface table and TRANSACTION_TYPE = 'CANCEL' then BUILDING_CODE must be NULL
2256 	 IF l_cur_sch_int.transaction_type IN ('CANCEL')  AND p_n_building_code IS NOT NULL THEN
2257 	    fnd_message.set_name ( 'IGS', 'IGS_PS_SCH_BLDIS_NOT' );
2258 	    fnd_msg_pub.add;
2259 	    p_uso_rec.status := 'E';
2260          END IF;
2261 
2262          --Update the interface record transaction type and schedule status
2263 	 IF p_uso_rec.status = 'S' THEN
2264             UPDATE igs_ps_sch_int_all set transaction_type='COMPLETE',schedule_status=NVL(p_schedule_status,schedule_status),import_done_flag='Y' WHERE int_occurs_id = l_cur_sch_int.int_occurs_id;
2265             UPDATE igs_ps_sch_usec_int_all set import_done_flag='Y' WHERE int_usec_id = l_cur_sch_int.int_usec_id;
2266             UPDATE igs_ps_sch_pat_int set import_done_flag='Y' WHERE int_pat_id = l_cur_sch_int.int_pat_id;
2267 	 END IF;
2268 
2269        END IF;
2270        CLOSE cur_sch_int;
2271 
2272      ELSE
2273        --If the caling context is L/G then set the schedule_satus to USER_UPDATE if any of the column value is getting modified
2274        IF (l_cur_occur.monday <> p_uso_rec.monday OR
2275 	  l_cur_occur.tuesday <> p_uso_rec.tuesday OR
2276 	  l_cur_occur.wednesday <> p_uso_rec.wednesday OR
2277 	  l_cur_occur.thursday <> p_uso_rec.thursday OR
2278 	  l_cur_occur.friday <> p_uso_rec.friday OR
2279 	  l_cur_occur.saturday <> p_uso_rec.saturday OR
2280 	  l_cur_occur.sunday <> p_uso_rec.sunday OR
2281 	  NVL(l_cur_occur.building_code,-999) <> NVL(p_n_building_code,-999) OR
2282 	  NVL(l_cur_occur.room_code,-999) <> NVL(p_n_room_code,-999) OR
2283 	  NVL(l_cur_occur.start_date,TRUNC(SYSDATE)) <> NVL(p_uso_rec.start_date,TRUNC(SYSDATE)) OR
2284 	  NVL(l_cur_occur.end_date,TRUNC(SYSDATE)) <> NVL(p_uso_rec.end_date,TRUNC(SYSDATE)) OR
2285 	  NVL(l_cur_occur.start_time,TRUNC(SYSDATE)) <> NVL(p_uso_rec.start_time,TRUNC(SYSDATE)) OR
2286 	  NVL(l_cur_occur.end_time,TRUNC(SYSDATE)) <> NVL(p_uso_rec.end_time,TRUNC(SYSDATE))) AND
2287 	  p_uso_rec.no_set_day_ind = 'N' AND
2288 	  p_uso_rec.to_be_announced = 'N' AND
2289 	  l_cur_occur.schedule_status IS NOT NULL THEN
2290 
2291           p_schedule_status := 'USER_UPDATE';
2292        END IF;
2293 
2294      END IF;
2295 
2296 
2297      --If any of the days/time/scheduled building/schedule room is changed the set the notify_status to 'TRIGGER' and
2298      --insert/updatet the shadow table
2299 
2300      IF l_cur_occur.monday <> p_uso_rec.monday OR
2301 	l_cur_occur.tuesday <> p_uso_rec.tuesday OR
2302 	l_cur_occur.wednesday <> p_uso_rec.wednesday OR
2303 	l_cur_occur.thursday <> p_uso_rec.thursday OR
2304 	l_cur_occur.friday <> p_uso_rec.friday OR
2305 	l_cur_occur.saturday <> p_uso_rec.saturday OR
2306 	l_cur_occur.sunday <> p_uso_rec.sunday OR
2307 	NVL(l_cur_occur.building_code,-999) <> NVL(p_n_building_code,-999) OR
2308 	NVL(l_cur_occur.room_code,-999) <> NVL(p_n_room_code,-999) OR
2309 	NVL(l_cur_occur.start_time,TRUNC(SYSDATE)) <> NVL(p_uso_rec.start_time,TRUNC(SYSDATE)) OR
2310 	NVL(l_cur_occur.end_time,TRUNC(SYSDATE)) <> NVL(p_uso_rec.end_time,TRUNC(SYSDATE)) THEN
2311 
2312 	p_notify_status:='TRIGGER';
2313 
2314 	OPEN c_shadow_num(p_n_uso_id);
2315         FETCH c_shadow_num INTO l_shadow_num;
2316         IF c_shadow_num%NOTFOUND THEN
2317   	  l_shadow_num :=0;
2318         END IF;
2319         CLOSE c_shadow_num;
2320 
2321 	l_old_monday := l_cur_occur.monday;
2322 	l_old_tuesday := l_cur_occur.tuesday;
2323 	l_old_wednesday := l_cur_occur.wednesday;
2324 	l_old_thursday := l_cur_occur.thursday;
2325 	l_old_friday := l_cur_occur.friday;
2326 	l_old_saturday := l_cur_occur.saturday;
2327 	l_old_sunday := l_cur_occur.sunday;
2328 	l_old_start_time := l_cur_occur.start_time;
2329 	l_old_end_time := l_cur_occur.end_time;
2330 	l_old_building_code := l_cur_occur.building_code;
2331 	l_old_room_code := l_cur_occur.room_code;
2332 
2333 
2334         IF l_shadow_num <1 THEN
2335 
2336 	  IF NVL(l_old_monday,'X') <> NVL(p_uso_rec.monday,'X') THEN
2337 	    l_new_monday:= l_old_monday;
2338 	  ELSE
2339 	    l_new_monday:=NULL;
2340 	  END IF;
2341 	  IF NVL(l_old_tuesday,'X') <> NVL(p_uso_rec.tuesday,'X') THEN
2342 	    l_new_tuesday:= l_old_tuesday;
2343 	  ELSE
2344 	    l_new_tuesday:=NULL;
2345 	  END IF;
2346 	  IF NVL(l_old_wednesday,'X') <> NVL(p_uso_rec.wednesday,'X') THEN
2347 	    l_new_wednesday:= l_old_wednesday;
2348 	  ELSE
2349 	    l_new_wednesday:=NULL;
2350 	  END IF;
2351 	  IF NVL(l_old_thursday,'X') <> NVL(p_uso_rec.thursday,'X') THEN
2352 	    l_new_thursday:= l_old_thursday;
2353 	  ELSE
2354 	    l_new_thursday:=NULL;
2355 	  END IF;
2356 	  IF NVL(l_old_friday,'X') <> NVL(p_uso_rec.friday,'X') THEN
2357 	    l_new_friday:= l_old_friday;
2358 	  ELSE
2359 	    l_new_friday := NULL;
2360 	  END IF;
2361 	  IF NVL(l_old_saturday,'X') <> NVL(p_uso_rec.saturday,'X') THEN
2362 	    l_new_saturday:= l_old_saturday;
2363 	  ELSE
2364 	    l_new_saturday := NULL;
2365 	  END IF;
2366 	  IF NVL(l_old_sunday,'X') <> NVL(p_uso_rec.sunday,'X') THEN
2367 	    l_new_sunday:= l_old_sunday;
2368 	  ELSE
2369 	    l_new_sunday := NULL;
2370 	  END IF;
2371 	  IF NVL(l_old_start_time,'X') <> NVL(TO_CHAR(p_uso_rec.Start_Time,'DD-MON-YYYY HH24:MI:SS'),'X') THEN
2372 	    l_new_start_time:= l_old_start_time;
2373 	  ELSE
2374 	    l_new_start_time := NULL;
2375 	  END IF;
2376 	  IF NVL(l_old_end_time,'X') <> NVL(TO_CHAR(p_uso_rec.End_Time,'DD-MON-YYYY HH24:MI:SS'),'X')  THEN
2377 	    l_new_end_time:= l_old_end_time;
2378 	  ELSE
2379 	    l_new_end_time := NULL;
2380 	  END IF;
2381 	  IF NVL(l_old_building_code,'X') <> NVL(p_uso_rec.building_code,'X') THEN
2382 	    l_new_building_code:= l_old_building_code;
2383 	  ELSE
2384 	    l_new_building_code := NULL;
2385 	  END IF;
2386 	  IF NVL(l_old_room_code,'X') <> NVL(p_uso_rec.room_code,'X') THEN
2387 	    l_new_room_code:= l_old_room_code;
2388 	  ELSE
2389 	    l_new_room_code := NULL;
2390 	  END IF;
2391 
2392 	  l_new_instructor_id := NULL;
2393 
2394 
2395 	  SELECT  IGS_PS_SH_USEC_OCCURS_S.NEXTVAL INTO l_new_usecsh_id FROM dual;
2396 	  l_new_unit_section_occur_id :=p_n_uso_id;
2397 	  INSERT INTO IGS_PS_SH_USEC_OCCURS(USECSH_ID,
2398 		  UNIT_SECTION_OCCURRENCE_ID,
2399 		  MONDAY,
2400 		  TUESDAY,
2401 		  WEDNESDAY,
2402 		  THURSDAY,
2403 		  FRIDAY,
2404 		  SATURDAY,
2405 		  SUNDAY,
2406 		  ROOM_CODE,
2407 		  BUILDING_CODE,
2408 		  START_TIME,
2409 		  END_TIME,
2410 		  INSTRUCTOR_ID,
2411 		  CREATED_BY,
2412 		  CREATION_DATE,
2413 		  LAST_UPDATED_BY,
2414 		  LAST_UPDATE_DATE,
2415 		  LAST_UPDATE_LOGIN  )
2416 	  VALUES (
2417 		  l_new_USECSH_ID,
2418 		  l_new_unit_section_occur_id,
2419 		  l_new_MONDAY,
2420 		  l_new_TUESDAY,
2421 		  l_new_WEDNESDAY,
2422 		  l_new_THURSDAY,
2423 		  l_new_FRIDAY,
2424 		  l_new_SATURDAY,
2425 		  l_new_SUNDAY,
2426 		  to_number(l_new_ROOM_CODE),
2427 		  to_number(l_new_BUILDING_CODE),
2428 		  fnd_date.canonical_to_date(fnd_date.string_to_canonical(l_new_START_TIME,'DD-MON-YYYY HH24:MI:SS')),
2429 		  fnd_date.canonical_to_date(fnd_date.string_to_canonical(l_new_END_TIME,'DD-MON-YYYY HH24:MI:SS')),
2430 		  l_new_INSTRUCTOR_ID,
2431 		  g_n_user_id,
2432 		  SYSDATE,
2433 		  g_n_user_id,
2434 		  SYSDATE,
2435 		  g_n_login_id);
2436 
2437 	ELSE
2438 
2439 	  OPEN c_shadow_rec(p_n_uso_id);
2440 	  FETCH c_shadow_rec INTO l_shd_monday, l_shd_tuesday, l_shd_wednesday, l_shd_thursday, l_shd_friday,
2441 			       l_shd_saturday,l_shd_sunday, l_shd_start_time, l_shd_end_time,
2442 			       l_shd_building_code, l_shd_room_code, l_shd_instructor_id;
2443 	  IF c_shadow_rec%NOTFOUND THEN
2444 	    l_shd_monday := NULL;
2445 	    l_shd_tuesday := NULL;
2446 	    l_shd_wednesday := NULL;
2447 	    l_shd_thursday := NULL;
2448 	    l_shd_friday := NULL;
2449 	    l_shd_saturday := NULL;
2450 	    l_shd_sunday := NULL;
2451 	    l_shd_start_time := NULL;
2452 	    l_shd_end_time := NULL;
2453 	    l_shd_building_code := NULL;
2454 	    l_shd_room_code := NULL;
2455 	    l_shd_instructor_id := NULL;
2456 	  END IF;
2457 
2458 	  IF NVL(l_old_monday,'X') <> NVL(p_uso_rec.monday,'X') AND l_shd_monday IS NULL THEN
2459 	    l_new_monday := l_old_monday;
2460 	  ELSIF NVL(l_old_monday,'X') <> NVL(p_uso_rec.monday,'X') AND l_shd_monday IS NOT NULL THEN
2461 	    l_new_monday := l_shd_monday;
2462 	  ELSIF NVL(l_old_monday,'X') = NVL(p_uso_rec.monday,'X') THEN
2463 	    l_new_monday := l_shd_monday;
2464 	  END IF;
2465 
2466 	  IF NVL(l_old_tuesday,'X') <> NVL(p_uso_rec.tuesday,'X') AND l_shd_tuesday IS NULL THEN
2467 	    l_new_tuesday := l_old_tuesday;
2468 	  ELSIF NVL(l_old_tuesday,'X') <> NVL(p_uso_rec.tuesday,'X') AND l_shd_tuesday IS NOT NULL THEN
2469 	    l_new_tuesday := l_shd_tuesday;
2470 	  ELSIF NVL(l_old_tuesday,'X') = NVL(p_uso_rec.tuesday,'X') THEN
2471 	    l_new_tuesday := l_shd_tuesday;
2472 	  END IF;
2473 
2474 	  IF NVL(l_old_wednesday,'X') <> NVL(p_uso_rec.wednesday,'X') AND l_shd_wednesday IS NULL THEN
2475 	    l_new_wednesday := l_old_wednesday;
2476 	  ELSIF NVL(l_old_wednesday,'X') <> NVL(p_uso_rec.wednesday,'X') AND l_shd_wednesday IS NOT NULL THEN
2477 	    l_new_wednesday := l_shd_wednesday;
2478 	  ELSIF NVL(l_old_wednesday,'X') = NVL(p_uso_rec.wednesday,'X') THEN
2479 	    l_new_wednesday := l_shd_wednesday;
2480 	  END IF;
2481 
2482 	  IF NVL(l_old_thursday,'X') <> NVL(p_uso_rec.thursday,'X') AND l_shd_thursday IS NULL THEN
2483 	    l_new_thursday := l_old_thursday;
2484 	  ELSIF NVL(l_old_thursday,'X') <> NVL(p_uso_rec.thursday,'X') AND l_shd_thursday IS NOT NULL THEN
2485 	    l_new_thursday := l_shd_thursday;
2486 	  ELSIF NVL(l_old_thursday,'X') = NVL(p_uso_rec.thursday,'X') THEN
2487 	    l_new_thursday := l_shd_thursday;
2488 	  END IF;
2489 
2490 	  IF NVL(l_old_friday,'X') <> NVL(p_uso_rec.friday,'X') AND l_shd_friday IS NULL THEN
2491 	    l_new_friday := l_old_friday;
2492 	  ELSIF NVL(l_old_friday,'X') <> NVL(p_uso_rec.friday,'X') AND l_shd_friday IS NOT NULL THEN
2493 	    l_new_friday := l_shd_friday;
2494 	  ELSIF NVL(l_old_friday,'X') = NVL(p_uso_rec.friday,'X') THEN
2495 	    l_new_friday := l_shd_friday;
2496 	  END IF;
2497 
2498 	  IF NVL(l_old_saturday,'X') <> NVL(p_uso_rec.saturday,'X') AND l_shd_saturday IS NULL THEN
2499 	    l_new_saturday := l_old_saturday;
2500 	  ELSIF NVL(l_old_saturday,'X') <> NVL(p_uso_rec.saturday,'X') AND l_shd_saturday IS NOT NULL THEN
2501 	    l_new_saturday := l_shd_saturday;
2502 	  ELSIF NVL(l_old_saturday,'X') = NVL(p_uso_rec.saturday,'X') THEN
2503 	    l_new_saturday := l_shd_saturday;
2504 	  END IF;
2505 
2506 	  IF NVL(l_old_sunday,'X') <> NVL(p_uso_rec.sunday,'X') AND l_shd_sunday IS NULL THEN
2507 	    l_new_sunday := l_old_sunday;
2508 	  ELSIF NVL(l_old_sunday,'X') <> NVL(p_uso_rec.sunday,'X') AND l_shd_sunday IS NOT NULL THEN
2509 	    l_new_sunday := l_shd_sunday;
2510 	  ELSIF NVL(l_old_sunday,'X') = NVL(p_uso_rec.sunday,'X') THEN
2511 	    l_new_sunday := l_shd_sunday;
2512 	  END IF;
2513 
2514 	  IF NVL(l_old_start_time,'X') <> NVL(TO_CHAR(p_uso_rec.Start_Time,'DD-MON-YYYY HH24:MI:SS'),'X') AND l_shd_start_time IS NULL THEN
2515 	    l_new_start_time := l_old_start_time;
2516 	  ELSIF NVL(l_old_start_time,'X') <> NVL(TO_CHAR(p_uso_rec.Start_Time,'DD-MON-YYYY HH24:MI:SS'),'X') AND l_shd_start_time IS NOT NULL THEN
2517 	    l_new_start_time := l_shd_start_time;
2518 	  ELSIF NVL(l_old_start_time,'X') = NVL(TO_CHAR(p_uso_rec.Start_Time,'DD-MON-YYYY HH24:MI:SS'),'X') THEN
2519 	    l_new_start_time := l_shd_start_time;
2520 	  END IF;
2521 
2522 	  IF NVL(l_old_end_time,'X') <> NVL(TO_CHAR(p_uso_rec.end_Time,'DD-MON-YYYY HH24:MI:SS'),'X') AND l_shd_end_time IS NULL THEN
2523 	    l_new_end_time := l_old_end_time;
2524 	  ELSIF NVL(l_old_end_time,'X') <> NVL(TO_CHAR(p_uso_rec.end_Time,'DD-MON-YYYY HH24:MI:SS'),'X') AND l_shd_end_time IS NOT NULL THEN
2525 	    l_new_end_time := l_shd_end_time;
2526 	  ELSIF NVL(l_old_end_time,'X') = NVL(TO_CHAR(p_uso_rec.end_Time,'DD-MON-YYYY HH24:MI:SS'),'X') THEN
2527 	    l_new_end_time := l_shd_end_time;
2528 	  END IF;
2529 
2530 	  IF NVL(l_old_building_code,'X') <> NVL(p_uso_rec.building_code,'X') AND l_shd_building_code IS NULL THEN
2531 	    l_new_building_code := l_old_building_code;
2532 	  ELSIF NVL(l_old_building_code,'X') <> NVL(p_uso_rec.building_code,'X') AND l_shd_building_code IS NOT NULL THEN
2533 	    l_new_building_code := l_shd_building_code;
2534 	  ELSIF NVL(l_old_building_code,'X') = NVL(p_uso_rec.building_code,'X') THEN
2535 	    l_new_building_code := l_shd_building_code;
2536 	  END IF;
2537 
2538 	  IF NVL(l_old_room_code,'X') <> NVL(p_uso_rec.room_code,'X') AND l_shd_room_code IS NULL THEN
2539 	    l_new_room_code := l_old_room_code;
2540 	  ELSIF NVL(l_old_room_code,'X') <> NVL(p_uso_rec.room_code,'X') AND l_shd_room_code IS NOT NULL THEN
2541 	    l_new_room_code := l_shd_room_code;
2542 	  ELSIF NVL(l_old_room_code,'X') = NVL(p_uso_rec.room_code,'X') THEN
2543 	    l_new_room_code := l_shd_room_code;
2544 	  END IF;
2545 
2546 	  OPEN c_insv_unit_sec_occur_id(p_n_uso_id);
2547 	  FETCH c_insv_unit_sec_occur_id INTO  l_insv_instructor_id;
2548 	  IF c_insv_unit_sec_occur_id%NOTFOUND THEN
2549 	    NULL;
2550 	  END IF;
2551 
2552 	  l_new_instructor_id := l_insv_instructor_id;
2553 
2554 	  IF  NVL(l_shd_monday,'X') <>  NVL(l_new_monday,'X') OR
2555 	      NVL(l_shd_tuesday,'X') <> NVL(l_new_tuesday,'X') OR
2556 	      NVL(l_shd_wednesday,'X') <> NVL(l_new_wednesday,'X') OR
2557 	      NVL(l_shd_thursday,'X')  <> NVL(l_new_thursday,'X') OR
2558 	      NVL(l_shd_friday,'X')  <> NVL(l_new_friday,'X') OR
2559 	      NVL(l_shd_saturday,'X')  <> NVL(l_new_saturday,'X') OR
2560 	      NVL(l_shd_sunday ,'X') <> NVL(l_new_sunday,'X') OR
2561 	      NVL(l_shd_start_time ,'X')<> NVL(l_new_start_time,'X') OR
2562 	      NVL(l_shd_end_time,'X')<> NVL(l_new_end_time,'X') OR
2563 	      NVL(l_shd_building_code ,'X')<> NVL(l_new_building_code,'X') OR
2564 	      NVL(l_shd_room_code,'X')  <> NVL(l_new_room_code,'X') OR
2565 	      NVL(l_shd_instructor_id ,'X')<> NVL(l_new_instructor_id,'X') THEN
2566 
2567 
2568 	    UPDATE IGS_PS_SH_USEC_OCCURS SET
2569 		 monday           = l_new_monday,
2570 		 tuesday          = l_new_tuesday,
2571 		 wednesday        = l_new_wednesday,
2572 		 thursday         = l_new_thursday,
2573 		 friday           = l_new_friday,
2574 		 saturday         = l_new_saturday,
2575 		 sunday           = l_new_sunday,
2576 		 start_time       = fnd_date.canonical_to_date(fnd_date.string_to_canonical(l_new_START_TIME,'DD-MON-YYYY HH24:MI:SS')),
2577 		 end_time         = fnd_date.canonical_to_date(fnd_date.string_to_canonical(l_new_END_TIME,'DD-MON-YYYY HH24:MI:SS')),
2578 		 room_code        = to_number(l_new_room_code),
2579 		 building_code    = to_number(l_new_building_code),
2580 		 instructor_id    = l_new_instructor_id,
2581 		 last_updated_by  = g_n_user_id,
2582 		 last_update_date = SYSDATE
2583 	    WHERE  unit_section_occurrence_id = p_n_uso_id;
2584 
2585 	  END IF;
2586 	  CLOSE c_shadow_rec;
2587         END IF;
2588       END IF;
2589 
2590     ELSE --insert
2591       IF   p_calling_context = 'S' THEN
2592 
2593 	OPEN cur_int_usec(p_n_uoo_id);
2594 	FETCH cur_int_usec INTO l_cur_int_usec;
2595 	IF cur_int_usec%FOUND THEN
2596           UPDATE igs_ps_sch_usec_int_all set import_done_flag='Y' WHERE int_usec_id = l_cur_int_usec.int_usec_id;
2597           UPDATE igs_ps_sch_pat_int set import_done_flag='Y' WHERE int_pat_id = l_cur_int_usec.int_pat_id;
2598         END IF;
2599         CLOSE cur_int_usec;
2600 
2601       END IF;
2602 
2603     END IF; --insert/update
2604 
2605 --
2606 
2607   END validate_usec_occurs;
2608 
2609   PROCEDURE set_msg(p_c_msg_name IN VARCHAR2,
2610                     p_c_token IN VARCHAR2,
2611                     p_c_lkup_type IN VARCHAR2,
2612                     p_b_delete_flag IN BOOLEAN
2613                     )AS
2614   /***********************************************************************************************
2615     Created By     :  smvk
2616     Date Created By:  18-NOV-2002
2617     Purpose        :  This procedure sets the particular message in the  message stack.
2618                       Based upon the input arguments this procedure does the following functions
2619                       -- if the p_c_msg_name is null then returns immediately
2620                       -- if p_c_token and p_c_lkup_type
2621                       -- if the p_b_delete_flag is true then it deletes last message in the message stack.
2622                       -- if the
2623                       -- if p_c_token and p_c_lkup_type are not null then
2624                       it returns null for invalid lookup_code or/and lookup_type.
2625 
2626     Known limitations,enhancements,remarks:
2627     Change History (in reverse chronological order)
2628     Who         When            What
2629   ********************************************************************************************** */
2630 
2631   l_n_count NUMBER;
2632   l_c_meaning igs_lookups_view.meaning%TYPE;
2633 
2634   BEGIN
2635   l_c_meaning := null;
2636     -- If the message name is null, then return false
2637     IF p_c_msg_name IS NULL THEN
2638       RETURN;
2639     END IF;
2640 
2641     IF p_c_lkup_type IS NOT NULL THEN
2642       IF p_c_token IS NULL  THEN
2643         RETURN;
2644       ELSE
2645         l_c_meaning := get_lkup_meaning(p_c_token,p_c_lkup_type);
2646       END IF;
2647     END IF;
2648 
2649     IF p_b_delete_flag THEN
2650       l_n_count:= FND_MSG_PUB.COUNT_MSG;
2651       -- Delete the message 'IGS_GE_INVALID_VALUE'
2652       IF l_n_count > 0 THEN
2653         FND_MSG_PUB.DELETE_MSG(l_n_count);
2654       END IF;
2655     END IF;
2656 
2657     FND_MESSAGE.SET_NAME('IGS',p_c_msg_name);
2658       IF p_c_token IS NOT NULL THEN
2659         IF l_c_meaning IS NOT NULL THEN
2660           FND_MESSAGE.SET_TOKEN('PARAM',l_c_meaning);
2661         ELSE
2662           FND_MESSAGE.SET_TOKEN('PARAM',p_c_token);
2663         END IF;
2664       END IF;
2665     FND_MSG_PUB.ADD;
2666 
2667   END set_msg;
2668 
2669   FUNCTION get_lkup_meaning(p_c_lkup_cd IN VARCHAR2,
2670                             p_c_lkup_type IN VARCHAR2
2671                            ) RETURN VARCHAR2 AS
2672   /***********************************************************************************************
2673     Created By     :  smvk
2674     Date Created By:  18-NOV-2002
2675     Purpose        :  This function returns the meaning for the given lookup_code and lookup_type.
2676                       it returns null for invalid lookup_code or/and lookup_type.
2677 
2678     Known limitations,enhancements,remarks:
2679     Change History (in reverse chronological order)
2680     Who         When            What
2681   ********************************************************************************************** */
2682 
2683     CURSOR c_meaning (cp_c_lkup_cd IN igs_lookups_view.lookup_code%TYPE,
2684                       cp_c_lkup_type IN igs_lookups_view.lookup_type%TYPE) IS
2685       SELECT  A.meaning
2686         FROM  igs_lookups_view A
2687         WHERE A.lookup_code  = cp_c_lkup_cd
2688         AND   A.lookup_type  = cp_c_lkup_type
2689         AND   A.enabled_flag = 'Y'
2690         AND   TRUNC(SYSDATE) BETWEEN NVL(A.start_date_active,TRUNC(SYSDATE))
2691         AND   NVL(A.end_date_active,TRUNC(SYSDATE)) ;
2692 
2693     l_c_meaning igs_lookups_view.meaning%TYPE;
2694 
2695   BEGIN
2696     OPEN c_meaning(p_c_lkup_cd,p_c_lkup_type);
2697     FETCH c_meaning INTO l_c_meaning;
2698     CLOSE c_meaning;
2699     return l_c_meaning;
2700   END get_lkup_meaning;
2701 
2702   PROCEDURE get_uoo_id( p_unit_cd IN VARCHAR2,
2703                         p_ver_num IN NUMBER,
2704                         p_cal_type IN VARCHAR2,
2705                         p_seq_num IN NUMBER,
2706                         p_loc_cd IN VARCHAR2,
2707                         p_unit_class IN VARCHAR2,
2708                         p_uoo_id OUT NOCOPY NUMBER,
2709                         p_message OUT NOCOPY VARCHAR2
2710                       )AS
2711     CURSOR c_uoo_id (cp_unit_cd IN igs_ps_unit_ofr_opt_all.unit_cd%TYPE,
2712                      cp_ver_num IN igs_ps_unit_ofr_opt_all.version_number%TYPE,
2713                      cp_cal_type IN igs_ps_unit_ofr_opt_all.cal_type%TYPE,
2714                      cp_seq_num IN igs_ps_unit_ofr_opt_all.ci_sequence_number%TYPE,
2715                      cp_loc_cd IN igs_ps_unit_ofr_opt_all.location_cd%TYPE,
2716                      cp_unit_class IN igs_ps_unit_ofr_opt_all.unit_class%TYPE ) IS
2717       SELECT   uoo_id
2718         FROM   igs_ps_unit_ofr_opt_all
2719         WHERE  UNIT_CD = cp_unit_cd
2720            AND version_number = cp_ver_num
2721            AND cal_type = cp_cal_type
2722            AND ci_sequence_number = cp_seq_num
2723            AND location_cd = cp_loc_cd
2724            AND unit_class = cp_unit_class;
2725 
2726   BEGIN
2727     OPEN c_uoo_id( p_unit_cd, p_ver_num, p_cal_type, p_seq_num, p_loc_cd, p_unit_class);
2728     FETCH c_uoo_id INTO p_uoo_id;
2729     IF c_uoo_id%NOTFOUND THEN
2730       p_message := 'IGS_PS_LGCY_REC_NOT_EXISTS';
2731     END IF;
2732     CLOSE c_uoo_id;
2733   END get_uoo_id;
2734 
2735   FUNCTION validate_waitlist_allowed ( p_c_cal_type IN igs_ca_type.cal_type%TYPE,
2736                                        p_n_seq_num  IN igs_ca_inst_all.sequence_number%TYPE ) RETURN BOOLEAN
2737   AS
2738   /***********************************************************************************************
2739     Created By     :  shtatiko
2740     Date Created By:  21-NOV-2002
2741     Purpose        :  This function will check whether waitlisting is allowed for the given teaching calendar.
2742                       Returns TRUE if allowed and FALSE if not.
2743 
2744     Known limitations,enhancements,remarks:
2745     Change History (in reverse chronological order)
2746     Who         When            What
2747     smvk       10-Oct-2003      Bug # 3052445. Modified the procedure.
2748   ********************************************************************************************** */
2749   CURSOR c_waitlist_allowed ( cp_c_cal_type igs_ca_type.cal_type%TYPE,
2750                               cp_n_seq_num  igs_ca_inst_all.sequence_number%TYPE ) IS
2751   SELECT inst.waitlist_alwd
2752   FROM igs_en_inst_wlst_opt inst,
2753        igs_ca_load_to_teach_v lot
2754   WHERE
2755     inst.cal_type = lot.load_cal_type AND
2756     lot.teach_cal_type = cp_c_cal_type AND
2757     lot.teach_ci_sequence_number = cp_n_seq_num;
2758 
2759   rec_waitlist_allowed c_waitlist_allowed%ROWTYPE;
2760   l_b_wlst_allowed  BOOLEAN := FALSE;
2761 
2762   BEGIN
2763   IF is_waitlist_allowed THEN
2764      l_b_wlst_allowed := TRUE;
2765      FOR rec_waitlist_allowed IN c_waitlist_allowed(p_c_cal_type, p_n_seq_num)
2766      LOOP
2767        IF rec_waitlist_allowed.waitlist_alwd = 'Y' THEN
2768           l_b_wlst_allowed := TRUE;
2769           EXIT;
2770        ELSE
2771           l_b_wlst_allowed := FALSE;
2772        END IF;
2773     END LOOP;
2774   END IF;
2775   RETURN l_b_wlst_allowed;
2776 
2777   END validate_waitlist_allowed;
2778 
2779   FUNCTION validate_gs_type ( p_c_gs_cd IN VARCHAR2, p_n_gs_ver IN NUMBER, p_c_gs_type IN VARCHAR2) RETURN BOOLEAN
2780   AS
2781   /***********************************************************************************************
2782     Created By     :  shtatiko
2783     Date Created By:  18-NOV-2002
2784     Purpose        :  This function is to check whether the grading schema code and version number are of
2785                       particular grading schema type.
2786                       This function will returns TRUE if the passed grading schema is of 'UNIT' type and
2787                       returns FALSE, if not.
2788 
2789     Known limitations,enhancements,remarks:
2790     Change History (in reverse chronological order)
2791     Who         When            What
2792   ********************************************************************************************** */
2793   CURSOR c_gs_exists ( cp_gs_cd igs_ps_unit_grd_schm.grading_schema_code%TYPE,
2794                          cp_gs_ver igs_ps_unit_grd_schm.grd_schm_version_number%TYPE,
2795                          cp_gs_type igs_as_grd_schema.grading_schema_type%TYPE ) IS
2796   SELECT 1
2797   FROM igs_as_grd_schema
2798   WHERE
2799     grading_schema_cd = cp_gs_cd AND
2800     version_number = cp_gs_ver AND
2801     grading_schema_type = cp_gs_type ;
2802   rec_gs_exists c_gs_exists%ROWTYPE;
2803 
2804   BEGIN
2805     OPEN c_gs_exists ( p_c_gs_cd, p_n_gs_ver, p_c_gs_type );
2806     FETCH c_gs_exists INTO rec_gs_exists;
2807     IF ( c_gs_exists%FOUND ) THEN
2808       CLOSE c_gs_exists;
2809       RETURN TRUE;
2810     ELSE
2811       CLOSE c_gs_exists;
2812       RETURN FALSE;
2813     END IF;
2814   END validate_gs_type;
2815 
2816   FUNCTION validate_cal_cat ( p_c_cal_type IN igs_ca_inst_all.cal_type%TYPE,
2817                               p_c_cal_cat  IN igs_ca_type.s_cal_cat%TYPE) RETURN BOOLEAN
2818   AS
2819   /***********************************************************************************************
2820     Created By     :  shtatiko
2821     Date Created By:  21-NOV-2002
2822     Purpose        :  This function will returns true if the passed calendar type's category is matches
2823                       with passed category and false, otherwise.
2824 
2825     Known limitations,enhancements,remarks:
2826     Change History (in reverse chronological order)
2827     Who         When            What
2828   ********************************************************************************************** */
2829   CURSOR c_cal ( cp_cal_type igs_ca_inst_all.cal_type%TYPE,
2830                  cp_cal_cat  igs_ca_type.s_cal_cat%TYPE ) IS
2831   SELECT 1
2832   FROM igs_ca_type
2833   WHERE
2834     s_cal_cat = cp_cal_cat AND
2835     cal_type  = cp_cal_type;
2836   rec_cal c_cal%ROWTYPE;
2837 
2838   BEGIN
2839 
2840     OPEN c_cal ( p_c_cal_type, p_c_cal_cat );
2841     FETCH c_cal INTO rec_cal;
2842     IF ( c_cal%NOTFOUND ) THEN
2843       CLOSE c_cal;
2844       RETURN FALSE;
2845     ELSE
2846       CLOSE c_cal;
2847       RETURN TRUE;
2848     END IF;
2849 
2850   END validate_cal_cat;
2851 
2852   -- Validate Orgaization Unit Code
2853   FUNCTION validate_org_unit_cd ( p_c_org_unit_cd IN igs_ps_unit_ver_all.owner_org_unit_cd%TYPE,
2854                                   p_c_object_name IN VARCHAR2 ) RETURN BOOLEAN
2855   AS
2856   /***********************************************************************************************
2857     Created By     :  shtatiko
2858     Date Created By:  22-NOV-2002
2859     Purpose        :  This function validates the Organization Unit Code and returns TRUE if Org
2860                       Unit Code is valid and retuns false, if not.
2861 
2862     Known limitations,enhancements,remarks:
2863     Change History (in reverse chronological order)
2864     Who         When            What
2865     sommukhe    15-FEB-2006        Bug#5040156, Changed call from GET_WHERE_CLAUSE to GET_WHERE_CLAUSE_FORM1 as a part of Literal fix
2866     jbegum      02-June-2003       Bug #2972950.
2867                                    For the Legacy Enhancements TD:
2868                                    As a part of Binding issues, using bind variable in the ref cursor.
2869   ********************************************************************************************** */
2870   TYPE c_ref_cur IS REF CURSOR;
2871   c_org_cur c_ref_cur;
2872   l_c_cur_stat VARCHAR2(2000);
2873   l_c_where_clause VARCHAR2(1000);
2874   l_n_rec_found NUMBER(1);
2875 
2876   BEGIN
2877 
2878     igs_or_gen_012_pkg.get_where_clause_api1( p_c_object_name, l_c_where_clause );
2879     IF l_c_where_clause IS NULL THEN
2880       l_c_cur_stat := 'SELECT 1 FROM igs_or_inst_org_base_v WHERE party_number = :p_c_org_unit_cd ';
2881       OPEN c_org_cur FOR l_c_cur_stat USING p_c_org_unit_cd;
2882     ELSE
2883       l_c_cur_stat := 'SELECT 1 FROM igs_or_inst_org_base_v WHERE party_number = :p_c_org_unit_cd  AND ' || l_c_where_clause;
2884       OPEN c_org_cur FOR l_c_cur_stat USING p_c_org_unit_cd,p_c_object_name;
2885    END IF;
2886     FETCH c_org_cur INTO l_n_rec_found;
2887     IF ( c_org_cur%FOUND ) THEN
2888       CLOSE c_org_cur;
2889       RETURN TRUE;
2890     ELSE
2891       CLOSE c_org_cur;
2892       RETURN FALSE;
2893     END IF;
2894 
2895   END validate_org_unit_cd;
2896 
2897   PROCEDURE get_party_id(p_c_person_number IN hz_parties.party_number%TYPE,
2898                          p_n_person_id OUT NOCOPY hz_parties.party_id%TYPE) AS
2899   /***********************************************************************************************
2900     Created By     :  smvk
2901     Date Created By:  26-DEC-2002
2902     Purpose        :  Gets the party identifier for the given party number for Active and Inactive records.
2903 
2904     Known limitations,enhancements,remarks:
2905     Change History (in reverse chronological order)
2906     Who         When            What
2907   ********************************************************************************************** */
2908     CURSOR c_party_id (cp_c_party_number IN hz_parties.party_number%type) IS
2909       SELECT hz.party_id
2910       FROM hz_parties hz
2911        WHERE hz.party_number = cp_c_party_number
2912        AND   hz.status in ('A','I');
2913 
2914   BEGIN
2915     OPEN c_party_id (p_c_person_number);
2916     FETCH c_party_id INTO p_n_person_id;
2917     CLOSE c_party_id;
2918   END get_party_id;
2919 
2920   -- Removed the function validate_staff_person
2921 
2922   PROCEDURE validate_enr_lmts( p_n_ern_min igs_ps_unit_ver_all.enrollment_minimum%TYPE,
2923                                p_n_enr_max igs_ps_unit_ver_all.enrollment_maximum%TYPE,
2924                                p_n_ovr_max igs_ps_unit_ver_all.override_enrollment_max%TYPE,
2925                                p_n_adv_max igs_ps_unit_ver_all.advance_maximum%TYPE,
2926                                p_c_rec_status IN OUT NOCOPY VARCHAR2) IS
2927   /***********************************************************************************************
2928     Created By     :  jbegum
2929     Date Created By:  02-June-2003
2930     Purpose        :  Bug # 2972950.
2931                       For the Legacy Enhancements TD:
2932                       This procedure does the business validation related to enrollment limits.
2933                       This procedure will be called from business validation part of importing unit and unit section.
2934                       As mentioned in TD.
2935 
2936     Known limitations,enhancements,remarks:
2937     Change History (in reverse chronological order)
2938     Who         When            What
2939   ********************************************************************************************** */
2940   BEGIN
2941 
2942      IF p_n_ern_min > p_n_enr_max THEN
2943         p_c_rec_status := 'E';
2944         fnd_message.set_name('IGS','IGS_PS_ENROLL_MIN_GREATER');
2945         fnd_msg_pub.add;
2946      END IF;
2947 
2948      IF p_n_enr_max > p_n_ovr_max THEN
2949         p_c_rec_status := 'E';
2950         fnd_message.set_name('IGS','IGS_PS_OVERIDE_MIN_MAX_CP');
2951         fnd_msg_pub.add;
2952      END IF;
2953 
2954      IF p_n_adv_max > p_n_enr_max THEN
2955         p_c_rec_status := 'E';
2956         fnd_message.set_name('IGS','IGS_PS_ADV_MAX_LESS_ENR_MAX');
2957         fnd_msg_pub.add;
2958      END IF;
2959 
2960   END validate_enr_lmts;
2961 
2962   PROCEDURE validate_usec_el(p_usec_rec IN OUT NOCOPY igs_ps_generic_pub.usec_rec_type,
2963                              p_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
2964 			     p_insert_update VARCHAR2) AS
2965 
2966   /***********************************************************************************************
2967     Created By     :  jbegum
2968     Date Created By:  02-June-2003
2969     Purpose        :  Bug # 2972950.
2970                       For the Legacy Enhancements TD:
2971                       This procedure does the business validation related to enrollment limits of unit section
2972                       As mentioned in TD.
2973 
2974     Known limitations,enhancements,remarks:
2975     Change History (in reverse chronological order)
2976     Who         When            What
2977     sommukhe    23-NOV-2005     BUG#4675113,include cursor c_usec_st, so that unit section is not updated to open on updating  Enrollment Maximum
2978                                 when unit is planned.
2979     sarakshi    12-Jul-2004     Bug#3729462, Added the predicate DELETE_FLAG in the cursor c_waitlist_allowed.
2980     smvk        25-Nov-2003     Bug # 2833971. Removed the validation associated with displaying error
2981                                 messages IGS_PS_WLST_MAX_LESS_THAN_ACT and IGS_PS_ENR_MAX_LESS_THAN_ACT.
2982   ********************************************************************************************** */
2983 
2984      CURSOR c_act (cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
2985      SELECT NVL(enrollment_actual, 0) enrollment_actual,
2986             NVL(auditable_ind,'N') auditable_ind,
2987 	    waitlist_actual
2988      FROM   igs_ps_unit_ofr_opt_all a
2989      WHERE  uoo_id = cp_n_uoo_id;
2990 
2991      CURSOR c_waitlist_allowed (cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
2992      SELECT waitlist_allowed
2993      FROM   igs_ps_unit_ofr_pat_all a,
2994             igs_ps_unit_ofr_opt_all b
2995      WHERE  b.uoo_id = cp_n_uoo_id
2996      AND    a.unit_cd = b.unit_cd
2997      AND    a.version_number = b.version_number
2998      AND    a.cal_type = b.cal_type
2999      AND    a.ci_sequence_number = b.ci_sequence_number
3000      AND    a.delete_flag='N';
3001 
3002      CURSOR c_usec_lim(cp_n_uoo_id NUMBER) IS
3003      SELECT *
3004      FROM igs_ps_usec_lim_wlst
3005      WHERE uoo_id = cp_n_uoo_id;
3006 
3007      c_usec_lim_rec c_usec_lim%ROWTYPE;
3008      rec_act  c_act%ROWTYPE;
3009      CURSOR cur_is_audited(cp_uoo_id igs_en_su_attempt.uoo_id%TYPE) IS
3010      SELECT count(*)
3011      FROM  igs_en_su_attempt
3012      WHERE uoo_id  =  cp_uoo_id
3013      AND   no_assessment_ind = 'Y';
3014 
3015      CURSOR cur_db_value(cp_uoo_id igs_ps_usec_lim_wlst.uoo_id%TYPE) IS
3016      SELECT max_auditors_allowed
3017      FROM   igs_ps_usec_lim_wlst
3018      WHERE  uoo_id = cp_uoo_id;
3019 
3020      CURSOR c_usec_wlst_pri(cp_n_uoo_id NUMBER) IS
3021      SELECT 'X' FROM  igs_ps_usec_wlst_pri
3022      WHERE uoo_id = cp_n_uoo_id;
3023 
3024      c_usec_wlst_pri_rec c_usec_wlst_pri%ROWTYPE;
3025 
3026      CURSOR c_usec_st(cp_unit_cd        igs_ps_unit_ver_all.unit_cd%TYPE,
3027                     cp_version_number igs_ps_unit_ver_all.version_number%TYPE) IS
3028      SELECT b.s_unit_status unit_status
3029      FROM igs_ps_unit_ver_all a,igs_ps_unit_stat b
3030      WHERE a.UNIT_STATUS=b.UNIT_STATUS
3031      AND   a.unit_cd=cp_unit_cd
3032      AND   a.version_number=cp_version_number;
3033      c_usec_st_rec c_usec_st%ROWTYPE;
3034 
3035      l_max_auditors_allowed  igs_ps_usec_lim_wlst.max_auditors_allowed%TYPE;
3036      l_ctx_value igs_ps_usec_lim_wlst.max_auditors_allowed%TYPE := p_usec_rec.max_auditors_allowed;
3037      l_count  NUMBER;
3038      l_c_waitlist_allowed  igs_ps_unit_ofr_pat_all.waitlist_allowed%TYPE;
3039      l_message_name VARCHAR2(30);
3040 
3041      l_n_enr_max IGS_PS_USEC_LIM_WLST.ENROLLMENT_MAXIMUM%TYPE;
3042      l_n_wlst_max IGS_PS_USEC_LIM_WLST.MAX_STUDENTS_PER_WAITLIST%TYPE;
3043      l_c_wlst_allowed IGS_PS_USEC_LIM_WLST.WAITLIST_ALLOWED%TYPE;
3044      l_n_enr_act IGS_PS_UNIT_OFR_OPT_ALL.ENROLLMENT_ACTUAL%TYPE;
3045      l_n_wlst_act  IGS_PS_UNIT_OFR_OPT_ALL.WAITLIST_ACTUAL%TYPE;
3046      l_c_usec_status IGS_PS_UNIT_OFR_OPT_ALL.UNIT_SECTION_STATUS%TYPE := NULL;
3047      l_request_id   NUMBER;
3048 
3049   BEGIN
3050 
3051      OPEN c_act(p_n_uoo_id);
3052      FETCH c_act INTO rec_act;
3053      CLOSE c_act;
3054      IF p_usec_rec.usec_waitlist_allowed = 'Y' THEN
3055         OPEN  c_waitlist_allowed (p_n_uoo_id);
3056         FETCH c_waitlist_allowed INTO l_c_waitlist_allowed;
3057         CLOSE c_waitlist_allowed;
3058         IF l_c_waitlist_allowed = 'N' THEN
3059            p_usec_rec.status := 'E';
3060            fnd_message.set_name ('IGS', 'IGS_PS_WLST_ALWD_NO_ORG');
3061            fnd_msg_pub.add;
3062         END IF;
3063      ELSE
3064         p_usec_rec.usec_max_students_per_waitlist := 0;
3065      END IF;
3066 
3067      IF NVL(p_usec_rec.override_enrollment_maximum,999999) < rec_act.enrollment_actual THEN
3068         p_usec_rec.status := 'E';
3069         fnd_message.set_name ('IGS', 'IGS_PS_OVRENR_MAX_LESS_ACTMAX');
3070         fnd_msg_pub.add;
3071      END IF;
3072 
3073      IF rec_act.auditable_ind = 'N' and p_usec_rec.max_auditors_allowed IS NOT NULL THEN
3074         p_usec_rec.status := 'E';
3075         fnd_message.set_name ('IGS', 'IGS_PS_MAX_AUD_MUST_BE_NULL');
3076         fnd_msg_pub.add;
3077      END IF;
3078 
3079      IF p_usec_rec.enrollment_maximum IS NULL AND
3080         p_usec_rec.override_enrollment_maximum IS NOT NULL THEN
3081         p_usec_rec.status := 'E';
3082         fnd_message.set_name ('IGS', 'IGS_PS_ENR_NULL_OVR_NOT');
3083         fnd_msg_pub.add;
3084      END IF;
3085 
3086      validate_enr_lmts (p_usec_rec.enrollment_minimum, p_usec_rec.enrollment_maximum, p_usec_rec.override_enrollment_maximum, p_usec_rec.advance_maximum, p_usec_rec.status);
3087 
3088     IF p_insert_update = 'U' THEN
3089 
3090       OPEN c_usec_lim(p_n_uoo_id);
3091       FETCH c_usec_lim INTO c_usec_lim_rec;
3092       CLOSE c_usec_lim;
3093 
3094       --Before updating check the scheduling status is processing or not
3095       IF IGS_PS_USEC_SCHEDULE.PRGP_GET_SCHD_STATUS( p_n_uoo_id,
3096 						    NULL,
3097 						    l_message_name ) = TRUE THEN
3098 	IF l_message_name IS NULL THEN
3099 	   l_message_name := 'IGS_PS_SCST_PROC';
3100 	END IF;
3101 	fnd_message.set_name( 'IGS', l_message_name);
3102 	p_usec_rec.status := 'E';
3103 	fnd_msg_pub.add;
3104       END IF;
3105 
3106       OPEN cur_db_value(p_n_uoo_id);
3107       FETCH cur_db_value INTO l_max_auditors_allowed;
3108       CLOSE cur_db_value;
3109       --If user tries to clear/lower Maximum Auditors Allowed field,than which is saved in database...
3110       IF ( (l_ctx_value IS NULL AND l_max_auditors_allowed IS NOT NULL) OR
3111 	   (l_max_auditors_allowed > l_ctx_value)
3112 	 ) THEN
3113 	--check the count that have been used for auditing...
3114 	OPEN cur_is_audited(p_n_uoo_id);
3115 	FETCH cur_is_audited INTO l_count;
3116 	--if used....
3117 	IF l_count > 0 THEN
3118 	  --if the count is more than context value...
3119 	  IF (l_ctx_value IS NULL OR (l_ctx_value < NVL(l_count,0))) THEN
3120 	    --display error message to the user saying that this field cannot be lowered/cleared since the
3121 	    --unit has been used for auditing.
3122 	    fnd_message.set_name('IGS','IGS_PS_LOW_NO_MAX_AUD_USEC');
3123 	    p_usec_rec.status := 'E';
3124 	    fnd_msg_pub.add;
3125 	  END IF;
3126 	END IF;
3127 	CLOSE cur_is_audited;
3128       END IF;
3129 
3130       -- Cannot unckeck waitlist allowed as there are students in the actual waitlist
3131       IF NVL(p_usec_rec.usec_waitlist_allowed,'N') = 'N' AND NVL(rec_act.WAITLIST_ACTUAL,0) > 0 THEN
3132 	 fnd_message.set_name('IGS','IGS_PS_ACT_WLST_GRT_ZERO');
3133 	 p_usec_rec.status := 'E';
3134 	 fnd_msg_pub.add;
3135       END IF;
3136 
3137       OPEN c_usec_st(p_usec_rec.unit_cd,p_usec_rec.version_number);
3138       FETCH c_usec_st INTO c_usec_st_rec;
3139       CLOSE c_usec_st;
3140       IF  p_usec_rec.enrollment_maximum <> c_usec_lim_rec.enrollment_maximum  AND c_usec_st_rec.unit_status <> 'PLANNED' THEN
3141         l_n_enr_max      := NVL( p_usec_rec.enrollment_maximum,'999999');
3142         l_c_wlst_allowed := NVL(c_usec_lim_rec.waitlist_allowed,'N');
3143         l_n_enr_act      := rec_act.ENROLLMENT_ACTUAL;
3144         l_n_wlst_max     := NVL(c_usec_lim_rec.MAX_STUDENTS_PER_WAITLIST,'999999');
3145         l_n_wlst_act     := NVL(rec_act.WAITLIST_ACTUAL,0);
3146 
3147 	IF l_c_wlst_allowed = 'N' THEN
3148 	   IF l_n_enr_act >= l_n_enr_max THEN
3149 	      l_c_usec_status := 'CLOSED';
3150 	   ELSIF l_n_enr_act < l_n_enr_max THEN
3151 	      l_c_usec_status := 'OPEN';
3152 	   END IF;
3153 	ELSE
3154 	   IF l_n_enr_act >= l_n_enr_max AND l_n_wlst_act >= l_n_wlst_max THEN
3155 	     l_c_usec_status := 'CLOSED';
3156 	   ELSIF l_n_enr_act < l_n_enr_max  AND l_n_wlst_act >0 THEN
3157 	     l_c_usec_status := 'HOLD';
3158 	   ELSIF l_n_enr_act >= l_n_enr_max AND l_n_wlst_act < l_n_wlst_max THEN
3159 	     l_c_usec_status := 'FULLWAITOK';
3160 	   ELSIF l_n_enr_act < l_n_enr_max  AND l_n_wlst_act = 0 THEN
3161 	     l_c_usec_status := 'OPEN';
3162 	   END IF;
3163 	END IF;
3164 	IF l_c_usec_status IS NOT NULL THEN
3165 	   UPDATE igs_ps_unit_ofr_opt_all
3166 	   SET unit_section_status = l_c_usec_status
3167 	   WHERE uoo_id = p_n_uoo_id;
3168 	END IF;
3169       END IF;
3170 
3171 	--If Priority exists then do not allow to uncheck the waitlist allowed
3172 	IF p_usec_rec.usec_waitlist_allowed = 'N' THEN
3173 
3174 	  OPEN c_usec_wlst_pri(p_n_uoo_id);
3175 	  FETCH c_usec_wlst_pri INTO c_usec_wlst_pri_rec;
3176 	  IF c_usec_wlst_pri%FOUND THEN
3177 	    fnd_message.set_name('IGS','IGS_PS_PRIORITY_EXISTS');
3178 	    p_usec_rec.status := 'E';
3179 	    fnd_msg_pub.add;
3180 	  END IF;
3181 	END IF;
3182 
3183        IF p_usec_rec.usec_waitlist_allowed = 'N' THEN
3184 	 IF p_usec_rec.usec_max_students_per_waitlist IS NULL THEN
3185 	   p_usec_rec.usec_max_students_per_waitlist:= 0;
3186 	 ELSIF  p_usec_rec.usec_max_students_per_waitlist > 0 THEN
3187 	   fnd_message.set_name('IGS','IGS_PS_MAX_STD_CNT_GT_0');
3188 	   p_usec_rec.status := 'E';
3189 	   fnd_msg_pub.add;
3190 	 END IF;
3191        END IF;
3192 
3193        IF (
3194             NVL(p_usec_rec.enrollment_maximum,-999) <>  NVL(c_usec_lim_rec.enrollment_maximum,-999) OR
3195             NVL(p_usec_rec.enrollment_expected,-999) <> NVL(c_usec_lim_rec.enrollment_expected,-999) OR
3196             NVL(p_usec_rec.override_enrollment_maximum,-999) <> NVL(c_usec_lim_rec.override_enrollment_max,-999)
3197           ) THEN
3198         IF igs_ps_usec_schedule.prgp_upd_usec_dtls(
3199                                                    p_uoo_id=>p_n_uoo_id,
3200                                                    p_max_enrollments =>NVL(p_usec_rec.enrollment_maximum,-999) ,
3201                                                    p_override_enrollment_max => NVL(p_usec_rec.override_enrollment_maximum,-999),
3202                                                    p_enrollment_expected => NVL(p_usec_rec.enrollment_expected,-999),
3203                                                    p_request_id =>l_request_id,
3204                                                    p_message_name=>l_message_name
3205                                                   ) = FALSE THEN
3206 
3207 
3208           p_usec_rec.status := 'E';
3209           fnd_message.set_name ('IGS', 'l_message_name');
3210           fnd_msg_pub.add;
3211         END IF;
3212       END IF;
3213 
3214     END IF;
3215 
3216 
3217   END validate_usec_el;
3218 
3219  PROCEDURE post_usec_limits(p_usec_rec IN OUT NOCOPY igs_ps_generic_pub.usec_rec_type,
3220                             p_calling_context IN VARCHAR2,
3221                             p_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
3222 		            p_insert_update VARCHAR2) AS
3223 
3224      CURSOR cur_unit_limit(cp_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
3225      SELECT enrollment_maximum,enrollment_expected,override_enrollment_max
3226      FROM   igs_ps_unit_ver_all uv,
3227            igs_ps_unit_ofr_opt_all uoo
3228      WHERE  uv.unit_cd=uoo.unit_cd
3229      AND    uv.version_number=uoo.version_number
3230      AND    uoo.uoo_id=cp_uoo_id;
3231      l_c_unit cur_unit_limit%ROWTYPE;
3232      l_request_id NUMBER;
3233      l_message_name VARCHAR2(30);
3234 
3235   BEGIN
3236 
3237     IF p_calling_context <> 'S' THEN
3238 
3239       IF p_insert_update = 'I' THEN
3240 	OPEN cur_unit_limit(p_n_uoo_id);
3241 	FETCH cur_unit_limit INTO l_c_unit;
3242 	CLOSE cur_unit_limit;
3243 
3244 	IF   (
3245 	 NVL(p_usec_rec.enrollment_maximum,-999) <>  NVL(l_c_unit.enrollment_maximum,-999) OR
3246 	 NVL(p_usec_rec.enrollment_expected,-999) <> NVL(l_c_unit.enrollment_expected,-999) OR
3247 	 NVL(p_usec_rec.override_enrollment_maximum,-999) <> NVL(l_c_unit.override_enrollment_max,-999)
3248 	) THEN
3249 
3250 	  IF igs_ps_usec_schedule.prgp_upd_usec_dtls(
3251 						     p_uoo_id=>p_n_uoo_id,
3252 						     p_max_enrollments =>NVL(l_c_unit.enrollment_maximum,-999) ,
3253 						     p_override_enrollment_max => NVL(l_c_unit.override_enrollment_max,-999),
3254 						     p_enrollment_expected => NVL(l_c_unit.enrollment_expected,-999),
3255 						     p_request_id =>l_request_id,
3256 						     p_message_name=>l_message_name
3257 						    ) = FALSE THEN
3258 
3259 
3260 	    p_usec_rec.status := 'E';
3261 	    fnd_message.set_name ('IGS', 'l_message_name');
3262 	    fnd_msg_pub.add;
3263 	  END IF;
3264 	END IF;
3265 
3266       END IF;
3267 
3268     END IF;
3269 
3270   END post_usec_limits;
3271 
3272   PROCEDURE post_uso_ins (p_n_ins_id IN igs_ps_uso_instrctrs.instructor_id%TYPE,
3273                           p_n_uoo_id IN igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
3274                           p_uso_ins_rec  IN OUT NOCOPY igs_ps_generic_pub.uso_ins_rec_type,
3275                           p_n_index IN NUMBER) AS
3276   /***********************************************************************************************
3277     Created By     :  jbegum
3278     Date Created By:  02-June-2003
3279     Purpose        :  Bug # 2972950.
3280                       For the Legacy Enhancements TD:
3281                       This procedure does the post validation for unit section occurrence of instructors.
3282                       if the instructor getting imported is not a part of Unit Section Teaching Responsibility then
3283                       the instructor would be added in Unit Section Teaching Responsibility .As mentioned in TD.
3284 
3285     Known limitations,enhancements,remarks:
3286     Change History (in reverse chronological order)
3287     Who         When            What
3288     smvk        04-May-2004     Bug # 3568858.  Faculty Teaching Responsibility build. Removed the code which were deriving
3289                                 % allocation based on workload values, % allocation and workload value match and workload validations.
3290     smvk        19-Jun-2003     Bug # 2833853. HR integration Build. when instructors are imported, if the confirmed flag
3291                                 is set to 'Y' then their corresponding workloads are calculated and checked against the expected workload.
3292                                 Erroring out if the calculated workload exceeds the expected workload / calendar category is not at all set up /
3293                                 work load is not set up for employment category of instrutor getting imported.
3294   ********************************************************************************************** */
3295 
3296      CURSOR c_check_instrctr_exists(cp_n_instructor_id IGS_PS_USEC_TCH_RESP.INSTRUCTOR_ID%TYPE,
3297                                     cp_n_uoo_id IGS_PS_UNIT_OFR_OPT.UOO_ID%TYPE) IS
3298        SELECT COUNT(*)
3299        FROM   igs_ps_usec_tch_resp
3300        WHERE  instructor_id = cp_n_instructor_id
3301        AND    uoo_id = cp_n_uoo_id
3302        AND    ROWNUM = 1;
3303 
3304      CURSOR c_lead_cnd (cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%type) IS
3305        SELECT COUNT(*)
3306        FROM   IGS_PS_USEC_TCH_RESP
3307        WHERE  lead_instructor_flag='Y'
3308        AND    uoo_id = cp_n_uoo_id
3309        AND    ROWNUM = 1;
3310 
3311      CURSOR c_cal_inst (cp_n_uoo_id IN NUMBER) IS
3312        SELECT A.cal_type,
3313               A.ci_sequence_number,
3314               A.unit_section_status
3315        FROM   IGS_PS_UNIT_OFR_OPT_ALL A
3316        WHERE  A.uoo_id  =  cp_n_uoo_id;
3317 
3318      CURSOR c_cal_setup IS
3319        SELECT 'x'
3320        FROM   IGS_PS_EXP_WL
3321        WHERE  ROWNUM=1;
3322 
3323      rec_cal_inst c_cal_inst%ROWTYPE;
3324 
3325      l_n_t_lecture        igs_ps_usec_tch_resp.instructional_load_lecture%TYPE :=0;
3326      l_n_t_lab            igs_ps_usec_tch_resp.instructional_load_lab%TYPE :=0;
3327      l_n_t_other          igs_ps_usec_tch_resp.instructional_load%TYPE :=0;
3328      l_n_total_wl         NUMBER(10,2);
3329      l_n_exp_wl           NUMBER(6,2);
3330      l_n_tot_fac_wl       NUMBER(10,2);
3331      l_c_cal              VARCHAR2(1);
3332      l_n_no_of_instructor NUMBER;
3333      l_n_count            NUMBER;
3334 
3335   BEGIN
3336 
3337     --Check if the unit section is NOT_OFFERED
3338     IF NOT igs_ps_validate_lgcy_pkg.check_not_offered_usec_status(p_n_uoo_id) THEN
3339       fnd_message.set_name ( 'IGS', 'IGS_PS_IMP_NOT_ALD_NOT_OFFERED' );
3340       fnd_msg_pub.add;
3341       p_uso_ins_rec.status := 'E';
3342     END IF;
3343 
3344 
3345     OPEN c_check_instrctr_exists(p_n_ins_id, p_n_uoo_id);
3346     FETCH c_check_instrctr_exists INTO l_n_no_of_instructor;
3347     CLOSE c_check_instrctr_exists;
3348 
3349     IF l_n_no_of_instructor > 0 THEN
3350        RETURN;
3351     ELSE
3352        -- Derivation of values
3353        IF p_uso_ins_rec.confirmed_flag IS NULL THEN
3354           p_uso_ins_rec.confirmed_flag := 'Y';
3355        END IF;
3356 
3357        IF p_uso_ins_rec.lead_instructor_flag IS NULL THEN
3358           p_uso_ins_rec.lead_instructor_flag := 'N';
3359        END IF;
3360 
3361        -- Check constraints
3362        BEGIN
3363           igs_ps_usec_tch_resp_pkg.check_constraints('LEAD_INSTRUCTOR_FLAG', p_uso_ins_rec.lead_instructor_flag);
3364        EXCEPTION
3365           WHEN OTHERS THEN
3366              fnd_message.set_name('IGS','IGS_PS_LEAD_INSTRUCTOR_FLAG');
3367              igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_Y_OR_N',fnd_message.get, NULL,TRUE);
3368              p_uso_ins_rec.status :='E';
3369        END;
3370        BEGIN
3371           igs_ps_usec_tch_resp_pkg.check_constraints('CONFIRMED_FLAG', p_uso_ins_rec.confirmed_flag);
3372        EXCEPTION
3373           WHEN OTHERS THEN
3374              fnd_message.set_name('IGS','IGS_PS_CONFIRMED_FLAG');
3375              igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_Y_OR_N',fnd_message.get, NULL,TRUE);
3376              p_uso_ins_rec.status :='E';
3377        END;
3378 
3379        -- Validation : Either percentage allocation or workload value should be provided. Both cannot be null
3380        -- Presently coded the mandatory validation for confirmed records.
3381        IF p_uso_ins_rec.confirmed_flag = 'Y' AND
3382           p_uso_ins_rec.wl_percentage_allocation IS NULL AND
3383           p_uso_ins_rec.instructional_load_lecture IS NULL AND
3384           p_uso_ins_rec.instructional_load_laboratory IS NULL AND
3385           p_uso_ins_rec.instructional_load_other IS NULL THEN
3386             fnd_message.set_name('IGS','IGS_PS_PERCENT_WKLD_MANDATORY');
3387             fnd_msg_pub.add;
3388             p_uso_ins_rec.status := 'E';
3389        END IF;
3390 
3391        IF p_uso_ins_rec.wl_percentage_allocation IS NOT NULL THEN
3392           BEGIN
3393              igs_ps_usec_tch_resp_pkg.check_constraints('PERCENTAGE_ALLOCATION', p_uso_ins_rec.wl_percentage_allocation);
3394           EXCEPTION
3395              WHEN OTHERS THEN
3396                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_PTS_RANGE_0_999','PERCENTAGE','LEGACY_TOKENS',TRUE);
3397                 p_uso_ins_rec.status :='E';
3398           END;
3399           --Format mask validation
3400 	  IF p_uso_ins_rec.status <> 'E' THEN
3401 	    IF NOT igs_ps_validate_lgcy_pkg.boundary_check_number(p_uso_ins_rec.wl_percentage_allocation,3,2) THEN
3402                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_PTS_RANGE_0_999','PERCENTAGE','LEGACY_TOKENS',FALSE);
3403 		p_uso_ins_rec.status :='E';
3404 	    END IF;
3405 	  END IF;
3406 
3407        END IF;
3408 
3409        IF p_uso_ins_rec.instructional_load_lecture IS NOT NULL THEN
3410           BEGIN
3411              igs_ps_usec_tch_resp_pkg.check_constraints('INSTRUCTIONAL_LOAD_LECTURE', p_uso_ins_rec.instructional_load_lecture);
3412           EXCEPTION
3413              WHEN OTHERS THEN
3414                fnd_message.set_name('IGS','IGS_PS_INS_LOAD_LECTURE');
3415                igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_VAL_0_9999D99',fnd_message.get, NULL,TRUE);
3416                p_uso_ins_rec.status :='E';
3417           END;
3418 
3419           --Format mask validation
3420 	  IF p_uso_ins_rec.status <> 'E' THEN
3421 	    IF NOT igs_ps_validate_lgcy_pkg.boundary_check_number(p_uso_ins_rec.instructional_load_lecture,4,2) THEN
3422                 fnd_message.set_name('IGS','IGS_PS_INS_LOAD_LECTURE');
3423                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_VAL_0_9999D99',fnd_message.get, NULL,FALSE);
3424 		p_uso_ins_rec.status :='E';
3425 	    END IF;
3426 	  END IF;
3427 
3428        END IF;
3429 
3430        IF p_uso_ins_rec.instructional_load_laboratory IS NOT NULL THEN
3431           BEGIN
3432              igs_ps_usec_tch_resp_pkg.check_constraints('INSTRUCTIONAL_LOAD_LAB', p_uso_ins_rec.instructional_load_laboratory);
3433           EXCEPTION
3434              WHEN OTHERS THEN
3435                 fnd_message.set_name('IGS','IGS_PS_INS_LOAD_LAB');
3436                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_VAL_0_9999D99',fnd_message.get,NULL,TRUE);
3437                 p_uso_ins_rec.status :='E';
3438           END;
3439 
3440 	  --Format mask validation
3441 	  IF p_uso_ins_rec.status <> 'E' THEN
3442 	    IF NOT igs_ps_validate_lgcy_pkg.boundary_check_number(p_uso_ins_rec.instructional_load_laboratory,4,2) THEN
3443                 fnd_message.set_name('IGS','IGS_PS_INS_LOAD_LAB');
3444                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_VAL_0_9999D99',fnd_message.get,NULL,FALSE);
3445 		p_uso_ins_rec.status :='E';
3446 	    END IF;
3447 	  END IF;
3448 
3449        END IF;
3450 
3451        IF p_uso_ins_rec.instructional_load_other IS NOT NULL THEN
3452           BEGIN
3453              igs_ps_usec_tch_resp_pkg.check_constraints('INSTRUCTIONAL_LOAD', p_uso_ins_rec.instructional_load_other);
3454           EXCEPTION
3455              WHEN OTHERS THEN
3456                 fnd_message.set_name('IGS','IGS_PS_INS_LOAD_OTHER');
3457                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_VAL_0_9999D99',fnd_message.get,NULL,TRUE);
3458                 p_uso_ins_rec.status :='E';
3459           END;
3460 
3461 	  --Format mask validation
3462 	  IF p_uso_ins_rec.status <> 'E' THEN
3463 	    IF NOT igs_ps_validate_lgcy_pkg.boundary_check_number(p_uso_ins_rec.instructional_load_other,4,2) THEN
3464                 fnd_message.set_name('IGS','IGS_PS_INS_LOAD_OTHER');
3465                 igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_VAL_0_9999D99',fnd_message.get,NULL,FALSE);
3466 		p_uso_ins_rec.status :='E';
3467 	    END IF;
3468 	  END IF;
3469 
3470        END IF;
3471 
3472        IF p_uso_ins_rec.lead_instructor_flag = 'Y' THEN
3473           OPEN c_lead_cnd(p_n_uoo_id);
3474           FETCH c_lead_cnd INTO l_n_count;
3475           CLOSE c_lead_cnd;
3476           IF l_n_count <> 0 THEN
3477              fnd_message.set_name('IGS','IGS_PS_LEAD_INSTRUCTOR_ONE');
3478              fnd_msg_pub.add;
3479              p_uso_ins_rec.status := 'E';
3480           END IF;
3481        END IF;
3482 
3483        -- if workload percentage is provided need to dervie the lecture /lab / other workloads.
3484        IF p_uso_ins_rec.wl_percentage_allocation IS NOT NULL AND
3485           p_uso_ins_rec.instructional_load_lecture IS NULL AND
3486           p_uso_ins_rec.instructional_load_laboratory IS NULL AND
3487           p_uso_ins_rec.instructional_load_other IS NULL THEN
3488           igs_ps_fac_credt_wrkload.calculate_teach_work_load(p_n_uoo_id, p_uso_ins_rec.wl_percentage_allocation, l_n_t_lab , l_n_t_lecture, l_n_t_other);
3489              p_uso_ins_rec.instructional_load_lecture := l_n_t_lecture;
3490              p_uso_ins_rec.instructional_load_laboratory := l_n_t_lab;
3491              p_uso_ins_rec.instructional_load_other := l_n_t_other;
3492        END IF;
3493 
3494 
3495        --Instructor should be staff or faculty
3496        IF validate_staff_faculty (p_person_id => p_n_ins_id) = FALSE THEN
3497              p_uso_ins_rec.status :='E';
3498              fnd_message.set_name('IGS','IGS_PS_INST_NOT_FACULTY_STAFF');
3499              fnd_msg_pub.add;
3500        END IF;
3501 
3502        IF p_uso_ins_rec.confirmed_flag = 'Y' THEN
3503           OPEN c_cal_setup;
3504           FETCH c_cal_setup INTO l_c_cal;
3505           CLOSE c_cal_setup;
3506           IF l_c_cal IS NULL THEN
3507              p_uso_ins_rec.status :='E';
3508              fnd_message.set_name('IGS','IGS_PS_NO_CAL_CAT_SETUP');
3509              fnd_msg_pub.add;
3510           ELSIF l_c_cal = 'x' THEN
3511              l_n_total_wl := NVL(p_uso_ins_rec.instructional_load_lecture,0) +
3512                              NVL(p_uso_ins_rec.instructional_load_laboratory,0) +
3513                              NVL(p_uso_ins_rec.instructional_load_other,0);
3514 
3515              OPEN c_cal_inst(p_n_uoo_id);
3516              FETCH c_cal_inst INTO rec_cal_inst;
3517              IF c_cal_inst%FOUND THEN
3518                 IF rec_cal_inst.unit_section_status NOT IN ('CANCELLED','NOT_OFFERED') THEN
3519                    IF igs_ps_gen_001.teach_fac_wl (rec_cal_inst.cal_type,
3520                                                    rec_cal_inst.ci_sequence_number,
3521                                                    p_n_ins_id,
3522                                                    l_n_total_wl,
3523                                                    l_n_tot_fac_wl,
3524                                                    l_n_exp_wl
3525                                                    ) THEN
3526                       p_uso_ins_rec.status :='E';
3527                       fnd_message.set_name('IGS','IGS_PS_FAC_EXCEED_EXP_WL');
3528                       fnd_msg_pub.add;
3529                    END IF;
3530                    IF l_n_exp_wl IS NULL OR l_n_exp_wl = 0 THEN
3531                       p_uso_ins_rec.status :='E';
3532                       fnd_message.set_name('IGS','IGS_PS_NO_SETUP_FAC_EXCEED');
3533                       fnd_msg_pub.add;
3534                    END IF;
3535                 END IF;
3536              END IF;
3537              CLOSE c_cal_inst;
3538           END IF;
3539        END IF;
3540        IF p_uso_ins_rec.status = 'S' THEN
3541           INSERT INTO IGS_PS_USEC_TCH_RESP(
3542                                              UNIT_SECTION_TEACH_RESP_ID,
3543                                              UOO_ID,
3544                                              INSTRUCTOR_ID,
3545                                              CONFIRMED_FLAG,
3546                                              PERCENTAGE_ALLOCATION,
3547                                              INSTRUCTIONAL_LOAD_LECTURE,
3548                                              INSTRUCTIONAL_LOAD_LAB,
3549                                              INSTRUCTIONAL_LOAD,
3550                                              LEAD_INSTRUCTOR_FLAG,
3551                                              CREATED_BY,
3552                                              CREATION_DATE,
3553                                              LAST_UPDATED_BY,
3554                                              LAST_UPDATE_DATE,
3555                                              LAST_UPDATE_LOGIN
3556                                            ) VALUES (
3557                                              IGS_PS_USEC_TCH_RESP_S.nextval,
3558                                              p_n_uoo_id,
3559                                              p_n_ins_id,
3560                                              p_uso_ins_rec.confirmed_flag,
3561                                              p_uso_ins_rec.wl_percentage_allocation,
3562                                              p_uso_ins_rec.instructional_load_lecture,
3563                                              p_uso_ins_rec.instructional_load_laboratory,
3564                                              p_uso_ins_rec.instructional_load_other,
3565                                              p_uso_ins_rec.lead_instructor_flag,
3566                                              g_n_user_id,
3567                                              SYSDATE,
3568                                              g_n_user_id,
3569                                              SYSDATE,
3570                                              g_n_login_id
3571                                            );
3572           v_tab_usec_tr(v_tab_usec_tr.count +1).uoo_id := p_n_uoo_id;
3573           v_tab_usec_tr(v_tab_usec_tr.count).instr_index := p_n_index;
3574        END IF;
3575     END IF;
3576   END post_uso_ins;
3577 
3578  FUNCTION post_uso_ins_busi (p_tab_uso_ins IN OUT NOCOPY igs_ps_generic_pub.uso_ins_tbl_type) RETURN BOOLEAN AS
3579   /***********************************************************************************************
3580     Created By     :  jbegum
3581     Date Created By:  02-June-2003
3582     Purpose        :  Bug # 2972950.
3583                       For the Legacy Enhancements TD:
3584                       This function does the post business validation for unit section occurrence instructor process.
3585                       This validations make sure that the unit section teaching responisibilities record getting created as a part of
3586                       import unit section occurrence instrcutors process are valid. Changes are as mentioned in TD.
3587 
3588     Known limitations,enhancements,remarks:
3589     Change History (in reverse chronological order)
3590     Who         When            What
3591     sarakshi    14-May-2004     Bug#3629483 , changed the message IGS_PS_TCHRESP_NOTTOTAL_100 to IGS_PS_US_TCHRESP_NOTTOTAL_100.Also added null to token for the message IGS_PS_WKLOAD_VALIDATION
3592     smvk        04-May-2004     Bug # 3568858.  Faculty Teaching Responsibility build. Workload validation based on profile
3593                                 "IGS: Unit Section Teaching Responsibility Validation".
3594   ********************************************************************************************** */
3595 
3596    l_tab_uoo igs_ps_create_generic_pkg.uoo_tbl_type;
3597 
3598    CURSOR c_count_lead (cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
3599      SELECT count(*)
3600      FROM   IGS_PS_USEC_TCH_RESP
3601      WHERE  uoo_id = cp_n_uoo_id
3602       AND   lead_instructor_flag = 'Y';
3603 
3604    CURSOR c_count_percent(cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
3605      SELECT SUM(PERCENTAGE_ALLOCATION)
3606      FROM   IGS_PS_USEC_TCH_RESP
3607      WHERE  confirmed_flag = 'Y'
3608      AND    uoo_id = cp_n_uoo_id;
3609 
3610    CURSOR c_unit_dtls (cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
3611      SELECT unit_cd,
3612             version_number
3613      FROM   igs_ps_unit_ofr_opt_all
3614      WHERE  uoo_id = cp_n_uoo_id
3615      AND    ROWNUM < 2;
3616 
3617    CURSOR c_null IS
3618    SELECT message_text
3619    FROM   fnd_new_messages
3620    WHERE  message_name = 'IGS_PS_NULL'
3621    AND    application_id = 8405
3622    AND    LANGUAGE_CODE = USERENV('LANG');
3623 
3624    l_c_null  fnd_new_messages.message_text%TYPE;
3625 
3626    l_n_count NUMBER;
3627    l_n_from NUMBER;
3628    l_n_to NUMBER;
3629    l_b_validation BOOLEAN;
3630    l_b_status BOOLEAN;
3631    l_b_wl_validation BOOLEAN;
3632    l_n_tot_lec NUMBER;
3633    l_n_tot_lab NUMBER;
3634    l_n_tot_oth NUMBER;
3635    rec_unit_dtls c_unit_dtls%ROWTYPE;
3636    l_c_validation_type igs_ps_unit_ver_all.workload_val_code%TYPE;
3637 
3638  BEGIN
3639    l_b_validation := TRUE;
3640    l_b_status :=TRUE;
3641    l_b_wl_validation := TRUE;
3642 
3643    IF v_tab_usec_tr.EXISTS(1) THEN
3644       l_tab_uoo(1) := v_tab_usec_tr(1).uoo_id;
3645 
3646      FOR I in 2.. v_tab_usec_tr.COUNT LOOP
3647          IF NOT isExists(v_tab_usec_tr(I).uoo_id,l_tab_uoo) THEN
3648            l_tab_uoo(l_tab_uoo.count+1) := v_tab_usec_tr(I).uoo_id;
3649          END IF;
3650      END LOOP;
3651 
3652      -- Get the parent unit version.
3653      OPEN c_unit_dtls (l_tab_uoo(1));
3654      FETCH c_unit_dtls INTO rec_unit_dtls;
3655      CLOSE c_unit_dtls;
3656 
3657      -- Get the workload validation type
3658      l_c_validation_type := igs_ps_fac_credt_wrkload.get_validation_type (rec_unit_dtls.unit_cd, rec_unit_dtls.version_number);
3659 
3660      FOR I in 1.. l_tab_uoo.count LOOP
3661         l_n_from := fnd_msg_pub.count_msg;
3662         l_b_validation := TRUE;
3663         l_b_wl_validation := TRUE;
3664         OPEN c_count_lead(l_tab_uoo(I));
3665         FETCH c_count_lead INTO l_n_count;
3666         CLOSE c_count_lead;
3667         IF l_n_count < 1 THEN
3668              fnd_message.set_name('IGS','IGS_PS_ATLST_ONE_LD_INSTRCTR');
3669              fnd_msg_pub.add;
3670              l_b_validation :=FALSE;
3671         ELSIF l_n_count > 1 THEN
3672              fnd_message.set_name ('IGS','IGS_PS_LEAD_INSTRUCTOR_ONE');
3673              fnd_msg_pub.add;
3674              l_b_validation :=FALSE;
3675         END IF;
3676 
3677         IF l_c_validation_type <> 'NONE' THEN
3678            OPEN c_count_percent(l_tab_uoo(I));
3679            FETCH c_count_percent INTO l_n_count;
3680            CLOSE c_count_percent;
3681 
3682            IF l_n_count <> 100 THEN
3683               fnd_message.set_name('IGS', 'IGS_PS_US_TCHRESP_NOTTOTAL_100');
3684               fnd_msg_pub.add;
3685               l_b_wl_validation :=FALSE;  -- modified as a part of Bug # 3568858.
3686            END IF;
3687 
3688            IF NOT igs_ps_fac_credt_wrkload.validate_workload(l_tab_uoo(I),l_n_tot_lec,l_n_tot_lab,l_n_tot_oth) THEN
3689               fnd_message.set_name('IGS','IGS_PS_WKLOAD_VALIDATION');
3690 	      OPEN c_null;
3691 	      FETCH c_null INTO l_c_null;
3692 	      CLOSE c_null;
3693 
3694               IF l_n_tot_lec = -999 THEN
3695                 fnd_message.set_token('WKLOAD_LECTURE',l_c_null);
3696               ELSE
3697                 fnd_message.set_token('WKLOAD_LECTURE',l_n_tot_lec);
3698               END IF;
3699 
3700               IF l_n_tot_lab = -999 THEN
3701                 fnd_message.set_token('WKLOAD_LAB',l_c_null);
3702               ELSE
3703                 fnd_message.set_token('WKLOAD_LAB',l_n_tot_lab);
3704               END IF;
3705 
3706               IF l_n_tot_oth = -999 THEN
3707                 fnd_message.set_token('WKLOAD_OTHER',l_c_null);
3708               ELSE
3709                 fnd_message.set_token('WKLOAD_OTHER',l_n_tot_oth);
3710               END IF;
3711 
3712 	      fnd_msg_pub.add;
3713               l_b_wl_validation :=FALSE;  -- modified as a part of Bug # 3568858.
3714            END IF;
3715         END IF;
3716 
3717         IF NOT (l_b_validation AND l_b_wl_validation) THEN
3718            l_n_to := fnd_msg_pub.count_msg;
3719            FOR j in 1.. v_tab_usec_tr.COUNT LOOP
3720                IF l_tab_uoo(I) = v_tab_usec_tr(j).uoo_id AND p_tab_uso_ins(v_tab_usec_tr(j).instr_index).status = 'S' THEN
3721                   -- Setting the status of the record properly
3722                   -- Set the status of records as error and return status (l_b_status) as error when
3723                   -- 1) if the lead instructor validation is fails
3724                   -- 2) if the percentage allocation or workload validation fails, when the workload validation type is 'DENY'.
3725                   -- Set the status of record as warning
3726                   -- 1) if the percentage allocation or workload validation fails, when the workload validation type is 'WARN'.
3727                   IF NOT l_b_validation THEN
3728                      -- Failure of lead instructor validation.
3729                      p_tab_uso_ins(v_tab_usec_tr(j).instr_index).status := 'E';
3730                      l_b_status :=FALSE;
3731                   ELSE
3732                       -- when workload validation type is not equal to NONE
3733                       IF l_c_validation_type = 'WARN' THEN
3734                          -- setting the status as warning for the record and not setting the value for l_b_status.
3735                          p_tab_uso_ins(v_tab_usec_tr(j).instr_index).status := 'W';
3736                       ELSE  -- workload workload validation type is DENY
3737                          -- setting the status of the record and l_b_status as error.
3738                          p_tab_uso_ins(v_tab_usec_tr(j).instr_index).status := 'E';
3739                          l_b_status :=FALSE;
3740                       END IF;
3741                    END IF;
3742 
3743                    p_tab_uso_ins(v_tab_usec_tr(j).instr_index).msg_from := l_n_from +1;
3744                    p_tab_uso_ins(v_tab_usec_tr(j).instr_index).msg_to := l_n_to;
3745                END IF;
3746            END LOOP;
3747         END IF;
3748      END LOOP;
3749      v_tab_usec_tr.delete;
3750      return l_b_status;
3751    ELSE
3752       RETURN TRUE;
3753    END IF;
3754  END post_uso_ins_busi;
3755 
3756  PROCEDURE validate_unit_reference(p_unit_ref_rec IN OUT NOCOPY igs_ps_generic_pub.unit_ref_rec_type,
3757                                    p_n_uoo_id     IN NUMBER,
3758 				   p_n_uso_id     IN NUMBER,
3759 				   p_calling_context IN VARCHAR2) IS
3760     CURSOR c_ref_flag (cp_c_ref_cd_type  igs_ge_ref_cd_type.reference_cd_type%TYPE) IS
3761        SELECT  unit_flag,
3762                unit_section_flag,
3763                unit_section_occurrence_flag
3764        FROM igs_ge_ref_cd_type
3765        WHERE reference_cd_type = cp_c_ref_cd_type;
3766 
3767     rec_ref_flag c_ref_flag%ROWTYPE;
3768 
3769     CURSOR c_occurs(cp_unit_section_occurrence_id igs_ps_usec_occurs_all.unit_section_occurrence_id%TYPE) IS
3770     SELECT uso.unit_section_occurrence_id
3771     FROM igs_ps_usec_occurs_all uso
3772     WHERE (uso.schedule_status IS NOT NULL AND uso.schedule_status NOT IN ('PROCESSING','USER_UPDATE'))
3773     AND uso.no_set_day_ind ='N'
3774     AND uso.unit_section_occurrence_id=cp_unit_section_occurrence_id;
3775 
3776     CURSOR c_ref_code (cp_uso_id igs_ps_uso_facility.unit_section_occurrence_id%TYPE) IS
3777     SELECT 'X'
3778     FROM   igs_ps_usec_occurs_all
3779     WHERE  unit_section_occurrence_id = cp_uso_id
3780     AND    schedule_status = 'PROCESSING';
3781 
3782     l_c_var   VARCHAR2(1);
3783  BEGIN
3784 
3785     OPEN c_ref_flag(p_unit_ref_rec.reference_cd_type);
3786     FETCH c_ref_flag INTO rec_ref_flag;
3787     CLOSE c_ref_flag;
3788 
3789     IF p_unit_ref_rec.data_type = 'UNIT' THEN  -- check whether the reference code type is allowable at unit level
3790 
3791        IF rec_ref_flag.unit_flag IS NULL OR rec_ref_flag.unit_flag = 'N' THEN
3792           fnd_message.set_name('IGS','IGS_PS_LGCY_UNIT_REF_LVL');
3793           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_REF_NA', fnd_message.get, NULL, FALSE);
3794           p_unit_ref_rec.status := 'E';
3795        END IF;
3796 
3797     ELSIF p_unit_ref_rec.data_type = 'SECTION' THEN  -- check whether the reference code type is allowable at unit section level
3798 
3799        IF rec_ref_flag.unit_section_flag IS NULL OR rec_ref_flag.unit_section_flag = 'N' THEN
3800           fnd_message.set_name('IGS','IGS_PS_LGCY_USEC_REF_LVL');
3801           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_REF_NA', fnd_message.get, NULL, FALSE);
3802           p_unit_ref_rec.status := 'E';
3803        END IF;
3804 
3805     ELSIF p_unit_ref_rec.data_type = 'OCCURRENCE' THEN  -- check whether the reference code type is allowable at unit sectin occurrence level
3806 
3807        IF rec_ref_flag.unit_section_occurrence_flag IS NULL OR rec_ref_flag.unit_section_occurrence_flag = 'N' THEN
3808           fnd_message.set_name('IGS','IGS_PS_LGCY_OCCUR_REF_LVL');
3809           igs_ps_validate_lgcy_pkg.set_msg('IGS_PS_LGCY_REF_NA', fnd_message.get, NULL, FALSE);
3810           p_unit_ref_rec.status := 'E';
3811        END IF;
3812 
3813        IF p_calling_context <> 'S' THEN
3814 	 OPEN c_ref_code (p_n_uso_id);
3815 	 FETCH c_ref_code INTO l_c_var;
3816 	 IF c_ref_code%FOUND THEN
3817 	    fnd_message.set_name ( 'IGS', 'IGS_PS_SCHEDULING_IN_PROGRESS' );
3818 	    fnd_msg_pub.add;
3819 	    p_unit_ref_rec.status := 'E';
3820 	 END IF;
3821 	 CLOSE c_ref_code;
3822 
3823 
3824 	 IF p_unit_ref_rec.status = 'S' THEN
3825 	   --Update the schedule status of the occurrence to USER_UPDATE if inserting/updating a record
3826 	   FOR l_occurs_rec IN c_occurs(p_n_uso_id) LOOP
3827 	     igs_ps_usec_schedule.update_occurrence_status(l_occurs_rec.unit_section_occurrence_id,'USER_UPDATE','N');
3828 	   END LOOP;
3829 	 END IF;
3830        END IF;
3831 
3832     END IF;
3833 
3834     IF p_unit_ref_rec.data_type IN ('SECTION','OCCURRENCE') THEN
3835       --Check if the unit section is NOT_OFFERED
3836       IF NOT igs_ps_validate_lgcy_pkg.check_not_offered_usec_status(p_n_uoo_id) THEN
3837 	fnd_message.set_name ( 'IGS', 'IGS_PS_IMP_NOT_ALD_NOT_OFFERED' );
3838 	fnd_msg_pub.add;
3839 	p_unit_ref_rec.status := 'E';
3840       END IF;
3841 
3842     END IF;
3843 
3844  END validate_unit_reference;
3845 
3846   -- This Function will returns true if waitlist is allowed otherwise false.
3847   FUNCTION is_waitlist_allowed RETURN BOOLEAN AS
3848   /***********************************************************************************************
3849     Created By     :  smvk
3850     Date Created By:  10-Oct-2003.
3851     Purpose        :  This procedure returns true if waitlist is allowed at institutional level
3852                       otherwise false.
3853 
3854     Known limitations,enhancements,remarks:
3855     Change History (in reverse chronological order)
3856     Who         When            What
3857   ********************************************************************************************** */
3858 
3859     CURSOR c_wlst_allowed IS
3860       SELECT waitlist_allowed_flag
3861       FROM   igs_en_inst_wl_stps;
3862     l_c_allowed igs_en_inst_wl_stps.waitlist_allowed_flag%TYPE;
3863 
3864   BEGIN
3865     OPEN c_wlst_allowed;
3866     FETCH c_wlst_allowed INTO l_c_allowed;
3867     CLOSE c_wlst_allowed;
3868     IF l_c_allowed = 'Y' THEN
3869       RETURN TRUE;
3870     END IF;
3871     RETURN FALSE;
3872   END;
3873 
3874   PROCEDURE get_uso_id( p_uoo_id                IN NUMBER,
3875                         p_occurrence_identifier IN VARCHAR2,
3876                         p_uso_id                OUT NOCOPY NUMBER,
3877                         p_message               OUT NOCOPY VARCHAR2
3878                        ) AS
3879   /***********************************************************************************************
3880     Created By     :  smvk
3881     Date Created By:  28-Jul-2004.
3882     Purpose        :  This utility procedure is use to identify the unit section occurrence with the given
3883                       information.
3884                       Returns Unit section occurrence identifier in out parameter p_uso_id.
3885                       Returns error message in the out parameter p_message, if it could not resolve the
3886                       unit section occurrence uniquely with the provided information.
3887 
3888     Known limitations,enhancements,remarks:
3889     Change History (in reverse chronological order)
3890     Who         When            What
3891   ********************************************************************************************** */
3892   CURSOR occur IS
3893   SELECT unit_section_occurrence_id
3894   FROM  igs_ps_usec_occurs_all
3895   WHERE uoo_id= p_uoo_id
3896   AND occurrence_identifier=p_occurrence_identifier;
3897 
3898   BEGIN
3899 
3900     IF p_uoo_id IS NOT NULL AND p_occurrence_identifier IS NOT NULL THEN
3901        OPEN occur;
3902        FETCH occur INTO p_uso_id;
3903        CLOSE occur;
3904     END IF;
3905     IF p_uso_id IS NULL THEN
3906       P_message:= 'IGS_PS_LGCY_USO_CANT_RESOLVE';
3907     END IF;
3908 
3909   END get_uso_id;
3910 
3911 
3912 -- to validate whether the person is a staff/faculty member
3913 FUNCTION validate_staff_faculty (p_person_id IN NUMBER ) RETURN BOOLEAN IS
3914   /***********************************************************************************************
3915     Created By     :  sarakshi
3916     Date Created By:  20-Jun-2005.
3917     Purpose        :  This utility procedure is to validate whether a person is a staff/faculty.
3918 
3919     Known limitations,enhancements,remarks:
3920     Change History (in reverse chronological order)
3921     Who         When            What
3922   ***********************************************************************************************/
3923 
3924  CURSOR C IS
3925     SELECT 'X'
3926     FROM  IGS_PE_PERSON_TYPES PT,IGS_PE_TYP_INSTANCES_ALL PTI,HZ_PARTIES HZ
3927                      WHERE HZ.PARTY_ID = PTI.PERSON_ID
3928 		     AND HZ.PARTY_ID = p_person_id
3929                      AND PTI.PERSON_TYPE_CODE = PT.PERSON_TYPE_CODE
3930                      AND PT.SYSTEM_TYPE IN ('STAFF','FACULTY')
3931                      AND TRUNC(SYSDATE) BETWEEN TRUNC(PTI.START_DATE) AND TRUNC(NVL(PTI.END_DATE,SYSDATE))
3932                      AND HZ.STATUS = 'A'
3933     UNION
3934                      SELECT  'X'
3935                      FROM PER_PERSON_TYPE_USAGES_F USG,PER_PEOPLE_F PEO,IGS_PE_PER_TYPE_MAP MAP,HZ_PARTIES HZ
3936                      WHERE HZ.PARTY_ID = peo.party_id
3937                      AND USG.PERSON_ID = PEO.PERSON_ID
3938 		     AND HZ.PARTY_ID = p_person_id
3939                      AND USG.PERSON_TYPE_ID = MAP.PER_PERSON_TYPE_ID AND TRUNC(SYSDATE) BETWEEN
3940                      TRUNC(PEO.EFFECTIVE_START_DATE) AND TRUNC(PEO.EFFECTIVE_END_DATE)
3941                      AND TRUNC(SYSDATE) BETWEEN TRUNC(USG.EFFECTIVE_START_DATE) AND TRUNC(USG.EFFECTIVE_END_DATE)
3942                      AND HZ.STATUS = 'A' ;
3943 
3944  l_c_var VARCHAR2(1);
3945 
3946 BEGIN
3947          OPEN c;
3948          FETCH c INTO l_c_var;
3949          IF c%FOUND THEN
3950            RETURN TRUE;
3951          ELSE
3952            RETURN FALSE;
3953          END IF;
3954          CLOSE C;
3955 END validate_staff_faculty;
3956 
3957 
3958 FUNCTION isexists(p_n_uoo_id IN igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
3959                   p_tab_uoo  IN igs_ps_create_generic_pkg.uoo_tbl_type) RETURN BOOLEAN AS
3960   /***********************************************************************************************
3961     Created By     :  sarakshi
3962     Date Created By:  20-Jun-2005.
3963     Purpose        :  This utility procedure is to check if a uoo_id exists in a pl/sql table
3964 
3965     Known limitations,enhancements,remarks:
3966     Change History (in reverse chronological order)
3967     Who         When            What
3968   ***********************************************************************************************/
3969 BEGIN
3970   FOR i in 1..p_tab_uoo.count LOOP
3971      IF p_n_uoo_id = p_tab_uoo(i) THEN
3972 	RETURN TRUE;
3973      END IF;
3974   END LOOP;
3975   RETURN FALSE;
3976 END isexists;
3977 
3978 FUNCTION  check_import_allowed( p_unit_cd IN VARCHAR2,p_version_number IN NUMBER,p_alternate_code IN VARCHAR2,p_location_cd IN VARCHAR2, p_unit_class IN VARCHAR2,p_uso_id IN NUMBER) RETURN BOOLEAN AS
3979   /***********************************************************************************************
3980     Created By     :  sarakshi
3981     Date Created By:  20-Jun-2005.
3982     Purpose        :  This utility procedure is to check whether import is allowed in context to scheduling (overlodad function)
3983 
3984     Known limitations,enhancements,remarks:
3985     Change History (in reverse chronological order)
3986     Who         When            What
3987     sommukhe    15-NOV-2005     Bug# 4721543, Included the the check for cancelled status of unit section.
3988   ***********************************************************************************************/
3989 
3990 	l_c_cal_type igs_ps_unit_ofr_opt_all.cal_type%TYPE;
3991         l_n_seq_num  igs_ps_unit_ofr_opt_all.ci_sequence_number%TYPE;
3992         l_d_start_dt igs_ca_inst_all.start_dt%TYPE;
3993         l_d_end_dt   igs_ca_inst_all.end_dt%TYPE;
3994         l_c_message  VARCHAR2(30);
3995 	l_n_uoo_id   igs_ps_unit_ofr_opt_all.uoo_id%TYPE;
3996 
3997         CURSOR c_uso_chk(p_n_uso_id NUMBER) IS
3998         SELECT   schedule_status,abort_flag
3999         FROM   igs_ps_usec_occurs_all
4000         WHERE  unit_section_occurrence_id = p_n_uso_id;
4001 
4002 
4003         c_uso_chk_rec  c_uso_chk%ROWTYPE;
4004 
4005         CURSOR c_usec_chk(cp_cal_type IN VARCHAR2,
4006 	                  cp_seq_num  IN NUMBER) IS
4007         SELECT  abort_flag,unit_section_status
4008         FROM   igs_ps_unit_ofr_opt_all
4009         WHERE unit_cd = p_unit_cd
4010         AND version_number =  p_version_number
4011         AND cal_type = cp_cal_type
4012 	AND ci_sequence_number =cp_seq_num
4013         AND location_cd = p_location_cd
4014         AND unit_class = p_unit_class;
4015 
4016         c_usec_chk_rec c_usec_chk%ROWTYPE;
4017 
4018         CURSOR c_pattern_chk(cp_cal_type igs_ps_unit_ofr_opt_all.cal_type%TYPE,
4019 	                         cp_seq_num igs_ps_unit_ofr_opt_all.ci_sequence_number%TYPE,
4020 				 cp_version_number igs_ps_unit_ver_all.version_number%type,
4021 				 cp_unit_cd igs_ps_unit_ver_all.unit_cd%type
4022 				 ) IS
4023         SELECT 'X'
4024         FROM   igs_ps_unit_ofr_pat_all
4025 	WHERE   cal_type= cp_cal_type
4026 	AND     ci_sequence_number=cp_seq_num
4027 	AND     unit_cd = cp_unit_cd
4028 	AND     version_number=cp_version_number
4029 	AND     abort_flag = 'Y';
4030 
4031          c_pattern_chk_rec c_pattern_chk%ROWTYPE;
4032     BEGIN
4033 
4034       -- Derive Calander Type and Sequence Number
4035       igs_ge_gen_003.get_calendar_instance ( p_alternate_cd       => p_alternate_code,
4036                                              p_cal_type           => l_c_cal_type,
4037                                              p_ci_sequence_number => l_n_seq_num,
4038                                              p_start_dt           => l_d_start_dt,
4039                                              p_end_dt             => l_d_end_dt,
4040                                              p_return_status      => l_c_message );
4041       IF ( l_c_message <> 'SINGLE' ) THEN
4042          RETURN TRUE;
4043       END IF;
4044 
4045 
4046 
4047      --check if the corresponding occurrence record exists in production table with status as CANCELLED or the record is aborted.
4048 
4049      IF p_uso_id IS NOT NULL THEN
4050 
4051         OPEN c_uso_chk(p_uso_id);
4052         FETCH c_uso_chk INTO c_uso_chk_rec;
4053         IF c_uso_chk%FOUND  THEN
4054           IF (c_uso_chk_rec.schedule_status='CANCELLED' OR c_uso_chk_rec.abort_flag='Y' )  THEN
4055             CLOSE c_uso_chk;
4056 	    RETURN FALSE;
4057           ELSE
4058             CLOSE c_uso_chk;
4059     	    RETURN TRUE;
4060           END IF;
4061 	END IF;
4062         CLOSE c_uso_chk;
4063      END IF;
4064 
4065 
4066      --check if the corresponding unit section record exists in production table which is aborted.
4067      OPEN c_usec_chk(l_c_cal_type,l_n_seq_num);
4068      FETCH c_usec_chk INTO c_usec_chk_rec;
4069      IF c_usec_chk%FOUND  THEN
4070     	  IF (c_usec_chk_rec.abort_flag='Y' OR c_usec_chk_rec.unit_section_status='CANCELLED' ) THEN
4071            CLOSE c_usec_chk;
4072 	   RETURN FALSE;
4073           ELSE
4074            CLOSE c_usec_chk;
4075     	   RETURN TRUE;
4076           END IF;
4077      END IF;
4078      CLOSE c_usec_chk;
4079 
4080      --check if the corresponding pattern record exists in production  table which is aborted.
4081      OPEN c_pattern_chk(l_c_cal_type,l_n_seq_num,p_version_number,p_unit_cd);
4082      FETCH c_pattern_chk INTO c_pattern_chk_rec;
4083      IF c_pattern_chk%FOUND THEN
4084        CLOSE c_pattern_chk;
4085        RETURN FALSE;
4086      END IF;
4087      CLOSE c_pattern_chk;
4088 
4089      RETURN TRUE;
4090 
4091    END check_import_allowed;
4092 
4093   FUNCTION  check_import_allowed( p_uoo_id IN NUMBER,p_uso_id IN NUMBER) RETURN BOOLEAN AS
4094   /***********************************************************************************************
4095     Created By     :  sarakshi
4096     Date Created By:  20-Jun-2005.
4097     Purpose        :  This utility procedure is to check whether import is allowed in context to scheduling (overlodad function)
4098 
4099     Known limitations,enhancements,remarks:
4100     Change History (in reverse chronological order)
4101     Who         When            What
4102     sommukhe    15-NOV-2005     Bug# 4721543, Included the the check for cancelled status of unit section.
4103   ***********************************************************************************************/
4104         CURSOR c_uso_chk(cp_n_uso_id IN NUMBER) IS
4105         SELECT   schedule_status,abort_flag
4106         FROM   igs_ps_usec_occurs_all
4107         WHERE  unit_section_occurrence_id = cp_n_uso_id;
4108         c_uso_chk_rec  c_uso_chk%ROWTYPE;
4109 
4110         CURSOR c_usec_chk(cp_n_uoo_id IN NUMBER) IS
4111         SELECT  abort_flag,unit_section_status
4112         FROM   igs_ps_unit_ofr_opt_all
4113         WHERE  uoo_id = cp_n_uoo_id;
4114         c_usec_chk_rec c_usec_chk%ROWTYPE;
4115 
4116         CURSOR c_pattern_chk(cp_n_uoo_id IN NUMBER) IS
4117         SELECT 'X'
4118         FROM   igs_ps_unit_ofr_pat_all pt, igs_ps_unit_ofr_opt_all uoo
4119 	WHERE  uoo.uoo_id=  cp_n_uoo_id
4120 	AND    uoo.unit_cd=pt.unit_cd
4121 	AND    uoo.version_number=pt.version_number
4122 	AND    uoo.cal_type= pt.cal_type
4123 	AND    uoo.ci_sequence_number=pt.ci_sequence_number
4124 	AND    pt.abort_flag = 'Y';
4125 
4126        c_pattern_chk_rec c_pattern_chk%ROWTYPE;
4127     BEGIN
4128 
4129      --check if the corresponding occurrence record exists in production table with status as CANCELLED or the record is aborted.
4130      IF p_uso_id IS NOT NULL THEN
4131 
4132         OPEN c_uso_chk(p_uso_id);
4133         FETCH c_uso_chk INTO c_uso_chk_rec;
4134         IF c_uso_chk%FOUND  THEN
4135           IF (c_uso_chk_rec.schedule_status='CANCELLED' OR c_uso_chk_rec.abort_flag='Y' )  THEN
4136             CLOSE c_uso_chk;
4137 	    RETURN FALSE;
4138           ELSE
4139             CLOSE c_uso_chk;
4140     	    RETURN TRUE;
4141           END IF;
4142 	END IF;
4143         CLOSE c_uso_chk;
4144      END IF;
4145 
4146 
4147      --check if the corresponding unit section record exists in production table which is aborted.
4148      OPEN c_usec_chk(p_uoo_id);
4149      FETCH c_usec_chk INTO c_usec_chk_rec;
4150      IF c_usec_chk%FOUND  THEN
4151     	  IF (c_usec_chk_rec.abort_flag='Y' OR c_usec_chk_rec.unit_section_status='CANCELLED' ) THEN
4152            CLOSE c_usec_chk;
4153 	   RETURN FALSE;
4154           ELSE
4155            CLOSE c_usec_chk;
4156     	   RETURN TRUE;
4157           END IF;
4158      END IF;
4159      CLOSE c_usec_chk;
4160 
4161      --check if the corresponding pattern record exists in production  table which is aborted.
4162      OPEN c_pattern_chk(p_uoo_id);
4163      FETCH c_pattern_chk INTO c_pattern_chk_rec;
4164      IF c_pattern_chk%FOUND THEN
4165        CLOSE c_pattern_chk;
4166        RETURN FALSE;
4167      END IF;
4168      CLOSE c_pattern_chk;
4169 
4170      RETURN TRUE;
4171 
4172    END check_import_allowed;
4173 
4174 
4175    FUNCTION check_not_offered_usec_status(p_uoo_id IN NUMBER ) RETURN BOOLEAN AS
4176   /***********************************************************************************************
4177     Created By     :  sarakshi
4178     Date Created By:  20-Jun-2005.
4179     Purpose        :  This utility procedure is to check whether the unit section status is NOT_OFFERED
4180 
4181     Known limitations,enhancements,remarks:
4182     Change History (in reverse chronological order)
4183     Who         When            What
4184   ***********************************************************************************************/
4185     CURSOR c_usec_chk(cp_n_uoo_id IN NUMBER) IS
4186     SELECT  'X'
4187     FROM   igs_ps_unit_ofr_opt_all
4188     WHERE  uoo_id = cp_n_uoo_id
4189     AND    unit_section_status='NOT_OFFERED';
4190     l_c_var VARCHAR2(1);
4191   BEGIN
4192     OPEN c_usec_chk(p_uoo_id);
4193     FETCH c_usec_chk INTO l_c_var;
4194     IF c_usec_chk%FOUND THEN
4195       CLOSE c_usec_chk;
4196       RETURN FALSE;
4197     ELSE
4198       CLOSE c_usec_chk;
4199       RETURN TRUE;
4200     END IF;
4201 
4202   END check_not_offered_usec_status;
4203 
4204   FUNCTION boundary_check_number( p_n_value IN NUMBER,p_n_int_part IN NUMBER,p_n_dec_part IN NUMBER) RETURN BOOLEAN AS
4205   /***********************************************************************************************
4206     Created By     :  sarakshi
4207     Date Created By:  11-Jul-2005.
4208     Purpose        :  This utility procedure is to check whether a number is falling in a specifuc format mask
4209 
4210     Known limitations,enhancements,remarks:
4211     Change History (in reverse chronological order)
4212     Who         When            What
4213   ***********************************************************************************************/
4214     n2 NUMBER;
4215     a VARCHAR2(100);
4216     b VARCHAR2(100);
4217     c VARCHAR2(100);
4218   BEGIN
4219     a:= TO_CHAR(p_n_value);
4220     n2:= instr(a,'.');
4221     IF n2 > 0 THEN
4222       b:= substr(a,1,n2);
4223       c:= substr(a,n2);
4224 
4225       IF NVL(length(b),0) > (p_n_int_part+1)  OR  NVL(length(c),0) > (p_n_dec_part+1) THEN
4226         RETURN FALSE;
4227       END IF;
4228 
4229     END IF;
4230 
4231     RETURN TRUE;
4232 
4233   END boundary_check_number;
4234 
4235 END igs_ps_validate_lgcy_pkg;