DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGF_SL_DL_CHG_ORIG

Source


1 PACKAGE BODY igf_sl_dl_chg_orig AS
2 /* $Header: IGFSL05B.pls 120.1 2006/04/19 08:40:35 bvisvana noship $ */
3 
4 --
5 ---------------------------------------------------------------------------------------
6 --
7 -- Procedure chg_originate :
8 --
9 -- User inputs are
10 -- Award year (required) : Consists of Cal_type and sequence_number concatenated
11 -- LOAN_CATEGORY         : Valid values are DL_STAFFORD/DL_PLUS.
12 --
13 ---------------------------------------------------------------------------------------
14 -- Change History:
15 ---------------------------------------------------------------------------------------
16 -- Who          When            What
17 -----------------------------------------------------------------------------------
18 -- veramach     04-May-2004     bug 3603289
19 --                              Modified cursor cur_student_licence to select
20 --                              dependency_status from ISIR. other details are
21 --                              derived from igf_sl_gen.get_person_details.
22 -----------------------------------------------------------------------------------
23 -- veramach        29-Jan-2004     bug 3408092 added 2004-2005 in p_dl_version checks
24 -----------------------------------------------------------------------------------
25 -- ugummall   23-OCT-2003     Bug 3102439. FA 126 Multiple FA Offices.
26 --                             Modified the cursor c_lor to include the clause which filter only
27 --                             the loans having the school id matched with parameter p_school_code.
28 ---------------------------------------------------------------------------------------
29 -- ugummall    17-OCT-2003      Bug 3102439. FA 126 Multiple FA Offices.
30 --                              1. Added two new parameters to chg_originate process.
31 --                              2. Passed the parameter p_school_code to DLHeader_cur
32 --                                 as extra parameter
33 --                              3. Processed only those students whose associated org unit
34 --                                 has an alternate identifier of Direct Loan School Code and it
35 --                                 is matching with the supplied p_school_code parameter.
36 ---------------------------------------------------------------------------------------
37 -- sjadhav     14-Oct-2003      Bug 3104228 Removed ref to obsolete columns
38 ---------------------------------------------------------------------------------------
39 -- bkkumar     07-oct-2003      Bug 3104228 FA 122 Loan Enhancemtns
40 --                              a) Changed the cursor c_lor
41 --                                 containing igf_sl_lor_dtls_v with simple
42 --                                 joins and got the details of student and parent
43 --                                 from igf_sl_gen.get_person_details.
44 --                                 Added the debugging log messages.
45 --                              b) The DUNS_BORW_LENDER_ID,
46 --                                 DUNS_GUARNT_ID,
47 --                                 DUNS_LENDER_ID,
48 --                                 DUNS_RECIP_ID columns are osboleted from the
49 --                                 igf_sl_lor_loc_all table.
50 ---------------------------------------------------------------------------------------
51 -- sjadhav      26-Mar-2003     Bug 2863960
52 --                              lcur_award.disb_gross_amt replaced with
53 --                              lcur_award.disb_accepted_amt as accepted amount is the
54 --                              gross amount
55 ---------------------------------------------------------------------------------------
56 -- vvutukur     21-Feb-2003     Enh#2758823.FA117 Build. Modified procedure Trans_Rec.
57 ---------------------------------------------------------------------------------------
58 --
59 -- ## Forward Declaration of Trans_rec Procedure
60 
61 PROCEDURE Trans_Rec( p_dl_version           igf_lookups_view.lookup_code%TYPE,
62                      p_dl_dbth_id           igf_sl_dl_batch.dbth_id%TYPE,
63                      p_dl_batch_id          igf_sl_dl_batch.batch_id%TYPE,
64                      p_tot_rec_count        IN OUT NOCOPY NUMBER);
65 
66 PROCEDURE chg_originate(errbuf  OUT NOCOPY    VARCHAR2,
67                        retcode OUT NOCOPY     NUMBER,
68                        p_award_year    VARCHAR2,
69                        p_dl_loan_catg  igf_lookups_view.lookup_code%TYPE,
70                        p_org_id IN     NUMBER,
71                        school_type    IN    VARCHAR2,
72                        p_school_code  IN    VARCHAR2
73                        )
74 AS
75   /*************************************************************
76    Created By : prchandr
77   Date Created On : 2000/12/13
78   Purpose : Main Procedure for the Direct Loan change process
79   Know limitations, enhancements or remarks
80   Change History:
81   Who             When            What
82   bvisvana       10-Apr-2006      Build FA 161.
83                                   TBH Impact change in igf_sl_lor_loc_pkg.update_row()
84   Bug No:2332668 Desc:LOAN ORIGINATION PROCESS NOT RUNNING SUCCESSFULLY.
85   Who             When            What
86   mesriniv        23-APR-2002     Added code to display the Parameters Passed
87 
88   Bug :- 2255281
89   Desc:- DL Version Change
90   Who             When            What
91   mesriniv        20-MAR-2002     Added Code to SKIP LOAN when an error occurs
92 
93   Who             When            What
94   agairola        19-Mar-2002     Modifed the update row call of the IGF_SL_LOANS_PKG to include
95                                   Borrower determination as part of Refunds DLD - 2144600
96 
97 
98   (reverse chronological order - newest change first)
99   ***************************************************************/
100 
101    lv_cal_type       igs_ca_inst.cal_type%TYPE;               -- ##  Used for the award year ##
102    lv_cal_seq_num    igs_ca_inst.sequence_number%TYPE;        -- ##  Both cal_seq_num and cal_type forms the award year ##
103    lv_dl_version     igf_lookups_view.lookup_code%TYPE;          -- ##  Variable for the storing the version number ##
104    lv_batch_id       igf_sl_dl_batch.batch_id%TYPE;              -- ##  Variable to have the batch ID ##
105    lv_dbth_id        igf_sl_dl_batch.dbth_id%TYPE;
106    lv_mesg_class     igf_sl_dl_batch.message_class%TYPE;
107    lv_begin_date     igf_sl_lor_loc.acad_yr_begin_date %TYPE;    -- ##  Variable to have the academic begin date ##
108    lv_end_date       igf_sl_lor_loc.acad_yr_end_date%TYPE;       -- ##  Variable to have the academic end date ##
109 
110   --Bug No:2332668
111    l_i               NUMBER(1);
112    l_alternate_code  igs_ca_inst.alternate_code%TYPE;
113    l_display        VARCHAR2(1) := 'N';
114 
115    TYPE l_parameters IS TABLE OF VARCHAR2(100) INDEX BY BINARY_INTEGER;
116    l_para_rec l_parameters;
117 
118    SKIP_LOAN         EXCEPTION;
119    yr_full_participant  EXCEPTION;
120 
121    lv_data_record    VARCHAR2(4000);   --  ##  Variable to store the concatenated value to be stored in file ##
122    lv_orig_award_id  igf_aw_award.award_id%TYPE;
123    p_tot_rec_count   NUMBER := 0;      --  ##  Variable to store the number of records to be placed in Trailer Record ##
124    lc_chg_flag       VARCHAR2(1);      --  ##  Flag to Indicate if any changes are there between Oldvalues and New values ##
125    lc_disb_chg_flag  VARCHAR2(1);      --  ##  Flag to Indicate if any changes are there between Oldvalues and New ones in Disbursement tables##
126    lc_header_flag    VARCHAR2(1) := 'N';  --  ##  Flag to indicate if any changes had happened in loans or disbursement so as to set the header record ##
127    l_rowid           ROWID;
128    lv_loan_number    igf_sl_dl_chg_send.loan_number%TYPE;
129 
130    -- ## REF Cursor Record Types.
131 
132    Header_Rec        igf_sl_dl_record.DLHeaderType;
133    Trailer_Rec       igf_sl_dl_record.DLTrailerType;
134 
135    lv_bool           BOOLEAN;
136    l_disb            BOOLEAN := TRUE;  -- ## Variable for disbursement calculations
137    l_disb_loc        BOOLEAN := FALSE; -- ## Variable for disbursement calculations
138 
139    l_driver_license_number     igf_ap_isir_matched.driver_license_number%TYPE;
140    l_driver_license_state      igf_ap_isir_matched.driver_license_state%TYPE;
141    l_citizenship_status        igf_ap_isir_matched.citizenship_status%TYPE;
142    l_alien_reg_number          igf_ap_isir_matched.alien_reg_number%TYPE;
143    l_dependency_status         igf_ap_isir_matched.dependency_status%TYPE;
144    l_fed_fund_1 igf_aw_fund_cat.fed_fund_code%TYPE;
145    l_fed_fund_2 igf_aw_fund_cat.fed_fund_code%TYPE;
146     student_dtl_cur igf_sl_gen.person_dtl_cur;
147     parent_dtl_cur  igf_sl_gen.person_dtl_cur;
148     student_dtl_rec  igf_sl_gen.person_dtl_rec;
149     parent_dtl_rec   igf_sl_gen.person_dtl_rec;
150 
151 
152    -- ## Cursor to Retrieve the active direct loan records with change status as Send from the igf_sl_lor table
153    -- ## for the particular award Year
154   -- FA 122 Loans Enhancemnts changed the cursor to remove the obsolete view igf_sl_lor_dtls_v
155    CURSOR c_lor(
156                 p_cal_type         igs_ca_inst.cal_type%TYPE,
157                 p_seq_num          igs_ca_inst.sequence_number%TYPE,
158                 p_fed_fund_1       igf_aw_fund_cat.fed_fund_code%TYPE,
159                 p_fed_fund_2       igf_aw_fund_cat.fed_fund_code%TYPE,
160                 p_loan_status      igf_sl_loans.loan_status%TYPE,
161                 p_loan_chg_status  igf_sl_loans.loan_chg_status%TYPE,
162                 p_active           igf_sl_loans.active%TYPE
163                 ) IS
164     SELECT
165     loans.row_id,
166     loans.loan_id,
167     loans.loan_number,
168     loans.award_id,
169     awd.accepted_amt loan_amt_accepted,
170     loans.loan_per_begin_date,
171     loans.loan_per_end_date,
172     lor.orig_fee_perct,
173     lor.pnote_print_ind,
174     lor.s_default_status,
175     lor.p_default_status,
176     lor.p_person_id,
177     lor.grade_level_code,
178     lor.unsub_elig_for_heal,
179     lor.disclosure_print_ind,
180     lor.unsub_elig_for_depnt,
181     lor.pnote_batch_id,
182     lor.pnote_ack_date,
183     lor.pnote_mpn_ind,
184     fabase.base_id,
185     fabase.person_id student_id,
186     awd.accepted_amt
187     FROM
188     igf_sl_loans       loans,
189     igf_sl_lor         lor,
190     igf_aw_award       awd,
191     igf_aw_fund_mast   fmast,
192     igf_aw_fund_cat    fcat,
193     igf_ap_fa_base_rec fabase
194     WHERE
195     fabase.ci_cal_type        = p_cal_type      AND
196     fabase.ci_sequence_number = p_seq_num       AND
197     fabase.base_id            = awd.base_id     AND
198     awd.fund_id               = fmast.fund_id   AND
199     fmast.fund_code           = fcat.fund_code  AND
200     (fcat.fed_fund_code       = p_fed_fund_1    OR  fcat.fed_fund_code =  p_fed_fund_2) AND
201     loans.award_id            = awd.award_id    AND
202     loans.loan_id             = lor.loan_id     AND
203     loans.loan_status         = p_loan_status      AND
204     loans.loan_chg_status     = p_loan_chg_status  AND
205     loans.active              = p_active           AND
206     substr(loans.loan_number, 13, 6) = p_school_code;
207 
208    -- masehgal  # 2593215    define variables to be used in the call to get_acad_cal_dtls
209    l_loan_number    igf_sl_loans.loan_number%TYPE := NULL ;
210    lv_acad_cal_type igs_ca_inst.cal_type%TYPE := NULL ;
211    lv_acad_seq_num  igs_ca_inst.sequence_number%TYPE := NULL ;
212    lv_message       VARCHAR2(100) := NULL ;
213 
214    -- ## Cursor to Retrieve the Originated record to compare with the igf_sl_lor table to see if any
215    -- ## change records exist.
216 
217    CURSOR c_lor_loc(p_loan_id igf_sl_lor_loc.loan_id%TYPE) IS
218    SELECT igf_sl_lor_loc.*
219    FROM igf_sl_lor_loc
220    WHERE loan_id  = p_loan_id;
221 
222    -- ## Cursor to retrieve the license number,license state,citizenship status,alien reg number and
223    -- ## dependency status of the Student to be compared with that in IGF_SL_LOR_LOC to see if
224    -- ## any changes exists.
225 
226    CURSOR cur_isir_depend_status(l_base_id  igf_ap_fa_base_rec.base_id%TYPE)
227        IS
228        SELECT isir.dependency_status
229        FROM   igf_ap_fa_base_rec fabase,igf_ap_isir_matched isir
230        WHERE  isir.isir_id   = fabase.payment_isir_id
231        AND    fabase.base_id = l_base_id;
232 
233     -- ## Cursor to Retrieve the disburesment records
234 
235     CURSOR cur_award(p_award_id igf_aw_award.award_id%TYPE) IS
236          SELECT disb.* FROM igf_aw_awd_disb disb
237          WHERE disb.award_id = p_award_id
238          ORDER BY disb.disb_num;
239 
240 
241     -- ## Cursor to Retrieve the Originated disbursement records for the particular award ID
242     -- ## to compare with the disbursement table to know if any change exists
243 
244     CURSOR cur_disb_loc(p_award_id igf_aw_award.award_id%TYPE) IS
245            SELECT disb.row_id row_id, disb.disb_num, disb.disb_gross_amt, disb.disb_date
246            FROM igf_sl_awd_disb_loc disb
247            WHERE award_id = p_award_id
248            ORDER BY disb.disb_num FOR UPDATE OF disb.disb_gross_amt NOWAIT;
249 
250     lcur_award        cur_award%ROWTYPE;
251     lcur_disb_loc     cur_disb_loc%ROWTYPE;
252     lc_lor_loc        c_lor_loc%ROWTYPE;
253 
254     --Cursor to fetch the Meaning for displaying parameters passed
255     --Used UNION ALL here since individual select clauses
256     --have the same cost
257     --Bug 2332668
258 
259      CURSOR cur_get_parameters IS
260      SELECT meaning FROM igf_lookups_view
261      WHERE  lookup_type='IGF_SL_DL_LOAN_CATG' AND lookup_code=p_dl_loan_catg AND enabled_flag = 'Y'
262 
263      UNION ALL
264 
265      SELECT  meaning FROM igf_lookups_view
266      WHERE  lookup_type='IGF_GE_PARAMETERS' AND lookup_code IN ('AWARD_YEAR','LOAN_CATG','PARAMETER_PASS') AND enabled_flag = 'Y';
267 
268     -- Get the details of school meaning from lookups to print in the log file
269     CURSOR c_get_sch_code IS
270       SELECT meaning
271         FROM igs_lookups_view
272        WHERE lookup_type = 'OR_SYSTEM_ID_TYPE'
273          AND lookup_code = 'DL_SCH_CD'
274          AND enabled_flag = 'Y';
275     c_get_sch_code_rec c_get_sch_code%ROWTYPE;
276 
277      --Cursor to get the alternate code for the calendar instance
278      --Bug 2332668
279      CURSOR cur_alternate_code IS
280      SELECT ca.alternate_code FROM igs_ca_inst ca
281      WHERE  ca.cal_type =lv_cal_type
282      AND    ca.sequence_number = lv_cal_seq_num;
283 
284     -- Private Definition of the Procedure comp_lor_loc
285 
286     PROCEDURE  comp_lor_loc
287                           ( p_field_lor      IN     VARCHAR2,
288                             p_field_lor_loc  IN     VARCHAR2,
289                             p_field_name     IN     VARCHAR2,
290                             p_chg_flg        IN OUT NOCOPY VARCHAR2
291                             )
292     AS
293     /*************************************************************
294       Created By : prchandr
295       Date Created On : 2000/12/07
296       Purpose : Procedure to compare the values in igf_sl_lor_loc and igf_sl_lor_dtls_v also for disbursements
297       Know limitations, enhancements or remarks
298       Change History:
299       Bug 2438434.Incorrect Format in Output File.
300       Who             When            What
301       masehgal        # 2593215       removed begin/end dates fetching functions
302                                       used procedure get_acad_cal_dtls instead
303       mesriniv        1-jul-2002      Made UPPERCASE for Name,Address Fields,and LPAD with 0 for Amount Fields
304       Who             When            What
305 
306       (reverse chronological order - newest change first)
307       ***************************************************************/
308 
309     -- ## Cursor to get the changed code values
310     CURSOR c_chg_code IS
311            SELECT chg_code FROM igf_sl_dl_chg_fld
312                  WHERE fld_name =p_field_name
313                  AND   loan_catg= p_dl_loan_catg
314                  AND   dl_version =lv_dl_version;
315 
316      lc_chg_code   c_chg_code%ROWTYPE;
317      l_rowid       ROWID;
318      l_chg_num     igf_sl_dl_chg_send.chg_num%TYPE;
319 
320     BEGIN
321     -- ## Comparing the old field value with new field value, if any difference
322     -- ## exists a record is inserted in igf_sl_dl_chg_send table with the status as
323     -- ## Ready to send.
324 
325         IF   (p_field_lor IS NULL AND p_field_lor_loc IS NULL)
326         OR   (p_field_lor = p_field_lor_loc) THEN
327               NULL;
328         ELSE
329 
330             OPEN c_chg_code;
331             FETCH c_chg_code INTO lc_chg_code;
332             IF c_chg_code%NOTFOUND THEN
333                  CLOSE c_chg_code;
334                  fnd_message.set_name('IGF','IGF_SL_NO_CHG_CODE');
335                  fnd_message.set_token('FLD_NAME',  igf_aw_gen.lookup_desc('IGF_SL_LOAN_FIELDS', p_field_name));
336                  fnd_message.set_token('LOAN_CATG', igf_aw_gen.lookup_desc('IGF_SL_DL_LOAN_CATG',p_dl_loan_catg));
337                  fnd_message.set_token('DL_VERSION',igf_aw_gen.lookup_desc('IGF_SL_DL_VERSION',  lv_dl_version ));
338                  igs_ge_msg_stack.add;
339                  app_exception.raise_exception;
340             END IF;
341 
342              -- Directly setting to Send, as the Trans_rec() procedure picks up only the
343              -- picks up record belonging to this dbth_id
344 
345              igf_sl_dl_chg_send_pkg.insert_row (
346                            x_mode                              => 'R',
347                            x_rowid                             => l_rowid,
348                            X_chg_num                           => l_chg_num,
349                            X_dbth_id                           => lv_dbth_id,
350                            X_loan_number                       => lv_loan_number,
351                            X_chg_code                          => lc_chg_code.chg_code,
352                            X_new_value                         => p_field_lor,
353                            X_status                            => 'S'
354                                                     );
355                  p_chg_flg  := 'Y';    -- ## Set the chg flag as Y to indicate changes exists between 2 tables
356               CLOSE c_chg_code;    -- ## Close the Cursor
357 
358         END IF;
359 
360        EXCEPTION
361        WHEN OTHERS THEN
362            IF c_chg_code%ISOPEN THEN
363                 CLOSE c_chg_code;
364            END IF;
365            fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
366            fnd_message.set_token('NAME','IGF_SL_DL_CHG_ORIG.COMP_LOR_LOC');
367            fnd_file.put_line(fnd_file.log,SQLERRM);
368            igs_ge_msg_stack.add;
369            app_exception.raise_exception;
370     END comp_lor_loc;
371 
372 -- main
373 BEGIN
374 
375   retcode := 0;
376   igf_aw_gen.set_org_id(p_org_id);
377 
378   lv_cal_type    := rtrim(substr(p_award_year,1,10));
379   lv_cal_seq_num := rtrim(substr(p_award_year,11));
380 
381     --Get the alternate code
382   OPEN cur_alternate_code;
383   FETCH cur_alternate_code INTO l_alternate_code;
384   IF cur_alternate_code%NOTFOUND THEN
385      CLOSE cur_alternate_code;
386      fnd_message.set_name('IGF','IGF_SL_NO_CALENDAR');
387      IGS_GE_MSG_STACK.ADD;
388      fnd_file.put_line(fnd_file.log,fnd_message.get);
389 
390      app_exception.raise_exception;
391    END IF;
392      CLOSE cur_alternate_code;
393 
394   --Write the details of Parameters Passed into LOG File.
395   --Bug 2332668
396     l_i:=0;
397     OPEN cur_get_parameters;
398      LOOP
399       l_i:=l_i+1;
400      FETCH cur_get_parameters INTO l_para_rec(l_i);
401      EXIT WHEN cur_get_parameters%NOTFOUND;
402      END LOOP;
403      CLOSE cur_get_parameters;
404 
405     OPEN c_get_sch_code; FETCH c_get_sch_code INTO c_get_sch_code_rec; CLOSE c_get_sch_code;
406 
407         --Show the parameters passed
408         --Bug No:2332668
409         fnd_file.put_line(fnd_file.log,RPAD(l_para_rec(4),50,' '));
410         fnd_file.put_line(fnd_file.log,RPAD(l_para_rec(2),50,' ')||':'||RPAD(' ',4,' ')||l_alternate_code);
411         fnd_file.put_line(fnd_file.log,RPAD(l_para_rec(3),50,' ')||':'||RPAD(' ',4,' ')||l_para_rec(1));
412         fnd_file.put_line(fnd_file.log,RPAD(c_get_sch_code_rec.meaning,50,' ')||':'||RPAD(' ',4,' ')||p_school_code);
413 
414    IF  (igf_sl_dl_validation.check_full_participant (lv_cal_type, lv_cal_seq_num,'DL') ) THEN
415      -- Log an error message
416       fnd_message.set_name('IGF','IGF_SL_COD_NO_CHG_ORIG');
417        fnd_file.put_line(fnd_file.log,fnd_message.get);
418         raise yr_full_participant;
419     END IF;
420 
421   --Get the Direct Loan File Spec Version Bug :-2490289 DL Header and Trailer Formatting Error.
422   --Handled the NO_DATA_FOUND exception if the DL Setup record is not available
423   BEGIN
424   lv_dl_version := igf_sl_gen.get_dl_version(lv_cal_type, lv_cal_seq_num);
425   EXCEPTION
426   WHEN NO_DATA_FOUND THEN
427    fnd_message.set_name('IGF','IGF_SL_NO_DL_SETUP');
428    fnd_file.put_line(fnd_file.log,fnd_message.get);
429    RAISE NO_DATA_FOUND;
430   END;
431 
432   -- Initialise the Data Record field
433   lv_data_record := NULL;
434 
435   /************************************************************************
436      Using REF CURSORS.
437      Header Record specifications, for each Direct Loan Version
438      is specified in the igf_sl_dl_record.DLHeader_cur procedure.
439      By calling this procedure, the following are done
440        1. Computes Batch ID
441        2. Inserts the Batch ID details in igf_sl_dl_batch
442        3. For the specified version, Opens a REF CURSOR, having
443           header file Specs.
444      Since the Batch-Type and File-Specifications are same for STAFFORD
445      and PLUS, we are passing Loan_catg='DL' and File-Type='DL_CHG_SEND'
446      to DLHeader_Cur(). (Maintaining only 1 record in igf_sl_dl_file_type Seed table)
447   *************************************************************************/
448 
449   igf_sl_dl_record.DLHeader_cur(lv_dl_version, 'DL',
450                                 lv_cal_type, lv_cal_seq_num, 'DL_CHG_SEND', p_school_code,
451                                 lv_dbth_id, lv_batch_id, lv_mesg_class, Header_Rec);
452   FETCH Header_Rec into lv_data_record;
453 
454   IF Header_Rec%NOTFOUND THEN
455      fnd_message.set_name ('IGF', 'IGF_GE_HDR_CREATE_ERROR');
456      igs_ge_msg_stack.add;
457      app_exception.raise_exception;
458   END IF;
459 
460   -- FA 122 Loan Enhancements derive the paramters to be passed to the c_lor cursor
461   IF p_dl_loan_catg = 'DL_STAFFORD' THEN
462     l_fed_fund_1 := 'DLS';
463     l_fed_fund_2 := 'DLU';
464   ELSIF p_dl_loan_catg = 'DL_PLUS' THEN
465     l_fed_fund_1 := 'DLP';
466     l_fed_fund_2 := 'DLP';
467   END IF;
468 
469   -- ## Comparisons of Old records and the new records in c_lor cursor and igf_sl_lor_loc
470   -- ## Outer Loop get the various Loan ID for the Particular award year whereas the inner loop
471   -- ## gets the originated records for the particular loan ID and passes it to a procedure
472   -- ## called comp_lor_loc to check if any changes are there between 2 tables. If changes exists
473   -- ## returns a flag with status as Y
474 
475   FOR lc_lor IN c_lor(lv_cal_type,lv_cal_seq_num,l_fed_fund_1,l_fed_fund_2,'A','G','Y')
476   LOOP
477               BEGIN
478                 -- FA 122 Loan Enhancements Use the igf_sl_gen.get_person_details for getting the student as
479                  -- well as parent details.
480                  igf_sl_gen.get_person_details(lc_lor.student_id,student_dtl_cur);
481                  FETCH student_dtl_cur INTO student_dtl_rec;
482                  igf_sl_gen.get_person_details(lc_lor.p_person_id,parent_dtl_cur);
483                  FETCH parent_dtl_cur INTO parent_dtl_rec;
484 
485                  CLOSE student_dtl_cur;
486                  CLOSE parent_dtl_cur;
487 
488                 --Added Code to SKIP this LOAN instead of Raising an Exception
489                 --So that next correct record can be processed.
490                 --Raising Exception Code is being removed
491                 OPEN c_lor_loc(lc_lor.loan_id);
492                 FETCH c_lor_loc INTO lc_lor_loc;
493                 IF c_lor_loc%NOTFOUND THEN
494                        CLOSE c_lor_loc;
495                        fnd_message.set_name('IGF','IGF_SL_NO_LOR_LOC_REC');
496                        fnd_message.set_token('LOAN_NUMBER',lc_lor.loan_number);
497                        fnd_file.put_line(fnd_file.log,' ');
498                        fnd_file.put_line(fnd_file.log,fnd_message.get);
499 
500                        RAISE SKIP_LOAN;
501                 END IF;
502 
503                 --Added Code to SKIP this LOAN instead of Raising an Exception
504                 --So that next correct record can be processed.
505                 --Raising Exception Code is being removed
506                OPEN cur_isir_depend_status(lc_lor.base_id);
507                FETCH cur_isir_depend_status INTO l_dependency_status;
508                IF cur_isir_depend_status%NOTFOUND THEN
509                        CLOSE cur_isir_depend_status;
510                        fnd_message.set_name('IGF','IGF_GE_REC_NO_DATA_FOUND');
511                        fnd_message.set_token('P_RECORD',' Payment ISIR');
512                        fnd_file.put_line(fnd_file.log,' ');
513                        fnd_file.put_line(fnd_file.log,fnd_message.get);
514                        RAISE SKIP_LOAN;
515                END IF;
516 
517               --Code added for bug 3603289 start
518               l_driver_license_number := student_dtl_rec.p_license_num;
519               l_driver_license_state  := student_dtl_rec.p_license_state;
520               l_citizenship_status    := student_dtl_rec.p_citizenship_status;
521               l_alien_reg_number      := student_dtl_rec.p_alien_reg_num;
522               --Code added for bug 3603289 end
523 
524             -- PUT THE DEBUGGING LOG MESSAGES
525 
526               IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
527                  FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT,'igf.plsql.igf_sl_dl_chg_orig.chg_originate.debug','loan_number passed to igf_sl_dl_record.get_acad_cal_dtls:'|| lc_lor.loan_number);
528               END IF;
529                l_loan_number := lc_lor.loan_number ;
530                -- To get the academic begin and end dates.
531                -- masehgal   # 2593215   removed begin/end dates fetching functions
532                --                        used procedure get_acad_cal_dtls instead
533                igf_sl_dl_record.get_acad_cal_dtls ( l_loan_number,
534                                                     lv_acad_cal_type,
535                                                     lv_acad_seq_num,
536                                                     lv_begin_date,
537                                                     lv_end_date,
538                                                     lv_message ) ;
539 
540 
541               IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
542                    FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT,'igf.plsql.igf_sl_dl_chg_orig.chg_originate.debug','lv_message got from igf_sl_dl_record.get_acad_cal_dtls:'|| lv_message);
543               END IF;
544               IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
545                    FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT,'igf.plsql.igf_sl_dl_chg_orig.chg_originate.debug','lv_acad_begin_date got from igf_sl_dl_record.get_acad_cal_dtls:'|| lv_begin_date);
546               END IF;
547               IF FND_LOG.LEVEL_STATEMENT >= FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
548                    FND_LOG.STRING(FND_LOG.LEVEL_STATEMENT,'igf.plsql.igf_sl_dl_chg_orig.chg_originate.debug','lv_acad_end_date got from igf_sl_dl_record.get_acad_cal_dtls:'|| lv_end_date);
549               END IF;
550                     -- ## The If conditions checks if it is Plus records and else the Stafford records
551 
552                     lc_chg_flag      := 'N';
553                     lc_disb_chg_flag := 'N';
554                     lv_loan_number   := lc_lor.loan_number;
555 
556                     IF p_dl_loan_catg = 'DL_PLUS' THEN
557 
558 
559                        comp_lor_loc(SUBSTR(igf_ap_matching_process_pkg.remove_spl_chr(student_dtl_rec.p_ssn),1,9),
560                                     SUBSTR(igf_ap_matching_process_pkg.remove_spl_chr(lc_lor_loc.s_ssn),1,9),'S_SSN', lc_chg_flag);
561                        comp_lor_loc(UPPER(student_dtl_rec.p_first_name),UPPER(lc_lor_loc.s_first_name),'S_FIRST_NAME' ,lc_chg_flag);
562 
563 
564                        comp_lor_loc(UPPER(student_dtl_rec.p_last_name),UPPER(lc_lor_loc.s_last_name),'S_LAST_NAME',lc_chg_flag);
565                        comp_lor_loc(UPPER(student_dtl_rec.p_middle_name),UPPER(lc_lor_loc.s_middle_name),'S_MIDDLE_NAME',lc_chg_flag);
566                        comp_lor_loc(TO_CHAR(student_dtl_rec.p_date_of_birth,'YYYYMMDD'),TO_CHAR(lc_lor_loc.s_date_of_birth,'YYYYMMDD'),
567                                      'S_DATE_OF_BIRTH',lc_chg_flag);
568                        comp_lor_loc(lc_lor.s_default_status,lc_lor_loc.s_default_status,'S_DEFAULT_STATUS',lc_chg_flag);
569                        comp_lor_loc(SUBSTR(igf_ap_matching_process_pkg.remove_spl_chr(parent_dtl_rec.p_ssn),1,9),
570                                     SUBSTR(igf_ap_matching_process_pkg.remove_spl_chr(lc_lor_loc.p_ssn),1,9),'P_SSN',lc_chg_flag);
571                        comp_lor_loc(UPPER(parent_dtl_rec.p_first_name),UPPER(lc_lor_loc.p_first_name),'P_FIRST_NAME',lc_chg_flag);
572                        comp_lor_loc(UPPER(parent_dtl_rec.p_last_name),UPPER(lc_lor_loc.p_last_name),'P_LAST_NAME',lc_chg_flag);
573                        comp_lor_loc(UPPER(parent_dtl_rec.p_middle_name),UPPER(lc_lor_loc.p_middle_name),'P_MIDDLE_NAME',lc_chg_flag);
574                        comp_lor_loc( RPAD(NVL(UPPER(parent_dtl_rec.p_permt_addr1)    ||' '||UPPER(parent_dtl_rec.p_permt_addr2),' '),35),
575                                      RPAD(NVL(UPPER(lc_lor_loc.p_permt_addr1)||' '||UPPER(lc_lor_loc.p_permt_addr2),' '),35),
576                                      'P_PERMT_ADDR1',lc_chg_flag);
577                        comp_lor_loc(UPPER(parent_dtl_rec.p_permt_city),UPPER(lc_lor_loc.p_permt_city),'P_PERMT_CITY',lc_chg_flag);
578                        comp_lor_loc(UPPER(parent_dtl_rec.p_permt_state),UPPER(lc_lor_loc.p_permt_state),'P_PERMT_STATE',lc_chg_flag);
579                        comp_lor_loc(parent_dtl_rec.p_permt_zip,lc_lor_loc.p_permt_zip,'P_PERMT_ZIP',lc_chg_flag);
580                        comp_lor_loc(UPPER(parent_dtl_rec.p_license_state),UPPER(lc_lor_loc.p_license_state),'P_LICENSE_STATE',lc_chg_flag);
581                        comp_lor_loc(UPPER(parent_dtl_rec.p_license_num),UPPER(lc_lor_loc.p_license_num),'P_LICENSE_NUM',lc_chg_flag);
582                        comp_lor_loc(parent_dtl_rec.p_citizenship_status,lc_lor_loc.p_citizenship_status,'P_CITIZENSHIP_STATUS',lc_chg_flag);
583                        comp_lor_loc(parent_dtl_rec.p_alien_reg_num,lc_lor_loc.p_alien_reg_num,'P_ALIEN_REG_NUM',lc_chg_flag);
584                        comp_lor_loc(lc_lor.p_default_status,lc_lor_loc.p_default_status,'P_DEFAULT_STATUS',lc_chg_flag);
585                        comp_lor_loc(lc_lor.grade_level_code,lc_lor_loc.grade_level_code,'GRADE_LEVEL_CODE',lc_chg_flag);
586                        comp_lor_loc(LPAD(TO_CHAR(lc_lor.loan_amt_accepted),5,0),LPAD(TO_CHAR(lc_lor_loc.loan_amt_accepted),5,0),'LOAN_AMT_ACCEPTED',lc_chg_flag);
587                        comp_lor_loc(TO_CHAR(lc_lor.loan_per_begin_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.loan_per_begin_date,'YYYYMMDD'),
588                                       'LOAN_PER_BEGIN_DATE',lc_chg_flag);
589                        comp_lor_loc(TO_CHAR(lc_lor.loan_per_end_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.loan_per_end_date,'YYYYMMDD'),
590                                       'LOAN_PER_END_DATE',lc_chg_flag);
591                        comp_lor_loc(lc_lor.pnote_print_ind,lc_lor_loc.pnote_print_ind,'PNOTE_PRINT_IND',lc_chg_flag);
592                        comp_lor_loc(lc_lor.unsub_elig_for_heal,lc_lor_loc.unsub_elig_for_heal,'UNSUB_ELIG_FOR_HEAL',lc_chg_flag);
593                        comp_lor_loc(lc_lor.disclosure_print_ind,lc_lor_loc.disclosure_print_ind,'DISCLOSURE_PRINT_IND',lc_chg_flag);
594                        comp_lor_loc(LPAD(NVL(LTRIM(TO_CHAR(lc_lor.orig_fee_perct*1000,'00000')),'0'),5),LPAD(NVL(LTRIM(TO_CHAR(lc_lor_loc.orig_fee_perct*1000,'00000')),'0'),5),'ORIG_FEE_PERCT',lc_chg_flag);
595                        comp_lor_loc(lc_lor.unsub_elig_for_depnt,lc_lor_loc.unsub_elig_for_depnt,'UNSUB_ELIG_FOR_DEPNT',lc_chg_flag);
596                        comp_lor_loc(student_dtl_rec.p_email_addr,lc_lor_loc.s_email_addr,'S_EMAIL_ADDR',lc_chg_flag);
597                        comp_lor_loc(TO_CHAR(lv_begin_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.acad_yr_begin_date,'YYYYMMDD'),
598                                         'ACAD_YR_BEGIN_DATE',lc_chg_flag);
599                        comp_lor_loc(TO_CHAR(lv_end_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.acad_yr_end_date,'YYYYMMDD'),
600                                         'ACAD_YR_END_DATE',lc_chg_flag);
601 
602                        comp_lor_loc(l_citizenship_status,lc_lor_loc.s_citizenship_status,'S_CITIZENSHIP_STATUS',lc_chg_flag);
603                        comp_lor_loc(l_alien_reg_number,lc_lor_loc.s_alien_reg_num,'S_ALIEN_REG_NUM',lc_chg_flag);
604                        comp_lor_loc(l_dependency_status,lc_lor_loc.s_depncy_status,'S_DEPNCY_STATUS',lc_chg_flag);
605 
606                    ELSIF   p_dl_loan_catg = 'DL_STAFFORD' THEN
607 
608                         comp_lor_loc(SUBSTR(igf_ap_matching_process_pkg.remove_spl_chr(student_dtl_rec.p_ssn),1,9),
609                                      SUBSTR(igf_ap_matching_process_pkg.remove_spl_chr(lc_lor_loc.s_ssn),1,9),
610                                     'S_SSN', lc_chg_flag);
611                         comp_lor_loc(UPPER(student_dtl_rec.p_first_name),UPPER(lc_lor_loc.s_first_name),'S_FIRST_NAME',lc_chg_flag);
612                         comp_lor_loc(UPPER(student_dtl_rec.p_last_name),UPPER(lc_lor_loc.s_last_name),'S_LAST_NAME',lc_chg_flag);
613                         comp_lor_loc(UPPER(student_dtl_rec.p_middle_name),UPPER(lc_lor_loc.s_middle_name),'S_MIDDLE_NAME',lc_chg_flag);
614                         comp_lor_loc( RPAD(NVL(UPPER(student_dtl_rec.p_permt_addr1)    ||' '||UPPER(student_dtl_rec.p_permt_addr2),' '),35),
615                                       RPAD(NVL(UPPER(lc_lor_loc.s_permt_addr1)||' '||UPPER(lc_lor_loc.s_permt_addr2),' '),35),
616                                       'S_PERMT_ADDR1',lc_chg_flag);
617                         comp_lor_loc(UPPER(student_dtl_rec.p_permt_city),UPPER(lc_lor_loc.s_permt_city),'S_PERMT_CITY',lc_chg_flag);
618                         comp_lor_loc(UPPER(student_dtl_rec.p_permt_state),UPPER(lc_lor_loc.s_permt_state),'S_PERMT_STATE',lc_chg_flag);
619                         comp_lor_loc(student_dtl_rec.p_permt_zip,lc_lor_loc.s_permt_zip,'S_PERMT_ZIP',lc_chg_flag);
620 
621                         comp_lor_loc(lc_lor.s_default_status,lc_lor_loc.s_default_status,'S_DEFAULT_STATUS',lc_chg_flag);
622                         comp_lor_loc(lc_lor.grade_level_code,lc_lor_loc.grade_level_code,'GRADE_LEVEL_CODE',lc_chg_flag);
623                         comp_lor_loc(LPAD(TO_CHAR(NVL(lc_lor.loan_amt_accepted,0)),5,0),LPAD(TO_CHAR(lc_lor_loc.loan_amt_accepted),5,0),'LOAN_AMT_ACCEPTED',lc_chg_flag);
624                         comp_lor_loc(TO_CHAR(lc_lor.loan_per_begin_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.loan_per_begin_date,'YYYYMMDD'),
625                                        'LOAN_PER_BEGIN_DATE',lc_chg_flag);
626                         comp_lor_loc(TO_CHAR(lc_lor.loan_per_end_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.loan_per_end_date,'YYYYMMDD'),
627                                        'LOAN_PER_END_DATE',lc_chg_flag);
628                         comp_lor_loc(lc_lor.pnote_print_ind,lc_lor_loc.pnote_print_ind,'PNOTE_PRINT_IND',lc_chg_flag);
629                         comp_lor_loc( RPAD(NVL(UPPER(student_dtl_rec.p_local_addr1)    ||' '||UPPER(student_dtl_rec.p_local_addr2),' '),35),
630                                       RPAD(NVL(UPPER(lc_lor_loc.s_local_addr1)||' '||UPPER(lc_lor_loc.s_local_addr2),' '),35),
631                                       'S_LOCAL_ADDR1',lc_chg_flag);
632                         comp_lor_loc(UPPER(student_dtl_rec.p_local_city),UPPER(lc_lor_loc.s_local_city),'S_LOCAL_CITY',lc_chg_flag);
633                         comp_lor_loc(UPPER(student_dtl_rec.p_local_state),UPPER(lc_lor_loc.s_local_state),'S_LOCAL_STATE',lc_chg_flag);
634                         comp_lor_loc(student_dtl_rec.p_local_zip,lc_lor_loc.s_local_zip,'S_LOCAL_ZIP',lc_chg_flag);
635                         comp_lor_loc(lc_lor.unsub_elig_for_heal,lc_lor_loc.unsub_elig_for_heal,'UNSUB_ELIG_FOR_HEAL',lc_chg_flag);
636                         comp_lor_loc(lc_lor.disclosure_print_ind,lc_lor_loc.disclosure_print_ind,'DISCLOSURE_PRINT_IND',lc_chg_flag);
637                         comp_lor_loc(LPAD(NVL(LTRIM(TO_CHAR(lc_lor.orig_fee_perct*1000,'00000')),'0'),5),
638                                      LPAD(NVL(LTRIM(TO_CHAR(lc_lor_loc.orig_fee_perct*1000,'00000')),'0'),5),'ORIG_FEE_PERCT', lc_chg_flag);
639                         comp_lor_loc(lc_lor.unsub_elig_for_depnt,lc_lor_loc.unsub_elig_for_depnt,'UNSUB_ELIG_FOR_DEPNT',lc_chg_flag);
640                         comp_lor_loc(student_dtl_rec.p_email_addr,lc_lor_loc.s_email_addr,'S_EMAIL_ADDR',lc_chg_flag);
641                         comp_lor_loc(TO_CHAR(lv_begin_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.acad_yr_begin_date,'YYYYMMDD'),
642                                       'ACAD_YR_BEGIN_DATE',lc_chg_flag);
643                         comp_lor_loc(TO_CHAR(lv_end_date,'YYYYMMDD'),TO_CHAR(lc_lor_loc.acad_yr_end_date,'YYYYMMDD'),
644                                       'ACAD_YR_END_DATE',lc_chg_flag);
645 
646                         comp_lor_loc(UPPER(l_driver_license_state),UPPER(lc_lor_loc.s_license_state),'S_LICENSE_STATE',lc_chg_flag);
647                         comp_lor_loc(UPPER(l_driver_license_number),UPPER(lc_lor_loc.s_license_num),'S_LICENSE_NUM',lc_chg_flag);
648                         comp_lor_loc(l_dependency_status,lc_lor_loc.s_depncy_status,'S_DEPNCY_STATUS',lc_chg_flag);
649                         comp_lor_loc(l_citizenship_status,lc_lor_loc.s_citizenship_status,'S_CITIZENSHIP_STATUS',lc_chg_flag);
650                         comp_lor_loc(l_alien_reg_number,lc_lor_loc.s_alien_reg_num,'S_ALIEN_REG_NUM',lc_chg_flag);
651 
652                     END IF;
653 
654                     -- ## This loop is to calculate the disbursement based records. initially it is set to NULL and
655                     -- ## the record is fetced from the igf_aw_awd_disb and origination table. The condition is made
656                     -- ## in such a way that even if a Disbursement is Deleted, we still need to send Disb-gross-amt
657                     -- ## as ZERO and disb-date as blank we need to overwrite these values at the LOC also.
658                     -- ## So, 3 scenarios possible are
659                     -- ##      - No. of Disbursement in IGF_AW_AWD_DISB = No. of Disb in IGF_SL_AWD_DISB_LOC
660                     -- ##        and Disb-gross-amt and disb-date may be same or different.
661                     -- ##      - A New disbursment is added in IGF_AW_AWD_DISB
662                     -- ##      - A disbursement is deleted in IGF_AW_AWD_DISB.
663 
664 
665                      l_disb     := TRUE;
666                      l_disb_loc := TRUE;
667                      OPEN cur_award(lc_lor.award_id);
668                      OPEN cur_disb_loc(lc_lor.award_id);
669                      LOOP
670                                     lcur_disb_loc.disb_num           := NULL;
671                                     lcur_disb_loc.disb_date          := NULL;
672                                     lcur_disb_loc.disb_gross_amt     := NULL;
673                                     lcur_award.disb_num              := NULL;
674                                     lcur_award.disb_date             := NULL;
675                                     lcur_award.disb_accepted_amt     := NULL;
676 
677                                     FETCH cur_award INTO lcur_award;
678                                     IF cur_award%NOTFOUND THEN
679                                         l_disb := FALSE;
680                                     END IF;
681 
682                                     FETCH cur_disb_loc INTO lcur_disb_loc;
683                                     IF cur_disb_loc%NOTFOUND THEN
684                                         l_disb_loc := FALSE;
685                                     END IF;
686 
687                                     IF l_disb_loc = FALSE AND l_disb = FALSE THEN
688                                          EXIT;
689                                     END IF;
690 
691                                     comp_lor_loc( LPAD(TO_CHAR(NVL(lcur_award.disb_accepted_amt,0)),5,0), LPAD(TO_CHAR(NVL(lcur_disb_loc.disb_gross_amt,0)),5,0),
692                                        'DISB_GROSS_AMT'||'_'||NVL(lcur_disb_loc.disb_num,lcur_award.disb_num), lc_disb_chg_flag);
693                                     comp_lor_loc(TO_CHAR(lcur_award.disb_date,'YYYYMMDD'),TO_CHAR(lcur_disb_loc.disb_date,'YYYYMMDD'),
694                                        'DISB_DATE'||'_'||NVL(lcur_disb_loc.disb_num,lcur_award.disb_num), lc_disb_chg_flag);
695 
696                       END LOOP;
697                       CLOSE cur_award;
698                       CLOSE cur_disb_loc;
699 
700 
701                        IF lc_chg_flag ='Y' or lc_disb_chg_flag='Y' THEN
702                            lc_header_flag := 'Y';
703                        END IF;
704 
705                    -- ## The lc_chg_flag is the out NOCOPY parameter from the comp_lor_loc procedure, even if one changed column
706                    -- ## exists then the flag is set to Y and depending on that the igf_sl_lor_loc table is updated with
707                    -- ## the new value(changed value). In case of disbursement records if any changes exists then the
708                    -- ## igf_sl_awd_disb_loc table is deleted for the particular award Id and the new value from the
709                    -- ## igf_aw_awd_disb is inserted into this table.
710 
711                     IF lc_chg_flag ='Y' THEN
712 
713                        -- Update the igf_sl_lor_loc table with the New Values(Changes values)
714                        igf_sl_lor_loc_pkg.update_row (
715                                                  X_Mode                              => 'R',
716                                                  x_rowid                             => lc_lor_loc.row_id,
717                                                  x_loan_id                           => lc_lor_loc.loan_id,
718                                                  x_origination_id                    => lc_lor_loc.origination_id,
719                                                  x_loan_number                       => lc_lor_loc.loan_number,
720                                                  x_loan_type                         => lc_lor_loc.loan_type,
721                                                  x_loan_amt_offered                  => lc_lor_loc.loan_amt_offered,
722                                                  x_loan_amt_accepted                 => lc_lor.loan_amt_accepted,
723                                                  x_loan_per_begin_date               => lc_lor.loan_per_begin_date,
724                                                  x_loan_per_end_date                 => lc_lor.loan_per_end_date,
725                                                  X_acad_yr_begin_date                => lc_lor_loc.acad_yr_begin_date,
726                                                  X_acad_yr_end_date                  => lc_lor_loc.acad_yr_end_date,
727                                                  x_loan_status                       => lc_lor_loc.loan_status,
728                                                  x_loan_status_date                  => lc_lor_loc.loan_status_date,
729                                                  x_loan_chg_status                   => lc_lor_loc.loan_chg_status,
730                                                  x_loan_chg_status_date              => lc_lor_loc.loan_chg_status_date,
731                                                  x_req_serial_loan_code              => lc_lor_loc.req_serial_loan_code,
732                                                  x_act_serial_loan_code              => lc_lor_loc.act_serial_loan_code,
733                                                  x_active                            => lc_lor_loc.active,
734                                                  x_active_date                       => lc_lor_loc.active_date,
735                                                  x_sch_cert_date                     => lc_lor_loc.sch_cert_date,
736                                                  x_orig_status_flag                  => lc_lor_loc.orig_status_flag,
737                                                  x_orig_batch_id                     => lc_lor_loc.orig_batch_id,
738                                                  x_orig_batch_date                   => lc_lor_loc.orig_batch_date,
739                                                  x_chg_batch_id                      => NULL,
740                                                  x_orig_ack_date                     => lc_lor_loc.orig_ack_date,
741                                                  x_credit_override                   => lc_lor_loc.credit_override,
742                                                  x_credit_decision_date              => lc_lor_loc.credit_decision_date,
743                                                  x_pnote_delivery_code               => lc_lor_loc.pnote_delivery_code,
744                                                  x_pnote_status                      => lc_lor_loc.pnote_status,
745                                                  x_pnote_status_date                 => lc_lor_loc.pnote_status_date,
746                                                  x_pnote_id                          => lc_lor_loc.pnote_id,
747                                                  x_pnote_print_ind                   => lc_lor.pnote_print_ind,
748                                                  x_pnote_accept_amt                  => lc_lor_loc.pnote_accept_amt,
749                                                  x_pnote_accept_date                 => lc_lor_loc.pnote_accept_date,
750                                                  x_p_signature_code                  => lc_lor_loc.p_signature_code,
751                                                  x_p_signature_date                  => lc_lor_loc.p_signature_date,
752                                                  x_s_signature_code                  => lc_lor_loc.s_signature_code,
753                                                  x_unsub_elig_for_heal               => lc_lor.unsub_elig_for_heal,
754                                                  x_disclosure_print_ind              => lc_lor.disclosure_print_ind,
755                                                  x_orig_fee_perct                    => lc_lor.orig_fee_perct,
756                                                  x_borw_confirm_ind                  => lc_lor_loc.borw_confirm_ind,
757                                                  x_borw_interest_ind                 => lc_lor_loc.borw_interest_ind,
758                                                  x_unsub_elig_for_depnt              => lc_lor.unsub_elig_for_depnt,
759                                                  x_guarantee_amt                     => lc_lor_loc.guarantee_amt,
760                                                  x_guarantee_date                    => lc_lor_loc.guarantee_date,
761                                                  x_guarnt_adj_ind                    => lc_lor_loc.guarnt_adj_ind,
762                                                  x_guarnt_amt_redn_code              => lc_lor_loc.guarnt_amt_redn_code,
763                                                  x_guarnt_status_code                => lc_lor_loc.guarnt_status_code,
764                                                  x_guarnt_status_date                => lc_lor_loc.guarnt_status_date,
765                                                  x_lend_apprv_denied_code            => NULL,
766                                                  x_lend_apprv_denied_date            => NULL,
767                                                  x_lend_status_code                  => lc_lor_loc.lend_status_code,
768                                                  x_lend_status_date                  => lc_lor_loc.lend_status_date,
769                                                  x_grade_level_code                  => lc_lor.grade_level_code,
770                                                  x_enrollment_code                   => lc_lor_loc.enrollment_code,
771                                                  x_anticip_compl_date                => lc_lor_loc.anticip_compl_date,
772                                                  x_borw_lender_id                    => lc_lor_loc.borw_lender_id,
773                                                  x_duns_borw_lender_id               => NULL,
774                                                  x_guarantor_id                      => lc_lor_loc.guarantor_id,
775                                                  x_duns_guarnt_id                    => NULL,
776                                                  x_prc_type_code                     => lc_lor_loc.prc_type_code,
777                                                  x_rec_type_ind                      => lc_lor_loc.rec_type_ind,
778                                                  x_cl_loan_type                      => lc_lor_loc.cl_loan_type,
779                                                  x_cl_seq_number                     => lc_lor_loc.cl_seq_number,
780                                                  x_last_resort_lender                => lc_lor_loc.last_resort_lender,
781                                                  x_lender_id                         => lc_lor_loc.lender_id,
782                                                  x_duns_lender_id                    => NULL,
783                                                  x_lend_non_ed_brc_id                => lc_lor_loc.lend_non_ed_brc_id,
784                                                  x_recipient_id                      => lc_lor_loc.recipient_id,
785                                                  x_recipient_type                    => lc_lor_loc.recipient_type,
786                                                  x_duns_recip_id                     => NULL,
787                                                  x_recip_non_ed_brc_id               => lc_lor_loc.recip_non_ed_brc_id,
788                                                  x_cl_rec_status                     => NULL,
789                                                  x_cl_rec_status_last_update         => NULL,
790                                                  x_alt_prog_type_code                => lc_lor_loc.alt_prog_type_code,
791                                                  x_alt_appl_ver_code                 => lc_lor_loc.alt_appl_ver_code,
792                                                  x_borw_outstd_loan_code             => lc_lor_loc.borw_outstd_loan_code,
793                                                  x_mpn_confirm_code                  => NULL,
794                                                  x_resp_to_orig_code                 => lc_lor_loc.resp_to_orig_code,
795                                                  x_appl_loan_phase_code              => NULL,
796                                                  x_appl_loan_phase_code_chg          => NULL,
797                                                  x_tot_outstd_stafford               => lc_lor_loc.tot_outstd_stafford,
798                                                  x_tot_outstd_plus                   => lc_lor_loc.tot_outstd_plus,
799                                                  x_alt_borw_tot_debt                 => lc_lor_loc.alt_borw_tot_debt,
800                                                  x_act_interest_rate                 => lc_lor_loc.act_interest_rate,
801                                                  x_service_type_code                 => lc_lor_loc.service_type_code,
802                                                  x_rev_notice_of_guarnt              => lc_lor_loc.rev_notice_of_guarnt,
803                                                  x_sch_refund_amt                    => lc_lor_loc.sch_refund_amt,
804                                                  x_sch_refund_date                   => lc_lor_loc.sch_refund_date,
805                                                  x_uniq_layout_vend_code             => lc_lor_loc.uniq_layout_vend_code,
806                                                  x_uniq_layout_ident_code            => lc_lor_loc.uniq_layout_ident_code,
807                                                  x_p_person_id                       => lc_lor_loc.p_person_id,
808                                                  x_p_ssn                             => parent_dtl_rec.p_ssn,
809                                                  x_p_ssn_chg_date                    => NULL,
810                                                  x_p_last_name                       => parent_dtl_rec.p_last_name,
811                                                  x_p_first_name                      => parent_dtl_rec.p_first_name,
812                                                  x_p_middle_name                     => parent_dtl_rec.p_middle_name,
813                                                  x_p_permt_addr1                     => parent_dtl_rec.p_permt_addr1,
814                                                  x_p_permt_addr2                     => parent_dtl_rec.p_permt_addr2,
815                                                  x_p_permt_city                      => parent_dtl_rec.p_permt_city,
816                                                  x_p_permt_state                     => parent_dtl_rec.p_permt_state,
817                                                  x_p_permt_zip                       => parent_dtl_rec.p_permt_zip,
818                                                  x_p_permt_addr_chg_date             => NULL,
819                                                  x_p_permt_phone                     => lc_lor_loc.p_permt_phone,
820                                                  x_p_email_addr                      => parent_dtl_rec.p_email_addr,
821                                                  x_p_date_of_birth                   => parent_dtl_rec.p_date_of_birth,
822                                                  x_p_dob_chg_date                    => NULL,
823                                                  x_p_license_num                     => parent_dtl_rec.p_license_num,
824                                                  x_p_license_state                   => parent_dtl_rec.p_license_state,
825                                                  x_p_citizenship_status              => parent_dtl_rec.p_citizenship_status,
826                                                  x_p_alien_reg_num                   => parent_dtl_rec.p_alien_reg_num,
827                                                  x_p_default_status                  => lc_lor.p_default_status,
828                                                  x_p_foreign_postal_code             => NULL,
829                                                  x_p_state_of_legal_res              => parent_dtl_rec.p_state_of_legal_res,
830                                                  x_p_legal_res_date                  => parent_dtl_rec.p_legal_res_date,
831                                                  x_s_ssn                             => student_dtl_rec.p_ssn,
832                                                  x_s_ssn_chg_date                    => NULL,
833                                                  x_s_last_name                       => student_dtl_rec.p_last_name,
834                                                  x_s_first_name                      => student_dtl_rec.p_first_name,
835                                                  x_s_middle_name                     => student_dtl_rec.p_middle_name,
836                                                  x_s_permt_addr1                     => student_dtl_rec.p_permt_addr1,
837                                                  x_s_permt_addr2                     => student_dtl_rec.p_permt_addr2,
838                                                  x_s_permt_city                      => student_dtl_rec.p_permt_city,
839                                                  x_s_permt_state                     => student_dtl_rec.p_permt_state,
840                                                  x_s_permt_zip                       => student_dtl_rec.p_permt_zip,
841                                                  x_s_permt_addr_chg_date             => NULL,
842                                                  x_s_permt_phone                     => lc_lor_loc.s_permt_phone,
843                                                  x_s_local_addr1                     => student_dtl_rec.p_local_addr1,
844                                                  x_s_local_addr2                     => student_dtl_rec.p_local_addr2,
845                                                  x_s_local_city                      => student_dtl_rec.p_local_city,
846                                                  x_s_local_state                     => student_dtl_rec.p_local_state,
847                                                  x_s_local_zip                       => student_dtl_rec.p_local_zip,
848                                                  x_s_local_addr_chg_date             => NULL,
849                                                  x_s_email_addr                      => student_dtl_rec.p_email_addr,
850                                                  x_s_date_of_birth                   => student_dtl_rec.p_date_of_birth,
851                                                  x_s_dob_chg_date                    => NULL,
852                                                  x_s_license_num                     => l_driver_license_number,
853                                                  x_s_license_state                   => l_driver_license_state,
854                                                  x_s_depncy_status                   => l_dependency_status,
855                                                  x_s_default_status                  => lc_lor.s_default_status,
856                                                  x_s_citizenship_status              => l_citizenship_status,
857                                                  x_s_alien_reg_num                   => l_alien_reg_number,
858                                                  x_s_foreign_postal_code             => NULL,
859                                                  x_pnote_batch_id                    => lc_lor.pnote_batch_id,
860                                                  x_pnote_ack_date                    => lc_lor.pnote_ack_date,
861                                                  x_pnote_mpn_ind                     => lc_lor.pnote_mpn_ind ,
862                                                  x_award_id                          => lc_lor_loc.award_id,
863                                                  x_base_id                           => lc_lor_loc.base_id,
864                                                  x_document_id_txt                   => lc_lor_loc.document_id_txt,
865                                                  x_loan_key_num                      => lc_lor_loc.loan_key_num,
866                                                  x_interest_rebate_percent_num       => lc_lor_loc.interest_rebate_percent_num,
867                                                  x_fin_award_year                    => lc_lor_loc.fin_award_year,
868                                                  x_cps_trans_num                     => lc_lor_loc.cps_trans_num,
869                                                  x_atd_entity_id_txt                 => lc_lor_loc.atd_entity_id_txt,
870                                                  x_rep_entity_id_txt                 => lc_lor_loc.rep_entity_id_txt,
871                                                  x_source_entity_id_txt              => lc_lor_loc.source_entity_id_txt,
872                                                  x_pymt_servicer_amt                 => lc_lor_loc.pymt_servicer_amt,
873                                                  x_pymt_servicer_date                => lc_lor_loc.pymt_servicer_date,
874                                                  x_book_loan_amt                     => lc_lor_loc.book_loan_amt,
875                                                  x_book_loan_amt_date                => lc_lor_loc.book_loan_amt_date,
876                                                  x_s_chg_birth_date                  => lc_lor_loc.s_chg_birth_date,
877                                                  x_s_chg_ssn                         => lc_lor_loc.s_chg_ssn,
878                                                  x_s_chg_last_name                   => lc_lor_loc.s_chg_last_name,
879                                                  x_b_chg_birth_date                  => lc_lor_loc.b_chg_birth_date,
880                                                  x_b_chg_ssn                         => lc_lor_loc.b_chg_ssn,
881                                                  x_b_chg_last_name                   => lc_lor_loc.b_chg_last_name,
882                                                  x_note_message                      => lc_lor_loc.note_message,
883                                                  x_full_resp_code                    => lc_lor_loc.full_resp_code,
884                                                  x_s_permt_county                    => lc_lor_loc.s_permt_county,
885                                                  x_b_permt_county                    => lc_lor_loc.b_permt_county,
886                                                  x_s_permt_country                   => lc_lor_loc.s_permt_country,
887                                                  x_b_permt_country                   => lc_lor_loc.b_permt_country,
888                                                  x_crdt_decision_status              => lc_lor_loc.crdt_decision_status,
889                                                  x_external_loan_id_txt              => lc_lor_loc.external_loan_id_txt,
890                                                  x_deferment_request_code            => lc_lor_loc.deferment_request_code,
891                                                  x_eft_authorization_code            => lc_lor_loc.eft_authorization_code,
892                                                  x_requested_loan_amt                => lc_lor_loc.requested_loan_amt,
893                                                  x_actual_record_type_code           => lc_lor_loc.actual_record_type_code,
894                                                  x_reinstatement_amt                 => lc_lor_loc.reinstatement_amt,
895                                                  x_lender_use_txt                    => lc_lor_loc.lender_use_txt,
896                                                  x_guarantor_use_txt                 => lc_lor_loc.guarantor_use_txt,
897                                                  x_fls_approved_amt                  => lc_lor_loc.fls_approved_amt,
898                                                  x_flu_approved_amt                  => lc_lor_loc.flu_approved_amt,
899                                                  x_flp_approved_amt                  => lc_lor_loc.flp_approved_amt,
900                                                  x_alt_approved_amt                  => lc_lor_loc.alt_approved_amt,
901                                                  x_loan_app_form_code                => lc_lor_loc.loan_app_form_code,
902                                                  x_alt_borrower_ind_flag             => lc_lor_loc.alt_borrower_ind_flag,
903                                                  x_school_id_txt                     => lc_lor_loc.school_id_txt,
904                                                  x_cost_of_attendance_amt            => lc_lor_loc.cost_of_attendance_amt,
905                                                  x_established_fin_aid_amount        => lc_lor_loc.established_fin_aid_amount,
906                                                  x_student_electronic_sign_flag      => lc_lor_loc.student_electronic_sign_flag,
907                                                  x_mpn_type_flag                     => lc_lor_loc.mpn_type_flag,
908                                                  x_school_use_txt                    => lc_lor_loc.school_use_txt,
909                                                  x_expect_family_contribute_amt      => lc_lor_loc.expect_family_contribute_amt,
910                                                  x_borower_electronic_sign_flag      => lc_lor_loc.borower_electronic_sign_flag,
911                                                  x_borower_credit_authoriz_flag      => lc_lor_loc.borower_credit_authoriz_flag ,
912                                                  x_esign_src_typ_cd                  => lc_lor_loc.esign_src_typ_cd
913                                                  );
914 
915 
916                     END IF;
917 
918                      -- ## If any comparison difference exists for disbursement records
919                      -- ##  then delete the particular award id consisting of old records and
920                      -- ##  insert new records of from lor loc
921 
922                      IF lc_disb_chg_flag ='Y' THEN
923 
924                                   FOR lcur_disb_loc IN cur_disb_loc(lc_lor.award_id)
925                                   LOOP
926 
927                                    -- ## Delete the records from the LOC table.
928 
929                                     igf_sl_awd_disb_loc_pkg.delete_row (lcur_disb_loc.row_id);
930 
931                                    END LOOP;
932 
933                                        -- ## Insert the new record from igf_aw_awd record to igf_aw_awd_disb_loc table
934 
935                                    FOR lcur_award IN cur_award(lc_lor.award_id)
936                                    LOOP
937                                        igf_sl_awd_disb_loc_pkg.insert_row (
938                                                         x_mode                              => 'R',
939                                                         x_rowid                             => l_rowid,
940                                                         X_award_id                          => lcur_award.award_id,
941                                                         X_disb_num                          => lcur_award.disb_num,
942                                                         X_disb_gross_amt                    => lcur_award.disb_accepted_amt,
943                                                         X_fee_1                             => lcur_award.fee_1,
944                                                         X_fee_2                             => lcur_award.fee_1,
945                                                         X_disb_net_amt                      => lcur_award.disb_net_amt,
946                                                         X_disb_date                         => lcur_award.disb_date,
947                                                         X_hold_rel_ind                      => lcur_award.hold_rel_ind,
948                                                         X_fee_paid_1                        => lcur_award.fee_paid_1,
949                                                         X_fee_paid_2                        => lcur_award.fee_paid_2
950                                                         );
951 
952                                   END LOOP;
953                       END IF;
954 
955                       -- ## Update LOAN_STATUS, LOAN_STATUS_DATE to SENT, Current Date In IGF_SL_LOANS TABLE
956 
957                       IF lc_chg_flag='Y' or lc_disb_chg_flag='Y' THEN
958                                DECLARE
959                                   lv_row_id  VARCHAR2(25);
960                                   CURSOR c_tbh_cur IS
961                                          SELECT igf_sl_loans.* FROM igf_sl_loans
962                                          WHERE loan_id =lc_lor.loan_id;
963                                BEGIN
964 
965                                     FOR tbh_rec in c_tbh_cur LOOP
966 
967                                     -- ## Update the Loan Change Status as Sent and Loan Change status date as the current date
968                                     -- Modified the update row call of the IGF_SL_LOANS_PKG package to include Borrower
969                                     -- determination as part of Refunds DLD - 2144600
970                                        igf_sl_loans_pkg.update_row (
971                                                x_Mode                              => 'R',
972                                                x_rowid                             => tbh_rec.row_id,
973                                                x_loan_id                           => lc_lor.loan_id,
974                                                x_award_id                          => tbh_rec.award_id,
975                                                x_seq_num                           => tbh_rec.seq_num,
976                                                x_loan_number                       => tbh_rec.loan_number,
977                                                x_loan_per_begin_date               => tbh_rec.loan_per_begin_date,
978                                                x_loan_per_end_date                 => tbh_rec.loan_per_end_date,
979                                                x_loan_status                       => tbh_rec.loan_status,
980                                                x_loan_status_date                  => tbh_rec.loan_status_date,
981                                                x_loan_chg_status                   => 'S',     -- ## Change the loan change status as send
982                                                x_loan_chg_status_date              => TRUNC(SYSDATE), -- ## Change the loan change date as sysdate
983                                                x_active                            => tbh_rec.active,
984                                                x_active_date                       => tbh_rec.active_date,
985                                                x_borw_detrm_code                   => tbh_rec.borw_detrm_code,
986                                                x_external_loan_id_txt              => tbh_rec.external_loan_id_txt
987 
988                                                );
989 
990 
991                                       IF l_display <> 'Y' THEN
992                                        --Display mesg in LOG File that Change Records have been originated and an Output file has been created.
993                                          fnd_message.set_name('IGF','IGF_SL_LOAN_CHG_ORIG');
994                                          fnd_message.set_token('LOAN_CATEG',l_para_rec(1));
995                                          fnd_message.set_token('FILE_VERSION',lv_dl_version);
996                                          fnd_file.put_line(fnd_file.log,fnd_message.get);
997                                          l_display :='Y';
998                                       END IF;
999 
1000 
1001                                     END LOOP;
1002                               END;
1003                       END IF;
1004 
1005                    CLOSE cur_isir_depend_status;
1006                    CLOSE c_lor_loc;
1007 
1008                    EXCEPTION
1009                       WHEN SKIP_LOAN THEN
1010                           NULL;
1011                    END;
1012 --      END IF;
1013   END LOOP;
1014 
1015 
1016     -- ## If there are any changes then create a header record
1017 
1018     IF lc_header_flag= 'Y' THEN
1019 
1020           -- Write the Header Record into the Output file.
1021           fnd_file.put_line(FND_FILE.OUTPUT, lv_data_record);
1022 
1023            --Formulating the Transaction Record
1024 
1025          BEGIN
1026 
1027             --Calls a Procedure to create a Transaction record in the File.
1028 
1029             Trans_Rec(lv_dl_version,lv_dbth_id,lv_batch_id,p_tot_rec_count);
1030 
1031          END;
1032 
1033 
1034          -- Initialise the Data Record field
1035        lv_data_record := NULL;
1036 
1037        -- Write the Trailer Record
1038        igf_sl_dl_record.DLTrailer_cur(lv_dl_version, p_tot_rec_count, Trailer_Rec);
1039        FETCH Trailer_Rec into lv_data_record;
1040        IF Trailer_Rec%NOTFOUND THEN
1041           fnd_message.set_name ('IGF', 'IGF_GE_TRL_CREATE_ERROR');
1042           igs_ge_msg_stack.add;
1043           app_exception.raise_exception;
1044        END IF;
1045 
1046        -- Write the Trailer Record into the Output file.
1047        fnd_file.put_line(FND_FILE.OUTPUT, lv_data_record);
1048 
1049    ELSE
1050       -- We need to do a rollback as we would have inserted into IGF_SL_DL_BATCH
1051       -- table while calling igf_sl_dl_record.DLHeader_cur.
1052       ROLLBACK;
1053    END IF;
1054 
1055    --Display a message if No Loan Change Origination
1056    --Bug No:2332668
1057    IF l_display='N' THEN
1058        fnd_file.put_line(fnd_file.log,' ');
1059        fnd_file.put_line(fnd_file.log,' ');
1060        fnd_message.set_name('IGF','IGF_SL_NO_LOAN_CHG_ORIG');
1061        fnd_file.put_line(fnd_file.log,fnd_message.get);
1062 
1063    END IF;
1064 
1065 
1066 COMMIT;
1067 
1068 EXCEPTION
1069     WHEN NO_DATA_FOUND THEN
1070     NULL;
1071     WHEN yr_full_participant THEN
1072     NULL;
1073 
1074     WHEN OTHERS THEN
1075        ROLLBACK;
1076        IF c_lor_loc%ISOPEN THEN
1077           CLOSE c_lor_loc;
1078        END IF;
1079        IF cur_isir_depend_status%ISOPEN THEN
1080           CLOSE cur_isir_depend_status;
1081        END IF;
1082        IF cur_award%ISOPEN THEN
1083           CLOSE cur_award;
1084        END IF;
1085        IF cur_disb_loc%ISOPEN THEN
1086           CLOSE cur_disb_loc;
1087        END IF;
1088        retcode := 2;
1089        errbuf := fnd_message.get_string('IGS','IGS_GE_UNHANDLED_EXCEPTION');
1090        fnd_file.put_line(fnd_file.log,SQLERRM);
1091        igs_ge_msg_stack.conc_exception_hndl;
1092  END chg_originate;
1093 
1094 
1095 
1096 
1097 PROCEDURE Trans_Rec( p_dl_version           igf_lookups_view.lookup_code%TYPE,
1098                      p_dl_dbth_id           igf_sl_dl_batch.dbth_id%TYPE,
1099                      p_dl_batch_id          igf_sl_dl_batch.batch_id%TYPE,
1100                      p_tot_rec_count        IN OUT NOCOPY NUMBER)
1101 AS
1102   /*************************************************************
1103   Created By : prchandr
1104   Date Created On : 2000/11/13
1105   Purpose : To create the Transaction Record
1106   Know limitations, enhancements or remarks
1107   Change History
1108   Bug:-2255281
1109   Desc:-DL Version Change
1110   Who             When            What
1111   vvutukur        21-Feb-2003     Enh#2758823.FA117 Build. Modified the if condition to include 03-04 removing 02-03.
1112                                   ie., Changed IF p_dl_version IN ('2001-2002','2002-2003') to IF p_dl_version IN ('2002-2003','2003-2004').
1113   mesriniv        13-MAR-2002     Added DL Version 2002-2003
1114   (reverse chronological order - newest change first)
1115   ***************************************************************/
1116 
1117 
1118   l_Trans_Rec        VARCHAR2(4000)  := NULL;
1119   l_prev_loan_number igf_sl_dl_chg_send.loan_number%TYPE;
1120   l_line_rec_count   NUMBER := 0;
1121   l_tot_rec_count    NUMBER := 0;
1122 
1123   l_chg_rec_hdr_len  NUMBER := 0;
1124   l_chg_rec_len      NUMBER := 0;
1125   l_chg_code_len     NUMBER := 0;
1126   l_chg_val_len      NUMBER := 0;
1127   l_chg_err_len      NUMBER := 0;
1128 
1129   -- ## Cursor to retrieve the changed records for the particular loan_number and batch Id
1130 
1131   CURSOR cur_chg_rec  IS
1132          SELECT * from igf_sl_dl_chg_send
1133          WHERE dbth_id     = p_dl_dbth_id
1134          ORDER BY loan_number, chg_num;
1135 
1136   lcur_chg_rec  cur_chg_rec%ROWTYPE;
1137 BEGIN
1138 
1139    l_tot_rec_count := 0;
1140    l_line_rec_count := 0;
1141    l_prev_loan_number := 'XXX';
1142    l_trans_rec := NULL;
1143 
1144    IF p_dl_version  IN  ('2002-2003','2003-2004','2004-2005') THEN
1145       l_chg_code_len :=  4;
1146       l_chg_val_len  :=  50;
1147       l_chg_err_len  :=  2;
1148       l_chg_rec_hdr_len := 23;
1149       l_chg_rec_len := l_chg_rec_hdr_len + (4 + 50 + 2) * 10 + 6;
1150    END IF;
1151 
1152    OPEN cur_chg_rec;
1153 
1154    LOOP
1155       FETCH cur_chg_rec INTO lcur_chg_rec;
1156       IF cur_chg_rec%NOTFOUND THEN
1157          IF l_trans_rec IS NOT NULL THEN
1158               fnd_file.put_line(FND_FILE.OUTPUT, RPAD(l_Trans_Rec, l_chg_rec_len)||RPAD(p_dl_batch_id,'25'));
1159               l_tot_rec_count := l_tot_rec_count + 1;
1160          END IF;
1161          EXIT;
1162       END IF;
1163 
1164       IF l_prev_loan_number <> lcur_chg_rec.loan_number THEN
1165          l_prev_loan_number := lcur_chg_rec.loan_number;
1166          l_line_rec_count := 0;
1167          IF l_trans_rec IS NOT NULL THEN
1168               fnd_file.put_line(FND_FILE.OUTPUT, RPAD(l_Trans_Rec, l_chg_rec_len)||RPAD(p_dl_batch_id,'25'));
1169               l_tot_rec_count := l_tot_rec_count + 1;
1170               l_trans_rec     := RPAD(lcur_chg_rec.loan_number,21)||'  ';
1171          ELSE
1172               l_trans_rec     := RPAD(lcur_chg_rec.loan_number,21)||'  ';
1173          END IF;
1174 
1175       ELSE   -- If Loan-Number is Same
1176          IF l_line_rec_count = 10 THEN
1177             l_line_rec_count := 0;
1178             fnd_file.put_line(FND_FILE.OUTPUT, RPAD(l_Trans_Rec, l_chg_rec_len)||RPAD(p_dl_batch_id,'25'));
1179             l_tot_rec_count := l_tot_rec_count + 1;
1180             l_trans_rec     := RPAD(lcur_chg_rec.loan_number,21)||'  ';
1181          END IF;
1182       END IF;
1183 
1184       l_Trans_Rec := l_Trans_Rec ||RPAD(NVL(lcur_chg_rec.chg_code,' '), l_chg_code_len)
1185                                  ||RPAD(NVL(lcur_chg_rec.new_value ,' '), l_chg_val_len)
1186                                  ||RPAD(' ', l_chg_err_len);
1187 
1188       l_line_rec_count := l_line_rec_count + 1;
1189    END LOOP;
1190 
1191    CLOSE cur_chg_rec;
1192 
1193    p_tot_rec_count := l_tot_rec_count;
1194 
1195 EXCEPTION
1196 WHEN OTHERS THEN
1197    IF cur_chg_rec%ISOPEN THEN
1198         CLOSE cur_chg_rec;
1199    END IF;
1200    fnd_message.set_name('IGS','IGS_GE_UNHANDLED_EXP');
1201    fnd_message.set_token('NAME','IGF_SL_DL_CHG_ORIG.TRANS_REC');
1202    fnd_file.put_line(fnd_file.log,SQLERRM);
1203    igs_ge_msg_stack.add;
1204    app_exception.raise_exception;
1205 END Trans_Rec;
1206 
1207 END igf_sl_dl_chg_orig;