DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGF_SL_CL_CHG_PRC

Source


1 PACKAGE BODY igf_sl_cl_chg_prc AS
2 /* $Header: IGFSL23B.pls 120.3 2006/08/25 07:20:21 veramach noship $ */
3 ------------------------------------------------------------------
4 --Created by  : Sanil Madathil, Oracle IDC
5 --Date created: 10 October 2004
6 --
7 --Purpose:
8 -- Invoked     : Through Table Handlers of Disbursement and Loans table
9 -- Function    : To create Change Records for CommonLine Release 4 version Loans.
10 --               Four routines defined in this package would be invoked for changes
11 --               IN award or loan information for CommonLine Release 4 version Loans
12 --               that are "Accepted"
13 --
14 --Known limitations/enhancements and/or remarks:
15 --
16 --Change History:
17 --Who         When            What
18 --
19 --tsailaja    25-Jul-2006     Bug #5337555 FA 163 Included 'GPLUSFL'
20 --                            Included 'GPLUSFL' fund code for validating change records
21 --                            AND excluded 'GPLUSFL' fund code from Stafford Loan limit validation
22 -------------------------------------------------------------------
23 -- procedure for enabling statement level logging
24 PROCEDURE log_to_fnd ( p_v_module IN VARCHAR2,
25                        p_v_string IN VARCHAR2
26                      );
27 
28 FUNCTION validate_ssn ( p_n_person_id igf_ap_fa_base_rec_all.person_id%TYPE)
29 RETURN BOOLEAN;
30 
31 PROCEDURE validate_chg  (p_n_clchgsnd_id   IN  igf_sl_clchsn_dtls.clchgsnd_id%TYPE,
32                          p_b_return_status OUT NOCOPY BOOLEAN,
33                          p_v_message_name  OUT NOCOPY VARCHAR2,
34                          p_t_message_tokens  OUT NOCOPY token_tab%TYPE
35                         ) AS
36 ------------------------------------------------------------------
37 --Created by  : Sanil Madathil, Oracle IDC
38 --Date created: 10 October 2004
39 --
40 -- Purpose:
41 -- Invoked     : From igf_sl_cl_create_chg process to validate change record
42 -- Function    : This process would be invoked automatically for each change record
43 --
44 -- Parameters  : p_n_clchgsnd_id   : IN parameter. Required.
45 --               p_b_return_status : OUT parmeter.
46 --               p_v_message_name  : OUT parameter
47 --
48 --
49 --Known limitations/enhancements and/or remarks:
50 --
51 --Change History:
52 --Who         When            What
53 ------------------------------------------------------------------
54 CURSOR  c_igf_sl_lor_loans (cp_n_loan_id igf_sl_loans_all.loan_id%TYPE) IS
55 SELECT  isl.anticip_compl_date anticipated_completion_date
56         ,islv.loan_per_end_date loan_end_date
57 FROM    igf_sl_lor_v isl,
58         igf_sl_loans_v islv
59 WHERE   isl.loan_id = islv.loan_id and
60         isl.loan_id  = cp_n_loan_id;
61 
62 CURSOR  c_igf_sl_clchsn_dtls (cp_n_clchgsnd_id igf_sl_clchsn_dtls.clchgsnd_id%TYPE) IS
63 SELECT   clchgsnd.award_id
64         ,clchgsnd.loan_number_txt
65 FROM    igf_sl_clchsn_dtls clchgsnd
66 WHERE   clchgsnd.clchgsnd_id = cp_n_clchgsnd_id;
67 
68 CURSOR  c_igf_sl_loans (cp_v_loan_number igf_sl_loans_all.loan_number%TYPE) IS
69 SELECT  lar.loan_id
70 FROM    igf_sl_loans_all lar
71 WHERE   lar.loan_number = cp_v_loan_number;
72 
73 CURSOR  c_igf_sl_lor (cp_n_loan_id igf_sl_loans_all.loan_id%TYPE) IS
74 SELECT   lor.p_person_id        borrower_id
75         ,lor.relationship_cd    relationship_cd
76         ,lor.cl_seq_number   cl_seq_number
77 FROM    igf_sl_lor_all lor
78 WHERE   lor.loan_id = cp_n_loan_id;
79 
80 CURSOR  c_igf_aw_award (cp_n_award_id igf_aw_award_all.award_id%TYPE) IS
81 SELECT  awd.base_id
82 FROM    igf_aw_award_all awd
83 WHERE   awd.award_id = cp_n_award_id;
84 
85 CURSOR  c_igf_ap_fa_base_rec (cp_n_base_id igf_ap_fa_base_rec_all.base_id%TYPE) IS
86 SELECT  fabase.person_id
87 FROM    igf_ap_fa_base_rec_all fabase
88 WHERE   fabase.base_id = cp_n_base_id;
89 
90 CURSOR   c_igf_sl_cl_recipient (cp_v_relationship_cd igf_sl_cl_recipient.relationship_cd%TYPE) IS
91 SELECT   rcpt.guarantor_id
92         ,rcpt.lender_id
93 FROM     igf_sl_cl_recipient rcpt
94 WHERE    relationship_cd = cp_v_relationship_cd;
95 
96 l_n_clchgsnd_id      igf_sl_clchsn_dtls.clchgsnd_id%TYPE;
97 l_n_award_id         igf_aw_award_all.award_id%TYPE;
98 l_v_loan_number      igf_sl_loans_all.loan_number%TYPE;
99 l_n_person_id        igf_ap_fa_base_rec_all.person_id%TYPE;
100 l_n_loan_id          igf_sl_loans_all.loan_id%TYPE;
101 l_v_school_id        igs_pe_alt_pers_id.person_id_type%TYPE;
102 l_n_base_id          igf_ap_fa_base_rec_all.base_id%TYPE;
103 l_v_relationship_cd  igf_sl_cl_recipient.relationship_cd%TYPE;
104 l_v_guarantor_id     igf_sl_guarantor.guarantor_id%TYPE;
105 l_v_lender_id        igf_sl_lender.lender_id%TYPE;
106 l_n_cl_seq_number    igf_sl_lor_all.cl_seq_number%TYPE;
107 l_v_fed_fund_code    igf_aw_fund_cat_all.fed_fund_code%TYPE;
108 l_v_message_name     fnd_new_messages.message_name%TYPE;
109 l_b_return_status    BOOLEAN;
110 l_loan_tab           igf_aw_packng_subfns.std_loan_tab ;
111 l_n_aid              NUMBER ;
112 l_d_ant_comp_dt      igf_sl_lor_v.anticip_compl_date%TYPE;
113 l_d_loan_end_dt      igf_sl_loans_v.loan_per_end_date%TYPE;
114 BEGIN
115 
116   -- This process would be invoked automatically for each change record created.
117   -- While creating change record the validations would be performed. In case of
118   -- validation failures change record would not be created and the transaction
119   -- that initiated the change record creation would also be rolled back.
120   -- Rollback is handled in calling routine
121 
122   log_to_fnd(p_v_module => 'validate_chg',
123              p_v_string => ' Validating the input parameters. p_n_clchgsnd_id = '||p_n_clchgsnd_id
124             );
125 
126   IF p_n_clchgsnd_id IS NULL THEN
127     p_v_message_name  := 'IGS_GE_INVALID_VALUE';
128     p_b_return_status := FALSE;
129     RETURN;
130   END IF;
131 
132   --Validation for common fields would be done only once. If the required information
133   --is not available then the edit would be created. For each of the validation failures,
134   --p_v_message_name would be set and p_b_return_status would be set to FALSE
135   l_n_clchgsnd_id := p_n_clchgsnd_id;
136 
137   -- validating the loan type code
138   OPEN  c_igf_sl_clchsn_dtls (cp_n_clchgsnd_id => l_n_clchgsnd_id);
139   FETCH c_igf_sl_clchsn_dtls INTO l_n_award_id,l_v_loan_number;
140   CLOSE c_igf_sl_clchsn_dtls;
141 
142   log_to_fnd(p_v_module => ' validate_chg',
143              p_v_string => ' Validating the loan type code for award id = '||l_n_award_id
144             );
145 
146   l_v_fed_fund_code := igf_sl_gen.get_fed_fund_code (p_n_award_id     => l_n_award_id,
147                                                      p_v_message_name => l_v_message_name
148                                                      );
149   IF l_v_message_name IS NOT NULL THEN
150     p_v_message_name  := l_v_message_name;
151     p_b_return_status := FALSE;
152     RETURN;
153   END IF;
154 
155   -- tsailaja -FA 163  -Bug 5337555
156   IF l_v_fed_fund_code NOT IN ('FLS','FLU','FLP','ALT','GPLUSFL') THEN
157     p_v_message_name  := 'IGF_SL_CL_CHG_LOANT_REQD';
158     p_b_return_status := FALSE;
159     RETURN;
160   END IF;
161 
162    log_to_fnd(p_v_module => ' validate_chg ',
163              p_v_string =>  ' validated loan type code. loan type code = '||l_v_fed_fund_code
164             );
165 
166   OPEN  c_igf_sl_loans (cp_v_loan_number => l_v_loan_number);
167   FETCH c_igf_sl_loans INTO l_n_loan_id;
168   CLOSE c_igf_sl_loans ;
169 
170   OPEN  c_igf_sl_lor (cp_n_loan_id => l_n_loan_id);
171   FETCH c_igf_sl_lor INTO l_n_person_id, l_v_relationship_cd,l_n_cl_seq_number;
172   CLOSE c_igf_sl_lor ;
173 
174 -- validating CommonLine Unique Identifier
175   log_to_fnd(p_v_module => 'validate_chg',
176              p_v_string => ' Validating the CommonLine Unique Identifier. loan number = '||l_v_loan_number
177             );
178 
179   IF l_v_loan_number IS NULL THEN
180     p_v_message_name  := 'IGF_SL_CL_CHG_LNUMB_REQD';
181     p_b_return_status := FALSE;
182     RETURN;
183   END IF;
184 
185   -- validating borrower SSn required field
186   log_to_fnd(p_v_module => 'validate_chg',
187              p_v_string => 'Validating the Borrower SSN for borrower id = '||l_n_person_id
188             );
189 
190   l_b_return_status := validate_ssn(p_n_person_id => l_n_person_id);
191   IF NOT (l_b_return_status)  THEN
192     p_v_message_name  := 'IGF_SL_CL_CHG_BSSN_REQD';
193     p_b_return_status := FALSE;
194     RETURN;
195   END IF;
196 
197 --  Added anticipated Completeg date validation by upinjark : March 17th 2005.
198 --  Fix for Bug no. 4091086
199 
200 -- validating Anticipated Completed date Vs Loan end date
201   OPEN c_igf_sl_lor_loans (cp_n_loan_id => l_n_loan_id);
202   FETCH c_igf_sl_lor_loans INTO l_d_ant_comp_dt, l_d_loan_end_dt;
203   CLOSE c_igf_sl_lor_loans;
204 
205   log_to_fnd(p_v_module => 'validate_chg',
206              p_v_string => 'Validating the Anticipated Completion Date = '|| l_d_ant_comp_dt || ', for person = ' ||l_n_person_id
207             );
208 
209   IF (l_d_ant_comp_dt < l_d_loan_end_dt) THEN
210 	p_v_message_name := 'IGF_SL_CHECK_COMPLDATE';
211 	p_t_message_tokens(1).token_name  := 'VALUE' ;
212 	p_t_message_tokens(1).token_value := ' ' || to_char(l_d_ant_comp_dt, 'mm/dd/yyyy') ;
213         p_b_return_status := FALSE;
214 	RETURN;
215   END IF;
216 
217   log_to_fnd(p_v_module => 'validate_chg',
218              p_v_string => 'Validating the End Date = '|| l_d_loan_end_dt || ', for person = ' ||l_n_person_id
219             );
220 
221   -- validating school id required field
222   log_to_fnd(p_v_module => 'validate_chg',
223              p_v_string => 'Validating the School Id for loan Number = '||l_v_loan_number
224             );
225   l_v_school_id := SUBSTR(l_v_loan_number,1,6);
226   IF ( l_v_school_id IS NULL ) THEN
227     p_v_message_name  := 'IGF_SL_CL_CHG_SCHID_REQD';
228     p_b_return_status := FALSE;
229     RETURN;
230   END IF;
231   IF (LENGTH(l_v_school_id) <> 6) THEN
232     p_v_message_name  := 'IGF_SL_CL_CHG_SCHID_REQD';
233     p_b_return_status := FALSE;
234     RETURN;
235   END IF;
236 
237   log_to_fnd(p_v_module => 'validate_chg',
238              p_v_string => 'Validated the School Id school id = '||l_v_school_id
239             );
240 
241   -- validating Guarantor ID and Lender id required fields
242 
243   log_to_fnd(p_v_module => 'validate_chg',
244              p_v_string => 'Validating the Guarantor ID and Lender id required fields for relatioship code = '||l_v_relationship_cd
245             );
246 
247   OPEN   c_igf_sl_cl_recipient (cp_v_relationship_cd => l_v_relationship_cd);
248   FETCH  c_igf_sl_cl_recipient INTO l_v_guarantor_id ,l_v_lender_id;
249   CLOSE  c_igf_sl_cl_recipient ;
250 
251   IF l_v_guarantor_id IS NULL THEN
252     p_v_message_name  := 'IGF_SL_CL_CHG_GID_REQD';
253     p_b_return_status := FALSE;
254     RETURN;
255   END IF;
256 
257   IF l_v_lender_id IS NULL THEN
258     p_v_message_name  := 'IGF_SL_CL_CHG_LID_REQD';
259     p_b_return_status := FALSE;
260     RETURN;
261   END IF;
262 
263   log_to_fnd(p_v_module => 'validate_chg',
264              p_v_string => ' Validated Guarantor ID and Lender id required fields '||
265                            ' Guarantor ID = '||l_v_guarantor_id||
266                            ' Lender id    = '|| l_v_lender_id
267             );
268 
269   -- validating PLUS/Alternative Student SSN
270   l_n_person_id := NULL;
271 
272   OPEN  c_igf_aw_award (cp_n_award_id => l_n_award_id);
273   FETCH c_igf_aw_award INTO l_n_base_id;
274   CLOSE c_igf_aw_award ;
275 
276   OPEN  c_igf_ap_fa_base_rec (cp_n_base_id => l_n_base_id);
277   FETCH c_igf_ap_fa_base_rec INTO l_n_person_id;
278   CLOSE c_igf_ap_fa_base_rec;
279 
280   log_to_fnd(p_v_module => 'validate_chg',
281              p_v_string => 'Validating the PLUS/Alternative Student SSN for person id = '||l_n_person_id
282             );
283   l_b_return_status := TRUE;
284   l_b_return_status := validate_ssn(p_n_person_id => l_n_person_id);
285   IF NOT (l_b_return_status)  THEN
286     p_v_message_name  := 'IGF_SL_CL_CHG_SSSN_REQD';
287     p_b_return_status := FALSE;
288     RETURN;
289   END IF;
290 
291   -- validating Loan Sequence Number
292   IF l_n_cl_seq_number IS NULL THEN
293     p_v_message_name  := 'IGF_SL_CL_CHG_GSEQ_REQD';
294     p_b_return_status := FALSE;
295     RETURN;
296   END IF;
297   log_to_fnd(p_v_module => 'validate_chg',
298              p_v_string => 'Validated the Loan Sequence Number. cl_seq_number  = '||l_n_cl_seq_number
299              );
300   -- tsailaja -FA 163  -Bug 5337555
301   -- validating loan amount limits
302       -- Check the Loan Limts amounts for Loans other than DLP/FLP/ALT
303   IF l_v_fed_fund_code NOT IN ('PRK','DLP','FLP','ALT','GPLUSFL') THEN
304     -- re initializing the variables
305     l_loan_tab := igf_aw_packng_subfns.std_loan_tab();
306     l_n_aid    := 0;
307     l_v_message_name := NULL;
308     log_to_fnd(p_v_module => 'validate_chg',
309                p_v_string => 'Validating the Loan Limts amount invoking  igf_aw_packng_subfns.check_loan_limits '
310                );
311     igf_aw_packng_subfns.check_loan_limits
312     (
313       l_base_id        => l_n_base_id,
314       fund_type        => l_v_fed_fund_code,
315       l_award_id       => l_n_award_id,
316       l_adplans_id     => NULL,
317       l_aid            => l_n_aid,
318       l_std_loan_tab   => l_loan_tab,
319       p_msg_name       => l_v_message_name
320     );
321     -- bvisvana - FA 161 - Bug 5006583 - Stafford Loan Limit validation is treated as warning and not as error. So just print the message
322     -- bvisvana - Bug 5091652 - If no loan limit setup exists for class standing then it is treated as error.
323     -- In this case the l_aid = 0. So returning with return status as FALSE.
324     IF l_v_message_name IS NOT NULL THEN
325       IF l_n_aid = 0 THEN
326         p_v_message_name  := l_v_message_name;
327         p_b_return_status := FALSE;
328         RETURN ;
329       ELSIF l_n_aid < 0 THEN
330         p_v_message_name  := 'IGF_SL_CL_GRD_AMT_VAL';
331         fnd_message.set_name(substr(p_v_message_name,1,3),p_v_message_name);
332         fnd_file.put_line(fnd_file.log,fnd_message.get);
333       END IF;
334     END IF;
335   END IF;
336  log_to_fnd(p_v_module => 'validate_chg',
337             p_v_string => 'Validation of the change record successful. setting return status to true and message is cleared '
338             );
339   p_v_message_name  := NULL;
340   p_b_return_status := TRUE;
341 
342 EXCEPTION
343   WHEN OTHERS THEN
344    log_to_fnd(p_v_module => 'when others exception handler',
345               p_v_string => SQLERRM
346               );
347 
348    fnd_message.set_name ('IGS', 'IGS_GE_UNHANDLED_EXP');
349    fnd_message.set_token('NAME','igf_sl_cl_chg_prc.validate_chg');
350    igs_ge_msg_stack.add;
351    app_exception.raise_exception;
352 END validate_chg;
353 
354 PROCEDURE log_to_fnd ( p_v_module IN VARCHAR2,
355                        p_v_string IN VARCHAR2 ) AS
356 ------------------------------------------------------------------
357 --Created by  : Sanil Madathil, Oracle IDC
358 --Date created: 18 October 2004
359 --
360 -- Purpose:
361 -- Invoked     : from within validate_chg procedure
362 -- Function    : Private procedure for logging all the statement level
363 --               messages
364 -- Parameters  : p_v_module   : IN parameter. Required.
365 --               p_v_string   : IN parameter. Required.
366 --
367 --
368 --Known limitations/enhancements and/or remarks:
369 --
370 --Change History:
371 --Who         When            What
372 ------------------------------------------------------------------
373 BEGIN
374   IF (fnd_log.level_statement >= fnd_log.g_current_runtime_level) THEN
375     fnd_log.string( fnd_log.level_statement, 'igf.plsql.igf_sl_cl_chg_prc. '||p_v_module||' Debug', p_v_string);
376   END IF;
377 END log_to_fnd;
378 
379 FUNCTION validate_ssn ( p_n_person_id igf_ap_fa_base_rec_all.person_id%TYPE)
380 RETURN BOOLEAN AS
381 ------------------------------------------------------------------
382 --Created by  : Sanil Madathil, Oracle IDC
383 --Date created: 18 October 2004
384 --
385 -- Purpose:
386 -- Invoked     : from within validate_chg procedure
387 -- Function    : Private procedure which would validate SSN
388 --               for the input person id
389 -- Parameters  : p_n_person_id   : IN parameter. Required.
390 --
391 --
392 --Known limitations/enhancements and/or remarks:
393 --
394 --Change History:
395 --Who         When            What
396 ------------------------------------------------------------------
397 c_person_dtl_cur     igf_sl_gen.person_dtl_cur;
398 rec_c_person_dtl_cur igf_sl_gen.person_dtl_rec;
399 l_person_ssn         igs_pe_alt_pers_id.person_id_type%TYPE;
400 BEGIN
401 
402   log_to_fnd(p_v_module => 'validate_ssn ',
403              p_v_string => 'Private function validate_ssn input parameter p_n_person_id = '||p_n_person_id
404             );
405   -- invoke igf_sl_gen.get_person_details
406   igf_sl_gen.get_person_details
407   (
408     p_person_id       => p_n_person_id,
409     p_person_dtl_rec  => c_person_dtl_cur
410   );
411   FETCH c_person_dtl_cur INTO rec_c_person_dtl_cur;
412   CLOSE c_person_dtl_cur ;
413   l_person_ssn := NVL(rec_c_person_dtl_cur.p_ssn,'NULL');
414   log_to_fnd(p_v_module => 'validate_ssn ',
415              p_v_string => 'party ssn = '||l_person_ssn
416             );
417   IF l_person_ssn IS NULL THEN
418     log_to_fnd(p_v_module => 'validate_ssn ',
419                p_v_string => 'ssn null ' ||
420                              ' returning false'
421               );
422     RETURN FALSE;
423   END IF;
424   --if the SSN starts with 8, 9 or 0, it is deemed as invalid
425   IF (SUBSTR(l_person_ssn,1,1) IN ('8','9') OR SUBSTR(l_person_ssn,1,3) =  '000') THEN
426     log_to_fnd(p_v_module => 'validate_ssn ',
427                p_v_string => 'SSN starts with 8, 9 or 0 ' ||
428                              ' returning false'
429               );
430     RETURN FALSE;
431   END IF;
432     log_to_fnd(p_v_module => 'validate_ssn ',
433                p_v_string => 'validations are successful ' ||
434                              ' returning true'
435               );
436   RETURN TRUE;
437 END validate_ssn;
438 
439   PROCEDURE parse_tokens       ( p_t_message_tokens  IN  token_tab%TYPE) AS
440   BEGIN
441     IF (NVL(p_t_message_tokens.COUNT, 0) <> 0 AND p_t_message_tokens IS NOT NULL) THEN
442       FOR token_counter IN NVL(p_t_message_tokens.FIRST, 0)..NVL(p_t_message_tokens.LAST, 0) LOOP
443         fnd_message.set_token(p_t_message_tokens(token_counter).token_name, p_t_message_tokens(token_counter).token_value);
444       END LOOP;
445     END IF;
446   END parse_tokens;
447 
448 END igf_sl_cl_chg_prc;