DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGF_DB_DL_DISB_ORIG

Source


1 PACKAGE BODY igf_db_dl_disb_orig AS
2 /* $Header: IGFDB02B.pls 120.1 2006/02/01 02:41:33 ridas noship $ */
3 
4 
5   /*************************************************************
6    Created By : prchandr
7    Date Created On : 2000/12/13
8    Purpose : Direct Loan Disbursement Origination Process
9    Know limitations, enhancements or remarks
10    Change History
11    Who             When            What
12   (reverse chronological order - newest change first)
13   ayedubat        20-OCT-2004     FA 149 COD-XML Standards build bug # 3416863
14                                   Replaced the reference of igf_db_awd_disb_dtl with igf_aw_db_chg_dtls table
15                                   Changed the logic as per the TD, FA149_TD_COD_XML_i1a.doc
16   veramach        29-Jan-2004     bug 3408092 added 2004-2005 in p_dl_version checks
17   ugummall        23-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
18                                   Modified the cursor cur_disb_dtl to include the clause which
19                                   filter only the loans having the school id matched with parameter p_school_code.
20   ugummall        17-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
21                                   1. Added two new parameters to disb_originate process.
22                                   2. Hence added one parameter to Trans_Rec internal procedure
23                                      which is being called from disb_originate process.
24   sjadhav         28-Mar-2003     Bug 2863960
25                                   Added cursor cur_get_prev_date
26                                   Added clause for reading date
27                                   adjustment records into file
28 
29   vvutukur        21-Feb-2003     Enh#2758823.FA117 Build. Modified procedure Trans_Rec.
30   ***************************************************************/
31 
32 -- ## Forward Declaration of Trans_rec Procedure
33 
34 lv_data_record    VARCHAR2(4000);   --  ##  Variable to store the concatenated value to be stored in file ##
35 
36 PROCEDURE Trans_Rec( p_dl_version             igf_lookups_view.lookup_code%TYPE,
37                      p_dl_batch_id            igf_sl_dl_batch.batch_id%TYPE,
38                      p_Rec_count              IN OUT NOCOPY   NUMBER,
39                      p_ci_cal_type            igf_sl_dl_setup.ci_cal_type%TYPE,
40                      p_ci_sequence_number     igf_sl_dl_setup.ci_sequence_number%TYPE,
41                      p_school_code          IN    VARCHAR2
42                     );
43 
44 PROCEDURE disb_originate(errbuf      OUT NOCOPY    VARCHAR2,
45                          retcode      OUT NOCOPY     NUMBER,
46                          p_award_year     VARCHAR2,
47                          p_org_id     IN  NUMBER,
48                          school_type   IN    VARCHAR2,
49                          p_school_code IN    VARCHAR2
50                         )
51 AS
52   /*************************************************************
53    Created By : prchandr
54   Date Created On : 2000/12/13
55   Purpose : Main Procedure for the Direct Loan disbursement process
56   Know limitations, enhancements or remarks
57   Who             When            What
58   ugummall        23-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
59                                   Modified the cursor cur_disb_dtl to include the clause which
60                                   filter only the loans having the school id matched with parameter p_school_code.
61   ugummall        17-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
62                                   1. Added two new parameters
63                                   2. p_school_code parameter is passed as extra parameter to
64                                      procedures igf_sl_dl_record.DLHeader_cur and Trans_Rec.
65                                   3. Logic is changed so that header and trailer are written to the
66                                      output file only when at least one record is processed.
67   Bug :2383350 Loan Cancellation
68   Who             When            What
69   mesriniv      4-jun-2002      Removed SF_STATUS <> 'E' check in the two cursors
70                                 cur_disb_dtl
71   Bug:2255281
72   Desc:DL VERSION TO BE CHECKED FOR DL CHANGE ORIG AND DISB ORIGINATION LOAN PROGRAMS
73   Who             When            What
74   mesriniv        22-mar-2002     Modified cur_disb_dtl to pick up
75                                   Disbursements for future and also posted to Student A/C
76 
77   (reverse chronological order - newest change first)
78   ***************************************************************/
79 
80    l_cod_year_flag   BOOLEAN;
81    lv_cal_type       igs_ca_inst.cal_type%TYPE;                  -- ##  Used for the award year ##
82    lv_cal_seq_num    igs_ca_inst.sequence_number%TYPE;           -- ##  Both cal_seq_num and cal_type forms the award year ##
83    lv_dl_version     igf_lookups_view.lookup_code%TYPE;          -- ##  Variable for the storing the version number ##
84    lv_batch_id       igf_sl_dl_batch.batch_id%TYPE;              -- ##  Variable to have the batch ID ##
85    lv_dbth_id        igf_sl_dl_batch.dbth_id%TYPE;
86    lv_mesg_class     igf_sl_dl_batch.message_class%TYPE;
87 
88     -- ## REF Cursor Record Types.
89 
90    Header_Rec        igf_sl_dl_record.DLHeaderType;
91    Trailer_Rec       igf_sl_dl_record.DLTrailerType;
92 
93    lv_dl_loan_catg   igf_lookups_view.lookup_code%TYPE;
94    p_rec_count       NUMBER := 0;
95 
96    no_disb_data      EXCEPTION;  -- ## User Define Exception to check if any records to Originate.
97 
98    -- ## Cursor to check If any records is there to originate. If no records exists
99    -- ## then header file should not be created and a suitable user definede exception
100    -- ## is fired else the file is created.
101 
102    --SF Status is changed to P( Posted into Student A/C)
103    --Removed the check for Invoice Number being not null
104    --If a positive adjustment is done Invoice Number is NULL and credit id will be upadted by the
105    --student finance integration process.
106    --If a negative adjustment is done  Invoice Number is NOT NULL and
107    --Credit ID will be null
108    --So we consider only SF Status as P
109 
110    CURSOR cur_disb_dtl(lv_ci_cal_type igs_ca_inst.cal_type%TYPE,
111                        lv_ci_sequence_number igs_ca_inst.sequence_number%TYPE) IS
112         SELECT  '1'
113         FROM igf_aw_db_chg_dtls adtlv,
114              igf_aw_award awd,
115              igf_sl_loans lar,
116              igf_ap_fa_base_rec fabase
117         WHERE   -- ## Pick up all records with SF Status 1)"to be Posted" and Pick up Disbursements with Future dates and within 7 Future days,
118                 --    "Posted" to Student Account.
119               adtlv.disb_date-TRUNC(SYSDATE) <=7
120         AND   adtlv.disb_status         = 'G'           -- ## With Disbursement Status as Ready to Send
121         AND   adtlv.award_id            = awd.award_id
122         AND   adtlv.award_id            = lar.award_id
123         AND   awd.base_id               = fabase.base_id
124         AND   fabase.ci_cal_type        = lv_ci_cal_type
125         AND   fabase.ci_sequence_number = lv_ci_sequence_number
126         AND   substr(lar.loan_number, 13, 6) = p_school_code;
127 
128    --Cursor to fetch the minimum disbursement number for an award.
129 
130      lcur_disb_dtl       cur_disb_dtl%ROWTYPE;
131      l_year              VARCHAR2(80);
132      l_para              VARCHAR2(80);
133      l_alternate_code    igs_ca_inst.alternate_code%TYPE;
134 
135    -- Get the details of school meaning from lookups to print in the log file
136    CURSOR c_get_sch_code IS
137      SELECT meaning
138        FROM igs_lookups_view
139       WHERE lookup_type = 'OR_SYSTEM_ID_TYPE'
140         AND lookup_code = 'DL_SCH_CD'
141         AND enabled_flag = 'Y';
142     c_get_sch_code_rec c_get_sch_code%ROWTYPE;
143 
144    BEGIN
145      igf_aw_gen.set_org_id(p_org_id);
146 
147      retcode := 0;
148      l_year := igf_aw_gen.lookup_desc('IGF_AW_LOOKUPS_MSG','AWARD_YEAR');
149      l_para := igf_aw_gen.lookup_desc('IGF_GE_PARAMETERS','PARAMETER_PASS');
150 
151      lv_cal_type    := rtrim(substr(p_award_year,1,10));
152      lv_cal_seq_num := rtrim(substr(p_award_year,11));
153 
154      -- Check wether the awarding year is COD-XML processing Year or not
155      l_cod_year_flag  := NULL;
156      l_cod_year_flag := igf_sl_dl_validation.check_full_participant (lv_cal_type, lv_cal_seq_num,'DL');
157 
158      -- If the award year is FULL_PARTICIPANT then raise the error message and stop processing
159      -- else continue the process
160      IF l_cod_year_flag THEN
161 
162        fnd_message.set_name('IGF','IGF_SL_COD_NO_DISB_ORIG');
163        fnd_file.put_line(fnd_file.log,fnd_message.get);
164        RETURN;
165 
166      END IF;
167 
168      l_alternate_code:=igf_gr_gen.get_alt_code(lv_cal_type,lv_cal_seq_num);
169 
170      OPEN c_get_sch_code; FETCH c_get_sch_code INTO c_get_sch_code_rec; CLOSE c_get_sch_code;
171 
172      --Show the parameters Passed
173      fnd_file.put_line(fnd_file.log,RPAD(l_para,50,' '));
174      fnd_file.put_line(fnd_file.log,RPAD(l_year,50,' ')||':'||RPAD(' ',4,' ')||l_alternate_code);
175      fnd_file.put_line(fnd_file.log,RPAD(c_get_sch_code_rec.meaning,50,' ')||':'||RPAD(' ',4,' ')||p_school_code);
176      fnd_file.put_line(fnd_file.log,' ');
177 
178      -- Get the Direct Loan File Spec Version
179      BEGIN
180        lv_dl_version := igf_sl_gen.get_dl_version(lv_cal_type, lv_cal_seq_num);
181      EXCEPTION
182        WHEN NO_DATA_FOUND THEN
183        fnd_message.set_name('IGF','IGF_DB_DL_VERSION_FALSE');
184        fnd_file.put_line(fnd_file.log,fnd_message.get);
185        RAISE NO_DATA_FOUND;
186      END;
187 
188      -- Initialise the Data Record field
189      lv_data_record := NULL;
190 
191      /************************************************************************
192              Using REF CURSORS.
193              Header Record specifications, for each Direct Loan Version
194              is specified in the igf_sl_dl_record.DLHeader_cur procedure.
195              By calling this procedure, the following are done
196                1. Computes Batch ID
197                2. Inserts the Batch ID details in igf_sl_dl_batch
198                3. For the specified version, Opens a REF CURSOR, having
199                   header file Specs.
200       *************************************************************************/
201 
202      OPEN cur_disb_dtl(lv_cal_type,lv_cal_seq_num);
203      FETCH cur_disb_dtl INTO lcur_disb_dtl;
204 
205      IF cur_disb_dtl%NOTFOUND THEN
206        --Obseleted message IGF_NO_DL_DISB_DATA_ORIG as it does not comply standards.
207        --Added a new message.
208        fnd_message.set_name('IGF','IGF_DB_DLDISB_NOTORIG');
209        fnd_file.put_line(FND_FILE.LOG,fnd_message.get);
210        CLOSE cur_disb_dtl;
211        RAISE no_disb_data;
212      END IF;
213 
214      lv_dl_loan_catg := 'DL';
215      igf_sl_dl_record.DLHeader_cur(lv_dl_version,
216                                   lv_dl_loan_catg,
217                                   lv_cal_type,
218                                   lv_cal_seq_num,
219                                   'DL_DISB_SEND',
220                                   p_school_code,
221                                   lv_dbth_id,
222                                   lv_batch_id,
223                                   lv_mesg_class,
224                                   Header_Rec);
225 
226      FETCH Header_Rec into lv_data_record;
227 
228      IF Header_Rec%NOTFOUND THEN
229        fnd_message.set_name ('IGF', 'IGF_GE_HDR_CREATE_ERROR');
230        igs_ge_msg_stack.add;
231        app_exception.raise_exception;
232      END IF;
233 
234      -- Write the Header Record into the Output file.
235      -- fnd_file.put_line(FND_FILE.OUTPUT, lv_data_record);
236      -- The above line(code) commented here and is being used in the trans_rec procedure
237      -- as the header record is created if there exists a valid transaction
238      -- record to process
239 
240      --Formulating the Transaction Record
241      --Calls a Procedure to create a Transaction record in the File.
242       Trans_Rec(lv_dl_version,
243                 lv_batch_id,
244                 p_Rec_count,
245                 lv_cal_type,
246                 lv_cal_seq_num,
247                 p_school_code);
248 
249 
250      -- Initialise the Data Record field
251      lv_data_record := NULL;
252 
253      -- process the trailer record only if atleast one transaction record has been processed
254      IF(p_Rec_count > 0)THEN
255      -- Write the Trailer Record
256        igf_sl_dl_record.DLTrailer_cur(lv_dl_version, p_Rec_count,Trailer_Rec);
257        FETCH Trailer_Rec into lv_data_record;
258        IF Trailer_Rec%NOTFOUND THEN
259          fnd_message.set_name ('IGF', 'IGF_GE_TRL_CREATE_ERROR');
260          igs_ge_msg_stack.add;
261          app_exception.raise_exception;
262        END IF;
263        -- Write the Trailer Record into the Output file
264        fnd_file.put_line(FND_FILE.OUTPUT, lv_data_record);
265 
266        --Display message that DL Disb Records are originated.See output File.
267        fnd_file.put_line(fnd_file.log,' ');
268        fnd_message.set_name('IGF','IGF_DB_DL_DISB_ORIG');
269        fnd_file.put_line(fnd_file.log,fnd_message.get);
270      ELSE
271        FND_MESSAGE.SET_NAME('IGF','IGF_AP_TOTAL_RECS');
272        FND_MESSAGE.SET_TOKEN('COUNT', p_Rec_count);
273        FND_FILE.PUT_LINE(FND_FILE.LOG, FND_MESSAGE.GET);
274      END IF;
275      COMMIT;
276 
277 EXCEPTION
278   WHEN NO_DATA_FOUND THEN
279     NULL;
280   WHEN no_disb_data THEN
281     ROLLBACK;
282     retcode := 0;
283     errbuf  := NULL;
284   WHEN app_exception.record_lock_exception THEN
285     ROLLBACK;
286     retcode := 2;
287     errbuf := fnd_message.get_string('IGF','IGF_GE_LOCK_ERROR');
288     IGS_GE_MSG_STACK.CONC_EXCEPTION_HNDL;
289   WHEN OTHERS THEN
290     ROLLBACK;
291     retcode := 2;
292     errbuf := fnd_message.get_string('IGS','IGS_GE_UNHANDLED_EXCEPTION');
293     fnd_file.put_line(fnd_file.log,SQLERRM);
294     IGS_GE_MSG_STACK.CONC_EXCEPTION_HNDL;
295 END disb_originate;
296 
297 PROCEDURE trans_rec( p_dl_version           igf_lookups_view.lookup_code%TYPE,
298                      p_dl_batch_id          igf_sl_dl_batch.batch_id%TYPE,
299                      p_rec_count            IN OUT NOCOPY NUMBER,
300                      p_ci_cal_type          igf_sl_dl_setup.ci_cal_type%TYPE,
301                      p_ci_sequence_number   igf_sl_dl_setup.ci_sequence_number%TYPE,
302                      p_school_code        IN    VARCHAR2 )
303 AS
304   /*************************************************************
305   Created By : prchandr
306   Date Created On : 2000/12/19
307   Purpose : To create the Transaction Record
308   Know limitations, enhancements or remarks
309   Change History:
310   Bug 2438434.Incorrect Format in Output File.
311   Who             When            What
312   ugummall        23-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
313                                   Modified the cursor cur_disb_dtl to include the clause which
314                                   filter only the loans having the school id matched with parameter p_school_code.
315   ugummall        17-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
316                                   1. Logic is changed so that it processes for only those students whose associated
317                                      Org Unit has an alternate identifier for Direct Loan School Code matching with
318                                      the supplied parameter p_school_code(instead of school_id picked from igf_sl_dl_setup table)
319                                   2. school_id is removed from the cursor cur_school and its references are replaced with the
320                                      supplied parameter p_school_code.
321   vvutukur        25-Feb-2003     Enh#2758823.FA117 Build. Modified the if condition to include 03-04 removing 02-03.
322                                   ie., Changed IF p_dl_version IN ('2001-2002','2002-2003') to IF p_dl_version IN ('2002-2003','2003-2004').
323                                   Also added new cursor cur_min_disb_num used the min. disb.num of the award to log details
324                                   in column number 129 in the output file. In when others section exception section, NOTFOUND is changed to ISOPEN
325                                   to close a cursor is still open.
326   mesriniv        1-jul-2002      LPAD with 0 for Amount Fields
327   Bug:2255281
328   Desc:DL VERSION TO BE CHECKED FOR DL CHANGE ORIG AND DISB ORIGINATION LOAN PROGRAMS
329   Who             When            What
330   mesriniv        22-mar-2002     Added Check for 2002-2003
331                                   Modified cur_disb_dtl to pick up
332                                   Disbursements for future and also posted to Student A/C
333 
334   (reverse chronological order - newest change first)
335   ***************************************************************/
336 
337 
338  l_Trans_Rec               VARCHAR2(4000)  := NULL; -- ## Variable to store the Disbursement Detail Record
339  l_Rec_count               NUMBER          := 0;    -- ## Variable to store the Record Count
340  l_orig_fee_perct_stafford igf_sl_dl_setup.orig_fee_perct_stafford%TYPE;
341  l_orig_fee_perct_plus     igf_sl_dl_setup.orig_fee_perct_plus%TYPE;
342  l_int_rebate_amt          igf_aw_awd_disb.fee_1%TYPE;     -- This field's data type is similar to Fees.
343 
344 -- ## Cursor to Retrieve the disbursements being credited to the Students Account
345 
346  CURSOR cur_disb_dtl IS
347         SELECT  adtlv.*, fabase.base_id, lar.loan_number
348         FROM igf_aw_db_chg_dtls adtlv,
349              igf_aw_award awd,
350              igf_sl_loans lar,
351              igf_ap_fa_base_rec fabase
352         WHERE
353              adtlv.disb_date-TRUNC(SYSDATE) <=7
354         AND   adtlv.disb_status         = 'G'           -- ## With Disbursement Status as Ready to Send
355         AND   adtlv.award_id            = awd.award_id
356         AND   adtlv.award_id            = lar.award_id
357         AND   awd.base_id               = fabase.base_id
358         AND   fabase.ci_cal_type        = p_ci_cal_type
359         AND   fabase.ci_sequence_number = p_ci_sequence_number
360         AND   substr(lar.loan_number, 13, 6) = p_school_code
361         ORDER BY adtlv.disb_num, adtlv.disb_seq_num;
362 
363  -- ## Cursor to Retrieve the School ID for a Particular Award Year.
364  -- ## by ugummall. school_id is removed as it is being obsoleted w.r.t. FA 126.
365  -- ## Supplied parameter p_school_id is used instead of school_id.
366  CURSOR cur_school IS
367         SELECT orig_fee_perct_stafford, orig_fee_perct_plus FROM igf_sl_dl_setup
368         WHERE  ci_cal_type         = p_ci_cal_type
369         AND    ci_sequence_number  = p_ci_sequence_number;
370 
371  -- Cursor to get the Fed Fund code for the specified award.
372  CURSOR cur_fund_details(p_award_id igf_aw_award_all.award_id%TYPE) IS
373         SELECT awd.fund_id, fcat.fed_fund_code
374         FROM   igf_aw_fund_mast fmast,
375                igf_aw_fund_cat  fcat,
376                igf_aw_award awd
377         WHERE awd.award_id    = p_award_id
378         AND   awd.fund_id     = fmast.fund_id
379         AND   fmast.fund_code = fcat.fund_code;
380 
381  CURSOR cur_min_disb_num (cp_award_id igf_aw_award_all.award_id%TYPE) IS
382    SELECT MIN(disb_num)
383    FROM   igf_aw_awd_disb
384    WHERE  award_id = cp_award_id;
385 
386 
387    CURSOR cur_get_prev_date (cp_award_id      igf_aw_db_chg_dtls.award_id%TYPE,
388                              cp_disb_num      igf_aw_db_chg_dtls.disb_num%TYPE,
389                              cp_disb_seq_num  igf_aw_db_chg_dtls.disb_seq_num%TYPE)
390    IS
391    SELECT disb_date
392    FROM   igf_aw_db_chg_dtls
393    WHERE  award_id     = cp_award_id
394      AND  disb_num     = cp_disb_num
395      AND  disb_seq_num = cp_disb_seq_num;
396 
397    ld_date             igf_aw_db_chg_dtls.disb_date%TYPE;
398    l_min_disb_num      igf_aw_db_chg_dtls.disb_num%TYPE;
399 
400    lcur_disb_dtl       cur_disb_dtl%ROWTYPE; -- ## Cursor Type for the Disb Cursor
401    lcur_fund_dtl       cur_fund_details%ROWTYPE;
402    lcur_fund_dtl_temp  cur_fund_details%ROWTYPE;
403 
404 
405 BEGIN
406   -- ## Loop to Get the School ID
407   OPEN cur_school;
408   FETCH cur_school INTO l_orig_fee_perct_stafford, l_orig_fee_perct_plus;
409   IF cur_school%NOTFOUND THEN
410     CLOSE cur_school;
411     fnd_message.set_name ('IGF', 'IGF_SL_NO_DL_SETUP');
412     fnd_file.put_line(fnd_file.log,fnd_message.get);
413     RAISE NO_DATA_FOUND;
414   END IF;
415   CLOSE cur_school;
416 
417   OPEN cur_disb_dtl; -- ## Open the Cursor
418   -- ## Check for the DL Version and according to fetch the
419   -- ## Disbursements detail records and Store it in a variable
420   -- ## to be put in a file
421 
422   IF p_dl_version  IN ('2002-2003','2003-2004','2004-2005') THEN
423     LOOP
424       FETCH cur_disb_dtl INTO lcur_disb_dtl;
425       EXIT WHEN cur_disb_dtl%NOTFOUND;
426 
427           -- Calculate the Interest Rebate Amt, for this set of disbursement figures
428           lcur_fund_dtl := lcur_fund_dtl_temp;
429           l_int_rebate_amt := 0;
430 
431           OPEN cur_fund_details(lcur_disb_dtl.award_id);
432           FETCH cur_fund_details INTO lcur_fund_dtl;
433           CLOSE cur_fund_details;
434 
435           --Interest Rebate = Net Disb Amt - (Gross Disb- Loan Fee)
436           --Loan Fee Amount = orig fee perct (PLUS or STAFFORD) * Gross Disb
437           --Using this Formula the Interest Rebate Amount was being calculated.
438           --Since this interest rebate amount is available in the IGF_AW_AWD_DISB
439           --we can make use of the same instead of re-calculating here.
440           --Hence removing code which calculated the value and using same from IGF_AW_AWD_DISB.
441 
442           l_int_rebate_amt := lcur_disb_dtl.interest_rebate_amt;
443 
444           l_Trans_Rec  :=  RPAD(NVL(lcur_disb_dtl.loan_number,' '),21) ||
445                            LPAD(NVL(TO_CHAR(lcur_disb_dtl.disb_num),'0'),2,'0') ||
446                            NVL(lcur_disb_dtl.disb_activity,' ');
447 
448           -- ## Check if disb activity is Actual Disbursement(D) or
449           -- ## Adjusted Disbursement(A) then send the SF Status Date
450           -- If Adjusted Disbursement Date (Q) then send the new disbursement date
451 
452           --Made a specific check for 'D' and 'A' as per FACR007
453 
454           IF lcur_disb_dtl.disb_activity IN ('D','A') THEN
455             l_Trans_Rec :=   l_Trans_Rec
456                             || RPAD( NVL( TO_CHAR(lcur_disb_dtl.disb_status_date,'YYYYMMDD'), ' '),8);
457 
458           ELSIF lcur_disb_dtl.disb_activity ='Q' THEN
459             l_Trans_Rec :=   l_Trans_Rec
460                              || RPAD( NVL( TO_CHAR(lcur_disb_dtl.disb_date,'YYYYMMDD'), ' '),8);
461           ELSE
462             l_Trans_Rec := l_Trans_Rec || RPAD(' ',8);
463           END IF;
464 
465           -- ## Add the disbursement Sequence Number
466           l_Trans_Rec := l_Trans_Rec || LPAD(NVL(TO_CHAR(lcur_disb_dtl.disb_seq_num),'0'),2,'0');
467 
468           -- ## Check if the disb activity is Ajusted Disbursement(A) then
469           -- ## Add the gross amt else sent blank
470 
471           --LPAD  with 0 for amount fields as per Bug 2438434
472           IF lcur_disb_dtl.disb_activity IN ('D','A') THEN
473             l_Trans_Rec := l_Trans_Rec || LPAD(NVL(TO_CHAR(lcur_disb_dtl.orig_fee_amt)    ,'0'),5,'0')
474                                          || LPAD(NVL(TO_CHAR(lcur_disb_dtl.orig_fee_amt)  ,'0'),5,'0')
475                                          || LPAD(NVL(TO_CHAR(lcur_disb_dtl.disb_net_amt)  ,'0'),5,'0')
476                                          || LPAD(NVL(TO_CHAR(l_int_rebate_amt)            ,'0'),5,'0');
477 
478           ELSE
479             l_Trans_Rec := l_Trans_rec||LPAD(' ',5)
480                                         ||LPAD(' ',5)
481                                         ||LPAD(' ',5)
482                                         ||RPAD(' ',5);
483           END IF;
484 
485           -- ## Add 9 spaces including Filler ,and batch ID
486           l_Trans_Rec := l_Trans_Rec || RPAD(' ',9)
487                                       || RPAD(NVL(p_dl_batch_id,' '),23);
488 
489 
490           l_Trans_Rec := l_Trans_Rec ||RPAD(NVL(p_school_code,' '),6)
491                                          ||RPAD(' ',1)
492                                          ||RPAD(' ',1)
493                                          ||RPAD(' ',1) -- Totally 3 Filler
494                                          ||RPAD(' ',10)
495                                          ||RPAD(' ',1)
496                                          ||RPAD(' ',1)
497                                          ||LPAD(' ',5)
498                                          ||LPAD(' ',5)
499                                          ||LPAD(' ',5)
500                                          ||LPAD(' ',6);
501 
502 
503           -- ##  Check if disbursement Number is 1 and it is the first actual disbursement then
504           -- ##  Send F (first disbursement required)
505 
506           OPEN cur_min_disb_num(lcur_disb_dtl.award_id);
507           FETCH cur_min_disb_num INTO l_min_disb_num;
508           CLOSE cur_min_disb_num;
509 
510           IF (lcur_disb_dtl.disb_num = l_min_disb_num AND l_min_disb_num > 1 AND lcur_disb_dtl.disb_seq_num = 1) THEN
511              l_Trans_Rec := l_Trans_Rec ||'F';
512           ELSE
513              l_Trans_Rec := l_Trans_Rec || RPAD(' ',1);
514           END IF;
515 
516           l_Trans_Rec := l_Trans_Rec || LPAD(' ',5)
517                                         || LPAD(' ',4)
518                                         || LPAD(' ',5);
519 
520           -- ## Check if the disb activity is Ajusted Disbursement Date(Q) then
521           -- ## Add the gross adjusted amt
522 
523           IF lcur_disb_dtl.disb_activity = 'Q' THEN
524 
525           --
526           -- here we should put the previous adjustment date
527           --
528              OPEN  cur_get_prev_date(lcur_disb_dtl.award_id,
529                                      lcur_disb_dtl.disb_num,
530                                      lcur_disb_dtl.disb_seq_num - 1);
531              FETCH cur_get_prev_date INTO ld_date;
532              CLOSE cur_get_prev_date;
533 
534              l_Trans_Rec :=    l_Trans_Rec
535                             || LPAD( NVL( TO_CHAR(ld_date,'YYYYMMDD'),' '),8);
536           ELSE
537              l_Trans_Rec := l_Trans_Rec || LPAD(' ',8);
538           END IF;
539 
540           -- ## Check if the disb activity is Ajusted Disbursement(A) then
541           -- ## Add the Affirm Flag else sent blank
542 
543           IF lcur_disb_dtl.disb_activity IN ('D','A') THEN
544              l_Trans_Rec := l_Trans_Rec || RPAD(NVL(lcur_disb_dtl.disb_conf_flag,' '),1);
545           ELSE
546              l_Trans_Rec := l_Trans_Rec || RPAD(' ',1);
547           END IF;
548 
549           l_Rec_count := l_Rec_count + 1;  -- ## Increment the Record Count
550           -- ## Write the header to file only first time
551           IF (l_Rec_count = 1) THEN
552             fnd_file.put_line(FND_FILE.OUTPUT, lv_data_record);
553           END IF;
554           fnd_file.put_line(FND_FILE.OUTPUT, l_Trans_Rec); -- ## Write the Transaction Record to file
555 
556           -- ## Update the igf_aw_db_chg_dtls table with the disb_status as sent
557           -- ## , disb_status_date as sysdate and disb_batch_id as current batch id
558           -- ## for each award ID,disbnum and disb_seq_num.
559 
560           DECLARE
561 
562             CURSOR c_tbh_cur IS
563               SELECT igf_aw_db_chg_dtls.*,igf_aw_db_chg_dtls.ROWID
564                 FROM igf_aw_db_chg_dtls
565                WHERE award_id     = lcur_disb_dtl.award_Id
566                  AND disb_num     = lcur_disb_dtl.disb_num
567                  AND disb_seq_num = lcur_disb_dtl.disb_seq_num
568                  FOR UPDATE OF award_Id NOWAIT;
569           BEGIN
570             FOR tbh_rec in c_tbh_cur LOOP
571 
572               igf_aw_db_chg_dtls_pkg.update_row (
573                 x_rowid                 => tbh_rec.ROWID,
574                 x_award_id              => tbh_rec.award_id,
575                 x_disb_num              => tbh_rec.disb_num,
576                 x_disb_seq_num          => tbh_rec.disb_seq_num,
577                 x_disb_accepted_amt     => tbh_rec.disb_accepted_amt,
578                 x_orig_fee_amt          => tbh_rec.orig_fee_amt,
579                 x_disb_net_amt          => tbh_rec.disb_net_amt,
580                 x_disb_date             => tbh_rec.disb_date,
581                 x_disb_activity         => tbh_rec.disb_activity,
582                 x_disb_status           => 'S',
583                 x_disb_status_date      => TRUNC(SYSDATE),
584                 x_disb_rel_flag         => tbh_rec.disb_rel_flag,
585                 x_first_disb_flag       => tbh_rec.first_disb_flag,
586                 x_interest_rebate_amt   => tbh_rec.interest_rebate_amt,
587                 x_disb_conf_flag        => tbh_rec.disb_conf_flag,
588                 x_pymnt_prd_start_date  => tbh_rec.pymnt_prd_start_date,
589                 x_note_message          => tbh_rec.note_message,
590                 x_batch_id_txt          => p_dl_batch_Id,
591                 x_ack_date              => tbh_rec.ack_date,
592                 x_booking_id_txt        => tbh_rec.booking_id_txt,
593                 x_booking_date          => tbh_rec.booking_date,
594                 x_mode                  => 'R');
595 
596             END LOOP;
597           END;
598     END LOOP;  -- ## OUter End Loop
599     p_Rec_count := l_Rec_count;
600     CLOSE cur_disb_dtl; -- ## Close The cursor.
601   END IF;   --end of version check
602 
603 EXCEPTION
604 WHEN NO_DATA_FOUND THEN
605      NULL;
606 WHEN app_exception.record_lock_exception THEN
607    IF cur_disb_dtl%ISOPEN THEN
608      CLOSE cur_disb_dtl;
609    END IF;
610    IF cur_school%ISOPEN THEN
611      CLOSE cur_school;
612    END IF;
613    RAISE;
614 
615 WHEN OTHERS THEN
616    IF cur_disb_dtl%ISOPEN THEN
617      CLOSE cur_disb_dtl;
618    END IF;
619    IF cur_school%ISOPEN THEN
620      CLOSE cur_school;
621    END IF;
622    fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
623    fnd_message.set_token('NAME','IGF_DB_DL_DISB_ORIG.TRANS_REC');
624    fnd_file.put_line(fnd_file.log,SQLERRM);
625    igs_ge_msg_stack.add;
626    app_exception.raise_exception;
627 END trans_rec;
628 END igf_db_dl_disb_orig;