DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_PS_UNIT_OFR_OPT_PKG

Source


1 package body IGS_PS_UNIT_OFR_OPT_PKG as
2 /* $Header: IGSPI85B.pls 120.6 2006/05/08 00:15:34 bdeviset ship $ */
3   /*************************************************************
4   -- Bug # 1956374 Procedure assp_val_gs_cur_fut reference is changed
5 
6    Created By : kdande@in
7    Date Created By :2000/05/11
8    Purpose :
9    Know limitations, enhancements or remarks
10    Change History
11    Who             When            What
12    vvutukur       05-Aug-2003     Enh#3045069.PSP Enh Build. Added new column not_multiple_section_flag.
13    rgangara       07-May-2001     Added Ss
14    (reverse chronological order - newest change first)
15   ***************************************************************/
16   l_rowid VARCHAR2(25);
17   old_references IGS_PS_UNIT_OFR_OPT_ALL%RowType;
18   new_references IGS_PS_UNIT_OFR_OPT_ALL%RowType;
19 
20   PROCEDURE beforerowdelete AS
21     ------------------------------------------------------------------
22     --Created by  : SMVK, Oracle India
23     --Date created: 08-Jan-2002
24     --
25     --Purpose: Only planned unit section status are allowed for deletion
26     --
27     --
28     --Known limitations/enhancements and/or remarks:
29     --
30     --Change History:
31     --Who         When            What
32     -------------------------------------------------------------------
33 
34   BEGIN
35     -- Only planned unit status are allowed for deletion
36     IF old_references.unit_section_status <> 'PLANNED' THEN
37       fnd_message.set_name('IGS','IGS_PS_USEC_NO_DEL_ALLOWED');
38       igs_ge_msg_stack.add;
39       app_exception.raise_exception;
40     END IF;
41 
42   END beforerowdelete;
43 
44 
45   PROCEDURE check_status_transition( p_n_uoo_id IN NUMBER,
46                                      p_c_old_usec_sts IN VARCHAR2,
47                                      p_c_new_usec_sts IN VARCHAR2) AS
48 
49     ------------------------------------------------------------------
50     --Created by  : smvk, Oracle India
51     --Date created: 30-Dec-2004
52     --
53     --Purpose: This procedure has the consolidated validation which deals with
54     --         unit section status transition.
55     --         Please refere the document Unit Section Status Tansistions.doc
56     --         available at the following location in OFO to understand unit section
57     --         status transition with respect to unit attempt statuses.
58     -- Oracle Student System Development  >  IGS.L  >  PSP  >  Administration
59     --Known limitations/enhancements and/or remarks:
60     --
61     --Change History:
62     --Who         When            What
63     --sommukhe    10-AUG-2005     Bug #4417223, Made the status transition from OPEN to HOLD as a valid one.
64     --smvk        30-Dec-2004     Bug #4089230, Created the procedure
65     -------------------------------------------------------------------
66 
67 
68      -- Cursor to check whether any unit attempt exists for the unit section with unit attempt status other than 'DISCONTIN' and 'DROPPED'.
69      CURSOR c_discontin(cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
70      SELECT  unit_attempt_status
71      FROM    igs_en_su_attempt_all
72      WHERE   uoo_id= cp_n_uoo_id
73      AND     unit_attempt_status NOT IN ('DISCONTIN', 'DROPPED')
74      AND     ROWNUM <2 ;
75 
76      l_c_unit_attempt_status  igs_en_su_attempt_all.unit_attempt_status%TYPE;
77 
78      -- Cursor to check whether any unit attempt exists for the unit section.
79      CURSOR c_exist (cp_n_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
80      SELECT 1
81      FROM   igs_en_su_attempt_all
82      WHERE  uoo_id = cp_n_uoo_id
83      AND    ROWNUM < 2 ;
84 
85      l_n_exist NUMBER;
86 
87      -- Cursor to check whether unit attempt exists for the unit section in unit attempt statuses
88      -- other than 'DISCONTIN','DROPPED','COMPLETED','DUPLICATE'
89      CURSOR c_enrollment_status(cp_n_uoo_id  igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
90      SELECT DISTINCT unit_attempt_status
91      FROM   igs_en_su_attempt_all
92      WHERE  uoo_id = cp_n_uoo_id
93      AND    unit_attempt_status NOT IN ('DISCONTIN','DROPPED','COMPLETED','DUPLICATE');
94 
95 
96      -- Cursor to get system unit status for the unit section.
97      CURSOR c_unit_sts (cp_n_uoo_id IN IGS_PS_UNIT_OFR_OPT_ALL.UOO_ID%TYPE) IS
98      SELECT a.s_unit_status
99      FROM   igs_ps_unit_stat a,
100             igs_ps_unit_ver_all b,
101             igs_ps_unit_ofr_opt_all c
102      WHERE  a.unit_status = b.unit_status
103      AND    b.unit_cd = c.unit_cd
104      AND    b.version_number = c.version_number
105      AND    c.uoo_id = cp_n_uoo_id;
106 
107      l_c_unit_status  IGS_PS_UNIT_STAT.S_UNIT_STATUS%TYPE;
108 
109      -- Internal function to get the meaning for the given lookup_type and lookup_code.
110      FUNCTION get_meaning(p_c_lookup_type IN VARCHAR2,
111                           p_c_lookup_code IN VARCHAR2) RETURN VARCHAR2 IS
112 
113        CURSOR c_meaning (cp_c_lookup_type IN VARCHAR2,
114                          cp_c_lookup_code IN VARCHAR2) IS
115        SELECT meaning
116        FROM   igs_lookup_values
117        WHERE  lookup_type = cp_c_lookup_type
118        AND    lookup_code = cp_c_lookup_code
119        AND    enabled_flag = 'Y'
120        AND    NVL(closed_ind,'N') = 'N'
121        AND    SYSDATE BETWEEN NVL(START_DATE_ACTIVE, SYSDATE) AND NVL(END_DATE_ACTIVE,SYSDATE);
122 
123        l_c_meaning igs_lookup_values.meaning%TYPE;
124 
125      BEGIN
126        OPEN c_meaning(p_c_lookup_type,p_c_lookup_code) ;
127        FETCH c_meaning INTO l_c_meaning;
128        CLOSE c_meaning;
129        RETURN l_c_meaning;
130      END get_meaning;
131 
132   BEGIN
133 
134     -- Any Other Statuses to 'PLANNED' is invalid - Overcome locking issue. (Status Codes 7,13,19,25,31,37)
135     IF p_c_new_usec_sts = 'PLANNED' AND
136        p_c_old_usec_sts <> 'PLANNED' THEN
137        fnd_message.set_name ('IGS','IGS_PS_USEC_STATUS_TO_PLANNED');
138        igs_ge_msg_stack.add;
139        app_exception.raise_exception;
140     END IF;
141 
142     -- get the unit version system status
143     l_c_unit_status := NULL;
144     OPEN c_unit_sts (p_n_uoo_id);
145     FETCH c_unit_sts INTO l_c_unit_status;
146     CLOSE c_unit_sts;
147 
148    -- if unit version is planned then it can have unit section in status 'PLANNED' or 'NOT_OFFERED'.
149     IF l_c_unit_status IS NOT NULL AND l_c_unit_status = 'PLANNED' AND
150        p_c_new_usec_sts NOT IN ('PLANNED', 'NOT_OFFERED') THEN
151        fnd_message.set_name ('IGS','IGS_PS_PLN_UNT_VER');
152        fnd_message.set_token('STATUS',get_meaning('UNIT_SECTION_STATUS', p_c_new_usec_sts));
153        igs_ge_msg_stack.add;
154        app_exception.raise_exception;
155     END IF;
156 
157     -- Following Status transition are invalid.
158     -- (2) PLANNED -> FULLWAITOK, (5) PLANNED -> CLOSED, (27) CANCELLED -> FULLWAITOK, (29) CANCELLED -> CLOSED
159     IF p_c_old_usec_sts IN ('CANCELLED','PLANNED') AND
160        p_c_new_usec_sts IN ('CLOSED', 'FULLWAITOK') THEN
161           fnd_message.set_name('IGS','IGS_PS_INVALID_STATE_TRANS' );
162           fnd_message.set_token('OLD_STATUS_DESC', get_meaning('UNIT_SECTION_STATUS',p_c_old_usec_sts));
163           fnd_message.set_token('NEW_STATUS_DESC', get_meaning('UNIT_SECTION_STATUS',p_c_new_usec_sts));
164           igs_ge_msg_stack.add;
165           app_exception.raise_exception;
166     END IF;
167 
168     -- Can reach 'HOLD' status only from FULLWAITOK,OPEN and CLOSED.
169     -- Following status transitions are valid
170     -- (15) FULLOWAITOK -> HOLD , (34) CLOSED -> HOLD  ,(9) OPEN -> HOLD,
171     -- Following status transitions are invalid
172     -- (3) PLANNED -> HOLD, (28) CANCELLED -> HOLD, (40) NOT_OFFERED -> HOLD
173     IF p_c_old_usec_sts NOT IN ('FULLWAITOK','CLOSED','OPEN') AND
174        p_c_new_usec_sts = 'HOLD' THEN
175           fnd_message.set_name('IGS','IGS_PS_INVALID_STATE_TRANS' );
176           fnd_message.set_token('OLD_STATUS_DESC', get_meaning('UNIT_SECTION_STATUS',p_c_old_usec_sts));
177           fnd_message.set_token('NEW_STATUS_DESC', get_meaning('UNIT_SECTION_STATUS',p_c_new_usec_sts));
178           igs_ge_msg_stack.add;
179           app_exception.raise_exception;
180     END IF;
181 
182 
183     -- Can Cancel the unit section status if it does not have unit attempt or have unit attempt in unit attempt status 'DISCONTIN' and/or 'DROPPED'.
184     -- (4) PLANNED -> CANCELLED, (10) OPEN -> CANCELLED, (16) FULLWAITOK -> CANCELLED, (22) HOLD -> CANCELLED, (35) CLOSED -> CANCELLED, (41) NOT_OFFERED -> CANCELLED
185     IF p_c_new_usec_sts = 'CANCELLED' THEN
186       OPEN c_discontin(p_n_uoo_id);
187       FETCH c_discontin INTO l_c_unit_attempt_status;
188       IF c_discontin%FOUND THEN
189         CLOSE c_discontin;
190         fnd_message.set_name('IGS','IGS_PS_USEC_STATUS_PLN_CNC');
191         fnd_message.set_token('SUASTATUS',get_meaning('UNIT_ATTEMPT_STATUS',l_c_unit_attempt_status));
192         -- IGS_PS_USEC_STATUS_CNC'); -- "Unit Section status cannot be changed to Cancelled as there exists student unit attempt which is not discontinued"
193         igs_ge_msg_stack.add;
194         app_exception.raise_exception;
195       END IF;
196       CLOSE c_discontin;
197     END IF;
198 
199     -- Can reach 'NOT_OFFERED' status only when unit section does not have student attempt (irrespective of unit attempt status)
200     -- (6) PLANNED -> NOT_OFFERED, (12) OPEN -> NOT_OFFERED, (18) FULLWAITOK -> NOT_OFFERED, (24) HOLD -> NOT_OFFERED, (30) CANCELLED -> NOT_OFFERED, (36) CLOSED -> NOT_OFFERED
201     IF p_c_new_usec_sts = 'NOT_OFFERED' THEN
202        OPEN c_exist(p_n_uoo_id);
203        FETCH c_exist INTO l_n_exist;
204        IF c_exist%FOUND THEN
205           CLOSE c_exist;
206           fnd_message.set_name ('IGS','IGS_PS_CNT_UPD_NOT_OFFERED');
207           igs_ge_msg_stack.add;
208           app_exception.raise_exception;
209         END IF;
210        CLOSE c_exist;
211     END IF;
212 
213     -- From NOT_OFFERED status only allowed status transition is 'OPEN', when the deactived calendar is activated.
214     -- (38) NOT_OFFERED -> OPEN Valid transition
215     -- (39) NOT_OFFERED -> FULLWAITOK,  (42) NOT_OFFERED -> CLOSED - Invalid transition
216     IF p_c_old_usec_sts = 'NOT_OFFERED' AND
217        p_c_new_usec_sts <> 'OPEN' THEN
218          fnd_message.set_name('IGS','IGS_PS_INVALID_STATE_TRANS' );
219          fnd_message.set_token('OLD_STATUS_DESC', get_meaning('UNIT_SECTION_STATUS',p_c_old_usec_sts));
220          fnd_message.set_token('NEW_STATUS_DESC', get_meaning('UNIT_SECTION_STATUS',p_c_new_usec_sts));
221          igs_ge_msg_stack.add;
222          app_exception.raise_exception;
223     END IF;
224 
225   END check_status_transition;
226 
227   PROCEDURE beforerowupdate AS
228     ------------------------------------------------------------------
229     --Created by  : smvk, Oracle India
230     --Date created: 03-Jan-2003
231     --
232     --Purpose: once the unit section status is changed to any other status
233     --         from planned, then it cannot go back to planned.
234     --
235     --
236     --Known limitations/enhancements and/or remarks:
237     --
238     --Change History:
239     --Who         When            What
240     --smvk        30-Dec-2005     Bug #4089230, Modified the procedure to call check_status_transition
241     --                            when the unit section is getting modified.
242     --sarakshi    26-Jul-2004     Bug#3793607, added validation regarding the unit section status
243     -------------------------------------------------------------------
244 
245   BEGIN
246      -- if the unit section status is getting modified, calling the procedure check_status_transition
247      -- to check whether the transition is valid.
248      IF new_references.unit_section_status <> old_references.unit_section_status THEN
249         check_status_transition( p_n_uoo_id       => new_references.uoo_id,
250                                  p_c_old_usec_sts => old_references.unit_section_status,
251                                  p_c_new_usec_sts => new_references.unit_section_status);
252      END IF;
253 
254   END beforerowupdate;
255 
256   PROCEDURE Set_Column_Values (
257     p_action IN VARCHAR2,
258     x_rowid IN VARCHAR2 ,
259     x_unit_cd IN VARCHAR2 ,
260     x_version_number IN NUMBER ,
261     x_cal_type IN VARCHAR2 ,
262     x_ci_sequence_number IN NUMBER ,
263     x_location_cd IN VARCHAR2 ,
264     x_unit_class IN VARCHAR2 ,
265     x_uoo_id IN NUMBER ,
266     x_ivrs_available_ind IN VARCHAR2 ,
267     x_call_number IN NUMBER ,
268     x_unit_section_status IN VARCHAR2 ,
269     x_unit_section_start_date IN DATE ,
270     x_unit_section_end_date IN DATE ,
271     x_enrollment_actual IN NUMBER ,
272     x_waitlist_actual IN NUMBER ,
273     x_offered_ind IN VARCHAR2 ,
274     x_state_financial_aid IN VARCHAR2 ,
275     x_grading_schema_prcdnce_ind IN VARCHAR2 ,
276     x_federal_financial_aid IN VARCHAR2 ,
277     x_unit_quota IN NUMBER ,
278     x_unit_quota_reserved_places IN NUMBER ,
279     x_institutional_financial_aid IN VARCHAR2 ,
280     x_unit_contact IN NUMBER ,
281     x_grading_schema_cd IN VARCHAR2 ,
282     x_gs_version_number IN NUMBER ,
283     x_owner_org_unit_cd                 IN     VARCHAR2 ,
284     x_attendance_required_ind           IN     VARCHAR2 ,
285     x_reserved_seating_allowed          IN     VARCHAR2 ,
286     x_special_permission_ind            IN     VARCHAR2 ,
287     x_ss_display_ind                    IN     VARCHAR2 ,
288     x_creation_date IN DATE ,
289     x_created_by IN NUMBER ,
290     x_last_update_date IN DATE ,
291     x_last_updated_by IN NUMBER ,
292     x_last_update_login IN NUMBER ,
293     x_org_id IN NUMBER ,
294     x_ss_enrol_ind IN VARCHAR2 ,
295     x_dir_enrollment IN NUMBER ,
296     x_enr_from_wlst  IN NUMBER ,
297     x_inq_not_wlst  IN NUMBER ,
298     x_rev_account_cd IN VARCHAR2 ,
299     x_anon_unit_grading_ind IN VARCHAR2 ,
300     x_anon_assess_grading_ind IN VARCHAR2 ,
301     X_NON_STD_USEC_IND IN VARCHAR2 ,
302     x_auditable_ind IN VARCHAR2,
303     x_audit_permission_ind IN VARCHAR2,
304     x_not_multiple_section_flag IN VARCHAR2,
305     x_sup_uoo_id IN NUMBER ,
306     x_relation_type VARCHAR2 ,
307     x_default_enroll_flag VARCHAR2,
308     x_abort_flag VARCHAR2
309 
310   ) AS
311   /*************************************************************
312    Created By : kdande@in
313    Date Created By :2000/05/11
314    Purpose :
315    Know limitations, enhancements or remarks
316    Change History
317    Who             When            What
318     vvutukur      05-Aug-2003     Enh#3045069.PSP Enh Build. Added column not_multiple_section_flag.
319     shtatiko      06-NOV-2001     Added auditable_ind and audit_permission_ind as part of Bug# 2636716.
320     rgangara      07-May-2001     Added ss_enrol_ind Col
321    (reverse chronological order - newest change first)
322   ***************************************************************/
323     CURSOR cur_old_ref_values IS
324       SELECT   *
325       FROM     IGS_PS_UNIT_OFR_OPT_ALL
326       WHERE    rowid = x_rowid;
327 
328   BEGIN
329 
330     l_rowid := x_rowid;
331 
332     -- Code for setting the Old and New Reference Values.
333     -- Populate Old Values.
334     Open cur_old_ref_values;
335     Fetch cur_old_ref_values INTO old_references;
336     IF (cur_old_ref_values%NOTFOUND) AND (p_action NOT IN ('INSERT','VALIDATE_INSERT')) THEN
337       Close cur_old_ref_values;
338       Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
339       IGS_GE_MSG_STACK.ADD;
340       App_Exception.Raise_Exception;
341       Return;
342     END IF;
343     Close cur_old_ref_values;
344 
345     -- Populate New Values.
346     new_references.unit_cd := x_unit_cd;
347     new_references.version_number := x_version_number;
348     new_references.cal_type := x_cal_type;
349     new_references.ci_sequence_number := x_ci_sequence_number;
350     new_references.location_cd := x_location_cd;
351     new_references.unit_class := x_unit_class;
352     new_references.uoo_id := x_uoo_id;
353     new_references.ivrs_available_ind := x_ivrs_available_ind;
354     new_references.call_number := x_call_number;
355     new_references.unit_section_status := x_unit_section_status;
356     new_references.unit_section_start_date := x_unit_section_start_date;
357     new_references.unit_section_end_date := x_unit_section_end_date;
358     new_references.enrollment_actual := x_enrollment_actual;
359     new_references.waitlist_actual := x_waitlist_actual;
360     new_references.offered_ind := x_offered_ind;
361     new_references.state_financial_aid := x_state_financial_aid;
362     new_references.grading_schema_prcdnce_ind := x_grading_schema_prcdnce_ind;
363     new_references.federal_financial_aid := x_federal_financial_aid;
364     new_references.unit_quota := x_unit_quota;
365     new_references.unit_quota_reserved_places := x_unit_quota_reserved_places;
366     new_references.institutional_financial_aid := x_institutional_financial_aid;
367     new_references.unit_contact := x_unit_contact;
368     new_references.grading_schema_cd := x_grading_schema_cd;
369     new_references.gs_version_number := x_gs_version_number;
370     new_references.owner_org_unit_cd := x_owner_org_unit_cd;
371     new_references.attendance_required_ind := x_attendance_required_ind;
372     new_references.reserved_seating_allowed := x_reserved_seating_allowed;
373     new_references.special_permission_ind := x_special_permission_ind;
374     new_references.ss_display_ind := x_ss_display_ind;
375     new_references.org_id:=x_org_id;
376     IF (p_action = 'UPDATE') THEN
377       new_references.creation_date := old_references.creation_date;
378       new_references.created_by := old_references.created_by;
379     ELSE
380       new_references.creation_date := x_creation_date;
381       new_references.created_by := x_created_by;
382     END IF;
383     new_references.last_update_date := x_last_update_date;
384     new_references.last_updated_by := x_last_updated_by;
385     new_references.last_update_login := x_last_update_login;
386     new_references.ss_enrol_ind := x_ss_enrol_ind;
387     new_references.dir_enrollment:=x_dir_enrollment;
388     new_references.enr_from_wlst:=x_enr_from_wlst;
389     new_references.inq_not_wlst:=x_inq_not_wlst;
390     new_references.rev_account_cd    := x_rev_account_cd;
391     new_references.anon_unit_grading_ind := x_anon_unit_grading_ind;
392     new_references.anon_assess_grading_ind := x_anon_assess_grading_ind;
393     new_references.non_std_usec_ind := x_non_std_usec_ind;
394     new_references.auditable_ind := x_auditable_ind;
395     new_references.audit_permission_ind := x_audit_permission_ind;
396     new_references.not_multiple_section_flag := x_not_multiple_section_flag;
397     new_references.sup_uoo_id:= x_sup_uoo_id;
398     new_references.relation_type:= x_relation_type;
399     new_references.default_enroll_flag:= x_default_enroll_flag;
400     new_references.abort_flag:= x_abort_flag;
401 
402   END Set_Column_Values;
403 
404   PROCEDURE BeforeRowInsertUpdateDelete1(
405     p_inserting IN BOOLEAN ,
406     p_updating IN BOOLEAN ,
407     p_deleting IN BOOLEAN
408     ) AS
409         v_unit_cd                       IGS_PS_UNIT_OFR_OPT_ALL.unit_cd%TYPE;
410         v_version_number                IGS_PS_UNIT_OFR_OPT_ALL.version_number%TYPE;
411         v_cal_type              IGS_PS_UNIT_OFR_OPT_ALL.cal_type%TYPE;
412         v_ci_sequence_number    IGS_PS_UNIT_OFR_OPT_ALL.ci_sequence_number%TYPE;
413         v_message_name          Varchar2(30);
414   BEGIN
415 
416         -- Validation : Unit Section Start Date is mandatory for Non Standard Unit Section
417         -- Added as a part of Non Standard Unit Section Retention date build.
418         IF (p_inserting OR p_updating) AND
419             ( NVL(new_references.non_std_usec_ind,'N') = 'Y' AND
420                   new_references.unit_section_start_date IS NULL
421              )THEN
422            fnd_message.set_name ('IGS','IGS_EN_OFFSET_DT_NULL');
423            igs_ge_msg_stack.add;
424            app_exception.raise_exception;
425         END IF;
426 
427         -- Set variables.
428         IF p_deleting THEN
429                 v_unit_cd := old_references.unit_cd;
430                 v_version_number := old_references.version_number;
431                 v_cal_type := old_references.cal_type;
432                 v_ci_sequence_number := old_references.ci_sequence_number;
433         ELSE -- p_inserting or p_updating
434                 v_unit_cd := new_references.unit_cd;
435                 v_version_number := new_references.version_number;
436                 v_cal_type := new_references.cal_type;
437                 v_ci_sequence_number := new_references.ci_sequence_number;
438         END IF;
439         -- Validate the insert/update/delete.
440         IF IGS_PS_VAL_UNIT.crsp_val_iud_uv_dtl (
441                         v_unit_cd,
442                         v_version_number,
443 v_message_name) = FALSE THEN
444                 Fnd_Message.Set_Name('IGS',v_message_name);
445       IGS_GE_MSG_STACK.ADD;
446                 App_Exception.Raise_Exception;
447         END IF;
448 --      IF IGS_aS_VAL_uai.crsp_val_crs_ci (
449 --                      v_cal_type,
450 --                      v_ci_sequence_number,
451 --                      v_message_num) = FALSE THEN
452 --              raise_application_error(-20000, IGS_GE_GEN_002.GENP_GET_MESSAGE(374));
453 --      END IF;
454         IF p_inserting THEN
455                 -- Validate calendar type.
456                 -- As part of the bug# 1956374 changed to the below call from IGS_PS_VAL_UOo.crsp_val_uo_cal_type
457                 IF IGS_AS_VAL_UAI.crsp_val_uo_cal_type (
458                                 new_references.cal_type,
459                                 v_message_name) = FALSE THEN
460                                 Fnd_Message.Set_Name('IGS','IGS_PS_UOO_UAI_CANNOT_CREATE');
461       IGS_GE_MSG_STACK.ADD;
462                                 App_Exception.Raise_Exception;
463                 END IF;
464                 -- Validate IGS_AD_LOCATION code.  IGS_AD_LOCATION code is not updateable.
465                 IF IGS_PS_VAL_UOo.crsp_val_loc_cd (
466                                 new_references.location_cd,
467 v_message_name) = FALSE THEN
468                 Fnd_Message.Set_Name('IGS',v_message_name);
469       IGS_GE_MSG_STACK.ADD;
470                 App_Exception.Raise_Exception;
471                 END IF;
472                 -- Validate IGS_PS_UNIT class.  IGS_PS_UNIT class is not updateable.
473                 IF IGS_PS_VAL_UOo.crsp_val_uoo_uc (
474                                 new_references.unit_class,
475 v_message_name) = FALSE THEN
476                 Fnd_Message.Set_Name('IGS',v_message_name);
477       IGS_GE_MSG_STACK.ADD;
478                 App_Exception.Raise_Exception;
479                 END IF;
480         END IF;
481         IF p_inserting OR p_updating THEN
482                 -- Validate grading schema.
483                 IF IGS_AS_VAL_GSG.assp_val_gs_cur_fut (
484                                 new_references.grading_schema_cd,
485                                 new_references.gs_version_number,
486 v_message_name) = FALSE THEN
487                 Fnd_Message.Set_Name('IGS',v_message_name);
488       IGS_GE_MSG_STACK.ADD;
489                 App_Exception.Raise_Exception;
490                 END IF;
491         END IF;
492         -- Validate IGS_PS_UNIT contact.
493         IF new_references.unit_contact IS NOT NULL AND
494                 (NVL(old_references.unit_contact, 0) <> new_references.unit_contact) THEN
495                 IF igs_ad_val_acai.genp_val_staff_prsn (
496                                 new_references.unit_contact,
497 v_message_name) = FALSE THEN
498                 Fnd_Message.Set_Name('IGS',v_message_name);
499       IGS_GE_MSG_STACK.ADD;
500                 App_Exception.Raise_Exception;
501                 END IF;
502         END IF;
503 
504         -- Validate that atleast one enrollment method is checked
505         IF p_inserting or p_updating THEN
506               IF NOT (new_references.ss_enrol_ind = 'Y' or new_references.ivrs_available_ind = 'Y') THEN
507                    Fnd_Message.Set_Name('IGS','IGS_PS_ONE_UNIT_ENR_MTHD');
508                    IGS_GE_MSG_STACK.ADD;
509                    App_Exception.Raise_Exception;
510               END IF;
511         END IF;
512 
513        --Record cannot be updated if the values of location_cd and unit_class unit_class r different
514        IF p_updating THEN
515          IF new_references.location_cd<> old_references.location_cd OR
516            new_references.unit_class<> old_references.unit_class THEN
517              Fnd_message.Set_Name('IGS','IGS_PS_UPDN_LOCCD_UNTCLS');
518              IGS_GE_MSG_STACK.ADD;
519              App_Exception.Raise_Exception;
520         END IF;
521       END IF;
522   END BeforeRowInsertUpdateDelete1;
523 
524 FUNCTION  check_call_number (p_teach_cal_type igs_ca_teach_to_load_v.teach_cal_type%TYPE,
525                              p_teach_sequence_num igs_ca_teach_to_load_v.teach_ci_sequence_number%TYPE,
526                              p_call_number  igs_ps_unit_ofr_opt_pe_v.call_number%TYPE,
527                              p_rowid   VARCHAR2)
528 RETURN BOOLEAN AS
529   /*************************************************************
530    Created By : sarakshi
531    Date Created By :9-Apr-2002
532    Purpose :To create unique call number across a load calendar as a part of bug#1689872
533    Know limitations, enhancements or remarks
534    Change History
535    Who             When            What
536    --sarakshi      17-sep-2003     Bug#3060094,removed cursor cur_parent and changed the view igs_ps_unit_ofr_opt_pe_v
537                                    to igs_pe_unit_ofr_opt_all in the cursor cur_detail.
538    (reverse chronological order - newest change first)
539   ***************************************************************/
540 
541 CURSOR cur_teach_load(cp_cal_type        igs_ca_teach_to_load_v.teach_cal_type%TYPE,
542                       cp_sequence_number igs_ca_teach_to_load_v.teach_ci_sequence_number%TYPE)  IS
543 SELECT load_cal_type,load_ci_sequence_number
544 FROM   igs_ca_teach_to_load_v
545 WHERE  teach_cal_type=cp_cal_type
546 AND    teach_ci_sequence_number=cp_sequence_number;
547 
548 CURSOR  cur_load_teach(cp_cal_type         igs_ca_load_to_teach_v.load_cal_type%TYPE,
549                        cp_sequence_number  igs_ca_load_to_teach_v.load_ci_sequence_number%TYPE) IS
550 SELECT  teach_cal_type,teach_ci_sequence_number
551 FROM    igs_ca_load_to_teach_v
552 WHERE   load_cal_type=cp_cal_type
553 AND     load_ci_sequence_number=cp_sequence_number;
554 
555 CURSOR  cur_detail (cp_cal_type         igs_ps_unit_ofr_opt_all.cal_type%TYPE,
556                     cp_sequence_number  igs_ps_unit_ofr_opt_all.ci_sequence_number%TYPE) IS
557 SELECT  'X'
558 FROM    igs_ps_unit_ofr_opt_all
559 WHERE   cal_type=cp_cal_type
560 AND     ci_sequence_number=cp_sequence_number
561 AND     call_number=p_call_number
562 AND    (rowid <> p_rowid OR (p_rowid IS NULL))
563 AND     ROWNUM = 1;
564 
565 l_c_var  VARCHAR2(1);
566 
567 BEGIN
568   FOR l_cur_teach_load IN cur_teach_load(p_teach_cal_type,p_teach_sequence_num) LOOP
569     FOR l_cur_load_teach IN cur_load_teach(l_cur_teach_load.load_cal_type,l_cur_teach_load.load_ci_sequence_number) LOOP
570         OPEN cur_detail(l_cur_load_teach.teach_cal_type,l_cur_load_teach.teach_ci_sequence_number);
571         FETCH cur_detail INTO l_c_var;
572         IF cur_detail%FOUND THEN
573           CLOSE cur_detail;
574           RETURN FALSE;
575         END IF;
576         CLOSE cur_detail;
577     END LOOP;
578   END LOOP;
579   --call number is unique
580   RETURN TRUE;
581 
582 END check_call_number;
583 
584 PROCEDURE Check_Uniqueness AS
585   /*************************************************************
586    Created By : kdande@in
587    Date Created By : 2000/05/11
588    Purpose :
589    Know limitations, enhancements or remarks
590    Change History
591    Who             When            What
592    sarakshi        09-Apr-2002     Removed the unique key igs_ps_unit_ofr_opt_all_uk2, hence removing the
593                                    call to the get_uk2_for_validation , bug#1689872
594    (reverse chronological order - newest change first)
595   ***************************************************************/
596 BEGIN
597 
598         IF Get_UK_For_Validation (new_references.uoo_id) THEN
599                         Fnd_Message.Set_Name ('IGS', 'IGS_GE_MULTI_ORG_DUP_REC');
600                 IGS_GE_MSG_STACK.ADD;
601                     App_Exception.Raise_Exception;
602         END IF;
603 
604 END Check_Uniqueness;
605 
606 PROCEDURE Check_Constraints(
607                                 Column_Name     IN      VARCHAR2   ,
608                                 Column_Value    IN      VARCHAR2   )
609 AS
610   /*************************************************************
611    Created By : kdande@in
612    Date Created By : 2000/05/11
613    Purpose :
614    Know limitations, enhancements or remarks
615    Change History
616    Who             When            What
617    vvutukur        05-Aug-2003     Enh#3045069.PSP Enh Build. Added validation
618                                    to restrict values of new column not_multiple_section_flag to either 'Y' or 'N'.
619    shtatiko        25-NOV-2002     Changed the validating condition of unit_quota and ci_sequence_number
620                                    (Bug# 2649028, Legacy Data Import)
621    (reverse chronological order - newest change first)
622   ***************************************************************/
623 BEGIN
624 
625         IF Column_Name IS NULL Then
626                 NULL;
627         ELSIF Upper(Column_Name)='CAL_TYPE' Then
628                 New_References.Cal_Type := Column_Value;
629         ELSIF Upper(Column_Name)='GRADING_SCHEMA_CD' Then
630                 New_References.Grading_Schema_Cd := Column_Value;
631         ELSIF Upper(Column_Name)='GRADING_SCHEMA_PRCDNCE_IND' Then
632                 New_References.grading_schema_prcdnce_ind := Column_Value;
633         ELSIF Upper(Column_Name)='IVRS_AVAILABLE_IND' Then
634                 New_References.ivrs_available_ind := Column_Value;
635         ELSIF Upper(Column_Name)='LOCATION_CD' Then
636                 New_References.Location_Cd := Column_Value;
637         ELSIF Upper(Column_Name)='OFFERED_IND' Then
638                 New_References.Offered_ind := Column_Value;
639         ELSIF Upper(Column_Name)='UNIT_CD' Then
640                 New_References.Unit_Cd := Column_Value;
641         ELSIF Upper(Column_Name)='UNIT_CLASS' Then
642                 New_References.Unit_Class := Column_Value;
643         ELSIF Upper(Column_Name)='UNIT_QUOTA' Then
644                 New_References.Unit_Quota := igs_ge_number.to_num(Column_Value);
645         ELSIF Upper(Column_Name)='CI_SEQUENCE_NUMBER' Then
646                 New_References.Ci_Sequence_Number := igs_ge_number.to_num(Column_Value);
647         ELSIF Upper(Column_Name)='SS_ENROL_IND' THEN
648                 New_References.Ss_enrol_ind := Column_value;
649         ELSIF Upper(Column_Name)= 'NON_STD_USEC_IND' THEN
650                 New_References.Non_std_usec_ind := Column_value;
651         ELSIF Upper(Column_Name)= 'AUDITABLE_IND' THEN
652                 New_References.auditable_ind := Column_value;
653         ELSIF Upper(Column_Name)= 'AUDIT_PERMISSION_IND' THEN
654                 New_References.audit_permission_ind := Column_value;
655         ELSIF UPPER(column_name)= 'NOT_MULTIPLE_SECTION_FLAG' THEN
656                 new_references.not_multiple_section_flag := column_value;
657         ELSIF UPPER(column_name)= 'DEFAULT_ENROLL_FLAG' THEN
658                 new_references.default_enroll_flag:= column_value;
659         ELSIF UPPER(column_name)= 'ABORT_FLAG' THEN
660                 new_references.abort_flag:= column_value;
661         END IF;
662 
663 
664         IF Upper(Column_Name)='CAL_TYPE' OR Column_Name IS NULL Then
665                 IF New_References.Cal_Type <> UPPER(New_References.Cal_Type) Then
666                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
667                                 IGS_GE_MSG_STACK.ADD;
668                                 App_Exception.Raise_Exception;
669                 END IF;
670         END IF;
671 
672         IF Upper(Column_Name)='GRADING_SCHEMA_CD' OR Column_Name IS NULL Then
673                 IF New_References.Grading_Schema_Cd <> UPPER(New_References.Grading_Schema_Cd) Then
674                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
675                                 IGS_GE_MSG_STACK.ADD;
676                                 App_Exception.Raise_Exception;
677                 END IF;
678         END IF;
679 
680         IF Upper(Column_Name)='GRADING_SCHEMA_PRCDNCE_IND' OR Column_Name IS NULL Then
681 
682                 IF New_References.grading_schema_prcdnce_ind NOT IN ( 'Y' , 'N' ) Then
683                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
684                                 IGS_GE_MSG_STACK.ADD;
685                                 App_Exception.Raise_Exception;
686                 END IF;
687 
688         END IF;
689 
690         IF Upper(Column_Name)='IVRS_AVAILABLE_IND' OR Column_Name IS NULL Then
691 
692                 IF New_References.ivrs_available_ind NOT IN ( 'Y' , 'N' ) Then
693                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
694                                 IGS_GE_MSG_STACK.ADD;
695                                 App_Exception.Raise_Exception;
696                 END IF;
697 
698         END IF;
699 
700         IF Upper(Column_Name)='OFFERED_IND' OR Column_Name IS NULL Then
701 
702                 IF New_References.Offered_ind NOT IN ( 'Y' , 'N' ) Then
703                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
704                                 IGS_GE_MSG_STACK.ADD;
705                                 App_Exception.Raise_Exception;
706                 END IF;
707 
708         END IF;
709 
710         IF Upper(Column_Name)='LOCATION_CD' OR Column_Name IS NULL Then
711                 IF New_References.Location_Cd <> UPPER(New_References.Location_Cd) Then
712                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
713                                 IGS_GE_MSG_STACK.ADD;
714                                 App_Exception.Raise_Exception;
715                 END IF;
716         END IF;
717 
718         IF Upper(Column_Name)='UNIT_CD' OR Column_Name IS NULL Then
719                 IF New_References.Unit_Cd <> UPPER(New_References.Unit_CD) Then
720                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
721                                 IGS_GE_MSG_STACK.ADD;
722                                 App_Exception.Raise_Exception;
723                 END IF;
724         END IF;
725 
726         IF Upper(Column_Name)='UNIT_CLASS' OR Column_Name IS NULL Then
727                 IF New_References.Unit_Class <> UPPER(New_References.Unit_Class) Then
728                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
729                                 IGS_GE_MSG_STACK.ADD;
730                                 App_Exception.Raise_Exception;
731                 END IF;
732         END IF;
733 
734         IF Upper(Column_Name)='UNIT_QUOTA' OR Column_Name IS NULL Then
735                 IF New_References.Unit_Quota < 0 OR New_References.Unit_Quota > 999999 Then
736                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
737                                 IGS_GE_MSG_STACK.ADD;
738                                 App_Exception.Raise_Exception;
739                 END IF;
740         END IF;
741 
742         IF Upper(Column_Name)='CI_SEQUENCE_NUMBER' OR Column_Name IS NULL Then
743                 IF New_References.Ci_sequence_Number < 1 OR New_References.Ci_sequence_Number > 999999 Then
744                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
745                                 IGS_GE_MSG_STACK.ADD;
746                                 App_Exception.Raise_Exception;
747                 END IF;
748         END IF;
749 
750 
751         -- Validate that atleast one enrollment method is checked
752         IF (Upper(Column_Name)='SS_ENROL_IND' OR Upper(Column_Name)='IVRS_AVAILABLE_IND') OR Column_Name is NULL THEN
753               IF NOT (new_references.ss_enrol_ind = 'Y' OR new_references.ivrs_available_ind = 'Y') THEN
754                    Fnd_Message.Set_Name('IGS','IGS_PS_ONE_UNIT_ENR_MTHD');
755                    IGS_GE_MSG_STACK.ADD;
756                    App_Exception.Raise_Exception;
757               END IF;
758         END IF;
759 
760         -- Added by Prem Raj for the build of PSCR017 bug #2224366
761         -- To check that NON_STD_USEC_IND should have a value in 'Y' or 'N'
762         IF Upper(Column_Name)= 'NON_STD_USEC_IND' OR Column_Name IS NULL Then
763           IF New_References.Non_std_usec_ind NOT IN ( 'Y' , 'N' ) Then
764             Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
765             IGS_GE_MSG_STACK.ADD;
766             App_Exception.Raise_Exception;
767           END IF;
768         END IF;
769 
770         --Added by shtatiko as part of Bug# 2636716, EN Integration
771         IF Upper(Column_Name)= 'AUDITABLE_IND' OR Column_Name IS NULL Then
772           IF New_References.auditable_ind NOT IN ( 'Y' , 'N' ) Then
773             Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
774             IGS_GE_MSG_STACK.ADD;
775             App_Exception.Raise_Exception;
776           END IF;
777         END IF;
778 
779         IF Upper(Column_Name)= 'AUDIT_PERMISSION_IND' OR Column_Name IS NULL Then
780           IF New_References.audit_permission_ind NOT IN ( 'Y' , 'N' ) Then
781             Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
782             IGS_GE_MSG_STACK.ADD;
783             App_Exception.Raise_Exception;
784           END IF;
785         END IF;
786 
787         IF Upper(Column_Name)='UNIT_QUOTA_RESERVED_PLACES' OR Column_Name IS NULL Then
788                 IF New_References.unit_quota_reserved_places < 0 OR New_References.unit_quota_reserved_places > 999999 Then
789                                 Fnd_Message.Set_Name ('IGS', 'IGS_GE_INVALID_VALUE');
790                                 IGS_GE_MSG_STACK.ADD;
791                                 App_Exception.Raise_Exception;
792                 END IF;
793         END IF;
794 
795         IF UPPER(column_name)= 'NOT_MULTIPLE_SECTION_FLAG' OR column_name IS NULL THEN
796           IF new_references.not_multiple_section_flag NOT IN ('Y','N') THEN
797             fnd_message.set_name('IGS','IGS_GE_INVALID_VALUE');
798             igs_ge_msg_stack.add;
799             app_exception.raise_exception;
800           END IF;
801         END IF;
802 
803         IF UPPER(column_name)= 'DEFAULT_ENROLL_FLAG' OR column_name IS NULL THEN
804           IF new_references.default_enroll_flag NOT IN ('Y','N') THEN
805             fnd_message.set_name('IGS','IGS_GE_INVALID_VALUE');
806             igs_ge_msg_stack.add;
807             app_exception.raise_exception;
808           END IF;
809         END IF;
810 
811 	IF UPPER(column_name)= 'ABORT_FLAG' OR column_name IS NULL THEN
812           IF new_references.abort_flag NOT IN ('Y','N') THEN
813             fnd_message.set_name('IGS','IGS_GE_INVALID_VALUE');
814             igs_ge_msg_stack.add;
815             app_exception.raise_exception;
816           END IF;
817         END IF;
818 
819   END Check_Constraints;
820 
821 
822   PROCEDURE Check_Parent_Existance AS
823   CURSOR c_check_hz_exists IS
824   SELECT 'x' FROM hz_parties hp,igs_pe_hz_parties pe
825   WHERE hp.party_id = pe.party_id
826   AND pe.oss_org_unit_cd =new_references.owner_org_unit_cd;
827   cur_rec_hz_exists c_check_hz_exists%ROWTYPE;
828   /*************************************************************
829    Created By : kdande@in
830    Date Created By : 2000/05/11
831    Purpose :
832    Know limitations, enhancements or remarks
833    Change History
834    Who             When            What
835   sommukhe      12-AUG-2005	  Bug#4377818,changed the cursor c_check_hz_exists, included table igs_pe_hz_parties in
836 				  FROM clause and modified the WHERE clause by joining HZ_PARTIES and IGS_PE_HZ_PARTIES
837 				  using party_id and org unit being compared with oss_org_unit_cd of IGS_PE_HZ_PARTIES.
838   smadathi       25-MAY-2001      foreign key references to IGS_PS_USEC_RPT_FMLY removed as per new DLD
839    (reverse chronological order - newest change first)
840   ***************************************************************/
841   BEGIN
842 
843     IF (((old_references.grading_schema_cd = new_references.grading_schema_cd) AND
844          (old_references.gs_version_number = new_references.gs_version_number)) OR
845         ((new_references.grading_schema_cd IS NULL) OR
846          (new_references.gs_version_number IS NULL))) THEN
847       NULL;
848     ELSE
849       IF NOT IGS_AS_GRD_SCHEMA_PKG.Get_PK_For_Validation (
850         new_references.grading_schema_cd,
851         new_references.gs_version_number) THEN
852                                   Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
853                           IGS_GE_MSG_STACK.ADD;
854                           App_Exception.Raise_Exception;
855         END IF;
856 
857     END IF;
858 
859     IF (((old_references.location_cd = new_references.location_cd)) OR
860         ((new_references.location_cd IS NULL))) THEN
861       NULL;
862     ELSE
863       IF NOT IGS_AD_LOCATION_PKG.Get_PK_For_Validation (
864         new_references.location_cd, 'N') THEN
865                                     Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
866                                 IGS_GE_MSG_STACK.ADD;
867                                 App_Exception.Raise_Exception;
868         END IF;
869 
870     END IF;
871 
872     IF (((old_references.unit_contact = new_references.unit_contact)) OR
873         ((new_references.unit_contact IS NULL))) THEN
874       NULL;
875     ELSE
876       IF NOT IGS_PE_PERSON_PKG.Get_PK_For_Validation (
877         new_references.unit_contact) THEN
878                                     Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
879                                 IGS_GE_MSG_STACK.ADD;
880                                 App_Exception.Raise_Exception;
881         END IF;
882 
883     END IF;
884 
885     IF (((old_references.unit_class = new_references.unit_class)) OR
886         ((new_references.unit_class IS NULL))) THEN
887       NULL;
888     ELSE
889       IF NOT IGS_AS_UNIT_CLASS_PKG.Get_PK_For_Validation (
890         new_references.unit_class) THEN
891                                     Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
892                                 IGS_GE_MSG_STACK.ADD;
893                                 App_Exception.Raise_Exception;
894         END IF;
895 
896     END IF;
897 
898     IF (((old_references.unit_cd = new_references.unit_cd) AND
899          (old_references.version_number = new_references.version_number) AND
900          (old_references.cal_type = new_references.cal_type) AND
901          (old_references.ci_sequence_number = new_references.ci_sequence_number)) OR
902         ((new_references.unit_cd IS NULL) OR
903          (new_references.version_number IS NULL) OR
904          (new_references.cal_type IS NULL) OR
905          (new_references.ci_sequence_number IS NULL))) THEN
906       NULL;
907     ELSE
908           IF NOT IGS_PS_UNIT_OFR_PAT_PKG.Get_PK_For_Validation (
909         new_references.unit_cd,
910         new_references.version_number,
911         new_references.cal_type,
912         new_references.ci_sequence_number)  THEN
913                                     Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
914                                 IGS_GE_MSG_STACK.ADD;
915                                 App_Exception.Raise_Exception;
916         END IF;
917 
918     END IF;
919 
920 
921     IF (((old_references.owner_org_unit_cd = new_references.owner_org_unit_cd)) OR
922         ((new_references.owner_org_unit_cd IS NULL))) THEN
923       NULL;
924     ELSE
925         OPEN c_check_hz_exists;
926         FETCH c_check_hz_exists INTO cur_rec_hz_exists;
927         IF c_check_hz_exists%NOTFOUND THEN
928           CLOSE c_check_hz_exists;
929           fnd_message.set_name ('FND', 'FORM_RECORD_DELETED');
930           igs_ge_msg_stack.add;
931           app_exception.raise_exception;
932         ELSE
933               CLOSE c_check_hz_exists;
934         END IF;
935      END IF;
936 
937     IF ((old_references.rev_account_cd = new_references.rev_account_cd) OR
938          (new_references.rev_account_cd IS NULL)) THEN
939       NULL;
940     ELSE
941       IF NOT IGS_FI_ACC_PKG.Get_PK_For_Validation (
942                new_references.rev_account_cd
943                ) THEN
944         Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
945         IGS_GE_MSG_STACK.ADD;
946         App_Exception.Raise_Exception;
947       END IF;
948     END IF;
949 
950     --check the existance of sup_uoo_id as a uoo_id
951     IF ((old_references.sup_uoo_id = new_references.sup_uoo_id) OR
952          (new_references.sup_uoo_id IS NULL)) THEN
953       NULL;
954     ELSE
955       IF NOT Get_UK_For_Validation (
956                new_references.sup_uoo_id
957                ) THEN
958         Fnd_Message.Set_Name ('FND', 'FORM_RECORD_DELETED');
959         IGS_GE_MSG_STACK.ADD;
960         App_Exception.Raise_Exception;
961       END IF;
962     END IF;
963 
964   END Check_Parent_Existance;
965 
966   FUNCTION get_call_number ( p_c_cal_type IN igs_ca_type.cal_type%TYPE,
967                              p_n_seq_num IN igs_ca_inst_all.sequence_number%TYPE ) RETURN NUMBER AS
968 
969      -- Cursor to lock all the load calendars for the given teaching calendar instance
970      -- in the table igs_ps_usec_cal_nums
971      CURSOR c_loc_cal_num (cp_c_cal_type IN VARCHAR2,
972                            cp_n_seq_num IN NUMBER) IS
973      SELECT call_number
974      FROM igs_ps_usec_cal_nums a,
975           igs_ca_teach_to_load_v b
976      WHERE a.calender_type = b.load_cal_type AND
977            a.ci_sequence_number = b.load_ci_sequence_number AND
978            b.teach_cal_type = cp_c_cal_type AND
979            b.teach_ci_sequence_number = cp_n_seq_num
980      FOR UPDATE OF call_number;
981 
982      -- Cursor to get the maximum call number across different load calendars for the given teaching calendar instance
983      CURSOR c_max_cal_num (cp_c_cal_type IN VARCHAR2,
984                            cp_n_seq_num IN NUMBER) IS
985      SELECT MAX(call_number)
986      FROM igs_ps_usec_cal_nums a,
987           igs_ca_teach_to_load_v b
988      WHERE a.calender_type = b.load_cal_type AND
989            a.ci_sequence_number = b.load_ci_sequence_number AND
990          b.teach_cal_type = cp_c_cal_type AND
991          b.teach_ci_sequence_number = cp_n_seq_num;
992 
993      -- Cursor to get the information of igs_ps_usec_cal_nums record, for updating the record
994      CURSOR c_call_number ( cp_cal_type igs_ca_type.cal_type%TYPE,
995                             cp_seq_num igs_ca_inst_all.sequence_number%TYPE ) IS
996      SELECT rowid ROW_ID, unit_section_call_number_id call_id
997      FROM   igs_ps_usec_cal_nums
998      WHERE  calender_type = cp_cal_type AND
999            ci_sequence_number = cp_seq_num;
1000 
1001      rec_call_number c_call_number%ROWTYPE;
1002 
1003      -- Cursor to get load claendar instance information for creating new records in igs_ps_usec_cal_nums
1004      CURSOR c_teach_to_load ( cp_cal_type igs_ca_type.cal_type%TYPE,
1005                               cp_seq_num igs_ca_inst_all.sequence_number%TYPE ) IS
1006      SELECT load_cal_type lcal_type, load_ci_sequence_number lseq_num
1007      FROM igs_ca_teach_to_load_v
1008      WHERE
1009      teach_cal_type = cp_cal_type AND
1010      teach_ci_sequence_number = cp_seq_num;
1011 
1012      -- Gets the maximum call number
1013      l_n_max_cal_num igs_ps_usec_cal_nums.call_number%TYPE;
1014      l_c_rowid ROWID;
1015      l_n_usc_number_id igs_ps_usec_cal_nums.unit_section_call_number_id%TYPE;
1016 
1017   BEGIN
1018 
1019     SAVEPOINT  IGS_PS_USEC_CAL_NUMS;
1020 
1021     OPEN c_loc_cal_num (p_c_cal_type,p_n_seq_num);
1022     FETCH c_loc_cal_num INTO l_n_max_cal_num;
1023     CLOSE c_loc_cal_num;
1024 
1025     l_n_max_cal_num := NULL;
1026 
1027     OPEN c_max_cal_num (p_c_cal_type,p_n_seq_num);
1028     FETCH c_max_cal_num INTO l_n_max_cal_num;
1029     CLOSE c_max_cal_num;
1030 
1031     l_n_max_cal_num := NVL(l_n_max_cal_num,0);
1032     l_n_max_cal_num := l_n_max_cal_num + 1;
1033 
1034     FOR rec_teach_to_load IN c_teach_to_load(p_c_cal_type,p_n_seq_num) LOOP
1035         OPEN c_call_number (rec_teach_to_load.lcal_type,rec_teach_to_load.lseq_num);
1036         FETCH c_call_number INTO rec_call_number;
1037         IF c_call_number%FOUND THEN
1038            igs_ps_usec_cal_nums_pkg.update_row(  x_mode                        => 'R',
1039                                                  x_rowid                       => rec_call_number.row_id,
1040                                                  x_unit_section_call_number_id => rec_call_number.call_id,
1041                                                  x_calender_type               => rec_teach_to_load.lcal_type,
1042                                                  x_ci_sequence_number          => rec_teach_to_load.lseq_num,
1043                                                  x_call_number                 => l_n_max_cal_num);
1044 
1045         ELSE
1046            l_c_rowid := NULL;
1047            l_n_usc_number_id := NULL;
1048            igs_ps_usec_cal_nums_pkg.insert_row ( x_rowid                       => l_c_rowid,
1049                                                  x_unit_section_call_number_id => l_n_usc_number_id,
1050                                                  x_calender_type               => rec_teach_to_load.lcal_type,
1051                                                  x_ci_sequence_number          => rec_teach_to_load.lseq_num,
1052                                                  x_call_number                 => l_n_max_cal_num,
1053                                                  x_mode                        => 'R' );
1054 
1055         END IF;
1056         CLOSE c_call_number;
1057     END LOOP;
1058     RETURN l_n_max_cal_num;
1059 
1060   EXCEPTION
1061      WHEN OTHERS THEN
1062         ROLLBACK TO IGS_PS_USEC_CAL_NUMS;
1063         RETURN -1;
1064   END get_call_number;
1065 
1066   PROCEDURE get_ufk_for_validation (
1067     x_uoo_id IN NUMBER
1068     ) AS
1069   /*************************************************************
1070    Created By : sarakshi
1071    Date Created By : 30-oct-2003
1072    Purpose :
1073    Know limitations, enhancements or remarks
1074    Change History
1075    Who             When            What
1076 
1077    (reverse chronological order - newest change first)
1078   ***************************************************************/
1079 
1080     CURSOR cur_rowid IS
1081     SELECT   rowid
1082     FROM     IGS_PS_UNIT_OFR_OPT_ALL
1083     WHERE    sup_uoo_id=x_uoo_id;
1084 
1085     lv_rowid cur_rowid%RowType;
1086 
1087   BEGIN
1088 
1089     Open cur_rowid;
1090     Fetch cur_rowid INTO lv_rowid;
1091     IF (cur_rowid%FOUND) THEN
1092         Close cur_rowid;
1093      Fnd_Message.Set_Name ('IGS', 'IGS_PS_UOO_UOO_FK');
1094       IGS_GE_MSG_STACK.ADD;
1095       App_Exception.Raise_Exception;
1096       Return;
1097     END IF;
1098     Close cur_rowid;
1099 
1100   END get_ufk_for_validation;
1101 
1102   PROCEDURE Check_Child_Existance AS
1103   /*************************************************************
1104    Created By : kdande@in
1105    Date Created By : 2000/05/11
1106    Purpose :
1107    Know limitations, enhancements or remarks
1108    Change History
1109    Who             When            What
1110   svuppala   15-JUL-2005    Enh 3442712 - Called igs_fi_invln_int_pkg.get_fk_igs_ps_unit_ofr_opt_all
1111   sarakshi   27-Jul-2004  Bug#3795883, shifted Uk related child to Check_UK_Child_Existance procedure.
1112   sarakshi     15-sep-2003  Enh#2520994,added a call to igs_ps_usec_pri_pkg.get_ufk_igs_ps_unit_ofr_opt
1113   vvutukur    10-Jun-2003  Enh#2831572.Financial Accounting Build.Added call to igs_fi_ftci_accts_pkg.get_ufk_igs_ps_unit_ofr_opt.
1114    smvk        08-May-2003        Bug #2532094. Added child table call igs_ps_usec_x_grpmem_pkg.get_ufk_igs_ps_unit_ofr_opt.
1115    sarakshi    28-Oct-2002        Enh#2613933,added child table IGS_PS_USO_CLAS_MEET existance of record.
1116    smadathi    02-May-2002        Bug 2261649. This procedure contains reference to table IGS_PS_USEC_CHARGE.
1117                                   The table became obsolete. The references to the same have been removed.
1118                                   Removed IGS_PS_USEC_CHARGE_PKG.GET_UFK_IGS_PS_UNIT_OFR_OPT removed.
1119    smadathi        03-JUL-2001    Added IGS_EN_ELGB_OVR_STEP_PKG.GET_UFK_IGS_PS_UNIT_OFR_OPT . This is as per
1120                                   enhancement bug no. 1830175
1121    svenkata     02-06-2003       Modified to remove references to TBH of pkg IGS_EN_ELGB_OVR_STEP_PKG. Instead , added
1122                                  references to package IGS_EN_ELGB_OVR_UOO.Bug #2829272
1123    (reverse chronological order - newest change first)
1124   ***************************************************************/
1125   BEGIN
1126 
1127     IGS_AD_PS_APLINSTUNT_PKG.GET_FK_IGS_PS_UNIT_OFR_OPT (
1128       old_references.unit_cd,
1129       old_references.version_number,
1130       old_references.cal_type,
1131       old_references.ci_sequence_number,
1132       old_references.location_cd,
1133       old_references.unit_class
1134       );
1135 
1136     IGS_EN_SU_ATTEMPT_PKG.GET_FK_IGS_PS_UNIT_OFR_OPT (
1137       old_references.unit_cd,
1138       old_references.version_number,
1139       old_references.cal_type,
1140       old_references.ci_sequence_number,
1141       old_references.location_cd,
1142       old_references.unit_class
1143       );
1144 
1145     IGS_PS_TCH_RESP_OVRD_PKG.GET_FK_IGS_PS_UNIT_OFR_OPT (
1146       old_references.unit_cd,
1147       old_references.version_number,
1148       old_references.cal_type,
1149       old_references.ci_sequence_number,
1150       old_references.location_cd,
1151       old_references.unit_class
1152       );
1153 
1154     IGS_PS_TCH_RSOV_HIST_PKG.GET_FK_IGS_PS_UNIT_OFR_OPT (
1155       old_references.unit_cd,
1156       old_references.version_number,
1157       old_references.cal_type,
1158       old_references.ci_sequence_number,
1159       old_references.location_cd,
1160       old_references.unit_class
1161       );
1162 
1163     IGS_PS_UNT_OFR_OPT_N_PKG.GET_FK_IGS_PS_UNIT_OFR_OPT (
1164       old_references.unit_cd,
1165       old_references.version_number,
1166       old_references.cal_type,
1167       old_references.ci_sequence_number,
1168       old_references.location_cd,
1169       old_references.unit_class
1170       );
1171 
1172     igs_fi_invln_int_pkg.get_fk_igs_ps_unit_ofr_opt_all (
1173            old_references.uoo_id
1174          );
1175 
1176   END Check_Child_Existance;
1177 
1178 
1179   PROCEDURE Check_UK_Child_Existance AS
1180   /*************************************************************
1181    Created By : kdande@in
1182    Date Created By : 2000/05/11
1183    Purpose :
1184    Know limitations, enhancements or remarks
1185    Change History
1186    Who             When            What
1187    (reverse chronological order - newest change first)
1188    sarakshi    23-sep-2004  Bug#3888835, added child validation for igs_ps_nsus_rtn_pkg.
1189    sarakshi    27-Jul-2004  Bug#3795883, shifted Uk related child to Check_UK_Child_Existance procedure and added few new entries.
1190    vvutukur    04-Aug-2003  Enh#3045069.PSP Enh Build. Removed call
1191                             to igs_ps_usec_rpt_cond_pkg.get_ufk_igs_ps_unit_ofr_opt.
1192   ***************************************************************/
1193   BEGIN
1194 
1195       igs_en_nstd_usec_dl_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1196 
1197       igs_en_usec_disc_dl_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1198 
1199       igs_en_elgb_ovr_uoo_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id );
1200 
1201       igs_en_su_attempt_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1202 
1203       igs_ps_tch_resp_ovrd_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1204 
1205       igs_ps_unt_ofr_opt_n_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1206 
1207       igs_ps_usec_grd_schm_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1208 
1209       igs_ps_usec_occurs_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id );
1210 
1211       igs_ps_usec_lim_wlst_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1212 
1213       igs_ps_usec_cps_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1214 
1215       igs_ps_usec_spnsrshp_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1216 
1217       igs_ps_usec_tch_resp_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1218 
1219       igs_ps_usec_as_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1220 
1221       igs_ps_usec_ref_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1222 
1223       igs_ps_us_exam_meet_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1224 
1225       igs_ps_us_unsched_cl_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1226 
1227       igs_ps_usec_category_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1228 
1229       igs_ps_rsv_usec_pri_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1230 
1231       igs_en_spl_perm_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1232 
1233       igs_ps_usec_accts_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1234 
1235       igs_ps_uso_clas_meet_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1236 
1237       igs_ps_usec_x_grpmem_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1238 
1239       igs_ps_usec_wlst_pri_pkg.get_ufk_igs_ps_unit_ofr_opt (old_references.uoo_id);
1240 
1241       --To prevent deletion of unit section which is superior
1242       get_ufk_for_validation(old_references.uoo_id);
1243 
1244       --Bug 3199686
1245       --Created IGS_AS_USEC_SESSNS table
1246       igs_as_usec_sessns_pkg.get_fk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1247 
1248       --To prevent deletion of unit section if unit section special fees exists.
1249       igs_ps_usec_sp_fees_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1250 
1251       igs_ps_rsv_ext_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1252 
1253       igs_ps_usec_ru_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1254 
1255       igs_as_us_ai_group_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1256 
1257       igs_fi_ftci_accts_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1258 
1259       igs_ps_nsus_rtn_pkg.get_ufk_igs_ps_unit_ofr_opt(old_references.uoo_id);
1260 
1261   END Check_UK_Child_Existance;
1262 
1263   FUNCTION Get_PK_For_Validation (
1264     x_unit_cd IN VARCHAR2,
1265     x_version_number IN NUMBER,
1266     x_cal_type IN VARCHAR2,
1267     x_ci_sequence_number IN NUMBER,
1268     x_location_cd IN VARCHAR2,
1269     x_unit_class IN VARCHAR2
1270     ) RETURN BOOLEAN AS
1271   /*************************************************************
1272    Created By : kdande@in
1273    Date Created By : 2000/05/11
1274    Purpose :
1275    Know limitations, enhancements or remarks
1276    Change History
1277    Who             When            What
1278   smvk           08-Jan-2003      Bug # 2735076. Locking the record only when the status of the unit section is 'PLANNED'.
1279    (reverse chronological order - newest change first)
1280   ***************************************************************/
1281 
1282     CURSOR cur_rowid IS
1283       SELECT   rowid
1284       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1285       WHERE    unit_cd = x_unit_cd
1286       AND      version_number = x_version_number
1287       AND      cal_type = x_cal_type
1288       AND      ci_sequence_number = x_ci_sequence_number
1289       AND      location_cd = x_location_cd
1290       AND      unit_class = x_unit_class
1291       FOR UPDATE NOWAIT;
1292 
1293     CURSOR cur_status IS
1294       SELECT   unit_section_status
1295       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1296       WHERE    unit_cd = x_unit_cd
1297       AND      version_number = x_version_number
1298       AND      cal_type = x_cal_type
1299       AND      ci_sequence_number = x_ci_sequence_number
1300       AND      location_cd = x_location_cd
1301       AND      unit_class = x_unit_class;
1302 
1303     lv_rowid cur_rowid%RowType;
1304     l_c_usec_status igs_ps_unit_ofr_opt_all.unit_section_status%TYPE;
1305 
1306   BEGIN
1307 
1308     OPEN cur_status ;
1309     FETCH cur_status INTO l_c_usec_status;
1310     IF cur_status%FOUND THEN                -- whether the record exists
1311        CLOSE cur_status;
1312        IF l_c_usec_status = 'PLANNED' THEN  -- for planned unit section
1313          OPEN cur_rowid;
1314          FETCH cur_rowid INTO lv_rowid;
1315          IF (cur_rowid%FOUND) THEN
1316            CLOSE cur_rowid;
1317            RETURN(TRUE);
1318          ELSE
1319            CLOSE cur_rowid;
1320            RETURN(FALSE);
1321          END IF;
1322        ELSE                                 -- for other unit section statuses
1323          RETURN(TRUE);
1324        END IF;
1325     ELSE                                    -- Unit section record does n't exists.
1326        CLOSE cur_status;
1327        RETURN(FALSE);
1328     END IF;
1329 
1330   END Get_PK_For_Validation;
1331 
1332   FUNCTION Get_UK_For_Validation (
1333     x_uoo_id IN NUMBER
1334     ) RETURN BOOLEAN AS
1335   /*************************************************************
1336    Created By : kdande@in
1337    Date Created By : 2000/05/11
1338    Purpose :
1339    Know limitations, enhancements or remarks
1340    Change History
1341    Who             When            What
1342    smvk           08-Jan-2003      Bug # 2735076. Locking the record only when the status of the unit section is 'PLANNED'.
1343    (reverse chronological order - newest change first)
1344   ***************************************************************/
1345 
1346     CURSOR cur_rowid IS
1347       SELECT   rowid
1348       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1349       WHERE    uoo_id = x_uoo_id
1350       AND      (l_rowid IS NULL OR rowid <> l_rowid)
1351       FOR UPDATE NOWAIT;
1352 
1353     CURSOR cur_status IS
1354       SELECT   unit_section_status
1355       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1356       WHERE    uoo_id = x_uoo_id
1357       AND      (l_rowid IS NULL OR rowid <> l_rowid);
1358 
1359     lv_rowid cur_rowid%RowType;
1360     l_c_usec_status igs_ps_unit_ofr_opt_all.unit_section_status%TYPE;
1361 
1362   BEGIN
1363     OPEN cur_status ;
1364     FETCH cur_status INTO l_c_usec_status;
1365     IF cur_status%FOUND THEN                -- whether the record exists
1366        CLOSE cur_status ;
1367        IF l_c_usec_status ='PLANNED' THEN   -- for planned unit section
1368          OPEN cur_rowid;
1369          FETCH cur_rowid INTO lv_rowid;
1370          IF (cur_rowid%FOUND) THEN
1371            CLOSE cur_rowid;
1372            RETURN(TRUE);
1373          ELSE
1374            CLOSE cur_rowid;
1375            RETURN(FALSE);
1376          END IF;
1377        ELSE                                 -- for other unit section statuses
1378          RETURN TRUE;
1379        END IF;
1380     ELSE                                    -- Unit section record does n't exists.
1381        CLOSE cur_status ;
1382        RETURN FALSE;
1383     END IF;
1384 
1385   END Get_UK_For_Validation;
1386 
1387 
1388   PROCEDURE GET_FK_IGS_AS_GRD_SCHEMA (
1389     x_grading_schema_cd IN VARCHAR2,
1390     x_version_number IN NUMBER
1391     ) AS
1392   /*************************************************************
1393    Created By : kdande@in
1394    Date Created By : 2000/05/11
1395    Purpose :
1396    Know limitations, enhancements or remarks
1397    Change History
1398    Who             When            What
1399 
1400    (reverse chronological order - newest change first)
1401   ***************************************************************/
1402 
1403     CURSOR cur_rowid IS
1404       SELECT   rowid
1405       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1406       WHERE    grading_schema_cd = x_grading_schema_cd
1407       AND      gs_version_number = x_version_number ;
1408 
1409     lv_rowid cur_rowid%RowType;
1410 
1411   BEGIN
1412 
1413     Open cur_rowid;
1414     Fetch cur_rowid INTO lv_rowid;
1415     IF (cur_rowid%FOUND) THEN
1416         Close cur_rowid;
1417       Fnd_Message.Set_Name ('IGS', 'IGS_PS_UOO_GS_FK');
1418       IGS_GE_MSG_STACK.ADD;
1419       App_Exception.Raise_Exception;
1420       Return;
1421     END IF;
1422     Close cur_rowid;
1423 
1424   END GET_FK_IGS_AS_GRD_SCHEMA;
1425 
1426   PROCEDURE GET_FK_IGS_AD_LOCATION (
1427     x_location_cd IN VARCHAR2
1428     ) AS
1429   /*************************************************************
1430    Created By : kdande@in
1431    Date Created By : 2000/05/11
1432    Purpose :
1433    Know limitations, enhancements or remarks
1434    Change History
1435    Who             When            What
1436 
1437    (reverse chronological order - newest change first)
1438   ***************************************************************/
1439 
1440     CURSOR cur_rowid IS
1441       SELECT   rowid
1442       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1443       WHERE    location_cd = x_location_cd ;
1444 
1445     lv_rowid cur_rowid%RowType;
1446 
1447   BEGIN
1448 
1449     Open cur_rowid;
1450     Fetch cur_rowid INTO lv_rowid;
1451     IF (cur_rowid%FOUND) THEN
1452         Close cur_rowid;
1453       Fnd_Message.Set_Name ('IGS', 'IGS_PS_UOO_LOC_FK');
1454       IGS_GE_MSG_STACK.ADD;
1455       App_Exception.Raise_Exception;
1456       Return;
1457     END IF;
1458     Close cur_rowid;
1459 
1460   END GET_FK_IGS_AD_LOCATION;
1461 
1462   PROCEDURE GET_FK_IGS_PE_PERSON (
1463     x_person_id IN VARCHAR2
1464     ) AS
1465   /*************************************************************
1466    Created By : kdande@in
1467    Date Created By : 2000/05/11
1468    Purpose :
1469    Know limitations, enhancements or remarks
1470    Change History
1471    Who             When            What
1472 
1473    (reverse chronological order - newest change first)
1474   ***************************************************************/
1475 
1476     CURSOR cur_rowid IS
1477       SELECT   rowid
1478       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1479       WHERE    unit_contact = x_person_id ;
1480 
1481     lv_rowid cur_rowid%RowType;
1482 
1483   BEGIN
1484 
1485     Open cur_rowid;
1486     Fetch cur_rowid INTO lv_rowid;
1487     IF (cur_rowid%FOUND) THEN
1488         Close cur_rowid;
1489       Fnd_Message.Set_Name ('IGS', 'IGS_PS_UOO_PE_FK');
1490       IGS_GE_MSG_STACK.ADD;
1491       App_Exception.Raise_Exception;
1492       Return;
1493     END IF;
1494     Close cur_rowid;
1495 
1496   END GET_FK_IGS_PE_PERSON;
1497 
1498   PROCEDURE GET_FK_IGS_PS_UNIT_OFR_PAT (
1499     x_unit_cd IN VARCHAR2,
1500     x_version_number IN NUMBER,
1501     x_cal_type IN VARCHAR2,
1502     x_ci_sequence_number IN NUMBER
1503     ) AS
1504   /*************************************************************
1505    Created By : kdande@in
1506    Date Created By : 2000/05/11
1507    Purpose :
1508    Know limitations, enhancements or remarks
1509    Change History
1510    Who             When            What
1511 
1512    (reverse chronological order - newest change first)
1513   ***************************************************************/
1514 
1515     CURSOR cur_rowid IS
1516       SELECT   rowid
1517       FROM     IGS_PS_UNIT_OFR_OPT_ALL
1518       WHERE    unit_cd = x_unit_cd
1519       AND      version_number = x_version_number
1520       AND      cal_type = x_cal_type
1521       AND      ci_sequence_number = x_ci_sequence_number ;
1522 
1523     lv_rowid cur_rowid%RowType;
1524 
1525   BEGIN
1526 
1527     Open cur_rowid;
1528     Fetch cur_rowid INTO lv_rowid;
1529     IF (cur_rowid%FOUND) THEN
1530         Close cur_rowid;
1531       Fnd_Message.Set_Name ('IGS', 'IGS_PS_UOO_UOP_FK');
1532       IGS_GE_MSG_STACK.ADD;
1533       App_Exception.Raise_Exception;
1534       Return;
1535     END IF;
1536     Close cur_rowid;
1537 
1538   END GET_FK_IGS_PS_UNIT_OFR_PAT;
1539 
1540   PROCEDURE Before_DML (
1541     p_action IN VARCHAR2,
1542     x_rowid IN VARCHAR2 ,
1543     x_unit_cd IN VARCHAR2 ,
1544     x_version_number IN NUMBER ,
1545     x_cal_type IN VARCHAR2 ,
1546     x_ci_sequence_number IN NUMBER ,
1547     x_location_cd IN VARCHAR2 ,
1548     x_unit_class IN VARCHAR2 ,
1549     x_uoo_id IN NUMBER ,
1550     x_ivrs_available_ind IN VARCHAR2 ,
1551     x_call_number IN NUMBER ,
1552     x_unit_section_status IN VARCHAR2 ,
1553     x_unit_section_start_date IN DATE ,
1554     x_unit_section_end_date IN DATE ,
1555     x_enrollment_actual IN NUMBER ,
1556     x_waitlist_actual IN NUMBER ,
1557     x_offered_ind IN VARCHAR2 ,
1558     x_state_financial_aid IN VARCHAR2 ,
1559     x_grading_schema_prcdnce_ind IN VARCHAR2 ,
1560     x_federal_financial_aid IN VARCHAR2 ,
1561     x_unit_quota IN NUMBER ,
1562     x_unit_quota_reserved_places IN NUMBER ,
1563     x_institutional_financial_aid IN VARCHAR2 ,
1564     x_unit_contact IN NUMBER ,
1565     x_grading_schema_cd IN VARCHAR2 ,
1566     x_gs_version_number IN NUMBER ,
1567     x_owner_org_unit_cd                 IN     VARCHAR2 ,
1568     x_attendance_required_ind           IN     VARCHAR2 ,
1569     x_reserved_seating_allowed          IN     VARCHAR2 ,
1570     x_special_permission_ind            IN     VARCHAR2 ,
1571     x_ss_display_ind                    IN     VARCHAR2 ,
1572     x_creation_date IN DATE ,
1573     x_created_by IN NUMBER ,
1574     x_last_update_date IN DATE ,
1575     x_last_updated_by IN NUMBER ,
1576     x_last_update_login IN NUMBER ,
1577     x_org_id IN NUMBER ,
1578     x_ss_enrol_ind IN VARCHAR2 ,
1579     x_dir_enrollment IN NUMBER ,
1580     x_enr_from_wlst  IN NUMBER ,
1581     x_inq_not_wlst  IN NUMBER ,
1582     x_rev_account_cd IN VARCHAR2 ,
1583     x_anon_unit_grading_ind IN VARCHAR2 ,
1584     x_anon_assess_grading_ind IN VARCHAR2 ,
1585     X_NON_STD_USEC_IND IN VARCHAR2,
1586     x_auditable_ind IN VARCHAR2,
1587     x_audit_permission_ind IN VARCHAR2,
1588     x_not_multiple_section_flag IN VARCHAR2,
1589     x_sup_uoo_id IN NUMBER ,
1590     x_relation_type VARCHAR2 ,
1591     x_default_enroll_flag VARCHAR2,
1592     x_abort_flag VARCHAR2
1593   ) AS
1594   /*************************************************************
1595    Created By : kdande@in
1596    Date Created By : 2000/05/11
1597    Purpose :
1598    Know limitations, enhancements or remarks
1599    Change History
1600    Who             When            What
1601    smvk             21-Jul-2004     Bug # 3765800. Adding billing_hrs.
1602    sarakshi         12-Apr-2004     Bug#3555871, call_number function is only called for profile option of USER_DEFINED
1603    vvutukur         05-Aug-2003     Enh#3045069.PSP Enh Build. Added column not_multiple_section_flag.
1604    shtatiko         06-NOV-2002     bug# 2616716, Added auditable_ind and audit_permission_ind columns
1605    sarakshi         18-Sep-2002     bug#2563596, added check for cal type associated to a load cal
1606    msrinivi         17-Aug-2001     Added new col rev_account_cd bug 1882122
1607    rgangara         07-May-2001     Added ss_enrol_ind column
1608    (reverse chronological order - newest change first)
1609   ***************************************************************/
1610         --Bug#2563596,Check that teach calendar is associated to a load calendar
1611         CURSOR cur_teach_to_load(cp_cal_type        igs_ca_teach_to_load_v.teach_cal_type%TYPE,
1612                                  cp_sequence_number igs_ca_teach_to_load_v.teach_ci_sequence_number%TYPE)
1613         IS
1614         SELECT load_cal_type,load_ci_sequence_number
1615         FROM   igs_ca_teach_to_load_v
1616         WHERE  teach_cal_type=cp_cal_type
1617         AND    teach_ci_sequence_number=cp_sequence_number;
1618         l_cur_teach_to_load   cur_teach_to_load%ROWTYPE;
1619 
1620         CURSOR c_audit_credit (cp_c_uoo_id igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
1621         SELECT ucp.rowid,ucp.*
1622         FROM   igs_ps_usec_cps ucp
1623         WHERE  ucp.uoo_id= cp_c_uoo_id
1624         AND    ucp.billing_credit_points IS NOT NULL;
1625         l_c_audit_credit c_audit_credit%ROWTYPE;
1626 
1627   BEGIN
1628 
1629     Set_Column_Values (
1630       p_action,
1631       x_rowid,
1632       x_unit_cd,
1633       x_version_number,
1634       x_cal_type,
1635       x_ci_sequence_number,
1636       x_location_cd,
1637       x_unit_class,
1638       x_uoo_id,
1639       x_ivrs_available_ind,
1640       x_call_number,
1641       x_unit_section_status,
1642       x_unit_section_start_date,
1643       x_unit_section_end_date,
1644       x_enrollment_actual,
1645       x_waitlist_actual,
1646       x_offered_ind,
1647       x_state_financial_aid,
1648       x_grading_schema_prcdnce_ind,
1649       x_federal_financial_aid,
1650       x_unit_quota,
1651       x_unit_quota_reserved_places,
1652       x_institutional_financial_aid,
1653       x_unit_contact,
1654       x_grading_schema_cd,
1655       x_gs_version_number,
1656       x_owner_org_unit_cd,
1657       x_attendance_required_ind,
1658       x_reserved_seating_allowed,
1659       x_special_permission_ind,
1660       x_ss_display_ind,
1661       x_creation_date,
1662       x_created_by,
1663       x_last_update_date,
1664       x_last_updated_by,
1665       x_last_update_login,
1666       x_org_id,
1667       x_ss_enrol_ind,
1668       x_dir_enrollment,
1669       x_enr_from_wlst,
1670       x_inq_not_wlst,
1671       x_rev_account_cd,
1672       x_anon_unit_grading_ind,
1673       x_anon_assess_grading_ind,
1674       x_non_std_usec_ind,
1675       x_auditable_ind,
1676       x_audit_permission_ind,
1677       x_not_multiple_section_flag,
1678       x_sup_uoo_id ,
1679       x_relation_type ,
1680       x_default_enroll_flag,
1681       x_abort_flag
1682      );
1683 
1684 
1685     IF (p_action = 'INSERT') THEN
1686       -- Call all the procedures related to Before Insert.
1687       BeforeRowInsertUpdateDelete1 ( p_inserting => TRUE,p_updating=>FALSE,p_deleting=>FALSE );
1688           IF Get_PK_For_Validation (
1689                                              New_References.unit_cd,
1690                                              New_References.version_number,
1691                                              New_References.cal_type,
1692                                              New_References.ci_sequence_number,
1693                                              New_References.location_cd,
1694                                              New_References.unit_class) THEN
1695                     Fnd_Message.Set_Name ('IGS', 'IGS_GE_MULTI_ORG_DUP_REC');
1696                     IGS_GE_MSG_STACK.ADD;
1697                     App_Exception.Raise_Exception;
1698            END IF;
1699            Check_Uniqueness;
1700            Check_Constraints;
1701            Check_Parent_Existance;
1702     ELSIF (p_action = 'UPDATE') THEN
1703       -- Call all the procedures related to Before Update.
1704        beforerowupdate;
1705        BeforeRowInsertUpdateDelete1 ( p_inserting => FALSE,p_updating=>TRUE,p_deleting=>FALSE );
1706        Check_Constraints;
1707        Check_Parent_Existance;
1708 
1709 
1710        --Added as a part of Enh#3116171
1711        IF new_references.auditable_ind = 'N' THEN
1712          OPEN c_audit_credit(new_references.uoo_id);
1713          FETCH c_audit_credit INTO l_c_audit_credit;
1714          IF c_audit_credit%FOUND THEN
1715            igs_ps_usec_cps_pkg.update_row(
1716                 x_rowid                        =>l_c_audit_credit.rowid,
1717                 x_unit_sec_credit_points_id    =>l_c_audit_credit.unit_sec_credit_points_id,
1718                 x_uoo_id                       =>l_c_audit_credit.uoo_id,
1719                 x_minimum_credit_points        =>l_c_audit_credit.minimum_credit_points,
1720                 x_maximum_credit_points        =>l_c_audit_credit.maximum_credit_points,
1721                 x_variable_increment           =>l_c_audit_credit.variable_increment,
1722                 x_lecture_credit_points        =>l_c_audit_credit.lecture_credit_points,
1723                 x_lab_credit_points            =>l_c_audit_credit.lab_credit_points,
1724                 x_other_credit_points          =>l_c_audit_credit.other_credit_points,
1725                 x_clock_hours                  =>l_c_audit_credit.clock_hours,
1726                 x_work_load_cp_lecture         =>l_c_audit_credit.work_load_cp_lecture,
1727                 x_work_load_cp_lab             =>l_c_audit_credit.work_load_cp_lab,
1728                 x_continuing_education_units   =>l_c_audit_credit.continuing_education_units,
1729                 x_work_load_other              =>l_c_audit_credit.work_load_other,
1730                 x_contact_hrs_lecture          =>l_c_audit_credit.contact_hrs_lecture,
1731                 x_contact_hrs_lab              =>l_c_audit_credit.contact_hrs_lab,
1732                 x_contact_hrs_other            =>l_c_audit_credit.contact_hrs_other,
1733                 x_non_schd_required_hrs        =>l_c_audit_credit.non_schd_required_hrs,
1734                 x_exclude_from_max_cp_limit    =>l_c_audit_credit.exclude_from_max_cp_limit,
1735                 x_mode                         =>'R',
1736                 x_claimable_hours              =>l_c_audit_credit.claimable_hours,
1737                 x_achievable_credit_points     =>l_c_audit_credit.achievable_credit_points,
1738                 x_enrolled_credit_points       =>l_c_audit_credit.enrolled_credit_points,
1739                 x_billing_credit_points        =>NULL,
1740                 x_billing_hrs                  => l_c_audit_credit.billing_hrs
1741                );
1742          END IF;
1743          CLOSE c_audit_credit;
1744        END IF;
1745 
1746 
1747     ELSIF (p_action = 'DELETE') THEN
1748       -- Call all the procedures related to Before Delete.
1749       beforerowdelete;
1750       BeforeRowInsertUpdateDelete1 ( p_inserting => FALSE,p_updating=>FALSE,p_deleting=>TRUE);
1751       Check_Child_Existance;
1752       Check_UK_Child_Existance;
1753     ELSIF (p_action = 'VALIDATE_INSERT') THEN
1754            IF Get_PK_For_Validation (New_References.unit_cd,
1755                                              New_References.version_number,
1756                                              New_References.cal_type,
1757                                              New_References.ci_sequence_number,
1758                                              New_References.location_cd,
1759                                              New_References.unit_class) THEN
1760                       Fnd_Message.Set_Name ('IGS', 'IGS_GE_MULTI_ORG_DUP_REC');
1761               IGS_GE_MSG_STACK.ADD;
1762                       App_Exception.Raise_Exception;
1763            END IF;
1764            Check_Uniqueness;
1765            Check_Constraints;
1766    ELSIF (p_action = 'VALIDATE_UPDATE') THEN
1767            beforerowupdate;
1768            Check_Uniqueness;
1769            Check_Constraints;
1770    ELSIF (p_action = 'VALIDATE_DELETE') THEN
1771            beforerowdelete;
1772            Check_Child_Existance;
1773            Check_UK_Child_Existance;
1774    END IF;
1775 
1776    --This if condition is added as a part of bug#1689872
1777    IF p_action IN ( 'INSERT', 'VALIDATE_INSERT') THEN
1778 
1779       --Bug#2563596,Check that teach calendar is associated to a load calendar
1780       OPEN cur_teach_to_load(x_cal_type,x_ci_sequence_number);
1781       FETCH cur_teach_to_load INTO l_cur_teach_to_load ;
1782       IF cur_teach_to_load%NOTFOUND THEN
1783          CLOSE cur_teach_to_load;
1784          fnd_message.set_name('IGS','IGS_PS_TECH_NO_LOAD_CAL_EXST');
1785          IGS_GE_MSG_STACK.ADD;
1786          App_Exception.Raise_Exception;
1787       END IF;
1788       CLOSE cur_teach_to_load;
1789 
1790       --check the call number uniqueness
1791       IF ((FND_PROFILE.VALUE('IGS_PS_CALL_NUMBER') = 'USER_DEFINED') AND (x_call_number IS NOT NULL) ) THEN
1792         IF NOT check_call_number(x_cal_type,x_ci_sequence_number,x_call_number,x_rowid) THEN
1793           Fnd_Message.Set_Name ('IGS', 'IGS_PS_DUPLICATE_CALL_NUMBER');
1794           IGS_GE_MSG_STACK.ADD;
1795           App_Exception.Raise_Exception;
1796         END IF;
1797      END IF;
1798 
1799    ELSIF  p_action IN ('UPDATE','VALIDATE_UPDATE')  THEN
1800 
1801       IF ((old_references.call_number = new_references.call_number) OR
1802          (new_references.call_number IS NULL)) THEN
1803          NULL;
1804       ELSE
1805         --check the call number uniqueness
1806         IF ((FND_PROFILE.VALUE('IGS_PS_CALL_NUMBER') = 'USER_DEFINED') AND (x_call_number IS NOT NULL) ) THEN
1807           IF NOT check_call_number(x_cal_type,x_ci_sequence_number,x_call_number,x_rowid) THEN
1808             Fnd_Message.Set_Name ('IGS', 'IGS_PS_DUPLICATE_CALL_NUMBER');
1809             IGS_GE_MSG_STACK.ADD;
1810             App_Exception.Raise_Exception;
1811           END IF;
1812         END IF;
1813 
1814       END IF;
1815    END IF;
1816 
1817 
1818   END Before_DML;
1819 
1820 Procedure     dflt_usec_ref_code ( p_n_uoo_id      IGS_PS_UNIT_OFR_OPT.UOO_ID%TYPE )
1821   AS
1822 
1823   /************************************************************************
1824   Created By                                : Aiyer
1825   Date Created By                           : 14/06/2001
1826   Purpose                                   : Inserts into table IGS_PS_USEC_REF values inherited from igs_ps_unit_ver and  IGS_PS_USEC_REF_CD
1827                                             : mandatory ref code types for unit_section with default ref code id's for the current uoo_id
1828                                             : at unit_section level
1829   Known limitations, enhancements or remarks:
1830   Change History                            :
1831   Who          When          What
1832   stutta      14-May-2004   Passing 'N' as default value for X_CLASS_SCHED_EXCLUSION_FLAG in call
1833                             to igs_ps_usec_ref_pkg.INSERT_ROW
1834   *************************************************************************/
1835   CURSOR c_igs_ge_ref_cd_type
1836   IS
1837   SELECT
1838       reference_cd_type
1839   FROM
1840       igs_ge_ref_cd_type
1841   WHERE
1842       mandatory_flag ='Y'
1843   AND
1844       unit_section_flag ='Y'
1845   AND
1846       restricted_flag='Y'
1847   AND
1848       closed_ind = 'N';
1849 
1850   CURSOR c_igs_ge_ref_cd (p_c_reference_cd_type IGS_GE_REF_CD_TYPE.REFERENCE_CD_TYPE%TYPE)
1851   IS
1852   SELECT
1853          reference_cd_type,reference_cd,description
1854   FROM
1855          igs_ge_ref_cd
1856   WHERE
1857          reference_cd_type = p_c_reference_cd_type
1858   AND
1859          default_flag      =  'Y';
1860 
1861   -- Used to Inherit value from IGS_PS_UNIT_VER table
1862   CURSOR c_igs_ps_unit_ver
1863    IS
1864   SELECT
1865          SHORT_TITLE,
1866          SUBTITLE_MODIFIABLE_FLAG,
1867          RECORD_EXCLUSION_FLAG ,
1868          TITLE ,
1869          SUBTITLE_ID ,
1870          ATTRIBUTE_CATEGORY,
1871          ATTRIBUTE1  ,
1872          ATTRIBUTE2  ,
1873          ATTRIBUTE3  ,
1874          ATTRIBUTE4  ,
1875          ATTRIBUTE5  ,
1876          ATTRIBUTE6  ,
1877          ATTRIBUTE7  ,
1878          ATTRIBUTE8  ,
1879          ATTRIBUTE9  ,
1880          ATTRIBUTE10 ,
1881          ATTRIBUTE11 ,
1882          ATTRIBUTE12 ,
1883          ATTRIBUTE13 ,
1884          ATTRIBUTE14 ,
1885          ATTRIBUTE15 ,
1886          ATTRIBUTE16 ,
1887          ATTRIBUTE17 ,
1888          ATTRIBUTE18 ,
1889          ATTRIBUTE19 ,
1890          ATTRIBUTE20
1891    FROM
1892          igs_ps_unit_ofr_opt_all uoo,
1893          igs_ps_unit_ver    uv
1894    WHERE
1895          uv.unit_cd = uoo.unit_cd
1896    AND
1897          uv.version_number = uoo.version_number
1898    AND
1899          uoo.uoo_id = p_n_uoo_id;
1900    ln_usec_ref_id        IGS_PS_USEC_REF.UNIT_SECTION_REFERENCE_ID%TYPE := NULL;
1901    ln_usec_ref_cd_id     IGS_PS_USEC_REF_CD.UNIT_SECTION_REFERENCE_CD_ID%TYPE := NULL;
1902    l_c_rowid1            VARCHAR2(25)   :=NULL;
1903    l_c_rowid2            VARCHAR2(25)   :=NULL;
1904  BEGIN
1905   FOR cur_igs_ps_unit_ver IN c_igs_ps_unit_ver
1906   LOOP
1907   BEGIN
1908     l_c_rowid1:=NULL;
1909     igs_ps_usec_ref_pkg.INSERT_ROW (
1910                                      X_ROWID                        => l_c_rowid1,
1911                                      X_UNIT_SECTION_REFERENCE_ID    => ln_usec_ref_id,
1912                                      X_UOO_ID                       => p_n_uoo_id,
1913                                      X_CLASS_SCHED_EXCLUSION_FLAG   => 'N',
1914                                      X_SHORT_TITLE                  => cur_igs_ps_unit_ver.Short_title,
1915                                      X_SUBTITLE                     => NULL   ,
1916                                      X_SUBTITLE_MODIFIABLE_FLAG     => cur_igs_ps_unit_ver.Subtitle_modifiable_flag,
1917                                      X_REGISTRATION_EXCLUSION_FLAG  => NULL  ,
1918                                      X_RECORD_EXCLUSION_FLAG        => cur_igs_ps_unit_ver.Record_exclusion_flag ,
1919                                      X_TITLE                        => cur_igs_ps_unit_ver.Title ,
1920                                      X_SUBTITLE_ID                  => cur_igs_ps_unit_ver.Subtitle_id,
1921                                      X_ATTRIBUTE_CATEGORY           => cur_igs_ps_unit_ver.Attribute_category,
1922                                      X_ATTRIBUTE1                   => cur_igs_ps_unit_ver.Attribute1  ,
1923                                      X_ATTRIBUTE2                   => cur_igs_ps_unit_ver.Attribute2  ,
1924                                      X_ATTRIBUTE3                   => cur_igs_ps_unit_ver.Attribute3  ,
1925                                      X_ATTRIBUTE4                   => cur_igs_ps_unit_ver.Attribute4  ,
1926                                      X_ATTRIBUTE5                   => cur_igs_ps_unit_ver.Attribute5  ,
1927                                      X_ATTRIBUTE6                   => cur_igs_ps_unit_ver.Attribute6  ,
1928                                      X_ATTRIBUTE7                   => cur_igs_ps_unit_ver.Attribute7  ,
1929                                      X_ATTRIBUTE8                   => cur_igs_ps_unit_ver.Attribute8  ,
1930                                      X_ATTRIBUTE9                   => cur_igs_ps_unit_ver.Attribute9  ,
1931                                      X_ATTRIBUTE10                  => cur_igs_ps_unit_ver.Attribute10 ,
1932                                      X_ATTRIBUTE11                  => cur_igs_ps_unit_ver.Attribute11 ,
1933                                      X_ATTRIBUTE12                  => cur_igs_ps_unit_ver.Attribute12 ,
1934                                      X_ATTRIBUTE13                  => cur_igs_ps_unit_ver.Attribute13 ,
1935                                      X_ATTRIBUTE14                  => cur_igs_ps_unit_ver.Attribute14 ,
1936                                      X_ATTRIBUTE15                  => cur_igs_ps_unit_ver.Attribute15 ,
1937                                      X_ATTRIBUTE16                  => cur_igs_ps_unit_ver.Attribute16 ,
1938                                      X_ATTRIBUTE17                  => cur_igs_ps_unit_ver.Attribute17 ,
1939                                      X_ATTRIBUTE18                  => cur_igs_ps_unit_ver.Attribute18 ,
1940                                      X_ATTRIBUTE19                  => cur_igs_ps_unit_ver.Attribute19 ,
1941                                      X_ATTRIBUTE20                  => cur_igs_ps_unit_ver.Attribute20 ,
1942                                      X_MODE                         => 'R'
1943                                    );
1944     FOR cur_igs_ge_ref_cd_type IN c_igs_ge_ref_cd_type
1945     LOOP
1946       FOR cur_igs_ge_ref_cd IN c_igs_ge_ref_cd (cur_igs_ge_ref_cd_type.reference_cd_type)
1947       LOOP
1948         l_c_rowid2:=NULL;
1949         ln_usec_ref_cd_id:=NULL;
1950         igs_ps_usec_ref_cd_pkg.INSERT_ROW (
1951                                             X_ROWID                           => l_c_rowid2,
1952                                             X_UNIT_SECTION_REFERENCE_CD_ID    => ln_usec_ref_cd_id,
1953                                             X_UNIT_SECTION_REFERENCE_ID       => ln_usec_ref_id,
1954                                             X_MODE                            => 'R',
1955                                             x_reference_code_type             => cur_igs_ge_ref_cd.reference_cd_type,
1956                                             x_reference_code                  => cur_igs_ge_ref_cd.reference_cd,
1957                                             x_reference_code_desc             => cur_igs_ge_ref_cd.description
1958 
1959                                           );
1960       END LOOP;
1961     END LOOP;
1962    EXCEPTION
1963       WHEN OTHERS THEN
1964        NULL;
1965    END;
1966   END LOOP;
1967   EXCEPTION
1968    WHEN OTHERS THEN
1969      -- If an error occurs during insertion in igs_ps_ref_cd then raise an exception.
1970     igs_ge_msg_stack.add;
1971     app_exception.raise_exception;
1972     RETURN;
1973 END dflt_usec_ref_code;
1974 
1975   PROCEDURE After_DML (
1976     p_action IN VARCHAR2,
1977     x_rowid IN VARCHAR2
1978   ) IS
1979   /*************************************************************
1980   Created By : jdeekoll
1981   Date Created By : 27-Dec-2000
1982   Purpose :
1983   Know limitations, enhancements or remarks
1984   Change History
1985   Who             When            What
1986 
1987   (reverse chronological order - newest change first)
1988   ***************************************************************/
1989   -- This code has been added by aiyer.
1990   -- After inserting value into igs_ps_unit_ofr_opt insert values into igs_ps_usec_ref and mandatory reference_cd_types of unit_section type
1991   -- a having default reference_cd in the table igs_ps_usec_ref_cd
1992   CURSOR c_igs_ps_unit_ofr_opt
1993    IS
1994    SELECT uoo_id
1995    FROM
1996          IGS_PS_UNIT_OFR_OPT
1997    WHERE
1998          row_id = x_rowid;
1999   BEGIN
2000    l_rowid := x_rowid;
2001    IF (p_action = 'INSERT') THEN
2002         l_rowid:=NULL;
2003         FOR cur_igs_ps_unit_ofr_opt IN c_igs_ps_unit_ofr_opt
2004         LOOP
2005           dflt_usec_ref_code (p_n_uoo_id => cur_igs_ps_unit_ofr_opt.uoo_id);
2006         END LOOP;
2007     END IF;
2008    l_rowid:=NULL;
2009   END After_DML;
2010 
2011  procedure INSERT_ROW (
2012       X_ROWID in out NOCOPY VARCHAR2,
2013        x_UNIT_CD IN VARCHAR2,
2014        x_VERSION_NUMBER IN NUMBER,
2015        x_CAL_TYPE IN VARCHAR2,
2016        x_CI_SEQUENCE_NUMBER IN NUMBER,
2017        x_LOCATION_CD IN VARCHAR2,
2018        x_UNIT_CLASS IN VARCHAR2,
2019        x_UOO_ID IN NUMBER,
2020        x_IVRS_AVAILABLE_IND IN VARCHAR2,
2021        x_CALL_NUMBER IN OUT NOCOPY NUMBER,
2022        x_UNIT_SECTION_STATUS IN VARCHAR2,
2023        x_UNIT_SECTION_START_DATE IN DATE,
2024        x_UNIT_SECTION_END_DATE IN DATE,
2025        x_ENROLLMENT_ACTUAL IN NUMBER,
2026        x_WAITLIST_ACTUAL IN NUMBER,
2027        x_OFFERED_IND IN VARCHAR2,
2028        x_STATE_FINANCIAL_AID IN VARCHAR2,
2029        x_GRADING_SCHEMA_PRCDNCE_IND IN VARCHAR2,
2030        x_FEDERAL_FINANCIAL_AID IN VARCHAR2,
2031        x_UNIT_QUOTA IN NUMBER,
2032        x_UNIT_QUOTA_RESERVED_PLACES IN NUMBER,
2033        x_INSTITUTIONAL_FINANCIAL_AID IN VARCHAR2,
2034        x_UNIT_CONTACT IN NUMBER,
2035        x_GRADING_SCHEMA_CD IN VARCHAR2,
2036        x_GS_VERSION_NUMBER IN NUMBER,
2037        x_owner_org_unit_cd                 IN     VARCHAR2 ,
2038        x_attendance_required_ind           IN     VARCHAR2 ,
2039        x_reserved_seating_allowed          IN     VARCHAR2 ,
2040        x_special_permission_ind            IN     VARCHAR2 ,
2041        x_ss_display_ind                    IN     VARCHAR2 ,
2042        X_MODE in VARCHAR2 ,
2043        x_org_id IN NUMBER,
2044        x_ss_enrol_ind IN VARCHAR2 ,
2045        x_dir_enrollment IN NUMBER ,
2046        x_enr_from_wlst  IN NUMBER ,
2047        x_inq_not_wlst  IN NUMBER ,
2048        x_rev_account_cd IN VARCHAR2 ,
2049        x_anon_unit_grading_ind IN VARCHAR2 ,
2050        x_anon_assess_grading_ind IN VARCHAR2 ,
2051        X_NON_STD_USEC_IND IN VARCHAR2 ,
2052        x_auditable_ind IN VARCHAR2,
2053        x_audit_permission_ind IN VARCHAR2,
2054        x_not_multiple_section_flag IN VARCHAR2,
2055        x_sup_uoo_id IN NUMBER ,
2056        x_relation_type VARCHAR2 ,
2057        x_default_enroll_flag VARCHAR2,
2058        x_abort_flag VARCHAR2
2059   ) AS
2060   /*************************************************************
2061    Created By : kdande@in
2062    Date Created By : 2000/05/11
2063    Purpose :
2064    Know limitations, enhancements or remarks
2065    Change History
2066    Who             When            What
2067    vvutukur        05-Aug-2003     Enh#3045069.PSP Enh Build. Added column not_multiple_section_flag.
2068    shtatiko        06-NOV-2002     Added auditable_ind and audit_permission_ind as part of Bug# 2636716
2069    sbaliga         13-feb-2002     Assigned igs_ge_gen_003.get_org_id to x_org_id in call to before_dml
2070                                    as part of SWCR006 build.
2071    rgangara        07-May-2001     Ss_enrol_ind column added
2072    (reverse chronological order - newest change first)
2073   ***************************************************************/
2074     cursor C is select ROWID from IGS_PS_UNIT_OFR_OPT_ALL
2075       where UNIT_CD = X_UNIT_CD
2076       and VERSION_NUMBER = X_VERSION_NUMBER
2077       and LOCATION_CD = X_LOCATION_CD
2078       and UNIT_CLASS = X_UNIT_CLASS
2079       and CI_SEQUENCE_NUMBER = X_CI_SEQUENCE_NUMBER
2080       and CAL_TYPE = X_CAL_TYPE;
2081     X_LAST_UPDATE_DATE DATE;
2082     X_LAST_UPDATED_BY NUMBER;
2083     X_LAST_UPDATE_LOGIN NUMBER;
2084     X_REQUEST_ID NUMBER;
2085     X_PROGRAM_ID NUMBER;
2086     X_PROGRAM_APPLICATION_ID NUMBER;
2087     X_PROGRAM_UPDATE_DATE DATE;
2088 begin
2089   X_LAST_UPDATE_DATE := SYSDATE;
2090   if(X_MODE = 'I') then
2091     X_LAST_UPDATED_BY := 1;
2092     X_LAST_UPDATE_LOGIN := 0;
2093   elsif (X_MODE = 'R') then
2094     X_LAST_UPDATED_BY := FND_GLOBAL.USER_ID;
2095     if X_LAST_UPDATED_BY is NULL then
2096       X_LAST_UPDATED_BY := -1;
2097     end if;
2098     X_LAST_UPDATE_LOGIN :=FND_GLOBAL.LOGIN_ID;
2099     if X_LAST_UPDATE_LOGIN is NULL then
2100       X_LAST_UPDATE_LOGIN := -1;
2101    end if;
2102    X_REQUEST_ID := FND_GLOBAL.CONC_REQUEST_ID;
2103    X_PROGRAM_ID := FND_GLOBAL.CONC_PROGRAM_ID;
2104 
2105    X_PROGRAM_APPLICATION_ID := FND_GLOBAL.PROG_APPL_ID;
2106    if (X_REQUEST_ID = -1) then
2107      X_REQUEST_ID := NULL;
2108      X_PROGRAM_ID := NULL;
2109      X_PROGRAM_APPLICATION_ID := NULL;
2110      X_PROGRAM_UPDATE_DATE := NULL;
2111    else
2112      X_PROGRAM_UPDATE_DATE := SYSDATE;
2113    end if;
2114   else
2115     FND_MESSAGE.SET_NAME( 'FND', 'SYSTEM-INVALID ARGS');
2116       IGS_GE_MSG_STACK.ADD;
2117     app_exception.raise_exception;
2118   end if;
2119 
2120 
2121 
2122     Before_DML(
2123                 p_action=>'INSERT',
2124                 x_rowid=>X_ROWID,
2125                x_unit_cd=>X_UNIT_CD,
2126                x_version_number=>X_VERSION_NUMBER,
2127                x_cal_type=>X_CAL_TYPE,
2128                x_ci_sequence_number=>X_CI_SEQUENCE_NUMBER,
2129                x_location_cd=>X_LOCATION_CD,
2130                x_unit_class=>X_UNIT_CLASS,
2131                x_uoo_id=>X_UOO_ID,
2132                x_ivrs_available_ind=>NVL(X_IVRS_AVAILABLE_IND,'Y' ),
2133                x_call_number=>X_CALL_NUMBER,
2134                x_unit_section_status=>X_UNIT_SECTION_STATUS,
2135                x_unit_section_start_date=>X_UNIT_SECTION_START_DATE,
2136                x_unit_section_end_date=>X_UNIT_SECTION_END_DATE,
2137                x_enrollment_actual=>X_ENROLLMENT_ACTUAL,
2138                x_waitlist_actual=>X_WAITLIST_ACTUAL,
2139                x_offered_ind=>NVL(X_OFFERED_IND,'Y' ),
2140                x_state_financial_aid=>X_STATE_FINANCIAL_AID,
2141                x_grading_schema_prcdnce_ind=>NVL(X_GRADING_SCHEMA_PRCDNCE_IND,'N' ),
2142                x_federal_financial_aid=>X_FEDERAL_FINANCIAL_AID,
2143                x_unit_quota=>X_UNIT_QUOTA,
2144                x_unit_quota_reserved_places=>X_UNIT_QUOTA_RESERVED_PLACES,
2145                x_institutional_financial_aid=>X_INSTITUTIONAL_FINANCIAL_AID,
2146                x_unit_contact=>X_UNIT_CONTACT,
2147                x_grading_schema_cd=>X_GRADING_SCHEMA_CD,
2148                x_gs_version_number=>X_GS_VERSION_NUMBER,
2149                x_owner_org_unit_cd =>X_OWNER_ORG_UNIT_CD,
2150                x_attendance_required_ind =>NVL(X_ATTENDANCE_REQUIRED_IND,'N'),
2151                x_reserved_seating_allowed =>NVL(X_RESERVED_SEATING_ALLOWED,'Y'),
2152                x_special_permission_ind => NVL(X_SPECIAL_PERMISSION_IND,'N'),
2153                x_ss_display_ind  => NVL(X_SS_DISPLAY_IND,'N'),
2154                x_creation_date=>X_LAST_UPDATE_DATE,
2155                x_created_by=>X_LAST_UPDATED_BY,
2156                x_last_update_date=>X_LAST_UPDATE_DATE,
2157                x_last_updated_by=>X_LAST_UPDATED_BY,
2158                x_last_update_login=>X_LAST_UPDATE_LOGIN,
2159                x_org_id=>igs_ge_gen_003.get_org_id,
2160                x_ss_enrol_ind => X_SS_ENROL_IND,
2161                x_dir_enrollment =>X_DIR_ENROLLMENT,
2162                x_enr_from_wlst =>X_ENR_FROM_WLST ,
2163                x_inq_not_wlst =>X_INQ_NOT_WLST,
2164                x_rev_account_cd => x_rev_account_cd ,
2165                x_anon_unit_grading_ind => x_anon_unit_grading_ind,
2166                x_anon_assess_grading_ind => x_anon_assess_grading_ind,
2167                x_non_std_usec_ind => x_non_std_usec_ind,
2168                x_auditable_ind => x_auditable_ind,
2169                x_audit_permission_ind => x_audit_permission_ind,
2170                x_not_multiple_section_flag => x_not_multiple_section_flag,
2171                x_sup_uoo_id => x_sup_uoo_id ,
2172                x_relation_type => x_relation_type ,
2173                x_default_enroll_flag => x_default_enroll_flag,
2174 	       x_abort_flag => x_abort_flag
2175              );
2176 
2177      --When the profile option is AUTO then use the sequence number to populate the call_number value
2178      IF FND_PROFILE.VALUE('IGS_PS_CALL_NUMBER') = 'AUTO' THEN
2179         x_call_number := get_call_number(new_references.cal_type, new_references.ci_sequence_number);
2180         IF x_call_number = -1 THEN
2181            fnd_message.set_name('IGS','IGS_GE_INVALID_VALUE');
2182            app_exception.raise_exception;
2183         END IF;
2184      END IF;
2185 
2186      insert into IGS_PS_UNIT_OFR_OPT_ALL (
2187                 UNIT_CD
2188                 ,VERSION_NUMBER
2189                 ,CAL_TYPE
2190                 ,CI_SEQUENCE_NUMBER
2191                 ,LOCATION_CD
2192                 ,UNIT_CLASS
2193                 ,UOO_ID
2194                 ,IVRS_AVAILABLE_IND
2195                 ,CALL_NUMBER
2196                 ,UNIT_SECTION_STATUS
2197                 ,UNIT_SECTION_START_DATE
2198                 ,UNIT_SECTION_END_DATE
2199                 ,ENROLLMENT_ACTUAL
2200                 ,WAITLIST_ACTUAL
2201                 ,OFFERED_IND
2202                 ,STATE_FINANCIAL_AID
2203                 ,GRADING_SCHEMA_PRCDNCE_IND
2204                 ,FEDERAL_FINANCIAL_AID
2205                 ,UNIT_QUOTA
2206                 ,UNIT_QUOTA_RESERVED_PLACES
2207                 ,INSTITUTIONAL_FINANCIAL_AID
2208                 ,UNIT_CONTACT
2209                 ,GRADING_SCHEMA_CD
2210                 ,GS_VERSION_NUMBER
2211                 ,owner_org_unit_cd
2212                 ,attendance_required_ind
2213                 ,reserved_seating_allowed
2214                 ,special_permission_ind
2215                 ,ss_display_ind
2216                 ,CREATION_DATE
2217                 ,CREATED_BY
2218                 ,LAST_UPDATE_DATE
2219                 ,LAST_UPDATED_BY
2220                 ,LAST_UPDATE_LOGIN
2221                 ,REQUEST_ID
2222                 ,PROGRAM_ID
2223                 ,PROGRAM_APPLICATION_ID
2224                 ,PROGRAM_UPDATE_DATE
2225                 ,ORG_ID
2226                 ,SS_ENROL_IND
2227                 ,DIR_ENROLLMENT
2228                 ,ENR_FROM_WLST
2229                 ,INQ_NOT_WLST
2230                 ,rev_account_cd
2231                 ,anon_unit_grading_ind
2232                 ,anon_assess_grading_ind
2233                 ,non_std_usec_ind,
2234                 auditable_ind,
2235                 audit_permission_ind,
2236                 not_multiple_section_flag,
2237                 sup_uoo_id,
2238                 relation_type,
2239                 default_enroll_flag,
2240 		abort_flag
2241         ) values  (
2242                 NEW_REFERENCES.UNIT_CD
2243                 ,NEW_REFERENCES.VERSION_NUMBER
2244                 ,NEW_REFERENCES.CAL_TYPE
2245                 ,NEW_REFERENCES.CI_SEQUENCE_NUMBER
2246                 ,NEW_REFERENCES.LOCATION_CD
2247                 ,NEW_REFERENCES.UNIT_CLASS
2248                 ,NEW_REFERENCES.UOO_ID
2249                 ,NEW_REFERENCES.IVRS_AVAILABLE_IND
2250                 ,x_call_number
2251                 ,NEW_REFERENCES.UNIT_SECTION_STATUS
2252                 ,NEW_REFERENCES.UNIT_SECTION_START_DATE
2253                 ,NEW_REFERENCES.UNIT_SECTION_END_DATE
2254                 ,NEW_REFERENCES.ENROLLMENT_ACTUAL
2255                 ,NEW_REFERENCES.WAITLIST_ACTUAL
2256                 ,NEW_REFERENCES.OFFERED_IND
2257                 ,NEW_REFERENCES.STATE_FINANCIAL_AID
2258                 ,NEW_REFERENCES.GRADING_SCHEMA_PRCDNCE_IND
2259                 ,NEW_REFERENCES.FEDERAL_FINANCIAL_AID
2260                 ,NEW_REFERENCES.UNIT_QUOTA
2261                 ,NEW_REFERENCES.UNIT_QUOTA_RESERVED_PLACES
2262                 ,NEW_REFERENCES.INSTITUTIONAL_FINANCIAL_AID
2263                 ,NEW_REFERENCES.UNIT_CONTACT
2264                 ,NEW_REFERENCES.GRADING_SCHEMA_CD
2265                 ,NEW_REFERENCES.GS_VERSION_NUMBER
2266                 ,NEW_REFERENCES.owner_org_unit_cd
2267                 ,NEW_REFERENCES.attendance_required_ind
2268                 ,NEW_REFERENCES.reserved_seating_allowed
2269                 ,NEW_REFERENCES.special_permission_ind
2270                 ,NEW_REFERENCES.ss_display_ind
2271                 ,X_LAST_UPDATE_DATE
2272                 ,X_LAST_UPDATED_BY
2273                 ,X_LAST_UPDATE_DATE
2274                 ,X_LAST_UPDATED_BY
2275                 ,X_LAST_UPDATE_LOGIN
2276                 ,X_REQUEST_ID
2277                 ,X_PROGRAM_ID
2278                 ,X_PROGRAM_APPLICATION_ID
2279                 ,X_PROGRAM_UPDATE_DATE
2280                 ,NEW_REFERENCES.ORG_ID
2281                 ,NEW_REFERENCES.SS_ENROL_IND
2282                 ,NEW_REFERENCES.DIR_ENROLLMENT
2283                 ,NEW_REFERENCES.ENR_FROM_WLST
2284                 ,NEW_REFERENCES.INQ_NOT_WLST
2285                 ,new_references.rev_account_cd
2286                 ,new_references.anon_unit_grading_ind
2287                 ,new_references.anon_assess_grading_ind
2288                 ,new_references.non_std_usec_ind,
2289                 new_references.auditable_ind,
2290                 new_references.audit_permission_ind,
2291                 new_references.not_multiple_section_flag,
2292                 new_references.sup_uoo_id,
2293                 new_references.relation_type,
2294                 new_references.default_enroll_flag,
2295 		new_references.abort_flag
2296 );
2297   open c;
2298   fetch c into X_ROWID;
2299   if (c%notfound) then
2300     close c;
2301     raise no_data_found;
2302   end if;
2303   close c;
2304   After_DML (
2305                 p_action => 'INSERT' ,
2306                 x_rowid => X_ROWID
2307             );
2308 
2309 end INSERT_ROW;
2310 
2311 procedure LOCK_ROW (
2312       X_ROWID in  VARCHAR2,
2313        x_UNIT_CD IN VARCHAR2,
2314        x_VERSION_NUMBER IN NUMBER,
2315        x_CAL_TYPE IN VARCHAR2,
2316        x_CI_SEQUENCE_NUMBER IN NUMBER,
2317        x_LOCATION_CD IN VARCHAR2,
2318        x_UNIT_CLASS IN VARCHAR2,
2319        x_UOO_ID IN NUMBER,
2320        x_IVRS_AVAILABLE_IND IN VARCHAR2,
2321        x_CALL_NUMBER IN NUMBER,
2322        x_UNIT_SECTION_STATUS IN VARCHAR2,
2323        x_UNIT_SECTION_START_DATE IN DATE,
2324        x_UNIT_SECTION_END_DATE IN DATE,
2325        x_ENROLLMENT_ACTUAL IN NUMBER,
2326        x_WAITLIST_ACTUAL IN NUMBER,
2327        x_OFFERED_IND IN VARCHAR2,
2328        x_STATE_FINANCIAL_AID IN VARCHAR2,
2329        x_GRADING_SCHEMA_PRCDNCE_IND IN VARCHAR2,
2330        x_FEDERAL_FINANCIAL_AID IN VARCHAR2,
2331        x_UNIT_QUOTA IN NUMBER,
2332        x_UNIT_QUOTA_RESERVED_PLACES IN NUMBER,
2333        x_INSTITUTIONAL_FINANCIAL_AID IN VARCHAR2,
2334        x_UNIT_CONTACT IN NUMBER,
2335        x_GRADING_SCHEMA_CD IN VARCHAR2,
2336        x_GS_VERSION_NUMBER IN NUMBER,
2337        x_owner_org_unit_cd                 IN     VARCHAR2 ,
2338        x_attendance_required_ind           IN     VARCHAR2 ,
2339        x_reserved_seating_allowed          IN     VARCHAR2 ,
2340        x_special_permission_ind            IN     VARCHAR2 ,
2341        x_ss_display_ind                    IN     VARCHAR2 ,
2342        x_ss_enrol_ind in VARCHAR2 ,
2343        x_dir_enrollment IN NUMBER ,
2344        x_enr_from_wlst  IN NUMBER ,
2345        x_inq_not_wlst  IN NUMBER ,
2346        x_rev_account_cd IN VARCHAR2 ,
2347        x_anon_unit_grading_ind IN VARCHAR2 ,
2348        x_anon_assess_grading_ind IN VARCHAR2 ,
2349        X_NON_STD_USEC_IND IN VARCHAR2,
2350        x_auditable_ind IN VARCHAR2,
2351        x_audit_permission_ind IN VARCHAR2,
2352        x_not_multiple_section_flag IN VARCHAR2,
2353        x_sup_uoo_id IN NUMBER ,
2354        x_relation_type VARCHAR2 ,
2355        x_default_enroll_flag VARCHAR2,
2356        x_abort_flag VARCHAR2
2357   ) AS
2358   /*************************************************************
2359    Created By : kdande@in
2360    Date Created By : 2000/05/11
2361    Purpose :
2362    Know limitations, enhancements or remarks
2363    Change History
2364    Who             When            What
2365    vvutukur        05-Aug-2003     Enh#3045069.PSP Enh Build. Added column not_multiple_section_flag.
2366    shtatiko        06-NOV-2002     added auditable_ind and audit_permission_ind as part of Bug# 2636716.
2367    rgangara        07-May-2001     ss_enrol_ind col added
2368    (reverse chronological order - newest change first)
2369   ***************************************************************/
2370    cursor c1 is select
2371       UOO_ID
2372 ,      IVRS_AVAILABLE_IND
2373 ,      CALL_NUMBER
2374 ,      UNIT_SECTION_STATUS
2375 ,      UNIT_SECTION_START_DATE
2376 ,      UNIT_SECTION_END_DATE
2377 ,      ENROLLMENT_ACTUAL
2378 ,      WAITLIST_ACTUAL
2379 ,      OFFERED_IND
2380 ,      STATE_FINANCIAL_AID
2381 ,      GRADING_SCHEMA_PRCDNCE_IND
2382 ,      FEDERAL_FINANCIAL_AID
2383 ,      UNIT_QUOTA
2384 ,      UNIT_QUOTA_RESERVED_PLACES
2385 ,      INSTITUTIONAL_FINANCIAL_AID
2386 ,      UNIT_CONTACT
2387 ,      GRADING_SCHEMA_CD
2388 ,      GS_VERSION_NUMBER
2389 ,      OWNER_ORG_UNIT_CD
2390 ,      ATTENDANCE_REQUIRED_IND
2391 ,      RESERVED_SEATING_ALLOWED
2392 ,      SPECIAL_PERMISSION_IND
2393 ,      SS_DISPLAY_IND
2394 ,      SS_ENROL_IND
2395 ,      DIR_ENROLLMENT
2396 ,      ENR_FROM_WLST
2397 ,      INQ_NOT_WLST
2398 ,      rev_account_cd
2399 ,      anon_unit_grading_ind
2400 ,      anon_assess_grading_ind
2401 ,      NON_STD_USEC_IND,
2402 auditable_ind,
2403 audit_permission_ind,
2404 not_multiple_section_flag,
2405 sup_uoo_id,
2406 relation_type,
2407 default_enroll_flag,
2408 abort_flag
2409     from IGS_PS_UNIT_OFR_OPT_ALL
2410     where ROWID = X_ROWID
2411     for update nowait;
2412 
2413         tlinfo c1%rowtype;
2414 
2415 begin
2416   open c1;
2417   fetch c1 into tlinfo;
2418   if (c1%notfound) then
2419     close c1;
2420     fnd_message.set_name('FND', 'FORM_RECORD_DELETED');
2421       IGS_GE_MSG_STACK.ADD;
2422     app_exception.raise_exception;
2423     return;
2424   end if;
2425   close c1;
2426 
2427 if ( (  tlinfo.UOO_ID = X_UOO_ID)
2428   AND (tlinfo.IVRS_AVAILABLE_IND = X_IVRS_AVAILABLE_IND)
2429   AND ((tlinfo.CALL_NUMBER = X_CALL_NUMBER)
2430             OR ((tlinfo.CALL_NUMBER is null)
2431                 AND (X_CALL_NUMBER is null)))
2432   AND ((tlinfo.UNIT_SECTION_STATUS = X_UNIT_SECTION_STATUS)
2433             OR ((tlinfo.UNIT_SECTION_STATUS is null)
2434                 AND (X_UNIT_SECTION_STATUS is null)))
2435   AND ((tlinfo.UNIT_SECTION_START_DATE = X_UNIT_SECTION_START_DATE)
2436             OR ((tlinfo.UNIT_SECTION_START_DATE is null)
2437                 AND (X_UNIT_SECTION_START_DATE is null)))
2438   AND ((tlinfo.UNIT_SECTION_END_DATE = X_UNIT_SECTION_END_DATE)
2439             OR ((tlinfo.UNIT_SECTION_END_DATE is null)
2440                 AND (X_UNIT_SECTION_END_DATE is null)))
2441   AND ((tlinfo.ENROLLMENT_ACTUAL = X_ENROLLMENT_ACTUAL)
2442             OR ((tlinfo.ENROLLMENT_ACTUAL is null)
2443                 AND (X_ENROLLMENT_ACTUAL is null)))
2444   AND ((tlinfo.WAITLIST_ACTUAL = X_WAITLIST_ACTUAL)
2445             OR ((tlinfo.WAITLIST_ACTUAL is null)
2446                 AND (X_WAITLIST_ACTUAL is null)))
2447   AND (tlinfo.OFFERED_IND = X_OFFERED_IND)
2448   AND ((tlinfo.STATE_FINANCIAL_AID = X_STATE_FINANCIAL_AID)
2449             OR ((tlinfo.STATE_FINANCIAL_AID is null)
2450                 AND (X_STATE_FINANCIAL_AID is null)))
2451   AND (tlinfo.GRADING_SCHEMA_PRCDNCE_IND = X_GRADING_SCHEMA_PRCDNCE_IND)
2452   AND ((tlinfo.FEDERAL_FINANCIAL_AID = X_FEDERAL_FINANCIAL_AID)
2453             OR ((tlinfo.FEDERAL_FINANCIAL_AID is null)
2454                 AND (X_FEDERAL_FINANCIAL_AID is null)))
2455   AND ((tlinfo.UNIT_QUOTA = X_UNIT_QUOTA)
2456             OR ((tlinfo.UNIT_QUOTA is null)
2457                 AND (X_UNIT_QUOTA is null)))
2458   AND ((tlinfo.UNIT_QUOTA_RESERVED_PLACES = X_UNIT_QUOTA_RESERVED_PLACES)
2459             OR ((tlinfo.UNIT_QUOTA_RESERVED_PLACES is null)
2460                 AND (X_UNIT_QUOTA_RESERVED_PLACES is null)))
2461   AND ((tlinfo.INSTITUTIONAL_FINANCIAL_AID = X_INSTITUTIONAL_FINANCIAL_AID)
2462             OR ((tlinfo.INSTITUTIONAL_FINANCIAL_AID is null)
2463                 AND (X_INSTITUTIONAL_FINANCIAL_AID is null)))
2464   AND ((tlinfo.UNIT_CONTACT = X_UNIT_CONTACT)
2465             OR ((tlinfo.UNIT_CONTACT is null)
2466                 AND (X_UNIT_CONTACT is null)))
2467   AND (tlinfo.GRADING_SCHEMA_CD = X_GRADING_SCHEMA_CD)
2468   AND (tlinfo.GS_VERSION_NUMBER = X_GS_VERSION_NUMBER)
2469   AND ((tlinfo.owner_org_unit_cd = x_owner_org_unit_cd)
2470             OR ((tlinfo.owner_org_unit_cd IS NULL)
2471                 AND (X_owner_org_unit_cd IS NULL)))
2472   AND ((tlinfo.attendance_required_ind = x_attendance_required_ind)
2473             OR ((tlinfo.attendance_required_ind IS NULL)
2474                 AND (X_attendance_required_ind IS NULL)))
2475   AND ((tlinfo.reserved_seating_allowed = x_reserved_seating_allowed)
2476             OR ((tlinfo.reserved_seating_allowed IS NULL)
2477                 AND (X_reserved_seating_allowed IS NULL)))
2478   AND ((tlinfo.special_permission_ind = x_special_permission_ind)
2479             OR ((tlinfo.special_permission_ind IS NULL)
2480                 AND (X_special_permission_ind IS NULL)))
2481   AND ((tlinfo.ss_display_ind = x_ss_display_ind)
2482             OR ((tlinfo.ss_display_ind IS NULL)
2483                 AND (X_ss_display_ind IS NULL)))
2484   AND ((tlinfo.SS_ENROL_IND = X_SS_ENROL_IND)
2485       OR ((tlinfo.SS_ENROL_IND IS NULL)
2486          AND (X_SS_ENROL_IND is NULL)))
2487   AND ((tlinfo.DIR_ENROLLMENT = X_DIR_ENROLLMENT)
2488       OR ((tlinfo.DIR_ENROLLMENT IS NULL)
2489          AND (X_DIR_ENROLLMENT is NULL)))
2490   AND ((tlinfo.ENR_FROM_WLST = X_ENR_FROM_WLST)
2491       OR ((tlinfo.ENR_FROM_WLST IS NULL)
2492          AND (X_ENR_FROM_WLST is NULL)))
2493   AND ((tlinfo.INQ_NOT_WLST = X_INQ_NOT_WLST)
2494       OR ((tlinfo.INQ_NOT_WLST IS NULL)
2495          AND (X_INQ_NOT_WLST is NULL)))
2496   AND ((tlinfo.rev_account_cd = x_rev_account_cd)
2497      OR ((tlinfo.rev_account_cd IS NULL)
2498         AND (x_rev_account_cd is NULL)))
2499   AND ((tlinfo.anon_unit_grading_ind = x_anon_unit_grading_ind)
2500      OR ((tlinfo.anon_unit_grading_ind IS NULL)
2501         AND (x_anon_unit_grading_ind is NULL)))
2502   AND ((tlinfo.anon_assess_grading_ind = x_anon_assess_grading_ind)
2503      OR ((tlinfo.anon_assess_grading_ind IS NULL)
2504         AND (x_anon_assess_grading_ind is NULL)))
2505   AND ((tlinfo.non_std_usec_ind = x_non_std_usec_ind)
2506      OR ((tlinfo.non_std_usec_ind IS NULL)
2507         AND (x_non_std_usec_ind is NULL)))
2508   AND ((tlinfo.auditable_ind = x_auditable_ind)
2509      OR ((tlinfo.auditable_ind IS NULL)
2510         AND (x_auditable_ind is NULL)))
2511   AND ((tlinfo.audit_permission_ind = x_audit_permission_ind)
2512      OR ((tlinfo.audit_permission_ind IS NULL)
2513         AND (x_audit_permission_ind is NULL)))
2514   AND ((tlinfo.not_multiple_section_flag = x_not_multiple_section_flag)
2515      OR ((tlinfo.not_multiple_section_flag IS NULL)
2516         AND (x_not_multiple_section_flag IS NULL)))
2517   AND ((tlinfo.sup_uoo_id= x_sup_uoo_id)
2518      OR ((tlinfo.sup_uoo_id IS NULL)
2519         AND (x_sup_uoo_id IS NULL)))
2520   AND ((tlinfo.relation_type= x_relation_type)
2521      OR ((tlinfo.relation_type IS NULL)
2522         AND (x_relation_type IS NULL)))
2523   AND ((tlinfo.default_enroll_flag= x_default_enroll_flag)
2524      OR ((tlinfo.default_enroll_flag IS NULL)
2525         AND (x_default_enroll_flag IS NULL)))
2526  AND (tlinfo.abort_flag = x_abort_flag)
2527 
2528   ) then
2529     null;
2530   else
2531     fnd_message.set_name('FND', 'FORM_RECORD_CHANGED');
2532     IGS_GE_MSG_STACK.ADD;
2533     app_exception.raise_exception;
2534   end if;
2535   return;
2536 end LOCK_ROW;
2537 
2538  Procedure UPDATE_ROW (
2539       X_ROWID in  VARCHAR2,
2540        x_UNIT_CD IN VARCHAR2,
2541        x_VERSION_NUMBER IN NUMBER,
2542        x_CAL_TYPE IN VARCHAR2,
2543        x_CI_SEQUENCE_NUMBER IN NUMBER,
2544        x_LOCATION_CD IN VARCHAR2,
2545        x_UNIT_CLASS IN VARCHAR2,
2546        x_UOO_ID IN NUMBER,
2547        x_IVRS_AVAILABLE_IND IN VARCHAR2,
2548        x_CALL_NUMBER IN NUMBER,
2549        x_UNIT_SECTION_STATUS IN VARCHAR2,
2550        x_UNIT_SECTION_START_DATE IN DATE,
2551        x_UNIT_SECTION_END_DATE IN DATE,
2552        x_ENROLLMENT_ACTUAL IN NUMBER,
2553        x_WAITLIST_ACTUAL IN NUMBER,
2554        x_OFFERED_IND IN VARCHAR2,
2555        x_STATE_FINANCIAL_AID IN VARCHAR2,
2556        x_GRADING_SCHEMA_PRCDNCE_IND IN VARCHAR2,
2557        x_FEDERAL_FINANCIAL_AID IN VARCHAR2,
2558        x_UNIT_QUOTA IN NUMBER,
2559        x_UNIT_QUOTA_RESERVED_PLACES IN NUMBER,
2560        x_INSTITUTIONAL_FINANCIAL_AID IN VARCHAR2,
2561        x_UNIT_CONTACT IN NUMBER,
2562        x_GRADING_SCHEMA_CD IN VARCHAR2,
2563        x_GS_VERSION_NUMBER IN NUMBER,
2564        x_owner_org_unit_cd                 IN     VARCHAR2 ,
2565        x_attendance_required_ind           IN     VARCHAR2 ,
2566        x_reserved_seating_allowed          IN     VARCHAR2 ,
2567        x_special_permission_ind            IN     VARCHAR2 ,
2568        x_ss_display_ind                    IN     VARCHAR2 ,
2569        X_MODE in VARCHAR2 ,
2570        x_ss_enrol_ind IN VARCHAR2 ,
2571        x_dir_enrollment IN NUMBER ,
2572        x_enr_from_wlst  IN NUMBER ,
2573        x_inq_not_wlst  IN NUMBER ,
2574        x_rev_account_cd IN VARCHAR2 ,
2575        x_anon_unit_grading_ind IN VARCHAR2 ,
2576        x_anon_assess_grading_ind IN VARCHAR2 ,
2577        X_NON_STD_USEC_IND IN VARCHAR2,
2578        x_auditable_ind IN VARCHAR2,
2579        x_audit_permission_ind IN VARCHAR2,
2580        x_not_multiple_section_flag IN VARCHAR2,
2581        x_sup_uoo_id IN NUMBER ,
2582        x_relation_type VARCHAR2 ,
2583        x_default_enroll_flag VARCHAR2,
2584        x_abort_flag VARCHAR2
2585 
2586   ) AS
2587   /*************************************************************
2588    Created By : kdande@in
2589    Date Created By : 2000/05/11
2590    Purpose :
2591    Know limitations, enhancements or remarks
2592    Change History
2593    Who             When            What
2594    bdeviset        03-MAY-2006     Bug# 5204703. Modified the if condition for calling
2595                                    'Enroll Students From Waitlist Process' CP.
2596    vvutukur        05-Aug-2003     Enh#3045069.PSP Enh Build. Added column not_multiple_section_flag.
2597    shtatiko        06-NOV-2002     Added auditable_ind and audit_permission_ind as part of Bug# 2636716.
2598    (reverse chronological order - newest change first)
2599   ***************************************************************/
2600     X_LAST_UPDATE_DATE DATE;
2601     X_LAST_UPDATED_BY NUMBER;
2602     X_LAST_UPDATE_LOGIN NUMBER;
2603     X_REQUEST_ID NUMBER;
2604     X_PROGRAM_ID NUMBER;
2605     X_PROGRAM_APPLICATION_ID NUMBER;
2606     X_PROGRAM_UPDATE_DATE DATE;
2607 
2608 
2609 begin
2610   X_LAST_UPDATE_DATE := SYSDATE;
2611   if(X_MODE = 'I') then
2612     X_LAST_UPDATED_BY := 1;
2613     X_LAST_UPDATE_LOGIN := 0;
2614   elsif (X_MODE = 'R') then
2615     X_LAST_UPDATED_BY := FND_GLOBAL.USER_ID;
2616     if X_LAST_UPDATED_BY is NULL then
2617       X_LAST_UPDATED_BY := -1;
2618     end if;
2619     X_LAST_UPDATE_LOGIN :=FND_GLOBAL.LOGIN_ID;
2620     if X_LAST_UPDATE_LOGIN is NULL then
2621       X_LAST_UPDATE_LOGIN := -1;
2622     end if;
2623   else
2624     FND_MESSAGE.SET_NAME('FND', 'SYSTEM-INVALID ARGS');
2625       IGS_GE_MSG_STACK.ADD;
2626     app_exception.raise_exception;
2627   end if;
2628 
2629    Before_DML(
2630                 p_action=>'UPDATE',
2631                 x_rowid=>X_ROWID,
2632                x_unit_cd=>X_UNIT_CD,
2633                x_version_number=>X_VERSION_NUMBER,
2634                x_cal_type=>X_CAL_TYPE,
2635                x_ci_sequence_number=>X_CI_SEQUENCE_NUMBER,
2636                x_location_cd=>X_LOCATION_CD,
2637                x_unit_class=>X_UNIT_CLASS,
2638                x_uoo_id=>X_UOO_ID,
2639                x_ivrs_available_ind=>NVL(X_IVRS_AVAILABLE_IND,'Y' ),
2640                x_call_number=>X_CALL_NUMBER,
2641                x_unit_section_status=>X_UNIT_SECTION_STATUS,
2642                x_unit_section_start_date=>X_UNIT_SECTION_START_DATE,
2643                x_unit_section_end_date=>X_UNIT_SECTION_END_DATE,
2644                x_enrollment_actual=>X_ENROLLMENT_ACTUAL,
2645                x_waitlist_actual=>X_WAITLIST_ACTUAL,
2646                x_offered_ind=>NVL(X_OFFERED_IND,'Y' ),
2647                x_state_financial_aid=>X_STATE_FINANCIAL_AID,
2648                x_grading_schema_prcdnce_ind=>NVL(X_GRADING_SCHEMA_PRCDNCE_IND,'N' ),
2649                x_federal_financial_aid=>X_FEDERAL_FINANCIAL_AID,
2650                x_unit_quota=>X_UNIT_QUOTA,
2651                x_unit_quota_reserved_places=>X_UNIT_QUOTA_RESERVED_PLACES,
2652                x_institutional_financial_aid=>X_INSTITUTIONAL_FINANCIAL_AID,
2653                x_unit_contact=>X_UNIT_CONTACT,
2654                x_grading_schema_cd=>X_GRADING_SCHEMA_CD,
2655                x_gs_version_number=>X_GS_VERSION_NUMBER,
2656                x_owner_org_unit_cd                 => x_owner_org_unit_cd,
2657                x_attendance_required_ind           => x_attendance_required_ind,
2658                x_reserved_seating_allowed          => x_reserved_seating_allowed,
2659                x_special_permission_ind            => x_special_permission_ind,
2660                x_ss_display_ind                    => x_ss_display_ind,
2661                x_creation_date=>X_LAST_UPDATE_DATE,
2662                x_created_by=>X_LAST_UPDATED_BY,
2663                x_last_update_date=>X_LAST_UPDATE_DATE,
2664                x_last_updated_by=>X_LAST_UPDATED_BY,
2665                x_last_update_login=>X_LAST_UPDATE_LOGIN,
2666                x_ss_enrol_ind =>X_SS_ENROL_IND,
2667                x_dir_enrollment =>X_DIR_ENROLLMENT,
2668                x_enr_from_wlst =>X_ENR_FROM_WLST,
2669                x_inq_not_wlst =>X_INQ_NOT_WLST,
2670                x_rev_account_cd => x_rev_account_cd,
2671                x_anon_unit_grading_ind => x_anon_unit_grading_ind,
2672                x_anon_assess_grading_ind => x_anon_assess_grading_ind,
2673                x_non_std_usec_ind => x_non_std_usec_ind,
2674                x_auditable_ind => x_auditable_ind,
2675                x_audit_permission_ind => x_audit_permission_ind,
2676                x_not_multiple_section_flag => x_not_multiple_section_flag,
2677                x_sup_uoo_id => x_sup_uoo_id,
2678                x_relation_type => x_relation_type,
2679                x_default_enroll_flag => x_default_enroll_flag,
2680 	       x_abort_flag => x_abort_flag
2681 );
2682 
2683   if (X_MODE = 'R') then
2684    X_REQUEST_ID := FND_GLOBAL.CONC_REQUEST_ID;
2685    X_PROGRAM_ID := FND_GLOBAL.CONC_PROGRAM_ID;
2686    X_PROGRAM_APPLICATION_ID := FND_GLOBAL.PROG_APPL_ID;
2687   if (X_REQUEST_ID = -1) then
2688      X_REQUEST_ID := OLD_REFERENCES.REQUEST_ID;
2689      X_PROGRAM_ID := OLD_REFERENCES. PROGRAM_ID;
2690      X_PROGRAM_APPLICATION_ID :=
2691                 OLD_REFERENCES.PROGRAM_APPLICATION_ID;
2692      X_PROGRAM_UPDATE_DATE :=
2693                   OLD_REFERENCES.PROGRAM_UPDATE_DATE;
2694   else
2695      X_PROGRAM_UPDATE_DATE := SYSDATE;
2696   end if;
2697   end if;
2698 
2699    update IGS_PS_UNIT_OFR_OPT_ALL set
2700       UOO_ID =  NEW_REFERENCES.UOO_ID,
2701       IVRS_AVAILABLE_IND =  NEW_REFERENCES.IVRS_AVAILABLE_IND,
2702       CALL_NUMBER =  NEW_REFERENCES.CALL_NUMBER,
2703       UNIT_SECTION_STATUS =  NEW_REFERENCES.UNIT_SECTION_STATUS,
2704       UNIT_SECTION_START_DATE =  NEW_REFERENCES.UNIT_SECTION_START_DATE,
2705       UNIT_SECTION_END_DATE =  NEW_REFERENCES.UNIT_SECTION_END_DATE,
2706       ENROLLMENT_ACTUAL =  NEW_REFERENCES.ENROLLMENT_ACTUAL,
2707       WAITLIST_ACTUAL =  NEW_REFERENCES.WAITLIST_ACTUAL,
2708       OFFERED_IND =  NEW_REFERENCES.OFFERED_IND,
2709       STATE_FINANCIAL_AID =  NEW_REFERENCES.STATE_FINANCIAL_AID,
2710       GRADING_SCHEMA_PRCDNCE_IND =  NEW_REFERENCES.GRADING_SCHEMA_PRCDNCE_IND,
2711       FEDERAL_FINANCIAL_AID =  NEW_REFERENCES.FEDERAL_FINANCIAL_AID,
2712       UNIT_QUOTA =  NEW_REFERENCES.UNIT_QUOTA,
2713       UNIT_QUOTA_RESERVED_PLACES =  NEW_REFERENCES.UNIT_QUOTA_RESERVED_PLACES,
2714       INSTITUTIONAL_FINANCIAL_AID =  NEW_REFERENCES.INSTITUTIONAL_FINANCIAL_AID,
2715       UNIT_CONTACT =  NEW_REFERENCES.UNIT_CONTACT,
2716       GRADING_SCHEMA_CD =  NEW_REFERENCES.GRADING_SCHEMA_CD,
2717       GS_VERSION_NUMBER =  NEW_REFERENCES.GS_VERSION_NUMBER,
2718       owner_org_unit_cd                 = new_references.owner_org_unit_cd,
2719       attendance_required_ind           = new_references.attendance_required_ind,
2720       reserved_seating_allowed          = new_references.reserved_seating_allowed,
2721       special_permission_ind            = new_references.special_permission_ind,
2722       ss_display_ind                    = new_references.ss_display_ind,
2723       LAST_UPDATE_DATE = X_LAST_UPDATE_DATE,
2724       LAST_UPDATED_BY = X_LAST_UPDATED_BY,
2725       LAST_UPDATE_LOGIN = X_LAST_UPDATE_LOGIN,
2726       REQUEST_ID = X_REQUEST_ID,
2727       PROGRAM_ID = X_PROGRAM_ID,
2728       PROGRAM_APPLICATION_ID = X_PROGRAM_APPLICATION_ID,
2729       PROGRAM_UPDATE_DATE = X_PROGRAM_UPDATE_DATE,
2730       SS_ENROL_IND = X_SS_ENROL_IND,
2731       DIR_ENROLLMENT = new_references.DIR_ENROLLMENT,
2732       ENR_FROM_WLST = new_references.ENR_FROM_WLST,
2733       INQ_NOT_WLST = new_references.INQ_NOT_WLST,
2734       rev_account_cd = new_references.rev_account_cd ,
2735       anon_unit_grading_ind = new_references.anon_unit_grading_ind ,
2736       anon_assess_grading_ind = new_references.anon_assess_grading_ind,
2737       NON_STD_USEC_IND = new_references.NON_STD_USEC_IND ,
2738       auditable_ind = new_references.auditable_ind,
2739       audit_permission_ind = new_references.audit_permission_ind,
2740       not_multiple_section_flag = new_references.not_multiple_section_flag,
2741       sup_uoo_id = new_references.sup_uoo_id,
2742       relation_type = new_references.relation_type,
2743       default_enroll_flag = new_references.default_enroll_flag,
2744       abort_flag= new_references.abort_flag
2745      where ROWID = X_ROWID;
2746 
2747   if (sql%notfound) then
2748     raise no_data_found;
2749   end if;
2750   --
2751   -- code added as part of waitlist part 1 build
2752   -- code is added to call the auto enroll process
2753   --
2754   DECLARE
2755       l_request_id   NUMBER;
2756       l_auto_enroll igs_en_inst_wl_stps.auto_enroll_waitlist_flag%TYPE;
2757       CURSOR cur_auto_enroll is
2758       SELECT auto_enroll_waitlist_flag
2759       FROM IGS_EN_INST_WL_STPS;
2760   BEGIN
2761     OPEN cur_auto_enroll;
2762     FETCH cur_auto_enroll INTO l_auto_enroll;
2763     CLOSE cur_auto_enroll;
2764 
2765 
2766     IF new_references.unit_section_status = 'HOLD'AND
2767         (old_references.unit_section_status <> 'HOLD' OR new_references.reserved_seating_allowed = 'Y') AND
2768         nvl(l_auto_enroll,'N') = 'Y' THEN
2769 
2770       l_request_id := FND_REQUEST.SUBMIT_REQUEST (
2771          application => 'IGS',
2772          program => 'IGSENJ04',
2773          description => 'Enroll Students From Waitlist Process',
2774          start_time => NULL,
2775          sub_request => FALSE,
2776          argument1 => new_references.uoo_id,
2777          argument2 => new_references.org_id,
2778          argument3 => chr(0),
2779          argument4  => '', argument5  => '', argument6  => '', argument7  => '', argument8  => '',
2780          argument9  => '', argument10 => '', argument11 => '', argument12 => '', argument13 => '',
2781          argument14 => '', argument15 => '', argument16 => '', argument17 => '', argument18 => '',
2782          argument19 => '', argument20 => '', argument21 => '', argument22 => '', argument23 => '',
2783          argument24 => '', argument25 => '', argument26 => '', argument27 => '', argument28 => '',
2784          argument29 => '', argument30 => '', argument31 => '', argument32 => '', argument33 => '',
2785          argument34 => '', argument35 => '', argument36 => '', argument37 => '', argument38 => '',
2786          argument39 => '', argument40 => '', argument41 => '', argument42 => '', argument43 => '',
2787          argument44 => '', argument45 => '', argument46 => '', argument47 => '', argument48 => '',
2788          argument49 => '', argument50 => '', argument51 => '', argument52 => '', argument53 => '',
2789          argument54 => '', argument55 => '', argument56 => '', argument57 => '', argument58 => '',
2790          argument59 => '', argument60 => '', argument61 => '', argument62 => '', argument63 => '',
2791          argument64 => '', argument65 => '', argument66 => '', argument67 => '', argument68 => '',
2792          argument69 => '', argument70 => '', argument71 => '', argument72 => '', argument73 => '',
2793          argument74 => '', argument75 => '', argument76 => '', argument77 => '', argument78 => '',
2794          argument79 => '', argument80 => '', argument81 => '', argument82 => '', argument83 => '',
2795          argument84 => '', argument85 => '', argument86 => '', argument87 => '', argument88 => '',
2796          argument89 => '', argument90 => '', argument91 => '', argument92 => '', argument93 => '',
2797          argument94 => '', argument95 => '', argument96 => '', argument97 => '', argument98 => '',
2798          argument99 => '', argument100 => '');
2799 
2800     END IF;
2801   END; -- end of code addition as part of waitlist part 1
2802   After_DML (
2803                 p_action => 'UPDATE' ,
2804                 x_rowid => X_ROWID );
2805 
2806 end UPDATE_ROW;
2807 
2808  procedure ADD_ROW (
2809       X_ROWID in out NOCOPY VARCHAR2,
2810        x_UNIT_CD IN VARCHAR2,
2811        x_VERSION_NUMBER IN NUMBER,
2812        x_CAL_TYPE IN VARCHAR2,
2813        x_CI_SEQUENCE_NUMBER IN NUMBER,
2814        x_LOCATION_CD IN VARCHAR2,
2815        x_UNIT_CLASS IN VARCHAR2,
2816        x_UOO_ID IN NUMBER,
2817        x_IVRS_AVAILABLE_IND IN VARCHAR2,
2818        x_CALL_NUMBER IN OUT NOCOPY NUMBER,
2819        x_UNIT_SECTION_STATUS IN VARCHAR2,
2820        x_UNIT_SECTION_START_DATE IN DATE,
2821        x_UNIT_SECTION_END_DATE IN DATE,
2822        x_ENROLLMENT_ACTUAL IN NUMBER,
2823        x_WAITLIST_ACTUAL IN NUMBER,
2824        x_OFFERED_IND IN VARCHAR2,
2825        x_STATE_FINANCIAL_AID IN VARCHAR2,
2826        x_GRADING_SCHEMA_PRCDNCE_IND IN VARCHAR2,
2827        x_FEDERAL_FINANCIAL_AID IN VARCHAR2,
2828        x_UNIT_QUOTA IN NUMBER,
2829        x_UNIT_QUOTA_RESERVED_PLACES IN NUMBER,
2830        x_INSTITUTIONAL_FINANCIAL_AID IN VARCHAR2,
2831        x_UNIT_CONTACT IN NUMBER,
2832        x_GRADING_SCHEMA_CD IN VARCHAR2,
2833        x_GS_VERSION_NUMBER IN NUMBER,
2834        x_owner_org_unit_cd                 IN     VARCHAR2 ,
2835        x_attendance_required_ind           IN     VARCHAR2 ,
2836        x_reserved_seating_allowed          IN     VARCHAR2 ,
2837        x_special_permission_ind            IN     VARCHAR2 ,
2838        x_ss_display_ind                    IN     VARCHAR2 ,
2839        X_MODE in VARCHAR2 ,
2840        X_ORG_ID IN NUMBER,
2841        x_SS_ENROL_IND IN VARCHAR2 ,
2842        x_dir_enrollment IN NUMBER ,
2843        x_enr_from_wlst  IN NUMBER ,
2844        x_inq_not_wlst  IN NUMBER ,
2845        x_rev_account_cd IN VARCHAR2 ,
2846        x_anon_unit_grading_ind IN VARCHAR2 ,
2847        x_anon_assess_grading_ind IN VARCHAR2 ,
2848        X_NON_STD_USEC_IND IN VARCHAR2 ,
2849        x_auditable_ind IN VARCHAR2,
2850        x_audit_permission_ind IN VARCHAR2,
2851        x_not_multiple_section_flag IN VARCHAR2,
2852        x_sup_uoo_id IN NUMBER ,
2853        x_relation_type VARCHAR2 ,
2854        x_default_enroll_flag VARCHAR2,
2855        x_abort_flag VARCHAR2
2856 
2857   ) AS
2858   /*************************************************************
2859   Created By :
2860   Date Created By :
2861   Purpose :
2862   Know limitations, enhancements or remarks
2863   Change History
2864   Who             When            What
2865   vvutukur        05-Aug-2003     Enh#3045069.PSP Enh Build. Added column not_multiple_section_flag.
2866   shtatiko        06-NOV-2002     Added auditable_ind and audit_permission_ind
2867                                   as part of Bug# 2636716
2868   msrinivi        17 Aug-2001     Bug 1882122 : Added rev_account_cd
2869   rgangara        07-May-2001     Added ss_enrol_ind col
2870   (reverse chronological order - newest change first)
2871   ***************************************************************/
2872 
2873     cursor c1 is select ROWID from IGS_PS_UNIT_OFR_OPT_ALL
2874              where     UNIT_CD= X_UNIT_CD
2875             and VERSION_NUMBER = X_VERSION_NUMBER
2876             and CAL_TYPE = X_CAL_TYPE
2877             and CI_SEQUENCE_NUMBER = X_CI_SEQUENCE_NUMBER
2878             and LOCATION_CD = X_LOCATION_CD
2879             and UNIT_CLASS = X_UNIT_CLASS
2880 ;
2881 begin
2882         open c1;
2883                 fetch c1 into X_ROWID;
2884         if (c1%notfound) then
2885         close c1;
2886     INSERT_ROW (
2887       X_ROWID,
2888        X_UNIT_CD,
2889        X_VERSION_NUMBER,
2890        X_CAL_TYPE,
2891        X_CI_SEQUENCE_NUMBER,
2892        X_LOCATION_CD,
2893        X_UNIT_CLASS,
2894        X_UOO_ID,
2895        X_IVRS_AVAILABLE_IND,
2896        X_CALL_NUMBER,
2897        X_UNIT_SECTION_STATUS,
2898        X_UNIT_SECTION_START_DATE,
2899        X_UNIT_SECTION_END_DATE,
2900        X_ENROLLMENT_ACTUAL,
2901        X_WAITLIST_ACTUAL,
2902        X_OFFERED_IND,
2903        X_STATE_FINANCIAL_AID,
2904        X_GRADING_SCHEMA_PRCDNCE_IND,
2905        X_FEDERAL_FINANCIAL_AID,
2906        X_UNIT_QUOTA,
2907        X_UNIT_QUOTA_RESERVED_PLACES,
2908        X_INSTITUTIONAL_FINANCIAL_AID,
2909        X_UNIT_CONTACT,
2910        X_GRADING_SCHEMA_CD,
2911        X_GS_VERSION_NUMBER,
2912        x_owner_org_unit_cd,
2913        x_attendance_required_ind,
2914        x_reserved_seating_allowed,
2915        x_special_permission_ind,
2916        x_ss_display_ind,
2917       X_MODE,
2918       X_ORG_ID,
2919       X_SS_ENROL_IND,
2920       X_DIR_ENROLLMENT,
2921       X_ENR_FROM_WLST,
2922       X_INQ_NOT_WLST,
2923       x_rev_account_cd ,
2924       x_anon_unit_grading_ind,
2925       x_anon_assess_grading_ind,
2926       X_NON_STD_USEC_IND,
2927       x_auditable_ind,
2928       x_audit_permission_ind,
2929       x_not_multiple_section_flag,
2930       x_sup_uoo_id,
2931       x_relation_type,
2932       x_default_enroll_flag,
2933       x_abort_flag
2934  );
2935      return;
2936         end if;
2937            close c1;
2938 UPDATE_ROW (
2939       X_ROWID,
2940        X_UNIT_CD,
2941        X_VERSION_NUMBER,
2942        X_CAL_TYPE,
2943        X_CI_SEQUENCE_NUMBER,
2944        X_LOCATION_CD,
2945        X_UNIT_CLASS,
2946        X_UOO_ID,
2947        X_IVRS_AVAILABLE_IND,
2948        X_CALL_NUMBER,
2949        X_UNIT_SECTION_STATUS,
2950        X_UNIT_SECTION_START_DATE,
2951        X_UNIT_SECTION_END_DATE,
2952        X_ENROLLMENT_ACTUAL,
2953        X_WAITLIST_ACTUAL,
2954        X_OFFERED_IND,
2955        X_STATE_FINANCIAL_AID,
2956        X_GRADING_SCHEMA_PRCDNCE_IND,
2957        X_FEDERAL_FINANCIAL_AID,
2958        X_UNIT_QUOTA,
2959        X_UNIT_QUOTA_RESERVED_PLACES,
2960        X_INSTITUTIONAL_FINANCIAL_AID,
2961        X_UNIT_CONTACT,
2962        X_GRADING_SCHEMA_CD,
2963        X_GS_VERSION_NUMBER,
2964        x_owner_org_unit_cd,
2965        x_attendance_required_ind,
2966        x_reserved_seating_allowed,
2967        x_special_permission_ind,
2968        x_ss_display_ind,
2969        X_MODE,
2970        X_SS_ENROL_IND,
2971        X_DIR_ENROLLMENT,
2972        X_ENR_FROM_WLST,
2973        X_INQ_NOT_WLST,
2974        x_rev_account_cd,
2975        x_anon_unit_grading_ind,
2976        x_anon_assess_grading_ind,
2977        X_NON_STD_USEC_IND,
2978        x_auditable_ind,
2979        x_audit_permission_ind,
2980        x_not_multiple_section_flag,
2981        x_sup_uoo_id,
2982        x_relation_type,
2983        x_default_enroll_flag,
2984        x_abort_flag
2985 );
2986 end ADD_ROW;
2987 
2988 procedure DELETE_ROW (
2989   X_ROWID in VARCHAR2
2990 ) AS
2991   /*************************************************************
2992    Created By : kdande@in
2993    Date Created By : 2000/05/11
2994    Purpose :
2995    Know limitations, enhancements or remarks
2996    Change History
2997    Who             When            What
2998 
2999    (reverse chronological order - newest change first)
3000   ***************************************************************/
3001 begin
3002   Before_DML (
3003      p_action => 'DELETE',
3004      x_rowid => X_ROWID
3005     );
3006 
3007   delete from IGS_PS_UNIT_OFR_OPT_ALL
3008   where ROWID = X_ROWID
3009   ;
3010   if (sql%notfound) then
3011     raise no_data_found;
3012   end if;
3013   After_DML (
3014                 p_action => 'DELETE' ,
3015                 x_rowid => X_ROWID );
3016 
3017 end DELETE_ROW;
3018 
3019 end IGS_PS_UNIT_OFR_OPT_PKG;