DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGS_FI_GEN_008

Source


1 PACKAGE BODY igs_fi_gen_008  AS
2 /* $Header: IGSFI88B.pls 120.5 2006/05/16 22:58:36 abshriva ship $ */
3 
4 /***********************************************************************************************
5   Created By     : shtatiko
6   Date Created By: 25-AUG-2003 ( Created as part of Enh# 3045007 )
7   Purpose        : This package contains number of generic procedures called from various places
8                    for Payment Plans Funtionality.
9 
10   Known limitations,enhancements,remarks:
11   Change History
12   Who           When            What
13   abshriva      17-May-2006     Bug 5113295 - Added function chk_unit_prg_transfer
14   uudayapr      8-Oct-2005      BUG 4660773 Added the Function mask_card_number for masking the CC Number
15   agairola      27-Sep-2005     Bug # 4625955 Added new PLSQL procedure chk_spa_rec_exists
16   svuppala      16-May-2005     Bug # 4226849 Added New PLSQL function which will return the latest standard
17                                 balance of the student for the personid provided as input to it.
18   bannamal      14-Apr-2005     Bug#4297359 ER Registration fee issue.
19                                  Modified the function get_complete_withdr_ret_amt. Added the parameter p_v_nonzero_billable_cp_flag.
20                                  Modified the where clause of the cursor cur_unit_attmpt.
21                                 Bug#4304524 Registration Fee Retention not working for the first date of Retention.
22                                  Modified the cursor cur_tp_ret
23   pathipat      03-Sep-2004     Enh 3880438 - Retention Enhancements
24                                 Added new functions.
25   rmaddipa      26-Jul-2004      Enh#3787816  Added  chk_chg_adj as part of Manual Reversal Build
26   uudayapr       20-oct-2003     Enh#3117341 Added get_invoice_number fuction as a part of
27                                 audit and special Fees Build.
28   shtatiko      25-AUG-2003     Enh# 3045007, Created this package.
29 ********************************************************************************************** */
30 
31   g_v_opt_fee_decl CONSTANT  VARCHAR2(1) := 'D';
32   g_v_waiver_yes   CONSTANT  VARCHAR2(1) := 'Y';
33 
34   PROCEDURE get_plan_details( p_n_person_id IN NUMBER,           /* Person Id */
35                               p_n_act_plan_id OUT NOCOPY NUMBER,        /* Active Payment Plan Id */
36                               p_v_act_plan_name OUT NOCOPY VARCHAR2     /* Active Payment Plan Name */
37                             ) IS
38   /***********************************************************************************************
39     Created By     :  Shtatiko
40     Date Created By:  25-AUG-2003 ( Created as part of Enh# 3045007 )
41     Purpose        :  Procedure to get Payment Plan Details
42 
43     Known limitations,enhancements,remarks:
44     Change History
45     Who         When            What
46   ***********************************************************************************************/
47   CURSOR cur_plan_details( cp_n_person_id NUMBER ) IS
48     SELECT student_plan_id,
49            payment_plan_name
50     FROM igs_fi_pp_std_attrs
51     WHERE person_id = p_n_person_id
52     AND plan_status_code = 'ACTIVE';
53   rec_plan_details cur_plan_details%ROWTYPE;
54 
55   BEGIN
56 
57     OPEN cur_plan_details ( p_n_person_id );
58     FETCH cur_plan_details INTO rec_plan_details;
59     IF cur_plan_details%NOTFOUND THEN
60       p_n_act_plan_id := NULL;
61       p_v_act_plan_name := NULL;
62     ELSE
63       p_n_act_plan_id := rec_plan_details.student_plan_id;
64       p_v_act_plan_name := rec_plan_details.payment_plan_name;
65     END IF;
66     CLOSE cur_plan_details;
67 
68   END get_plan_details;
69 
70   FUNCTION get_plan_balance( p_n_act_plan_id IN NUMBER,         /* Active Payment Plan Id */
71                              p_d_effective_date IN DATE         /* Effective Date */
72                            ) RETURN NUMBER IS
73   /***********************************************************************************************
74     Created By     :  Shtatiko
75     Date Created By:  25-AUG-2003 ( Created as part of Enh# 3045007 )
76     Purpose        :  Fuction to get Balance Amount for a given Payment Plan as of given date.
77 
78     Known limitations,enhancements,remarks:
79     Change History
80     Who         When            What
81   ***********************************************************************************************/
82   CURSOR cur_plan_balance ( cp_n_act_plan_id NUMBER, cp_d_effective_date DATE ) IS
83     SELECT SUM(due_amt)
84     FROM igs_fi_pp_instlmnts
85     WHERE student_plan_id = cp_n_act_plan_id
86     AND ((TRUNC(due_date) <= TRUNC(cp_d_effective_date)) OR (cp_d_effective_date IS NULL));
87   l_n_balance_amount igs_fi_pp_instlmnts.due_amt%TYPE;
88 
89   BEGIN
90 
91     OPEN cur_plan_balance ( p_n_act_plan_id, p_d_effective_date );
92     FETCH cur_plan_balance INTO l_n_balance_amount;
93     CLOSE cur_plan_balance;
94 
95     RETURN NVL(l_n_balance_amount, 0);
96 
97   END get_plan_balance;
98 
99   FUNCTION chk_active_pay_plan( p_n_person_id IN NUMBER ) RETURN VARCHAR2 IS
100   /***********************************************************************************************
101     Created By     :  Shtatiko
102     Date Created By:  25-AUG-2003 ( Created as part of Enh# 3045007 )
103     Purpose        :  Fucntion to check whether a give Payment Plan is active or not.
104 
105     Known limitations,enhancements,remarks:
106     Change History
107     Who         When            What
108   ***********************************************************************************************/
109   l_n_act_plan_id   igs_fi_pp_std_attrs.student_plan_id%TYPE;
110   l_v_act_plan_name igs_fi_pp_std_attrs.payment_plan_name%TYPE;
111 
112   BEGIN
113 
114     get_plan_details ( p_n_person_id, l_n_act_plan_id, l_v_act_plan_name );
115     IF l_n_act_plan_id IS NULL THEN
116       RETURN 'N';
117     ELSE
118       RETURN 'Y';
119     END IF;
120 
121   END chk_active_pay_plan;
122 
123   FUNCTION get_start_date ( p_d_start_date IN DATE,
124                             p_n_due_day IN NUMBER,
125                             p_v_last_day IN VARCHAR2,
126                             p_n_offset_days IN NUMBER
127                           ) RETURN DATE IS
128   /***********************************************************************************************
129     Created By     :  Shtatiko
130     Date Created By:  25-AUG-2003 ( Created as part of Enh# 3045007 )
131     Purpose        :  Function to get First Installment Date
132 
133     Known limitations,enhancements,remarks:
134     Change History
135     Who         When            What
136   ***********************************************************************************************/
137 
138   l_d_ret_start_date DATE;
139   l_v_date VARCHAR2(12);
140   BEGIN
141     -- The first installment must not come due if it is within the given number of days (Offset Days)
142     -- past the Start Date as specified by the parameters.
143     -- This is to prevent an installment from coming too soon after the Payment Plan start date.
144 
145     IF ( p_n_due_day IS NULL AND p_v_last_day = 'N')
146        OR ( p_n_due_day IS NOT NULL AND p_v_last_day = 'Y' ) THEN
147       RETURN NULL;
148     END IF;
149 
150     -- First Installment date should not be within offset days of Given Start Date.
151     l_d_ret_start_date := p_d_start_date + NVL(p_n_offset_days, 0);
152 
153     IF p_n_due_day IS NOT NULL THEN
154       IF TO_CHAR(l_d_ret_start_date, 'DD') >= p_n_due_day THEN
155         l_d_ret_start_date := ADD_MONTHS(l_d_ret_start_date, 1);
156       END IF;
157       l_v_date := TO_CHAR(p_n_due_day) || '-' || TO_CHAR(l_d_ret_start_date, 'MON-YYYY') ;
158       l_d_ret_start_date := fnd_date.string_to_date( l_v_date, 'DD-MON-YYYY' );
159     ELSE
160       l_d_ret_start_date := LAST_DAY(l_d_ret_start_date);
161     END IF;
162 
163     RETURN l_d_ret_start_date;
164 
165   END get_start_date;
166 
167   FUNCTION get_party_number ( p_n_party_id IN NUMBER ) RETURN VARCHAR2 IS
168   /***********************************************************************************************
169     Created By     :  Shtatiko
170     Date Created By:  25-AUG-2003 ( Created as part of Enh# 3045007 )
171     Purpose        :  Function that return Party Number for a given Party Id
172 
173     Known limitations,enhancements,remarks:
174     Change History
175     Who         When            What
176   ***********************************************************************************************/
177   CURSOR cur_party_number(cp_n_party_id NUMBER) IS
178     SELECT party_number
179     FROM   hz_parties
180     WHERE  party_id = cp_n_party_id;
181   l_v_party_number hz_parties.party_number%TYPE;
182 
183   BEGIN
184 
185     IF p_n_party_id IS NULL THEN
186       RETURN NULL;
187     END IF;
188 
189     OPEN cur_party_number(p_n_party_id);
190     FETCH cur_party_number INTO l_v_party_number;
191     IF cur_party_number%NOTFOUND THEN
192       l_v_party_number := NULL;
193     END IF;
194     CLOSE cur_party_number;
195     RETURN l_v_party_number;
196 
197   END get_party_number;
198 
199 
200    FUNCTION get_invoice_number ( p_n_invoice_id IN PLS_INTEGER ) RETURN VARCHAR2 IS
201   /***********************************************************************************************
202     Created By     :  UUDAYAPR
203     Date Created By:  20-OCT-2003 ( Created as part of Enh# 3117341 )
204     Purpose        :  Function That Return Charge Number For A Given Invoice Id
205 
206     Known limitations,enhancements,remarks:
207     Change History
208     Who         When            What
209   ***********************************************************************************************/
210 
211   CURSOR cur_charge_number(cp_v_invoice_id igs_fi_inv_int.invoice_id%TYPE) IS
212    SELECT invoice_number
213    FROM igs_fi_inv_int
214    WHERE invoice_id = cp_v_invoice_id;
215 
216    l_v_invoice_number cur_charge_number%ROWTYPE;
217   BEGIN
218     IF p_n_invoice_id IS NULL THEN
219       RETURN null;
220     ELSE
221       OPEN cur_charge_number(p_n_invoice_id);
222       FETCH cur_charge_number INTO l_v_invoice_number;
223             IF cur_charge_number%NOTFOUND THEN
224               CLOSE cur_charge_number;
225         RETURN null;
226       ELSE
227         CLOSE cur_charge_number;
228         RETURN l_v_invoice_number.invoice_number;
229       END IF;
230     END IF;
231   END get_invoice_number;
232 
233 
234 
235   PROCEDURE chk_chg_adj( p_n_person_id     IN  hz_parties.party_id%TYPE,
236                          p_v_location_cd   IN  igs_fi_fee_as_items.location_cd%TYPE,
237                          p_v_course_cd     IN  igs_ps_ver.course_cd%TYPE,
238                          p_v_fee_cal_type  IN  igs_fi_f_typ_ca_inst.fee_cal_type%TYPE,
239                          p_v_fee_cat       IN  igs_fi_fee_as_items.fee_cat%TYPE,
240                          p_n_fee_ci_sequence_number IN igs_fi_f_typ_ca_inst.fee_ci_sequence_number%TYPE,
244                          p_n_invoice_id    IN  igs_fi_inv_int_all.invoice_id%TYPE,
241                          p_v_fee_type      IN  igs_fi_fee_type.fee_type%TYPE,
242                          p_n_uoo_id        IN  igs_ps_unit_ofr_opt.uoo_id%TYPE,
243                          p_v_transaction_type IN igs_fi_inv_int_all.transaction_type%TYPE,
245                          p_v_invoice_num   OUT NOCOPY igs_fi_inv_int_all.invoice_number%TYPE,
246                          p_b_chg_decl_rev  OUT NOCOPY BOOLEAN
247                         ) IS
248 
249 /***********************************************************************************************
250     Created By     :  RMADDIPA
251     Date Created By:  26-Jul-04 ( Created as part of Enh# 3787816 )
252     Purpose        :  Procedure that checks if a particular charge has been reversed or declined
253 
254     Known limitations,enhancements,remarks:
255     Change History
256     Who         When            What
257   ***********************************************************************************************/
258   --cursor to check whether the charge with given invoice id has already been reversed or declined
259   CURSOR cur_chk_rev_decl(cp_invoice_id igs_fi_inv_int_all.invoice_id%TYPE) IS
260       SELECT inv.invoice_number
261       FROM igs_fi_inv_int inv
262       WHERE inv.invoice_id=cp_invoice_id
263       AND   (inv.optional_fee_flag = g_v_opt_fee_decl OR inv.waiver_flag = g_v_waiver_yes);
264 
265   --cursor to check whether a particular charge has been reversed or declined
266   CURSOR cur_chk_rev_decl_no_inv_id(
267                   cp_person_id    hz_parties.party_id%TYPE,
268                   cp_location_cd  igs_fi_fee_as_items.location_cd%TYPE,
269                   cp_course_cd    igs_ps_ver.course_cd%TYPE,
270                   cp_fee_cal_type igs_fi_f_typ_ca_inst.fee_cal_type%TYPE,
271                   cp_fee_cat      igs_fi_fee_as_items.fee_cat%TYPE,
272                   cp_fee_ci_sequence_number igs_fi_f_typ_ca_inst.fee_ci_sequence_number%TYPE,
273                   cp_fee_type     igs_fi_fee_type.fee_type%TYPE,
274                   cp_uoo_id       igs_ps_unit_ofr_opt.uoo_id%TYPE,
275                   cp_transaction_type igs_fi_inv_int_all.transaction_type%TYPE) IS
276       SELECT inv.invoice_number
277       FROM igs_fi_inv_int inv,
278            igs_fi_invln_int invln
279       WHERE inv.person_id=cp_person_id
280       AND   invln.invoice_id=inv.invoice_id
281       AND   inv.fee_cal_type=cp_fee_cal_type
282       AND   (inv.fee_cat = cp_fee_cat OR (inv.fee_cat IS NULL AND cp_fee_cat IS NULL))
283       AND   inv.fee_type = cp_fee_type
284       AND   inv.fee_ci_sequence_number = cp_fee_ci_sequence_number
285       AND   (inv.course_cd=cp_course_cd OR (inv.course_cd IS NULL AND cp_course_cd IS NULL))
286       AND   (invln.location_cd = cp_location_cd OR (invln.location_cd IS NULL AND cp_location_cd IS NULL))
287       AND   NVL(invln.uoo_id,0) = NVL(cp_uoo_id,0)
288       AND   inv.transaction_type = cp_transaction_type
289       AND   (inv.optional_fee_flag = g_v_opt_fee_decl OR inv.waiver_flag = g_v_waiver_yes);
290 
291   BEGIN
292 
293      IF (p_n_invoice_id IS NOT NULL) THEN
294          -- If the invoice id is known check whether the charge corresponding to the invoice id is reversed or declined
295          OPEN cur_chk_rev_decl(p_n_invoice_id);
296          FETCH cur_chk_rev_decl INTO p_v_invoice_num;
297 
298          IF (cur_chk_rev_decl%NOTFOUND) THEN
299              -- if charge is not reversed or declined return false
300              p_b_chg_decl_rev := FALSE;
301              p_v_invoice_num  := NULL;
302          ELSE
303              -- if charge has already been declined pass back the invoice number
304              p_b_chg_decl_rev := TRUE;
305          END IF;
306 
307          CLOSE cur_chk_rev_decl;
308 
309          RETURN;
310      ELSE
311          -- If invoice id is not known check whether the charge corresponding
312          --   to the context of person and other details is reversed or declined
313          OPEN cur_chk_rev_decl_no_inv_id( p_n_person_id,
314                                           p_v_location_cd,
315                                           p_v_course_cd,
316                                           p_v_fee_cal_type,
317                                           p_v_fee_cat,
318                                           p_n_fee_ci_sequence_number,
319                                           p_v_fee_type,
320                                           p_n_uoo_id,
321                                           p_v_transaction_type);
322          FETCH cur_chk_rev_decl_no_inv_id INTO p_v_invoice_num;
323 
324          IF (cur_chk_rev_decl_no_inv_id%NOTFOUND) THEN
325              -- if charge is not reversed or declined return false
326              p_b_chg_decl_rev := FALSE;
327              p_v_invoice_num  := NULL;
328          ELSE
329              -- if charge has already been declined pass back the invoice number
330              p_b_chg_decl_rev := TRUE;
331          END IF;
332 
333          CLOSE cur_chk_rev_decl_no_inv_id;
334 
335          RETURN;
336      END IF;
337 
338   END chk_chg_adj;
339 
340 
341   PROCEDURE get_retention_params( p_v_fee_cal_type            IN igs_fi_f_typ_ca_inst_all.fee_cal_type%TYPE,
342                                   p_n_fee_ci_sequence_number  IN igs_fi_f_typ_ca_inst_all.fee_ci_sequence_number%TYPE,
343                                   p_v_fee_type                IN igs_fi_f_typ_ca_inst_all.fee_type%TYPE,
344                                   p_v_ret_level               OUT NOCOPY igs_fi_f_typ_ca_inst_all.retention_level_code%TYPE,
345                                   p_v_complete_withdr_ret     OUT NOCOPY igs_fi_f_typ_ca_inst_all.complete_ret_flag%TYPE) AS
346   /**************************************************************************
347     Created By     :  Priya Athipatla
348     Date Created By:  03-Sep-2004
352     Known limitations,enhancements,remarks:
349     Purpose        :  Procedure to obtain values of columns retention_level_code
350                       and complete_ret_flag from table igs_fi_f_typ_ca_inst to
351                       be used in determing Retention Amount.
353 
354     Change History
355     Who         When            What
356    **************************************************************************/
357 
358    CURSOR cur_get_ret_params(cp_v_fee_type              igs_fi_f_typ_ca_inst_all.fee_type%TYPE,
359                              cp_v_fee_cal_type          igs_fi_f_typ_ca_inst_all.fee_cal_type%TYPE,
360                              cp_n_fee_ci_sequence_num   igs_fi_f_typ_ca_inst_all.fee_ci_sequence_number%TYPE) IS
361      SELECT retention_level_code,
362             NVL(complete_ret_flag,'N')
363      FROM  igs_fi_f_typ_ca_inst
364      WHERE fee_type               = cp_v_fee_type
365      AND   fee_cal_type           = cp_v_fee_cal_type
366      AND   fee_ci_sequence_number = cp_n_fee_ci_sequence_num;
367 
368   BEGIN
369 
370      p_v_ret_level := NULL;
371      p_v_complete_withdr_ret := NULL;
372 
373      -- Fetch values of retention_level_code and complete_ret_flag from the table
374      OPEN cur_get_ret_params(p_v_fee_type, p_v_fee_cal_type, p_n_fee_ci_sequence_number);
375      FETCH cur_get_ret_params INTO p_v_ret_level, p_v_complete_withdr_ret;
376      CLOSE cur_get_ret_params;
377 
378      IF (p_v_ret_level IS NULL AND p_v_complete_withdr_ret = 'N') THEN
379         p_v_ret_level := 'FEE_PERIOD';
380      END IF;
381 
382   END get_retention_params;
383 
384 
385   FUNCTION get_teach_retention( p_v_fee_cal_type             IN igs_fi_tp_ret_schd.fee_cal_type%TYPE,
386                                 p_n_fee_ci_sequence_number   IN igs_fi_tp_ret_schd.fee_ci_sequence_number%TYPE,
387                                 p_v_fee_type                 IN igs_fi_tp_ret_schd.fee_type%TYPE,
388                                 p_v_teach_cal_type           IN igs_fi_tp_ret_schd.teach_cal_type%TYPE,
389                                 p_n_teach_ci_sequence_number IN igs_fi_tp_ret_schd.teach_ci_sequence_number%TYPE,
390                                 p_d_effective_date           IN DATE,
391                                 p_n_diff_amount              IN NUMBER) RETURN NUMBER IS
392   /**************************************************************************
393     Created By     :  Priya Athipatla
394     Date Created By:  03-Sep-2004
395     Purpose        :  Function to determine the Retention Amount when the
396                       Retention Level at FTCI is set to Teaching Period
397     Known limitations,enhancements,remarks:
398 
399     Change History
400     Who         When            What
401    **************************************************************************/
402 
403    -- Cursor to fetch Retention Schedules defined at Teaching Period level and
404    -- overridden at the FTCI level.
405    CURSOR cur_tp_ovrd_ret(cp_v_fee_type              igs_fi_tp_ret_schd.fee_type%TYPE,
406                           cp_v_fee_cal_type          igs_fi_tp_ret_schd.fee_cal_type%TYPE,
407                           cp_n_fee_ci_sequence_num   igs_fi_tp_ret_schd.fee_ci_sequence_number%TYPE,
408                           cp_v_teach_cal_type        igs_fi_tp_ret_schd.teach_cal_type%TYPE,
409                           cp_n_teach_ci_seq_num      igs_fi_tp_ret_schd.teach_ci_sequence_number%TYPE) IS
410      SELECT *
411      FROM igs_fi_tp_ret_schd_v
412      WHERE teach_cal_type = cp_v_teach_cal_type
413      AND teach_ci_sequence_number =  cp_n_teach_ci_seq_num
414      AND fee_cal_type = cp_v_fee_cal_type
415      AND fee_ci_sequence_number = cp_n_fee_ci_sequence_num
416      AND fee_type = cp_v_fee_type
417      ORDER BY dai_alias_val;
418 
419   -- Cursor to fetch Retention Schedules defined at Teaching Period level
420   CURSOR cur_tp_ret(cp_v_teach_cal_type    igs_fi_tp_ret_schd.teach_cal_type%TYPE,
421                     cp_n_teach_ci_seq_num  igs_fi_tp_ret_schd.teach_ci_sequence_number%TYPE) IS
422     SELECT *
423     FROM igs_fi_tp_ret_schd_v
424     WHERE teach_cal_type = cp_v_teach_cal_type
425     AND teach_ci_sequence_number = cp_n_teach_ci_seq_num
426     AND fee_type IS NULL
427     AND fee_cal_type IS NULL
428     AND fee_ci_sequence_number IS NULL
429     ORDER BY dai_alias_val;
430 
431   l_n_ret_amount       igs_fi_tp_ret_schd.ret_amount%TYPE := 0;
432   l_n_ret_percent      igs_fi_tp_ret_schd.ret_percentage%TYPE := 0;
433 
434   -- Flag to indicate whether or not overridden retention schedules were found
435   l_b_override_ret     BOOLEAN := FALSE;
436 
437   -- Retention Amount calculated
438   l_n_amount           NUMBER := 0.0;
439 
440   BEGIN
441       -- If the Difference Amount is zero, then no Retention is applicable, return 0
442       IF (NVL(p_n_diff_amount,0) = 0) THEN
443          RETURN 0;
444       END IF;
445 
446       -- Determine if the Teaching Period Retention Schedules have been overridden at the FTCI level
447       -- Use the schedules overridden at FTCI level to calculate the retention amount.
448       FOR rec_tp_ovrd_ret IN cur_tp_ovrd_ret(p_v_fee_type, p_v_fee_cal_type, p_n_fee_ci_sequence_number,
449                                              p_v_teach_cal_type, p_n_teach_ci_sequence_number)
450       LOOP
451          l_b_override_ret := TRUE;
452          -- Compare the Effective Date parameter against each of the Date Alias values fetched
453          IF TRUNC(rec_tp_ovrd_ret.dai_alias_val) <= TRUNC(p_d_effective_date) THEN
454 
455             l_n_ret_percent := rec_tp_ovrd_ret.ret_percentage;
456             l_n_ret_amount  := rec_tp_ovrd_ret.ret_amount;
457          ELSE
458             -- If the Effective Date falls before the Date Alias value, then exit loop
459             EXIT;
460          END IF;
461       END LOOP;
462 
466          FOR rec_tp_ret IN cur_tp_ret(p_v_teach_cal_type, p_n_teach_ci_sequence_number)
463       -- If the Retention Schedules were not overridden at the FTCI level, then fetch the schedules from
464       -- the Teaching Period level and calculate the retention amount.
465       IF NOT l_b_override_ret THEN
467          LOOP
468             -- Compare the Effective Date parameter against each of the Date Alias values fetched
469             IF TRUNC(rec_tp_ret.dai_alias_val) <= TRUNC(p_d_effective_date) THEN
470                l_n_ret_percent := rec_tp_ret.ret_percentage;
471                l_n_ret_amount  := rec_tp_ret.ret_amount;
472             ELSE
473                -- If the Effective Date falls before the Date Alias value, then exit loop
474                EXIT;
475             END IF;
476          END LOOP;
477       END IF;
478 
479       IF l_n_ret_amount IS NOT NULL THEN
480           l_n_amount := l_n_ret_amount;
481       ELSIF l_n_ret_percent IS NOT NULL THEN
482           l_n_amount := ABS(p_n_diff_amount) * (l_n_ret_percent/100);
483       END IF;
484 
485       RETURN l_n_amount;
486 
487   END get_teach_retention;
488 
489 
490   FUNCTION get_fee_retention_amount(p_v_fee_cat                IN igs_fi_fee_ret_schd.fee_cat%TYPE,
491                                     p_v_fee_cal_type           IN igs_fi_fee_ret_schd.fee_cal_type%TYPE,
492                                     p_n_fee_ci_sequence_number IN igs_fi_fee_ret_schd.fee_ci_sequence_number%TYPE,
493                                     p_v_fee_type               IN igs_fi_fee_ret_schd.fee_type%TYPE,
494                                     p_n_diff_amount            IN NUMBER) RETURN NUMBER IS
495   /**************************************************************************
496     Created By     :  Priya Athipatla
497     Date Created By:  03-Sep-2004
498     Purpose        :  Function to determine Retention Amount when Retention Level
499                       is set to Fee Period
500     Known limitations,enhancements,remarks:
501 
502     Change History
503     Who         When            What
504    **************************************************************************/
505 
506    -- Select retention records for the specified FTCI and Fee Cat
507    -- This cursor will be used for non-Special Fee Types
508    CURSOR cur_fee_ret(cp_v_fee_type        igs_fi_fee_ret_schd.fee_type%TYPE,
509                       cp_v_fee_cal_type    igs_fi_fee_ret_schd.fee_cal_type%TYPE,
510                       cp_n_fee_ci_seq_num  igs_fi_fee_ret_schd.fee_ci_sequence_number%TYPE,
511                       cp_v_fee_cat         igs_fi_fee_ret_schd.fee_cat%TYPE) IS
512      SELECT retention_percentage,
513             retention_amount
514      FROM igs_fi_fee_ret_schd_f_type_v
515      WHERE fee_type             = cp_v_fee_type
516      AND fee_cal_type           = cp_v_fee_cal_type
517      AND fee_ci_sequence_number = cp_n_fee_ci_seq_num
518      AND ( (fee_cat = cp_v_fee_cat) OR (fee_cat IS NULL) )
519      AND ( (TRUNC(SYSDATE) >= TRUNC(start_dt)) OR (start_dt IS NULL) )
520      AND ( (TRUNC(SYSDATE) <= TRUNC(end_dt)) OR (end_dt IS NULL) )
521      ORDER BY start_dt;
522 
523    -- Cursor to select retention records for Special Fee Types
524    CURSOR cur_ret_special(cp_v_fee_type               igs_fi_fee_type.fee_type%TYPE,
525                           cp_v_fee_cal_type           igs_fi_f_typ_ca_inst.fee_cal_type%TYPE,
526                           cp_n_fee_ci_sequence_number igs_fi_f_typ_ca_inst.fee_ci_sequence_number%TYPE,
527                           cp_v_relation_ftci          VARCHAR2) IS
528      SELECT retention_percentage,
529             retention_amount
530      FROM  igs_fi_fee_ret_schd_v
531      WHERE fee_type               = cp_v_fee_type
532      AND   fee_cal_type           = cp_v_fee_cal_type
533      AND   fee_ci_sequence_number = cp_n_fee_ci_sequence_number
534      AND   s_relation_type        = cp_v_relation_ftci
535      AND   ( (TRUNC(SYSDATE) >= TRUNC(start_dt)) OR start_dt IS NULL)
536      AND   ( (TRUNC(SYSDATE) <= TRUNC(end_dt)) OR end_dt IS NULL)
537      ORDER BY start_dt;
538 
539    -- To determine System Fee Type of input Fee Type
540    CURSOR cur_fee_type(cp_v_fee_type    igs_fi_fee_type.fee_type%TYPE) IS
541      SELECT s_fee_type
542      FROM igs_fi_fee_type
543      WHERE fee_type = cp_v_fee_type;
544 
545    l_v_s_fee_type       igs_fi_fee_type.s_fee_type%TYPE := NULL;
546 
547    l_n_ret_amount       igs_fi_fee_ret_schd.retention_amount%TYPE := 0.0;
548    l_n_ret_percent      igs_fi_fee_ret_schd.retention_percentage%TYPE := 0.0;
549 
550    -- Retention Amount calculated
551    l_n_amount           NUMBER := 0.0;
552 
553   BEGIN
554 
555       -- If the Difference Amount is zero, then no Retention is applicable, return 0
556       IF (NVL(p_n_diff_amount,0) = 0) THEN
557          RETURN 0;
558       END IF;
559 
560       -- Determine System Fee Type
561       OPEN cur_fee_type(p_v_fee_type);
562       FETCH cur_fee_type INTO l_v_s_fee_type;
563       CLOSE cur_fee_type;
564 
565       IF l_v_s_fee_type = 'SPECIAL' THEN
566          -- For Special Fees, obtain the Retention Schedules
567          OPEN cur_ret_special(p_v_fee_type,
568                               p_v_fee_cal_type,
569                               p_n_fee_ci_sequence_number,
570                               'FTCI');
571          FETCH cur_ret_special INTO l_n_ret_percent, l_n_ret_amount;
572          CLOSE cur_ret_special;
573       ELSE
574          -- For all other System Fee Types, obtain the Retention Schedules
575          OPEN cur_fee_ret(p_v_fee_type,
576                           p_v_fee_cal_type,
577                           p_n_fee_ci_sequence_number,
578                           p_v_fee_cat);
579          FETCH cur_fee_ret INTO l_n_ret_percent, l_n_ret_amount;
580          CLOSE cur_fee_ret;
581       END IF;
582 
586           l_n_amount := ABS(p_n_diff_amount) * (l_n_ret_percent/100);
583       IF l_n_ret_amount IS NOT NULL THEN
584           l_n_amount := l_n_ret_amount;
585       ELSIF l_n_ret_percent IS NOT NULL THEN
587       END IF;
588 
589       RETURN l_n_amount;
590 
591   END get_fee_retention_amount;
592 
593 
594   FUNCTION get_complete_withdr_ret_amt( p_n_person_id                IN igs_en_su_attempt.person_id%TYPE,
595                                         p_v_course_cd                IN igs_en_su_attempt.course_cd%TYPE,
599                                         p_v_fee_type                 IN igs_fi_f_typ_ca_inst_all.fee_type%TYPE,
596                                         p_v_load_cal_type            IN igs_ca_inst.cal_type%TYPE,
597                                         p_n_load_ci_sequence_number  IN igs_ca_inst.sequence_number%TYPE,
598                                         p_n_diff_amount              IN NUMBER,
600                                         p_v_nonzero_billable_cp_flag  IN igs_fi_f_typ_ca_inst_all.nonzero_billable_cp_flag%TYPE ) RETURN NUMBER IS
601   /**************************************************************************
602     Created By     :  Priya Athipatla
603     Date Created By:  03-Sep-2004
604     Purpose        :  Function to determine the Retention Amount when the
605                       Complete Withdrawal Retention checkbox is checked.
606 
607     Process Flow:
608     1. If Diff Amount = 0, Return 0;
609     2. For each Unit Attempt of the student, verify if the Usec still incurs load.
610        2.1  If even one Unit Section incurs load, then no Retention is applicable.
611        2.2  If none of the Unit Sections incur load, then verify if all the
612             Unit sections were dropped in the 0% Retention Period.
613             ( Discontinued Date < Date Alias of the Earliest Retention Schedule)
614             2.2.1  If Usec is Non-Standard, compare against schedules defined at
615                    NS Unit Section level, not from Teaching Period schedules
616                    2.2.1.1  Usec + Fee Type level OR  Usec level OR  Institution level
617             2.2.2  If Standard Usec,
618                    2.2.2.1  If the Usec were dropped in the 0% Retention Period, then no
619                             Retention is applicable. Return 0.
620                    2.2.2.2  If the Usec were NOT dropped in the 0% Retention Period, then
621                             set local flag (l_b_zero_ret_drop) to TRUE. Apply 100% Retention.
622 
623     Known limitations,enhancements,remarks:
624 
625     Change History
626     Who         When            What
627     abshriva    17-May-2006     Bug 5113295 - Added call out to function chk_unit_prg_transfer in cur_unit_attmpt
628     bannamal   14-Apr-2005     Bug#4297359 ER Registration fee issue.
629                                 Added one more paramter in the function, p_v_nonzero_billable_cp_flag.
630                                 Modified the where clause of the cursor cur_unit_attmpt.
631                                Bug#4304524 Registration Fee Retention not working for the first date of Retention.
632                                 Modified the cursor cur_tp_ret
633    **************************************************************************/
634 
635    CURSOR cur_unit_attmpt(cp_n_person_id                igs_en_su_attempt.person_id%TYPE,
636                           cp_v_course_cd                igs_en_su_attempt.course_cd%TYPE,
637                           cp_v_load_cal_type            igs_ca_inst_all.cal_type%TYPE,
638                           cp_n_load_ci_seq_num          igs_ca_inst_all.sequence_number%TYPE,
639                           cp_v_nz_billable_cp_flag      igs_fi_f_typ_ca_inst_all.nonzero_billable_cp_flag%TYPE
640                           ) IS
644      WHERE sua.person_id = cp_n_person_id
641      SELECT sua.*, usec.non_std_usec_ind
642      FROM igs_en_su_attempt sua,
643           igs_ps_unit_ofr_opt usec
645      AND sua.course_cd = cp_v_course_cd
646      AND usec.uoo_id = sua.uoo_id
647      AND sua.unit_attempt_status NOT IN ('INVALID','DUPLICATE')
648      AND ( (NVL(cp_v_nz_billable_cp_flag,'N') = 'Y' AND igs_fi_prc_fee_ass.finpl_clc_sua_cp( sua.unit_cd,
649                                               sua.version_number,
650                                               sua.cal_type,
651                                               sua.ci_sequence_number,
652                                               cp_v_load_cal_type,
653                                               cp_n_load_ci_seq_num,
654                                               sua.override_enrolled_cp,
655                                               sua.override_eftsu,
656                                               sua.uoo_id,
657                                               sua.no_assessment_ind) <> 0)
658           OR NVL(cp_v_nz_billable_cp_flag,'N') = 'N' )
659      AND (igs_fi_gen_008.chk_unit_prg_transfer(sua.dcnt_reason_cd) = 'N');
660 
661    -- Cursor to fetch Retention Schedules defined at Teaching Period level
662    -- Also to filter based on the Discontinued Date.
663    CURSOR cur_tp_ret(cp_v_teach_cal_type    igs_fi_tp_ret_schd.teach_cal_type%TYPE,
664                      cp_n_teach_ci_seq_num  igs_fi_tp_ret_schd.teach_ci_sequence_number%TYPE,
665                      cp_d_disc_dt           igs_en_su_attempt.discontinued_dt%TYPE) IS
666      SELECT 'X'
667      FROM igs_fi_tp_ret_schd_v
668      WHERE teach_cal_type = cp_v_teach_cal_type
669      AND teach_ci_sequence_number = cp_n_teach_ci_seq_num
670      AND fee_type IS NULL
671      AND fee_cal_type IS NULL
672      AND fee_ci_sequence_number IS NULL
673      AND TRUNC(dai_alias_val) <= TRUNC(cp_d_disc_dt);
674 
675    -- Cursor to fetch retention schedules defined at Unit Section + Fee Type level
676    CURSOR cur_ns_ft_ret(cp_n_uoo_id    igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
677                         cp_v_fee_type  igs_fi_fee_type.fee_type%TYPE) IS
678      SELECT dtl.offset_date
679      FROM igs_ps_nsus_rtn_dtl dtl,
680           igs_ps_nsus_rtn rtn
681      WHERE rtn.non_std_usec_rtn_id = dtl.non_std_usec_rtn_id
682      AND rtn.uoo_id = cp_n_uoo_id
683      AND rtn.fee_type = cp_v_fee_type
684      ORDER BY dtl.offset_date;
685 
686    -- Cursor to fetch retention schedules defined at Unit Section level.
687    -- This cursor is used when cur_ns_ft_ret does not find any rows
691           igs_ps_nsus_rtn rtn
688    CURSOR cur_ns_usec_ret(cp_n_uoo_id    igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
689      SELECT dtl.offset_date
690      FROM igs_ps_nsus_rtn_dtl dtl,
692      WHERE rtn.non_std_usec_rtn_id = dtl.non_std_usec_rtn_id
693      AND rtn.uoo_id = cp_n_uoo_id
694      AND rtn.fee_type IS NULL
695      ORDER BY dtl.offset_date;
696 
697    -- Cursor to fetch retention schedules defined at Institution level.
698    -- Used if cur_ns_ft_ret and cur_ns_usec_ret both do not return any rows
699    CURSOR cur_ns_inst_ret(cp_n_uoo_id    igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
700      SELECT igs_ps_gen_004.f_retention_offset_date(cp_n_uoo_id,
701                                                       rtn.formula_method,
702                                                       rtn.round_method,
703                                                       rtn.incl_wkend_duration_flag,
704                                                       dtl.offset_value) offset_date
705      FROM igs_ps_nsus_rtn_dtl dtl,
706           igs_ps_nsus_rtn rtn
707      WHERE rtn.non_std_usec_rtn_id = dtl.non_std_usec_rtn_id
708      AND rtn.uoo_id IS NULL
709      AND rtn.fee_type IS NULL
710      ORDER BY offset_date;
711 
712    -- Variable to indicate whether or not load is incurred. Y = Incurred, N = Not Incurred.
713    l_v_load_apply   VARCHAR2(1) := NULL;
714    l_v_rec_exists   VARCHAR2(1) := NULL;
715 
716    -- Variable to indicate whether retention is 0 or Full Amount
717    l_b_zero_ret_drop  BOOLEAN := FALSE;
718 
719    -- Local variable to indicate whether Retention Schedules have been found
720    -- at the (Non Standard Unit Section + Fee Type) level
721    l_b_ft_ret_found   BOOLEAN := FALSE;
722 
723    -- Local variable to indicate whether Retention Schedules have been found
724    -- at the Non Standard Unit Section level
725    l_b_usec_ret_found  BOOLEAN := FALSE;
726 
727 
728   BEGIN
729 
730       -- If the Difference Amount is zero, then no Retention is applicable, return 0
731       IF (NVL(p_n_diff_amount,0) = 0) THEN
732          RETURN 0;
733       END IF;
734 
735       -- Loop through all the Unit Attempts for the person and determine if load is incurred
736       FOR rec_unit_attmpt IN cur_unit_attmpt(p_n_person_id, p_v_course_cd,p_v_load_cal_type,p_n_load_ci_sequence_number,p_v_nonzero_billable_cp_flag)
737       LOOP
738          l_v_load_apply := igs_en_prc_load.enrp_get_load_apply(p_teach_cal_type              => rec_unit_attmpt.cal_type,
739                                                                p_teach_sequence_number       => rec_unit_attmpt.ci_sequence_number,
740                                                                p_discontinued_dt             => rec_unit_attmpt.discontinued_dt,
741                                                                p_administrative_unit_status  => rec_unit_attmpt.administrative_unit_status,
742                                                                p_unit_attempt_status         => rec_unit_attmpt.unit_attempt_status,
743                                                                p_no_assessment_ind           => rec_unit_attmpt.no_assessment_ind,
744                                                                p_load_cal_type               => p_v_load_cal_type,
745                                                                p_load_sequence_number        => p_n_load_ci_sequence_number,
746                                                                p_include_audit               => rec_unit_attmpt.no_assessment_ind);
747          -- If even one unit attempt incurs load, then no retention is applicable, return 0.
748          IF (l_v_load_apply = 'Y') THEN
749              EXIT;
750          END IF;
751 
752          IF rec_unit_attmpt.non_std_usec_ind = 'Y' THEN
753 
754             -- For Non-Standard Unit Sections
755             -- If load is not incurred, check the Discontinued Date against the Retention Date Alias defined at Usec level
756             -- Fetch Retention Schedules defined at Unit Section + Fee Type level
757             FOR rec_ns_ft_ret IN cur_ns_ft_ret(rec_unit_attmpt.uoo_id, p_v_fee_type)
758             LOOP
759                 l_b_ft_ret_found := TRUE;
760                 IF TRUNC(rec_unit_attmpt.discontinued_dt) > TRUNC(rec_ns_ft_ret.offset_date) THEN
761                     -- Unit Section was dropped AFTER the 0% Retention Period
762                     l_b_zero_ret_drop := TRUE;
763                 END IF;
764                 -- Exit since we check only for the earliest Retention Schedule,i.e. only the first record
765                 EXIT;
766             END LOOP;
767 
768             -- Fetch Retention Schedules defined at Unit Section level. This is done only
769             -- if the schedules were not defined at the US + Fee Type level.
770             IF (l_b_ft_ret_found = FALSE) THEN
771                 FOR rec_ns_usec_ret IN cur_ns_usec_ret(rec_unit_attmpt.uoo_id)
772                 LOOP
773                     l_b_usec_ret_found := TRUE;
774                     IF TRUNC(rec_unit_attmpt.discontinued_dt) > TRUNC(rec_ns_usec_ret.offset_date) THEN
775                          -- Unit Section was dropped AFTER the 0% Retention Period
776                          l_b_zero_ret_drop := TRUE;
777                     END IF;
778                     EXIT;
779                 END LOOP;
780             END IF;
781 
782             -- Fetch Retention Schedules defined at Institution level. Done only if the schedules
783             -- were not defined at (US + Fee Type) or at US level
784             IF (l_b_ft_ret_found = FALSE AND l_b_usec_ret_found = FALSE) THEN
785                 FOR rec_ns_inst_ret IN cur_ns_inst_ret(rec_unit_attmpt.uoo_id)
786                 LOOP
787                     IF TRUNC(rec_unit_attmpt.discontinued_dt) > TRUNC(rec_ns_inst_ret.offset_date) THEN
788                          -- Unit Section was dropped AFTER the 0% Retention Period
789                          l_b_zero_ret_drop := TRUE;
790                     END IF;
791                     EXIT;
795          ELSE  -- rec_unit_attmpt.non_std_usec_ind <> 'Y'
792                 END LOOP;
793             END IF;
794 
796 
797             -- For Standard Unit Sections
798             -- If load is not incurred, check the Discontinued Date against the Retention Date Alias (done in cursor cur_tp_ret)
799             OPEN cur_tp_ret(rec_unit_attmpt.cal_type,
800                             rec_unit_attmpt.ci_sequence_number,
801                             rec_unit_attmpt.discontinued_dt);
802             FETCH cur_tp_ret INTO l_v_rec_exists;
803             IF cur_tp_ret%FOUND THEN
804                -- Unit Section does not incur load and was dropped AFTER the 0% Retention Period
805                l_b_zero_ret_drop := TRUE;
806             END IF;
807             CLOSE cur_tp_ret;
808 
809          END IF;  -- End if for rec_unit_attmpt.non_std_usec_ind = 'Y'
810 
811       END LOOP;  -- End of loop across all Unit Attempts of the Person
812 
813       IF l_v_load_apply = 'Y' THEN
814          RETURN 0.0;
815       END IF;
816 
817       -- Check for the zero retention flag
818       IF l_b_zero_ret_drop THEN
819          -- If no unit sections have incurred load and were
820          -- dropped after the 0% Retention Period, then apply 100% retention
821          RETURN ABS(p_n_diff_amount);
822       ELSE
823          -- If atleast one unit section incurs load or the unit sections were all
824          -- dropped BEFORE the 0% Retention Period ended, Retention = 0
825          RETURN 0;
826       END IF;
827 
828   END get_complete_withdr_ret_amt;
829 
830   FUNCTION get_ns_usec_retention(p_n_uoo_id            IN igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
831                                  p_v_fee_type          IN igs_fi_fee_type.fee_type%TYPE,
832                                  p_d_effective_date    IN DATE,
833                                  p_n_diff_amount       IN NUMBER) RETURN NUMBER IS
834   /**************************************************************************
835     Created By     :  Priya Athipatla
836     Date Created By:  03-Sep-2004
837     Purpose        :  Function to determine the Retention Amount for a
838                       Non-Standard Unit Section
839     Known limitations,enhancements,remarks:
840 
841     Change History
842     Who         When            What
843    **************************************************************************/
844    -- Definition of a pl/sql table to hold the Retention details for a NS Unit Section
845    TYPE ns_usec_retention_rec IS RECORD ( offset_date        DATE,
846                                           retention_amount   NUMBER,
847                                           retention_percent  NUMBER);
848    TYPE ns_usec_retention_tbl_typ IS TABLE OF  ns_usec_retention_rec  INDEX BY BINARY_INTEGER;
849    ns_usec_retention_tbl   ns_usec_retention_tbl_typ;
850 
851    -- Cursor to fetch retention schedules defined at Unit Section + Fee Type level
852    CURSOR cur_ns_ft_ret(cp_n_uoo_id    igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
853                         cp_v_fee_type  igs_fi_fee_type.fee_type%TYPE) IS
854      SELECT dtl.offset_date,
855             dtl.retention_amount,
856             dtl.retention_percent
857      FROM igs_ps_nsus_rtn_dtl dtl,
858           igs_ps_nsus_rtn rtn
859      WHERE rtn.non_std_usec_rtn_id = dtl.non_std_usec_rtn_id
860      AND rtn.uoo_id = cp_n_uoo_id
861      AND rtn.fee_type = cp_v_fee_type
862      ORDER BY offset_date;
863 
864    -- Cursor to fetch retention schedules defined at Unit Section level.
865    -- This cursor is used when cur_ns_ft_ret does not find any rows
866    CURSOR cur_ns_usec_ret(cp_n_uoo_id    igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
867      SELECT dtl.offset_date,
868             dtl.retention_amount,
869             dtl.retention_percent
870      FROM igs_ps_nsus_rtn_dtl dtl,
871           igs_ps_nsus_rtn rtn
872      WHERE rtn.non_std_usec_rtn_id = dtl.non_std_usec_rtn_id
873      AND rtn.uoo_id = cp_n_uoo_id
874      AND rtn.fee_type IS NULL
875      ORDER BY offset_date;
876 
877    -- Cursor to fetch retention schedules defined at Institution level.
878    -- Used if cur_ns_ft_ret and cur_ns_usec_ret both do not return any rows
879    CURSOR cur_ns_inst_ret(cp_n_uoo_id    igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
880      SELECT dtl.retention_amount,
881             dtl.retention_percent,
882             igs_ps_gen_004.f_retention_offset_date(cp_n_uoo_id,
883                                                    rtn.formula_method,
884                                                    rtn.round_method,
885                                                    rtn.incl_wkend_duration_flag,
886                                                    dtl.offset_value) offset_date
887     FROM igs_ps_nsus_rtn_dtl dtl,
888          igs_ps_nsus_rtn rtn
889     WHERE rtn.non_std_usec_rtn_id = dtl.non_std_usec_rtn_id
890     AND rtn.uoo_id IS NULL
891     AND rtn.fee_type IS NULL
892     ORDER BY offset_date;
893 
894    l_n_cntr    NUMBER := 0;
895 
896    -- Local variable to indicate whether Retention Schedules have been found
897    -- at the (Non Standard Unit Section + Fee Type) level or Unit Section level
898    -- or at the Institution level
899    l_b_ret_found   BOOLEAN := FALSE;
900 
901    l_n_ret_amount       igs_ps_nsus_rtn_dtl.retention_amount%TYPE := 0;
902    l_n_ret_percent      igs_ps_nsus_rtn_dtl.retention_percent%TYPE := 0;
903    l_n_amount           NUMBER := 0.0;
904 
905   BEGIN
906 
907      -- Initialize the pl/sql table
908      ns_usec_retention_tbl.DELETE;
909 
910      -- Fetch Retention Schedules defined at Unit Section + Fee Type level
911      FOR rec_ns_ft_ret IN cur_ns_ft_ret(p_n_uoo_id, p_v_fee_type)
912      LOOP
913         l_b_ret_found := TRUE;
914         l_n_cntr := l_n_cntr + 1;
918      END LOOP;
915         ns_usec_retention_tbl(l_n_cntr).offset_date        := rec_ns_ft_ret.offset_date;
916         ns_usec_retention_tbl(l_n_cntr).retention_amount   := rec_ns_ft_ret.retention_amount;
917         ns_usec_retention_tbl(l_n_cntr).retention_percent  := rec_ns_ft_ret.retention_percent;
919 
920      -- Fetch Retention Schedules defined at Unit Section level. This is done only
921      -- if the schedules were not defined at the US + Fee Type level.
922      IF l_b_ret_found = FALSE THEN
923         FOR rec_ns_usec_ret IN cur_ns_usec_ret(p_n_uoo_id)
924         LOOP
925            l_b_ret_found := TRUE;
926            l_n_cntr := l_n_cntr + 1;
927            ns_usec_retention_tbl(l_n_cntr).offset_date        := rec_ns_usec_ret.offset_date;
928            ns_usec_retention_tbl(l_n_cntr).retention_amount   := rec_ns_usec_ret.retention_amount;
929            ns_usec_retention_tbl(l_n_cntr).retention_percent  := rec_ns_usec_ret.retention_percent;
930         END LOOP;
931      END IF;
932 
933      -- Fetch Retention Schedules defined at Institution level. Done only if the schedules
934      -- were not defined at (US + Fee Type) or at US level
935      IF (l_b_ret_found = FALSE) THEN
936         FOR rec_ns_inst_ret IN cur_ns_inst_ret(p_n_uoo_id)
937         LOOP
938            l_n_cntr := l_n_cntr + 1;
939            ns_usec_retention_tbl(l_n_cntr).offset_date        := rec_ns_inst_ret.offset_date;
940            ns_usec_retention_tbl(l_n_cntr).retention_amount   := rec_ns_inst_ret.retention_amount;
941            ns_usec_retention_tbl(l_n_cntr).retention_percent  := rec_ns_inst_ret.retention_percent;
942         END LOOP;
943      END IF;
944 
945      -- Loop across records of the pl/sql table
946      IF (ns_usec_retention_tbl.COUNT > 0) THEN
947         FOR i IN ns_usec_retention_tbl.FIRST..ns_usec_retention_tbl.LAST
948         LOOP
949            IF ns_usec_retention_tbl.EXISTS(i) THEN
950               -- If Effective Date falls beyond the Offset Date, apply retention
951               IF TRUNC(p_d_effective_date) >= TRUNC(ns_usec_retention_tbl(i).offset_date)  THEN
952                  l_n_ret_percent := ns_usec_retention_tbl(i).retention_percent;
953                  l_n_ret_amount  := ns_usec_retention_tbl(i).retention_amount;
954               ELSE
955                  -- If the Effective Date falls before the Offset Date value, then exit loop
956                  EXIT;
957               END IF;
958            END IF; -- End if for ns_usec_retention_tbl.EXISTS(i)
959         END LOOP; -- End loop for looping across all records in the pl/sql table
960 
961         -- Determine the Retention Amount
962         IF l_n_ret_amount IS NOT NULL THEN
963             l_n_amount := l_n_ret_amount;
964         ELSIF l_n_ret_percent IS NOT NULL THEN
965             l_n_amount := ABS(p_n_diff_amount) * (l_n_ret_percent/100);
966         END IF; -- End if for l_n_ret_amount IS NOT NULL
967 
968      END IF;  -- End if for ns_usec_retention_tbl.COUNT > 0
969 
970      RETURN l_n_amount;
971 
972   END get_ns_usec_retention;
973 
974 
975   FUNCTION get_special_retention_amt(p_n_uoo_id                  IN igs_ps_unit_ofr_opt_all.uoo_id%TYPE,
976                                      p_v_fee_cal_type            IN igs_fi_f_typ_ca_inst_all.fee_cal_type%TYPE,
977                                      p_n_fee_ci_sequence_number  IN igs_fi_f_typ_ca_inst_all.fee_ci_sequence_number%TYPE,
978                                      p_v_fee_type                IN igs_fi_f_typ_ca_inst_all.fee_type%TYPE,
979                                      p_d_effective_date          IN DATE,
980                                      p_n_diff_amount             IN NUMBER) RETURN NUMBER IS
981   /**************************************************************************
982     Created By     :  Priya Athipatla
983     Date Created By:  08-Sep-2004
984     Purpose        :  Function to determine the Retention Amount for Special Fees
985     Known limitations,enhancements,remarks:
986 
987     Change History
988     Who         When            What
989    **************************************************************************/
990 
991    -- Cursor to determine if a given Unit Section is Non-Standard
992    CURSOR cur_non_std_usec(cp_n_uoo_id   igs_ps_unit_ofr_opt_all.uoo_id%TYPE) IS
993      SELECT cal_type,
994             ci_sequence_number,
995             non_std_usec_ind
996      FROM igs_ps_unit_ofr_opt
997      WHERE uoo_id = cp_n_uoo_id;
998 
999    rec_non_std_usec          cur_non_std_usec%ROWTYPE;
1000    l_n_retention_amount      NUMBER := 0.0;
1001 
1002    BEGIN
1003 
1004      OPEN cur_non_std_usec(p_n_uoo_id);
1005      FETCH cur_non_std_usec INTO rec_non_std_usec;
1006      CLOSE cur_non_std_usec;
1007 
1008      IF (rec_non_std_usec.non_std_usec_ind = 'Y') THEN
1009           l_n_retention_amount := get_ns_usec_retention(p_n_uoo_id         => p_n_uoo_id,
1010                                                         p_v_fee_type       => p_v_fee_type,
1011                                                         p_d_effective_date => p_d_effective_date,
1012                                                         p_n_diff_amount    => p_n_diff_amount);
1013          RETURN l_n_retention_amount;
1014      ELSE
1015           l_n_retention_amount := get_teach_retention(p_v_fee_cal_type             => p_v_fee_cal_type,
1016                                                       p_n_fee_ci_sequence_number   => p_n_fee_ci_sequence_number,
1017                                                       p_v_fee_type                 => p_v_fee_type,
1018                                                       p_v_teach_cal_type           => rec_non_std_usec.cal_type,
1019                                                       p_n_teach_ci_sequence_number => rec_non_std_usec.ci_sequence_number,
1020                                                       p_d_effective_date           => p_d_effective_date,
1021                                                       p_n_diff_amount              => p_n_diff_amount);
1025    END get_special_retention_amt;
1022          RETURN l_n_retention_amount;
1023      END IF;
1024 
1026 
1027 FUNCTION get_std_balance(p_partyid  IN igs_fi_balances.party_id%TYPE) RETURN NUMBER AS
1028 
1029 /***************************************************************************
1030   ||  Created By : svuppala
1031   ||  Created On : 10-Apr-2002
1032   ||  Purpose :  New PLSQL function which will return the latest standard
1033   ||             balance for the student for the personid provided as input to it
1034   ||
1035   ||  Known limitations, enhancements or remarks :
1036   ||  Change History :
1037   ||  Who             When            What
1038   ||  (reverse chronological order - newest change first)
1039  ******************************************************************************/
1040 
1041 -- Cursor for fetching the standard balance for the partyid passed as input to the function
1042   CURSOR cur_partyid(cp_partyid  NUMBER) IS
1043      SELECT standard_balance
1044      FROM   igs_fi_balances
1045      WHERE  party_id = cp_partyid
1046      ORDER BY balance_date DESC;
1047 
1048   l_std_balance  igs_fi_balances.standard_balance%TYPE;
1049 
1050  BEGIN
1051 
1052 -- Fetch the standard Balance
1053     OPEN cur_partyid(p_partyid);
1054     FETCH cur_partyid INTO l_std_balance;
1055     IF cur_partyid%NOTFOUND THEN
1056       l_std_balance := 0;
1057     END IF;
1058     CLOSE cur_partyid;
1059 
1060 -- Return the value for the l_std_balance
1061   RETURN l_std_balance;
1062 
1063 END get_std_balance;
1064 
1065 PROCEDURE chk_spa_rec_exists(p_n_person_id      IN  igs_en_stdnt_ps_att.person_id%TYPE,
1066                              p_v_course_cd      IN  igs_en_stdnt_ps_att.course_cd%TYPE,
1067                              p_v_load_cal_type  IN  igs_ca_inst.cal_type%TYPE,
1068 			     p_n_load_ci_seq    IN  igs_ca_inst.sequence_number%TYPE,
1069 			     p_v_fee_cat        IN  igs_fi_fee_cat.fee_cat%TYPE,
1070 			     p_v_status         OUT NOCOPY VARCHAR2,
1071 			     p_v_message        OUT NOCOPY VARCHAR2) AS
1072   /***********************************************************************************************
1073     Created By     :  Amit Gairola
1074     Date Created By:  27-Sep-2005
1075     Purpose        :  Procedure to check if a term record exists
1076 
1077     Known limitations,enhancements,remarks:
1078     Change History
1079     Who         When            What
1080   ***********************************************************************************************/
1081 
1082 -- Cursor for checking if the Charge exists
1083   CURSOR cur_chg(cp_n_person_id      igs_en_stdnt_ps_att.person_id%TYPE,
1084                  cp_v_course_cd      igs_en_stdnt_ps_att.course_cd%TYPE,
1085 	         cp_v_fee_cal_type   igs_ca_inst.cal_type%TYPE,
1086 	         cp_n_fee_ci_seq     igs_ca_inst.sequence_number%TYPE) IS
1087     SELECT 'x'
1088     FROM   igs_fi_fee_as_all
1089     WHERE  person_id = cp_n_person_id
1090     AND    ((course_cd = cp_v_course_cd OR course_cd IS NULL))
1091     AND    fee_cal_type = cp_v_fee_cal_type
1092     AND    fee_ci_sequence_number = cp_n_fee_ci_seq
1093     AND    s_transaction_type = 'ASSESSMENT';
1094 
1095 -- Cursor for checking if Contract Rates exist
1096   CURSOR cur_cntrct_rates(cp_n_person_id     igs_en_stdnt_ps_att.person_id%TYPE,
1097                           cp_v_course_cd     igs_en_stdnt_ps_att.course_cd%TYPE,
1098 			  cp_v_fee_cat       igs_fi_fee_cat.fee_cat%TYPE) IS
1099     SELECT 'x'
1100     FROM igs_fi_f_cat_fee_lbl_all lbl,
1101          igs_fi_fee_as_rt rt
1102     WHERE lbl.fee_type = rt.fee_type
1103     AND   rt.person_id = cp_n_person_id
1104     AND   rt.course_cd = cp_v_course_cd
1105     AND   lbl.fee_cat =  cp_v_fee_cat
1106     AND TRUNC(SYSDATE) BETWEEN TRUNC(rt.start_dt) AND TRUNC(NVL(rt.end_dt,SYSDATE));
1107 
1108     l_b_bool                BOOLEAN;
1109     l_v_chr                 VARCHAR2(1);
1110     l_v_fee_cal_type        igs_ca_inst.cal_type%TYPE;
1111     l_n_fee_ci_seq          igs_ca_inst.sequence_number%TYPE;
1112 
1113 
1114 BEGIN
1115   p_v_status := 'N';
1116   p_v_message := NULL;
1117 
1118 -- Cursor for checking if any of the mandatory parameters are Null
1119   IF p_n_person_id IS NULL OR
1120      p_v_course_cd IS NULL OR
1121      p_v_load_cal_type IS NULL OR
1122      p_n_load_ci_seq IS NULL THEN
1123     p_v_status := 'Y';
1124     p_v_message := 'IGS_GE_INSUFFICIENT_PARAMETER';
1125   END IF;
1126 
1127 -- Derive the Fee Calendar
1128   l_b_bool := igs_fi_gen_001.finp_get_lfci_reln(p_cal_type                 => p_v_load_cal_type,
1129                                                 p_ci_sequence_number       => p_n_load_ci_seq,
1130                                                 p_cal_category             => 'LOAD',
1131                                                 p_ret_cal_type             => l_v_fee_cal_type,
1132                                                 p_ret_ci_sequence_number   => l_n_fee_ci_seq,
1133                                                 p_message_name             => p_v_message);
1134 
1135 
1136   IF NOT l_b_bool THEN
1137     p_v_status := 'N';
1138     RETURN;
1139   END IF;
1140 
1141 -- Check if a Fee Assessment record exists
1142   OPEN cur_chg(p_n_person_id,
1143                p_v_course_cd,
1144 	       l_v_fee_cal_type,
1145 	       l_n_fee_ci_seq);
1146   FETCH cur_chg INTO l_v_chr;
1147   IF cur_chg%FOUND THEN
1148     p_v_status := 'Y';
1149     p_v_message := 'IGS_GE_RECORD_ALREADY_EXISTS';
1150   END IF;
1151   CLOSE cur_chg;
1152 
1153   IF p_v_status = 'Y' THEN
1154     RETURN;
1155   END IF;
1156 
1157 -- Check if a Contract Fee Rate exists
1158   OPEN cur_cntrct_rates(p_n_person_id,
1159                         p_v_course_cd,
1160                         p_v_fee_cat);
1161   FETCH cur_cntrct_rates INTO l_v_chr;
1162   IF cur_cntrct_rates%FOUND THEN
1163     p_v_status := 'Y';
1164     p_v_message := 'IGS_GE_RECORD_ALREADY_EXISTS';
1165   END IF;
1166   CLOSE cur_cntrct_rates;
1167 
1168   RETURN;
1169 
1170 END chk_spa_rec_exists;
1171 
1172 
1173 FUNCTION mask_card_number( p_credit_card IN VARCHAR2 )  RETURN VARCHAR2
1174   IS
1175   /***********************************************************************************************
1176     Created By     :  Umesh Udayaprakash
1177     Date Created By:  10/7/2005
1178     Purpose        :  Function to Mask the Credit card Number
1179 
1180     Known limitations,enhancements,remarks:
1181     Change History
1182     Who         When            What
1183     uudayapr   8-Oct-2005   BUG 4660773 Added the Function mask_card_number for masking the CC Number
1184   ***********************************************************************************************/
1185 CURSOR cur_mask_card IS
1186     SELECT DECODE(  NVL(FND_PROFILE.VALUE('IGS_FI_MASK_CREDIT_CARD_NUMBERS'),'F'),
1187              'N', p_credit_card,
1188              'F', RPAD( SUBSTR(p_credit_card,1,4),LENGTH(p_credit_card),'*'),
1189              'L', LPAD( SUBSTR(p_credit_card,-4),LENGTH(p_credit_card),'*')
1190                 )
1191     FROM dual;
1192     l_v_masked_card_num  IGS_FI_CREDITS_ALL.CREDIT_CARD_NUMBER%TYPE;
1193 BEGIN
1194    OPEN cur_mask_card;
1195    FETCH cur_mask_card INTO l_v_masked_card_num;
1196    CLOSE cur_mask_card;
1197    RETURN l_v_masked_card_num;
1198 END Mask_Card_Number;
1199 
1200   -- Function to check if the Unit in context (UOO_ID) has been part of a Program Transfer or not.
1201   -- Returns Y or N
1202   FUNCTION chk_unit_prg_transfer(p_v_disc_reason_code  IN igs_en_dcnt_reasoncd.discontinuation_reason_cd%TYPE) RETURN VARCHAR2 AS
1203   /***********************************************************************************************
1204     Created By     :  abshriva
1205     Date Created   :  17-May-2006
1206     Purpose        :  Fuction to check if the unit dropped was due to program transfer or not.
1207 
1208     Known limitations,enhancements,remarks:
1209     Change History
1210     Who         When            What
1211   ***********************************************************************************************/
1212 
1213    -- Cursor to find out if the unit has been dropped due to a Program Transfer, in which case Retention
1214    -- calculation needs to be skipped for the unit drop.
1215    CURSOR cur_chk_transfer(cp_v_disc_reason_cd  igs_en_dcnt_reasoncd.discontinuation_reason_cd%TYPE) IS
1216      SELECT 'x'
1217      FROM igs_en_dcnt_reasoncd
1218      WHERE s_discontinuation_reason_type = 'UNIT_TRANS'
1219      AND discontinuation_reason_cd = cp_v_disc_reason_cd;
1220 
1221    l_v_transferred   VARCHAR2(1);
1222 
1223    BEGIN
1224 
1225        OPEN cur_chk_transfer(p_v_disc_reason_code);
1226        FETCH cur_chk_transfer INTO l_v_transferred;
1227        -- If cursor found, return Y - this will skip retention from Fee Assessment/Special fees
1228        IF cur_chk_transfer%FOUND THEN
1229           l_v_transferred := 'Y';
1230        ELSE
1231           l_v_transferred := 'N';
1232        END IF;
1233 
1234        RETURN l_v_transferred;
1235 
1236    END chk_unit_prg_transfer;
1237 
1238 
1239 END igs_fi_gen_008;