DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGF_AP_GEN

Source


1 PACKAGE BODY igf_ap_gen AS
2 /* $Header: IGFAP36B.pls 120.2 2005/12/11 03:59:59 appldev ship $ */
3 
4   FUNCTION validate_cal_inst(
5                              p_cal_cat         IN            igs_ca_type.s_cal_cat%TYPE,
6                              p_alt_code_one    IN            igs_ca_inst.alternate_code%TYPE,
7                              p_alt_code_two    IN            igs_ca_inst.alternate_code%TYPE,
8                              p_cal_type        IN OUT NOCOPY igs_ca_inst.cal_type%TYPE,
9                              p_sequence_number IN OUT NOCOPY igs_ca_inst.sequence_number%TYPE
10                             ) RETURN BOOLEAN AS
11 
12       /*
13       ||  Created By : brajendr
14       ||  Created On : 03-June-2003
15       ||  Purpose : Routine will verify whethere the metnioned alternate code (one) is a valid calendar instance or not.
16       ||            If valid calendar instance then checks whether alternate code two is under alternate code one.
17       ||            Valid values for cal category are AWARD, LOAD, TEACHING. Returns TRUE if sucessful else FALSE.
18       ||  Known limitations, enhancements or remarks :
19       ||  Change History :
20       ||  Who             When            What
21       ||  (reverse chronological order - newest change first)
22       */
23 
24       -- Get the details of
25       CURSOR check_cal_inst(
26                             cp_cal_cat       igs_ca_type.s_cal_cat%TYPE,
27                             cp_alternate_code igs_ca_inst.alternate_code%TYPE
28                            ) IS
29       SELECT cainst.alternate_code, cainst.cal_type, cainst.sequence_number
30         FROM igs_ca_inst cainst, igs_ca_type catyp
31        WHERE catyp.s_cal_cat = cp_cal_cat
32          AND cainst.cal_type = catyp.cal_type
33          AND cainst.ALTERNATE_CODE = cp_alternate_code
34          AND ROWNUM = 1;
35 
36       check_cal_inst_rec check_cal_inst%ROWTYPE;
37 
38       -- Get the details of
39       CURSOR check_awd_load_rel(
40                                 cp_alternate_code     igs_ca_inst.alternate_code%TYPE,
41                                 cp_ld_cal_type        igs_ca_inst.cal_type%TYPE,
42                                 cp_ld_sequence_number igs_ca_inst.sequence_number%TYPE
43                                ) IS
44       SELECT 'X' val
45         FROM igs_ca_inst_rel rel,
46              igs_ca_inst ca
47        WHERE rel.sup_cal_type = ca.cal_type
48          AND rel.sup_ci_sequence_number = ca.sequence_number
49          AND ca.alternate_code = cp_alternate_code
50          AND sub_cal_type = cp_ld_cal_type
51          AND sub_ci_sequence_number = cp_ld_sequence_number
52          AND ROWNUM = 1;
53 
54       check_awd_load_rel_rec check_awd_load_rel%ROWTYPE;
55 
56       -- Get the details of
57       CURSOR check_load_teach_rel(
58                                   cp_alternate_code_load  igs_ca_inst.alternate_code%TYPE,
59                                   cp_alternate_code_teach igs_ca_inst.alternate_code%TYPE
60                                  ) IS
61       SELECT 'X' val
62         FROM igs_ca_load_to_teach_v
63        WHERE load_alternate_code  = cp_alternate_code_load
64          AND teach_alternate_code = cp_alternate_code_teach
65          AND ROWNUM = 1;
66 
67       check_load_teach_rel_rec check_load_teach_rel%ROWTYPE;
68 
69       return_val        BOOLEAN;
70 
71     BEGIN
72 
73       return_val := FALSE;
74       p_cal_type        := NULL;
75       p_sequence_number := NULL;
76 
77       IF p_cal_cat = 'AWARD' THEN
78 
79         OPEN check_cal_inst(p_cal_cat, p_alt_code_one);
80         FETCH check_cal_inst INTO check_cal_inst_rec;
81         IF check_cal_inst%FOUND THEN
82           return_val := TRUE;
83           p_cal_type        := check_cal_inst_rec.cal_type;
84           p_sequence_number := check_cal_inst_rec.sequence_number;
85         END IF;
86         CLOSE check_cal_inst;
87 
88       ELSIF p_cal_cat = 'LOAD'  THEN
89 
90         OPEN check_cal_inst(p_cal_cat, p_alt_code_two);
91         FETCH check_cal_inst INTO check_cal_inst_rec;
92         IF check_cal_inst%FOUND THEN
93 
94           p_cal_type        := check_cal_inst_rec.cal_type;
95           p_sequence_number := check_cal_inst_rec.sequence_number;
96 
97           OPEN check_awd_load_rel(p_alt_code_one, p_cal_type, p_sequence_number );
98           FETCH check_awd_load_rel INTO check_awd_load_rel_rec;
99           IF check_awd_load_rel%FOUND AND check_awd_load_rel_rec.val = 'X' THEN
100             return_val := TRUE;
101           END IF;
102           CLOSE check_awd_load_rel;
103 
104         END IF;
105         CLOSE check_cal_inst;
106 
107       ELSIF p_cal_cat = 'TEACHING' THEN
108 
109         OPEN check_cal_inst(p_cal_cat, p_alt_code_two);
110         FETCH check_cal_inst INTO check_cal_inst_rec;
111         IF check_cal_inst%FOUND THEN
112 
113           p_cal_type        := check_cal_inst_rec.cal_type;
114           p_sequence_number := check_cal_inst_rec.sequence_number;
115 
116           OPEN check_load_teach_rel(p_alt_code_one, p_alt_code_two );
117           FETCH check_load_teach_rel INTO check_load_teach_rel_rec;
118           IF check_load_teach_rel%FOUND AND check_load_teach_rel_rec.val = 'X' THEN
119             return_val := TRUE;
120           END IF;
121           CLOSE check_load_teach_rel;
122 
123         END IF;
124         CLOSE check_cal_inst;
125 
126       ELSE
127         return_val := FALSE;
128 
129       END IF;
130 
131 
132       RETURN return_val;
133 
134     END validate_cal_inst;
135 
136 
137   PROCEDURE check_person ( p_person_number     IN                         igf_aw_li_coa_ints.person_number%TYPE,
138                            p_ci_cal_type         IN                         igs_ca_inst.cal_type%TYPE,
139                            p_ci_sequence_number  IN                         igs_ca_inst.sequence_number%TYPE,
140                            p_person_id           OUT  NOCOPY                         igf_ap_fa_base_rec_all.person_id%TYPE,
141                            p_fa_base_id          OUT  NOCOPY                         igf_ap_fa_base_rec_all.base_id%TYPE )  IS
142 
143     /*
144     ||  Created By : masehgal
145     ||  Created On : 28-May-2003
146     ||  Purpose    : check person's existence, fa base rec existence
147     ||  Known limitations, enhancements or remarks :
148     ||  Change History :
149     ||  Who             When            What
150     ||  (reverse chronological order - newest change first)
151     */
152 
153       -- check person existence
154       CURSOR  c_person_exist ( cp_person_number
155   igs_pe_person_base_v.person_number%TYPE ) IS
156          SELECT hz.party_id  person_id
157            FROM igs_pe_hz_parties  hz,
158                 hz_parties hz1
159           WHERE hz1.party_number = cp_person_number
160           AND   hz.party_id = hz1.party_id;
161       l_person_id    c_person_exist%ROWTYPE;
162 
163       -- check for fa base rec existence
164       CURSOR c_fabase_exist ( cp_person_id
165   igf_ap_fa_base_rec_all.person_id%TYPE ) IS
166          SELECT base_id   fa_base_id
167            FROM igf_ap_fa_base_rec_all
168           WHERE person_id          = cp_person_id
169             AND ci_cal_type        = p_ci_cal_type
170             AND ci_sequence_number = p_ci_sequence_number ;
171       l_fa_base_id    c_fabase_exist%ROWTYPE;
172 
173 
174      BEGIN  -- check person
175         -- check for person number existence
176         IF p_person_number IS NULL THEN
177             p_person_id := NULL;
178             p_fa_base_id   := NULL;
179             RETURN;
180         END IF;
181 
182         OPEN  c_person_exist (p_person_number) ;
183         FETCH c_person_exist INTO l_person_id ;
184         IF c_person_exist%FOUND THEN
185            p_person_id := l_person_id.person_id ;
186 
187            IF (p_ci_cal_type IS NULL) OR (p_ci_sequence_number IS NULL) THEN
188               p_fa_base_id := NULL;
189               RETURN;
190            END IF;
191                    -- check for fa base rec existence
192            OPEN  c_fabase_exist (l_person_id.person_id) ;
193            FETCH c_fabase_exist INTO l_fa_base_id ;
194            IF c_fabase_exist%FOUND THEN
195 
196               p_fa_base_id  := l_fa_base_id.fa_base_id  ;
197            ELSE
198 
199               p_fa_base_id := NULL ;
200            END IF ;  -- fa base check
201            CLOSE c_fabase_exist ;
202         ELSE
203 
204            p_person_id := NULL ;
205            p_fa_base_id := NULL;
206         END IF ; -- person check
207         CLOSE c_person_exist ;
208 
209     END check_person ;
210 
211 
212 
213 
214 
215 
216 
217   FUNCTION get_lookup_meaning (p_lookup_type  IN VARCHAR2,
218                                p_lookup_code  IN VARCHAR2)
219   RETURN VARCHAR2 IS
220 
221   /*
222       ||  Created By : cdcruz
223       ||  Created On : 03-June-2003
224       ||  Purpose :
225       ||  Known limitations, enhancements or remarks :
226       ||  Change History :
227       ||  Who             When            What
228       ||  (reverse chronological order - newest change first)
229       */
230 
231 
232   l_meaning igf_lookups_view.meaning%TYPE;
233 
234   l_hash_code    NUMBER;
235   l_hash_type    NUMBER;
236   l_db_hash_code NUMBER;
237   l_is_code_valid   BOOLEAN;
238   l_is_lktype_chc   BOOLEAN;
239 
240   CURSOR c_lookup (lv_lookup_type VARCHAR2)
241   IS
242   SELECT
243     lookup_type,
244     lookup_code,
245     meaning
246   FROM
247     igf_lookups_view
248   WHERE
249     lookup_type = lv_lookup_type
250     AND enabled_flag='Y';
251 
252   l_lookup_rec c_lookup%rowtype;
253 
254   BEGIN
255 
256     l_meaning := NULL;
257 
258     -- If parameters are not valid return
259 
260     IF p_lookup_code IS NULL OR p_lookup_type IS NULL THEN
261 
262        return(NULL);
263 
264     END IF;
265 
266       -- Get the hash value of the Type + Code
267       l_hash_code := DBMS_UTILITY.get_hash_value(
268                                            p_lookup_type||'@*?'||p_lookup_code,
269                                            1000,
270                                            25000);
271 
272       IF l_lookups_rec.EXISTS(l_hash_code) THEN
273           l_meaning := l_lookups_rec(l_hash_code);
274           return(l_meaning);
275       END IF;
276 
277       -- Check if the Type is already cached
278       l_hash_type := DBMS_UTILITY.get_hash_value(
279                                            p_lookup_type,
280                                            1000,
281                                            25000);
282 
283       IF l_lookups_type_rec.EXISTS(l_hash_type) THEN
284           return(NULL);
285       END IF;
286 
287       --Type not cached so cache it.
288 
289       l_is_code_valid  := FALSE;
290       l_is_lktype_chc  := FALSE;
291       OPEN c_lookup(p_lookup_type);
292       LOOP
293 
294        FETCH c_lookup into l_lookup_rec;
295        EXIT WHEN c_lookup%NOTFOUND;
296 
297       -- Cache the Lookup Type only once
298       IF NOT l_is_lktype_chc THEN
299         l_is_lktype_chc  := TRUE;
300         l_hash_type := DBMS_UTILITY.get_hash_value(
301                                                    p_lookup_type,
302                                                    1000,
303                                                    25000
304                                                   );
305         l_lookups_type_rec(l_hash_type) := p_lookup_type;
306 
307       END IF;
308 
309        l_db_hash_code := DBMS_UTILITY.get_hash_value(
310                                            l_lookup_rec.lookup_type||'@*?'||l_lookup_rec.lookup_code,
311                                            1000,
312                                            25000);
313 
314        l_lookups_rec(l_db_hash_code) := l_lookup_rec.meaning;
315 
316        IF l_db_hash_code = l_hash_code THEN
317            l_is_code_valid := TRUE;
318            l_meaning := l_lookup_rec.meaning;
319        END IF;
320 
321       END LOOP;
322       CLOSE c_lookup;
323 
324       return(l_meaning);
325 
326   END get_lookup_meaning;
327 
328 
329   FUNCTION get_aw_lookup_meaning (p_lookup_type  IN VARCHAR2,
330                                   p_lookup_code  IN VARCHAR2,
331                                   p_sys_award_year IN VARCHAR2)
332   RETURN VARCHAR2 IS
333 
334     /*
335       ||  Created By : brajendr
336       ||  Created On : 03-June-2003
337       ||  Purpose :
338       ||  Known limitations, enhancements or remarks :
339       ||  Change History :
340       ||  Who             When            What
341       ||  (reverse chronological order - newest change first)
342       */
343 
344 
345   l_meaning igf_lookups_view.meaning%TYPE;
346 
347   l_hash_code    NUMBER;
348   l_hash_type    NUMBER;
349   l_db_hash_code NUMBER;
350   l_is_code_valid   BOOLEAN;
351   l_is_lktype_chc   BOOLEAN;
352 
353   CURSOR c_lookup (lv_lookup_type VARCHAR2,
354                    lv_sys_award_year VARCHAR2)
355   IS
356   SELECT
357     lookup_type,
358     lookup_code,
359     meaning
360   FROM
361     igf_aw_lookups_view
362   WHERE
363     lookup_type    = lv_lookup_type and
364     sys_award_year = lv_sys_award_year
365     AND enabled_flag='Y';
366 
367   l_lookup_rec c_lookup%rowtype;
368 
369   BEGIN
370 
371     l_meaning := NULL;
372 
373     -- If parameters are not valid return
374     IF p_lookup_code IS NULL OR p_lookup_type IS NULL OR p_sys_award_year IS NULL THEN
375       return(NULL);
376     END IF;
377 
378     -- Get the hash value of the Type + Code
379     l_hash_code := DBMS_UTILITY.get_hash_value(
380                                          p_lookup_type||'@*?'||p_lookup_code||'@*?'||p_sys_award_year,
381                                          1000,
382                                          25000);
383 
384     IF l_lookups_rec.EXISTS(l_hash_code) THEN
385         l_meaning := l_lookups_rec(l_hash_code);
386         return(l_meaning);
387     END IF;
388 
389     -- Check if the Type is already cached
390     l_hash_type := DBMS_UTILITY.get_hash_value(
391                                          p_lookup_type||'@*?'||p_sys_award_year,
392                                          1000,
393                                          25000);
394 
395     IF l_lookups_type_rec.EXISTS(l_hash_type) THEN
396       return(NULL);
397     END IF;
398 
399     --Type not cached so cache it.
400     l_is_code_valid  := FALSE;
401     l_is_lktype_chc  := FALSE;
402     OPEN c_lookup(p_lookup_type,p_sys_award_year);
403     LOOP
404 
405      FETCH c_lookup INTO l_lookup_rec;
406      EXIT WHEN c_lookup%NOTFOUND;
407 
408       -- Cache the Lookup Type only once
409       IF NOT l_is_lktype_chc THEN
410         l_is_lktype_chc  := TRUE;
411         l_hash_type := DBMS_UTILITY.get_hash_value(
412                                                    p_lookup_type||'@*?'||p_sys_award_year,
413                                                    1000,
414                                                    25000
415                                                   );
416         l_lookups_type_rec(l_hash_type) := p_lookup_type;
417 
418       END IF;
419 
420       l_db_hash_code := DBMS_UTILITY.get_hash_value(
421                                            l_lookup_rec.lookup_type||'@*?'||l_lookup_rec.lookup_code||'@*?'||p_sys_award_year,
422                                            1000,
423                                            25000);
424 
425       l_lookups_rec(l_db_hash_code) := l_lookup_rec.meaning;
426 
427       IF l_db_hash_code = l_hash_code THEN
428         l_is_code_valid := TRUE;
429         l_meaning := l_lookup_rec.meaning;
430       END IF;
431 
432     END LOOP;
433     CLOSE c_lookup;
434 
435     return(l_meaning);
436 
437   END get_aw_lookup_meaning;
438 
439   FUNCTION check_profile
440   RETURN VARCHAR2
441   IS
442     /*
443       ||  Created By : rasahoo
444       ||  Created On : 03-June-2003
445       ||  Purpose : Checks the profile set to US country code and participating in financial aid programme.
446       ||  Known limitations, enhancements or remarks :
447       ||  Change History :
448       ||  Who             When            What
449       ||  (reverse chronological order - newest change first)
450       */
451 
452   lv_cntry_code  VARCHAR2(100);
453   lv_fin_aid         VARCHAR2(100);
454 
455   lv_retval  VARCHAR2(10);
456 
457   BEGIN
458 
459            lv_retval := 'NULL';
460 
461            fnd_profile.get('OSS_COUNTRY_CODE',lv_cntry_code);
462            fnd_profile.get('IGS_PS_PARTICIPATE_FA_PROG',lv_fin_aid);
463 
464           IF lv_cntry_code ='US' AND lv_fin_aid      = 'Y'    THEN
465                 lv_retval     := 'Y';
466           ELSE
467                 lv_retval     := 'N';
468           END IF;
469 
470 
471   RETURN     lv_retval;
472 
473   END check_profile;
474 
475   FUNCTION check_batch(p_batch_id   IN  NUMBER,
476                        p_batch_type IN  VARCHAR2)
477   RETURN VARCHAR2
478   IS
479    /*
480       ||  Created By : bkkumar
481       ||  Created On : 03-June-2003
482       ||  Purpose : Routine will verify whether the batch id is valid for
483       ||            the current batch type.
484       ||  Known limitations, enhancements or remarks :
485       ||  Change History :
486       ||  Who             When            What
487       ||  (reverse chronological order - newest change first)
488       */
489   CURSOR c_chk_batch(cp_batch_num NUMBER,
490                    cp_batch_type VARCHAR2)
491   IS
492   SELECT 'x'
493   FROM   igf_ap_li_bat_ints
494   WHERE  batch_num = cp_batch_num
495   AND    batch_type = cp_batch_type
496   AND    rownum = 1;
497 
498   l_chk_batch c_chk_batch%ROWTYPE;
499 
500   l_retval  VARCHAR2(1) := 'Y';
501 
502   BEGIN
503 
504      OPEN c_chk_batch(p_batch_id,p_batch_type);
505      FETCH c_chk_batch INTO l_chk_batch;
506      IF c_chk_batch%NOTFOUND OR c_chk_batch%NOTFOUND IS NULL THEN
507         l_retval := 'N';
508      END IF;
509      CLOSE c_chk_batch;
510 
511   RETURN     l_retval;
512 
513   END check_batch;
514 
515   FUNCTION get_isir_value(
516                           p_base_id          IN igf_ap_fa_base_rec_all.base_id%TYPE,
517                           p_sar_field_name   IN igf_fc_sar_cd_mst.sar_field_name%TYPE
518                          ) RETURN VARCHAR2 AS
519 
520     /*
521     ||  Created By : brajendr
522     ||  Created On : 16-Oct-2003
523     ||  Purpose    : Gets the Payment ISIR Value, it is used in the
524     ||               Verification SS pages to display the payment isir value.
525     ||  Known limitations, enhancements or remarks :
526     ||  Change History :
527     ||  Who             When            What
528     ||  (reverse chronological order - newest change first)
529     */
530 
531     lv_cur               PLS_INTEGER;
532     lv_retval            igf_ap_isir_corr.original_value%TYPE;
533     lv_stmt              VARCHAR2(2000);
534     lv_rows              integer;
535 
536   BEGIN
537 
538     IF p_base_id IS NULL OR p_sar_field_name IS NULL THEN
539       RETURN NULL;
540 
541     ELSE
542 
543       IF p_sar_field_name IS NOT NULL THEN
544         lv_cur  := DBMS_SQL.OPEN_CURSOR;
545         lv_stmt := 'SELECT '||p_sar_field_name ||' FROM igf_ap_isir_matched_all WHERE payment_isir = ''Y'' AND system_record_type = ''ORIGINAL'' AND base_id =  '||to_char(p_base_id);
546 
547         DBMS_SQL.PARSE(lv_cur, lv_stmt, 2);
548         DBMS_SQL.DEFINE_COLUMN(lv_cur, 1, lv_retval, 30);
549         lv_rows := DBMS_SQL.EXECUTE_AND_FETCH(lv_cur);
550         DBMS_SQL.COLUMN_VALUE(lv_cur,1,lv_retval);
551         DBMS_SQL.CLOSE_CURSOR(lv_cur);
552 
553         RETURN lv_retval;
554 
555       END IF;
556 
557     END IF;
558 
559     RETURN NULL;
560 
561   EXCEPTION
562     WHEN others THEN
563       RETURN NULL;
564   END get_isir_value;
565 
566 
567   FUNCTION get_indv_efc_4_term(
568                                p_base_id         IN igf_ap_fa_base_rec_all.base_id%TYPE,
569                                p_cal_type        IN igf_ap_fa_base_rec_all.ci_cal_type%TYPE,
570                                p_sequence_number IN igf_ap_fa_base_rec_all.ci_sequence_number%TYPE,
571                                p_isir_id         IN igf_ap_isir_matched_all.isir_id%TYPE
572                               ) RETURN NUMBER AS
573    /*
574     ||  Created By : rasahoo
575     ||  Created On : 15-10-2003
576     ||  Purpose    : get individual family contribution for a term
577     ||  Known limitations, enhancements or remarks :
578     ||  Change History :
579     ||  Who             When            What
580     ||  (reverse chronological order - newest change first)
581     ||  rasahoo         20-NOV-2003    Changed the cursor c_cum_efc as part of
582     ||                                 Build ISIR update 2004 - 05
583     */
584 
585     CURSOR c_cum_efc(
586                      cp_base_id  igf_ap_fa_base_rec_all.base_id%TYPE,
587                      cp_isir_id  igf_ap_isir_matched_all.isir_id%TYPE
588                     ) IS
589     SELECT distinct ca.alternate_code,
590            ca.start_dt ld_start_dt,
591            ca.end_dt ld_end_dt,
592            igf_ap_gen.get_individual_coa_amt(ca.start_dt,fa.base_id) coa,
593            ca.cal_type ld_cal_type, ca.sequence_number ld_sequence_number,
594            DECODE(fa.AWARD_FMLY_CONTRIBUTION_TYPE, '2',
595              DECODE ( igf_ap_efc_calc.get_efc_no_of_months(ca.end_dt, coa.base_id ),
596                  1 , SEC_ALTERNATE_MONTH_1,
597                  2 , SEC_ALTERNATE_MONTH_2,
598                  3 , SEC_ALTERNATE_MONTH_3,
599                  4 , SEC_ALTERNATE_MONTH_4,
600                  5 , SEC_ALTERNATE_MONTH_5,
601                  6 , SEC_ALTERNATE_MONTH_6,
602                  7 , SEC_ALTERNATE_MONTH_7,
603                  8 , SEC_ALTERNATE_MONTH_8,
604                  9 , SECONDARY_EFC,
605                  10, SEC_ALTERNATE_MONTH_10,
606                  11, SEC_ALTERNATE_MONTH_11,
607                  12, SEC_ALTERNATE_MONTH_12 ) ,
608              DECODE ( igf_ap_efc_calc.get_efc_no_of_months(ca.end_dt, coa.base_id ),
609                  1 , PRIMARY_ALTERNATE_MONTH_1,
610                  2 , PRIMARY_ALTERNATE_MONTH_2,
611                  3 , PRIMARY_ALTERNATE_MONTH_3,
612                  4 , PRIMARY_ALTERNATE_MONTH_4,
613                  5 , PRIMARY_ALTERNATE_MONTH_5,
614                  6 , PRIMARY_ALTERNATE_MONTH_6,
615                  7 , PRIMARY_ALTERNATE_MONTH_7,
616                  8 , PRIMARY_ALTERNATE_MONTH_8,
617                  9 , PRIMARY_EFC,
618                  10, PRIMARY_ALTERNATE_MONTH_10,
619                  11, PRIMARY_ALTERNATE_MONTH_11,
620                  12, PRIMARY_ALTERNATE_MONTH_12 ) ) efc
621       FROM igf_ap_isir_matched_all isir,
622            igf_ap_fa_base_rec_all fa,
623            igs_ca_inst_all ca,
624            igf_aw_coa_itm_terms coa
625      WHERE coa.base_id = fa.base_id
626        AND coa.base_id = isir.base_id
627        AND fa.base_id = cp_base_id
628        AND isir.isir_id = cp_isir_id
629        AND coa.ld_sequence_number = ca.sequence_number
630        AND coa.ld_cal_type = ca.cal_type
631        ORDER BY ca.start_dt;
632 
633     l_prev_efc  NUMBER := 0;
634     l_efc       NUMBER := 0;
635 
636   BEGIN
637 
638     FOR lc_cum_efc IN c_cum_efc(p_base_id, p_isir_id) LOOP
639 
640       IF (lc_cum_efc.LD_CAL_TYPE = p_cal_type) AND (lc_cum_efc.LD_SEQUENCE_NUMBER = p_sequence_number) THEN
641         l_efc := (lc_cum_efc.efc - l_prev_efc);
642         IF l_efc < 0 THEN
643           return 0;
644         ELSE
645           return l_efc;
646         END IF;
647       ELSE
648         l_prev_efc := lc_cum_efc.efc;
649       END IF;
650 
651     END LOOP;
652 
653     RETURN 0;
654   EXCEPTION
655     WHEN OTHERS THEN
656       RETURN 0;
657   END get_indv_efc_4_term;
658 
659 
660   FUNCTION get_cumulative_coa_amt(
661                                   p_ld_start_dt    IN  DATE,
662                                   p_base_id        IN  igf_ap_fa_base_rec_all.base_id%TYPE
663                                  ) RETURN NUMBER IS
664     /*
665     ||  Created By : rasahoo
666     ||  Created On : 27-NOV-2003
667     ||  Purpose    : get Cumulative COA Amount for the student based on the start date
668     ||  Known limitations, enhancements or remarks :
669     ||  Change History :
670     ||  Who             When            What
671     ||  (reverse chronological order - newest change first)
672     ||  rasahoo         27-NOV-2003    Created the file
673     */
674 
675     CURSOR sel_coa_amt_cur(
676                            cp_ld_start_dt    IN  DATE,
677                            cp_base_id        IN  igf_ap_fa_base_rec_all.base_id%TYPE
678                           )IS
679     SELECT SUM(coait.amount) coa
680       FROM igf_aw_coa_itm_terms coait,
681            igs_ca_inst ca
682      WHERE ca.cal_type   = coait.ld_cal_type
683        AND ca.sequence_number = coait.ld_sequence_number
684        AND ca.start_dt   <= cp_ld_start_dt
685        AND coait.base_id =  cp_base_id;
686 
687     l_tot_coa_amt   NUMBER := 0;
688 
689   BEGIN
690 
691     OPEN sel_coa_amt_cur(p_ld_start_dt, p_base_id);
692     FETCH sel_coa_amt_cur  INTO l_tot_coa_amt;
693 
694     -- If no Data Found return the default value 0
695     IF sel_coa_amt_cur%NOTFOUND  THEN
696       CLOSE  sel_coa_amt_cur;
697       RETURN 0;
698     ELSE
699       CLOSE sel_coa_amt_cur;
700       RETURN l_tot_coa_amt;
701     END IF;
702 
703   EXCEPTION
704     WHEN OTHERS THEN
705       fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
706       fnd_message.set_token('NAME','IGF_AP_GEN.GET_CUMULATIVE_COA_AMT'||SQLERRM);
707       igs_ge_msg_stack.add;
708       app_exception.raise_exception;
709   END get_cumulative_coa_amt ;
710 
711 
712   FUNCTION get_individual_coa_amt(
713                                   p_ld_start_dt    IN  DATE,
714                                   p_base_id        IN  igf_ap_fa_base_rec_all.base_id%TYPE
715                                  ) RETURN NUMBER IS
716     /*
717     ||  Created By : rasahoo
718     ||  Created On : 27-NOV-2003
719     ||  Purpose    : get Individual COA Amount for the student based on the start date
720     ||  Known limitations, enhancements or remarks :
721     ||  Change History :
722     ||  Who             When            What
723     ||  (reverse chronological order - newest change first)
724     ||  rasahoo         27-NOV-2003    Created the file
725     */
726 
727     CURSOR sel_coa_amt_cur(
728                            cp_ld_start_dt    IN  DATE,
729                            cp_base_id        IN  igf_ap_fa_base_rec_all.base_id%TYPE
730                           )IS
731     SELECT SUM(coait.amount) coa
732       FROM igf_aw_coa_itm_terms coait,
733            igs_ca_inst ca
734      WHERE ca.cal_type   = coait.ld_cal_type
735        AND ca.sequence_number = coait.ld_sequence_number
736        AND ca.start_dt   = cp_ld_start_dt
737        AND coait.base_id = cp_base_id;
738 
739     l_tot_coa_amt   NUMBER := 0;
740 
741   BEGIN
742 
743     OPEN sel_coa_amt_cur(p_ld_start_dt, p_base_id);
744     FETCH sel_coa_amt_cur  INTO l_tot_coa_amt;
745 
746     -- If no Data Found return the default value 0
747     IF sel_coa_amt_cur%NOTFOUND  THEN
748       CLOSE  sel_coa_amt_cur;
749       RETURN 0;
750     ELSE
751       CLOSE sel_coa_amt_cur;
752       RETURN l_tot_coa_amt;
753     END IF;
754 
755   EXCEPTION
756     WHEN OTHERS THEN
757       fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
758       fnd_message.set_token('NAME','IGF_AP_GEN.GET_INDIVIDUAL_COA_AMT'||SQLERRM);
759       igs_ge_msg_stack.add;
760       app_exception.raise_exception;
761 
762   END get_individual_coa_amt;
763 
764   PROCEDURE update_preflend_todo_status ( p_person_id	     IN igf_ap_fa_base_rec_all.person_id%TYPE,
765                                           p_return_status  OUT NOCOPY VARCHAR2
766                                         ) IS
767   ------------------------------------------------------------------
768   --Created by  : bvisvana, Oracle India
769   --Date created: 09-Dec-2005
770   --
771   --Purpose: Bug 4773795 - To update the PREFLEND todo status when user assigns a preferred lender through the Manage Preferred Lender page
772   --
773   --Known limitations/enhancements and/or remarks:
774   --
775   --Change History:
776   --Who         When            What
777   -------------------------------------------------------------------
778 
779     CURSOR get_active_preflend(cp_person_id igf_ap_fa_base_rec_all.person_id%TYPE) IS
780       SELECT clprl_id FROM igf_sl_cl_pref_lenders WHERE
781       person_id = cp_person_id AND TRUNC(SYSDATE) BETWEEN start_date AND NVL(end_date,TRUNC(SYSDATE));
782 
783     CURSOR preflend_todo_item_dtls (cp_person_id igf_ap_fa_base_rec_all.person_id%TYPE) IS
784       SELECT clprl_id,base_id,item_sequence_number,status FROM igf_ap_td_item_inst_v WHERE
785       person_id = cp_person_id AND system_todo_type_code='PREFLEND';
786 
787     preflend_todo_item_rec preflend_todo_item_dtls%ROWTYPE;
788     l_status	      VARCHAR2(10);
789     l_return_status VARCHAR2(10);
790     l_clprl_id	    NUMBER;
791     l_update	      BOOLEAN := FALSE;
792 
793   BEGIN
794     -- 1. If there is an active preferred lender for the person. Check if it is in REQ or INC, if so make it 'COM'
795     -- 2. If No active Pref lender but there exists a system to do item of PREFLEND with COM , then make it REQ
796     p_return_status := 'S';
797     OPEN get_active_preflend(cp_person_id => p_person_id);
798     FETCH get_active_preflend INTO l_clprl_id;
799 
800     IF get_active_preflend%FOUND THEN -- Active Preflender is there
801 
802       OPEN preflend_todo_item_dtls(cp_person_id => p_person_id);
803       FETCH  preflend_todo_item_dtls INTO preflend_todo_item_rec;
804       IF preflend_todo_item_dtls%FOUND THEN
805         IF (preflend_todo_item_rec.status IN ('REQ','INC')) THEN
806           l_status := 'COM';
807           l_update := TRUE;
808         END IF;
809       END IF;
810 
811     ELSE -- No Active Preflender is there
812 
813       OPEN preflend_todo_item_dtls(cp_person_id => p_person_id);
814       FETCH  preflend_todo_item_dtls INTO preflend_todo_item_rec;
815       IF preflend_todo_item_dtls%FOUND THEN
816         IF (preflend_todo_item_rec.status = 'COM') THEN
817           l_status := 'REQ';
818           l_update := TRUE;
819           preflend_todo_item_rec.clprl_id := NULL;
820         END IF;
821       END IF;
822     END IF;
823 
824     IF l_update THEN
825       update_td_status( p_base_id		           => preflend_todo_item_rec.base_id,
826                         p_item_sequence_number => preflend_todo_item_rec.item_sequence_number,
827                         p_status               => l_status,
828                         p_clprl_id             => preflend_todo_item_rec.clprl_id,
829                         p_return_status        => l_return_status
830                       );
831       p_return_status := l_return_status;
832     END IF;
833     CLOSE get_active_preflend;
834     CLOSE preflend_todo_item_dtls;
835 
836     EXCEPTION
837       WHEN OTHERS THEN
838         p_return_status := 'F';
839         fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
840         fnd_message.set_token('NAME','IGF_AP_GEN.UPDATE_PREFLEND_TODO_STATUS'||SQLERRM);
841         igs_ge_msg_stack.add;
842         app_exception.raise_exception;
843 
844   END update_preflend_todo_status;
845 
846   PROCEDURE update_td_status(
847                              p_base_id                IN         igf_ap_fa_base_rec_all.base_id%TYPE,
848                              p_item_sequence_number   IN         igf_ap_td_item_inst_all.item_sequence_number%TYPE,
849                              p_status                 IN         igf_ap_td_item_inst_all.status%TYPE,
850                              p_clprl_id               IN         igf_sl_cl_pref_lenders.clprl_id%TYPE DEFAULT NULL,
851                              p_return_status          OUT NOCOPY VARCHAR2
852                             ) AS
853   ------------------------------------------------------------------
854   --Created by  : veramach, Oracle India
855   --Date created:
856   --
857   --Purpose:
858   --
859   --
860   --Known limitations/enhancements and/or remarks:
861   --
862   --Change History:
863   --Who         When            What
864   -------------------------------------------------------------------
865 
866   -- Get the item
867   CURSOR c_inst(
868                 cp_base_id              igf_ap_fa_base_rec_all.base_id%TYPE,
869                 cp_item_sequence_number igf_ap_td_item_inst_all.item_sequence_number%TYPE
870                ) IS
871     SELECT td.ROWID row_id,
872            td.*
873       FROM igf_ap_td_item_inst_all td
874      WHERE base_id = cp_base_id
875        AND item_sequence_number = cp_item_sequence_number;
876    l_inst c_inst%ROWTYPE;
877 
878    -- Get the system to do type code of the item
879    CURSOR c_system_todo_type(
880                              cp_todo_number igf_ap_td_item_mst_all.todo_number%TYPE
881                             ) IS
882      SELECT system_todo_type_code
883        FROM igf_ap_td_item_mst_all
884       WHERE todo_number = cp_todo_number;
885     l_system_todo_type c_system_todo_type%ROWTYPE;
886 
887    l_seq_val       NUMBER;
888 
889    l_wf_event_t           WF_EVENT_T;
890    l_wf_parameter_list_t  WF_PARAMETER_LIST_T;
891 
892    lv_event_name          VARCHAR2(4000);
893 
894    -- Get person number
895    CURSOR c_person_number(
896                           cp_base_id igf_ap_fa_base_rec_all.base_id%TYPE
897                          ) IS
898      SELECT hz.party_number
899        FROM hz_parties hz,
900             igf_ap_fa_base_rec_all fa
901       WHERE fa.person_id = hz.party_id
902         AND fa.base_id = cp_base_id;
903     l_person_number hz_parties.party_number%TYPE;
904 
905     -- Get item description
906     CURSOR c_td_item(
907                      cp_item_sequence_number igf_ap_td_item_inst_all.item_sequence_number%TYPE
908                     ) IS
909       SELECT description
910         FROM igf_ap_td_item_mst_all
911        WHERE todo_number = cp_item_sequence_number;
912     l_desc igf_ap_td_item_mst_all.description%TYPE;
913 
914     -- Get award year alternate code
915     CURSOR c_award_year(
916                         cp_base_id igf_ap_fa_base_rec_all.base_id%TYPE
917                        ) IS
918       SELECT ca.alternate_code
919         FROM igs_ca_inst_all ca,
920              igf_ap_fa_base_rec_all fa
921        WHERE fa.base_id = cp_base_id
922          AND fa.ci_cal_type = ca.cal_type
923          AND fa.ci_sequence_number = ca.sequence_number;
924     l_alternate_code igs_ca_inst_all.alternate_code%TYPE;
925 
926   BEGIN
927     OPEN c_inst(p_base_id,p_item_sequence_number);
928     FETCH c_inst INTO l_inst;
929     CLOSE c_inst;
930 
931     OPEN c_system_todo_type(p_item_sequence_number);
932     FETCH c_system_todo_type INTO l_system_todo_type;
933     CLOSE c_system_todo_type;
934 
935     IF l_system_todo_type.system_todo_type_code = 'PREFLEND' THEN
936       l_inst.clprl_id := p_clprl_id;
937     END IF;
938 
939     igf_ap_td_item_inst_pkg.update_row(
940                                        x_rowid                    => l_inst.row_id,
941                                        x_base_id                  => l_inst.base_id,
942                                        x_item_sequence_number     => l_inst.item_sequence_number,
943                                        x_status                   => p_status,
944                                        x_status_date              => TRUNC(SYSDATE),
945                                        x_add_date                 => l_inst.add_date,
946                                        x_corsp_date               => l_inst.corsp_date,
947                                        x_corsp_count              => l_inst.corsp_count,
948                                        x_inactive_flag            => l_inst.inactive_flag,
949                                        x_freq_attempt             => l_inst.freq_attempt,
950                                        x_max_attempt              => l_inst.max_attempt,
951                                        x_required_for_application => l_inst.required_for_application,
952                                        x_mode                     => 'R',
953                                        x_legacy_record_flag       => l_inst.legacy_record_flag,
954                                        x_clprl_id                 => l_inst.clprl_id
955                                       );
956     IF p_status IN ('COM','REC') THEN
957       OPEN c_person_number(p_base_id);
958       FETCH c_person_number INTO l_person_number;
959       CLOSE c_person_number;
960 
961       OPEN c_td_item(p_item_sequence_number);
962       FETCH c_td_item INTO l_desc;
963       CLOSE c_td_item;
964 
965       OPEN c_award_year(p_base_id);
966       FETCH c_award_year INTO l_alternate_code;
967       CLOSE c_award_year;
968 
969       SELECT igs_pe_res_chg_s.nextval INTO l_seq_val FROM DUAL;
970 
971       -- Initialize the wf_event_t object
972       WF_EVENT_T.Initialize(l_wf_event_t);
973 
974       -- Set the event name
975       IF p_status = 'COM' THEN
976         lv_event_name := 'oracle.apps.igf.td.ToDoCompleted';
977 
978       ELSIF p_status = 'REC' THEN
979         lv_event_name :=  'oracle.apps.igf.td.ToDoReceived';
980       END IF;
981       l_wf_event_t.setEventName(pEventName => lv_event_name);
982 
983       -- Set the event key
984         l_wf_event_t.setEventKey(
985                                  pEventKey => lv_event_name || l_seq_val
986                                 );
987 
988       -- Set the parameter list
989       l_wf_event_t.setParameterList(
990                                     pParameterList => l_wf_parameter_list_t
991                                    );
992 
993       -- Set the message's subject
994       IF p_status = 'COM' THEN
995         fnd_message.set_name('IGF','IGF_AP_TD_COMPLTD_SUBJ');
996       ELSIF p_status = 'REC' THEN
997         fnd_message.set_name('IGF','IGF_AP_TD_RECD_SUBJ');
998       END IF;
999       wf_event.addparametertolist(
1000                                   p_name          => 'SUBJECT',
1001                                   p_value         => fnd_message.get,
1002                                   p_parameterlist => l_wf_parameter_list_t
1003                                  );
1004 
1005       -- Set the person number
1006       wf_event.addparametertolist(
1007                                   p_name          => 'STUDENT_NUMBER',
1008                                   p_value         => l_person_number,
1009                                   p_parameterlist => l_wf_parameter_list_t
1010                                  );
1011 
1012       -- Set the to do item description
1013       wf_event.addparametertolist(
1014                                   p_name          => 'TO_DO_ITEM',
1015                                   p_value         => l_desc,
1016                                   p_parameterlist => l_wf_parameter_list_t
1017                                  );
1018 
1019       -- Set the award year alternate code
1020       wf_event.addparametertolist(
1021                                   p_name          => 'AWARD_YEAR',
1022                                   p_value         => l_alternate_code,
1023                                   p_parameterlist => l_wf_parameter_list_t
1024                                  );
1025 
1026       wf_Event.raise(
1027                      p_event_name => lv_event_name,
1028                      p_event_key  => lv_event_name || l_seq_val,
1029                      p_parameters => l_wf_parameter_list_t
1030                     );
1031     END IF;
1032     p_return_status := 'S';
1033 
1034     EXCEPTION
1035       WHEN OTHERS THEN
1036         p_return_status := 'F';
1037         fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
1038         fnd_message.set_token('NAME','IGF_AP_GEN.UPDATE_TD_STATUS'||SQLERRM);
1039         igs_ge_msg_stack.add;
1040         app_exception.raise_exception;
1041 
1042   END update_td_status;
1043 
1044 END igf_ap_gen;