DBA Data[Home] [Help]

PACKAGE BODY: APPS.PA_REVENUE_AMT

Source


1 PACKAGE BODY pa_revenue_amt AS
2 /*$Header: PAXIIRSB.pls 120.6 2010/10/14 19:10:48 apaul ship $ */
3 
4 -- 1. Procedure calls the client labor billing extension for calculating
5 --    bill amount
6 -- 2. Procedure calls the IRS api for populating raw revenue
7 --    and bill amount, irs rate sch rev id for revenue/invoice in
8 --    pa_expenditure_items_all table.
9 --    This procedure verifies whether 'Indirect rate schedule'
10 --    this applicable for an ei or not and if applicable then it calls the
11 --    cost plus api to compute the Indirect amount which later on gets added
12 --    to raw revenue and bill amount.
13 
14 g1_debug_mode varchar2(1) := NVL(FND_PROFILE.value('PA_DEBUG_MODE'), 'N');
15 
16 PROCEDURE get_irs_amt
17 (
18  process_irs                        OUT   NOCOPY  VARCHAR2,
19  process_bill_rate                  OUT   NOCOPY  VARCHAR2,
20  message_code                       OUT   NOCOPY  VARCHAR2,
21  rows_this_time			    IN     INTEGER,
22  error_code			    IN OUT  NOCOPY    t_int,
23  reason				    OUT     NOCOPY t_varchar_30,
24  bill_amount			    OUT      NOCOPY t_varchar_100,  /* for bug 8593881 */
25  rev_amount			    OUT     NOCOPY t_varchar_30,
26  inv_amount			    OUT     NOCOPY t_varchar_30,
27  d_rule_decode			    IN OUT     NOCOPY t_int,
28  sl_function			    IN OUT     NOCOPY t_int,
29  ei_id			    	    IN OUT     NOCOPY t_int,
30  t_rev_irs_id		    	    IN OUT     NOCOPY t_int,
31  t_inv_irs_id		    	    IN OUT     NOCOPY t_int,
32  rev_comp_set_id	    	    IN OUT     NOCOPY t_int,
33  inv_comp_set_id	    	    IN OUT     NOCOPY t_int,
34  bill_rate_markup		    OUT     NOCOPY t_varchar_2,
35  t_lab_sch			    IN     t_varchar_2,
36  t_nlab_sch			    IN     t_varchar_2,
37  p_mcb_flag                         IN     VARCHAR2,
38  x_bill_trans_currency_code         IN OUT  NOCOPY t_varchar_15,        /* MCB Chnages start */
39  x_bill_txn_bill_rate               IN OUT  NOCOPY t_varchar_30,
40  x_rate_source_id                   IN OUT  NOCOPY t_int,
41  x_markup_percentage                IN OUT  NOCOPY t_varchar_30,         /* MCB Changes end */
42  x_exp_type                         IN             t_varchar_30,        /*change for nonlabor client extension */
43  x_nl_resource                      IN             t_varchar_20,
44  x_nl_res_org_id                    IN             t_int            /*End of change for nonlabor client extension */
45 
46 )
47 IS
48 
49 /*-----------------------------------------------------------------------------
50  declare all the memory variables.
51  ----------------------------------------------------------------------------*/
52 
53     client_extn_system_error  EXCEPTION;
54     cost_plus_system_error    EXCEPTION;
55     amount                    number;
56     rate_sch_rev_id           number;
57     compiled_set_id           number;
58     status                    number;
59     stage                     number;
60     bill_rate_flag            varchar2(2);
61     sys_linkage_func          varchar2(30);
62     insert_error_message      boolean;
63     fetched_amount            boolean;
64     l_ind_cost_acct           NUMBER := NULL;
65     l_ind_cost_denm           NUMBER := NULL;
66     j			      INTEGER;
67 
68 
69     l_indirect_cost_project   NUMBER := NULL;    /* EPP Changes */
70 
71 
72   /*** MCB Changes : Declare the out variable for the function Call_Calc_Bill_Amount ***/
73 
74     l_x_bill_trans_currency_code      VARCHAR2(15);
75     l_x_bill_trans_bill_rate          NUMBER;
76     l_x_rate_source_id                NUMBER;
77     l_x_markup_percentage             NUMBER;
78 
79   /*** End MCB Changes ***/
80  l_mcb_cost_flag    varchar2(50);   /* Added for bug 2638840 */
81 --NOCOPY Changes
82 l_process_irs	      VARCHAR2(50);
83 l_process_bill_rate   VARCHAR2(50);
84 l_message_code        VARCHAR2(2000);
85 
86   BEGIN
87 
88   IF g1_debug_mode  = 'Y' THEN
89   	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Entering the get IRS procedure .....');
90   END IF;
91 
92 
93 /*-----------------------------------------------------------------------------
94  initialize array index j to 1,
95  initialize flags which determine whether irs, bill rate
96  schedules need to be processed or not
97  ----------------------------------------------------------------------------*/
98 
99      j  := 1;
100      l_process_irs := 'N';
101      l_process_bill_rate := 'N';
102      l_message_code := 'No errors while processing IRS....';
103 
104 /* Added for bug 2638840 */
105 
106 IF ( nvl(p_mcb_flag,'N') = 'Y' ) THEN
107 
108   IF  (j <= rows_this_time) THEN
109 
110   BEGIN
111  /* Added the following nvl so that code doesn't break even if upgrade script fails - For bug 2724185 */
112 
113          SELECT  nvl(BTC_COST_BASE_REV_CODE,'EXP_TRANS_CURR')
114           INTO   l_mcb_cost_flag
115          FROM pa_projects_all
116          WHERE  project_id =(select project_id from pa_expenditure_items_all
117                                      where expenditure_item_id=ei_id(1));
118   EXCEPTION
119     WHEN NO_DATA_FOUND THEN
120      IF g1_debug_mode  = 'Y' THEN
121   	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'No Data Found for the ei_id:' ||  ei_id(1));
122      END IF;
123     RAISE ;
124   END;
125 
126  IF g1_debug_mode  = 'Y' THEN
127  	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'BTC_COST_BASE_REV_CODE  :' || l_mcb_cost_flag);
128  END IF;
129 END IF;
130 END IF;
131 
132 /* End of Changes done for bug 2638840 */
133 
134 /*-----------------------------------------------------------------------------
135  loop until all 100 ei's are processed
136  ----------------------------------------------------------------------------*/
137 
138      WHILE j <= rows_this_time LOOP
139 
140           error_code( j ) := 0;
141 
142       /*    l_mcb_cost_flag := NULL;   Added for bug 2638840 and later commented for bug 2638840 */
143           rate_sch_rev_id := NULL;
144           compiled_set_id := NULL;
145           amount := NULL;
146           insert_error_message := FALSE;
147           fetched_amount := FALSE;
148 
149 /*-----------------------------------------------------------------------------
150   Call a client extension to fetch the bill amount for the ei.
151   This has to be done for Labor exp items which have WORK
152   distribution rule for Revenue or Invoice.
153  ----------------------------------------------------------------------------*/
154 
155          bill_amount( j )      := NULL;
156          bill_rate_markup( j ) := NULL;
157 
158         /* MCB Changes : Initialize the out variables */
159 
160            x_bill_trans_currency_code( j ) := NULL;
161            x_bill_txn_bill_rate( j )       := NULL;
162            x_rate_source_id( j )           := NULL;
163            x_markup_percentage( j )        := NULL;
164 
165 
166          IF ( ( d_rule_decode(j) > 0   )/*   AND
167               ( sl_function( j ) < 2   ) */) THEN   /*commented out  for nonlabor client extension*/
168               amount         := NULL;
169               status         := 0;
170               bill_rate_flag := ' ';
171 /** Added new values for new system linkages in proj. manf. **/
172 
173 
174               IF sl_function( j ) = 0 THEN
175                   sys_linkage_func := 'ST';
176               ELSIF sl_function( j ) = 1 THEN
177                   sys_linkage_func := 'OT';
178               ELSIF sl_function( j ) = 2 THEN
179                   sys_linkage_func := 'ER';
180               ELSIF sl_function( j ) = 3 THEN
181                   sys_linkage_func := 'USG';
182               ELSIF sl_function( j ) = 4 THEN
183                   sys_linkage_func := 'VI';
184               ELSIF sl_function( j ) = 5 THEN
185                   sys_linkage_func := 'WIP';
186               ELSIF sl_function( j ) = 6 THEN
187                   sys_linkage_func := 'BTC';
188               ELSIF sl_function( j ) = 7 THEN
189                   sys_linkage_func := 'PJ';
190               ELSIF sl_function( j ) = 8 THEN
191                   sys_linkage_func := 'INV';
192               ELSE
193                   sys_linkage_func := NULL;
194               END IF;
195 
196 
197               IF g1_debug_mode  = 'Y' THEN
198               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Calling call_calc_bill_amount procedure ' || ei_id(j));
199               END IF;
200 If ( sl_function( j ) < 2   )  THEN  /*change for nonlabor client extension*/
201 
202               pa_billing.Call_Calc_Bill_Amount( 'ACTUAL',ei_id( j ),
203                                                        sys_linkage_func,
204                                                        amount,
205                                                        bill_rate_flag,
206                                                        status,
207                                                        l_x_bill_trans_currency_code,
208                                                        l_x_bill_trans_bill_rate,
209                                                        l_x_markup_percentage,
210                                                        l_x_rate_source_id
211                                                 );
212 
213 
214               IF g1_debug_mode  = 'Y' THEN
215               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'After Calling call_calc_bill_amount procedure ' || ei_id(j));
216               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Amount :' || to_char(amount));
217               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Bill Rate Flag : ' || bill_rate_flag);
218               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Bill Trans Currency code :' || l_x_bill_trans_currency_code);
219               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Bill Trans Bill Rate :' || l_x_bill_trans_bill_rate);
220               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Markup Percentage :' || l_x_markup_percentage);
221               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Rate source Id :' || l_x_rate_source_id);
222               	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Status :' || status);
223               END IF;
224 
225 ELSE    /*change for nonlabor client extension
226          Else part of sl_function<2*/
227 
228      pa_billing.Call_Calc_Non_Labor_Bill_Amt
229                                   (
230                                       x_transaction_type=>'ACTUAL',
231                                       x_expenditure_item_id=>ei_id( j ),
232                                       x_sys_linkage_function=>sys_linkage_func,
233                                       x_amount=>amount,
234                                       x_expenditure_type=>x_exp_type(j),
235                                       x_non_labor_resource=>x_nl_resource(j),
236                                       x_non_labor_res_org=>x_nl_res_org_id(j),
237                                       x_bill_rate_flag=>bill_rate_flag,
238                                       x_status=>status,
239                                       x_bill_trans_currency_code=>l_x_bill_trans_currency_code,
240                                       x_bill_txn_bill_rate=>l_x_bill_trans_bill_rate,
241                                       x_markup_percentage=>l_x_markup_percentage,
242                                       x_rate_source_id=>l_x_rate_source_id);
243             IF g1_debug_mode  = 'Y' THEN
244                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'After Calling call_calc_non_labor_bill_amt procedure ' || ei_id(j));
245                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Amount :' || to_char(amount));
246                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Bill Rate Flag : ' || bill_rate_flag);
247                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Bill Trans Currency code :' || l_x_bill_trans_currency_code);
248                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Bill Trans Bill Rate :' || l_x_bill_trans_bill_rate);
249                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Markup Percentage :' || l_x_markup_percentage);
250                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Rate source Id :' || l_x_rate_source_id);
251                 PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Status :' || status);
252               END IF;
253 
254 END IF;
255 /*end of change for nonlabor client extension*/
256               IF ( ( status = 0              OR
257                      status is null )        AND
258                      amount is null        ) THEN
259                    null;
260               ELSIF ( (status = 0 OR status is null)
261                      and amount is not null ) THEN
262                        bill_amount( j ) := to_char(amount);
263                         fetched_amount := TRUE;
264                        l_process_irs := 'Y';
265 
266                       /* MCB Changes : Assign the value to the out variable to pass into pro*c */
267 
268                          x_bill_trans_currency_code( j )  := l_x_bill_trans_currency_code;
269                          x_bill_txn_bill_rate( j )        := l_x_bill_trans_bill_rate;
270                          x_rate_source_id( j )            := l_x_rate_source_id;
271                          x_markup_percentage( j )         := l_x_markup_percentage;
272 
273                       /* End MCB Changes */
274 
275 
276                    IF ( bill_rate_flag = 'B' ) THEN
277                        bill_rate_markup(j ) := 'B';
278                    ELSE
279                        bill_rate_markup( j ) := NULL;
280                    END IF;
281               ELSIF ( status > 0 and sl_function(j)<2) THEN
282                    fetched_amount := TRUE;
283                    reason( j ) := 'CALC_BILL_AMOUNT_EXT_FAIL';
284                    error_code( j ) := 1;
285               ELSIF ( status > 0 and sl_function(j)>1) THEN/*Change for nonlabor client extension*/
286                    fetched_amount := TRUE;
287                    reason( j ) := 'CALC_BILL_AMT_NL_EXT_FAIL';  /* for bug 6262893 'CALC_BILL_AMOUNT_NL_EXT_FAIL'; */
288                    error_code( j ) := 1;
289               ELSE
290                    RAISE client_extn_system_error;
291               END IF;
292 
293         END IF;
294 
295 /*----------------------------------------------------------------------------
296  For Revenue :
297  check whether revenue distribution is WORK, labor/non labor
298  schedule type is Indirect, irs sch id exists and ei is labor/
299  non labor. If all of this is true only then call the api to
300  calculate the indirect cost for Revenue.
301 
302  For Labor/non Labor expenditure items :
303  ----------------------------------------------------------------------------*/
304 
305            IF (  (d_rule_decode(j) = 1 OR d_rule_decode(j) =2)                               AND
306                  t_rev_irs_id( j ) IS NOT NULL                    AND
307               (( t_lab_sch( j ) = 'I'                             AND
308                  sl_function( j ) < 2                        )    OR
309                ( t_nlab_sch( j ) = 'I'                            AND
310                  sl_function( j ) > 1                        ))   AND
311                  NOT fetched_amount                               ) THEN
312 
313 
314                  l_ind_cost_acct := NULL;
315                  l_ind_cost_denm := NULL;
316                  l_indirect_cost_project := NULL;     /* EPP Changes */
317 
318           IF g1_debug_mode  = 'Y' THEN
319           	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Calling Procedure get_exp_item_indirect_cost for Revenue');
320           END IF;
321 
322 
323                  pa_cost_plus.get_exp_item_indirect_cost(
324                  ei_id( j ), 'R', amount,
325                  l_ind_cost_acct,l_ind_cost_denm,
326                  l_indirect_cost_project,             /* EPP Changes */
327                  rate_sch_rev_id, compiled_set_id,
328                  status, stage );
329 
330 /* ---------------------------------------------------------------------------
331  Check for success/failure of the called api :
332  check whether indirect amount and sch rev id were retrieved successfully,
333  if yes then assign these values to the host array variables for indirect
334  amount and rate sct rev id respectively, else set error code to 1 which
335  stands for 'NO COMPILED MULTIPLIER'.
336  ----------------------------------------------------------------------------*/
337                  IF ( status = 100 and stage <> 400 ) THEN
338                       rev_comp_set_id( j ) := NULL;
339                       rev_amount(j ) := NULL;
340                       error_code(j ) := 1;
341                       l_message_code :=
342                           'Error encountered during processing IRS....' ;
343                       insert_error_message := TRUE;
344 
345 /*-----------------------------------------------------------------------------
346   NO_COST_BASE case whereby raw_revenue amount should be populated with
347   raw_cost.
348   ---------------------------------------------------------------------------*/
349                  ELSIF ( status = 100 and stage = 400 ) THEN
350                          rev_comp_set_id(j ):= 0;
351                          rev_amount(j ) :=  '0';
352                          l_process_irs := 'Y';
353 
354 /*-----------------------------------------------------------------------------
355   If everything is retrieved as expected which means success.
356   ---------------------------------------------------------------------------*/
357                  ELSIF ( rate_sch_rev_id IS NOT NULL AND
358                          compiled_set_id IS NOT NULL AND
359                          amount          IS NOT NULL AND
360                          status = 0 ) THEN
361                          rev_comp_set_id( j ):= compiled_set_id;
362 
363                         /* MCB Changes : If MCB enabled then take the denom cost other wise
364                                          raw cost */
365 
366                          IF p_mcb_flag = 'Y' THEN
367 
368                         /* Commented for bug 2638840
369                        rev_amount( j ) :=  to_char(l_ind_cost_denm); */
370 
371      /* Bug 2638840 : Get the BTC_COST_BASE_REV_CODE from pa_projects_all table */
372 /* Moved the following code added for bug 2638840 out of the while loop and
373    added the same before the start of while, as each call of  get_irs_amt
374    has EIs that belong to the same project and hence retrieving the
375    btc_cost_base_rev_code once for each call of get_irs_amt would be sufficient
376 
377 BEGIN
378 
379    select BTC_COST_BASE_REV_CODE
380    into l_mcb_cost_flag
381    from pa_projects_all
382    where project_id =(select project_id from pa_expenditure_items_all where expenditure_item_id=ei_id(j));
383 
384 EXCEPTION
385   WHEN NO_DATA_FOUND THEN
386   IF g1_debug_mode  = 'Y' THEN
387   	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'No Data Found for the ei_id:' ||  ei_id(j));
388   END IF;
389   RAISE ;
390 END;
391 
392      IF g1_debug_mode  = 'Y' THEN
393      	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'BTC_COST_BASE_REV_CODE  :' || l_mcb_cost_flag);
394      END IF; */
395 
396 
397 
398       IF g1_debug_mode  = 'Y' THEN
399       	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'mcb_cost_bug l_ind_cost_denm ' || l_ind_cost_denm);
400       	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'mcb_cost_bug l_ind_cost_acct ' || l_ind_cost_acct);
401       	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'mcb_cost_bug amount ' || amount);
402       	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'mcb_cost_bug l_indirect_cost_project ' || l_indirect_cost_project);
403       END IF;
404 
405                             IF (l_mcb_cost_flag = 'EXP_TRANS_CURR') THEN
406 
407                                 rev_amount( j ) :=  to_char(l_ind_cost_denm);
408 
409                             ELSIF (l_mcb_cost_flag = 'EXP_FUNC_CURR') THEN
410 
411                                 rev_amount( j ) :=   to_char(l_ind_cost_acct);
412 
413                             ELSIF (l_mcb_cost_flag = 'PROJ_FUNC_CURR') THEN
414 
415                                 rev_amount( j ) :=   to_char(amount);
416 
417                             ELSIF (l_mcb_cost_flag = 'PROJECT_CURR') THEN
418 
419                                 rev_amount( j ) :=   to_char(l_indirect_cost_project);
420 
421                             END IF;
422 
423 
424       IF g1_debug_mode  = 'Y' THEN
425       	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'mcb_cost_bug rev_amount ' || rev_amount(j));
426       END IF;
427          /*End of Changes for bug 2638840 */
428 
429                          ELSE
430 
431                           rev_amount( j ) :=  to_char(amount);
432 
433                          END IF;
434 
435                          l_process_irs := 'Y';
436 /*-----------------------------------------------------------------------------
437   This case maynot arise, but has been added for safety reasons.
438   ---------------------------------------------------------------------------*/
439                  ELSE
440                          RAISE cost_plus_system_error;
441                  END IF;
442 /*----------------------------------------------------------------------------
443  if no condition satisfies which indirectly means that we need to process
444  for bill rate schedule.
445  ---------------------------------------------------------------------------*/
446             ELSE
447                  l_process_bill_rate := 'Y';
448                  rev_comp_set_id( j ) := NULL;
449                  rev_amount( j ) := NULL;
450             END IF;
451 
452             rate_sch_rev_id := NULL;
453             compiled_set_id := NULL;
454             amount := NULL;
455 /*----------------------------------------------------------------------------
456  For Invoice
457 
458  check whether invoice distribution is WORK, labor/non labor schedule
459  type is Indirect, irs sch id exists and ei is labor/non labor. If
460  all of this is true only then call the api to calculate the indirect
461  cost for Invoice.
462 
463  For Labor/Non Labor expenditure items.
464  ----------------------------------------------------------------------------*/
465 
466            IF (  (d_rule_decode(j) = 1 OR d_rule_decode(j) = 3)  AND
467                  t_inv_irs_id(j) IS NOT NULL                     AND
468               (( t_lab_sch(j ) = 'I'                          AND
469                  sl_function(j ) < 2                      )   OR
470                ( t_nlab_sch( j ) = 'I'                         AND
471                  sl_function( j ) > 1                      ))  AND
472                  NOT fetched_amount                            ) THEN
473 
474 
475             l_ind_cost_acct := NULL;
476             l_ind_cost_denm := NULL;
477             l_indirect_cost_project := NULL;      /* EPP Changes */
478 
479        IF g1_debug_mode  = 'Y' THEN
480        	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Calling Procedure get_exp_item_indirect_cost for Invoice');
481        END IF;
482 
483 
484 	    pa_cost_plus.get_exp_item_indirect_cost(
485                  ei_id( j ), 'I', amount,
486                  l_ind_cost_acct, l_ind_cost_denm,
487                  l_indirect_cost_project,              /* EPP Changes */
488                  rate_sch_rev_id, compiled_set_id,
489                  status, stage );
490 
491 /*----------------------------------------------------------------------------
492 
493  Check for success/failure of the called api :
494 
495  check whether indirect amount and sch rev id were retrieved successfully,
496  if yes then assign these values to the host array variables for indirect
497  amount and rate sct rev id respectively, else set error code to 1 which
498  stands for 'NO COMPILED MULTIPLIER'.
499 
500  status = 100 ==> indicates that Compiled Multiplier does not exist.
501  'stage' indicates the logical step within the procedure
502  pa_cost_plus.get_exp_item_indirect_cost.
503 
504  ---------------------------------------------------------------------------*/
505                  IF ( status = 100 and stage <> 400 ) THEN
506                      inv_comp_set_id(j) := NULL;
507                      inv_amount( j ) := NULL;
508                      error_code( j ) := 1;
509                      l_message_code :=
510                          'Error encountered during processing IRS....' ;
511                      insert_error_message := TRUE;
512 /*-----------------------------------------------------------------------------
513   NO_COST_BASE case whereby raw_revenue amount should be populated with
514   raw_cost.
515   ---------------------------------------------------------------------------*/
516                  ELSIF ( status = 100 and stage = 400 ) THEN
517                          inv_comp_set_id(j ) := 0;
518                          inv_amount( j ) := '0';
519                          l_process_irs := 'Y';
520 /*-----------------------------------------------------------------------------
521   If everything is retrieved as expected which means success.
522   ---------------------------------------------------------------------------*/
523                  ELSIF ( rate_sch_rev_id IS NOT NULL AND
524                          compiled_set_id IS NOT NULL AND
525                          amount          IS NOT NULL AND
526                          status = 0 ) THEN
527                          inv_comp_set_id(j ) := compiled_set_id;
528 
529                         /* MCB Changes : If MCB enabled then take the denom cost other wise
530                                          raw cost */
531 
532                          IF p_mcb_flag = 'Y' THEN
533 
534                           /* Commented for bug 2638840
535                    inv_amount( j ) :=  to_char(l_ind_cost_denm); */
536 
537 /* Bug 2638840 : Get the BTC_COST_BASE_REV_CODE from pa_projects_all table */
538   /* Moved the following code added for bug 2638840 out of the while loop and
539    added the same before the start of while, as each call of  get_irs_amt
540    has EIs that belong to the same project and hence retrieving the
541    btc_cost_base_rev_code once for each call of get_irs_amt would be sufficient
542 
543    l_mcb_cost_flag := NULL;
544 BEGIN
545 
546    select BTC_COST_BASE_REV_CODE
547    into l_mcb_cost_flag
548    from pa_projects_all
549    where project_id =(select project_id from pa_expenditure_items_all where expenditure_item_id=ei_id(j));
550 
551 EXCEPTION
552 WHEN NO_DATA_FOUND THEN
553    IF g1_debug_mode  = 'Y' THEN
554    	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'No Data Found for the ei_id:' ||  ei_id(j));
555    END IF;
556     RAISE ;
557 END;
558 
559      IF g1_debug_mode  = 'Y' THEN
560      	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'BTC_COST_BASE_REV_CODE  :' || l_mcb_cost_flag);
561      END IF; */
562 
563                             IF (l_mcb_cost_flag = 'EXP_TRANS_CURR') THEN
564 
565                                 inv_amount( j ) :=  to_char(l_ind_cost_denm);
566 
567                             ELSIF (l_mcb_cost_flag = 'EXP_FUNC_CURR') THEN
568 
569                                 inv_amount( j ) :=   to_char(l_ind_cost_acct);
570 
571                             ELSIF (l_mcb_cost_flag = 'PROJ_FUNC_CURR') THEN
572 
573                                 inv_amount( j ) :=   to_char(amount);
574 
575                             ELSIF (l_mcb_cost_flag = 'PROJECT_CURR') THEN
576 
577                                 inv_amount( j ) :=   to_char(l_indirect_cost_project);
578 
579                             END IF;
580                        /* End of Changes for bug 2638840 */
581                          ELSE
582 
583                           inv_amount( j ) :=  to_char(amount);
584 
585                          END IF;
586 
587                          l_process_irs := 'Y';
588 
589 /*-----------------------------------------------------------------------------
590   This case maynot arise, but has been added for safety reasons.
591   ---------------------------------------------------------------------------*/
592                  ELSE
593                          RAISE cost_plus_system_error;
594 /*                       inv_comp_set_id(j) := NULL;
595                          inv_amount(j) := NULL;
596                          error_code(j ) := 1;
597                          l_message_code := 'Error encountered during processing IRS....' ;
598 */
599                  END IF;
600 
601 /*----------------------------------------------------------------------------
602    if no condition satisfies which indirectly means that we need to process
603    for bill rate schedule.
604  ----------------------------------------------------------------------------*/
605              ELSE
606                     l_process_bill_rate := 'Y';
607                     inv_comp_set_id( j ) := NULL;
608                     inv_amount( j ) := NULL;
609              END IF;
610 /*-----------------------------------------------------------------------------
611    Rejection code error message which would be eventually populated in
612    pa_expenditure_items_all table.
613  ----------------------------------------------------------------------------*/
614 
615        IF ( insert_error_message ) THEN
616             IF (stage = 200) THEN
617                reason( j ) := 'NO_IND_RATE_SCH_REVISION';
618             ELSIF (stage = 300) THEN
619                reason( j ) := 'NO_COST_PLUS_STRUCTURE';
620             ELSIF (stage = 500) THEN
621                reason( j ) := 'NO_ORGANIZATION';
622             ELSIF (stage = 600) THEN
623                reason( j ) := 'NO_COMPILED_MULTIPLIER';/* BUG 5884742 */
624             ELSIF (stage = 700) THEN
625                reason( j ) := 'NO_ACTIVE_COMPILED_SET';
626             ELSE
627                reason( j ) := 'GET_INDIRECT_COST_FAIL';
628             END IF;
629        END IF;
630 
631        j := j + 1;
632 
633       END LOOP;
634 
635      IF g1_debug_mode  = 'Y' THEN
636      	PA_MCB_INVOICE_PKG.log_message('get_irs_amt: ' || 'Leaving Procedure get_irs_amount');
637      END IF;
638 --NOCOPY CHanges
639 message_code      := l_message_code;
640 process_irs       := l_process_irs;
641 process_bill_rate := l_process_bill_rate;
642 
643 EXCEPTION
644       WHEN client_extn_system_error THEN
645           message_code := 'ORA error encountered while processing pa_client_extn_billing.calc_bill_amount';
646 
647       WHEN cost_plus_system_error THEN
648           message_code := 'ORA error encountered while processing pa_cost_plus.get_exp_item_indirect_cost';
649 
650       WHEN OTHERS THEN
651           message_code := sqlerrm( sqlcode );
652 END get_irs_amt;
653 
654 /* The following Overloaded procedure get_irs_amt is added for Bug 2517675 .
655  !!!This is overloaded procedure for compilation of pro*c files of Patchset H.
656  !!!Note: This .pls with overload function should not be sent along with the patch for Patchset H customers */
657 
658 
659 PROCEDURE get_irs_amt
660 (
661  process_irs                        OUT   NOCOPY  VARCHAR2,
662  process_bill_rate                  OUT   NOCOPY  VARCHAR2,
663  message_code                       OUT   NOCOPY VARCHAR2,
664  rows_this_time                     IN     INTEGER,
665  error_code                         IN OUT  NOCOPY    t_int,
666  reason                             OUT     NOCOPY t_varchar_30,
667  bill_amount                        OUT     NOCOPY t_varchar_30,
668  rev_amount                         OUT     NOCOPY t_varchar_30,
669  inv_amount                         OUT     NOCOPY t_varchar_30,
670  d_rule_decode                      IN OUT     NOCOPY t_int,
671  sl_function                        IN OUT     NOCOPY t_int,
672  ei_id                              IN OUT     NOCOPY t_int,
673  t_rev_irs_id                       IN OUT     NOCOPY t_int,
674  t_inv_irs_id                       IN OUT     NOCOPY t_int,
675  rev_comp_set_id                    IN OUT     NOCOPY t_int,
676  inv_comp_set_id                    IN OUT     NOCOPY t_int,
677  bill_rate_markup                   OUT     NOCOPY t_varchar_2,
678  t_lab_sch                          IN      t_varchar_2,
679  t_nlab_sch                         IN     t_varchar_2
680 )
681 IS
682  BEGIN
683     null;
684  END;
685 /* End of overload for Patchset H */
686 
687 /*This procedure is overloaded for patchset L changes(nonlabor client extension)*/
688 PROCEDURE get_irs_amt
689 (
690  process_irs                        OUT NOCOPY    VARCHAR2,
691  process_bill_rate                  OUT NOCOPY    VARCHAR2,
692  message_code                       OUT NOCOPY    VARCHAR2,
693  rows_this_time                     IN     INTEGER,
694  error_code                         IN OUT  NOCOPY    t_int,
695  reason                             OUT     NOCOPY t_varchar_30,
696  bill_amount                        OUT     NOCOPY t_varchar_30,
697  rev_amount                         OUT     NOCOPY t_varchar_30,
698  inv_amount                         OUT     NOCOPY t_varchar_30,
699  d_rule_decode                      IN OUT     NOCOPY t_int,
700  sl_function                        IN OUT     NOCOPY t_int,
701  ei_id                              IN OUT     NOCOPY t_int,
702  t_rev_irs_id                       IN OUT     NOCOPY t_int,
703  t_inv_irs_id                       IN OUT     NOCOPY t_int,
704  rev_comp_set_id                    IN OUT     NOCOPY t_int,
705  inv_comp_set_id                    IN OUT     NOCOPY t_int,
706  bill_rate_markup                   OUT     NOCOPY t_varchar_2,
707  t_lab_sch                          IN     t_varchar_2,
708  t_nlab_sch                         IN     t_varchar_2,
709  p_mcb_flag                         IN     VARCHAR2,
710  x_bill_trans_currency_code         IN OUT  NOCOPY t_varchar_15,        /* MCB Chnages start */
711  x_bill_txn_bill_rate               IN OUT  NOCOPY t_varchar_30,
712  x_rate_source_id                   IN OUT  NOCOPY t_int,
713  x_markup_percentage                IN OUT  NOCOPY t_varchar_30)         /* MCB Changes end */
714 IS
715  BEGIN
716    null;
717 end;
718 
719 
720 /* Added adjust_rounding_error procedure for solving bug#658088
721 This procedure is called from pardfp.lpc program library.
722 
723 OBJECTIVE :
724  - Obective of procedure is to identify all those expenditure items for a
725    given request_id and project_id, which have ROUNDING_OF_ERROR and adjust
726    the rounding amount against any one of the agreements used to fund the
727    expenditure items.
728 
729 */
730 
731 PROCEDURE adjust_rounding_error
732 (
733  p_project_id         IN     NUMBER,
734  p_request_id         IN     NUMBER,
735  p_task_level_funding IN     NUMBER,
736  x_max_items_allowed  IN     NUMBER,          /* Maximum size of array in ProC   */
737  x_message_code       OUT   NOCOPY  VARCHAR2,
738  x_total_exp_items    OUT   NOCOPY NUMBER,
739  x_exp_item_list      OUT  NOCOPY    t_varchar_100 )
740 IS                                            /*   This is to control the size from calling place */
741 
742 
743 
744 /* --------------------------------------------------------------------
745   top_task_cur  will pick up tasks for a project having task level funding
746    -------------------------------------------------------------------- */
747  CURSOR top_task_cur ( p_project_id IN NUMBER, p_request_id IN NUMBER,
748         p_task_level_funding IN NUMBER )  IS
749  SELECT
750         t.top_task_id TOP_TASK_ID,
751         max(dr.draft_revenue_num) DRAFT_REVENUE_NUM
752  FROM   pa_tasks t,pa_draft_revenues_all dr
753  WHERE  p_task_level_funding = 1  /* for task level funding projects only */
754  AND    dr.project_id = p_project_id
755  AND    t.project_id = dr.project_id
756  AND    dr.request_id   = p_request_id
757  AND    EXISTS
758          ( SELECT NULL
759            FROM pa_expenditure_items_all x,
760                 pa_cust_rev_dist_lines_all rdl
761            WHERE x.request_id+0 = dr.request_id
762            AND   x.task_id      = t.task_id
763            AND   x.revenue_distributed_flag||'' = 'A'
764            AND   x.raw_revenue    = x.accrued_revenue
765            AND   x.raw_revenue     is not NULL
766            AND   x.accrued_revenue is not NULL
767            AND nvl(rdl.function_code,'*') not in ('LRL','LRB','URL','URB')
768            AND rdl.line_num_reversed+0 is null
769            AND nvl(rdl.reversed_flag, 'N' ) = 'N'
770            AND rdl.expenditure_item_id = x.expenditure_item_id+0
771            AND rdl.draft_revenue_num   = dr.draft_revenue_num
772            AND rdl.project_id+0        = dr.project_id
773            AND rdl.request_id+0        = dr.request_id)
774  GROUP BY t.top_task_id
775  UNION ALL
776  SELECT  max(to_number(NULL)) TOP_TASK_ID,
777          max(dr2.draft_revenue_num) DRAFT_REVENUE_NUM
778  FROM    pa_draft_revenues_all dr2
779  WHERE   p_task_level_funding = 0 /* for project level funding only */
780  AND     dr2.project_id    = p_project_id
781  AND     dr2.request_id+0    = p_request_id
782  AND    EXISTS
783          ( SELECT NULL
784            FROM pa_expenditure_items_all ei2,
785                 pa_cust_rev_dist_lines_all rdl2
786            WHERE ei2.request_id   = rdl2.request_id
787            AND rdl2.expenditure_item_id = ei2.expenditure_item_id
788            AND ei2.raw_revenue     is not NULL
789            AND ei2.accrued_revenue is not NULL
790            AND ei2.revenue_distributed_flag||'' = decode(dr2.project_id,NULL,'A','A')
791            AND ei2.raw_revenue    = ei2.accrued_revenue
792            AND nvl(rdl2.function_code,'*') not in ('LRL','LRB','URL','URB')
793            AND rdl2.line_num_reversed+0 is null
794            AND nvl(rdl2.reversed_flag, 'N' ) = 'N'
795            AND rdl2.draft_revenue_num   = dr2.draft_revenue_num
796            AND rdl2.project_id          = dr2.project_id
797            AND rdl2.request_id+0        = dr2.request_id);
798 /* GROUP BY to_number(NULL); */
799 
800 
801 
802 /* --------------------------------------------------------------
803 
804 exp_cur picks up all those expenditure  items
805    - Having raw_revenue <> accrued revenue and there exist
806      atleast one expenditure having raw_revenue = accrued revenue
807      from the set of processed expenditure items for a project_id,
808      task_id( if task level funding is there ).
809    -
810    -------------------------------------------------------------- */
811 
812  CURSOR  exp_cur ( p_project_id         IN NUMBER,
813                    p_request_id         IN NUMBER,
814                    p_top_task_id        IN NUMBER ,
815                    p_draft_revenue_num  IN NUMBER ) IS
816  select ei.expenditure_item_id,
817         rdl.draft_revenue_item_line_num,
818         rdl.draft_revenue_num,
819         ei.accrued_revenue ,
820         ei.raw_revenue
821  from   pa_cust_rev_dist_lines_all rdl,pa_expenditure_items_all ei,
822         pa_tasks t
823  where  p_top_task_id is not NULL
824  AND    ei.request_id+0  = p_request_id
825  AND    ei.raw_revenue     is not NULL
826  AND    ei.accrued_revenue is not NULL
827  AND    ei.revenue_distributed_flag||'' = 'A'
828  AND    ei.expenditure_item_id = rdl.expenditure_item_id
829  AND    ei.raw_revenue <> ei.accrued_revenue
830  AND    rdl.request_id+0  = ei.request_id
831  AND    rdl.project_id   = t.project_id
832  AND    nvl(rdl.function_code,'*') not in ('LRL','LRB','URL','URB')
833  AND    rdl.line_num_reversed+0 is null
834  AND    nvl(rdl.reversed_flag, 'N' ) = 'N'
835  AND    t.project_id   = p_project_id
836  AND    t.task_id      = ei.task_id
837  AND    t.top_task_id  = p_top_task_id
838  AND rdl.draft_revenue_num+0 = p_draft_revenue_num
839  UNION
840  select ei.expenditure_item_id,
841         rdl.draft_revenue_item_line_num,
842         rdl.draft_revenue_num,
843         ei.accrued_revenue ,
844         ei.raw_revenue
845  from   pa_cust_rev_dist_lines_all rdl,pa_expenditure_items_all ei
846  where  p_top_task_id is NULL
847  AND    ei.request_id+0  = p_request_id
848  AND    ei.raw_revenue     is not NULL
849  AND    ei.accrued_revenue is not NULL
850  AND    ei.revenue_distributed_flag||'' = 'A'||''
851  AND    ei.expenditure_item_id = rdl.expenditure_item_id
852  AND    ei.raw_revenue <> ei.accrued_revenue
853  AND    rdl.request_id+0  = ei.request_id
854  AND    rdl.project_id   = p_project_id
855  AND    nvl(rdl.function_code,'*') not in ('LRL','LRB','URL','URB')
856  AND    rdl.line_num_reversed+0 is null
857  AND    nvl(rdl.reversed_flag, 'N' ) = 'N'
858  AND rdl.draft_revenue_num   = p_draft_revenue_num;
859 
860 top_task_cur_rec               top_task_cur%ROWTYPE;
861 exp_cur_rec                    exp_cur%ROWTYPE;
862 roundoff_amount                NUMBER;
863 total_exp_items_processed       NUMBER;
864 total_round_positive            NUMBER;
865 total_round_negative           NUMBER;
866 j                              INTEGER;
867 dummy_x                        VARCHAR2(1);
868 
869 l_message_code                 VARCHAR2(2000);
870 l_total_exp_items 		NUMBER;
871 BEGIN
872 l_total_exp_items := x_total_exp_items;
873 l_message_code    := x_message_code;
874 
875         l_total_exp_items := 0;
876         total_exp_items_processed := 0;
877         total_round_positive := 0;
878         total_round_negative := 0;
879         j                    := 1;
880 
881         l_message_code := 'Error in processing top_task_cur  cursor';
882 
883 	FOR top_task_cur_rec IN top_task_cur
884                              ( p_project_id,
885                                p_request_id,
886                                p_task_level_funding ) LOOP
887 
888 
889              l_message_code := 'Error in processing exp_cur  cursor';
890 
891          BEGIN
892 /* bug#2190645: Joined the t.project_id and rdl_project_id  and
893 		Removed the suppression of index on rdl.draft_revenue_num  */
894           IF p_task_level_funding = 1  THEN
895  /*Modified the query for 9767275*/
896             select /*+ LEADING ( T ) ORDERED USE_NL ( T EI RDL ) INDEX ( RDL PA_CUST_REV_DIST_LINES_N1 ) */ 'X'
897             into   dummy_x
898             from pa_tasks t ,
899                  pa_expenditure_items_all ei ,
900                  pa_cust_rev_dist_lines_all rdl
901             where  ei.request_id+0  = p_request_id
902             AND    ei.raw_revenue     is not NULL
903             AND    ei.accrued_revenue is not NULL
904             AND    ei.revenue_distributed_flag||'' = 'A'
905             AND    ei.expenditure_item_id = rdl.expenditure_item_id
906             AND    ei.raw_revenue <> ei.accrued_revenue
907             AND    rdl.request_id+0  = ei.request_id
908             AND    rdl.project_id   = t.project_id
909             AND    nvl(rdl.function_code,'*') not in ('LRL','LRB','URL','URB')
910             AND    rdl.line_num_reversed+0 is null
911             AND    nvl(rdl.reversed_flag, 'N' ) = 'N'
912             AND    t.project_id   = rdl.project_id
913             AND    rdl.project_id   = p_project_id
914             AND    t.task_id      = ei.task_id
915             AND    t.top_task_id  =  top_task_cur_rec.TOP_TASK_ID
916             AND rdl.draft_revenue_num = top_task_cur_rec.DRAFT_REVENUE_NUM
917             having sum(ei.accrued_revenue) = sum(ei.raw_revenue);
918          ELSE
919 
920  /*Modified the query for 9767275*/
921             select /*+ LEADING(EI) ORDERED INDEX ( RDL PA_CUST_REV_DIST_LINES_N1 ) */ 'X'
922             into   dummy_x
923             from   pa_expenditure_items_all ei ,
924                    pa_cust_rev_dist_lines_all rdl
925             where  ei.request_id+0  = p_request_id
926             AND    ei.raw_revenue     is not NULL
927             AND    ei.accrued_revenue is not NULL
928             AND    ei.revenue_distributed_flag||''     = 'A'||''
929             AND    ei.expenditure_item_id = rdl.expenditure_item_id
930             AND    ei.raw_revenue <> ei.accrued_revenue
931             AND    rdl.request_id+0  = ei.request_id
932             AND    ei.project_id   = p_project_id /* 10063704 */
933             AND    rdl.project_id   = p_project_id
934             AND    nvl(rdl.function_code,'*') not in ('LRL','LRB','URL','URB')
935             AND    rdl.line_num_reversed+0 is null
936             AND    nvl(rdl.reversed_flag, 'N' ) = 'N'
937             AND rdl.draft_revenue_num   = top_task_cur_rec.DRAFT_REVENUE_NUM
938             having sum(ei.accrued_revenue) = sum(ei.raw_revenue);
939          END IF;
940 
941              FOR exp_cur_rec IN exp_cur
942                   ( p_project_id,
943                     p_request_id,
944                     top_task_cur_rec.TOP_TASK_ID,
945                     top_task_cur_rec.DRAFT_REVENUE_NUM ) LOOP
946 
947                   roundoff_amount := exp_cur_rec.ACCRUED_REVENUE -
948                                     exp_cur_rec.RAW_REVENUE;
949 
950              IF ( l_total_exp_items < x_max_items_allowed ) THEN
951                x_exp_item_list( j ) := 'Exp_Id : '||
952                     to_char(exp_cur_rec.EXPENDITURE_ITEM_ID,999999999999)||
953                     '  Accrued_revenue : '||
954                     to_char( exp_cur_rec.ACCRUED_REVENUE,999999999999999.9999)||
955                     ' Raw_revenue : '||
956                     to_char(exp_cur_rec.RAW_REVENUE,999999999999999.9999);
957                l_total_exp_items := l_total_exp_items + 1;
958                j := j + 1;
959              END IF;
960 
961                total_exp_items_processed := total_exp_items_processed +1;
962                if ( roundoff_amount > 0 ) then
963                  total_round_positive := total_round_positive   + roundoff_amount;
964                else
965                  total_round_negative := total_round_negative + roundoff_amount;
966                end if;
967 
968                BEGIN
969 
970                   l_message_code := 'Error in update on pa_cut_rev_dist_lines_all';
971 
972                   UPDATE pa_cust_rev_dist_lines_all l
973                      SET l.amount = PA_CURRENCY.ROUND_CURRENCY_AMT(l.amount -
974                          DECODE(code_combination_id, -1, roundoff_amount,
975                                                      -2, roundoff_amount,
976                                                      -roundoff_amount)),
977                          l.projfunc_revenue_amount =                            -- Below lines added for Bug 5042421
978                          DECODE(l.revproc_currency_code, l.projfunc_currency_code,
979                               PA_CURRENCY.ROUND_CURRENCY_AMT(l.amount -
980                                   DECODE(code_combination_id, -1, roundoff_amount,
981                                                      -2, roundoff_amount,
982                                                      -roundoff_amount)),
983                                 projfunc_revenue_amount),
984                          l.project_revenue_amount =
985                          DECODE(l.revproc_currency_code, l.project_currency_code,
986                               PA_CURRENCY.ROUND_CURRENCY_AMT(l.amount -
987                                   DECODE(code_combination_id, -1, roundoff_amount,
988                                                      -2, roundoff_amount,
989                                                      -roundoff_amount)),
990                                 project_revenue_amount),
991                          l.funding_revenue_amount =
992                          DECODE(l.revproc_currency_code, l.funding_currency_code,
993                               PA_CURRENCY.ROUND_CURRENCY_AMT(l.amount -
994                                   DECODE(code_combination_id, -1, roundoff_amount,
995                                                      -2, roundoff_amount,
996                                                      -roundoff_amount)),
997                                 funding_revenue_amount),
998                          l.revtrans_amount =
999                          DECODE(l.revproc_currency_code, l.revtrans_currency_code,
1000                               PA_CURRENCY.ROUND_CURRENCY_AMT(l.amount -
1001                                   DECODE(code_combination_id, -1, roundoff_amount,
1002                                                      -2, roundoff_amount,
1003                                                      -roundoff_amount)),
1004                                 revtrans_amount)                               -- End of Bug 5042421
1005                    WHERE l.expenditure_item_id =
1006                                      exp_cur_rec.EXPENDITURE_ITEM_ID
1007                      AND l.draft_revenue_num =
1008                                      exp_cur_rec.DRAFT_REVENUE_NUM
1009                      AND l.draft_revenue_item_line_num =
1010                                      exp_cur_rec.DRAFT_REVENUE_ITEM_LINE_NUM;
1011 
1012                 l_message_code := 'Error in update on pa_draft_revenue_items';
1013 
1014                   UPDATE pa_draft_revenue_items i
1015                      SET i.amount = i.amount - roundoff_amount,
1016                          i.projfunc_revenue_amount =	                   -- Below lines added for Bug 5042421
1017                           DECODE(i.revproc_currency_code, i.projfunc_currency_code,
1018                                    i.amount - roundoff_amount,
1019                                 i.projfunc_revenue_amount),
1020                          i.project_revenue_amount =
1021                           DECODE(i.revproc_currency_code, i.project_currency_code,
1022                                    i.amount - roundoff_amount,
1023                                 i.project_revenue_amount),
1024                          i.funding_revenue_amount =
1025                           DECODE(i.revproc_currency_code, i.funding_currency_code,
1026                                    i.amount - roundoff_amount,
1027                                 i.funding_revenue_amount),
1028                          i.revtrans_amount =
1029                           DECODE(i.revproc_currency_code, i.revtrans_currency_code,
1030                                    i.amount - roundoff_amount,
1031                                 i.revtrans_amount)				-- End of Bug 5042421
1032                    WHERE i.project_id = p_project_id
1033                      AND i.draft_revenue_num =
1034                                   exp_cur_rec.DRAFT_REVENUE_NUM
1035                      AND i.line_num =
1036                                   exp_cur_rec.DRAFT_REVENUE_ITEM_LINE_NUM;
1037 
1038                 l_message_code := 'Error in update on pa_expenditure_items_all';
1039 
1040                   UPDATE pa_expenditure_items_all x
1041                      SET x.accrued_revenue
1042                             = x.accrued_revenue - roundoff_amount
1043                    WHERE x.expenditure_item_id =
1044                                  exp_cur_rec.EXPENDITURE_ITEM_ID;
1045                EXCEPTION
1046                  WHEN OTHERS  THEN
1047                   RAISE;
1048                END;
1049 
1050              END LOOP;
1051 
1052           EXCEPTION
1053              WHEN NO_DATA_FOUND THEN
1054                 null;
1055              WHEN OTHERS THEN
1056                RAISE;
1057           END;
1058         END LOOP;
1059         l_message_code := 'OK toal_exp_items_processed : '||
1060              to_char(total_exp_items_processed)||' tot_pos : '||
1061              to_char(total_round_positive)||' tot_neg : '||
1062              to_char(total_round_negative);
1063 
1064 x_message_code    :=  l_message_code;
1065 x_total_exp_items :=  l_total_exp_items;
1066 
1067 EXCEPTION
1068   WHEN OTHERS THEN
1069 x_message_code := NULL;
1070 x_total_exp_items := NULL;
1071     RAISE;
1072 END adjust_rounding_error;
1073 
1074 
1075 procedure rev_ccid_chk (P_rec_ccid      IN  NUMBER,
1076                         P_rev_ccid      IN  NUMBER,
1077                         P_rg_ccid       IN  NUMBER,
1078                         P_rl_ccid       IN  NUMBER,
1079                         P_ou_reval_flag IN  VARCHAR2,
1080                         P_out_status    OUT  NOCOPY VARCHAR2
1081                         )
1082 IS
1083 
1084    l_dummy  VARCHAR2(1);
1085 
1086 BEGIN
1087 
1088     SELECT 'x'
1089     INTO   l_dummy
1090     FROM   gl_code_combinations
1091     WHERE  code_combination_id = P_Rec_ccid;
1092 
1093     SELECT 'x'
1094     INTO   l_dummy
1095     FROM   gl_code_combinations
1096     WHERE  code_combination_id = P_Rev_ccid;
1097 
1098   IF P_ou_reval_flag ='Y' then
1099 
1100     SELECT 'x'
1101     INTO   l_dummy
1102     FROM   gl_code_combinations
1103     WHERE  code_combination_id = P_rg_ccid;
1104 
1105     SELECT 'x'
1106     INTO   l_dummy
1107     FROM   gl_code_combinations
1108     WHERE  code_combination_id = P_rl_ccid;
1109 
1110   END IF;
1111 
1112     p_out_status:='Y';
1113 
1114   EXCEPTION
1115     WHEN NO_DATA_FOUND THEN
1116          p_out_status:='N';
1117     WHEN OTHERS THEN
1118 	p_out_status := NULL;
1119          Raise;
1120 
1121 END rev_ccid_chk;
1122 
1123 END pa_revenue_amt;