DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_AD_TI_COMP

Source


1 PACKAGE BODY igs_ad_ti_comp AS
2 /* $Header: IGSADA3B.pls 120.4 2006/04/25 04:17:09 rghosh ship $ */
3 
4   FUNCTION upd_trk_step_complete (
5                                    p_tracking_id igs_tr_step.tracking_id%TYPE,
6                                    p_tracking_step_id igs_tr_step.tracking_step_id%TYPE,
7                                    p_s_tracking_step_type igs_tr_step.s_tracking_step_type%TYPE,
8                                    p_recipient_id igs_tr_step.recipient_id%TYPE) RETURN BOOLEAN
9 
10   IS
11       l_message_name             VARCHAR2(30);
12    BEGIN
13    IF igs_tr_gen_002.trkp_upd_trst(
14                                    p_tracking_id,
15                                    p_tracking_step_id,
16                                    p_s_tracking_step_type,
17                                    NULL,
18                                    SYSDATE,
19                                    'Y',
20                                    NULL,
21                                    p_recipient_id,
22                                    l_message_name
23                                   )
24    THEN
25      -- Tracking Step Update to complete Successful
26      FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_STP_SUCFL');
27      FND_MESSAGE.SET_TOKEN('TRID', p_tracking_id);
28      FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
29      RETURN TRUE ;
30    ELSE
31      -- Tracking Step Update to complete Failed
32      FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_STP_NT_SUCFL');
33      FND_MESSAGE.SET_TOKEN('TRID', p_tracking_id);
34      FND_MESSAGE.SET_TOKEN('STPID', p_tracking_step_id);
35      FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET() );
36      FND_MESSAGE.SET_NAME('IGS', l_message_name);
37      FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
38      RETURN FALSE;
39      END IF;
40   END upd_trk_step_complete ;
41 
42   FUNCTION upd_trk_stp_cp(
43                            p_person_id                 IN   igs_ad_ps_appl_inst.person_id%TYPE,
44                            p_admission_appl_number     IN   igs_ad_ps_appl_inst.admission_appl_number%TYPE,
45                            p_course_cd                 IN   igs_ad_ps_appl_inst.course_cd%TYPE,
46                            p_sequence_number           IN   igs_ad_ps_appl_inst.sequence_number%TYPE,
47                            p_tracking_id               IN   igs_tr_step.tracking_id%TYPE,
48                            p_tracking_step_id          IN   igs_tr_step.tracking_step_id%TYPE,
49                            p_s_tracking_step_type      IN   igs_tr_step.s_tracking_step_type%TYPE,
50                            p_recipient_id              IN   igs_tr_step.recipient_id%TYPE
51                           ) RETURN BOOLEAN AS
52    /*
53    ||  Created By : brajendr
54    ||  Created On :
55    ||  Purpose :  This Function Checks for Completion of all the Tracking Steps for Each Tracking Item.
56    ||  Known limitations, enhancements or remarks :
57    ||  Change History :
58    ||  Who             When            What
59    ||  (reverse chronological order - newest change first)
60    ||  hreddych   09-OCT-2002 #2602077 Added a new case for Enrollment Deposit
61    ||  vdixit          07-Jan-2002     Changes pertaining to 2152871 enh.
62    */
63 
64 
65   CURSOR cur_enrolment_deposit (p_person_id igs_ad_app_req.person_id%TYPE,
66          p_admission_appl_number igs_ad_app_req.admission_appl_number%TYPE) IS
67           SELECT DISTINCT 1
68 	  FROM   igs_ad_app_req
69 	  WHERE  admission_appl_number = p_admission_appl_number
70 	  AND    person_id	= p_person_id
71 	  AND    applicant_fee_type IN (SELECT code_id
72 					FROM  igs_ad_code_classes
73 					WHERE class = 'SYS_FEE_TYPE'
74 					AND   system_status IN ('ENROLL_DEPOSIT')
75 					AND CLASS_TYPE_CODE='ADM_CODE_CLASSES')
76 	  AND    applicant_fee_status IN (SELECT code_id
77 					  FROM igs_ad_code_classes
78 					  WHERE class = 'SYS_FEE_STATUS'
79 					  AND system_status IN ('PAID','WAIVED')
80 					  AND CLASS_TYPE_CODE='ADM_CODE_CLASSES');
81 
82     -- Get all the Credential details for each application of the Person.
83     CURSOR cur_credentials(
84                            p_person_id                 IN   igs_ad_ps_appl_inst.person_id%TYPE ,
85 			   p_tracking_id               IN   igs_tr_step.tracking_id%TYPE,
86 			   p_tracking_step_id          IN   igs_tr_step.tracking_step_id%TYPE
87                           ) IS
88           SELECT DISTINCT 1
89            FROM  igs_pe_credentials pc,
90                  igs_ad_cred_types act,
91                  igs_tr_step ts
92           WHERE  pc.person_id = p_person_id
93             AND  act.credential_type_id = pc.credential_type_id
94             AND  ts.step_catalog_cd = act.step_code
95             AND  ts.tracking_id = p_tracking_id
96             AND  ts.tracking_step_id = p_tracking_step_id;
97 
98     -- Get all the Test details for each application of the Person.
99     CURSOR cur_test(
100                     p_person_id     IN   igs_ad_ps_appl_inst.person_id%TYPE  ,
101 		    p_tracking_id IN 	igs_tr_step.tracking_id%TYPE,
102 		    p_tracking_step_id IN     igs_tr_step.tracking_step_id%TYPE
103                    ) IS
104         SELECT DISTINCT 1
105 	FROM  igs_ad_test_results atr,
106 	      igs_ad_test_type att,
107 	      igs_tr_step ts
108 	WHERE ts.tracking_id = p_tracking_id
109 	AND   ts.tracking_step_id = p_tracking_step_id
110 	AND   att.step_code =ts.step_catalog_cd
111 	AND   atr.admission_test_type = att.admission_test_type
112 	AND   atr.person_id =p_person_id ;
113 
114     -- Get all the Education details for each application of the Person.
115 
116     CURSOR cur_trans      ( p_person_id   IN   igs_ad_ps_appl_inst.person_id%TYPE ) IS
117        SELECT DISTINCT institution_code,
118                        degree_attempted,
119        		             degree_earned
120        FROM   igs_ad_acad_history_v
121        WHERE  person_id = p_person_id
122        AND    transcript_required = 'Y'
123        AND    status = 'A' ;
124 
125 
126      -- Get all the transacript details for each application of the Person where the status is FINAL.
127      CURSOR cur_trans_final ( p_person_id   IN    igs_ad_acad_history_v.person_id%TYPE ,
128                        p_institution_code IN  igs_ad_acad_history_v.institution_code%TYPE,
129                        p_degree_attempted IN igs_ad_acad_history_v.degree_attempted%TYPE,
130                        p_degree_earned IN igs_ad_acad_history_v.degree_earned%TYPE ) IS
131        SELECT DISTINCT 1
132        FROM   igs_ad_acad_history_v a
133        WHERE  person_id= p_person_id
134        AND    institution_code =  p_institution_code
135        AND    NVL(degree_attempted,NVL(p_degree_attempted,'*')) = NVL(p_degree_attempted,'*')
136        AND    NVL(degree_earned,NVL(p_degree_earned,'*')) = NVL(p_degree_earned,'*')
137        AND    status = 'A'
138        AND    exists (
139                       SELECT 'x'
140                       FROM   igs_ad_transcript c
141                       WHERE  c.education_id = a.education_id
142                       AND    c.transcript_status  = 'FINAL'
143                       AND    c.transcript_type ='OFFICIAL');
144 
145      -- Get all the transacript details for each application of the Person where the status is PARTIAL or FINALL.
146      CURSOR cur_trans_partial(p_person_id   IN    igs_ad_acad_history_v.person_id%TYPE ,
147                        p_institution_code IN  igs_ad_acad_history_v.institution_code%TYPE,
148                        p_degree_attempted IN igs_ad_acad_history_v.degree_attempted%TYPE,
149                        p_degree_earned IN igs_ad_acad_history_v.degree_earned%TYPE ) IS
150        SELECT DISTINCT 1
151        FROM   igs_ad_acad_history_v a
152        WHERE  person_id = p_person_id
153        AND    institution_code=  p_institution_code
154        AND    NVL(degree_attempted,NVL(p_degree_attempted,'*')) = NVL(p_degree_attempted,'*')
155        AND    NVL(degree_earned,NVL(p_degree_earned,'*')) = NVL(p_degree_earned,'*')
156        AND    status = 'A'
157        AND    exists (
158                       SELECT 'x'
159                       FROM   igs_ad_transcript c
160                       WHERE  c.education_id = a.education_id
161                       AND    c.transcript_status IN ('FINAL','PARTIAL')
162                       AND    c.transcript_type ='OFFICIAL');
163 
164        -- Get all the transacript details for each application of the Person where the status is FINAL and type UNOFFICIAL.
165      CURSOR cur_trans_final_unofficial ( p_person_id   IN    igs_ad_acad_history_v.person_id%TYPE ,
166                        p_institution_code IN  igs_ad_acad_history_v.institution_code%TYPE,
167                        p_degree_attempted IN igs_ad_acad_history_v.degree_attempted%TYPE,
168                        p_degree_earned IN igs_ad_acad_history_v.degree_earned%TYPE ) IS
169        SELECT DISTINCT 1
170        FROM   igs_ad_acad_history_v a
171        WHERE  person_id = p_person_id
172        AND    institution_code=  p_institution_code
173        AND    NVL(degree_attempted,NVL(p_degree_attempted,'*')) = NVL(p_degree_attempted,'*')
174        AND    NVL(degree_earned,NVL(p_degree_earned,'*')) = NVL(p_degree_earned,'*')
175        AND    status = 'A'
176        AND    exists (
177                       SELECT 'x'
178                       FROM   igs_ad_transcript c
179                       WHERE  c.education_id = a.education_id
180                       AND    c.transcript_status  = 'FINAL'
181                       AND    c.transcript_type ='UNOFFICIAL');
182 
183      -- Get all the transacript details for each application of the Person where the status is PARTIAL or FINALL and type UNOFFICIAL.
184      CURSOR cur_trans_partial_unofficial(p_person_id   IN    igs_ad_acad_history_v.person_id%TYPE ,
185                        p_institution_code IN  igs_ad_acad_history_v.institution_code%TYPE,
186                        p_degree_attempted IN igs_ad_acad_history_v.degree_attempted%TYPE,
187                        p_degree_earned IN igs_ad_acad_history_v.degree_earned%TYPE ) IS
188        SELECT DISTINCT 1
189        FROM   igs_ad_acad_history_v a
190        WHERE  person_id = p_person_id
191        AND    institution_code=  p_institution_code
192        AND    NVL(degree_attempted,NVL(p_degree_attempted,'*')) = NVL(p_degree_attempted,'*')
193        AND    NVL(degree_earned,NVL(p_degree_earned,'*')) = NVL(p_degree_earned,'*')
194        AND    status = 'A'
195        AND    exists (
196                       SELECT 'x'
197                       FROM   igs_ad_transcript c
198                       WHERE  c.education_id = a.education_id
199                       AND    c.transcript_status IN ('FINAL','PARTIAL')
200                       AND    c.transcript_type ='UNOFFICIAL');
201 
202     -- Get the Personal Statements for the person
203     CURSOR cur_pers_statements(
204                            p_person_id                 IN   igs_ad_ps_appl_inst.person_id%TYPE ,
205                            p_admission_appl_number     IN   igs_ad_ps_appl_inst.admission_appl_number%TYPE ,
206 			   p_tracking_id               IN   igs_tr_step.tracking_id%TYPE,
207 			   p_tracking_step_id          IN   igs_tr_step.tracking_step_id%TYPE
208                           ) IS
209            SELECT DISTINCT 1
210             FROM  igs_ad_appl_perstat aaps,
211                   igs_ad_per_stm_typ apst,
212                   igs_tr_step ts
213            WHERE  ts.tracking_id = p_tracking_id
214              AND  ts.tracking_step_id = p_tracking_step_id
215              AND  apst.step_catalog_cd =ts.step_catalog_cd
216              AND  aaps.persl_stat_type =apst.persl_stat_type
217              AND  aaps.person_id =p_person_id
218              AND  aaps.admission_appl_number = p_admission_appl_number ;
219 
220     l_count                    NUMBER;
221     l_message_name             VARCHAR2(30);
222     tr_stp_fail_exp            EXCEPTION;
223     tr_stp_no_records_exp      EXCEPTION;
224     already_completed_exp      EXCEPTION;
225     l_eid_records_not_found    BOOLEAN := TRUE;
226     l_val1                     NUMBER;
227     l_val2                     NUMBER;
228     l_need_to_update           BOOLEAN := FALSE;
229 
230 
231   BEGIN
232 
233     -- Create a SavePoint in order to process each Application.
234     SAVEPOINT IGSADA3_SP1;
235 
236     -- Create a SavePoint in order to process each Application.
237     -- Check for Completion of all the Tracking Steps if the Tracking Step Type is ENR_DEP
238     IF p_s_tracking_step_type ='ENR_DEP' THEN
239 
240         -- If Enrollment Deposit records are not present in the system,
241 	-- then log a message and process the next Tracking Item in the Application.
242 	  OPEN cur_enrolment_deposit(p_person_id,p_admission_appl_number);
243 	  FETCH cur_enrolment_deposit INTO l_count;
244 	IF  cur_enrolment_deposit%NOTFOUND THEN
245 	    CLOSE cur_enrolment_deposit;
246 	    FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_ENR_DPT_NT_PAID');
247             FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
248             RAISE tr_stp_no_records_exp;
249         ELSE
250 	    CLOSE cur_enrolment_deposit;
251              -- If Enrollment Deposit records are present, then update the status to COMPLETED
252             IF  NOT upd_trk_step_complete ( p_tracking_id,
253                                             p_tracking_step_id,
254                                             p_s_tracking_step_type,
255                                             p_recipient_id
256                                            )
257             THEN
258                 RAISE tr_stp_fail_exp;
259             END IF;
260        END IF;  -- End of Processing all the Enrollment Deposit
261 
262 
263     -- Check for Completion of all the Tracking Steps if the Tracking Step Type is CREDENTIAL
264     ELSIF p_s_tracking_step_type ='CREDENTIAL' THEN
265 
266 	OPEN cur_credentials( p_person_id,p_tracking_id,p_tracking_step_id);
267 	FETCH cur_credentials INTO l_count;
268         -- If Credential records are not present in the system, then log a message and process the next Tracking Item in the Application.
269 	IF cur_credentials%NOTFOUND THEN
270 	  CLOSE cur_credentials;
271 	  FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_CRD_DTL_NT_EXISTS');
272           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
273           RAISE tr_stp_no_records_exp;
274         ELSE
275 	  CLOSE cur_credentials;
276           -- If Credential records are present, then update the status to COMPLETED
277             IF  NOT upd_trk_step_complete ( p_tracking_id,
278                                             p_tracking_step_id,
279                                             p_s_tracking_step_type,
280                                             p_recipient_id
281                                            )
282             THEN
283                 RAISE tr_stp_fail_exp;
284             END IF;
285         END IF;   -- End of Processing all the Credentials
286 
287     -- Check for Completion of all the Tracking Steps if the Tracking Step Type is TEST
288     ELSIF p_s_tracking_step_type = 'TEST' THEN
289 
290 	OPEN cur_test( p_person_id,p_tracking_id,p_tracking_step_id);
291 	FETCH cur_test INTO l_count;
292         -- If Test records are not present in the system, then log a message and process the next Tracking Item in the Application.
293 	IF cur_test%NOTFOUND THEN
294 	  CLOSE cur_test;
295           FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TST_DTL_NT_EXISTS');
296           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
297           RAISE tr_stp_no_records_exp;
298         ELSE
299 	  CLOSE cur_test;
300           -- If Test records are present, then update the status to COMPLETED
301             IF  NOT upd_trk_step_complete ( p_tracking_id,
302                                             p_tracking_step_id,
303                                             p_s_tracking_step_type,
304                                             p_recipient_id
305                                            )
306             THEN
307                 RAISE tr_stp_fail_exp;
308             END IF;
309         END IF;	  -- End of Processing all the Test
310 
311     -- Check for Completion of all the Tracking Steps if the Tracking Step Type is TRANS-PARTIAL or TRANS-FINAL
312     -- ELSIF p_s_tracking_step_type IN ( 'TRANS-PARTIAL', 'TRANS-FINAL') THEN
313 
314     ELSIF p_s_tracking_step_type = 'TRANS-PARTIAL' THEN
315 
316       -- l_eid_records_not_found has FALSE when there are any educational details where transcripts
320 
317       -- are required.
318        l_eid_records_not_found := TRUE ;
319        l_need_to_update := FALSE;
321       FOR cur_trans_rec IN cur_trans( p_person_id) LOOP
322 
323 	    l_eid_records_not_found := FALSE ;
324             OPEN cur_trans_partial ( p_person_id,
325 	                             cur_trans_rec.institution_code,
326 				     cur_trans_rec.degree_attempted,
327 				     cur_trans_rec.degree_earned ) ;
328             FETCH cur_trans_partial INTO l_val1 ;
329 	    IF cur_trans_partial%FOUND THEN
330                l_need_to_update := TRUE;
331 	    ELSE
332                l_need_to_update := FALSE;
333 	       EXIT ;
334 	    END IF;
335 	    CLOSE cur_trans_partial;
336       END LOOP;
337         IF (l_eid_records_not_found = TRUE) THEN
338           -- The tracking items are yet to be created for this application so the tracking items completion cannot take place.
339           -- Message ('Tracking items do not exist for this application');
340           l_need_to_update := FALSE;
341           FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_EID_NT_FND');
342           FND_MESSAGE.SET_TOKEN('TRID', p_tracking_id);
343           FND_MESSAGE.SET_TOKEN('STPID', p_tracking_step_id);
344           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
345         END IF;
346         IF  l_need_to_update THEN
347             IF  NOT upd_trk_step_complete ( p_tracking_id,
348                                             p_tracking_step_id,
349                                             p_s_tracking_step_type,
350                                             p_recipient_id
351                                            )
352             THEN
353                 RAISE tr_stp_fail_exp;
354             END IF;
355         END IF;  -- Check whether the Trackings need to get updated or not.
356 
357     ELSIF p_s_tracking_step_type = 'TRANS-FINAL' THEN
358 
359       -- l_eid_records_not_found has FALSE when there are any educational details where transcripts
360       -- are required.
361        l_eid_records_not_found := TRUE ;
362        l_need_to_update := FALSE;
363 
364       FOR cur_trans_rec IN cur_trans( p_person_id) LOOP
365 	    l_eid_records_not_found := FALSE ;
366             OPEN cur_trans_final ( p_person_id,
367 	                           cur_trans_rec.institution_code,
368 				   cur_trans_rec.degree_attempted,
369 				   cur_trans_rec.degree_earned ) ;
370             FETCH cur_trans_final INTO l_val1 ;
371 	    IF cur_trans_final%FOUND THEN
372                l_need_to_update := TRUE;
373 	    ELSE
374                l_need_to_update := FALSE;
375 	       EXIT;
376 	    END IF;
377 	    CLOSE cur_trans_final;
378       END LOOP;
379 
380         IF l_eid_records_not_found THEN
381           -- The tracking items are yet to be created for this application so the tracking items completion cannot take place.
382           -- Message ('Tracking items do not exist for this application');
383           l_need_to_update := FALSE;
384           FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_EID_NT_FND');
385           FND_MESSAGE.SET_TOKEN('TRID', p_tracking_id);
386           FND_MESSAGE.SET_TOKEN('STPID', p_tracking_step_id);
387           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
388         END IF;
389         IF  l_need_to_update THEN
390             IF  NOT upd_trk_step_complete ( p_tracking_id,
391                                             p_tracking_step_id,
392                                             p_s_tracking_step_type,
393                                             p_recipient_id
394                                            )
395             THEN
396                 RAISE tr_stp_fail_exp;
397             END IF;
398         END IF;  -- Check whether the Trackings need to get updated or not.
399 
400  -- Check for Completion of all the Tracking Steps if the Tracking Step Type is TRANS-PARTIAL or TRANS-FINAL
401     -- ELSIF p_s_tracking_step_type IN ( 'TRANS-PART-U', 'TRANS-FINAL-U') THEN
402 
403     ELSIF p_s_tracking_step_type = 'TRANS-PART-U' THEN
404 
405       -- l_eid_records_not_found has FALSE when there are any educational details where transcripts
406       -- are required.
407        l_eid_records_not_found := TRUE ;
408        l_need_to_update := FALSE;
409 
410       FOR cur_trans_rec IN cur_trans( p_person_id) LOOP
411 
412 	    l_eid_records_not_found := FALSE ;
413             OPEN cur_trans_partial_unofficial ( p_person_id,
414 	                             cur_trans_rec.institution_code,
415 				     cur_trans_rec.degree_attempted,
416 				     cur_trans_rec.degree_earned ) ;
417             FETCH cur_trans_partial_unofficial INTO l_val1 ;
418 	    IF cur_trans_partial_unofficial%FOUND THEN
419                l_need_to_update := TRUE;
420 	    ELSE
421                l_need_to_update := FALSE;
422 	       EXIT ;
423 	    END IF;
424 	    CLOSE cur_trans_partial_unofficial;
425       END LOOP;
426         IF (l_eid_records_not_found = TRUE) THEN
427           -- The tracking items are yet to be created for this application so the tracking items completion cannot take place.
428           -- Message ('Tracking items do not exist for this application');
429           l_need_to_update := FALSE;
430           FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_EID_NT_FND');
431           FND_MESSAGE.SET_TOKEN('TRID', p_tracking_id);
432           FND_MESSAGE.SET_TOKEN('STPID', p_tracking_step_id);
433           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
434         END IF;
438                                             p_s_tracking_step_type,
435         IF  l_need_to_update THEN
436             IF  NOT upd_trk_step_complete ( p_tracking_id,
437                                             p_tracking_step_id,
439                                             p_recipient_id
440                                            )
441             THEN
442                 RAISE tr_stp_fail_exp;
443             END IF;
444         END IF;  -- Check whether the Trackings need to get updated or not.
445 
446     ELSIF p_s_tracking_step_type = 'TRANS-FINAL-U' THEN
447 
448       -- l_eid_records_not_found has FALSE when there are any educational details where transcripts
449       -- are required.
450        l_eid_records_not_found := TRUE ;
451        l_need_to_update := FALSE;
452 
453       FOR cur_trans_rec IN cur_trans( p_person_id) LOOP
454 	    l_eid_records_not_found := FALSE ;
455             OPEN cur_trans_final_unofficial ( p_person_id,
456 	                           cur_trans_rec.institution_code,
457 				   cur_trans_rec.degree_attempted,
458 				   cur_trans_rec.degree_earned ) ;
459             FETCH cur_trans_final_unofficial INTO l_val1 ;
460 	    IF cur_trans_final_unofficial%FOUND THEN
461                l_need_to_update := TRUE;
462 	    ELSE
463                l_need_to_update := FALSE;
464 	       EXIT;
465 	    END IF;
466 	    CLOSE cur_trans_final_unofficial;
467       END LOOP;
468 
469         IF l_eid_records_not_found THEN
470           -- The tracking items are yet to be created for this application so the tracking items completion cannot take place.
471           -- Message ('Tracking items do not exist for this application');
472           l_need_to_update := FALSE;
473           FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_EID_NT_FND');
474           FND_MESSAGE.SET_TOKEN('TRID', p_tracking_id);
475           FND_MESSAGE.SET_TOKEN('STPID', p_tracking_step_id);
476           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
477         END IF;
478         IF  l_need_to_update THEN
479             IF  NOT upd_trk_step_complete ( p_tracking_id,
480                                             p_tracking_step_id,
481                                             p_s_tracking_step_type,
482                                             p_recipient_id
483                                            )
484             THEN
485                 RAISE tr_stp_fail_exp;
486             END IF;
487         END IF;  -- Check whether the Trackings need to get updated or not.
488 
489     ELSIF p_s_tracking_step_type = 'PERSONAL_STATEMENT' THEN
490 
491       OPEN cur_pers_statements(p_person_id, p_admission_appl_number,p_tracking_id,p_tracking_step_id );
492       FETCH cur_pers_statements INTO l_count;
493       IF  cur_pers_statements%FOUND THEN
494           CLOSE cur_pers_statements;
495             IF  NOT upd_trk_step_complete ( p_tracking_id,
496                                             p_tracking_step_id,
497                                             p_s_tracking_step_type,
498                                             p_recipient_id
499                                            )
500             THEN
501                 RAISE tr_stp_fail_exp;
502             END IF;
503       ELSE
504           CLOSE cur_pers_statements;
505       END IF;
506 
507 
508     END IF;
509 
510     -- Once all the Tracking Steps are completed successfull, then return the TRUE to the Calling Procedure and COMMIT the transactions.
511     -- If called from Job then commit , if called from SS skip commit
512     IF NVL( IGS_AD_TI_COMP.G_CALLED_FROM, 'J') = 'J' THEN
513       COMMIT;
514     END IF;
515     RETURN TRUE;
516 
517   EXCEPTION
518 
519     -- If Records are not found, then skip to the next Tracking Item in the Application Instance.
520     WHEN tr_stp_no_records_exp THEN
521       ROLLBACK TO IGSADA3_SP1;
522       RETURN TRUE;
523 
524     -- Rollback all the transactions, If the Exception is RAISED while Processing the Tracking Steps of Application Tracking Items.
525     WHEN tr_stp_fail_exp THEN
526       ROLLBACK TO IGSADA3_SP1;
527       RETURN FALSE;
528 
529     WHEN others THEN
530       ROLLBACK TO IGSADA3_SP1;
531       RETURN FALSE;
532 
533   END upd_trk_stp_cp;
534 
535 
536   PROCEDURE get_incp_trstp(
537                            p_person_id                 IN   igs_ad_ps_appl_inst.person_id%TYPE,
538                            p_admission_appl_number     IN   igs_ad_ps_appl_inst.admission_appl_number%TYPE,
539                            p_course_cd                 IN   igs_ad_ps_appl_inst.course_cd%TYPE,
540                            p_sequence_number           IN   igs_ad_ps_appl_inst.sequence_number%TYPE
541                           ) AS
542     /*
543     ||  Created By : brajendr
544     ||  Created On :
545     ||  Purpose :  This Procedure Checks for Completion of all the Tracking Items for each Application Instances.
546     ||  Known limitations, enhancements or remarks :
547     ||  Change History :
548     ||  Who             When            What
549     ||  (reverse chronological order - newest change first)
550     */
551 
552     -- Get all the Tracking Items for each Application of the Person.
553     CURSOR cur_tr(
554                   p_person_id                 IN   igs_ad_ps_appl_inst.person_id%TYPE,
555                   p_admission_appl_number     IN   igs_ad_ps_appl_inst.admission_appl_number%TYPE,
559     SELECT aa.tracking_id
556                   p_course_cd                 IN   igs_ad_ps_appl_inst.course_cd%TYPE,
557                   p_sequence_number           IN   igs_ad_ps_appl_inst.sequence_number%TYPE
558                  ) IS
560       FROM igs_ad_aplins_admreq aa,
561            igs_tr_item ti,
562 	   igs_tr_status ts
563       WHERE aa.person_id             = p_person_id
564         AND aa.admission_appl_number = p_admission_appl_number
565         AND aa.sequence_number       = p_sequence_number
566         AND aa.course_cd             = p_course_cd
567         AND aa.tracking_id           = ti.tracking_id -- changes made
568         AND ti.tracking_status = ts.tracking_status
569         AND ts.s_tracking_status = 'ACTIVE' ; --  the tracking status should be mapped to system tracking status of 'ACTIVE'  ( rghosh, bug#2919317)
570 
571     -- Get all the Tracking Steps of Each Tracking Item.
572     CURSOR cur_tr_stp(
573                       p_tracking_id  igs_ad_aplins_admreq.tracking_id%TYPE
574                      ) IS
575       SELECT tracking_step_id, s_tracking_step_type, recipient_id
576         FROM igs_tr_step ts
577           WHERE ts.tracking_id = p_tracking_id
578             AND ts.step_completion_ind='N'
579             AND ts.by_pass_ind = 'N'
580             AND ts.completion_dt IS NULL
581           ORDER BY s_tracking_step_type;
582 
583     l_records_not_found        BOOLEAN := TRUE;
584     l_stp_records_not_found    BOOLEAN := TRUE;
585 
586   BEGIN
587 
588     l_records_not_found := TRUE;
589     FOR cur_tr_rec IN cur_tr( p_person_id, p_admission_appl_number, p_course_cd, p_sequence_number) LOOP
590       l_records_not_found := FALSE;
591 
592       -- Process all the Tracking Items for each Tracking Step.
593       l_stp_records_not_found := TRUE;
594 
595       FOR cur_tr_stp_rec IN cur_tr_stp( cur_tr_rec.tracking_id) LOOP
596         -- For the tracking steps which are yet to be completed, call the  generic procedure which would check the tracking steps completion
597         -- for the application instance and update the tracking steps in case the pre-requisite has been found in the admission tables. For the
598         -- Tracking id steps found, fetch the tracking steps which are not completed and not by passed and the completion date has not been updated.
599         l_stp_records_not_found := FALSE;
600         IF upd_trk_stp_cp(
601                           p_person_id,
602                           p_admission_appl_number,
603                           p_course_cd,
604                           p_sequence_number,
605                           cur_tr_rec.tracking_id,
606                           cur_tr_stp_rec.tracking_step_id,
607                           cur_tr_stp_rec.s_tracking_step_type,
608                           cur_tr_stp_rec.recipient_id
609                          ) = FALSE
610         THEN
611           -- If any of the Tracking ID's are Invalid, then process the next Application Instance.
612           RETURN;
613         END IF;
614       END LOOP;  -- End of Each Tracking Item Steps.
615       IF l_stp_records_not_found THEN
616         -- The tracking items are yet to be created for this application so the tracking items completion cannot take place.
617         -- Message ('Tracking items do not exist for this application');
618         FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_NO_TR_STPS');
619         FND_MESSAGE.SET_TOKEN('TRID', cur_tr_rec.tracking_id);
620         FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
621 
622       END IF;
623 
624     END LOOP;
625 
626     IF l_records_not_found THEN
627       -- The tracking items are yet to be created for this application so the tracking items completion cannot take place.
628       -- Message ('Tracking items do not exist for this application');
629       FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_NO_TR_ITM');
630       FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
631 
632     END IF;
633 
634   EXCEPTION
635     WHEN others THEN
636       ROLLBACK;
637   END get_incp_trstp;
638 
639 
640  PROCEDURE upd_trk_itm_st(
641                            ERRBUF                         OUT NOCOPY  VARCHAR2,
642                            RETCODE                        OUT NOCOPY  NUMBER,
643                            p_person_id                    IN   igs_ad_ps_appl_inst.person_id%TYPE,
644                            p_person_id_group              IN   igs_pe_prsid_grp_mem_all.group_id%TYPE,
645                            p_admission_appl_number        IN   igs_ad_ps_appl_inst.admission_appl_number%TYPE,
646                            p_course_cd                    IN   igs_ad_ps_appl_inst.course_cd%TYPE,
647                            p_sequence_number              IN   igs_ad_ps_appl_inst.sequence_number%TYPE,
648                            p_calendar_details             IN   VARCHAR2,
649                            p_admission_process_category   IN   VARCHAR2,
650                            p_org_id                       IN   igs_pe_prsid_grp_mem_all.org_id%TYPE
651                           ) AS
652     /*
653     ||  Created By :
654     ||  Created On :
655     ||  Purpose    : This is a main Procedure which will check whether all the Tracking Items are COMPLETE or not.
656     ||               This is getting called from the forms as well as a Concurrent Job.
657     ||  Known limitations, enhancements or remarks :
658     ||  Change History :
659     ||  Who             When            What
660     ||  (reverse chronological order - newest change first)
664     ||                                                    (Enh# 3194295 , ADCR043: Person ID Group)
661     ||  hreddych   09-OCT-2002 #2602077 Added a new case where person_id and admission_appl_number are passed
662     ||  rghosh      21-Oct-2003        Added the REF CURSOR c_dyn_pig_check and hence the
663     ||                                                   logic for supporting dynamic Person ID Group
665     */
666 
667     -- Get the all the Application Instances Details of the Person with parameters as
668     -- p_person_id, p_admission_appl_number, p_course_cd and p_sequence_number.
669 
670 
671    TYPE c_dyn_pig_checkCurTyp IS REF CURSOR;
672    c_dyn_pig_check c_dyn_pig_checkCurTyp;
673    TYPE  c_dyn_pig_checkrecTyp IS RECORD ( person_id igs_ad_ps_appl_inst_all.person_id%TYPE,
674                                                                                      admission_appl_number igs_ad_ps_appl_inst_all.admission_appl_number%TYPE,
675                                                                                      nominated_course_cd igs_ad_ps_appl_inst_all.nominated_course_cd%TYPE,
676                                                                                      sequence_number igs_ad_ps_appl_inst_all.sequence_number%TYPE);
677    c_dyn_pig_check_rec c_dyn_pig_checkrecTyp ;
678 
679    lv_status     VARCHAR2(1) := 'S';  /*Defaulted to 'S' and the function will return 'F' in case of failure */
680    lv_sql_stmt   VARCHAR(32767);
681 
682 
683 
684 CURSOR cur_appl_details(  p_person_id	 igs_ad_ps_appl_inst.person_id%TYPE,
685         p_acad_cal_type  igs_ad_appl.acad_cal_type%TYPE,
686 			  p_adm_cal_type  igs_ad_appl.adm_cal_type%TYPE,
687 			  p_acad_ci_sequence_number  igs_ad_appl.acad_ci_sequence_number%TYPE,
688 			  p_adm_ci_sequence_number  igs_ad_appl.adm_ci_sequence_number%TYPE,
689 			  p_admission_cat  igs_ad_appl.admission_cat%TYPE,
690 			  p_s_admission_process_type  igs_ad_appl.s_admission_process_type%TYPE ,
691 			  p_admission_appl_number igs_ad_ps_appl_inst.admission_appl_number%TYPE	 ,
692 			  p_sequence_number  igs_ad_ps_appl_inst.sequence_number%TYPE )IS
693 
694 SELECT
695 	apai.person_id,
696 	apai.admission_appl_number,
697 	apai.nominated_course_cd,
698 	apai.sequence_number
699 FROM
700 	igs_ad_ps_appl_inst apai,
701 	igs_ad_ou_stat aos,
702 	igs_ad_doc_stat ads,
703 	igs_ad_appl aa
704 WHERE
705 	apai.person_id = nvl(p_person_id,apai.person_id) AND
706 	aa.acad_cal_type = nvl(p_acad_cal_type,aa.acad_cal_type) AND
707 	aa.acad_ci_sequence_number = nvl(p_acad_ci_sequence_number,aa.acad_ci_sequence_number) AND
708 	aa.adm_cal_type = nvl(p_adm_cal_type,aa.adm_cal_type) AND
709 	aa.adm_ci_sequence_number = nvl(p_adm_ci_sequence_number,aa.adm_ci_sequence_number) AND
710 	aa.admission_cat = nvl(p_admission_cat,aa.admission_cat) AND
711 	aa.s_admission_process_type = nvl(p_s_admission_process_type,aa.s_admission_process_type) AND
712 	apai.nominated_course_cd = nvl(p_course_cd,apai.nominated_course_cd) AND
713 	apai.admission_appl_number = nvl(p_admission_appl_number,apai.admission_appl_number) AND
714 	apai.sequence_number = nvl(p_sequence_number,apai.sequence_number) AND
715 	aos.s_adm_outcome_status = 'PENDING' AND
716 	apai.adm_outcome_status = aos.adm_outcome_status AND
717 	ads.s_adm_doc_status = 'PENDING' AND
718 	apai.adm_doc_status = ads.adm_doc_status AND
719 	aa.person_id=apai.person_id AND
720 	aa.admission_appl_number = apai.admission_appl_number ;
721 
722    --Check whether there is any tracking associated for the person and Application Number
723    CURSOR  cur_trk_exists(
724                   p_person_id                 IN   igs_ad_ps_appl_inst.person_id%TYPE,
725                   p_admission_appl_number     IN   igs_ad_ps_appl_inst.admission_appl_number%TYPE  ,
726                   p_course_cd                 IN   igs_ad_aplins_admreq.course_cd%TYPE  ,
727                   p_sequence_number           IN   igs_ad_aplins_admreq.sequence_number%TYPE  ) IS
728     SELECT  1
729       FROM  igs_ad_aplins_admreq aa,
730             igs_tr_item ti,
731  	   igs_tr_status ts
732      WHERE aa.person_id             = p_person_id
733         AND aa.admission_appl_number = p_admission_appl_number
734 	AND aa.course_cd             = p_course_cd
735 	AND aa.sequence_number       = p_sequence_number
736         AND aa.tracking_id           = ti.tracking_id
737 	AND ti.tracking_status = ts.tracking_status
738         AND ts.s_tracking_status = 'ACTIVE' ;  --  the tracking status should be mapped to system tracking status of 'ACTIVE'  ( rghosh, bug#2919317)
739 
740     l_acad_cal_type                igs_ca_inst_all.cal_type%TYPE;
741     l_acad_ci_sequence_number      igs_ca_inst_all.sequence_number%TYPE;
742     l_adm_cal_type                 igs_ca_inst_all.cal_type%TYPE;
743     l_adm_ci_sequence_number       igs_ca_inst_all.sequence_number%TYPE;
744     l_admission_cat                igs_ad_appl_all.admission_cat%TYPE;
745     l_s_admission_process_type     igs_ad_appl_all.s_admission_process_type%TYPE;
746     l_count                        NUMBER;
747     l_records_not_found            BOOLEAN := TRUE;
748 
749     lv_group_type IGS_PE_PERSID_GROUP_V.group_type%TYPE;
750 
751   BEGIN
752 
753     -- Set the Org_id for the corresponding responsibility.
754     igs_ge_gen_003.set_org_id( p_org_id);
755     RETCODE := 0;
756     ERRBUF  := NULL;
757    lv_sql_stmt   :=  igs_pe_dynamic_persid_group.get_dynamic_sql(p_person_id_group,lv_status,lv_group_type);
758     -- Log the Initial parameters into the LOG file.
759     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_TR_PRMS');
760     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
761 
765 
762     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_PID');
763     FND_MESSAGE.SET_TOKEN('PID', p_person_id);
764     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
766     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_PID_GRP');
767     FND_MESSAGE.SET_TOKEN('PGPID', p_person_id_group);
768     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
769 
770     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_ADM_APLNO');
771     FND_MESSAGE.SET_TOKEN('APLNO', p_admission_appl_number);
772     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
773 
774     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_CRCD');
775     FND_MESSAGE.SET_TOKEN('CRCD', p_course_cd);
776     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
777 
778     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_APP_SEQNO');
779     FND_MESSAGE.SET_TOKEN('SEQNO', p_sequence_number);
780     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
781 
782     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_CL_DTLS');
783     FND_MESSAGE.SET_TOKEN('CLDTLS', p_calendar_details);
784     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
785 
786     FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_LG_APC');
787     FND_MESSAGE.SET_TOKEN('APC', p_admission_process_category);
788     FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
789 
790            -- Get the Academic Calander details form the Academic Calender Parameter
791         l_acad_cal_type             := RTRIM ( SUBSTR ( p_calendar_details, 1, 10));
792         l_acad_ci_sequence_number   := IGS_GE_NUMBER.TO_NUM ( SUBSTR ( p_calendar_details, 14, 6));
793 
794    -- if l_acad_sequence_number is NULL (ie, calendar details are not entered) then
795    -- it is assigned a value of -1, if we keep it NULL then the value cannot be used while
796    -- opening the REF CURSOR c_dyn_pig_check.
797 
798         IF l_acad_ci_sequence_number IS NULL THEN
799           l_acad_ci_sequence_number := -1 ;
800         END IF;
801 
802         -- Get the Admission Calander details form the Admission Calender Parameter
803         l_adm_cal_type              := RTRIM ( SUBSTR ( p_calendar_details, 23, 10));
804         l_adm_ci_sequence_number    := IGS_GE_NUMBER.TO_NUM ( SUBSTR ( p_calendar_details, 37, 6));
805 
806    -- if l_adm_sequence_number is NULL (ie, calendar details are not entered) then
807    -- it is assigned a value of -1, if we keep it NULL then the value cannot be used while
808    -- opening the REF CURSOR c_dyn_pig_check.
809 
810        IF l_adm_ci_sequence_number IS NULL THEN
811          l_adm_ci_sequence_number := -1;
812        END IF;
813 
814         -- Get the Admission Process Category details form the APC
815         -- Do not change SUBSTR position for APC param in code and SEED
816         -- since the same value set is used in value set IGS_SRS_AD_PERSON_ID_COMPLETE
817        l_admission_cat             := RTRIM ( SUBSTR ( p_admission_process_category, 1, 10));
818        l_s_admission_process_type  := RTRIM ( SUBSTR ( p_admission_process_category, 11, 30));
819 
820        IF (  p_admission_process_category  IS NULL AND
821                p_calendar_details            IS NULL AND
822                p_person_id                   IS NULL AND
823                p_person_id_group             IS NULL ) THEN
824 
825 	  --Message One of the following Parameters Person Id, Person Id Group, Calendar Details
826 	  --or Admission Process Category is mandatory.
827 
828           FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_MANDATORY_PRM');
829           FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
830           RETURN;
831 
832 
833      ELSIF (p_person_id                   IS NOT NULL AND
834                   p_person_id_group             IS NOT NULL ) THEN
835     -- Message: Invalid parameters entered. Valid combinations for parameters
836     -- to be entered is Person ID or Person Group ID or Person ID, Admission Application
837     -- Number, Program Code, Sequence Number or Academic Calendar, Admission  Calendar,
838     -- Admission Process Category.
839 
840       FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_INV_PRM_COMB');
841       FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
842       RETURN;
843 
844 
845    ELSIF (    p_person_id                   IS NULL AND
846                     p_person_id_group             IS NOT NULL ) THEN
847 
848         l_records_not_found   := TRUE;
849 
850         IF lv_status = 'S' THEN
851   	  BEGIN
852 
853            IF (lv_group_type = 'STATIC') THEN
854             OPEN  c_dyn_pig_check FOR
855                 'SELECT
856 	                 apai.person_id,
857 	                 apai.admission_appl_number,
858 	                 apai.nominated_course_cd,
859                    apai.sequence_number
860                  FROM
861 	                 igs_ad_ps_appl_inst apai,
862 	                 igs_ad_ou_stat aos,
863 	                 igs_ad_doc_stat ads ,
864                    igs_ad_appl aa
865                  WHERE
866                    apai.person_id  IN ( '||lv_sql_stmt||')  AND
867 	                 aos.s_adm_outcome_status = ''PENDING'' AND
868 	                 apai.adm_outcome_status = aos.adm_outcome_status AND
869 	                 ads.s_adm_doc_status = ''PENDING'' AND
870 	                 apai.adm_doc_status = ads.adm_doc_status  AND
871                    aa.person_id = apai.person_id AND
872                    aa.admission_appl_number = apai.admission_appl_number AND
873                    aa.acad_cal_type = nvl(:1,aa.acad_cal_type) AND
874                  	aa.acad_ci_sequence_number = DECODE ( :2, -1,aa.acad_ci_sequence_number, :2 )  AND
878                  	aa.s_admission_process_type = nvl( :6, aa.s_admission_process_type)  '
875                  	aa.adm_cal_type = nvl(:3,aa.adm_cal_type) AND
876                  	aa.adm_ci_sequence_number = DECODE ( :4, -1 ,aa.adm_ci_sequence_number , :4 ) AND
877                  	aa.admission_cat = nvl( :5,aa.admission_cat) AND
879 		USING p_person_id_group,l_acad_cal_type, l_acad_ci_sequence_number, l_acad_ci_sequence_number, l_adm_cal_type, l_adm_ci_sequence_number, l_adm_ci_sequence_number, l_admission_cat, l_s_admission_process_type;
880 	    LOOP
881 
882             FETCH c_dyn_pig_check  INTO c_dyn_pig_check_rec;
883 
884             IF c_dyn_pig_check%NOTFOUND THEN
885               EXIT;
886             END IF;
887 
888             l_records_not_found   := FALSE;
889 
890             get_incp_trstp(c_dyn_pig_check_rec.person_id,
891 	                                     c_dyn_pig_check_rec.admission_appl_number,
892 			                                 c_dyn_pig_check_rec.nominated_course_cd,
893 			                                 c_dyn_pig_check_rec.sequence_number);
894 	           END LOOP;
895 
896            ELSIF (lv_group_type = 'DYNAMIC') THEN
897 
898 
899             OPEN  c_dyn_pig_check FOR
900                 'SELECT
901 	                 apai.person_id,
902 	                 apai.admission_appl_number,
903 	                 apai.nominated_course_cd,
904                    apai.sequence_number
905                  FROM
906 	                 igs_ad_ps_appl_inst apai,
907 	                 igs_ad_ou_stat aos,
908 	                 igs_ad_doc_stat ads ,
909                    igs_ad_appl aa
910                  WHERE
911                    apai.person_id  IN ( '||lv_sql_stmt||')  AND
912 	                 aos.s_adm_outcome_status = ''PENDING'' AND
913 	                 apai.adm_outcome_status = aos.adm_outcome_status AND
914 	                 ads.s_adm_doc_status = ''PENDING'' AND
915 	                 apai.adm_doc_status = ads.adm_doc_status  AND
916                    aa.person_id = apai.person_id AND
917                    aa.admission_appl_number = apai.admission_appl_number AND
918                    aa.acad_cal_type = nvl(:1,aa.acad_cal_type) AND
919                  	aa.acad_ci_sequence_number = DECODE ( :2, -1,aa.acad_ci_sequence_number, :2 )  AND
920                  	aa.adm_cal_type = nvl(:3,aa.adm_cal_type) AND
921                  	aa.adm_ci_sequence_number = DECODE ( :4, -1 ,aa.adm_ci_sequence_number , :4 ) AND
922                  	aa.admission_cat = nvl( :5,aa.admission_cat) AND
923                  	aa.s_admission_process_type = nvl( :6, aa.s_admission_process_type)  '
924 		USING l_acad_cal_type, l_acad_ci_sequence_number, l_acad_ci_sequence_number, l_adm_cal_type, l_adm_ci_sequence_number, l_adm_ci_sequence_number, l_admission_cat, l_s_admission_process_type;
925 	    LOOP
926 
927             FETCH c_dyn_pig_check  INTO c_dyn_pig_check_rec;
928 
929             IF c_dyn_pig_check%NOTFOUND THEN
930               EXIT;
931             END IF;
932 
933             l_records_not_found   := FALSE;
934 
935             get_incp_trstp(c_dyn_pig_check_rec.person_id,
936 	                                     c_dyn_pig_check_rec.admission_appl_number,
937 			                                 c_dyn_pig_check_rec.nominated_course_cd,
938 			                                 c_dyn_pig_check_rec.sequence_number);
939 	           END LOOP;
940 
941             END IF;
942 	     CLOSE c_dyn_pig_check;
943 
944               -- If the Applicaiton records are not found then log a message
945               IF l_records_not_found THEN
946                 -- Tracking steps cannot be completed for applications not having application completion status of pending
947                 -- and application outcome status of pending or conditional offer
948                 FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_PEND_STAT');
949                 FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
950 
951                  -- Abort the process and raise error
952                  RETURN;
953               END IF;
954 
955           EXCEPTION
956             WHEN OTHERS THEN
957               FND_MESSAGE.SET_NAME ('IGF','IGF_AP_INVALID_QUERY');
958               FND_FILE.PUT_LINE (FND_FILE.LOG,FND_MESSAGE.GET);
959               FND_FILE.PUT_LINE (FND_FILE.LOG,sqlerrm);
960   	      END;
961 
962 	      ELSE
963           FND_MESSAGE.SET_NAME ('IGS',' IGS_AZ_DYN_PERS_ID_GRP_ERR');
964           FND_FILE.PUT_LINE (FND_FILE.LOG,FND_MESSAGE.GET);
965         END IF;
966 
967      ELSE
968 
969 
970         -- Based  on the parameters entered fetch the application instance from admission
971         -- application instance table which have application completion status = 'PENDING' and
972         -- application outcome status = 'PENDING or COND-OFFER'
973         l_records_not_found := TRUE;
974        -- Reverting back the values of l_acad_ci_sequence_number and l_adm_ci_sequence_number
975        IF l_adm_ci_sequence_number = -1 THEN
976          l_adm_ci_sequence_number :=  NULL;
977        END IF;
978 
979         IF l_acad_ci_sequence_number = -1 THEN
980           l_acad_ci_sequence_number := NULL;
981         END IF;
982 
983         FOR cur_appl_details_rec IN cur_appl_details(  p_person_id ,  l_acad_cal_type ,
984 			  l_adm_cal_type  , l_acad_ci_sequence_number , l_adm_ci_sequence_number  ,
985 			  l_admission_cat , l_s_admission_process_type  , p_admission_appl_number ,
986 			  p_sequence_number )LOOP
987             OPEN cur_trk_exists(cur_appl_details_rec.person_id,
988 	                        cur_appl_details_rec.admission_appl_number,
989 				cur_appl_details_rec.nominated_course_cd,
990 				cur_appl_details_rec.sequence_number);
991             FETCH cur_trk_exists INTO l_count;
992             IF cur_trk_exists%FOUND THEN
993                CLOSE cur_trk_exists;
994                l_records_not_found := FALSE;
995 		-- Make a call to the procedure : get_cpti_apcmp
996 	       get_incp_trstp(cur_appl_details_rec.person_id,
997 	                      cur_appl_details_rec.admission_appl_number,
998 			      cur_appl_details_rec.nominated_course_cd,
999 			      cur_appl_details_rec.sequence_number);
1000 
1001 
1002 	            ELSE
1003                CLOSE cur_trk_exists;
1004            END IF;
1005 	       END LOOP;
1006                        IF l_records_not_found THEN
1007                 -- Tracking steps cannot be completed for applications not having application completion status of pending
1008                 -- and application outcome status of pending or conditional offer
1009                 FND_MESSAGE.SET_NAME('IGS', 'IGS_AD_APP_PEND_STAT');
1010                 FND_FILE.PUT_LINE( FND_FILE.LOG, FND_MESSAGE.GET());
1011 
1012                  -- Abort the process and raise error
1013                  RETURN;
1014               END IF;
1015     END IF;
1016 
1017     -- For all the successful transactions save the changes to the database
1018     -- If called from Job then commit , if called from SS skip commit
1019     IF NVL( IGS_AD_TI_COMP.G_CALLED_FROM, 'J') = 'J' THEN
1020       COMMIT;
1021     END IF;
1022 
1023   EXCEPTION
1024      WHEN OTHERS THEN
1025        FND_MESSAGE.SET_NAME ( 'IGS', 'IGS_GE_UNHANDLED_EXP');
1026        FND_MESSAGE.SET_TOKEN ( 'NAME', ' igs_ad_ti_comp.upd_trk_itm_st');
1027        errbuf := FND_MESSAGE.GET_STRING ( 'IGS', FND_MESSAGE.GET);
1028        -- Rollback the transaction
1029        ROLLBACK;
1030        retcode := 2;
1031        -- Handle the standard igs-message stack
1032        igs_ge_msg_stack.conc_exception_hndl;
1033  END upd_trk_itm_st;
1034 END igs_ad_ti_comp;