DBA Data[Home] [Help]

PACKAGE BODY: APPS.IGIRRPI

Source


1 PACKAGE BODY IGIRRPI AS
2 -- $Header: igirrpib.pls 120.18.12010000.5 2009/01/19 14:50:03 gaprasad ship $
3 
4 
5   l_state_level CONSTANT NUMBER := FND_LOG.LEVEL_STATEMENT;
6   l_proc_level  CONSTANT NUMBER := FND_LOG.LEVEL_PROCEDURE;
7   l_event_level CONSTANT NUMBER := FND_LOG.LEVEL_EVENT;
8   l_excep_level CONSTANT NUMBER := FND_LOG.LEVEL_EXCEPTION;
9   l_error_level CONSTANT NUMBER := FND_LOG.LEVEL_ERROR;
10   l_unexp_level CONSTANT NUMBER := FND_LOG.LEVEL_UNEXPECTED;
11 
12 TYPE    DATE_RANGE IS RECORD
13                       ( start_date        DATE
14                       , end_date          DATE
15                       , actual_start_date DATE
16                       , factor NUMBER );
17 SUBTYPE RAIL IS  ra_interface_lines_all%ROWTYPE;
18 SUBTYPE RAID IS  ra_interface_distributions_all%ROWTYPE;
19 
20 TYPE    RAID_TABLE       is table of RAID       index by binary_integer;
21 TYPE    DATE_RANGE_TABLE is table of DATE_RANGE index by binary_integer;
22 /*
23 -- The g_raid_Table which has global scope in this program
24 */
25 g_raid_table      RAID_TABLE;
26 /*
27 -- ---------------------------------------------------------------------------
28 -- Row <0  is the 'REC' entry and there may be many entries per standing charge
29 -- Row >0  is the 'REV' entry and there may be more than 1 entry for each
30 -- standing charge line this should be neccessary to accomodate price breaks etc.
31 -- The reason we need a table is that we need to calculate the % based on the
32 -- amounts and then clear the amount columns based on the options set at the batch
33 -- source level.
34 -- ----------------------------------------------------------------------------
35 */
36 g_curr_rec_idx BINARY_INTEGER ;
37 g_curr_rev_idx BINARY_INTEGER ;
38 
39 rev_idx BINARY_INTEGER ;
40 /*
41 -- Note: We need the above index to keep track of the number of entries made per run into
42 -- the RAID_TABLE per RUN.
43 -- Assumptions
44 -- 1. Context and other transaction flexfield information is set
45 -- 2. revenue proration is done at transaction line level.
46 -- Algo:
47 -- For each standing charge
48 --    For each charge line
49 --       Process Charge :
50 --            Determine Billing Period
51 --            Determine the overall ratio
52 --            Process Price Breaks :
53 --               Create entry in Ra_interface_lines
54 --                   -- Also create a parallel entry in the Ra_interface_salescredits
55 --               Build Ra_interface_distribution information in PLSQL table
56 --               Consolidate the amount, percent entries for all the REV distributions in the PLSQL table
57 --       Process Distributions :
58 --            Consolidate the amount, percent entries for all the REC distributions in the PLSQL table
59 --            Delete the entries from the PL/SQL table.
60 --       Update Sequence
61 --   End For Charge line
62 -- End for Charge
63 -- Set up issues :
64 --    To ensure that the information is transferred from the standing charge lines to the invoice
65 --       Set the revenue allocation rule as 'Amount' and ensure that the standing charges do not
66 --       use any accounting rules.
67 */
68 -- --------------------------------------------------------------------------
69 --           CONSTANTS - NEEDS VERIFICATION FOR NLS COMPLIANCE
70 -- --------------------------------------------------------------------------
71 STANDING_CHARGE_STATUS      CONSTANT VARCHAR2(30) :=  'ACTIVE';
72 ADVANCE_STATUS              CONSTANT VARCHAR2(30) :=  'ADVANCE';
73 ARREARS_STATUS              CONSTANT VARCHAR2(30) :=  'ARREARS';
74 REVENUE_CODE                CONSTANT VARCHAR2(30) :=  'REV';
75 RECEIVABLE_CODE             CONSTANT VARCHAR2(30) :=  'REC';
76 ALLOCATION_PERCENT_CODE     CONSTANT VARCHAR2(30) :=  'Percent';
77 ALLOCATION_AMOUNT_CODE      CONSTANT VARCHAR2(30) :=  'Amount';
78 LINE_CODE                   CONSTANT VARCHAR2(30) :=  'LINE';
79 USER_CODE                   CONSTANT VARCHAR2(30) :=  'User';
80 END_DATE_TIME               CONSTANT VARCHAR2(30) :=  ' 23:59:59';
81 BEGIN_DATE_TIME             CONSTANT VARCHAR2(30) :=  ' 00:00:00';
82 RPI_DATE_FORMAT             CONSTANT VARCHAR2(30) :=  'DD/MM/YYYY HH24:MI:SS';
83 DEF_DATE_FORMAT             CONSTANT VARCHAR2(30) :=  'DD/MM/YYYY';
84 -- ----------------------------------------------------------------------------
85 --  CUSTOM VALUES
86 -- ----------------------------------------------------------------------------
87 TRANSACTION_CODE       VARCHAR2(300);
88 FROM_DATE_INFO         VARCHAR2(300);
89 TO_DATE_INFO           VARCHAR2(300);
90 -- --------------------------------------------------------------------------
91 --                               CURSORS
92 -- --------------------------------------------------------------------------
93 CURSOR C_stand_charges ( cp_run_date in date
94                        , cp_sob_id in number
95                        , cp_batch_source_id in number )  IS
96 /*------------------------------------------------------*
97  |                                                      |
98  |       Cursor for Selecting Standing Charges          |
99  |                                                      |
100  *------------------------------------------------------*/
101         SELECT DISTINCT
102                sc.standing_charge_id
103         ,      sc.set_of_books_id
104         ,      sc.comments
105         ,      sc.charge_reference
106         ,      sc.description           desc_1
107         ,      sc.bill_to_customer_id
108         ,      sc.bill_to_site_use_id
109         ,      sc.bill_to_contact_id
110         ,      sc.ship_to_customer_id
111         ,      sc.ship_to_address_id
112         ,      sc.bill_to_address_id
113         ,      sc.ship_to_site_use_id
114         ,      sc.ship_to_contact_id
115         ,      sc.start_date
116         ,      sc.end_date
117         ,      sc.standing_charge_date
118         ,      sc.next_due_date
119         ,      sc.suppress_inv_print
120         ,      sc.cust_trx_type_id
121         ,      sc.receipt_method_id
122         ,      sc.batch_source_id
123         ,      sc.salesrep_id
124         ,      sc.advance_arrears_ind  -- change here to do testing
125         ,      sc.bank_account_id
126 	,      sc.payment_trxn_extension_id	/*Bug No 5905216 Payment Upgrade for R12*/
127         ,      sc.previous_due_date    -- change here to do testing
128         ,      sc.creation_date
129         ,      sc.created_by
130         ,      sc.last_update_date
131         ,      sc.last_updated_by
132         ,      sc.last_update_login
133         ,      SYSDATE
134         ,      sc.period_name          sc_period_name
135         ,      sc.rowid                sc_rowid
136         ,      sc.default_invoicing_rule
137         ,      bs.name                 bs_name
138         ,      nvl(sc.term_id,4) term_id
139         ,      bs.rev_acc_allocation_rule
140         ,      sob.currency_code
141 /*5905216*/
142 	,      sc.org_id
143 	,      sc.legal_entity_id
144         FROM   gl_sets_of_books           sob
145         ,      igi_rpi_standing_charges   sc
146         ,      ar_system_parameters       sp
147         ,      ra_batch_sources           bs
148         ,      ra_cust_trx_types          ct
149         ,      hz_cust_accounts           ca
150         WHERE  sp.set_of_books_id    = cp_sob_id
151         AND    sp.set_of_books_id    = sob.set_of_books_id
152         AND    sp.set_of_books_id    = sc.set_of_books_id
153         AND    bs.batch_source_id    = NVL(cp_batch_source_id,bs.batch_source_id)
154         AND    nvl(bs.end_date,cp_run_date +1)   >= cp_run_date
155         AND    nvl(bs.start_date,cp_run_date-1) <= cp_run_date
156         AND    sc.batch_source_id            = bs.batch_source_id
157         AND    sc.cust_trx_type_id           = ct.cust_trx_type_id
158         AND    nvl(ct.end_date,cp_run_date+1)   >= cp_run_date
159         AND    nvl(ct.start_date,cp_run_date-1) <= cp_run_date
160         AND    nvl(sc.date_synchronized_flag,'Y') = 'Y'
161         AND    sc.status                     = STANDING_CHARGE_STATUS
162         /*changed the following AND clause for bug 4436839*/
163         AND    (
164 
165                  (  nvl(sc.advance_arrears_ind,sc.default_invoicing_rule) = ARREARS_STATUS
166                     AND nvl(sc.previous_due_date,sc.start_date) <= nvl(sc.end_date,sc.next_due_date)
167                  )
168                  OR
169                  (   nvl(sc.advance_arrears_ind,sc.default_invoicing_rule)   = ADVANCE_STATUS
170                      AND sc.next_due_date <= NVL(sc.end_date,sc.next_due_date)
171                   )
172                )
173 	AND    cp_run_date                   >= sc.next_due_date
174         AND sc.bill_to_customer_id = ca.cust_account_id
175         AND ca.status = 'A'
176         ORDER BY sc.standing_charge_id;
177 --
178 CURSOR C_line_details (cp_standing_charge_id in number
179                       ,cp_sob_id             in number ) IS
180 /*---------------------------------------------------------------------------*
181  | Select Cursor for Line Details based on the Selected Standing Charge
182  | cursor above
183  *---------------------------------------------------------------------------*/
184         SELECT NVL(ld.price,0)            price
185         ,      NVL(ld.previous_price,0)   previous_price
186         ,      NVL(ld.revised_price,0)    revised_price
187         ,      ld.charge_item_number
188         ,      ld.revised_effective_date
189         ,      ld.current_effective_date
190         ,      ld.previous_effective_date
191         ,      ld.line_item_id
192         ,      ld.item_id
193         ,      ld.quantity
194         ,      ld.description          desc_2
195         ,      ld.vat_tax_id
196         ,      ld.revenue_code_combination_id
197         ,      ld.receivable_code_combination_id
198         ,      ld.period_name          ld_period_name
199         ,      ld.accounting_rule_id
200         ,      decode( ld.accounting_rule_id, null, null,
201                        ld.start_date )   start_date
202         ,      decode( ld.accounting_rule_id, null, null,
203                        ld.duration )   duration
204         ,      uom.uom_code            uom_uom_code
205         ,      uom.unit_of_measure     unit_of_measure
206         ,      vt.tax_rate_code
207         ,      vt.percentage_rate
208         ,      nvl(vt.allow_adhoc_tax_rate_flag,'N')  validate_flag
209         ,      ld.rowid ld_rowid
210 /*5905216*/
211 	,      ld.legal_entity_id
212         FROM   igi_rpi_line_details     ld
213         ,      mtl_units_of_measure       uom
214         ,      igi_rpi_component_periods  rcp
215         ,      ZX_RATES_B             vt                         			 /*Bug No 7606235*/
216         WHERE  ld.standing_charge_id          = cp_standing_charge_id
217         --AND    nvl(uom.disable_date,SYSDATE) >= SYSDATE
218         AND    uom.unit_of_measure            = rcp.unit_of_measure
219         AND    rcp.period_name                = ld.period_name
220         AND    ld.vat_tax_id                  = vt.tax_rate_id(+)
221         AND    NVL(vt.effective_from, SYSDATE)   <=  SYSDATE
222         AND    NVL(vt.effective_to, SYSDATE)     >=  SYSDATE        ORDER BY ld.line_item_id ;
223 
224 --
225 -- Set the Transaction Flexfield context and Line Transaction flexfield context
226 -- and other nls related stuff.
227 --
228 PROCEDURE  SetValuesForGlobals IS
229      CURSOR c_rpi_globals IS
230           SELECT  igiaso.rpi_header_context_code
231           ,       igiaso.rpi_line_context_code
232           FROM    igi_ar_system_options igiaso
233           ;
234     CURSOR C_rpi_labels (label_code in varchar2)
235     IS
236           SELECT  meaning
237           FROM    igi_lookups
238           WHERE   lookup_type = 'RPI_LABELS'
239           AND     lookup_code = label_code
240          ;
241 
242 BEGIN
243     FOR l_rpi in c_rpi_globals LOOP
244         IF l_rpi.rpi_header_context_code IS NULL
245         OR l_rpi.rpi_line_context_code IS NULL
246         THEN
247                return;
248         END IF;
249 
250         IF l_rpi.rpi_header_context_code <> l_rpi.rpi_line_context_code THEN
251            return;
252         END IF;
253 
254         TRANSACTION_CODE := l_rpi.rpi_line_context_code;
255 
256         FOR l_label in c_rpi_labels ( 'FROM_DATE_LABEL' )
257         LOOP
258            FROM_DATE_INFO := ' '||l_label.meaning||' ';
259         END LOOP;
260         FOR l_label in c_rpi_labels ( 'TO_DATE_LABEL' )
261         LOOP
262            TO_DATE_INFO := ' '||l_label.meaning||' ';
263         END LOOP;
264 
265     END LOOP;
266 
267 END SetValuesForGlobals;
268 -- -----------------------------------------------------------------------------
269 
270   PROCEDURE WriteToLogFile ( pp_msg_level in number,pp_path in varchar2, pp_mesg in varchar2 ) IS
271   BEGIN
272      IF pp_msg_level >=  FND_LOG.G_CURRENT_RUNTIME_LEVEL THEN
273          fnd_log.string(pp_msg_level, pp_path, pp_mesg );
274      END IF;
275   END;
276 
277 FUNCTION  UseSalesCreditsAtSystem return BOOLEAN IS
278 
279     CURSOR C_scredits IS
280         SELECT 'x'
281         FROM   ar_system_parameters
282         WHERE  salesrep_required_flag = 'Y'
283         ;
284 
285     -- check if autoaccounting is set up to use salesreps.
286    CURSOR c_auto_acc IS
287         select 'x'
288         from ra_account_defaults rad,
289             ra_account_default_segments rads
290         where rads.gl_default_id = rad.gl_default_id
291         and rads.table_name = 'RA_SALESREPS'
292         ;
293 
294 BEGIN
295 
296     FOR l_acc IN C_auto_acc LOOP
297         return TRUE;
298     END LOOP;
299 
300     FOR l_credits IN c_scredits LOOP
301         return TRUE;
302     END LOOP;
303 
304 
305     return FALSE;
306 EXCEPTION WHEN OTHERS THEN return FALSE;
307 END UseSalesCreditsAtSystem;
308 
309 FUNCTION UseSalesCreditsAtSource (p_source_id in number) return BOOLEAN IS
310    CURSOR c_batch_sources (cp_source_id in number) IS
311         SELECT 'x'
312         FROM   ra_batch_sources
313         WHERE  allow_sales_credit_flag = 'Y'
314         AND    batch_source_id = cp_source_id
315         ;
316 BEGIN
317    FOR l_bs IN c_batch_sources (p_source_id) LOOP
318        return TRUE;
319    END LOOP;
320    return FALSE;
321 EXCEPTION WHEN OTHERS THEN return FALSE;
322 END UseSalesCreditsAtSource;
323 /*
324 -- Sales Credits may be allowed at batch source and could override the system option
325 -- So see if enabled at system option then at batch source
326 --
327 */
328 FUNCTION UseSalesCredits ( p_source_id in number) return BOOLEAN
329 IS
330 BEGIN
331    IF UseSalesCreditsAtSystem THEN
332       return TRUE;
333    ELSIF UseSalesCreditsAtSource ( p_source_id ) THEN
334       return TRUE;
335    END IF;
336    return FALSE;
337 END UseSalesCredits;
338 
339 -- -----------------------------------------------------------------------------
340 FUNCTION  Get_invoicing_Rule (fp_name in varchar2) return NUMBER IS
341   CURSOR c_rule IS
342     SELECT rule_id
343     FROM   ra_rules
344     WHERE  rule_id IN (-2,-3)
345     AND    type    = 'I'
346     AND    UPPER(name) LIKE UPPER(fp_name)||'%'; -- Bug 2413794 vgadde added UPPER both sides
347     l_rule c_rule%ROWTYPE;
348 BEGIN
349     OPEN c_rule;
350     FETCH c_rule INTO l_rule;
351     CLOSE c_rule;
352     RETURN l_rule.rule_id;
353 EXCEPTION WHEN OTHERS THEN RETURN -1;
354 END Get_invoicing_Rule;
355 
356 PROCEDURE Next_Scheduled_Dates  ( pp_sched_id in number
360                                 , pp_new_prev_due_date in out NOCOPY date
357                                 , pp_period_name in varchar2
358                                 , pp_cur_next_due_date in date
359                                 , pp_new_next_due_date in out NOCOPY date
361                                 ) IS
362 CURSOR c_sched IS
363     SELECT date1, date2, date3, date4
364            , pp_cur_next_due_date old_date
365     FROM   igi_rpi_period_schedules
366     WHERE  schedule_id  = pp_sched_id
367     AND    period_name  = pp_period_name
368     AND    nvl(enabled_flag,'Y') = 'Y';
369 l_new_next_due_date_old   date;
370 l_new_prev_due_date_old   date;
371 BEGIN
372     l_new_next_due_date_old := pp_new_next_due_date;
373     l_new_prev_due_date_old := pp_new_prev_due_date;
374 
375     FOR l_s in C_sched LOOP
376 
377      /* next due date */
378 
379         if    to_date(to_char(l_s.date1,'DD/MM/')
380               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >
381               pp_cur_next_due_date
382         then
383               pp_new_next_due_date := to_date(to_char(l_s.date1,'DD/MM/')
384               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
385         elsif to_date(to_char(l_s.date2,'DD/MM/')
386               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >
387               pp_cur_next_due_date
388         then
389               pp_new_next_due_date := to_date(to_char(l_s.date2,'DD/MM/')
390               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
391         elsif to_date(to_char(l_s.date3,'DD/MM/')
392               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >
393               pp_cur_next_due_date
394         then
395               pp_new_next_due_date := to_date(to_char(l_s.date3,'DD/MM/')
396               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
397         elsif to_date(to_char(l_s.date4,'DD/MM/')
398               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >
399               pp_cur_next_due_date
400         then
401               pp_new_next_due_date := to_date(to_char(l_s.date4,'DD/MM/')
402               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
403         elsif to_date(to_char(l_s.date1,'DD/MM/')
404               ||to_char(to_number(to_char(pp_cur_next_due_date,'YYYY'))+1),
405                  DEF_DATE_FORMAT) >
406               pp_cur_next_due_date
407         then
408               pp_new_next_due_date := to_date(to_char(l_s.date1,'DD/MM/')
409               ||to_char(to_number(to_char(pp_cur_next_due_date,'YYYY'))+1),
410                  DEF_DATE_FORMAT);
411         end if;
412   --       pp_new_prev_due_date := pp_cur_next_due_date;
413      /* prev due date */
414 
415         if    to_date(to_char(l_s.date1,'DD/MM/')
416               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >=
417               pp_cur_next_due_date
418         then
419               pp_new_prev_due_date := to_date(to_char(l_s.date4,'DD/MM/')
420               ||to_char(to_number(to_char(pp_cur_next_due_date,'YYYY'))-1),DEF_DATE_FORMAT);
421         elsif to_date(to_char(l_s.date2,'DD/MM/')
422               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >=
423               pp_cur_next_due_date
424         then
425               pp_new_prev_due_date := to_date(to_char(l_s.date1,'DD/MM/')
426               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
427         elsif to_date(to_char(l_s.date3,'DD/MM/')
428               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >=
429               pp_cur_next_due_date
430         then
431               pp_new_prev_due_date := to_date(to_char(l_s.date2,'DD/MM/')
432               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
433         elsif to_date(to_char(l_s.date4,'DD/MM/')
434               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT) >=
435               pp_cur_next_due_date
436         then
437               pp_new_prev_due_date := to_date(to_char(l_s.date3,'DD/MM/')
438               ||to_char(pp_cur_next_due_date,'YYYY'),DEF_DATE_FORMAT);
439         elsif to_date(to_char(l_s.date1,'DD/MM/')
440               ||to_char(to_number(to_char(pp_cur_next_due_date,'YYYY'))+1),
441                  DEF_DATE_FORMAT) >=
442               pp_cur_next_due_date
443         then
444               pp_new_prev_due_date := to_date(to_char(l_s.date4,'DD/MM/')
445               ||to_char(pp_cur_next_due_date,'YYYY'),
446                  DEF_DATE_FORMAT);
447         end if;
448 
449 
450     END LOOP;
451 
452     WriteToLogFile (l_state_level,'igi.plsql.igirrpi.next_scheduled_dates ',' --> New Next Due Date '|| pp_new_next_due_date );
453     WriteToLogFile (l_state_level,'igi.plsql.igirrpi.next_scheduled_dates ',' --> Cur Next Due Date '|| pp_cur_next_due_date );
454     WriteToLogFile (l_state_level,'igi.plsql.igirrpi.next_scheduled_dates', ' --> New Prev Due Date '|| pp_new_prev_due_date );
455 EXCEPTION
456   WHEN OTHERS THEN
457      pp_new_next_due_date := l_new_next_due_date_old;
458      pp_new_prev_due_date := l_new_prev_due_date_old;
459      app_exception.raise_exception;
460 END Next_Scheduled_Dates;
461 --
462 --
463 PROCEDURE Next_Due_Dates      (  pp_curr_next_due_date in date
464                                 ,pp_period_name        in varchar2
465                                 ,pp_advance_arrears_ind in varchar2
466                                 ,pp_new_prev_due_date  in out NOCOPY date
467                                 ,pp_new_next_due_date  in out NOCOPY date
471                                 ) IS
468                                 ,pp_new_schedule_id    in out NOCOPY number
469                                 ,pp_new_factor         in out NOCOPY number
470                                 ,pp_new_component      in out NOCOPY varchar2
472 CURSOR c_info is
473      SELECT DECODE(component
474             ,'DAY'   ,TO_NUMBER(factor)*1 + pp_curr_next_due_date
475             ,'WEEK'  ,TO_NUMBER(factor)*7 + pp_curr_next_due_date
476             ,'MONTH' ,ADD_MONTHS(pp_curr_next_due_date,TO_NUMBER(factor))
477             ,'YEAR'  ,ADD_MONTHS(pp_curr_next_due_date,TO_NUMBER(factor)*12)
478             ) new_next_due_date
479      ,      DECODE(component,'DAY'   ,TO_NUMBER(factor)* -1 + pp_curr_next_due_date
480             ,'WEEK'  ,TO_NUMBER(factor)* -7 + pp_curr_next_due_date
481             ,'MONTH' ,ADD_MONTHS(pp_curr_next_due_date,TO_NUMBER(factor)* -1)
482             ,'YEAR'  ,ADD_MONTHS(pp_curr_next_due_date,TO_NUMBER(factor)* -12)
483             ) new_prev_due_date
484      ,      nvl( schedule_id,0) schedule_id
485      ,      period_name
486      ,      use_schedules_flag
487      ,      factor
488      ,      component
489      FROM   igi_rpi_component_periods
490      WHERE  period_name = pp_period_name
491      AND    nvl(enabled_flag,'Y') = 'Y' ;
492  l_new_prev_due_date_old  date          ;
493  l_new_next_due_date_old  date          ;
494  l_new_schedule_id_old    number        ;
495  l_new_factor_old         number        ;
496  l_new_component_old      varchar2(25)  ;
497 BEGIN
498  l_new_prev_due_date_old  :=  pp_new_prev_due_date;
499  l_new_next_due_date_old  :=  pp_new_next_due_date;
500  l_new_schedule_id_old    :=  pp_new_schedule_id;
501  l_new_factor_old         :=  pp_new_factor;
502  l_new_component_old      :=  pp_new_component;
503 
504   FOR l_info IN C_info LOOP
505 
506       pp_new_prev_due_date  :=  l_info.new_prev_due_date;
507       pp_new_next_due_date  :=  l_info.new_next_due_date;
508       pp_new_schedule_id    :=  l_info.schedule_id;
509       pp_new_factor         :=  l_info.factor;
510       pp_new_component      :=  l_info.component;
511 
512      IF l_info.use_schedules_flag = 'Y' and l_info.schedule_id <> 0
513         and l_info.component = 'DAY'
514      THEN
515         /* the period is of type 1/4 Days so calculate the FACTOR */
516         Next_Scheduled_Dates ( l_info.schedule_id
517                            ,   l_info.period_name
518                            ,   pp_curr_next_due_date
519                            ,   pp_new_next_due_date
520                            ,   pp_new_prev_due_date
521                            );
522 
523            pp_new_factor := to_date(to_char(pp_new_next_due_date -1,DEF_DATE_FORMAT)||END_DATE_TIME,
524                                    RPI_DATE_FORMAT)
525                             -
526                             to_date(to_char(pp_curr_next_due_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,
527                                     RPI_DATE_FORMAT)
528                             ;
529 
530      END IF;
531   END LOOP;
532 
533   RETURN;
534 EXCEPTION
535    WHEN OTHERS THEN
536      pp_new_prev_due_date  :=  l_new_prev_due_date_old;
537      pp_new_next_due_date  :=  l_new_next_due_date_old;
538      pp_new_schedule_id    :=  l_new_schedule_id_old;
539      pp_new_factor         :=  l_new_factor_old;
540      pp_new_component      :=  l_new_component_old;
541      app_exception.raise_exception;
542 END Next_Due_Dates;
543 --
544 /*
545 -- Ensure that the charge component <> billing component
546 -- Before using this function.
547 */
548 
549 FUNCTION Component_to_Days  ( p_component   in VARCHAR2
550                             , p_start_date  in DATE
551                             , p_factor      in number
552                             )
553 RETURN NUMBER IS
554       l_no_of_days NUMBER ;
555 BEGIN
556       l_no_of_days := 0;
557      IF p_component = 'YEAR' THEN
558          return (add_months(p_start_date,12 * p_factor) - p_start_date) ;
559       ELSIF p_component = 'MONTH' THEN
560          return (add_months(p_start_date,1 * p_factor ) - p_start_date) ;
561       ELSIF p_component = 'WEEK'  THEN
562          return ( (p_start_date + (7* p_factor)) - p_start_date);
563      ELSIF p_component = 'DAY'   THEN
564          return p_factor;
565      END If;
566 END Component_to_Days;
567 
568 
569 FUNCTION Component_factor  ( p_charge_component   in VARCHAR2
570                            , p_bill_component     in VARCHAR2
571                            , p_start_date         in DATE
572                           )
573 RETURN NUMBER IS
574       l_no_of_days NUMBER ;
575 BEGIN
576      l_no_of_days := add_months(p_start_date,1) - p_start_date;
577 
578      IF p_charge_component = 'YEAR' THEN
579          IF p_bill_component = 'MONTH' THEN
580             return 1/12;
581          ELSIF p_bill_component = 'WEEK' THEN
582             return 1/(add_months(p_start_date,12) - p_start_date)/7 ;
583          ELSIF p_bill_component = 'DAY'  THEN
584             return 1/(add_months(p_start_date,12) - p_start_date) ;
585          END IF;
586       ELSIF p_charge_component = 'MONTH' THEN
587          IF p_bill_component = 'YEAR' THEN
588             return 12;
589          ELSIF p_bill_component = 'WEEK' THEN
590             return 1/(l_no_of_days/7) ;
591          ELSIF p_bill_component = 'DAY'  THEN
592             return 1/l_no_of_days;
593          END IF;
597          ELSIF p_bill_component = 'MONTH' THEN
594       ELSIF p_charge_component = 'WEEK'  THEN
595          IF p_bill_component = 'YEAR' THEN
596             return (add_months(p_start_date,12) - p_start_date)/7;
598             return  (l_no_of_days/7);
599          ELSIF p_bill_component = 'DAY'  THEN
600             return  1/7;
601          END IF;
602      ELSIF p_charge_component = 'DAY'   THEN
603          IF p_bill_component = 'YEAR' THEN
604             return (add_months(p_start_date,12)-p_start_date);
605          ELSIF p_bill_component = 'MONTH' THEN
606             return l_no_of_days;
607          ELSIF p_bill_component = 'WEEK' THEN
608             return 7;
609          END IF;
610      END If;
611 END Component_Factor;
612 
613 FUNCTION Billing_Charge_Ratio  ( p_invoice_rule       in varchar2
614                                , p_factor             in number
615                                , p_from_date         in DATE
616                                , p_to_date           in DATE
617                                , p_charge_period     in varchar2
618                                , p_charge_factor     in number
619                                , p_charge_component  in varchar2
620                                , p_bill_period    in varchar2
621                                , p_bill_factor    in number
622                                , p_bill_component in varchar2
623                                )
624 RETURN NUMBER IS
625 
626 
627    l_no_of_days NUMBER ; /** Number of days in one billing period **/
628    l_factor NUMBER ; /* this factor is for 1 full charge period */
629    l_ratio  NUMBER ;
630 
631    l_component_factor NUMBER;
632 
633 BEGIN
634 
635     l_no_of_days := p_to_date - p_from_date;
636     l_factor := 0;
637     l_ratio  := 0;
638 
639     IF p_charge_factor = 0 OR p_bill_factor = 0 THEN
640        return 0;
641     END IF;
642 
643     IF (p_to_date - p_from_date) = 0 THEN
644        return 0;
645     END IF;
646     l_factor := 1;
647 
648 
649     if p_bill_component = p_charge_component then
650                   if p_bill_factor <> 0 then
651                      l_factor := ( p_bill_factor/ p_charge_factor ) ;
652                   end if;
653     else
654 
655 
656            l_component_factor :=  Component_factor  ( p_charge_component
657                                                     , p_bill_component
658                                                     , p_from_date  );
659 
660            l_factor   :=      l_component_factor * ( p_bill_factor/p_charge_factor );
661 
662    end if;
663 
664   /*
665   -- The factor is calculated for an ideal period
666   -- use the number of days to ensure that this factor
667   -- takes into consideration discrepancies between start date and next due dates
668   */
669 
670         if    p_bill_component = 'DAY' then
671               l_no_of_days := p_bill_factor;
672         elsif p_bill_component = 'MONTH' then
673             l_no_of_days := add_months(p_from_date, 1 * p_bill_factor) - p_from_date;
674         elsif p_bill_component = 'WEEK' then
675             l_no_of_days := 7 * p_bill_factor;
676         elsif p_bill_component = 'YEAR' then
677             l_no_of_days := add_months(p_from_date, 12 * p_bill_factor) - p_from_date;
678         end if;
679 
680 
681     WriteToLogFile ( l_state_level,'igi.plsql.igirrpi.billing_charge_ratio',' Factor due start date    : '|| p_factor );
682     WriteToLogFile ( l_state_level,'igi.plsql.igirrpi.billing_charge_ratio',' factor due to components : '|| l_factor );
683     WriteToLogFile ( l_state_level,'igi.plsql.igirrpi.billing_charge_ratio',' Number of Days           : '|| l_no_of_days );
684 
685 --bug3564100 sdixit: round (p_to_date - p_from_date) difference to smoothen out
686 --the small error due to end date time component being 23:59:59 and not 24:00:00
687     l_ratio :=  p_factor * l_factor *  round(p_to_date - p_from_date) / l_no_of_days;
688     return ( l_ratio ) ;
689 
690 EXCEPTION WHEN OTHERS THEN return -1;
691 END Billing_Charge_Ratio;
692 --
693 PROCEDURE ITEM_Interface_distributions (    pp_sc c_stand_charges%ROWTYPE
694                                           , pp_ld c_line_details%ROWTYPE
695                                           , pp_generate_sequence in number
696                                           , pp_amount in number
697                                           , pp_line_number in number
698                                           , pp_raid_Table  in out NOCOPY RAID_TABLE
699                                           , pp_curr_rec_idx in out NOCOPY BINARY_INTEGER
700                                           , pp_curr_rev_idx in out NOCOPY BINARY_INTEGER
701                                        ) IS
702    l_raid_Table_old    RAID_TABLE      ;
703    l_curr_rec_idx_old  BINARY_INTEGER  ;
704    l_curr_rev_idx_old  BINARY_INTEGER  ;
705 
706 BEGIN
707 
708    l_raid_Table_old    := pp_raid_Table;
709    l_curr_rec_idx_old  := pp_curr_rec_idx;
710    l_curr_rev_idx_old  := pp_curr_rev_idx;
711 
712 /*
713 -- Build Receivable Account entry
714 */
715      IF pp_ld.RECEIVABLE_CODE_COMBINATION_ID IS NOT NULL THEN
716            pp_raid_table ( pp_curr_rec_idx ).account_class             := RECEIVABLE_CODE;
717            pp_raid_table ( pp_curr_rec_idx ).interface_line_context    := TRANSACTION_CODE;
721            pp_raid_table ( pp_curr_rec_idx ).interface_line_attribute4 := pp_line_number;
718            pp_raid_table ( pp_curr_rec_idx ).interface_line_attribute1 := pp_sc.standing_charge_id;
719            pp_raid_table ( pp_curr_rec_idx ).interface_line_attribute2 := pp_generate_sequence;
720            pp_raid_table ( pp_curr_rec_idx ).interface_line_attribute3 := pp_ld.charge_item_number;
722            pp_raid_table ( pp_curr_rec_idx ).amount                    := pp_amount;
723            pp_raid_table ( pp_curr_rec_idx ).percent                   := 0;
724            pp_raid_table ( pp_curr_rec_idx ).code_combination_id       := pp_ld.RECEIVABLE_CODE_COMBINATION_ID;
725            pp_raid_table ( pp_curr_rec_idx ).created_by                := pp_sc.created_by;
726            pp_raid_table ( pp_curr_rec_idx ).creation_date             := sysdate;
727            pp_raid_table ( pp_curr_rec_idx ).last_updated_by           := pp_sc.last_updated_by;
728            pp_raid_table ( pp_curr_rec_idx ).last_update_date          := sysdate;
729 	   /*5905216*/
730 	   pp_raid_table ( pp_curr_rec_idx ).org_id		       := pp_sc.org_id;
731           -- pp_curr_rec_idx := pp_curr_rec_idx -1;
732           -- pp_curr_rec_idx := pp_curr_rec_idx +1;
733      END IF;
734 /*
735 -- Generate the revenue account entries
736 */
737     IF pp_ld.REVENUE_CODE_COMBINATION_ID IS NOT NULL THEN
738            pp_raid_table ( pp_curr_rev_idx ).account_class             := REVENUE_CODE;
739            pp_raid_table ( pp_curr_rev_idx ).interface_line_context    := TRANSACTION_CODE;
740            pp_raid_table ( pp_curr_rev_idx ).interface_line_attribute1 := pp_sc.standing_charge_id;
741            pp_raid_table ( pp_curr_rev_idx ).interface_line_attribute2 := pp_generate_sequence;
742            pp_raid_table ( pp_curr_rev_idx ).interface_line_attribute3 := pp_ld.charge_item_number;
743            pp_raid_table ( pp_curr_rev_idx ).interface_line_attribute4 := pp_line_number;
744            pp_raid_table ( pp_curr_rev_idx ).amount                    := pp_amount;
745            pp_raid_table ( pp_curr_rev_idx ).code_combination_id       := pp_ld.REVENUE_CODE_COMBINATION_ID;
746            pp_raid_table ( pp_curr_rev_idx ).created_by                := pp_sc.created_by;
747            pp_raid_table ( pp_curr_rev_idx ).creation_date             := sysdate;
748            pp_raid_table ( pp_curr_rev_idx ).last_updated_by           := pp_sc.last_updated_by;
749            pp_raid_table ( pp_curr_rev_idx ).last_update_date          := sysdate;
750 	   /*5905216*/
751 	   pp_raid_table ( pp_curr_rev_idx ).org_id		       := pp_sc.org_id;
752            IF nvl(pp_sc.rev_acc_allocation_rule,ALLOCATION_PERCENT_CODE)
753            <> ALLOCATION_PERCENT_CODE
754            AND nvl(pp_ld.accounting_rule_id,-1) = -1    THEN
755                pp_raid_table ( pp_curr_rev_idx ).percent                   := NULL;
756            ELSE
757                pp_raid_table ( pp_curr_rev_idx ).percent                   := 0;
758            END IF;
759            pp_curr_rev_idx := pp_curr_rev_idx +1;
760            --pp_curr_rev_idx := pp_curr_rev_idx -1;
761    END IF;
762 EXCEPTION
763   WHEN OTHERS THEN
764    pp_raid_Table   := l_raid_Table_old;
765    pp_curr_rec_idx := l_curr_rec_idx_old;
766    pp_curr_rev_idx := l_curr_rev_idx_old;
767    app_exception.raise_exception;
768 END ITEM_Interface_Distributions;
769 
770 PROCEDURE   ITEM_Interface_salescredits ( pp_sc c_stand_charges%ROWTYPE
771                                         , pp_rail in RAIL
772                                         )
773 IS
774 
775 
776     CURSOR   c_salescredits (cp_salesrep_id in number) IS
777        SELECT ras.salesrep_id
778             , ras.salesrep_number
779             , ras.sales_credit_type_id
780             , sct.name sales_credit_type_name
781        FROM ra_salesreps ras
782            , so_sales_credit_types sct
783        WHERE ras.salesrep_id = cp_salesrep_id
784        ;
785 
786     FUNCTION SalesCreditRuleAmt ( fp_batch_source_id in number) RETURN BOOLEAN
787     IS
788     CURSOR c_rule IS
789         SELECT 'x'
790         FROM   ra_batch_sources
791         WHERE  batch_source_id = fp_batch_source_id
792         AND    upper(sales_credit_rule) = upper('Amount')
793         ;
794     BEGIN
795         FOR l_rule in c_rule LOOP
796             return TRUE;
797         END LOOP;
798 
799         return FALSE;
800     EXCEPTION WHEN OTHERS THEN
801                  return FALSE;
802     END SalesCreditRuleAmt ;
803 
804     FUNCTION UseSalesCreditTypeValue ( fp_batch_source_id in number) RETURN BOOLEAN
805     IS
806        CURSOR c_typeid IS
807         SELECT 'x'
808         FROM   ra_batch_sources
809         WHERE  batch_source_id = fp_batch_source_id
810         AND    upper(sales_credit_type_rule) = upper('Value')
811         ;
812     BEGIN
813         FOR l_type in c_typeid LOOP
814             return TRUE;
815         END LOOP;
816 
817         return FALSE;
818     EXCEPTION WHEN OTHERS THEN
819                  return FALSE;
820     END UseSalesCreditTypeValue ;
821 
822     FUNCTION UseSalesRepNumber ( fp_batch_source_id in number) RETURN BOOLEAN
823     IS
824        CURSOR c_repid IS
825         SELECT 'x'
826         FROM   ra_batch_sources
827         WHERE  batch_source_id = fp_batch_source_id
828         AND    upper(salesperson_rule) = upper('Number')
829         ;
830     BEGIN
831         FOR l_rep in c_repid LOOP
832             return TRUE;
836     EXCEPTION WHEN OTHERS THEN
833         END LOOP;
834 
835         return FALSE;
837                  return FALSE;
838     END UseSalesRepNumber ;
839 
840 
841     FUNCTION AlreadyExists  RETURN BOOLEAN IS
842       CURSOR c_sales IS
843         SELECT   'x'
844         FROM     ra_interface_salescredits
845         WHERE
846             pp_rail.interface_line_context      = interface_line_context
847         AND pp_rail.interface_line_attribute1   = interface_line_attribute1
848         AND pp_rail.interface_line_attribute2   = interface_line_attribute2
849         AND pp_rail.interface_line_attribute3   = interface_line_attribute3
850         AND pp_rail.interface_line_attribute4   = interface_line_attribute4
851         ;
852     BEGIN
853         FOR l_sales IN c_sales LOOP
854             return TRUE;
855         END LOOP;
856         return FALSE;
857     EXCEPTION WHEN OTHERS THEN
858                  return FALSE;
859     END AlreadyExists;
860 
861 BEGIN
862 
863     IF  NOT UseSalesCredits ( pp_sc.batch_source_id ) THEN
864              return;
865     END IF;
866 
867  FOR l_sc in c_salescredits ( pp_sc.salesrep_id ) LOOP
868 
869     IF NOT AlreadyExists THEN
870 
871          INSERT INTO ra_interface_salescredits
872                   (  interface_line_context
873                   ,  interface_line_attribute1
874                   ,  interface_line_attribute2
875                   ,  interface_line_attribute3
876                   ,  interface_line_attribute4
877                   ,  sales_credit_amount_split
878                   ,  sales_credit_percent_split
879                   ,  sales_credit_type_name
880                   ,   sales_credit_type_id
881                   ,   salesrep_id
882                   ,  salesrep_number
883                   ,  created_by
884                   ,  creation_date
885                   ,  last_updated_by
886                   ,  last_update_date
887 		/*5905216*/
888 		  ,  org_id
889                                       )
890          VALUES (   pp_rail.interface_line_context
891                  ,  pp_rail.interface_line_attribute1
892                  ,  pp_rail.interface_line_attribute2
893                  ,  pp_rail.interface_line_attribute3
894                  ,  pp_rail.interface_line_attribute4
895                  ,  pp_rail.amount
896                  ,  100
897                  ,  l_sc.sales_credit_type_name
898                  ,  l_sc.sales_credit_type_id
899                  ,  l_sc.salesrep_id
900                  ,  l_sc.salesrep_number
901                  ,  pp_rail.created_by
902                  ,  pp_rail.creation_date
903                  ,  pp_rail.last_updated_by
904                  ,  pp_rail.last_update_date
905 		 ,  pp_rail.org_id
906                );
907      END IF;
908 
909      END LOOP;
910 EXCEPTION
911 WHEN OTHERS THEN
912 return;
913 
914 END         ITEM_Interface_salescredits  ;
915 -- ----------------------------------------------------------------------------------
916 PROCEDURE ITEM_Interface_taxes     (  pp_rail in   RAIL
917        , pp_line_number in out NOCOPY number, pp_adhoc_tax in boolean ) IS
918 
919      l_rail RAIL;
920      l_line_number NUMBER ;
921      l_line_number_old NUMBER ;
922 BEGIN
923      l_rail := pp_rail;
924      l_line_number := pp_line_number + 1;
925      l_line_number_old := pp_line_number;
926      l_rail.line_type := 'TAX';
927 
928      IF l_rail.tax_code is null or (not pp_adhoc_tax) or
929         l_rail.amount is null
930      THEN
931         return;
932      END IF;
933 
934      INSERT INTO ra_interface_lines( batch_source_name     -- Mandatory
935                                       , currency_code         -- Mandatory
936                                       , line_type             -- Mandatory
937                                       , set_of_books_id       -- Mandatory
938                                       , description           -- Mandatory
939                                       , conversion_type       -- MandatorY
940                                       , tax_code
941                                       , tax_rate
942                                       , link_to_line_context
943                                       , conversion_rate
944                                       , cust_trx_type_id
945                                       , interface_line_attribute1
946                                       , interface_line_attribute2
947                                       , interface_line_attribute3
948                                       , interface_line_attribute4
949                                       , link_to_line_attribute1
950                                       , link_to_line_attribute2
951                                       , link_to_line_attribute3
952                                       , link_to_line_attribute4
953                                       , interface_line_context
954                                       , created_by
955                                       , creation_date
956                                       , last_updated_by
957                                       , last_update_date
958 					/*5905216*/
959 				      , org_id
960 				      , legal_entity_id	)
961               VALUES
962                                (   l_rail.batch_source_name     -- Mandatory
963                                  , l_rail.currency_code         -- Mandatory
967                                  , l_rail.conversion_type       -- MandatorY
964                                  , l_rail.line_type             -- Mandatory
965                                  , l_rail.set_of_books_id       -- Mandatory
966                                  , l_rail.description           -- Mandatory
968                                  , l_rail.tax_code
969                                  , l_rail.tax_rate
970                                  , l_rail.link_to_line_context
971                                  , l_rail.conversion_rate
972                                  , l_rail.cust_trx_type_id
973                                  , l_rail.interface_line_attribute1
974                                  , l_rail.interface_line_attribute2
975                                  , l_rail.interface_line_attribute3
976                                  , l_line_number
977                                  , l_rail.interface_line_attribute1
978                                  , l_rail.interface_line_attribute2
979                                  , l_rail.interface_line_attribute3
980                                  , pp_line_number
981                                  , l_rail.interface_line_context
982                                  , l_rail.created_by
983                                  , l_rail.creation_date
984                                  , l_rail.last_updated_by
985                                  , l_rail.last_update_date
986 				 , l_rail.org_id
987 				 , l_rail.legal_entity_id
988                                 );
989                if sql%found then
990                  pp_line_number := l_line_number + 1;
991                end if;
992 EXCEPTION
993   WHEN OTHERS THEN
994     pp_line_number := l_line_number_old;
995     app_exception.raise_exception;
996 END ITEM_Interface_taxes;
997 -- -------------------------------------------------------------------------------
998 PROCEDURE ITEM_Interface_lines     (  pp_rail in   RAIL
999                                     , pp_price in number
1000                                     , pp_quantity in  number
1001                                     , pp_line_number in out NOCOPY number
1002                                     , pp_comment in varchar2
1003                                     , pp_sc c_stand_charges%ROWTYPE
1004                                     , pp_ld c_line_details%ROWTYPE
1005                                     , pp_from_date in date
1006                                     , pp_to_date   in date
1007                                    ) IS
1008   l_org_id    NUMBER;
1009   l_rail      RAIL ;
1010   l_date_info VARCHAR2(40);
1011   l_date_info_len NUMBER;
1012   l_line_number_old NUMBER ;
1013   v_precision NUMBER(1);
1014   v_min_acc_unit NUMBER;
1015 BEGIN
1016   l_rail      := pp_rail;
1017   l_date_info := rtrim(pp_from_date||' - '||pp_to_date) ;
1018   l_date_info_len := 240 - (length ( l_date_info ) + length(' : '));
1019   l_line_number_old := pp_line_number;
1020 /*Commeneted for Bug 5905216 - Used MO_GLOBAL instead of reading from profile*/
1021 --  FND_PROFILE.GET( 'ORG_ID', l_org_id );
1022   l_org_id := mo_global.get_current_org_id();
1023   l_rail.org_id             := l_org_id;
1024   l_rail.unit_selling_price := round(pp_price,2);
1025   l_rail.quantity           := pp_quantity;
1026 /* Code added for Amount validation against Precision by Shantanu for bug 6847437*/
1027 /*Code Start*/
1028   SELECT C.PRECISION, C.MINIMUM_ACCOUNTABLE_UNIT
1029 	INTO v_precision, v_min_acc_unit
1030 	FROM FND_CURRENCIES C
1031 	WHERE C.CURRENCY_CODE = l_rail.currency_code;
1032 
1033   If v_min_acc_unit IS NULL then
1034       l_rail.amount := ROUND((l_rail.unit_selling_price * pp_quantity),v_precision);
1035   else
1036       l_rail.amount := ROUND((l_rail.unit_selling_price * pp_quantity)/v_min_acc_unit) * v_min_acc_unit;
1037   end if;
1038 /*Code End*/
1039 
1040 /*Code commented by Shantanu for bug 6847437*/
1041   --l_rail.amount             := l_rail.unit_selling_price * pp_quantity;
1042   l_rail.line_number        := pp_line_number;
1043 /* Removed the comments concatenated to the description  by Panaraya for bug 2413756*/
1044   l_rail.comments           := substr( rtrim(pp_sc.desc_1)
1045                             ,1,l_date_info_len);
1046   l_rail.comments           := l_rail.comments || ' : ' || l_date_info;
1047   -- Trim the spaces of the description!
1048   l_rail.description         := rtrim(pp_comment);
1049   l_rail.interface_line_attribute4 := pp_line_number ;
1050   l_rail.uom_name            := pp_ld.unit_of_measure;
1051 
1052   WriteToLogFile (l_state_level, 'igi.plsql.igirrpi.item_interface_lines.Msg1',
1053                                     'Item Amount to be invoiced '|| l_rail.amount );
1054   /** Insert normal LINE for this ITEM **/
1055 
1056   INSERT INTO ra_interface_lines_all ( accounting_rule_id
1057                                     , amount
1058                                     , batch_source_name       -- Mandatory
1059                                     , comments
1060                                     , description             -- Mandatory
1061                                     , currency_code           -- Mandatory
1062                                     , conversion_rate
1063                                     , conversion_type         -- Mandatory
1064                                     , customer_bank_account_id
1065 				    , PAYMENT_TRXN_EXTENSION_ID	/*Bug No 5905216 Payment Upgrade - for R12*/
1066                                     , cust_trx_type_id
1067                                     , interface_line_attribute1
1068                                     , interface_line_attribute2
1072                                     , tax_code
1069                                     , interface_line_attribute3
1070                                     , interface_line_attribute4
1071                                     , interface_line_context
1073                                     , tax_rate
1074                                     , link_to_line_context
1075                                     , invoicing_rule_id
1076                                     , line_number
1077                                     , line_type               -- Mandatory
1078                                     , orig_system_bill_customer_id
1079                                     , orig_system_bill_address_id
1080                                     , orig_system_bill_contact_id
1081                                     , orig_system_ship_customer_id
1082                                     , orig_system_ship_address_id
1083                                     , orig_system_ship_contact_id
1084                                     , primary_salesrep_id
1085                                     , printing_option
1086                                     , quantity
1087                                     , receipt_method_id
1088                                     , set_of_books_id         -- Mandatory
1089                                     , trx_date
1090                                     , uom_name
1091                                     , uom_code
1092                                     , unit_selling_price
1093                                     , created_by
1094                                     , creation_date
1095                                     , last_updated_by
1096                                     , last_update_date
1097                                     , accounting_rule_duration
1098                                     , rule_start_date
1099                                     , gl_date
1100                                     , term_id
1101 					/*5905216*/
1102 				    , org_id
1103 				    , legal_entity_id
1104                             , TAX_RATE_CODE           /*Bug No 7606235*/
1105                             , TAXABLE_AMOUNT 	      /*Bug No 7606235*/ )
1106                      VALUES
1107                                ( l_rail.accounting_rule_id
1108                                     , l_rail.amount
1109                                     , l_rail.batch_source_name       -- Mandatory
1110                                     , l_rail.comments
1111                                     , l_rail.description             -- Mandatory
1112                                     , l_rail.currency_code           -- Mandatory
1113                                     , l_rail.conversion_rate
1114                                     , l_rail.conversion_type         -- Mandatory
1115                                     , l_rail.customer_bank_account_id
1116 				    , l_rail.payment_trxn_extension_id		/*Bug No 5905216 Payment Upgrade for R12*/
1117                                     , l_rail.cust_trx_type_id
1118                                     , l_rail.interface_line_attribute1
1119                                     , l_rail.interface_line_attribute2
1120                                     , l_rail.interface_line_attribute3
1121                                     , l_rail.interface_line_attribute4
1122                                     , l_rail.interface_line_context
1123                                     , l_rail.tax_code
1124                                     , l_rail.tax_rate
1125                                     , l_rail.link_to_line_context
1126                                     , l_rail.invoicing_rule_id
1127                                     , l_rail.line_number
1128                                     , l_rail.line_type               -- Mandatory
1129                                     , l_rail.orig_system_bill_customer_id
1130                                     , l_rail.orig_system_bill_address_id
1131                                     , l_rail.orig_system_bill_contact_id
1132                                     , l_rail.orig_system_ship_customer_id
1133                                     , l_rail.orig_system_ship_address_id
1134                                     , l_rail.orig_system_ship_contact_id
1135                                     , l_rail.primary_salesrep_id
1136                                     , l_rail.printing_option
1137                                     , l_rail.quantity
1138                                     , l_rail.receipt_method_id
1139                                     , l_rail.set_of_books_id         -- Mandatory
1140                                     , l_rail.trx_date
1141                                     , l_rail.uom_name
1142                                     , l_rail.uom_code
1143                                     , l_rail.unit_selling_price
1144                                     , l_rail.created_by
1145                                     , l_rail.creation_date
1146                                     , l_rail.last_updated_by
1147                                     , l_rail.last_update_date
1148                                     , l_rail.accounting_rule_duration
1149                                     , l_rail.rule_start_date
1150                                     , l_rail.gl_date
1151                                     , l_rail.term_id
1152 				    , l_rail.org_id
1153 				    , l_rail.legal_entity_id
1154  				    , l_rail.tax_code             /*Bug No 7606235*/
1155  				    , l_rail.amount	          /*Bug No 7606235*/ );
1156          -- CREATE THE ASSOCIATED DISTRIBUTION LINES FOR EACH ITEM
1157 /*
1158 -- Note here that the global variables are passed to this routine so that a
1159 -- table is built with the 'REV' and 'REC' entries
1160 -- g_raid_table is the TABLE
1161 -- g_curr_rec_idx is the idx to show the last empty slot available for the next
1165 --  ------------------------------------------------------------------------------
1162 -- 'REC' entry. This is -ve in value.
1163 -- g_curr_rev_idx is the idx to show the last empty slot available for the next
1164 -- 'REV' entry. This is +ve in value
1166 --    -M                                        0                                  N
1167 --     <-      g_curr_rec_idx                   |         g_curr_rev_idx          ->
1168 --             ( 'REC' entries )                |         ( 'REV' entries)
1169 */
1170             ITEM_Interface_taxes         ( pp_rail , pp_line_number, pp_ld.validate_flag = 'Y');
1171 
1172             ITEM_Interface_distributions (    pp_sc
1173                                           ,   pp_ld
1174                                           ,   pp_rail.interface_line_attribute2
1175                                           ,   l_rail.amount
1176                                           ,   l_rail.interface_line_attribute4
1177                                           ,   G_raid_Table
1178                                           ,   g_curr_rec_idx
1179                                           ,   g_curr_rev_idx
1180                                        ) ;
1181 
1182            ITEM_Interface_salescredits ( pp_sc
1183                                         , l_rail
1184                                         );
1185 EXCEPTION WHEN OTHERS THEN
1186   pp_line_number := l_line_number_old;
1187   RAISE_APPLICATION_ERROR( - 20601, SQLERRM );
1188 END ITEM_Interface_lines;
1189 -- -------------------------------------------------------------------------
1190 -- -------------------------------------------------------------------------
1191 PROCEDURE PROCESS_PRICE_BREAKS ( pp_sc c_stand_charges%ROWTYPE
1192                                , pp_ld c_line_details%ROWTYPE
1193                                , pp_rail in out NOCOPY RAIL
1194                                , pp_ratio in NUMBER
1195                                , pp_from_date IN DATE
1196                                , pp_to_date   IN DATE
1197                                , pp_line_number in out NOCOPY number
1198                                ) IS
1199           l_break_ratio              number;
1200           l_break_start_date         date   ;
1201           l_break_end_date           date   ;
1202           l_break_number             integer ;
1203           l_break_info               varchar2(500) ;
1204           l_break_price              igi_rpi_line_details.price%TYPE;
1205           l_rail_old                 rail   ;
1206           l_line_number_old          number ;
1207 BEGIN
1208           l_break_ratio              := pp_ratio;
1209           l_break_start_date         := pp_from_date;
1210           l_break_end_date           := pp_to_date;
1211           l_break_number             := 0;
1212           l_break_info               := null;
1213           l_rail_old                 := pp_rail;
1214           l_line_number_old          := pp_line_number;
1215 
1216           WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg1',
1217                                              'BEGIN Price Break Processing');
1218           WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg2',
1219                                              'Start Date '||l_Break_start_date||' End Date '||l_break_end_date);
1220 
1221          IF  pp_from_date = pp_to_date or pp_ratio = 0
1222              OR pp_from_date is null or pp_to_date is null THEN
1223              WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg3',
1224                                              'END Price Break Processing : Incorrect Parameters.');
1225              return;
1226          END IF;
1227 
1228          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg4',
1229                                        'Previous Effective date '|| pp_ld.previous_effective_date );
1230          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg5',
1231                                        'Previous Price          '|| pp_ld.previous_price );
1232          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg6',
1233                                        'Current Effective date  '|| pp_ld.current_effective_Date );
1234          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg7',
1235                                        'Current Price           '|| pp_ld.price );
1236          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg8',
1237                                        'Revised Effective date  '|| pp_ld.revised_effective_date );
1238          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg9',
1239                                        'Revised Price           '|| pp_ld.revised_price );
1240 
1241          --aa
1242          IF    pp_from_date  <=  nvl(pp_ld.current_effective_date, pp_from_date+1) THEN /**main **/
1243             WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg10',
1244                                           'From Date is Equal to or prior to the Current Eff Date');
1245             WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg11',
1246                                           'pp_to_date  '||pp_to_date||'    '||'effdat'||pp_ld.current_effective_date);
1247             --bb
1248             IF pp_to_date    >=   pp_ld.current_effective_date THEN
1249                pp_line_number        := pp_line_number +1;
1250                l_break_start_date   := pp_from_date;
1251                l_break_end_date     := pp_ld.current_effective_date - 1;
1252 
1253                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg12',
1254                                   'l_break_end_date'||l_break_end_date);
1258 
1255 
1256                l_break_start_date   :=
1257                 to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1259                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg13',
1260                                   'l_break_start_date'||l_break_start_date);
1261 
1262                l_break_end_date   :=
1263                to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1264 
1265 
1266                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg14',
1267                                   'l_break_end_date'||l_break_end_date);
1268 
1269                l_break_number       := l_break_number + 1;
1270                l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1271                                               / ( pp_to_date - pp_from_date) );
1272                l_break_price        := pp_ld.previous_price;
1273                l_break_info         := pp_ld.desc_2||
1274                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1275                                  TO_DATE_INFO||to_char(l_break_end_date);
1276 
1277                IF l_break_price * l_break_ratio <> 0 then
1278            	 WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg16',
1279                                           'in Break #1  before interface');
1280 
1281              	ITEM_Interface_lines     (  pp_rail
1282                                     , l_break_price * l_break_ratio
1283                                     , pp_ld.quantity
1284                                     , pp_line_number
1285                                     , substr(l_break_info,1,240)
1286                                     , pp_sc
1287                                     , pp_ld
1288                                     , pp_from_date
1289                                     , pp_to_date
1290                                    ) ;
1291          	END IF;
1292          	WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg17',
1293                                   'in cc');
1294          	WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg18',
1295                                   'pp_to_date='||pp_to_date||'   '||'effdat'||pp_ld.revised_effective_date);
1296 
1297                 IF pp_to_date >=  pp_ld.revised_effective_date THEN
1298                    pp_line_number        := pp_line_number +1;
1299                    l_break_start_date   := pp_ld.current_effective_date;
1300                    IF pp_to_date > pp_ld.revised_effective_Date THEN
1301                        l_break_end_date     := pp_ld.revised_effective_date -1 ;
1302                    ELSE
1303                        l_break_end_date     := pp_to_Date;
1304                    END IF;
1305                l_break_start_date   :=
1306            	 to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1307        	       l_break_end_date   :=
1308                  to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1309                l_break_number       := l_break_number + 1;
1310                l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1311                                               / ( pp_to_date - pp_from_date) );
1312                l_break_price        := pp_ld.price;
1313                l_break_info         :=  pp_ld.desc_2||
1314                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1315                                  TO_DATE_INFO||to_char(l_break_end_date);
1316                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg19',
1317                                               'Break #2 '||l_break_info );
1318                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg20',
1319                                               'diff='||to_char(l_break_end_date-l_break_start_date));
1320 
1321 
1322                ITEM_Interface_lines     (  pp_rail
1323                                     , l_break_price * l_break_ratio
1324                                     , pp_ld.quantity
1325                                     , pp_line_number
1326                                     , substr(l_break_info,1,240)
1327                                     , pp_sc
1328                                     , pp_ld
1329                                     , pp_from_date
1330                                     , pp_to_date
1331                                    ) ;
1332                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg21',
1333                                   'pp_to_date='||to_char(pp_to_date,'dd-mm-yyyy hh24:mi:ss'));
1334  		   WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg22',
1335                                   'l_break_end_date='||to_char(l_break_end_date,'dd-mm-yyyy hh24:mi:ss'));
1336    		 WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg23',
1337                                   'pp_ld.revised_effective_date='||to_char(pp_ld.revised_effective_date,'dd-mm-yyyy hh24:mi:ss'));
1338 
1339                IF pp_to_date > l_break_end_date
1340                   and pp_from_date <> pp_ld.revised_effective_date THEN --4525139
1341                   pp_line_number        := pp_line_number +1;
1342             	l_break_start_date   := pp_ld.revised_effective_date;
1343             	l_break_end_date     := pp_to_date ;
1344             	l_break_start_date   :=
1345 	            to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1346         	    l_break_end_date   :=
1347 	            to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1351             l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1348 	            l_break_number       := l_break_number + 1;
1349 	    WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg24',
1350                                   'diff='||to_char(l_break_end_date-l_break_start_date));
1352                                               / ( pp_to_date - pp_from_date) );
1353             l_break_price        := pp_ld.revised_price;
1354             l_break_info         :=  pp_ld.desc_2||
1355                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1356                                  TO_DATE_INFO||to_char(l_break_end_date);
1357             WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg25',
1358                                                      'Break #3 '|| l_break_info );
1359                    if l_break_price * l_break_ratio <> 0 then
1360 
1361 
1362                              ITEM_Interface_lines     (  pp_rail
1363                                     , l_break_price * l_break_ratio
1364                                     , pp_ld.quantity
1365                                     , pp_line_number
1366                                     , substr(l_break_info,1,240)
1367                                     , pp_sc
1368                                     , pp_ld
1369                                     , pp_from_date
1370                                     , pp_to_date
1371                                    ) ;
1372                   end if;
1373            END IF;
1374          ELSE
1375             pp_line_number        := pp_line_number +1;
1376             l_break_start_date   := pp_ld.current_effective_date;
1377             l_break_end_date     := pp_to_date ;
1378             l_break_start_date   :=
1379             to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1380             l_break_end_date   :=
1381             to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1382             l_break_number       := l_break_number + 1;
1383             l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1384                                               / ( pp_to_date - pp_from_date) );
1385             l_break_price        := pp_ld.price;
1386             l_break_info         :=  pp_ld.desc_2||
1387                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1388                                  TO_DATE_INFO||to_char(l_break_end_date);
1389                 WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg26',
1390                                               'Break #4 '|| l_break_info );
1391                    if l_break_price * l_break_ratio <> 0 then
1392 
1393 
1394                              ITEM_Interface_lines     (  pp_rail
1395                                     , l_break_price * l_break_ratio
1396                                     , pp_ld.quantity
1397                                     , pp_line_number
1398                                     , substr(l_break_info,1,240)
1399                                     , pp_sc
1400                                     , pp_ld
1401                                     , pp_from_date
1402                                     , pp_to_date
1403                                    ) ;
1404                   end if;
1405          END IF; -- cc
1406      ELSE  -- bb
1407          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg27',
1408                                            ' From date is being processed here.');
1409          pp_line_number        := pp_line_number +1;
1410          l_break_start_date   := pp_from_date;
1411          l_break_end_date     := pp_to_date;
1412          l_break_start_date   :=
1413             to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1414          l_break_end_date   :=
1415             to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1416          l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1417                                               / ( pp_to_date - pp_from_date) );
1418          l_break_info         :=  pp_ld.desc_2||
1419                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1420                                  TO_DATE_INFO||to_char(l_break_end_date);
1421          l_break_price        := pp_ld.previous_price;
1422          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg28',
1423                                                      'Break #6 '|| l_break_info );
1424                    if l_break_price * l_break_ratio <> 0 then
1425 
1426 
1427                              ITEM_Interface_lines     (  pp_rail
1428                                     , l_break_price * l_break_ratio
1429                                     , pp_ld.quantity
1430                                     , pp_line_number
1431                                     , substr(l_break_info,1,240)
1432                                     , pp_sc
1433                                     , pp_ld
1434                                     , pp_from_date
1435                                     , pp_to_date
1436                                    ) ;
1437                   end if;
1438       END IF;  -- bb
1439 
1440    END IF; -- aa
1441 
1442    IF pp_from_date <= nvl(pp_ld.revised_effective_date-1,pp_to_date) -- aa
1443          AND pp_from_date > pp_ld.current_effective_date
1444    THEN
1445      -- dd
1446          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg29',
1450         pp_ld.revised_effective_date is not null
1447                                        'From Date is Equal to or prior to the Rev Eff Date -1');
1448 
1449      IF pp_to_date    >=   pp_ld.revised_effective_date-1 and
1451      THEN
1452          pp_line_number        := pp_line_number +1;
1453          l_break_start_date   := pp_from_date;
1454          l_break_end_date     := pp_ld.revised_effective_date-1;
1455          l_break_start_date   :=
1456             to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1457          l_break_end_date   :=
1458             to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1459          l_break_number       := l_break_number + 1;
1460          l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1461                                               / ( pp_to_date - pp_from_date) );
1462          l_break_price        := pp_ld.price;
1463          l_break_info         :=  pp_ld.desc_2||
1464                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1465                                  TO_DATE_INFO||to_char(l_break_end_date);
1466          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg30',
1467                                                      'Break #7 '||l_break_info );
1468                    if l_break_price * l_break_ratio <> 0 then
1469 
1470                              ITEM_Interface_lines     (  pp_rail
1471                                     , l_break_price * l_break_ratio
1472                                     , pp_ld.quantity
1473                                     , pp_line_number
1474                                     , substr(l_break_info,1,240)
1475                                     , pp_sc
1476                                     , pp_ld
1477                                     , pp_from_date
1478                                     , pp_to_date
1479                                    ) ;
1480                   end if;
1481          -- ee
1482          IF pp_to_date >=  pp_ld.revised_effective_date THEN
1483             pp_line_number        := pp_line_number +1;
1484             l_break_start_date   := pp_ld.revised_effective_date;
1485             l_break_end_date     := pp_to_date ;
1486             l_break_number       := l_break_number + 1;
1487          l_break_start_date   :=
1488             to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1489          l_break_end_date   :=
1490             to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1491             l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1492                                               / ( pp_to_date - pp_from_date) );
1493             l_break_price        := pp_ld.revised_price;
1494             l_break_info         :=  pp_ld.desc_2||
1495                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1496                                  TO_DATE_INFO||to_char(l_break_end_date);
1497                           WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg31',
1498                                                         'Break #8 '||l_break_info );
1499                    if l_break_price * l_break_ratio <> 0 then
1500 
1501 
1502                              ITEM_Interface_lines     (  pp_rail
1503                                     , l_break_price * l_break_ratio
1504                                     , pp_ld.quantity
1505                                     , pp_line_number
1506                                     , substr(l_break_info,1,240)
1507                                     , pp_sc
1508                                     , pp_ld
1509                                     , pp_from_date
1510                                     , pp_to_date
1511                                    ) ;
1512                   end if;
1513          END IF;
1514        ELSE   -- dd
1515             pp_line_number        := pp_line_number +1;
1516             l_break_start_date   := pp_from_date;
1517             l_break_end_date     := pp_to_date ;
1518          l_break_start_date   :=
1519             to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1520          l_break_end_date   :=
1521             to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1522             l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1523                                               / ( pp_to_date - pp_from_date) );
1524                 WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg32',
1525                                               'Ratio for NPBUCP is '||l_Break_ratio);
1526             l_break_price        := pp_ld.price;
1527             l_break_info         :=  pp_ld.desc_2||
1528                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1529                                  TO_DATE_INFO||to_char(l_break_end_date);
1530                           WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg33',
1531                                                         'Break #9 '||l_break_info );
1532                    if l_break_price * l_break_ratio <> 0 then
1533 
1534 
1535                              ITEM_Interface_lines     (  pp_rail
1536                                     , l_break_price * l_break_ratio
1537                                     , pp_ld.quantity
1538                                     , pp_line_number
1539                                     , substr(l_break_info,1,240)
1540                                     , pp_sc
1544                                    ) ;
1541                                     , pp_ld
1542                                     , pp_from_date
1543                                     , pp_to_date
1545                   end if;
1546        END IF; -- dd
1547    END IF; -- aa
1548 
1549    IF pp_from_date  >= pp_ld.revised_effective_date THEN
1550           pp_line_number        := pp_line_number +1;
1551             l_break_start_date   := pp_from_date;
1552             l_break_end_date     := pp_to_date ;
1553          l_break_start_date   :=
1554             to_date(to_char(l_break_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT);
1555          l_break_end_date   :=
1556             to_date(to_char(l_break_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT);
1557 
1558                         l_break_ratio        := pp_ratio * ( ( l_break_end_date - l_break_start_date)
1559                                               / ( pp_to_date - pp_from_date) );
1560 
1561             l_break_price        := pp_ld.revised_price;
1562             l_break_info         :=  pp_ld.desc_2||
1563                                  FROM_DATE_INFO||to_char(l_break_start_date)||
1564                                  TO_DATE_INFO||to_char(l_break_end_date);
1565                   WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg34',
1566                                                 'Break #10'||l_break_info);
1567                   WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg35',
1568                                                 'price in 10='||l_break_price*l_break_ratio);
1569 
1570                    if l_break_price * l_break_ratio <> 0 then
1571 
1572 
1573                              ITEM_Interface_lines     (  pp_rail
1574                                     , l_break_price * l_break_ratio
1575                                     , pp_ld.quantity
1576                                     , pp_line_number
1577                                     , substr(l_break_info,1,240)
1578                                     , pp_sc
1579                                     , pp_ld
1580                                     , pp_from_date
1581                                     , pp_to_date
1582                                    ) ;
1583 
1584                   end if;
1585    END IF; -- aa
1586        WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg36',
1587                                      'END (Successful) Price Break Processing');
1588 
1589 EXCEPTION WHEN OTHERS THEN
1590 
1591     pp_rail        := l_rail_old;
1592     pp_line_number := l_line_number_old;
1593     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_price_breaks.Msg37',
1594                                      'END (Error) Price Break Processing');
1595     RAISE_APPLICATION_ERROR (-20301, SQLERRM );
1596 END PROCESS_PRICE_BREAKS;
1597 --
1598 -- Prorate Revenue at distribution level
1599 --
1600 PROCEDURE PROCESS_REC_DISTRIBUTIONS ( pp_sc c_stand_charges%ROWTYPE
1601                                 , pp_curr_rec_idx       in BINARY_INTEGER
1602                                 , pp_curr_rev_idx       in BINARY_INTEGER
1603                                 , pp_raid_table         in out NOCOPY RAID_TABLE
1604                                  ) IS
1605     idx BINARY_INTEGER;
1606     l_total_rev_amt NUMBER ;
1607     l_total_rec_amt NUMBER ;
1608     l_raid_table_old RAID_TABLE ;
1609 err_msg VARCHAR2(512);
1610 BEGIN
1611     l_total_rev_amt := 0;
1612     l_total_rec_amt := 0;
1613     l_raid_table_old := pp_raid_table;
1614 /*
1615 -- Get the totals for all 'REV' entries
1616 */
1617 
1618 
1619 l_total_rec_amt := 0;
1620                idx := 0;
1621 
1622              while idx < pp_curr_rev_idx  LOOP
1623                 IF pp_raid_table.exists( idx ) THEN
1624                    IF pp_raid_table( idx ).account_class = REVENUE_CODE THEN
1625                       l_total_rec_amt := l_total_rec_amt + pp_raid_table( idx ).
1626 amount;
1627                    END IF;
1628                 END IF;
1629                 idx :=  pp_raid_Table.next ( idx );
1630             END LOOP;
1631 
1632            idx := pp_curr_rec_idx;
1633 
1634 
1635               WHILE idx < 0 LOOP
1636                 IF pp_raid_table.exists( idx ) THEN
1637 
1638                    IF  pp_raid_table( idx).account_class = RECEIVABLE_CODE THEN
1639                            pp_raid_table( idx ).percent :=  100;
1640                            pp_raid_table(idx).amount :=l_total_rec_amt;
1641                    END IF;
1642                 END IF;
1643                 idx :=  pp_raid_Table.next ( idx );
1644 
1645             END LOOP;
1646 
1647              --idx := 0;
1648              idx := g_curr_rec_idx;
1649 
1650                WHILE  idx < 0 LOOP
1651 
1652 
1653                 IF pp_raid_table.exists( idx ) THEN
1654 
1655 
1656                     INSERT INTO ra_interface_distributions(  account_class    -- Mandatory
1657                                       ,  interface_line_context
1658                                       ,  interface_line_attribute1
1659                                       ,  interface_line_attribute2
1660                                       ,  interface_line_attribute3
1661                                       ,  interface_line_attribute4
1662                                       ,  amount
1663                                       ,  percent
1667                                       ,  last_updated_by
1664                                       ,  code_combination_id
1665                                       ,  created_by
1666                                       ,  creation_date
1668                                       ,  last_update_date
1669 					/*5905216*/
1670 				      ,  org_id
1671                                       )
1672                      VALUES
1673                                     (    pp_raid_table ( idx ).account_class    -- Mandatory
1674                                       ,  pp_raid_table ( idx ).interface_line_context
1675                                       ,  pp_raid_table ( idx ).interface_line_attribute1
1676                                       ,  pp_raid_table ( idx ).interface_line_attribute2
1677                                       ,  pp_raid_table ( idx ).interface_line_attribute3
1678                                       ,  pp_raid_table ( idx ).interface_line_attribute4
1679                                       ,  pp_raid_table ( idx ).amount
1680                                       ,  pp_raid_table ( idx ).percent
1681                                       ,  pp_raid_table ( idx ).code_combination_id
1682                                       ,  pp_raid_table ( idx ).created_by
1683                                       ,  pp_raid_table ( idx ).creation_date
1684                                       ,  pp_raid_table ( idx ).last_updated_by
1685                                       ,  pp_raid_table ( idx ).last_update_date
1686 				      ,  pp_raid_table ( idx ).org_id
1687                                       );
1688 
1689                 END IF;
1690                 idx :=  pp_raid_Table.next ( idx );
1691              END LOOP;
1692 
1693                     idx := g_curr_rec_idx;
1694                    WHILE idx < 0 LOOP
1695                 IF pp_raid_table.exists( idx ) THEN
1696                    pp_raid_table.delete( idx );
1697                 END IF;
1698                 idx := pp_raid_Table.next ( idx );
1699              END LOOP;
1700 
1701               idx := 0;
1702              WHILE idx <= pp_curr_rev_idx LOOP
1703                 IF pp_raid_table.exists( idx ) THEN
1704                    pp_raid_table.delete( idx );
1705                 END IF;
1706                 idx := pp_raid_Table.next ( idx );
1707              END LOOP;
1708 EXCEPTION
1709   WHEN OTHERS THEN
1710      pp_raid_table := l_raid_table_old;
1711      app_exception.raise_exception;
1712 END PROCESS_REC_DISTRIBUTIONS;
1713 /*
1714 --
1715 -- Distribute the receivables accounts and ensure that it follows
1716 -- all the rules as explained in the Open Interfaces Manual.
1717 --
1718 */
1719 PROCEDURE PROCESS_REV_DISTRIBUTIONS ( pp_sc c_stand_charges%ROWTYPE
1720                                 , pp_curr_rev_idx       in BINARY_INTEGER
1721                                 , pp_raid_table         in out NOCOPY RAID_TABLE
1722                                  ) IS
1723     idx BINARY_INTEGER;
1724     l_total_rec_amt NUMBER ;
1725     l_total_rev_amt NUMBER ;
1726     l_raid_table_old RAID_TABLE ;
1727 err_msg VARCHAR2(512);
1728 BEGIN
1729     l_total_rec_amt := 0;
1730     l_total_rev_amt := 0;
1731     l_raid_table_old := pp_raid_table;
1732 /*
1733 -- Get the totals for all 'REC' and 'REV' entries
1734 */
1735              l_total_rec_amt := 0;
1736 
1737                idx := 0;
1738 
1739              while idx < pp_curr_rev_idx  LOOP
1740                 IF pp_raid_table.exists( idx ) THEN
1741                    IF pp_raid_table( idx ).account_class = REVENUE_CODE THEN
1742                       l_total_rec_amt := l_total_rec_amt + pp_raid_table( idx ).amount;
1743                    END IF;
1744                 END IF;
1745                 idx :=  pp_raid_Table.next ( idx );
1746             END LOOP;
1747 
1748 
1749 
1750               idx := 0;
1751 
1752                 while idx <= pp_curr_rev_idx LOOP
1753                 IF pp_raid_table.exists( idx ) THEN
1754                    IF pp_raid_table( idx ).account_class = REVENUE_CODE THEN
1755                        pp_raid_table(idx).percent := 100;
1756                    END IF;
1757                 END IF;
1758                 idx :=  pp_raid_Table.next ( idx );
1759             END LOOP;
1760 
1761          idx := 0;
1762 
1763             WHILE rev_idx < g_curr_rev_idx LOOP
1764 
1765 
1766 
1767                 IF pp_raid_table.exists( rev_idx ) THEN
1768 
1769                     INSERT INTO ra_interface_distributions(  account_class    -- Mandatory
1770                                       ,  interface_line_context
1771                                       ,  interface_line_attribute1
1772                                       ,  interface_line_attribute2
1773                                       ,  interface_line_attribute3
1774                                       ,  interface_line_attribute4
1775                                       ,  amount
1776                                       ,  percent
1777                                       ,  code_combination_id
1778                                       ,  created_by
1779                                       ,  creation_date
1780                                       ,  last_updated_by
1781                                       ,  last_update_date
1782 					/*5905216*/
1783 				      ,  org_id
1784                                       )
1785                      VALUES
1789                                       ,  pp_raid_table ( rev_idx ).interface_line_attribute2
1786                                     (    pp_raid_table ( rev_idx ).account_class    -- Mandatory
1787                                       ,  pp_raid_table ( rev_idx ).interface_line_context
1788                                       ,  pp_raid_table ( rev_idx ).interface_line_attribute1
1790                                       ,  pp_raid_table ( rev_idx ).interface_line_attribute3
1791                                       ,  pp_raid_table ( rev_idx ).interface_line_attribute4
1792                                       ,  pp_raid_table ( rev_idx ).amount
1793                                       ,  pp_raid_table ( rev_idx ).percent
1794                                       ,  pp_raid_table ( rev_idx ).code_combination_id
1795                                       ,  pp_raid_table ( rev_idx ).created_by
1796                                       ,  pp_raid_table ( rev_idx ).creation_date
1797                                       ,  pp_raid_table ( rev_idx ).last_updated_by
1798                                       ,  pp_raid_table ( rev_idx ).last_update_date
1799 				      ,  pp_raid_table ( rev_idx ).org_id
1800                                       );
1801 
1802 
1803                 END IF;
1804 
1805         rev_idx := rev_idx+1;
1806              END LOOP;
1807 
1808                   idx := 0;
1809 EXCEPTION
1810   WHEN OTHERS THEN
1811      pp_raid_table := l_raid_table_old;
1812      app_exception.raise_exception;
1813 END PROCESS_REV_DISTRIBUTIONS;
1814 PROCEDURE PROCESS_DATE_RANGES( pp_sc_period_name         in varchar2
1815                              , pp_sc_advance_arrears_ind in varchar2
1816                              , pp_sc_start_date          in date
1817                              , pp_sc_end_date            in date
1818                              , pp_sc_next_due_date       in date
1819                              , pp_sc_prev_due_date       in date
1820                              , pp_date_range_idx         in out NOCOPY binary_integer
1821                              , pp_date_range_table       in out NOCOPY DATE_RANGE_TABLE
1822                              )
1823 IS
1824       l_start_date date;
1825   --     l_date_end date;
1826       l_temp_Date date;
1827       l_final_date date ;
1828       l_prev_date  date ;
1829       l_new_prev_due_date date;
1830       l_new_next_due_date date;
1831       l_schedule_id       number;
1832       l_factor            number;
1833       l_ratio             number;
1834       l_component         varchar2(40);
1835       l_range             number;
1836       l_dummy             number;
1837       l_date_range_idx_old binary_integer      ;
1838       l_date_range_table_old DATE_RANGE_TABLE  ;
1839 
1840   BEGIN
1841 
1842       l_final_date := pp_sc_next_due_date;
1843       l_date_range_idx_old := pp_date_range_idx;
1844       l_date_range_table_old := pp_date_range_table;
1845 
1846       Next_Due_Dates (  pp_curr_next_due_date    => pp_sc_next_due_date
1847                        ,  pp_period_name         => pp_sc_period_name
1848                        ,  pp_advance_arrears_ind => pp_sc_advance_arrears_ind
1849                        ,  pp_new_prev_due_date   => l_prev_date
1850                        ,  pp_new_next_due_date   => l_final_date
1851                        ,  pp_new_schedule_id     => l_schedule_id
1852                        ,  pp_new_factor          => l_factor
1853                        ,  pp_new_component       => l_component
1854                        );
1855 
1856      pp_date_range_idx := 1;
1857          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg1',
1858                                        'New  Next Due date '|| l_final_date );
1859          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg2',
1860                                        'New  Prev Due date '|| l_prev_date);
1861          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg3',
1862                                        'Curr Prev Due date '|| pp_sc_prev_due_date);
1863          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg4',
1864                                        'Curr Next Due date '|| pp_sc_next_due_date);
1865          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg5',
1866                                        'Start date         '|| pp_sc_start_date );
1867          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg6',
1868                                        'End   date         '|| pp_sc_end_date   );
1869 
1870 
1871      if nvl(pp_sc_advance_arrears_ind,'ADVANCE') = 'ADVANCE'
1872      then
1873              WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg7',
1874                                            'End date = '||pp_sc_end_date);
1875          IF pp_sc_end_date < l_final_date THEN
1876            l_final_date := pp_sc_end_date+1;
1877                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg8',
1878                                              'Final date = '||l_final_date);
1879          END IF;
1880 
1881              WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg9',
1882                                            pp_sc_next_due_date||'          '||l_final_date ||' a ' );
1883 
1884          IF (pp_sc_next_due_date < pp_sc_start_date) THEN
1885            pp_date_range_table(pp_date_range_idx).start_date        := pp_sc_start_date;
1886          ELSE
1890          pp_date_range_table(pp_date_range_idx).actual_start_date   := pp_sc_next_due_date;
1887            pp_date_range_table(pp_date_range_idx).start_date        := pp_sc_next_due_date;
1888          END IF;
1889 
1891          pp_date_range_table(pp_date_range_idx).end_date            := l_final_date -1;
1892 
1893      else /* for arrears */
1894 
1895          pp_date_range_table(pp_date_range_idx).start_date          := l_prev_date;
1896          pp_date_range_table(pp_date_range_idx).actual_start_date   := l_prev_date;
1897              WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg10',
1898                                            'Prev due date '|| l_prev_date );
1899              WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg11',
1900                                            'Start date    '|| pp_sc_start_date );
1901 
1902          if (pp_sc_start_date > l_prev_date) -- and (pp_sc_prev_due_date is null)
1903          then
1904            pp_date_range_table(pp_date_range_idx).start_date   := pp_sc_start_date;
1905                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg12',
1906                                              'start date '|| pp_sc_start_date );
1907          end if;
1908 
1909          /* Bug 2436978 ssemwal added if condition for end date validation */
1910          IF pp_sc_end_date < pp_sc_next_due_date THEN
1911 	           pp_date_range_table(pp_date_range_idx).end_date := pp_sc_end_date;
1912                     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_date_ranges.Msg13',
1913                                                   'Final date = '||pp_sc_end_date);
1914           ELSE
1915           	pp_date_range_table(pp_date_range_idx).end_date     := pp_sc_next_due_date - 1;
1916           END IF;
1917      end if;
1918 EXCEPTION
1919   WHEN OTHERS THEN
1920     pp_date_range_idx    := l_date_range_idx_old;
1921     pp_date_range_table  := l_date_range_table_old;
1922     app_exception.raise_exception;
1923 END PROCESS_DATE_RANGES;
1924 
1925 PROCEDURE PROCESS_CHARGES ( pp_sc c_stand_charges%ROWTYPE
1926                           , pp_ld c_line_details%ROWTYPE
1927                           , pp_generate_sequence in number
1928                           , pp_date_range_table IN OUT NOCOPY DATE_RANGE_TABLE
1929                           , pp_date_range_idx   IN OUT NOCOPY BINARY_INTEGER
1930                           ) IS
1931      l_rail   RAIL;  -- Ra interface ITEM lines record
1932      l_from_date date;  -- Start date for billing
1933      l_end_date  date;  -- End   date for billing
1934      l_ratio     number; -- Ratio of charge vs billing period
1935      l_quarter_days number;       --billing schedule info for 1/4 Days.
1936 
1937      l_date_range_idx_old binary_integer     ;
1938      l_date_range_table_old DATE_RANGE_TABLE ;
1939 
1940      FUNCTION IsVariableRule ( fp_rule_id in number)
1941      return BOOLEAN IS
1942        CURSOR c_var is
1943            select 'x'
1944            from   ra_rules
1945            where  rule_id = fp_rule_id
1946            and    type    = 'ACC_DUR'
1947            ;
1948      BEGIN
1949        for l_var in c_var loop
1950           return TRUE;
1951        end loop;
1952        return FALSE;
1953      END IsVariableRule;
1954  BEGIN
1955 
1956      l_quarter_days := 0;
1957      l_date_range_idx_old := pp_date_range_idx;
1958      l_date_range_table_old := pp_date_range_table;
1959         WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg1',
1960                                       'BEGIN  Process Standing Charges');
1961     /** Initialize the interface lines grouping information **/
1962         WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg2',
1963                                       'Charge reference '|| pp_sc.charge_reference );
1964     l_rail.interface_line_attribute1 := pp_sc.standing_charge_id;
1965     l_rail.interface_line_attribute2 := pp_generate_sequence      ;
1966     l_rail.interface_line_attribute3 := pp_ld.charge_item_number  ;
1967     l_rail.interface_line_attribute4 := pp_generate_sequence      ;
1968     l_rail.interface_line_context    := TRANSACTION_CODE;
1969     l_rail.accounting_rule_id        := pp_ld.accounting_rule_id ;
1970     l_rail.batch_source_name         := pp_sc.bs_name;
1971     l_rail.comments                  := null;
1972     l_rail.description               := pp_sc.desc_1;
1973     l_rail.currency_code             := pp_sc.currency_code;
1974     l_rail.conversion_rate           := '1';
1975     l_rail.conversion_type           := USER_CODE;
1976     l_rail.customer_bank_account_id  := pp_sc.bank_account_id;
1977     l_rail.payment_trxn_extension_id := pp_sc.payment_trxn_extension_id;
1978     l_rail.cust_trx_type_id          := pp_sc.cust_trx_type_id;
1979     l_rail.tax_code                  := pp_ld.tax_rate_code;                /* Bug 7606235 */
1980     l_rail.tax_rate                  := pp_ld.percentage_rate;              /* Bug 7606235 */
1981     l_rail.link_to_line_context      := TRANSACTION_CODE;
1982 /*  Line number and tax line number depends on price breaks */
1983 /*  Defaulting values here                                  */
1984     l_rail.line_number               := '1';
1985     l_rail.line_type                 :=  LINE_CODE;
1986     l_rail.orig_system_bill_customer_id :=  pp_sc.bill_to_customer_id;
1987     l_rail.orig_system_bill_address_id  :=  pp_sc.bill_to_address_id;
1988     l_rail.orig_system_bill_contact_id  :=  pp_sc.bill_to_contact_id;
1989     l_rail.orig_system_ship_customer_id :=  pp_sc.ship_to_customer_id;
1993      SELECT decode(pp_sc.suppress_inv_print,'Y','PRI','NOT')
1990     l_rail.orig_system_ship_address_id  :=  pp_sc.ship_to_address_id;
1991     l_rail.orig_system_ship_contact_id  :=  pp_sc.ship_to_contact_id;
1992     l_rail.primary_salesrep_id          :=  pp_sc.salesrep_id;
1994      INTO l_rail.printing_option
1995      FROM sys.dual;
1996     l_rail.quantity                     :=  pp_ld.quantity;
1997     l_rail.set_of_books_id              :=  pp_sc.set_of_books_id;
1998     l_rail.receipt_method_id            :=  pp_sc.receipt_method_id;
1999     l_rail.trx_date                     :=  pp_sc.next_due_date;
2000     l_rail.uom_code                     :=  pp_ld.uom_uom_code;
2001     l_rail.uom_name                     :=  pp_ld.ld_period_name;
2002     l_rail.term_id                      :=  pp_sc.term_id;
2003     l_rail.created_by                   :=  pp_sc.created_by;
2004     l_rail.creation_date                :=  pp_sc.sysdate;
2005     l_rail.last_updated_by              :=  pp_sc.created_by;
2006     l_rail.last_update_date             :=  pp_sc.sysdate;
2007     l_rail.gl_date                      :=  pp_sc.standing_charge_date;
2008 /*5905216*/
2009     l_rail.legal_entity_id		:= pp_sc.legal_entity_id;
2010     IF pp_sc.advance_arrears_ind  IS NULL THEN
2011        l_rail.accounting_rule_id := null;
2012        l_rail.invoicing_rule_id  := null;
2013        l_rail.rule_start_date := null;
2014        l_rail.accounting_rule_duration   := null;
2015     ELSE
2016        IF  l_rail.accounting_rule_id is not null
2017        then
2018            l_rail.invoicing_rule_id := Get_invoicing_rule
2019                                      ( pp_sc.advance_arrears_ind );
2020               WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg3',
2021                                             'Charge reference '|| pp_sc.charge_reference );
2022 /* Added by Panaraya for bug 2439363 - Start */
2023 	 IF (nvl(pp_sc.advance_arrears_ind,'ARREARS')= ARREARS_STATUS ) THEN
2024             l_rail.gl_date := null;
2025 	 END IF;
2026 /* Added by Panaraya for bug 2439363 - End */
2027 --for bug 2706422, praghura . start.
2028         l_rail.accounting_rule_duration := pp_ld.duration;
2029         l_rail.rule_start_date := pp_ld.start_date;
2030 --for bug 2706422, praghura . end.
2031         IF IsVariableRule( l_rail.accounting_rule_id )
2032            then
2033                l_rail.accounting_rule_duration
2034                            := pp_ld.duration;
2035                l_rail.rule_start_date
2036                            := nvl(pp_ld.start_date,pp_sc.standing_charge_date);
2037            else
2038                l_rail.accounting_rule_duration := null;
2039                l_rail.rule_start_date := null;
2040            END IF;
2041        ELSE
2042            l_rail.invoicing_rule_id := NULL;
2043            l_rail.rule_start_date := null;
2044            l_rail.accounting_rule_duration   := null;
2045            l_rail.gl_date := pp_sc.standing_charge_date;
2046        END IF;
2047     END IF;
2048     /** Now start computing the date ranges **/
2049          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg3',
2050                                        '*** Begin of Process date ranges *** ');
2051 
2052     PROCESS_DATE_RANGES( pp_sc_period_name         => pp_sc.sc_period_name
2053                        , pp_sc_advance_arrears_ind => nvl(pp_sc.advance_arrears_ind,pp_sc.default_invoicing_rule)
2054                        , pp_sc_start_date          => pp_sc.start_date
2055                        , pp_sc_end_date            => pp_sc.end_date
2056                        , pp_sc_next_due_date       => pp_sc.next_due_date
2057                        , pp_sc_prev_due_date       => pp_sc.previous_due_date
2058                        , pp_date_range_idx         => pp_date_range_idx
2059                        , pp_date_range_table       => pp_date_range_table
2060                        );
2061 
2062          WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg4',
2063                                        '*** End of Process date ranges *** ');
2064 
2065     declare
2066       l_binary_idx binary_integer ;
2067       io_ratio    number;
2068       l_new_prev_due_date2 date;
2069       l_new_next_due_date2 date;
2070       l_new_prev_due_date  date;
2071       l_new_next_due_date  date;
2072       l_charge_schedule number;
2073       l_charge_factor   number;
2074       l_charge_component varchar2(40);
2075       l_billing_schedule number;
2076       l_billing_factor   number;
2077       l_billing_component varchar2(40);
2078       l_days_ratio       number ;
2079       l_line_number      number ;
2080 
2081       FUNCTION Get_Days_Ratio ( pp_start_date in date,
2082                                 pp_actual_start_date in date,
2083                                 pp_end_date   in date )
2084       RETURN NUMBER IS
2085          l_factor number := 1;
2086       BEGIN
2087            select   (  to_date(to_char(pp_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT)
2088                      - to_date(to_char(pp_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT)
2089                     )
2090                    / (  to_date(to_char(pp_end_date,DEF_DATE_FORMAT)||END_DATE_TIME,RPI_DATE_FORMAT)
2091                      - to_date(to_char(pp_actual_start_date,DEF_DATE_FORMAT)||BEGIN_DATE_TIME,RPI_DATE_FORMAT)
2092                      )
2093            into   l_factor
2094            from    sys.dual
2098 
2095            ;
2096            return l_factor;
2097       END Get_Days_Ratio;
2099     begin
2100 
2101       l_binary_idx := pp_date_range_table.FIRST;
2102       l_days_ratio       := 0;
2103       l_line_number      := 1;
2104                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg5',
2105                                              '*** Binary idx *** '|| l_binary_idx );
2106                WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg6',
2107                                              '*** End idx    *** '|| pp_date_range_idx );
2108 
2109            while l_binary_idx <=  pp_date_range_idx loop
2110 
2111                  WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg7',
2112                                                'LHS 2 '|| pp_date_range_table(l_binary_idx).start_date
2113                                                          || '   RHS 2 '|| pp_date_range_table(l_binary_idx).end_date );
2114 
2115               /* Bug 2403906 vgadde 14/06/2002 modified < to <= to process standing charges with billing frequency DAY */
2116               if pp_date_range_table(l_binary_idx).start_date  <=
2117                 pp_date_range_table(l_binary_idx).end_date  then
2118 
2119                     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg8',
2120                                                   ' Actual Date '|| pp_date_range_table(l_binary_idx).actual_start_date );
2121                     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg9',
2122                                                   ' Start Date  '|| pp_date_range_table(l_binary_idx).start_date );
2123                     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg10',
2124                                                   ' End   date  '|| pp_date_range_table(l_binary_idx).end_date );
2125 
2126                 l_days_ratio := Get_Days_Ratio ( pp_date_range_table(l_binary_idx).start_date,
2127                                                 pp_date_range_table(l_binary_idx).actual_start_date,
2128                                                 pp_date_range_table(l_binary_idx).end_date )
2129                                 ;
2130 
2131                     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg11',
2132                                                   '** Days Ratio *** '|| l_days_ratio );
2133 
2134 
2135                 Next_Due_Dates    ( to_date(to_char(pp_date_range_table(l_binary_idx).start_date,DEF_DATE_FORMAT)
2136                                     ||BEGIN_DATE_TIME,RPI_DATE_FORMAT)
2137                                   ,  pp_ld.ld_period_name
2138                                   ,  nvl(pp_sc.advance_arrears_ind,pp_sc.default_invoicing_rule)
2139                                   ,  l_new_prev_due_date2
2140                                   ,  l_new_next_due_date2
2141                                   ,  l_charge_schedule
2142                                   ,  l_charge_factor
2143                                   ,  l_charge_component
2144                                   ) ;
2145 
2146               /** Get the billing dates etc **/
2147               Next_Due_Dates      ( to_date(to_char(pp_date_range_table(l_binary_idx).start_date,DEF_DATE_FORMAT)
2148                                     ||BEGIN_DATE_TIME,RPI_DATE_FORMAT)
2149                                   ,  pp_sc.sc_period_name
2150                                   ,  nvl(pp_sc.advance_arrears_ind,pp_sc.default_invoicing_rule)
2151                                   ,  l_new_prev_due_date
2152                                   ,  l_new_next_due_date
2153                                   ,  l_billing_schedule
2154                                   ,  l_billing_factor
2155                                   ,  l_billing_component
2156                                   ) ;
2157 
2158                  WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg12',
2159                                                '** Billing Schedule ** '|| l_billing_schedule );
2160 
2161              if l_billing_schedule = 0 then
2162                 l_days_ratio := 1;
2163              end if;
2164 
2165 
2166              io_ratio :=  Billing_Charge_Ratio
2167                   (  nvl(pp_sc.advance_arrears_ind,pp_sc.default_invoicing_rule)
2168                    , l_days_ratio
2169                    , to_date(to_char(pp_date_range_table(l_binary_idx).start_date,DEF_DATE_FORMAT)
2170                      ||BEGIN_DATE_TIME,RPI_DATE_FORMAT)
2171                    , to_date(to_char(pp_date_range_table(l_binary_idx).end_date,DEF_DATE_FORMAT)
2172                      ||END_DATE_TIME,RPI_DATE_FORMAT)
2173                    , pp_ld.ld_period_name
2174                    , l_charge_factor
2175                    , l_charge_component
2176                    , pp_sc.sc_period_name
2177                    , l_billing_factor
2178                    , l_billing_component
2179                   );
2180 
2181                   WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg13',
2182                                                 ' RATIO '|| io_ratio );
2183 
2184 
2185 
2186               PROCESS_PRICE_BREAKS ( pp_sc
2187                            , pp_ld
2188                            , l_rail
2189                            , io_ratio
2190                            , to_date(to_char(pp_date_range_table(l_binary_idx).start_date,DEF_DATE_FORMAT)
2191                              ||BEGIN_DATE_TIME,RPI_DATE_FORMAT)
2192                            , to_date(to_char(pp_date_range_table(l_binary_idx).end_date,DEF_DATE_FORMAT)
2196 
2193                              ||END_DATE_TIME,RPI_DATE_FORMAT)
2194                            , l_line_number
2195                            ) ;
2197 
2198         end if;
2199         l_binary_idx := l_binary_idx + 1;
2200       end loop;
2201 
2202     end;
2203         WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.process_charges.Msg14',
2204                                       'END (Successful)  Process Standing Charges');
2205 EXCEPTION
2206   WHEN OTHERS THEN
2207 
2208     pp_date_range_idx    := l_date_range_idx_old;
2209     pp_date_range_table  := l_date_range_table_old;
2210     app_exception.raise_exception;
2211 END PROCESS_CHARGES;
2212 --
2213 PROCEDURE AUTO_INVOICE ( errbuf            OUT NOCOPY VARCHAR2
2214                        , retcode           OUT NOCOPY NUMBER
2215                        , p_run_date1       IN  VARCHAR2
2216                        , p_set_of_books_id IN  NUMBER
2217                        , p_batch_source_id IN  NUMBER
2218                        , p_debug_mode IN VARCHAR2
2219                        )
2220 IS
2221 --
2222 --OPSF(I) RPI Bug 2068218 24-Oct-2001 S Brewer Start(1)
2223 -- p_run_date parameter was changed to p_run_date1 for fnd_standart_date format
2224 -- so assigning value to p_run_Date here
2225 -- commenting out following bug fix so that old date format can be used and
2226 -- patch can be released to customer immediately
2227 -- OPSF(I) RPI Bug 2068218 24-Oct-2001 S Brewer End(1)
2228  p_run_date DATE;
2229 -- Changed parameter back to follow standards.
2230  l_total_lines           number ;       -- total count of standing charge lines processed
2231  l_line_count            number ;       -- Number of lines in the standing charges
2232  l_run_sequence          number ;      -- Sequence to indentify this
2233  lv_mesg                 varchar2(200) ;
2234 
2235  l_date_range_table DATE_RANGE_TABLE;
2236  l_date_range_idx   BINARY_INTEGER  ;
2237  l_debug_mode       VARCHAR2(1);
2238 
2239 
2240 BEGIN
2241  p_run_date              := to_date(p_run_date1,'YYYY/MM/DD HH24:MI:SS');
2242  l_total_lines           := 0;
2243  l_line_count            := 0;
2244  lv_mesg                 := null;
2245  l_debug_mode := nvl(p_debug_mode,'N');
2246 
2247 
2248     IF igi_gen.is_req_installed('RPI') THEN
2249        null;
2250     ELSE
2251        fnd_message.set_name( 'IGI', 'IGI_RPI_IS_DISABLED');
2252        lv_mesg := fnd_message.get;
2253            WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg1',
2254                                          lv_mesg);
2255        retcode := 2;
2256        errbuf  := lv_mesg;
2257        RETURN;
2258     END IF;
2259 
2260         WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg2',
2261                                       'BEGIN Generate Interface Data.');
2262     /** issue a savepoint       **/
2263     savepoint rpi_txns;
2264     /** Load the Global Custom Values **/
2265     SetValuesForGlobals;
2266     /** initialize the counters **/
2267     l_total_lines           := 0;  -- total number of charge lines processed for this run
2268     /** get the sequences **/
2269 
2270     BEGIN
2271         SELECT igi_rpi_generate_s.nextval
2272         INTO   l_run_sequence
2273         FROM   sys.dual ;
2274     END;
2275 
2276     BEGIN
2277             WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg3',
2278                                           'Next due date : '|| p_run_date );
2279 
2280         FOR std_rec IN c_stand_charges ( p_run_date, p_set_of_books_id, p_batch_source_id )  LOOP
2281 
2282                 WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg4',
2283                                               'Processing Charge : '|| std_rec.charge_reference);
2284 
2285 
2286 
2287             l_line_count := 0;
2288             FOR ld_rec IN C_line_details ( std_rec.standing_charge_id, std_rec.set_of_books_id ) LOOP
2289 
2290 
2291 
2292                 l_line_count              := l_line_count + 1;
2293                 l_total_lines             := l_total_lines + 1;
2294                     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg5',
2295                                                   'Line count : '|| l_line_count );
2296                 l_date_range_table.delete;
2297                 l_date_range_idx  := 0;
2298 
2299 
2300 
2301                 PROCESS_CHARGES ( std_rec,  ld_rec,  l_run_sequence
2302                                , l_date_range_table, l_date_range_idx );
2303                 -- Prorate invoices at line leve if not processed at invoice level.
2304 
2305                     PROCESS_REV_DISTRIBUTIONS ( std_rec
2306                             , g_curr_rev_idx
2307                             , g_raid_table
2308                             );
2309 
2310             END LOOP;
2311             PROCESS_REC_DISTRIBUTIONS ( std_rec
2312                             , g_curr_rec_idx
2313                              ,g_curr_rev_idx
2314                             , g_raid_table
2315                             );
2316 
2317             IF l_line_count <> 0 and l_debug_mode <> 'Y' THEN
2318                 Update igi_rpi_standing_charges
2319                 set     generate_sequence = l_run_sequence
2320                 ,       date_synchronized_flag = 'N'
2321                 where   standing_charge_id = std_rec.standing_charge_id
2322                 and     set_of_books_id    = std_rec.set_of_books_id;
2326             g_curr_rev_idx := 1 ;
2323             END IF;
2324             rev_idx :=0;
2325             g_curr_rec_idx := -1;
2327 
2328         END LOOP;
2329     EXCEPTION WHEN OTHERS THEN RAISE; -- throw the message to the outermost handler.
2330     END;
2331     /** save the changes if and only if some standing charge lines have been processed **/
2332     IF l_total_lines <> 0  THEN
2333         if l_debug_mode = 'Y' then
2334            rollback to rpi_txns;
2335         else
2336            COMMIT ;
2337         end if;
2338 
2339         -- Submit_RAXMTR ( p_batch_source_id , p_run_date );
2340     ELSE
2341          rollback to rpi_txns;
2342     END IF;
2343     -- Signal Normal completion.
2344     WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg6',
2348 
2345                                       'END (Successful) Generate Interface Data.');
2346     errbuf := null;
2347     retcode := 0;
2349 EXCEPTION WHEN OTHERS THEN
2350    rollback;
2351        WriteToLogFile(l_state_level, 'igi.plsql.igirrpi.auto_invoice.Msg7',
2352                                      'END (Error) Generate Interface Data.');
2353    errbuf := SQLERRM;
2354    retcode := 2;
2355 
2356 END AUTO_INVOICE;
2357 --
2358 BEGIN
2359   g_curr_rec_idx := -1;
2360   g_curr_rev_idx   := 1 ;
2361   rev_idx := 0;
2362   TRANSACTION_CODE       :=  'PERIODICS';
2363   FROM_DATE_INFO         :=  ' From Date ';
2364   TO_DATE_INFO           :=  ' To Date ';
2365 END IGIRRPI;