DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_GE_GEN_003

Source


1 PACKAGE BODY igs_ge_gen_003 AS
2 /* $Header: IGSGE03B.pls 120.2 2006/05/30 09:08:06 vskumar noship $ */
3 /* Change History
4    Who        When         What
5    jbegum     15-Feb-02    As part of Enh bug #2222272 modified FUNCTION get_org_id
6                            Explicitly the org id is being returned as null
7                to remove multi org functionality from OSS
8    knaraset   14-Nov-2002  added get_person_id,get_program_version,get_calendar_instance,
9                            get_susa_sequence_num as part of Build TD Legacy HESA SPA Bug 2661533
10    kumma      08-May-2003  2941138, Changed the procedure get_calendar_instance to not to use bind variable for cal_category
11                            Bind variables should only be used for alternate code as cal_category is hard_coded in the caller and is not user enterable
12    knaraset  29-Apr-03   Added parameter p_uoo_id in procedure GENP_INS_TODO_REF and passed uoo_id in TBH calls of IGS_PE_STD_TODO_REF,
13                          as part of MUS build bug 2829262
14    pkpatel    11-JUN-2003  Bug 2941138 (Closed the cursors cur_cal_cat_inst_cnt, cur_cal_cat_inst_dtls in procedure get_calendar_instance)
15    pkpatel    6-sep-2004   Bug 3868572 (Made the variable l_reference_number from NUMBER(7) to NUMBER)
16 */
17 l_rowid VARCHAR2(25);
18 FUNCTION GENP_GET_USER_PERSON(
19   p_oracle_username IN VARCHAR2 ,
20   p_staff_member_ind OUT NOCOPY VARCHAR2 )
21 RETURN NUMBER AS
22     gv_other_detail         VARCHAR2(255);
23 BEGIN   -- genp_get_user_person
24     -- Module to get the IGS_PE_PERSON id for a system user
25 /*
26 DECLARE
27     v_person_id     IGS_PE_PERSON.person_id%TYPE;
28     v_staff_member_ind  IGS_PE_PERSON.staff_member_ind%TYPE;
29     CURSOR c_person (
30             cp_oracle_username  IGS_PE_PERSON.oracle_username%TYPE) IS
31         SELECT  pe.person_id,
32             pe.staff_member_ind
33         FROM    IGS_PE_PERSON pe
34         WHERE   pe.oracle_username = cp_oracle_username;
35 BEGIN
36 
37     OPEN    c_person(
38             p_oracle_username);
39     FETCH   c_person INTO   v_person_id,
40                 v_staff_member_ind;
41     IF(c_person%NOTFOUND) THEN
42         CLOSE c_person;
43         p_staff_member_ind := NULL;
44         RETURN NULL;
45     ELSE
46         CLOSE c_person;
47         p_staff_member_ind := v_staff_member_ind;
48         RETURN v_person_id;
49     END IF;
50 END;
51 EXCEPTION
52     WHEN OTHERS THEN
53         Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
54         IGS_GE_MSG_STACK.ADD;
55         App_Exception.Raise_Exception ;
56       */
57         RETURN 0;
58 END genp_get_user_person;
59 
60 PROCEDURE GENP_INS_LOG(
61   p_s_log_type IN VARCHAR2 ,
62   p_key IN VARCHAR2 ,
63   p_creation_dt OUT NOCOPY DATE )
64 AS
65     v_other_detail  VARCHAR2(255);
66     v_creation_dt   DATE;
67     l_rowid             VARCHAR2(25);
68 BEGIN
69     -- this module inserts an entry into the system
70     -- log and returns the creation date.
71     -- set the creation dt to be the system date
72     v_creation_dt := SYSDATE;
73     -- insert a record into IGS_GE_S_LOG
74     IGS_GE_S_LOG_PKG.INSERT_ROW(
75         x_rowid => l_rowid ,
76         x_s_log_type => p_s_log_type,
77         x_creation_dt =>v_creation_dt,
78         x_key =>p_key,
79         x_mode => 'R' );
80     -- set the output required
81     p_creation_dt := v_creation_dt;
82 EXCEPTION
83     WHEN OTHERS THEN
84        if SQLCODE <> -20001 then
85           Fnd_Message.Set_Name ('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
86           IGS_GE_MSG_STACK.ADD;
87          App_Exception.Raise_Exception(Null, Null, fnd_message.get);
88        else
89          RAISE;
90         end if;
91 --      Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
92                 IGS_GE_MSG_STACK.ADD;
93 --      App_Exception.Raise_Exception ;
94 END GENP_INS_LOG;
95 
96 
97  PROCEDURE GENP_INS_LOG_ENTRY(
98   p_s_log_type IN VARCHAR2 ,
99   p_creation_dt IN DATE ,
100   p_key IN VARCHAR2 ,
101   p_s_message_name IN VARCHAR2 ,
102   p_text IN VARCHAR2 )
103 AS
104     l_rowid             VARCHAR2(25);
105     v_other_detail  VARCHAR2(350);
106     L_VAL NUMBER;
107 BEGIN
108     -- this module inserts and entry into the
109     -- system logging structure
110     SELECT IGS_GE_S_ERROR_LOG_SEQ_NUM_S.nextval INTO L_VAL
111     FROM DUAL;
112 
113     IGS_GE_S_LOG_ENTRY_PKG.INSERT_ROW(
114         x_rowid => l_rowid ,
115         x_s_log_type => p_s_log_type,
116         x_creation_dt => p_creation_dt,
117         x_sequence_number => L_VAL,
118         x_key => p_key,
119         x_message_name => p_s_message_name,
120         x_text => p_text,
121         x_mode => 'R');
122 EXCEPTION
123     WHEN OTHERS THEN
124        if SQLCODE <> -20001 then
125           Fnd_Message.Set_Name ('IGS', 'IGS_GE_UNHANDLED_EXCEPTION');
126           IGS_GE_MSG_STACK.ADD;
127          App_Exception.Raise_Exception(Null, Null, fnd_message.get);
128        else
129          RAISE;
130         end if;
131 --      Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
132                 IGS_GE_MSG_STACK.ADD;
133 --      App_Exception.Raise_Exception ;
134 END genp_ins_log_entry;
135 
136 
137  FUNCTION genp_ins_stdnt_todo(
138   p_person_id IN NUMBER ,
139   p_s_student_todo_type IN VARCHAR2 ,
140   p_todo_dt IN DATE ,
141   p_single_entry_ind IN VARCHAR2)
142 RETURN NUMBER AS
143     gv_other_details        VARCHAR2(255);
144     l_rowid             VARCHAR2(25);
145 
146 BEGIN   -- genp_ins_stdnt_todo
147     -- Create a 'todo' item for a student on the IGS_PE_STD_TODO table.
148     -- The 'single entry' option, if flagged as Y indicates that if
149     -- an outstanding todo entry already exists (with an appropriate
150     -- todo date) then another isn't to be created.
151     -- The procedure was altered to a function to cater for returning
152     -- the sequence number so that it can be used when inserting IGS_PE_STD_TODO_REF
153     -- items for the todo item.
154 DECLARE
155     CURSOR c_st (
156             cp_person_id        IGS_PE_STD_TODO.person_id%TYPE,
157             cp_s_student_todo_type  IGS_PE_STD_TODO.s_student_todo_type%TYPE,
158             cp_todo_dt          IGS_PE_STD_TODO.todo_dt%TYPE) IS
159         SELECT  sequence_number
160         FROM    IGS_PE_STD_TODO
161         WHERE   person_id       = cp_person_id AND
162             s_student_todo_type     = cp_s_student_todo_type AND
163             logical_delete_dt   IS NULL AND
164             (todo_dt        IS NULL OR
165             todo_dt         <= cp_todo_dt);
166     CURSOR c_get_nxt_seq IS
167             SELECT IGS_PE_STD_TODO_SEQ_NUM_S.nextval
168             FROM DUAL;
169     v_st_rec                    c_st%ROWTYPE;
170     v_todo_compare              IGS_PE_STD_TODO.todo_dt%TYPE;
171     v_sequence_num              NUMBER;
172 BEGIN
173     IF (p_single_entry_ind = 'Y') THEN
174         IF (p_todo_dt IS NULL) THEN
175             v_todo_compare := SYSDATE;
176         ELSE
177             v_todo_compare := p_todo_dt;
178         END IF;
179         OPEN c_st(
180             p_person_id,
181             p_s_student_todo_type,
182             v_todo_compare);
183         FETCH c_st INTO v_st_rec;
184         IF (c_st%FOUND) THEN
185             CLOSE c_st;
186             -- Exit routine without inserting
187             RETURN v_st_rec.sequence_number;
188         END IF;
189         CLOSE c_st;
190     END IF;
191     OPEN c_get_nxt_seq;
192     FETCH c_get_nxt_seq INTO v_sequence_num;
193     CLOSE c_get_nxt_seq;
194 
195     IGS_PE_STD_TODO_PKG.INSERT_ROW (
196         x_rowid => l_rowid ,
197         X_person_id =>p_person_id,
198         x_s_student_todo_type => p_s_student_todo_type,
199         x_sequence_number => v_sequence_num,
200         x_todo_dt => p_todo_dt,
201         x_logical_delete_dt => NULL ,
202         x_mode => 'R');
203     RETURN v_sequence_num;
204 END;
205 EXCEPTION
206     WHEN OTHERS THEN
207         Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
208         IGS_GE_MSG_STACK.ADD;
209         App_Exception.Raise_Exception ;
210 END genp_ins_stdnt_todo;
211 
212  PROCEDURE GENP_SET_SLE_COUNT(
213   p_s_log_type IN VARCHAR2 ,
214   p_key IN VARCHAR2 ,
215   p_sle_key IN VARCHAR2 ,
216   p_message_name IN VARCHAR2,
217   p_count IN NUMBER ,
218   p_creation_dt IN OUT NOCOPY DATE ,
219   p_total_count OUT NOCOPY NUMBER )
220 AS
221     gv_other_detail     VARCHAR2(255);
222 BEGIN   -- genp_set_sle_count
223     -- This module is used to keep a count in the IGS_GE_S_LOG_ENTRY table.
224     -- It will generally be called by batch routines that keep a count of
225     -- records processed up to the point of the routines last commit point.
226     -- If an exception is encountered at anytime, then the count will not be
227     -- compromised upto the point of last committing and can be used in exception
228     -- reporting to indicate the number of records processed
229     -- (or what ever the count is to represent).
230 DECLARE
231     v_new_log   BOOLEAN := FALSE;
232     v_update_log    BOOLEAN := FALSE;
233     v_total_count   NUMBER := 0;
234     CURSOR  c_sle IS
235         SELECT  rowid, SLE.*
236         FROM    IGS_GE_S_LOG_ENTRY  sle
237         WHERE   sle.s_log_type  = p_s_log_type AND
238             sle.creation_dt = p_creation_dt AND
239             sle.key     = p_sle_key
240         FOR UPDATE OF sle.text NOWAIT;
241 BEGIN
242     -- Determine if an IGS_GE_S_LOG record exists already
243     IF p_creation_dt IS NULL THEN
244         -- 20Oct99 - This schema.pkg.proc notation should be removed later on.
245         genp_ins_log(
246             p_s_log_type,
247             p_key,
248             p_creation_dt);
249         v_new_log := TRUE;
250     END IF;
251     -- Determine if an entry exists already and update it, otherwise create it.
252     FOR v_sle_rec IN c_sle LOOP
253     --  v_total_count := TO_NUMBER(v_sle_rec.text) + p_count;
254 
255         IGS_GE_S_LOG_ENTRY_pkg.update_row(
256             X_ROWID => v_sle_rec.rowid,
257             X_S_LOG_TYPE => v_sle_rec.s_log_type ,
258             X_CREATION_DT => v_sle_rec.creation_dt ,
259             X_SEQUENCE_NUMBER =>v_sle_rec.sequence_number,
260             X_KEY => v_sle_rec.key ,
261             X_MESSAGE_NAME => v_sle_rec.message_name,
262             X_TEXT => TO_CHAR(TO_NUMBER(v_sle_rec.text) + p_count),
263             X_MODE => 'R'
264             );
265         v_update_log :=TRUE;
266     END LOOP;
267     IF v_new_log OR NOT v_update_log THEN
268         v_total_count := p_count;
269         genp_ins_log_entry (
270             p_s_log_type,
271             p_creation_dt,
272             p_sle_key,
273             p_message_name,
274             v_total_count);
275     END IF;
276     p_total_count := v_total_count;
277 EXCEPTION
278     WHEN OTHERS THEN
279         IF c_sle%ISOPEN THEN
280             CLOSE c_sle;
281         END IF;
282         RAISE;
283 END;
284 EXCEPTION
285     WHEN OTHERS THEN
286         Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
287         IGS_GE_MSG_STACK.ADD;
288         App_Exception.Raise_Exception ;
289 END genp_set_sle_count;
290 
291 
292  FUNCTION GENP_SET_TIME(
293   p_time IN DATE )
294 RETURN DATE AS
295     gv_other_detail         VARCHAR2(255);
296 BEGIN   -- genp_set_time
297     -- This routine will set the date component of a time field to have a
298     -- standard date. It will be used when comparing fields where the time
299     -- is the only component that is being analysed and the date is superfluous.
300 DECLARE
301 BEGIN
302     IF(p_time IS NULL) THEN
303         RETURN IGS_GE_DATE.IGSDATE(NULL);
304     ELSE
305 
306 
307         RETURN (IGS_GE_DATE.IGSDATE(IGS_GE_DATE.IGSCHAR(IGS_GE_DATE.IGSDATE('1900/01/01')) ||
308                 ' ' || TO_CHAR(p_time, 'HH24:MI:SS')));
309     END IF;
310 END;
311 EXCEPTION
312     WHEN OTHERS THEN
313         Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
314         IGS_GE_MSG_STACK.ADD;
315         App_Exception.Raise_Exception ;
316 END genp_set_time;
317 
318 
319  FUNCTION GENP_UPD_STR_LGC_DEL(
320   p_person_id IN NUMBER ,
321   p_s_student_todo_type IN VARCHAR2 ,
322   p_sequence_number IN NUMBER ,
323   p_reference_number IN NUMBER ,
324   p_message_name OUT NOCOPY VARCHAR2 )
325 RETURN BOOLEAN AS
326     e_resource_busy_exception           EXCEPTION;
327     PRAGMA EXCEPTION_INIT(e_resource_busy_exception, -54 );
328     gv_other_details    VARCHAR2(255);
329 BEGIN
330 DECLARE
331     v_str_record        IGS_PE_STD_TODO_REF%ROWTYPE;
332     v_message_name      VARCHAR2(30);
333     v_exists_flag       CHAR;
334     CURSOR c_lock_str_records IS
335         SELECT  *
336         FROM    IGS_PE_STD_TODO_REF
337         WHERE   person_id = p_person_id AND
338             s_student_todo_type = p_s_student_todo_type AND
339             sequence_number = p_sequence_number AND
340             reference_number = p_reference_number
341         FOR UPDATE
342         NOWAIT;
343     CURSOR c_chk_other_str_records IS
344         SELECT  'x'
345         FROM    dual
346         WHERE   EXISTS (
347                 SELECT  person_id
348                 FROM    IGS_PE_STD_TODO_REF
349                 WHERE   person_id = p_person_id                     AND
350                         s_student_todo_type = p_s_student_todo_type AND
351                         sequence_number = p_sequence_number         AND
352                         logical_delete_dt IS NULL
353                 );
354     CURSOR SI_PE_TODO_REF_CUR
355     IS
356     SELECT IGS_PE_STD_TODO_REF.* , ROWID
357     FROM IGS_PE_STD_TODO_REF
358     WHERE   person_id = p_person_id                         AND
359             s_student_todo_type = p_s_student_todo_type     AND
360             sequence_number = p_sequence_number             AND
361             reference_number = p_reference_number;
362 
363 BEGIN
364     -- Issue a save point so that if a lock occurs, the update can be rolled back.
365     SAVEPOINT  sp_str_lgc_del;
366     -- Update the IGS_PE_STD_TODO_REF table with the NOWAIT option.
367     OPEN c_lock_str_records;
368     FETCH c_lock_str_records INTO v_str_record;
369     CLOSE c_lock_str_records;
370 
371     FOR SI_RE_REC IN SI_PE_TODO_REF_CUR LOOP
372 
373     IGS_PE_STD_TODO_REF_PKG.UPDATE_ROW(
374         X_ROWID => SI_RE_REC.ROWID,
375         X_PERSON_ID => SI_RE_REC.PERSON_ID,
376         X_S_STUDENT_TODO_TYPE => SI_RE_REC.S_STUDENT_TODO_TYPE,
377         X_SEQUENCE_NUMBER => SI_RE_REC.SEQUENCE_NUMBER,
378         X_REFERENCE_NUMBER => SI_RE_REC.REFERENCE_NUMBER,
379         X_CAL_TYPE => SI_RE_REC.CAL_TYPE,
380         X_CI_SEQUENCE_NUMBER => SI_RE_REC.CI_SEQUENCE_NUMBER,
381         X_COURSE_CD => SI_RE_REC.COURSE_CD,
382         X_UNIT_CD=> SI_RE_REC.UNIT_CD,
383         X_OTHER_REFERENCE=> SI_RE_REC.OTHER_REFERENCE,
384         X_LOGICAL_DELETE_DT=> SYSDATE,
385         X_MODE=> 'R',
386         X_UOO_ID => SI_RE_REC.UOO_ID
387         );
388     END LOOP;
389     -- Determine if there are any remaining IGS_PE_STD_TODO_REF records remaining to
390     -- be actioned and if not, then logically delete the IGS_PE_STD_TODO record.
391     OPEN c_chk_other_str_records;
392     FETCH c_chk_other_str_records INTO v_exists_flag;
393     IF c_chk_other_str_records%NOTFOUND THEN
394         IF IGS_GE_GEN_004.genp_upd_st_lgc_del(p_person_id,
395             p_s_student_todo_type,
396             p_sequence_number,
397             v_message_name) = FALSE THEN
398             CLOSE c_chk_other_str_records;
399             ROLLBACK TO sp_str_lgc_del;
400             p_message_name := v_message_name;
401             RETURN FALSE;
402         END IF;
403     END IF;
404     CLOSE c_chk_other_str_records;
405     p_message_name := null;
406     RETURN TRUE;
407 END;
408 EXCEPTION
409     WHEN e_resource_busy_exception THEN
410         ROLLBACK TO sp_str_lgc_del;
411         p_message_name := 'IGS_GE_LOG_DEL_REF_ITEM_LOCK';
412         RETURN FALSE;
413     WHEN OTHERS THEN
414         Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
415         IGS_GE_MSG_STACK.ADD;
416         App_Exception.Raise_Exception ;
417 END genp_upd_str_lgc_del;
418 
419 PROCEDURE GENP_INS_TODO_REF(
420   p_person_id IN NUMBER ,
421   p_s_student_todo_type IN VARCHAR2 ,
422   p_sequence_number IN NUMBER ,
423   p_cal_type IN VARCHAR2 ,
424   p_ci_sequence_number IN NUMBER ,
425   p_course_cd IN VARCHAR2 ,
426   p_unit_cd IN VARCHAR2 ,
427   p_other_reference IN VARCHAR2,
428   p_uoo_id IN NUMBER)
429  IS
430  gv_other_detail  VARCHAR2(255);
431  l_rowid      VARCHAR2(25);
432  l_reference_number NUMBER;
433  l_flag VARCHAR2(1) := NULL;
434 BEGIN -- genp_ins_todo_ref
435 
436  -- This routine will insert a student_todo_ref record.
437 
438 DECLARE
439 
440 CURSOR c_dup IS
441   SELECT 1 FROM IGS_PE_STD_TODO_REF WHERE
442   PERSON_ID=P_PERSON_ID AND
443   S_STUDENT_TODO_TYPE=P_S_STUDENT_TODO_TYPE AND
444   SEQUENCE_NUMBER=P_SEQUENCE_NUMBER AND
445   ((CAL_TYPE = P_CAL_TYPE AND CAL_TYPE IS NOT NULL AND P_CAL_TYPE IS NOT NULL) OR (CAL_TYPE IS NULL AND P_CAL_TYPE IS NULL)) AND
446   ((CI_SEQUENCE_NUMBER= P_CI_SEQUENCE_NUMBER AND CI_SEQUENCE_NUMBER IS NOT NULL AND P_CI_SEQUENCE_NUMBER IS NOT NULL) OR (CI_SEQUENCE_NUMBER IS NULL AND P_CI_SEQUENCE_NUMBER IS NULL)) AND
447   ((COURSE_CD= P_COURSE_CD AND COURSE_CD IS NOT NULL AND P_COURSE_CD IS NOT NULL) OR (COURSE_CD IS NULL AND P_COURSE_CD IS NULL)) AND
448   ((UNIT_CD = P_UNIT_CD AND UNIT_CD IS NOT NULL AND P_UNIT_CD IS NOT NULL) OR (UNIT_CD IS NULL AND P_UNIT_CD IS NULL)) AND
449   ((UOO_ID = P_UOO_ID AND UOO_ID IS NOT NULL AND P_UOO_ID IS NOT NULL) OR (UOO_ID IS NULL AND P_UOO_ID IS NULL)) AND
450   ((OTHER_REFERENCE = P_OTHER_REFERENCE AND OTHER_REFERENCE IS NOT NULL AND P_OTHER_REFERENCE IS NOT NULL) OR (OTHER_REFERENCE IS NULL AND P_OTHER_REFERENCE IS NULL)) AND
451   LOGICAL_DELETE_DT IS NULL;
452 
453 
454 BEGIN
455 
456   -- check whether the record being created already exists.
457   OPEN c_dup;
458   FETCH c_dup INTO L_FLAG;
459   CLOSE c_dup;
460 
461   IF l_flag IS NULL THEN
462     SELECT IGS_PE_STD_TODO_REF_RF_NUM_S.NEXTVAL INTO l_reference_number
463                         FROM DUAL;
464 
465     IGS_PE_STD_TODO_REF_PKG.INSERT_ROW (
466         x_rowid => l_rowid ,
467         X_person_id =>p_person_id,
468         x_s_student_todo_type => p_s_student_todo_type,
469         x_sequence_number => p_sequence_number,
470                 x_reference_number => l_reference_number,
471                 x_cal_type  => p_cal_type,
472                 x_ci_sequence_number=>p_ci_sequence_number,
473                 x_course_cd => p_course_cd,
474                 x_unit_cd => p_unit_cd,
475                 x_other_reference => p_other_reference,
476         x_logical_delete_dt => NULL ,
477         x_mode => 'R',
478         x_uoo_id => p_uoo_id);
479   END IF;
480 /* INSERT INTO student_todo_ref (
481 
482     person_id,
483 
484     s_student_todo_type,
485 
486     sequence_number,
487 
488     reference_number,
489 
490     cal_type,
491 
492     ci_sequence_number,
493 
494     course_cd,
495 
496     unit_cd,
497 
498     other_reference)
499 
500  VALUES(
501 
502   p_person_id,
503 
504   p_s_student_todo_type,
505 
506   p_sequence_number,
507 
508   str_sequence_number.nextval,
509 
510   p_cal_type,
511 
512   p_ci_sequence_number,
513 
514   p_course_cd,
515 
516   p_unit_cd,
517 
518   p_other_reference);*/
519 
520 END;
521 
522 
523 EXCEPTION
524     WHEN OTHERS THEN
525         Fnd_Message.Set_Name('IGS' , 'IGS_GE_UNHANDLED_EXCEPTION');
526         IGS_GE_MSG_STACK.ADD;
527         App_Exception.Raise_Exception ;
528 
529 END genp_ins_todo_ref;
530 
531 
532 FUNCTION get_org_id RETURN NUMBER AS
533  CURSOR get_orgid IS
534    SELECT
535    NVL ( TO_NUMBER ( DECODE ( SUBSTRB ( USERENV ('CLIENT_INFO'
536                                                 ), 1, 1
537                                       ), ' ', NULL,  SUBSTRB (USERENV ('CLIENT_INFO'),1,10)
538                              )
539                    ), NULL
540        )
541  FROM dual;
542    l_org_id        NUMBER(15);
543 BEGIN
544  -- Commented out by jbegum as part of Enh bug #2222272
545  -- This code has been commented out to remove multi org functionality from OSS
546  /* OPEN    get_orgid;
547   FETCH   get_orgid  INTO    l_org_id;
548   CLOSE   get_orgid;*/
549   -- Added by jbegum as part of Enh bug #2222272
550   -- The org_id is being passed as null to remove multi org functionality from OSS
551   l_org_id := NULL;
552   RETURN l_org_id;
553 END get_org_id;
554 
555 PROCEDURE set_org_id(p_context IN VARCHAR2) AS
556 p_org_id VARCHAR2(15);
557 
558 BEGIN
559   IF disable_oss = 'Y' THEN
560      fnd_message.set_name ('IGS', 'IGS_GE_CONC_NOT_AVAIL_R12');
561      fnd_file.put_line (fnd_file.LOG, fnd_message.get);
562      fnd_msg_pub.ADD;
563      RAISE g_oss_disable_exception;
564   END IF;
565 
566   IF p_context is NULL THEN
567     FND_PROFILE.GET('ORG_ID',p_org_id);
568   ELSE
569     p_org_id := p_context;
570   END IF;
571   FND_CLIENT_INFO.SET_ORG_CONTEXT(p_org_id);
572 END set_org_id;
573 
574 /*------------------------------------------------------------------
575 --Created by  : knaraset, Oracle IDC
576 --Date created: 14-Nov-2002
577 --
578 --Purpose:Function to get the person ID for the given person number
579 --        returns NULL if no person or more than one person found in the system.
580 --
581 --Known limitations/enhancements and/or remarks:
582 --
583 --Change History:
584 --Who         When               What
585 --
586 ------------------------------------------------------------------  */
587 FUNCTION get_person_id(
588   p_person_number IN VARCHAR2)
589 RETURN NUMBER AS
590 
591 -- cursor to select person ID corresponding to the given person number
592 -- This cursor will fetch no records when the person is not exists in the system
593 -- or more than one person is matching the criteria.
594 CURSOR cur_person_id IS
595 SELECT person_id
596 FROM igs_pe_person_base_v
597 WHERE person_number = p_person_number
598 AND 1 = (SELECT COUNT(*)
599          FROM igs_pe_person_base_v
600          WHERE person_number = p_person_number);
601 
602 l_person_id igs_pe_person_base_v.person_id%TYPE;
603 BEGIN
604 
605   l_person_id := NULL;
606 
607   IF p_person_number IS NOT NULL THEN
608      OPEN  cur_person_id;
609      FETCH cur_person_id INTO l_person_id;
610      CLOSE cur_person_id;
611   END IF;
612 
613   RETURN l_person_id;
614 
615 EXCEPTION
616    WHEN OTHERS THEN
617         FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
618         FND_MESSAGE.SET_TOKEN('NAME', 'igs_ge_gen_003.get_person_id');
619         IGS_GE_MSG_STACK.ADD;
620         APP_EXCEPTION.RAISE_EXCEPTION;
621 
622 END get_person_id;
623 
624 /*------------------------------------------------------------------
625 --Created by  : knaraset, Oracle IDC
626 --Date created: 14-Nov-2002
627 --
628 --Purpose:Function to get the version number for the given program attempt
629 --        returns NULL if no program attempt found in the system.
630 --
631 --Known limitations/enhancements and/or remarks:
632 --
633 --Change History:
634 --Who         When               What
635 --
636 ------------------------------------------------------------------  */
637 FUNCTION get_program_version(
638   p_person_id IN NUMBER,
639   p_program_cd IN VARCHAR2)
640 RETURN NUMBER AS
641 
642 -- cursor to select version number of the program for the given program attempt
643 -- This cursor will fetch no records when the program attempt is not exists in the system
644 --
645 CURSOR cur_prgm_version IS
646 SELECT version_number
647 FROM igs_en_stdnt_ps_att
648 WHERE person_id = p_person_id
649 AND course_cd = p_program_cd;
650 
651 l_prgm_version igs_en_stdnt_ps_att.version_number%TYPE;
652 
653 BEGIN
654 
655   l_prgm_version := NULL;
656 
657   IF p_person_id IS NOT NULL AND p_program_cd IS NOT NULL THEN
658      OPEN cur_prgm_version;
659      FETCH cur_prgm_version INTO l_prgm_version;
660      CLOSE cur_prgm_version;
661   END IF;
662 
663   RETURN l_prgm_version;
664 
665 EXCEPTION
666    WHEN OTHERS THEN
667         FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
668         FND_MESSAGE.SET_TOKEN('NAME', 'igs_ge_gen_003.get_program_version');
669         IGS_GE_MSG_STACK.ADD;
670         APP_EXCEPTION.RAISE_EXCEPTION;
671 
672 END get_program_version;
673 
674 /*------------------------------------------------------------------
675 --Created by  : knaraset, Oracle IDC
676 --Date created: 14-Nov-2002
677 --
678 --Purpose:procedure which returns the calendar details of the given caledar alternate code as OUT params.
679 --        returns NULL if no calendar instance found or more than one calendar instance found in the system.
680 --
681 --Known limitations/enhancements and/or remarks:
682 --
683 -- Parameter p_s_cal_category is optional, if specified then it will be used to filter the calendar instance
684 -- if the value is NULL then category filter will not be used.
685 -- if the value is specified it should be with proper quotes.
686 -- ex.  p_s_cal_category => '''LOAD'',''ACADEMIC'''
687 --
688 --Change History:
689 --Who         When               What
690 --KUMMA       13-may-2003        2941138, Replaced p_alternate_code with the bind variable
691 --vskumar     24-May-2006	 xbuild3 performance fix. added a calander type parse code and used fnd_dsql.
692 ------------------------------------------------------------------  */
693  PROCEDURE get_calendar_instance(
694   p_alternate_cd IN VARCHAR2,
695   p_s_cal_category IN VARCHAR2,
696   p_cal_type OUT NOCOPY VARCHAR2,
697   p_ci_sequence_number OUT NOCOPY NUMBER,
698   p_start_dt OUT NOCOPY DATE,
699   p_end_dt OUT NOCOPY DATE,
700   p_return_status OUT NOCOPY VARCHAR2) AS
701 
702 -- REF cursor type variable
703 TYPE cur_cal_inst IS REF CURSOR;
704 
705 cur_cal_cat_inst_dtls cur_cal_inst; -- REF cursor variable for calendar details
706 cur_cal_cat_inst_cnt cur_cal_inst; -- REF cursor variable for calendar instances count
707 
708 --
709 -- cursor to fetch the count of calendar instances exists for the given alternate code
710 CURSOR cur_cal_inst_cnt IS
711 SELECT count(*)
712 FROM igs_ca_inst
713 WHERE alternate_code = p_alternate_cd;
714 
715 --
716 -- cursor to fetch the details of calendar instances for the given alternate code
717 CURSOR cur_cal_inst_dtls IS
718 SELECT cal_type,sequence_number,start_dt,end_dt
719 FROM igs_ca_inst
720 WHERE alternate_code = p_alternate_cd;
721 
722 l_cal_inst_cnt NUMBER;
723 l_cal_cat_inst_cnt NUMBER;
724 l_cal_cat_dtls_query VARCHAR2(1000);
725 l_cal_cat_cnt_query VARCHAR2(1000);
726 
727 curr_pos_lv NUMBER;
728 next_pos_lv NUMBER;
729 token_lv    VARCHAR2(50);
730 l_cursor_id NUMBER(15);
731 l_num_of_rows NUMBER(10);
732 l_p_s_cal_category VARCHAR2(100);
733 
734 BEGIN
735   p_cal_type := NULL;
736   p_ci_sequence_number := NULL;
737   p_start_dt := NULL;
738   p_end_dt := NULL;
739   p_return_status := 'INVALID';
740   l_p_s_cal_category :=REPLACE(p_s_cal_category,'''','');
741 
742   IF p_alternate_cd IS NOT NULL THEN
743 
744      -- If calendar category is specified then category should be used in criteria of fetching data along with alternate code
745      IF p_s_cal_category IS NOT NULL THEN
746 
747         l_cal_cat_inst_cnt := 0;
748 	p_cal_type := NULL;
749         p_ci_sequence_number := NULL;
750         p_start_dt := TO_DATE(NULL);
751         p_end_dt := TO_DATE(NULL);
752 
753 	fnd_dsql.init;
754 	curr_pos_lv := 1;
755 	next_pos_lv := 1;
756 
757 	-- Query to get the count of calendar instances for the given alternate code and calendar categories
758 
759 	fnd_dsql.add_text('SELECT ci.cal_type,ci.sequence_number,ci.start_dt,ci.end_dt FROM igs_ca_inst_all ci, igs_ca_type ct WHERE alternate_code =');
760 	fnd_dsql.add_bind(p_alternate_cd);
761 	fnd_dsql.add_text(' AND ci.cal_type = ct.cal_type AND ct.s_cal_cat IN (');
762 
763 	LOOP
764 	  next_pos_lv := INSTR(l_p_s_cal_category, ',', curr_pos_lv);
765 	  IF next_pos_lv = 0 THEN
766 	    token_lv := SUBSTR(l_p_s_cal_category,curr_pos_lv);
767 	    fnd_dsql.add_bind(token_lv);
768 	    fnd_dsql.add_text(')');
769 	    EXIT;
770 	  END IF;
771 	    token_lv := SUBSTR(l_p_s_cal_category, curr_pos_lv, next_pos_lv-curr_pos_lv);
772 	    fnd_dsql.add_bind(token_lv);
773 	    fnd_dsql.add_text(',');
774 	    curr_pos_lv := next_pos_lv + 1;
775 	END LOOP;
776 
777 	l_cal_cat_cnt_query := fnd_dsql.get_text(FALSE);
778 
779         l_cursor_id := dbms_sql.open_cursor;
780         fnd_dsql.set_cursor(l_cursor_id);
781         dbms_sql.parse(l_cursor_id, l_cal_cat_cnt_query, dbms_sql.native);
782         fnd_dsql.do_binds;
783 
784 	dbms_sql.define_column(l_cursor_id, 1, p_cal_type,10);
785 	dbms_sql.define_column(l_cursor_id, 2, p_ci_sequence_number);
786 	dbms_sql.define_column(l_cursor_id, 3, p_start_dt);
787 	dbms_sql.define_column(l_cursor_id, 4, p_end_dt);
788 
789 	l_num_of_rows := dbms_sql.EXECUTE(l_cursor_id);
790 	LOOP
791            IF dbms_sql.fetch_rows(l_cursor_id) > 0 THEN
792 	      l_cal_cat_inst_cnt := l_cal_cat_inst_cnt + 1;
793 	   ELSE
794               EXIT;
795            END IF;
796         END LOOP;
797 
798 
799        IF l_cal_cat_inst_cnt = 0 THEN
800           p_return_status := 'INVALID';
801 
802        ELSIF l_cal_cat_inst_cnt > 1 THEN
803           p_return_status := 'MULTIPLE';
804 
805        ELSE
806           p_return_status := 'SINGLE';
807           dbms_sql.column_value(l_cursor_id, 1, p_cal_type);
808           dbms_sql.column_value(l_cursor_id, 2, p_ci_sequence_number);
809           dbms_sql.column_value(l_cursor_id, 3, p_start_dt);
810           dbms_sql.column_value(l_cursor_id, 4, p_end_dt);
811 
812 	  dbms_sql.close_cursor(l_cursor_id);
813        END IF;
814 
815      ELSE -- p_s_cal_category is NULL
816        -- Calendar category is not specified, so only alternate code will be used as criteria for fetching data
817        OPEN cur_cal_inst_cnt;
818        FETCH cur_cal_inst_cnt INTO l_cal_inst_cnt;
819        CLOSE cur_cal_inst_cnt;
820 
821        IF l_cal_inst_cnt = 0 THEN
822           p_return_status := 'INVALID';
823        ELSIF l_cal_inst_cnt > 1 THEN
824           p_return_status := 'MULTIPLE';
825        ELSE
826           p_return_status := 'SINGLE';
827           OPEN cur_cal_inst_dtls;
828           FETCH cur_cal_inst_dtls INTO p_cal_type,p_ci_sequence_number,p_start_dt,p_end_dt;
829           CLOSE cur_cal_inst_dtls;
830        END IF;
831      END IF; -- p_s_cal_category <> NULL
832   END IF; -- p_alternate_cd <> NULL
833 
834   RETURN;
835 
836 EXCEPTION
837    WHEN OTHERS THEN
838         FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
839         FND_MESSAGE.SET_TOKEN('NAME', 'igs_ge_gen_003.get_calendar_instance');
840         IGS_GE_MSG_STACK.ADD;
841         APP_EXCEPTION.RAISE_EXCEPTION;
842 
843 END get_calendar_instance;
844 
845 /*------------------------------------------------------------------
846 --Created by  : knaraset, Oracle IDC
847 --Date created: 14-Nov-2002
848 --
849 --Purpose: procedure which returns the unit set version number and sequence number of the given unit set attempt.
850 --         returns NULL if no unit set attempt found or more than one unit set attempt found in the system.
851 --
852 --Known limitations/enhancements and/or remarks:
853 --
854 --Change History:
855 --Who         When               What
856 --
857 ------------------------------------------------------------------  */
858 PROCEDURE get_susa_sequence_num(
859   p_person_id IN NUMBER,
860   p_program_cd IN VARCHAR2,
861   p_unit_set_cd IN VARCHAR2,
862   p_us_version_number OUT NOCOPY NUMBER,
863   p_sequence_number OUT NOCOPY NUMBER) AS
864 
865 -- cursor to select version number,sequence number of the given unit set attempt
866 -- This cursor will fetch no records when the unit set attempt is not exists in the system
867 -- or more than one unit set attempt is matching the criteria.
868 CURSOR cur_susa_dtl IS
869 SELECT us_version_number,sequence_number
870 FROM igs_as_su_setatmpt
871 WHERE person_id = p_person_id
872 AND course_cd = p_program_cd
873 AND unit_set_cd = p_unit_set_cd
874 AND 1 = (SELECT COUNT(*)
875          FROM igs_as_su_setatmpt
876          WHERE person_id = p_person_id
877          AND course_cd = p_program_cd
878      AND unit_set_cd = p_unit_set_cd);
879 
880 BEGIN
881 
882   p_us_version_number := NULL;
883   p_sequence_number := NULL;
884 
885   IF p_person_id IS NOT NULL AND p_program_cd IS NOT NULL AND p_unit_set_cd IS NOT NULL THEN
886      OPEN cur_susa_dtl;
887      FETCH cur_susa_dtl INTO p_us_version_number,p_sequence_number;
888      CLOSE cur_susa_dtl;
889   END IF;
890 
891   RETURN;
892 EXCEPTION
893    WHEN OTHERS THEN
894         FND_MESSAGE.SET_NAME('IGS','IGS_GE_UNHANDLED_EXP');
895         FND_MESSAGE.SET_TOKEN('NAME', 'igs_ge_gen_003.get_susa_sequence_num');
896         IGS_GE_MSG_STACK.ADD;
897         APP_EXCEPTION.RAISE_EXCEPTION;
898 
899 END get_susa_sequence_num;
900 
901 FUNCTION disable_oss RETURN VARCHAR2 AS
902 BEGIN
903    IF(FND_PROFILE.VALUE('IGS_RELEASE_VERSION') = '12IGSA') THEN
904        RETURN 'Y';
905    ELSE
906        RETURN 'N';
907    END IF;
908 END disable_oss;
909 
910 END igs_ge_gen_003 ;