19
CREATE OR REPLACE PACKAGE BODY APPS.CISO_TU_INTCALC_PEP_PKG AS /******************************************************************************* **************/ /* NAME: Period End Process Program for Interest Deviation Calculation s */ /* DESCRIPTION: This Program creates the journals for the Charge Groups that have */ /* interest deviation calculation for a given invoice run. cc798 9 and cc7999 */ /* REVISIONS: */ /* Ver Date Author Description */ /* --------- ---------- --------------- ---------------------------------- -- */ /* 1.0 11/24/09 PProvost Initial Version - CMR #CHG00000012 1226 */ /******************************************************************************* **************/ /* Parameters: p_inv_run_id - Invoice Run ID of Invoices selected for processin g p_commit_flag - Create Journal for Interest Deviation */ PROCEDURE main( errbuf OUT NOCOPY VARCHAR2, retcode OUT NUMBER, p_inv_run_id IN VARCHAR2, p_commit_flag IN VARCHAR2) IS -- -- Global Variables -- v_current_date DATE := TRUNC(SYSDATE); v_org_id NUMBER := FND_GLOBAL.ORG_ID; v_user_id NUMBER := FND_GLOBAL.USER_ID; i INTEGER; -- counter to access record struct ure v_gl_insert BOOLEAN := FALSE; v_error_flag BOOLEAN := FALSE; -- assume no errors to start v_error_message VARCHAR2(1000) := NULL; v_inv_date DATE; -- invoice date of invoice run use d in control report heading -- used in control report routines v_ln_cnt INTEGER; v_pg_cnt INTEGER := 0; v_ln_cnt_max INTEGER := 50; v_spaces VARCHAR2(1) := ' '; v_rep_ln VARCHAR2(1000) := NULL; v_tu_data_cnt INTEGER := 0; -- total number of charge group re cords v_int_tot NUMBER := 0; -- total amount of Interest calcul ated on the current invoice v_ptb_tot NUMBER := 0; -- total amount of interest deviat ion in PTB table. Must equal v_int_tot v_cg_release_amt NUMBER := 0; -- any releases for charge group t his invoice run v_79x9s_exists BOOLEAN := FALSE; -- indicates if any 79x9 invoice l ines present this invoice run v_ptb_run_id VARCHAR2(20) := NULL; -- Invoice Run Number of the PTB r

Interest Dev Period End Package

Embed Size (px)

Citation preview

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 1/19

CREATE OR REPLACE PACKAGE BODY APPS.CISO_TU_INTCALC_PEP_PKG AS/*********************************************************************************************//* NAME: Period End Process Program for Interest Deviation Calculations *//* DESCRIPTION: This Program creates the journals for the Charge Groups thathave */

/* interest deviation calculation for a given invoice run. cc7989 and cc7999 *//* REVISIONS:

*//* Ver Date Author Description

*//* --------- ---------- --------------- ------------------------------------ *//* 1.0 11/24/09 PProvost Initial Version - CMR #CHG000000121226 *//*********************************************************************************************/

/*Parameters: p_inv_run_id - Invoice Run ID of Invoices selected for processing

p_commit_flag - Create Journal for Interest Deviation*/

PROCEDURE main( errbuf OUT NOCOPY VARCHAR2,retcode OUT NUMBER,p_inv_run_id IN VARCHAR2,p_commit_flag IN VARCHAR2) IS

---- Global Variables--

v_current_date DATE := TRUNC(SYSDATE);v_org_id NUMBER := FND_GLOBAL.ORG_ID;v_user_id NUMBER := FND_GLOBAL.USER_ID;i INTEGER; -- counter to access record struct

urev_gl_insert BOOLEAN := FALSE;v_error_flag BOOLEAN := FALSE; -- assume no errors to startv_error_message VARCHAR2(1000) := NULL;v_inv_date DATE; -- invoice date of invoice run use

d in control report heading-- used in control report routinesv_ln_cnt INTEGER;

v_pg_cnt INTEGER := 0;v_ln_cnt_max INTEGER := 50;v_spaces VARCHAR2(1) := ' ';v_rep_ln VARCHAR2(1000) := NULL;

v_tu_data_cnt INTEGER := 0; -- total number of charge group recordsv_int_tot NUMBER := 0; -- total amount of Interest calcul

ated on the current invoicev_ptb_tot NUMBER := 0; -- total amount of interest deviat

ion in PTB table. Must equal v_int_totv_cg_release_amt NUMBER := 0; -- any releases for charge group t

his invoice run

v_79x9s_exists BOOLEAN := FALSE; -- indicates if any 79x9 invoice lines present this invoice runv_ptb_run_id VARCHAR2(20) := NULL; -- Invoice Run Number of the PTB r

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 2/19

ecords. Used in cr_cg_invoice cursor to get the-- charge group totals in the last

invoice run num when interest deviation was calculatedv_ptb_trade_date DATE := NULL; -- used to lookup 79x9 PTB records

. Comes from bp end date in cr_79x9_inv_totv_bp_rep_tot NUMBER := 0; -- running total amount of interes

t. Used for rounding and must equal v_int_tot

v_bp_pct_tot NUMBER := 0; -- runnint total percent. Used forrounding and at the end and must 1.00v_cg_tot_amt NUMBER := 0; -- running total value of chg grps

. Used for prorating interest across chg grps

v_set_of_books_id NUMBER; -- for journal submissionv_srce_name VARCHAR2(20); -- dittov_market_cash_ccid NUMBER; -- Market Cash sourcev_int_dev_ccid NUMBER; -- interest deviation cash sourcev_int_dev_acct VARCHAR2(50); -- account name used for display p

urposesv_int_dev_baid VARCHAR2(5); -- baid used for for lookup in CIS

O_CHRG_GRP_RELEASES for shortfall releasesv_last_message VARCHAR2(1000); -- used to provide hold/release amounts at end of report

-- this type structure records Bill Determinants and Attributes passed to Settlements via PTB WebserviceTYPE charge_group_rec IS RECORD(

chrg_grp VARCHAR2(25), -- Charge Group Nameone_sided VARCHAR2(3), -- Is Charge Group 1-sided (Yes/No)prev_run_id VARCHAR2(20), -- Previous Run ID where the Interest Cal

culations took place and PTBs were createdprev_tx_date DATE, -- Previous Run Invoice Date displayed on

report

int_dev_tot NUMBER, -- Total Interest Deviation amount this Invoice Run ID or Shortfall Release

cg_amt NUMBER, -- Charge Group Totalcg_pct NUMBER, -- Charge Group Percent = cg_amt / cg_tot

 _amtcg_tot_amt NUMBER, -- Total for all Charge Groupsint_dev_amt NUMBER, -- Interest Deviation amount for Charge G

roup = cg_pct * v_int_totcr_acct NUMBER, -- ccid of GL acct to Creditdr_acct NUMBER, -- ccid of GL acct to Debitrouting_info VARCHAR2(100), -- informational text if charge group doe

s not have a checking acctchking_acct NUMBER); -- ccid of GL acct for trustee bank accou

ntTYPE cg_tab_typ IS TABLE OF charge_group_recINDEX BY BINARY_INTEGER;cg_data cg_tab_typ; -- stores charge group interest deviation totals for c

urrent Invoice Run and any Shortfall Releases

c7989 VARCHAR2(4) := '7989'; -- Deviation Interest Distribution Charge Codec7999 VARCHAR2(4) := '7999'; -- Deviation Interest AllocationCharge CodecINV_DEVIATION_INTEREST VARCHAR2(25) := 'INV_DEVIATION_INTEREST';-- column headings for reporting

v_heading1 VARCHAR2(300) := rpad('Previous Run ID/', 23, v_spaces) CHR(13)CHR(10)

lpad('Invoice Date', 22, v_spaces) ' '

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 3/19

rpad('Roll-Up Charge Group Name', 26, v_spaces) rpad('1-Sided', 8, v_spaces) lpad('Chg Grp Total', 15, v_spaces) lpad('% of Total', 11, v_spaces) lpad('Int. Dev. Total', 16, v_spaces) lpad('Chg Grp Interest', 19, v_spaces) CHR(13) CHR(10)rpad('----------------------', 23, v_spaces)

rpad('-------------------------', 26, v_spaces) rpad('-------', 8, v_spaces) rpad('---------------', 16, v_spaces) rpad('----------', 11, v_spaces) rpad('---------------', 19, v_spaces) rpad('---------------', 16, v_spaces);

/*Purpose: The following Cursor is called from the Mainline of the package*/CURSOR cr_sf_release ISSELECT inv_run_id, release_amt -- inv_run_id is the previou

s Run ID the Shortfall occurred in

FROM ciso_chrg_grp_releasesWHERE chrg_grp_baid = v_int_dev_baid -- process any releases madeto Invoice Deviation Interest Charge Group

AND release_run_id = p_inv_run_id; -- in the current run id bythe AR/AP invoice program/*Purpose: The following Cursor is called from the Mainline of the package and GET _INT_DEV_TOTALS and does the following:

1. Sums the interest deviation charge codes that show up on invoices for p_inv _run_id.

2. rctl.attribute9 is the Bill Period End Date which is used to link to the Trade Date in the CISO_PTB_APPROVED table3. This v_ptb_trade_date ensures the PTB interest totals = current Invoice 79x

9 totals and provides the Invoice Run IDused in the cursor CR_CG_INVOICE to lookup the recalculated charge group to

tals from the previous invoice run.*/

CURSOR cr_79x9_inv_tot( p_invoice_run VARCHAR2) ISSELECT SUM(rctl.extended_amount) int_tot, rctl.attribute9 bp_edateFROM ra_customer_trx rct,

ra_cust_trx_types ctt,ra_customer_trx_lines rctl,ra_cust_trx_line_gl_dist rcgd,gl_code_combinations gcc

WHERE rct.attribute1 = p_invoice_runAND ctt.cust_trx_type_id = rct.cust_trx_type_idAND ctt.name = 'MARKET' -- Exclude ANN

UAL_FERC invoices in the same inv_run_idAND rctl.customer_trx_id = rct.customer_trx_idAND rctl.extended_amount <> 0 -- incredibly,

I discovered Settlements sending $0 lines for 79x9AND rcgd.customer_trx_line_id = rctl.customer_trx_line_id -- don't ask m

e why, but I code to avoid accidentally picking upAND gcc.code_combination_id = rcgd.code_combination_id -- unwanted re

cordsAND gcc.segment4 IN (c7999,c7989)AND NOT EXISTS( SELECT * -- ensure invo

ice has not been cancelled

FROM ar_adjustments adj,ar_receivables_trx art

WHERE adj.customer_trx_id = rct.customer_trx_id

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 4/19

AND art.receivables_trx_id = adj.receivables_trx_idAND UPPER(art.name) = 'CANCEL/REBILL ADJUSTMENT

'AND art.status = 'A')

GROUP BY rctl.attribute9UNIONSELECT SUM(aid.amount * -1) int_tot, aid.attribute9 bp_edate

FROM ap_invoices ai,ap_invoice_distributions aid,gl_code_combinations gcc

WHERE ai.attribute1 = p_invoice_runAND ai.cancelled_date IS NULL -- exclude cance

lled invoicesAND ai.pay_group_lookup_code = 'MARKET' -- Exclude ANNUA

L_FERC invoices in the same inv_run_idAND aid.invoice_id = ai.invoice_idAND aid.amount <> 0AND gcc.code_combination_id = aid.dist_code_combination_idAND gcc.segment4 IN (c7999,c7989)

GROUP BY aid.attribute9; -- should onlybe one bill period end date---- MAINLINE Function Calls--FUNCTION error_in_set_of_books RETURN boolean ISBEGINSELECT gsob.set_of_books_idINTO v_set_of_books_idFROM ap_system_parameters asp,

gl_sets_of_books gsobWHERE asp.set_of_books_id = gsob.set_of_books_idAND UPPER(gsob.name) = 'MARKET ACTUALS';

RETURN FALSE;

EXCEPTIONWHEN OTHERS THENRETURN TRUE;

END;--FUNCTION error_in_jrnl_srce RETURN BOOLEAN ISBEGINSELECT je_source_nameINTO v_srce_nameFROM gl_je_sourcesWHERE user_je_source_name = 'CISO Period End';RETURN FALSE;

EXCEPTIONWHEN OTHERS THENRETURN TRUE;

END;---- There must exist an active internal bank account called Market. This acct-- is replaced by the v_int_dev_ccid in the following function.---- This is because we already moved $$ from the Market account to the INV_DEVIAT

ION_INTEREST-- charge group account in the CISO_PERIOD_END_PKG program which was run beforethis program.

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 5/19

---- This program distributes The Interest Deviation $$ to the 1-sided charge groups so we have-- to switch the ccid stored in attribute5 of the FlexField DFF from Market Cashto INV_DEVIATION_INTEREST--FUNCTION error_in_market_acct RETURN boolean IS

BEGINSELECT asset_code_combination_idINTO v_market_cash_ccidFROM ap_bank_accountsWHERE UPPER(bank_account_name) = 'MARKET'AND account_type = 'INTERNAL'AND NVL( inactive_date, v_current_date + 1) > v_current_date;

RETURN FALSE;

EXCEPTIONWHEN others THEN

RETURN TRUE;END;---- There must exist an active Invoice Deivation Interest Charge group Debit Account. This acct-- is where interest deviation money is distributed or allocated to the one-sided charge groups.-- Also, the baid is used in the cr_sf_release cursor for Shortfall releases--FUNCTION error_in_int_dev_acct RETURN boolean ISBEGINSELECT NVL(ffv.attribute5, '-1') dr_acct,

NVL(ffv.attribute8, 'XXX') routing_info,

NVL(ffv.attribute7, 'XXX') baidINTO v_int_dev_ccid,

v_int_dev_acct,v_int_dev_baid

FROM fnd_flex_value_sets fvs,fnd_flex_values_vl ffv

WHERE ffv.flex_value = cINV_DEVIATION_INTERESTAND ffv.enabled_flag = 'Y'AND ffv.flex_value_set_id = fvs.flex_value_set_idAND flex_value_set_name = 'CISO_ACCOUNT';

IF v_int_dev_ccid = -1 OR v_int_dev_acct = 'XXX' OR v_int_dev_baid = 'XXX' THEN

RETURN TRUE;ELSERETURN FALSE;

END IF;

EXCEPTIONWHEN OTHERS THENRETURN TRUE;

END;/*Purpose: The following procedure retrieves the total $$ for cc7989/7999 for thecurrent Invoice Run.

It ensures the amount is the same as what was calculated from the previous Initial Invoice Run.

If there is a discrepancy then an error is reported.

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 6/19

*/PROCEDURE get_int_dev_totals ISv_error_str VARCHAR2(300);v_cg_hold_amount NUMBER := 0; -- any holds applied to INV_DEVIATION_IN

TEREST charge group during this invoice Run---- Mainline of get_int_dev_total

--BEGINFOR inv_rec IN cr_79x9_inv_tot(p_inv_run_id) LOOP -- for each AR/AP invoic

e total for 7999/7989 charge codes in the invoice runv_int_tot := v_int_tot + inv_rec.int_tot; -- add to interest devia

tion total for entire invoice runv_ptb_trade_date := TO_DATE(inv_rec.bp_edate, 'MM/DD/YYYY'); -- bp_edate o

f current invoice run links to trade date in ciso_ptb_approvedv_79x9s_exists := TRUE;

END LOOP;-- if initial invoice lines have non-zero 79x9 charges-- then lookup the source PTB records and retrieve the Previous Invoice Run Num

(v_ptb_run_id)IF v_79x9s_exists THEN-- The following Select statement sums PTB Approved records by Invoice Run ID. Should only be one record as there is only-- one trade date for this batch of 79x9 PTBs. The trade date ensures the PTBs generated are on the next available invoice.

v_error_str := 'This invoice run has 79x9 charge codes; however, error occurred retrieving PTB Invoice Run ID '

'in the CISO_PTB_APPROVED table using Trade Date 'TO_CHAR(v_ptb_trade_date, 'DD-MON-YYYY');

SELECT cpa.invoice_run_num, SUM(cpa.value)INTO v_ptb_run_id, v_ptb_totFROM ciso_ptb_approved cpa

WHERE cpa.trade_date = v_ptb_trade_dateAND cpa.product_code IN (c7989,c7999)AND cpa.value <> 0

GROUP BY cpa.invoice_run_num;v_error_str := 'This invoice run has 79x9 charge codes; however, error occu

rred retrieving HOLD record ''for 'cINV_DEVIATION_INTEREST' in the CISO_CHRG_GRP_TOT

ALS table for this invoice Run ID.';SELECT NVL( SUM( a.hold_amount), 0)INTO v_cg_hold_amountFROM ciso_chrg_grp_totals aWHERE a.charge_group = cINV_DEVIATION_INTEREST -- subtract any holds place

d on Invoice Deviation InterestAND a.inv_run_id = p_inv_run_id; -- Charge Group in the cur

rent run id by the regular PEP programEND IF;

SELECT NVL( SUM(release_amt), 0) -- get the total release amounts

INTO v_cg_release_amtFROM ciso_chrg_grp_releasesWHERE chrg_grp_baid = v_int_dev_baid -- made to Invoice Deviation

Interest Charge GroupAND release_run_id = p_inv_run_id; -- in the current run id by

the AR/AP invoice program

IF v_ptb_tot - v_cg_hold_amount <> v_int_tot THENfnd_file.NEW_LINE(fnd_file.LOG, 1);

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 7/19

fnd_file.put_line(fnd_file.output,'Interest Deviation Total for current Invoices: 'TO_CHAR(v_int_tot,'9,999,999.99')

CHR(13)CHR(10)' does not equal PTBtotal: 'TO_CHAR(v_ptb_tot,'9,999,999.99')

CHR(13)CHR(10)' minus HoldTotal: 'TO_CHAR(v_cg_hold_amount,'9,999,999.99')

' with Trade DAte 'TO_CHAR(v_ptb_trade_date, 'DD-MON-YYY

Y'));v_error_flag := TRUE;

ELSEv_last_message := CHR(13)CHR(10)CHR(13)CHR(10)

' Current Deviation Interest PTB Amount Generated By Last Invoice Run : '

to_char(v_ptb_tot,'$9,999,999,999.99')CHR(13)CHR(10)

'Subtract Deviation Interest Hold Amount Due to CurrentShortFall : '

to_char(v_cg_hold_amount,'$9,999,999,999.99')CHR(13)CHR(10)

' Add Deviation Interest Release Amounts Received For Past Shortfalls: ' to_char(v_cg_release_amt,'$9,999,999,999.99')CHR(13)

CHR(10)lpad('-----------------', 92, v_spaces)CHR(13)CHR(10

)lpad('Total $$ Movement Amount Created For Journal Impor

t: ', 74, v_spaces) to_char(v_ptb_tot + v_cg_release_amt - v_cg_hold_amount,

'$9,999,999,999.99')CHR(13)CHR(10)CHR(13)CHR(10);

fnd_file.PUT_LINE(fnd_file.LOG, v_last_message);

v_ptb_tot := v_ptb_tot - v_cg_hold_amount; -- this is the revised amt tosmear across charge groups for current invoice run

END IF;

EXCEPTIONWHEN OTHERS THENfnd_file.put_line(fnd_file.output,v_error_str' 'SQLERRM);v_error_flag := TRUE;

END get_int_dev_totals;/*Purpose: The following procedure formats and lists the header of the report*/PROCEDURE control_report_header ISv_str VARCHAR2(300);

BEGINv_pg_cnt := v_pg_cnt + 1;-- Report Headerv_str := rpad('Market Actuals', 38, v_spaces)

rpad('Interest Deviation Period End Process', 59, v_spaces) 'RUN DATE:'

to_char(v_current_date, 'DD-MON-YYYY');fnd_file.put_line(fnd_file.output, v_str);v_str := 'Invoice Run ID: ' rpad( p_inv_run_id, 51, v_spaces) lp

ad( 'PAGE:', 33) lpad( v_pg_cnt, 11, v_spaces);fnd_file.put_line(fnd_file.output, v_str);

v_str := 'Initial Invoice Date: ' to_char(v_inv_date, 'DD-MON-YYYY');fnd_file.put_line(fnd_file.output, v_str);-- Skips 2 lines

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 8/19

fnd_file.new_line(fnd_file.output, 2);-- Report Column Headingfnd_file.put_line(fnd_file.output, v_heading1);

END control_report_header;/*Purpose: The following procedure lists each non-zero charge group from the previous invoice run.

It is called in the Mainline of the program after all validations havecompleted.

Procedures Called: print_report_totals, add_to_report_totals*/PROCEDURE control_report_body ISPROCEDURE print_report_line ISBEGINIF cg_data(i).cg_amt <> 0 THENv_rep_ln := cg_data(i).prev_run_id'/'rpad(TO_CHAR(cg_data(i).prev_tx

 _date,'DD-MON-YYYY'), 12, v_spaces) rpad(cg_data(i).chrg_grp, 26, v_spaces) rpad(cg_data(i).one_sided, 7, v_spaces)

lpad(TO_CHAR(cg_data(i).cg_amt,'$999,999,999.99'),16,v_spaces) lpad(TO_CHAR(cg_data(i).cg_pct*100,'999.99'),11,v_spaces) lpad(TO_CHAR(cg_data(i).int_dev_tot,'$999,999,999.99'),16,v_spac

es) lpad(TO_CHAR(cg_data(i).int_dev_amt,'$999,999,999.99'),19,v_spac

es);fnd_file.put_line(fnd_file.output, v_rep_ln);

END IF;END;

PROCEDURE print_report_totals ISBEGIN

v_rep_ln := lpad('--------------- ---------- --------------- ', 119, v_spaces)

CHR(13)CHR(10)lpad(TO_CHAR(v_cg_tot_amt,'$999,999,999.99'), 72, v_spaces)

lpad(TO_CHAR(v_bp_pct_tot,'999.99'), 11, v _spaces)

lpad(TO_CHAR(v_bp_rep_tot,'$999,999,999.99'), 35, v_spaces);

fnd_file.put_line(fnd_file.output, v_rep_ln);fnd_file.new_line(fnd_file.output, 2);

END;

PROCEDURE add_to_report_totals ISBEGINv_bp_rep_tot := v_bp_rep_tot + cg_data(i).int_dev_amt;v_bp_pct_tot := v_bp_pct_tot + (cg_data(i).cg_pct*100);v_cg_tot_amt := v_cg_tot_amt + cg_data(i).cg_amt;

END;

PROCEDURE reset_report_totals IS -- reset charge group total countersBEGINv_bp_rep_tot := 0; v_bp_pct_tot := 0; v_cg_tot_amt := 0;

END;BEGIN-- Verify page breaks

v_ln_cnt := v_ln_cnt + 1;IF (v_ln_cnt > v_ln_cnt_max) OR (v_pg_cnt = 0) THENv_ln_cnt := 6;

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 9/19

fnd_file.new_line(fnd_file.output, 1);fnd_file.put(fnd_file.output, chr(12));control_report_header;

END IF;

IF i = v_tu_data_cnt THEN -- last record to process soIF i = 1 THEN -- if only on

e record then report itprint_report_line;

ELSIF cg_data(i).prev_run_id = cg_data(i-1).prev_run_id THEN -- elsif sameas previous invoice run ID then report it

print_report_line;ELSE -- else new r

un ID so give totals for previous run IDprint_report_totals;print_report_line; -- and report

line by itself and reset countersreset_report_totals;

END IF;

add_to_report_totals; -- add current record to report totals and print them

print_report_totals;ELSE -- else not l

ast recordIF i > 1 THEN -- so if its

NOT the 1st record thenIF cg_data(i).prev_run_id <> cg_data(i-1).prev_run_id THEN -- if differe

nt invoice run ID thenprint_report_totals; -- report tot

als and reset countersreset_report_totals;

END IF;END IF;

print_report_line; -- print current record

add_to_report_totals; -- and add toreport totals

END IF;EXCEPTIONWHEN OTHERS THENfnd_file.put_line(fnd_file.output,'Error in Control_Report_Body Procedur

e 'SQLERRM);v_error_flag := TRUE;

END control_report_body;/*Purpose: The following procedure is called from the Mainline of the Package.

2 cursors and 1 function are called within this procedure.Cursors Called: cr_cg_invoice

*/PROCEDURE process_79X9_data( p_prev_inv_run_id VARCHAR2, p_int_dev_tot NUMBER)IS-- Local Variablesv_cg_totals NUMBER := 0;v_cg_counter INTEGER;

/*

The following Cursor selects AR/AP invoice lines based on the PTB Invoice Run ID from the previous run.

It groups invoice lines by charge groups and orders by lowest total to highe

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 10/19

st so rounding differencesare added/subtracted to/from the charge group with the largest dollar amount

.*/

CURSOR cr_cg_invoice IS-- attribute2 indicates if charge group is one-sided. attribute6 is rollup g

roup

-- rollup chg grp (ie. EXCESS_COST, RT_CONGESTION, PIRP_STLMT all rollup toIMBALANCE_ENERGY)

SELECT ci.transaction_date,NVL( ffv.attribute6, cil.major_account) chg_grp,DECODE(NVL(ffv.attribute2, 'N'), 'N', 'No', 'Yes') one_sided,NVL(ffv.attribute4, '-1') cr_acct,NVL(ffv.attribute5, '-1') dr_acct,NVL(ffv.attribute8, 'XXX') routing_info,NVL(ffv.attribute9, '0') chking_acct,SUM(cil.line_amount) cg_tot

FROM ciso_invoice ci,ciso_invoice_line cil,

fnd_flex_value_sets fvs,fnd_flex_values_vl ffvWHERE ci.inv_run_id = p_prev_inv_run_id -- only invoices

for the Previous run idAND ci.invoice_type = 'MARKET' -- exclude ANNUAL

 _FERC invoicesAND ci.process_status = 'P' -- include only s

uccessfully processed invoicesAND cil.name = ci.name -- invoice numberAND cil.line_type = 'RECALC' -- ignore INITIAL

line typesAND cil.sc <> '6710' -- exclude Intern

al ISO records used for neutrality

AND ffv.flex_value = cil.major_accountAND ffv.enabled_flag = 'Y'AND ffv.flex_value_set_id = fvs.flex_value_set_idAND flex_value_set_name = 'CISO_ACCOUNT'GROUP BY ci.transaction_date, NVL( ffv.attribute6, cil.major_account), NVL

( ffv.attribute2, 'N'), NVL( ffv.attribute4, '-1'),NVL( ffv.attribute5, '-1'), NVL( ffv.attribute8, 'XXX'), NVL( ff

v.attribute9, '0')ORDER BY ABS(cg_tot);

---- MAIN of process_79X9_data--BEGINv_cg_counter := v_tu_data_cnt; -- start where we last

left offi := v_tu_data_cnt;FOR cg_rec IN cr_cg_invoice LOOP -- get total $ for eac

h Charge Group in this Invoice Runv_cg_counter := v_cg_counter + 1; -- increment global co

unterv_cg_totals := v_cg_totals + cg_rec.cg_tot; -- running CG total fo

r this Invoice Run ID-- assign variables for this Charge Groupcg_data(v_cg_counter).int_dev_tot := p_int_dev_tot;cg_data(v_cg_counter).prev_run_id := p_prev_inv_run_id;

cg_data(v_cg_counter).prev_tx_date := cg_rec.transaction_date;cg_data(v_cg_counter).chrg_grp := cg_rec.chg_grp;cg_data(v_cg_counter).one_sided := cg_rec.one_sided;

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 11/19

cg_data(v_cg_counter).cr_acct := cg_rec.cr_acct;cg_data(v_cg_counter).dr_acct := cg_rec.dr_acct;cg_data(v_cg_counter).routing_info := cg_rec.routing_info;cg_data(v_cg_counter).chking_acct := cg_rec.chking_acct;cg_data(v_cg_counter).cg_amt := cg_rec.cg_tot;

END LOOP; -- get next charge group

v_bp_pct_tot := 0; v_bp_rep_tot := 0; -- reset totals for rounding while prorating interest

WHILE i < v_cg_counter LOOP -- if we have chg groups for this invoice Run ID

i := i + 1; -- we must prorate the interest for each Charge Group

IF v_cg_totals = 0 THEN -- avoid divide by 0. Means the last CG will be modified

cg_data(i).cg_pct := ROUND(cg_data(i).cg_amt / 1, 4); -- see code following this While Loop

ELSE

cg_data(i).cg_pct := ROUND(cg_data(i).cg_amt / v_cg_totals, 4);END IF;v_bp_pct_tot := v_bp_pct_tot + cg_data(i).cg_pct; --

must eventually = 1cg_data(i).int_dev_amt := ROUND(p_int_dev_tot * cg_data(i).cg_pct, 2);v_bp_rep_tot := v_bp_rep_tot + cg_data(i).int_dev_amt; --

must eventually = p_int_dev_totEND LOOP;-- The following adds/subtracts to/from the last Charge Group to account for

roundingIF i > 0 THENcg_data(i).int_dev_amt := cg_data(i).int_dev_amt + p_int_dev_tot - v_bp_re

p_tot; -- adjust int_dev_amt so p_int_dev_tot = v_bp_rep_tot

cg_data(i).cg_pct := cg_data(i).cg_pct + 1 - v_bp_pct_tot;-- adjust cg_pct so v_bp_pct_tot = 1 same as 100%

END IF;v_tu_data_cnt := v_cg_counter; -- remember new total

EXCEPTIONWHEN OTHERS THENfnd_file.put_line(fnd_file.output,'Error in Process_79X9_data Procedure.

'SQLERRM);v_error_flag := TRUE;

END process_79X9_data;/*Purpose: The following procedure is called from the Mainline of the Package.

It determines what journals to create for each charge group based on the values in the cg_data(i) record structure.

At the very least a debit and credit journal is created. If the cr_acctor dr_acct is missing then an error is reported.

If the charge group has a trustee bank account setup then two additional journal lines are created.

Procedures Called: summarize_chg_grpscreate_gl_int_recretrieve_subaccount

*/

PROCEDURE create_gl_rec IS

v_bank_account_name VARCHAR2(240); -- used for reporting purposes so the user knows which bank account

v_bank_account_num VARCHAR2(240); -- the money is going to or coming from.

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 12/19

v_chking_int_ccid NUMBER;v_cr_acct_int_ccid NUMBER;v_dr_acct_int_ccid NUMBER;

/*Purpose: The following procedure removes $0 charge groups from the cg_data record structure and summarizes

the charge group so only 1 journal is created for each charge group.

v_tu_data_cnt is modified as well as the cg_data record structure.*/

PROCEDURE summarize_chg_grps ISj INTEGER := 0;k INTEGER := 0;no_duplicate BOOLEAN;cg_data2 cg_tab_typ; -- temporary storage for charge group interest

deviation totalsBEGINi := 0;WHILE i < v_tu_data_cnt LOOP -- we have chg grp recordsi := i + 1;

IF cg_data(i).int_dev_amt <> 0 THEN -- exclude charge groups with no interest deviation charges to movej := j + 1; -- new counter for valid charge

groupscg_data2(j) := cg_data(i); -- assign the data recordFOR k IN i+1..v_tu_data_cnt LOOP -- summarize interest deviation

$$IF cg_data2(j).chrg_grp = cg_data(k).chrg_grp THENcg_data2(j).int_dev_amt := cg_data2(j).int_dev_amt + cg_data(k).in

t_dev_amt;END IF;

END LOOP;END IF;

END LOOP;i := 0; v_tu_data_cnt := 0; -- reset counters

WHILE i < j LOOP -- non zero chargegroups

i := i + 1; no_duplicate := TRUE;FOR k IN 1..i-1 LOOP -- looking backwar

dsIF cg_data2(i).chrg_grp = cg_data2(k).chrg_grp THEN -- if chr grp alre

ady existsno_duplicate := FALSE; -- then don't save

this oneEND IF;

END LOOP;IF no_duplicate THENv_tu_data_cnt := v_tu_data_cnt + 1; -- increment count

ercg_data(v_tu_data_cnt) := cg_data2(i); -- assign the data

recordEND IF;

END LOOP;END;

/*Purpose: It creates journal records in gl_interface. Parameters passed are the gl code combination id and the credit and debit

amounts. Remember one of the amounts passed has to be zero.*/

PROCEDURE create_gl_int_rec(p_ccid IN NUMBER, p_cr IN NUMBER, p_dr IN NUMBER

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 13/19

) ISBEGININSERT INTO gl_interface(

status,set_of_books_id,accounting_date,currency_code,

date_created,created_by,actual_flag,user_je_category_name,user_je_source_name,code_combination_id,entered_cr,entered_dr)

VALUES('NEW',v_set_of_books_id,v_inv_date,

'USD',v_current_date,v_user_id,'A','CISO Period End','CISO Period End',p_ccid,p_cr,p_dr);

v_gl_insert := TRUE;END;

-- This function returns the ccid of the INT sub-account the Interest Deviation

$$ are moving in/out of-- Parameter passed is either dr_acct, cr_acct or chking_acct ccid which shouldhave an INT subaccount-- already setup for it. If there isn't an INT subaccount created then an erroris flagged.--

FUNCTION retrieve_subaccount( p_ccid NUMBER, p_acct VARCHAR2) RETURN NUMBERIS

v_ccid NUMBER;v_missing_int_acct VARCHAR2(50);

BEGINSELECT b.code_combination_idINTO v_ccidFROM gl_code_combinations a,

gl_code_combinations bWHERE a.code_combination_id = p_ccidAND b.segment1 = a.segment1AND b.segment2 = a.segment2AND b.segment3 = a.segment3AND b.segment4 = 'INT';

RETURN v_ccid;

EXCEPTIONWHEN OTHERS THEN

SELECT segment1'.'segment2'.'segment3 -- we know the p_ccid exists so lets give a more meaningful error message

INTO v_missing_int_acct

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 14/19

FROM gl_code_combinationsWHERE code_combination_id = p_ccid;

fnd_file.put_line(fnd_file.output,'Error looking up INT Sub-Account for 'p_acct' 'v_missing_int_acct

' for Charge Group 'cg_data(i).chrg_grpCHR(13)CHR(10)'Make sure you create the Sub-Account and code combination befo

re rerunning this program'CHR(13)CHR(10));

RETURN -1; -- indicates an error occurredEND;

---- Mainline create_gl_rec--BEGINsummarize_chg_grps;i := 0;WHILE i < v_tu_data_cnt LOOP -- we have chg grp recordsi := i + 1;

-- if debit or credit accounts are not setup in Charge Group DFF then flag as an errorIF cg_data(i).cr_acct = -1 OR cg_data(i).dr_acct = -1 THENfnd_file.PUT_LINE(fnd_file.OUTPUT,'Missing Debit/Credit Accounts for Cha

rge Group 'cg_data(i).chrg_grp);fnd_file.PUT_LINE(fnd_file.OUTPUT,'You will need to assign valid account

s in the Charge Group Flexfield and then rerun this program!');fnd_file.NEW_LINE(fnd_file.OUTPUT,1);v_error_flag := TRUE;

ELSEIF cg_data(i).chking_acct = 0 THEN -- no checking account for this cha

rge groupv_chking_int_ccid := 0;

ELSE-- else charge group has a checking account then get the bank name and acc

ount number for display purposes-- as well as the INT subaccount ccid

SELECT bank_account_name, bank_account_numINTO v_bank_account_name, v_bank_account_numFROM ap_bank_accountsWHERE asset_code_combination_id = cg_data(i).chking_acct;

v_chking_int_ccid := retrieve_subaccount(cg_data(i).chking_acct,'Checking Acct');

END IF;

IF cg_data(i).cr_acct = v_market_cash_ccid THEN -- if the cr_acct is the Market Cash Account then we want

v_cr_acct_int_ccid := v_int_dev_ccid; -- to change it to theInvoice Deviation Interest account. That is where the $$ are

ELSEv_cr_acct_int_ccid := retrieve_subaccount(cg_data(i).cr_acct,'CR Acct'

); -- else get the interest subaccountEND IF;v_dr_acct_int_ccid := retrieve_subaccount(cg_data(i).dr_acct,'DR Acct');

-- get interest subaccount

IF v_cr_acct_int_ccid = -1 OR v_cr_acct_int_ccid = -1 OR v_chking_int_cc

id = -1 THEN -- no INT subaccount setupv_error_flag := TRUE;

-- so flag as an setup error

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 15/19

ELSEIF cg_data(i).int_dev_amt < 0 THEN -- if moving cash from char

ge group to INV_DEVIATION_INTEREST accountIF cg_data(i).chking_acct <> 0 THEN -- trust acct exists so cre

ate extra jrnlcreate_gl_int_rec(v_int_dev_ccid, 0, cg_data(i).int_dev_amt*-1);create_gl_int_rec(v_chking_int_ccid, cg_data(i).int_dev_amt*-1, 0)

;v_rep_ln := 'Move 'TO_CHAR(cg_data(i).int_dev_amt,'$9,999,999,99

9.99')' from 'rpad(v_bank_account_name' Acct # 'v_bank

 _account_num, 37, v_spaces)' to 'v_int_dev_acct;

ELSEv_rep_ln := 'Move 'TO_CHAR(cg_data(i).int_dev_amt,'$9,999,999,99

9.99')' from 'rpad('Acct # 'cg_data(i).routing_info, 37,

v_spaces)' to 'v_int_dev_acct;

END IF;create_gl_int_rec(v_cr_acct_int_ccid, 0, cg_data(i).int_dev_amt*-1);create_gl_int_rec(v_dr_acct_int_ccid, cg_data(i).int_dev_amt*-1, 0);

ELSE -- else we are moving cashfrom INV_DEVIATION_INTEREST account to charge group

IF cg_data(i).chking_acct <> 0 THEN -- trust acct exists so create extra jrnl

create_gl_int_rec(v_int_dev_ccid, cg_data(i).int_dev_amt, 0);create_gl_int_rec(v_chking_int_ccid, 0, cg_data(i).int_dev_amt);v_rep_ln := 'Move 'TO_CHAR(cg_data(i).int_dev_amt,'$9,999,999,99

9.99')' from 'rpad(v_int_dev_acct, 37, v_spaces)' to 'v_bank_account_name' Acct # 'v_bank_accoun

t_num;ELSEv_rep_ln := 'Move 'TO_CHAR(cg_data(i).int_dev_amt,'$9,999,999,99

9.99')' from 'rpad(v_int_dev_acct, 37, v_spaces)' to Acct # 'cg_data(i).routing_info;

END IF;create_gl_int_rec(v_cr_acct_int_ccid, cg_data(i).int_dev_amt, 0);create_gl_int_rec(v_dr_acct_int_ccid, 0, cg_data(i).int_dev_amt);

END IF;fnd_file.PUT_LINE(fnd_file.OUTPUT,v_rep_ln);

END IF; -- check for int_ccid = -1END IF; -- check for cr_acct/dr_acct = -1

END LOOP;-- list total movement dollarsfnd_file.put_line(fnd_file.output,' ---------------'CHR(13)CHR(10

)'Total: 'TO_CHAR(v_int_tot,'$999,999,999

.99'));EXCEPTIONWHEN NO_DATA_FOUND THENfnd_file.put_line(fnd_file.output,'Error looking up Bank Account using C

CID 'TO_CHAR(cg_data(i).chking_acct,'999999')' for Charge Group 'cg_data(i).chrg_ 

grp' 'SQLERRM);

v_error_flag := TRUE;WHEN OTHERS THENfnd_file.put_line(fnd_file.output,'Error in create_gl_rec Procedure. '

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 16/19

SQLERRM);v_error_flag := TRUE;

END;/*Purpose: The following procedure is called from the Mainline of the Package.

It submits a journal import job for the journal records created to movecash for Interest Deviation $$

*/PROCEDURE submit_jrnl_import ISv_run_id NUMBER;v_req_id NUMBER;

BEGINSELECT gl_journal_import_s.NEXTVAL -- This is used in the GLXJIRUN formINTO v_run_id -- See PROCEDURE interface_run_idFROM dual; -- and gl_interface_control_pkg.get_uniq

ue_run_id

INSERT INTO gl_interface_control -- 1st create interface control rec(je_source_name, -- referenced by the journal import

status, -- always 'S'interface_run_id, -- must be uniqueset_of_books_id)

VALUES (v_srce_name, 'S', v_run_id, v_set_of_books_id);COMMIT;v_req_id := FND_REQUEST.SUBMIT_REQUEST (

'SQLGL', -- application'GLLEZL', -- journal import program'Period End Jrnls', -- description prefixes program name'', -- start timeFALSE, -- parent request-- Parameters for journal import programv_run_id, -- unique run id

v_set_of_books_id,-- set of books id'N', -- post_errors_to_suspense'', -- start date'', -- end date'N', -- create_summary_journals'N'); -- import dff with validation

IF v_req_id = 0 THEN/* Handle submission error */fnd_file.put_line(fnd_file.output,'Failed to Submit Period End Process Jou

rnal Import Request. Must be Submitted MANUALLY!');v_error_flag := TRUE;

ELSECOMMIT;

END IF;END submit_jrnl_import;

---- Mainline of MAIN--BEGIN-- get invoice date for report headingSELECT DISTINCT trx_dateINTO v_inv_dateFROM ra_customer_trxWHERE attribute1 = p_inv_run_idAND attribute3 = 'MARKET';

-- get required variables for journal importIF error_in_set_of_books THEN

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 17/19

v_error_message := '''Market Actuals'' Set of Books has not been setup!'CHR(13)CHR(10);END IF;IF error_in_jrnl_srce THENv_error_message := v_error_message'''CISO Period End'' Journal Source has

not been setup!'CHR(13)CHR(10);END IF;

IF error_in_market_acct THENv_error_message := v_error_message'''Market Clearing'' Cash Account has no

t been setup!'CHR(13)CHR(10);END IF;IF error_in_int_dev_acct THENv_error_message := v_error_message'''Invoice Deviation Interest'' Debit Ac

count and/or Routing Info and/or BAID has/have not been setup!'CHR(13)CHR(10);END IF;

-- if no errors then get interest deviation totals based on the invoice run ID parameter

IF v_error_message IS NULL THENget_int_dev_totals;ELSEfnd_file.put_line(fnd_file.output,v_error_message);v_error_flag := TRUE;

END IF;

IF NOT v_error_flag THENIF v_79x9s_exists THEN -- we got some 79x9 charge co

des on current invoices so let's process themprocess_79X9_data(v_ptb_run_id, v_ptb_tot);

END IF;IF NOT v_error_flag THEN

-- release amounts are smeared across different charge groups from other run IDs-- so we have to distribute those deviation interest $$ as well

FOR sf_rec IN cr_sf_release LOOP -- for each release from a previous shortfall

FOR inv_rec IN cr_79x9_inv_tot(sf_rec.inv_run_id) LOOP -- get the bill period end date for that invoice run

v_ptb_trade_date := TO_DATE(inv_rec.bp_edate, 'MM/DD/YYYY'); -- bp_edate of invoice run links to trade date in ciso_ptb_approved

END LOOP;

SELECT DISTINCT cpa.invoice_run_num -- only 1 invoicerun per trade date in this table

INTO v_ptb_run_idFROM ciso_ptb_approved cpaWHERE cpa.trade_date = v_ptb_trade_date;

-- now we have the release amount of interest deviation $$ so we can smear those $$ across charge groups

-- from the invoice run that created the original 79x9 ptbsprocess_79x9_data(v_ptb_run_id, sf_rec.release_amt);

END LOOP;END IF;

END IF;

-- if errors encountered then

IF v_error_flag THENretcode := 2;

ELSE

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 18/19

UPDATE ap_invoices -- set flag of 1 AP invoice sothis batch

SET attribute4 = 'Z' -- does not get processed again. Only 1 AP invoice

WHERE attribute1 = p_inv_run_id -- header record is set duringAR/AP invoice import

AND attribute4 = 'X'; -- so Invoice Run ID DFF lists

only 1 Run ID ini := SQL%rowcount; -- list of values

IF i <> 1 THENfnd_file.put_line(fnd_file.output,'Error Updating AP_INVOICE. Updated 'T

O_CHAR(i)' records!');retcode := 2; ROLLBACK;

ELSE-- go thru the charge group record structure and report how the deviation inte

rest charges are distributedi := 0; v_bp_rep_tot := 0; v_bp_pct_tot := 0; v_cg_tot_amt := 0; v_int_tot

:= 0;

WHILE i < v_tu_data_cnt LOOP -- if we have chg grp recordsi := i + 1;v_int_tot := v_int_tot + cg_data(i).int_dev_amt;control_report_body; -- then report each Charge Grou

pEND LOOP;

IF i = 0 THEN -- in case there isn't any datato report

control_report_header;fnd_file.new_line(fnd_file.output, 2);IF p_commit_flag = 'N' THENfnd_file.put_line(fnd_file.output,'No 7999/7989 PTBs for this Invoice

Run Num. Better luck next time and don''t forget to commit.');ROLLBACK;

ELSEfnd_file.put_line(fnd_file.output,'No 7999/7989 PTBs for this Invoice

Run Num. Better luck next time.');COMMIT;

END IF;ELSEcreate_gl_rec;fnd_file.put_line(fnd_file.output, v_last_message); -- provide PTB - Hol

d + Releases Total at end of report

-- if error creating journals then rollbackIF v_error_flag THENretcode := 2; ROLLBACK;

-- else if non-commit mode then rollbackELSIF p_commit_flag = 'N' THENROLLBACK;

-- else if we created journal records then submit the jrnl import programELSIF v_gl_insert THENsubmit_jrnl_import;IF v_error_flag THEN -- give a warning if an error occurs submitting

journal importretcode := 1;

ELSE

fnd_file.put_line(fnd_file.output,'Submitted Period End Process Journal Import Request');

END IF;

8/8/2019 Interest Dev Period End Package

http://slidepdf.com/reader/full/interest-dev-period-end-package 19/19

ELSE-- else just commit our work and go home for the evening and watch Wheel o

f Fortune. Don't forget to buy a vowel.COMMIT;

END IF;END IF; -- if i = 0 ( no data to report)

END IF; -- if error updating ap_invoices

END IF; -- if error in process_79x9 procedureEND main;

END CISO_TU_INTCALC_PEP_PKG;/