DBA Data[Home] [Help]

PACKAGE BODY: APPS.PSA_MFAR_ADJUSTMENTS

Source


1 PACKAGE BODY PSA_MFAR_ADJUSTMENTS AS
2 /* $Header: PSAMFADB.pls 120.22 2006/09/13 12:14:12 agovil ship $ */
3 
4 --
5 -- global variables
6 --
7 g_adjustment_id		ar_adjustments_all.adjustment_id%type;
8 g_set_of_books_id	ra_customer_trx_all.set_of_books_id%type;
9 g_customer_trx_id 	ra_cust_trx_line_gl_dist_all.customer_trx_id%type;
10 g_cust_trx_line_id	ra_cust_trx_line_gl_dist_all.customer_trx_line_id%type;
11 g_adj_ccid		ar_adjustments_all.code_combination_id%type;
12 g_adj_amount		ar_adjustments_all.amount%type;
13 g_adj_type		ar_adjustments_all.type%type;
14 g_run_id		NUMBER;
15 
16 --===========================FND_LOG.START=====================================
17 g_state_level NUMBER	:=	FND_LOG.LEVEL_STATEMENT;
18 g_proc_level  NUMBER	:=	FND_LOG.LEVEL_PROCEDURE;
19 g_event_level NUMBER	:=	FND_LOG.LEVEL_EVENT;
20 g_excep_level NUMBER	:=	FND_LOG.LEVEL_EXCEPTION;
21 g_error_level NUMBER	:=	FND_LOG.LEVEL_ERROR;
22 g_unexp_level NUMBER	:=	FND_LOG.LEVEL_UNEXPECTED;
23 g_path        VARCHAR2(50)  := 'PSA.PLSQL.PSAMFADB.PSA_MFAR_ADJUSTMENTS.';
24 --===========================FND_LOG.END=======================================
25 
26 --
27 -- Local Procedures
28 --
29 
30 
31 FUNCTION is_reverse_entry(l_index IN NUMBER) return BOOLEAN
32 IS
33 
34     -- ========================= FND LOG ===========================
35        l_full_path VARCHAR2(100) := g_path || 'is_reverse_entry.';
36     -- ========================= FND LOG ===========================
37 BEGIN
38   -- ========================= FND LOG ===========================
39      psa_utils.debug_other_string(g_state_level,l_full_path,' Inside is_reverse_entry');
40      psa_utils.debug_other_string(g_state_level,l_full_path,' PARAMETERS: ');
41      psa_utils.debug_other_string(g_state_level,l_full_path,' =========== ');
42      psa_utils.debug_other_string(g_state_level,l_full_path,' l_index           --> ' || l_index);
43   -- ========================= FND LOG ===========================
44 
45 
46     For I IN 1..ccid_info.count
47     LOOP
48   -- ========================= FND LOG ===========================
49      psa_utils.debug_other_string(g_state_level,l_full_path,' I -> ' || I);
50   -- ========================= FND LOG ===========================
51 
52 	IF (ccid_info(I).code_combination_id=ccid_info(l_index).code_combination_id) and
53          ccid_info(I).amount_due <> 0  and ccid_info(l_index).amount_due <> 0 and
54          (ccid_info(I).amount_due= -1* ccid_info(l_index).amount_due) and
55          (ccid_info(I).cust_trx_line_id=ccid_info(l_INDEX).cust_trx_line_id) then
56 
57 
58   -- ========================= FND LOG ===========================
59      psa_utils.debug_other_string(g_state_level,l_full_path,' Return->  TRUE');
60   -- ========================= FND LOG ===========================
61 
62            RETURN TRUE;
63         END IF;
64     END LOOP;
65   -- ========================= FND LOG ===========================
66      psa_utils.debug_other_string(g_state_level,l_full_path,' Return-> False');
67   -- ========================= FND LOG ===========================
68    RETURN FALSE;
69  EXCEPTION
70     WHEN OTHERS THEN
71          -- ========================= FND LOG ===========================
72             psa_utils.debug_other_string(g_excep_level,l_full_path,'EXCEPTION - OTHERS : ERROR IN PSA_MFAR_UTILS.is_ccid_exists');
73             psa_utils.debug_other_string(g_excep_level,l_full_path,'RETURN -> FALSE');
74             psa_utils.debug_other_string(g_excep_level,l_full_path, sqlcode || sqlerrm);
75             psa_utils.debug_unexpected_msg(l_full_path);
76          -- ========================= FND LOG ===========================
77    RETURN FALSE;
78 END   is_reverse_entry;
79 
80 
81 FUNCTION generate_adj_dist
82 		(errbuf                OUT NOCOPY  VARCHAR2,
83                  retcode               OUT NOCOPY  VARCHAR2,
84  		 p_error_message       OUT NOCOPY  VARCHAR2) RETURN BOOLEAN;
85 
86 FUNCTION create_distributions
87 		(errbuf                OUT NOCOPY VARCHAR2,
88 		 retcode               OUT NOCOPY VARCHAR2,
89 		 p_adjustment_id	IN NUMBER,
90 		 p_set_of_books_id	IN NUMBER,
91 		 p_run_id		IN NUMBER,
92 		 p_error_message       OUT NOCOPY VARCHAR2)
93 
94 RETURN BOOLEAN
95 IS
96 
97 	-- Bug 2982757
98 	-- Modified c_adjustments to pick code_combination_id
99 	-- from ar_distribtuions_all
100 
101 	Cursor c_adjustments Is
102                 Select  adj.customer_trx_id             cust_trx_id,
103                         adj.customer_trx_line_id        cust_trx_line_id,
104                         ard.code_combination_id         adj_ccid,
105                         adj.amount                      adj_amount,
106                         adj.type                        adj_type
107                   From  ar_adjustments                  adj,
108                         ar_distributions                ard
109                   Where adj.adjustment_id		= g_adjustment_id
110                     and adj.adjustment_id 		= ard.source_id
111                     and ard.source_table  		= 'ADJ'
112                     and ard.source_type   		IN ('ADJ', 'FINCHRG');
113 
114 	Cursor c_adj_dist Is
115 		Select	B.mf_receivables_ccid		mf_rec_ccid,
116 			C.mf_adjustment_ccid		mf_adj_ccid,
117 			C.prev_mf_adjustment_ccid       prev_mf_adj_ccid,
118 			C.prev_cust_trx_line_id		prev_cust_trx_line_id
119 		  From 	ra_cust_trx_line_gl_dist        A,
120 		  	psa_mf_trx_dist_all             B,
121 		  	psa_mf_adj_dist_all             C
122 		 Where 	C.adjustment_id			= g_adjustment_id
123 		 And	A.customer_trx_id		= g_customer_trx_id
124                  And    A.CUST_TRX_LINE_GL_DIST_ID      = B.CUST_TRX_LINE_GL_DIST_ID
125 		 And	B.cust_trx_line_gl_dist_id	= C.cust_trx_line_gl_dist_id
126 		 FOR    UPDATE;
127 
128 	l_adjustments_rec	c_adjustments%rowtype;
129 	l_adj_dist_rec		c_adj_dist%rowtype;
130 	l_temp_rec_ccid		gl_code_combinations.code_combination_id%type;
131 
132 	-- EXCEPTION
133 
134 	l_exception_error       VARCHAR2(2000);
135 	l_errbuf                VARCHAR2(100);
136 	l_retcode               VARCHAR2(100);
137 
138 	FLEX_COMPARE_ERROR      EXCEPTION;
139         GENERATE_ADJ_DIST_EXCEP EXCEPTION;
140 
141       -- ========================= FND LOG ===========================
142          l_full_path VARCHAR2(100);
143       -- ========================= FND LOG ===========================
144 BEGIN
145 
146       -- GSCC defaulting local variables
147       l_full_path :=  g_path || 'create_distributions';
148 
149       -- ========================= FND LOG ===========================
150          psa_utils.debug_other_string(g_state_level,l_full_path, ' START Create_distributions ');
151          psa_utils.debug_other_string(g_state_level,l_full_path, ' PARAMETERS ');
152          psa_utils.debug_other_string(g_state_level,l_full_path, ' ========== ');
153          psa_utils.debug_other_string(g_state_level,l_full_path, ' p_adjustment_id   -> ' || p_adjustment_id);
154          psa_utils.debug_other_string(g_state_level,l_full_path, ' p_set_of_books_id -> ' || p_set_of_books_id);
155          psa_utils.debug_other_string(g_state_level,l_full_path, ' p_run_id          -> ' || p_run_id );
156          psa_utils.debug_other_string(g_state_level,l_full_path, ' Starting the process ');
157       -- ========================= FND LOG ===========================
158 
159       retcode := 'F';
160 
161       -- ========================= FND LOG ===========================
162          psa_utils.debug_other_string(g_state_level,l_full_path, ' Setting retcode to -> ' || retcode);
163          psa_utils.debug_other_string(g_state_level,l_full_path, ' arp_global.sysparam.accounting_method -> '
164                                       || arp_global.sysparam.accounting_method );
165       -- ========================= FND LOG ===========================
166 
167       IF arp_global.sysparam.accounting_method = 'CASH' THEN
168          retcode := 'S';
169          -- ========================= FND LOG ===========================
170             psa_utils.debug_other_string(g_state_level,l_full_path, ' Retcode -> ' || retcode);
171             psa_utils.debug_other_string(g_state_level,l_full_path, ' RETURN  -> TRUE ');
172          -- ========================= FND LOG ===========================
173          RETURN TRUE;
174       END IF;
175 
176 	--
177 	-- Initialize global variables
178 	--
179 
180 	g_adjustment_id   := p_adjustment_id;
181 	g_set_of_books_id := p_set_of_books_id;
182 	g_run_id          := p_run_id;
183 
184 	OPEN	c_adjustments;
185 	FETCH	c_adjustments INTO l_adjustments_rec;
186 	CLOSE	c_adjustments;
187 
188 	g_customer_trx_id 	:= l_adjustments_rec.cust_trx_id;
189 	g_cust_trx_line_id	:= l_adjustments_rec.cust_trx_line_id;
190 	g_adj_ccid              := l_adjustments_rec.adj_ccid;
191 	g_adj_amount		:= l_adjustments_rec.adj_amount;
192 	g_adj_type              := l_adjustments_rec.adj_type;
193 
194       -- ========================= FND LOG ===========================
195          psa_utils.debug_other_string(g_state_level,l_full_path, ' g_customer_trx_id  -> ' || g_customer_trx_id);
196          psa_utils.debug_other_string(g_state_level,l_full_path, ' g_cust_trx_line_id -> ' || g_cust_trx_line_id);
197          psa_utils.debug_other_string(g_state_level,l_full_path, ' g_adj_ccid         -> ' || g_adj_ccid);
198          psa_utils.debug_other_string(g_state_level,l_full_path, ' g_adj_amount       -> ' || g_adj_amount);
199          psa_utils.debug_other_string(g_state_level,l_full_path, ' g_adj_type         -> ' || g_adj_type);
200       -- ========================= FND LOG ===========================
201 
202 	--
203 	-- Check if distributions already created
204 	--
205 
206 	OPEN  c_adj_dist;
207 	FETCH c_adj_dist INTO l_adj_dist_rec;
208 	CLOSE c_adj_dist;
209 
210       -- ========================= FND LOG ===========================
211          psa_utils.debug_other_string(g_state_level,l_full_path, ' l_adj_dist_rec.mf_adj_ccid  -> ' || l_adj_dist_rec.mf_adj_ccid );
212       -- ========================= FND LOG ===========================
213 
214 
215 	IF (l_adj_dist_rec.mf_adj_ccid Is Not Null)  THEN -- Adjustment Distributions already created
216 
217             -- ========================= FND LOG ===========================
218                psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside if - l_adj_dist_rec.mf_adj_ccid  -> is not null ');
219             -- ========================= FND LOG ===========================
220 
221 		OPEN c_adj_dist;
222 		LOOP
223 
224 		    FETCH c_adj_dist INTO l_adj_dist_rec;
225 		    EXIT WHEN c_adj_dist%NOTFOUND;
226 
227                 -- ========================= FND LOG ===========================
228                    psa_utils.debug_other_string(g_state_level,l_full_path, ' Calling PSA_MFAR_UTILS.OVERRIDE_SEGMENTS ');
229                 -- ========================= FND LOG ===========================
230 
231                 IF NOT ( PSA_MFAR_UTILS.OVERRIDE_SEGMENTS ( P_PRIMARY_CCID         => g_adj_ccid,
232                                                             P_OVERRIDE_CCID        => l_adj_dist_rec.mf_rec_ccid,
233                                                             P_SET_OF_BOOKS_ID      => g_set_of_books_id,
234                                                             P_TRX_TYPE             => 'ADJ',
235                                                             P_CCID                 => l_temp_rec_ccid))          -- OUT
236                 THEN
237                    -- ========================= FND LOG ===========================
238                       psa_utils.debug_other_string(g_state_level,l_full_path, ' Raising FLEX_COMPARE_ERROR');
239                    -- ========================= FND LOG ===========================
240 			 RAISE FLEX_COMPARE_ERROR;
241                 ELSE
242                    -- ========================= FND LOG ===========================
243                       psa_utils.debug_other_string(g_state_level,l_full_path, ' l_temp_rec_ccid --> ' || l_temp_rec_ccid);
244                    -- ========================= FND LOG ===========================
245 		    END IF;
246 
247                 -- ========================= FND LOG ===========================
248                    psa_utils.debug_other_string(g_state_level,l_full_path, ' l_temp_rec_ccid                 --> '
249                                                 || l_temp_rec_ccid );
250                    psa_utils.debug_other_string(g_state_level,l_full_path, ' l_adj_dist_rec.prev_mf_adj_ccid --> '
251                                                 || l_adj_dist_rec.prev_mf_adj_ccid);
252                    psa_utils.debug_other_string(g_state_level,l_full_path, ' nvl(g_cust_trx_line_id, -1)     --> '
253                                                 || nvl(g_cust_trx_line_id, -1));
254                    psa_utils.debug_other_string(g_state_level,l_full_path, ' nvl(l_adj_dist_rec.prev_cust_trx_line_id, -1) --> '
255                                                 || nvl(l_adj_dist_rec.prev_cust_trx_line_id, -1));
256                 -- ========================= FND LOG ===========================
257 
258 		    IF NOT (l_temp_rec_ccid = l_adj_dist_rec.prev_mf_adj_ccid) OR
259 		       NOT (nvl(g_cust_trx_line_id, -1) = nvl(l_adj_dist_rec.prev_cust_trx_line_id, -1)) THEN
260 
261                    -- ========================= FND LOG ===========================
265 		       DELETE FROM psa_mf_adj_dist_all
262                       psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside IF ');
263                    -- ========================= FND LOG ===========================
264 
266 		       WHERE adjustment_id = g_adjustment_id;
267 
268                    -- ========================= FND LOG ===========================
269                       psa_utils.debug_other_string(g_state_level,l_full_path, ' DELETE FROM psa_mf_adj_dist_all --> ' || SQL%ROWCOUNT);
270                    -- ========================= FND LOG ===========================
271 
272                    IF NOT (GENERATE_ADJ_DIST ( ERRBUF          => l_errbuf,               -- OUT
273                                                RETCODE         => l_retcode,              -- OUT
274                                                P_ERROR_MESSAGE => l_exception_error))     -- OUT
275                    THEN
276                       -- ========================= FND LOG ===========================
277                          psa_utils.debug_other_string(g_state_level,l_full_path, ' Raising GENERATE_ADJ_DIST_EXCEP');
278                       -- ========================= FND LOG ===========================
279                       RAISE GENERATE_ADJ_DIST_EXCEP;
280                    END IF;
281                    -- ========================= FND LOG ===========================
282                       psa_utils.debug_other_string(g_state_level,l_full_path, ' Exiting ');
283                    -- ========================= FND LOG ===========================
284 		       EXIT;
285 		    END IF;
286 		END LOOP;
287             CLOSE c_adj_dist;
288 
289 	ELSE						-- New adjustment distributions to be created
290 
291            -- ========================= FND LOG ===========================
292               psa_utils.debug_other_string(g_state_level,l_full_path, ' Else part - l_adj_dist_rec.mf_adj_ccid  -> is null ');
293            -- ========================= FND LOG ===========================
294             IF NOT (GENERATE_ADJ_DIST ( ERRBUF          => l_errbuf,               -- OUT
295                                         RETCODE         => l_retcode,              -- OUT
296                                         P_ERROR_MESSAGE => l_exception_error))     -- OUT
297             THEN
298                -- ========================= FND LOG ===========================
299                   psa_utils.debug_other_string(g_state_level,l_full_path, ' Raising GENERATE_ADJ_DIST_EXCEP ');
300                -- ========================= FND LOG ===========================
301                RAISE  GENERATE_ADJ_DIST_EXCEP;
302             ELSE
303                -- ========================= FND LOG ===========================
304                   psa_utils.debug_other_string(g_state_level,l_full_path, ' l_temp_rec_ccid --> ' || l_temp_rec_ccid);
305                -- ========================= FND LOG ===========================
306             END IF;
307 	END IF;
308 
309       -- ========================= FND LOG ===========================
310          psa_utils.debug_other_string(g_state_level,l_full_path, ' Setting retcode to --> ' || retcode);
311          psa_utils.debug_other_string(g_state_level,l_full_path, ' RETURN TRUE ');
312       -- ========================= FND LOG ===========================
313       retcode := 'S';
314       RETURN TRUE;
315 
316 EXCEPTION
317 	WHEN GENERATE_ADJ_DIST_EXCEP THEN
318 	  PSA_MFAR_UTILS.INSERT_DISTRIBUTIONS_LOG (g_run_id, 'ADJUSTMENT', g_customer_trx_id, g_adjustment_id, l_exception_error);
319 	  p_error_message := l_exception_error;
320 	  retcode := 'F';
321         -- ========================= FND LOG ===========================
322            psa_utils.debug_other_string(g_excep_level,l_full_path,l_exception_error);
323         -- ========================= FND LOG ===========================
324 	  RETURN FALSE;
325 
326 	WHEN FLEX_COMPARE_ERROR THEN
327 	  l_exception_error := 'EXCEPTION - FLEX_COMPARE_ERROR PACKAGE - PSA_MFAR_ADJUSTMENTS.CREATE_DISTRIBUTIONS - '||FND_MESSAGE.GET;
328 	  PSA_MFAR_UTILS.INSERT_DISTRIBUTIONS_LOG (g_run_id, 'ADJUSTMENT', g_customer_trx_id, g_adjustment_id, l_exception_error);
329 	  p_error_message := l_exception_error;
330 	  retcode := 'F';
331           -- ========================= FND LOG ===========================
332           psa_utils.debug_other_string(g_excep_level,l_full_path,l_exception_error);
333           -- ========================= FND LOG ===========================
334 	  RETURN FALSE;
335 
336 	WHEN OTHERS THEN
337 	  l_exception_error := 'EXCEPTION - OTHERS PACKAGE - PSA_MFAR_ADJUSTMENTS.CREATE_DISTRIBUTIONS - '||SQLCODE || ' - ' || SQLERRM;
338 	  PSA_MFAR_UTILS.INSERT_DISTRIBUTIONS_LOG (g_run_id, 'ADJUSTMENT', g_customer_trx_id, g_adjustment_id, l_exception_error);
339 	  p_error_message := l_exception_error;
340 	  retcode := 'F';
341         -- ========================= FND LOG ===========================
342            psa_utils.debug_other_string(g_excep_level,l_full_path,l_exception_error);
343            psa_utils.debug_unexpected_msg(l_full_path);
344         -- ========================= FND LOG ===========================
345 	  RETURN FALSE;
346 
347 END create_distributions;
348 
349 /******************************** GENERATE_ADJ_DEST ********************************/
350 
351 FUNCTION generate_adj_dist
352 		(errbuf                OUT NOCOPY  VARCHAR2,
353                  retcode               OUT NOCOPY  VARCHAR2,
354  		 p_error_message       OUT NOCOPY  VARCHAR2) RETURN BOOLEAN
355 IS
356 
357  /*
358    Bug 3140981.
359    code_combination_id included in c_mf_adjustments.
360  */
364 	Select	A.customer_trx_line_id		cust_trx_line_id,
361 	l_customer_trx_line_id  ra_cust_trx_line_gl_dist_all.customer_trx_line_id%TYPE;
362 
363 	Cursor c_mf_adjustments (c_sum_adr in number) Is
365 		A.line_type			line_type,
366 		B.cust_trx_line_gl_dist_id	cust_trx_line_gl_dist_id,
367 		C.mf_receivables_ccid		mf_rec_ccid,
368                 b.code_combination_id           code_combination_id,
369                 decode (c_sum_adr,
370 			0, D.amount_due_original,
371                         D.amount_due_remaining) amount_due,
372 		B.percent	-- panatara
373         From 	ra_customer_trx_lines           A,
374 		ra_cust_trx_line_gl_dist        B,
375 		psa_mf_trx_dist_all		C,
376 		psa_mf_balances_view		D
377 	Where 	A.customer_trx_id		= g_customer_trx_id
378             and A.customer_trx_line_id		= B.customer_trx_line_id
379             and B.account_class <> 'REC'
380             and	B.cust_trx_line_gl_dist_id	= C.cust_trx_line_gl_dist_id
381 	    and	C.cust_trx_line_gl_dist_id	= D.cust_trx_line_gl_dist_id
382             and B.customer_trx_line_id 		= DECODE(g_adj_type,
383 					  		 'LINE', nvl(l_customer_trx_line_id, B.customer_trx_line_id),
384 					  		 B.customer_trx_line_id);
385 
386 -- Bug 3140981: c_adj_gl_source to identify the adjustment type's GL Account source
387 
388     	CURSOR c_adj_gl_source IS
389                    SELECT gl_account_source
390                    FROM   ar_receivables_trx r, ar_adjustments a
391                    WHERE  r.receivables_trx_id = a.receivables_trx_id
392                    AND    a.adjustment_id = g_adjustment_id;
393 
394 
395 	l_mf_adjustments_rec		c_mf_adjustments%rowtype;
396 	p_ccid				psa_mf_adj_dist_all.mf_adjustment_ccid%type;
397 	l_temp_adj_type			ar_adjustments_all.type%type;
398 	l_flexbuild_error_reason	VARCHAR2(2000);
399 	l_total_amount_due		NUMBER;
400 	l_row_id		            VARCHAR2(100);
401 
402 	-- Variables for calculating amount/percent
403 
404 	l_amount			NUMBER;
405 	l_percent			NUMBER;
406 	l_amount_adjusted 	NUMBER;
407 	l_running_amount 		NUMBER;
408 	l_running_total_amount_due 	NUMBER;
409 
410 	-- EXCEPTION
411 	l_exception_error		VARCHAR2(2000);
412 	FLEX_BUILD_ERROR		EXCEPTION;
413 
414         sum_amt_due_rem         NUMBER;
415         l_adj_gl_source         ar_receivables_trx_all.gl_account_source%TYPE;
416         l_adj_ccid              NUMBER(15);
417 
418         l_distr_line_count      NUMBER;
419         l_count number := 0; /*for temporary table*/
420 
421 
422       -- ========================= FND LOG ===========================
423          l_full_path VARCHAR2(100);
424       -- ========================= FND LOG ===========================
425 
426 BEGIN
427 
428     -- GSCC defaulting local variables.
429     l_full_path  := g_path || 'generate_adj_dist';
430 
431     -- ========================= FND LOG ===========================
432        psa_utils.debug_other_string(g_state_level,l_full_path, ' START generate_adj_dist');
433        psa_utils.debug_other_string(g_state_level,l_full_path, ' Starting the process ');
434     -- ========================= FND LOG ===========================
435 
436     -- Bug 3140981:  store the Adjustment type's gl account source
437     OPEN c_adj_gl_source;
438     FETCH c_adj_gl_source INTO l_adj_gl_source;
439     CLOSE c_adj_gl_source;
440 
441     -- ========================= FND LOG ===========================
442        psa_utils.debug_other_string(g_state_level,l_full_path, ' l_adj_gl_source --> ' || l_adj_gl_source);
443     -- ========================= FND LOG ===========================
444 
445     Select decode (sum(mf_balances.amount_due_remaining), 0, sum(mf_balances.amount_due_original),
446                    sum(mf_balances.amount_due_remaining)) total_amount_due,
447                    sum(mf_balances.amount_due_remaining) sum_amt_due_rem
448     Into  l_total_amount_due, sum_amt_due_rem
449     From  ra_customer_trx_lines	      trx_lines,
450           ra_cust_trx_line_gl_dist	trx_dist,
451           psa_mf_balances_view		mf_balances
452     Where trx_lines.customer_trx_id             = g_customer_trx_id
453     And   trx_lines.customer_trx_line_id        = trx_dist.customer_trx_line_id
454     And   trx_dist.cust_trx_line_gl_dist_id     = mf_balances.cust_trx_line_gl_dist_id
455     And   trx_lines.customer_trx_line_id        = nvl(g_cust_trx_line_id, trx_dist.customer_trx_line_id)
456     And   trx_lines.line_type                   = decode(g_adj_type, 'LINE', 'LINE',
457                                                                      'TAX', FIND_TAX_FREIGHT_LINES('TAX', trx_lines.line_type),
458                                                                      'FREIGHT', FIND_TAX_FREIGHT_LINES('FREIGHT', trx_lines.line_type),
459                                                                      'INVOICE', trx_lines.line_type, trx_lines.line_type);
460 
461     -- ========================= FND LOG ===========================
462        psa_utils.debug_other_string(g_state_level,l_full_path, ' l_total_amount_due --> ' || l_total_amount_due);
463        psa_utils.debug_other_string(g_state_level,l_full_path, ' sum_amt_due_rem    --> ' || sum_amt_due_rem);
464     -- ========================= FND LOG ===========================
465 
466 	--
467 	-- Initailize variables for running total
468 	--
469 
470 	l_running_amount 	   := 0;
471 	l_running_total_amount_due := l_total_amount_due;
472 
473 	-- Bug 3739491 .. Start
474 	-- Select the customer_trx_line_id if adjustment type is LINE
475 
476 	IF (g_adj_type = 'LINE') THEN
477 
481 
478 		SELECT customer_trx_line_id INTO l_customer_trx_line_id
479 		FROM ar_adjustments
480 		WHERE adjustment_id = g_adjustment_id;
482 	END IF;
483 
484         IF (l_total_amount_due = 0) THEN
485 		IF (l_customer_trx_line_id IS NOT NULL) THEN
486         		l_distr_line_count := 1;
487         	ELSE
488 			SELECT	count(*) INTO    l_distr_line_count
489         		FROM 	ra_customer_trx_lines           A,
490 				ra_cust_trx_line_gl_dist        B,
491 				psa_mf_trx_dist_all		C,
492 				psa_mf_balances_view		D
493 			WHERE 	A.customer_trx_id		= g_customer_trx_id
494             		    and A.customer_trx_line_id		= B.customer_trx_line_id
495             		    and B.account_class <> 'REC'
496             		    and	B.cust_trx_line_gl_dist_id	= C.cust_trx_line_gl_dist_id
497 	    		    and	C.cust_trx_line_gl_dist_id	= D.cust_trx_line_gl_dist_id;
498 
499 
500 
501         	END IF;
502 	END IF;
503 
504 
505           -- ========================= FND LOG ===========================
506              psa_utils.debug_other_string(g_state_level,l_full_path, ' l_distr_line_count -> '||l_distr_line_count );
507           -- ========================= FND LOG ===========================
508 
509 	-- Bug 3739491 .. End
510 
511 
512     OPEN c_mf_adjustments(sum_amt_due_rem);
513     LOOP
514 
515 	   FETCH c_mf_adjustments INTO l_mf_adjustments_rec;
516 	   Exit When c_mf_adjustments%NOTFOUND;
517 
518            l_count := nvl(ccid_info.count,0) + 1;
519            ccid_info(l_count).cust_trx_line_id :=l_mf_adjustments_rec.cust_trx_line_id;
520 	     ccid_info(l_count).line_type := l_mf_adjustments_rec.line_type;
521 	     ccid_info(l_count).cust_trx_line_gl_dist_id := l_mf_adjustments_rec.cust_trx_line_gl_dist_id;
522            ccid_info(l_count).mf_rec_ccid := l_mf_adjustments_rec.mf_rec_ccid;
523            ccid_info(l_count).code_combination_id := l_mf_adjustments_rec.code_combination_id;
524            ccid_info(l_count).amount_due := l_mf_adjustments_rec.amount_due;
525            ccid_info(l_count).percent := l_mf_adjustments_rec.percent;
526 
527           -- ========================= FND LOG ===========================
528                     psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside count --> '|| l_count );
529           -- ========================= FND LOG ===========================
530 
531 
532     END LOOP;
533     CLOSE c_mf_adjustments;
534 
535 
536     FOR I IN 1..l_count
537     LOOP
538      IF is_reverse_entry(I) THEN
539 
540          l_amount  := 0;
541          l_percent := 0;
542 
543      -- ========================= FND LOG ===========================
544         psa_utils.debug_other_string(g_state_level,l_full_path, ' Reverse entry.');
545      -- ========================= FND LOG ===========================
546 
547 
548      ELSE
549 
550 
551 
552 
553          -- Bug 3140981: Identify the appropriate adjustment ccid based on gl account source.
554          -- For 'Revenue on Invoice', use ccid from ra_cust_trx_line_gl_dist_all
555          -- For other gl account source, use the ccid from ar_distributions directly.
556 
557         -- ========================= FND LOG ===========================
558            psa_utils.debug_other_string(g_state_level,l_full_path, ' ccid_info(i).code_combination_id --> '
559                                         || ccid_info(i).code_combination_id);
560            psa_utils.debug_other_string(g_state_level,l_full_path, ' g_adj_ccid --> ' || g_adj_ccid);
561         -- ========================= FND LOG ===========================
562 
563         IF l_adj_gl_source = 'REVENUE_ON_INVOICE' THEN
564            l_adj_ccid :=  ccid_info(i).code_combination_id;
565         ELSE
566            l_adj_ccid := g_adj_ccid;
567         END IF;
568 
569         -- ========================= FND LOG ===========================
570            psa_utils.debug_other_string(g_state_level,l_full_path, ' l_adj_ccid  --> ' || l_adj_ccid );
571         -- ========================= FND LOG ===========================
572 
573         IF NOT ( PSA_MFAR_UTILS.OVERRIDE_SEGMENTS ( P_PRIMARY_CCID         => l_adj_ccid,
574 	                                            P_OVERRIDE_CCID        =>  ccid_info(i).mf_rec_ccid,
575                                                     P_SET_OF_BOOKS_ID      => g_set_of_books_id,
576                                                     P_TRX_TYPE             => 'ADJ',
577                                                     P_CCID                 => p_ccid))                  -- OUT
578         THEN
579            -- ========================= FND LOG ===========================
580               psa_utils.debug_other_string(g_state_level,l_full_path, ' Raising FLEX_COMPARE_ERROR');
581            -- ========================= FND LOG ===========================
582            RAISE FLEX_BUILD_ERROR;
583         ELSE
584            -- ========================= FND LOG ===========================
585               psa_utils.debug_other_string(g_state_level,l_full_path, ' p_ccid --> ' || p_ccid);
586            -- ========================= FND LOG ===========================
587         END IF;
588 
589         -- ========================= FND LOG ===========================
590            psa_utils.debug_other_string(g_state_level,l_full_path, ' g_cust_trx_line_id  --> ' || g_cust_trx_line_id );
591         -- ========================= FND LOG ===========================
592 
593         IF  g_cust_trx_line_id Is NOT NULL THEN
594 
595             -- ========================= FND LOG ===========================
596                psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside if - g_cust_trx_line_id Is NOT NULL ' );
597             -- ========================= FND LOG ===========================
598 
599  		IF  (g_cust_trx_line_id =  ccid_info(i).cust_trx_line_id )
600 		AND  NOT (l_running_total_amount_due = 0 OR NVL(g_adj_amount, 0) = 0) THEN 	-- to avoid divide by zero error
601 
602                  -- ========================= FND LOG ===========================
603                     psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside Second if ' );
604                  -- ========================= FND LOG ===========================
605 
606 		    l_amount_adjusted 		:= g_adj_amount - l_running_amount;
607 		    l_amount 			:= ROUND((l_amount_adjusted* ccid_info(i).amount_due/l_running_total_amount_due), 2);
608 		    l_percent 			:= ROUND((l_amount/g_adj_amount*100), 4);
609 		    l_running_amount 		:= l_running_amount + l_amount;
610 		    l_running_total_amount_due 	:= l_running_total_amount_due -  ccid_info(i).amount_due;
611 
612 
613                  -- ========================= FND LOG ===========================
614                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_amount_adjusted --> ' || l_amount_adjusted );
615                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_amount          --> ' || l_amount );
616                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_percent         --> ' || l_percent );
617                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_running_amount  --> ' || l_running_amount );
618                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_running_total_amount_due --> ' || l_running_total_amount_due );
619                  -- ========================= FND LOG ===========================
620 	        ELSIF ((g_adj_amount - l_running_amount) <> 0) AND (l_running_total_amount_due = 0) THEN
621 			--l_amount := ROUND(g_adj_amount * l_mf_adjustments_rec.percent/100, 2);
622 			--l_percent:= l_mf_adjustments_rec.percent;
623                     l_amount  := ROUND(g_adj_amount/l_distr_line_count, 2);
624                     l_percent := ROUND((l_amount/g_adj_amount*100), 4);
625 		ELSE
626                  -- ========================= FND LOG ===========================
627                     psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside Second else ' );
628                  -- ========================= FND LOG ===========================
629 
630 		    l_amount  := 0;
631 		    l_percent := 0;
632 
633                  -- ========================= FND LOG ===========================
634                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_amount          --> ' || l_amount );
635                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_percent         --> ' || l_percent );
636                  -- ========================= FND LOG ===========================
637 		END IF;
638 	   ELSE
639 
640             -- ========================= FND LOG ===========================
641                psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside else - g_cust_trx_line_id Is NULL ' );
642             -- ========================= FND LOG ===========================
643 
644 		 Select DECODE(g_adj_type, 'LINE',    'LINE',
645 					   'TAX',     FIND_TAX_FREIGHT_LINES('TAX',      ccid_info(i).line_type),
646 					   'FREIGHT', FIND_TAX_FREIGHT_LINES('FREIGHT', ccid_info(i).line_type),
647 					   'INVOICE', ccid_info(i).line_type, ccid_info(i).line_type)
648 		  Into l_temp_adj_type From Dual;
649 
650             -- ========================= FND LOG ===========================
651                psa_utils.debug_other_string(g_state_level,l_full_path, ' l_temp_adj_type --> ' || l_temp_adj_type  );
652             -- ========================= FND LOG ===========================
653 
654 		IF  ccid_info(i).line_type = l_temp_adj_type
655 		AND NOT (l_running_total_amount_due = 0)
656 		AND NOT (g_adj_amount = 0) THEN 	-- to avoid divide by zero error, Bug 3739491
657 
658                 -- ========================= FND LOG ===========================
659                    psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside third if ' );
660                 -- ========================= FND LOG ===========================
661 
662 		    l_amount_adjusted 		:= g_adj_amount - l_running_amount;
663 		    l_amount 			:= ROUND((l_amount_adjusted*ccid_info(i).amount_due/l_running_total_amount_due), 2);
664 		    l_percent 			:= ROUND((l_amount/g_adj_amount*100), 4);
665 		    l_running_amount 		:= l_running_amount + l_amount;
666 		    l_running_total_amount_due 	:= l_running_total_amount_due - ccid_info(i).amount_due;
667 
668                  -- ========================= FND LOG ===========================
669                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_amount_adjusted --> ' || l_amount_adjusted );
670                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_amount          --> ' || l_amount );
671                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_percent         --> ' || l_percent );
672                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_running_amount  --> ' || l_running_amount );
673                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_running_total_amount_due --> ' || l_running_total_amount_due );
674                  -- ========================= FND LOG ===========================
675 	        ELSIF ((g_adj_amount - l_running_amount) <> 0) AND (l_running_total_amount_due = 0) THEN
676 			/*l_amount := ROUND(g_adj_amount * l_mf_adjustments_rec.percent/100, 2);
680                     psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside else if' );
677 			l_percent := l_mf_adjustments_rec.percent;*/
678 
679                  -- ========================= FND LOG ===========================
681                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_distr_line_count --> '|| l_distr_line_count );
682                      psa_utils.debug_other_string(g_state_level,l_full_path, 'g_adj_amount  --> '|| g_adj_amount);
683                  -- ========================= FND LOG ===========================
684 
685 
686                     l_amount  := ROUND(g_adj_amount/l_distr_line_count, 2);
687                     l_percent := ROUND((l_amount/g_adj_amount*100), 4);
688 		ELSE
689 
690                  -- ========================= FND LOG ===========================
691                     psa_utils.debug_other_string(g_state_level,l_full_path, ' Inside third else ' );
692                  -- ========================= FND LOG ===========================
693 
694                  l_percent := 0;
695 		     l_amount  := 0;
696 
697                  -- ========================= FND LOG ===========================
698                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_amount          --> ' || l_amount );
699                     psa_utils.debug_other_string(g_state_level,l_full_path, ' l_percent         --> ' || l_percent );
700                  -- ========================= FND LOG ===========================
701 		END IF;
702 	   END IF;
703 
704 
705 	   --
706 	   -- Insert into psa_mf_adj_dist_all
707 	   --
708 
709          -- ========================= FND LOG ===========================
710             psa_utils.debug_other_string(g_state_level,l_full_path, ' Calling PSA_MF_ADJ_DIST_ALL_PKG.INSERT_ROW ');
711          -- ========================= FND LOG ===========================
712 
713 	   PSA_MF_ADJ_DIST_ALL_PKG.INSERT_ROW
714 				   ( X_ROWID 			=> l_row_id,
715 				     X_ADJUSTMENT_ID		=> g_adjustment_id,
716 				     X_CUST_TRX_LINE_GL_DIST_ID	=> ccid_info(i).cust_trx_line_gl_dist_id,
717 				     X_MF_ADJUSTMENT_CCID	=> p_ccid,
718 				     X_AMOUNT			=> l_amount,
719 				     X_PERCENT			=> l_percent,
720 				     X_PREV_CUST_TRX_LINE_ID 	=> g_cust_trx_line_id,
721 				     X_PREV_MF_ADJUSTMENT_CCID  => p_ccid,
722 				     X_POSTING_CONTROL_ID 	=> -3,
723 				     X_MODE 			=> 'R' );
724 
725          -- ========================= FND LOG ===========================
726             psa_utils.debug_other_string(g_state_level,l_full_path, ' Calling PSA_MF_ADJ_DIST_ALL_PKG.INSERT_ROW --> ' || SQL%ROWCOUNT);
727          -- ========================= FND LOG ===========================
728 
729    END IF;
730    END LOOP;
731 
732 
733       -- ========================= FND LOG ===========================
734          psa_utils.debug_other_string(g_state_level,l_full_path, ' Setting retcode --> ' || retcode);
735          psa_utils.debug_other_string(g_state_level,l_full_path, ' RETURN TRUE ');
736       -- ========================= FND LOG ===========================
737 
738 	RETCODE := 'S';
739       RETURN TRUE;
740 
741 EXCEPTION
742 	WHEN FLEX_BUILD_ERROR THEN
743 	  l_exception_error := 'EXCEPTION - FLEX_BUILD_ERROR PACKAGE - PSA_MFAR_ADJUSTMENTS.GENERATE_ADJ_DIST '||FND_MESSAGE.GET;
744 	  PSA_MFAR_UTILS.INSERT_DISTRIBUTIONS_LOG (g_run_id, 'ADJUSTMENT', g_customer_trx_id, g_adjustment_id, l_exception_error);
745         p_error_message := l_exception_error;
746         RETCODE := 'F';
747         -- ========================= FND LOG ===========================
748            psa_utils.debug_other_string(g_excep_level,l_full_path,l_exception_error);
749         -- ========================= FND LOG ===========================
750         RETURN FALSE;
751 
752 	WHEN OTHERS THEN
753 	  l_exception_error := 'EXCEPTION - OTHERS PACKAGE - PSA_MFAR_ADJUSTMENTS.GENERATE_ADJ_DIST '||SQLCODE || ' - ' || SQLERRM;
754 	  PSA_MFAR_UTILS.INSERT_DISTRIBUTIONS_LOG (g_run_id, 'ADJUSTMENT', g_customer_trx_id, g_adjustment_id, l_exception_error);
755         p_error_message := l_exception_error;
756         RETCODE := 'F';
757         -- ========================= FND LOG ===========================
758            psa_utils.debug_other_string(g_excep_level,l_full_path,l_exception_error);
759            psa_utils.debug_unexpected_msg(l_full_path);
760         -- ========================= FND LOG ===========================
761         RETURN FALSE;
762 
763 END generate_adj_dist;
764 
765  /*********************************  FIND_TAX_FREIGHT_LINES   ************************************/
766 
767 FUNCTION FIND_TAX_FREIGHT_LINES (p_adjustment_type VARCHAR2,
768 				         p_line_type	   VARCHAR2 )
769 RETURN VARCHAR2 IS
770 
771    -- for bug 2756530
772    -- modify the cursor to check if line_type exist to improve performance
773 
774    CURSOR c_tax_freight
775    IS
776     SELECT line_type
777     FROM   ra_customer_trx_lines
778     WHERE  line_type = p_adjustment_type
779     AND    rownum = 1;
780 
781    l_line_type_rec c_tax_freight%rowtype;
782 
783    -- ========================= FND LOG ===========================
784       l_full_path VARCHAR2(100);
785    -- ========================= FND LOG ===========================
786 
787 BEGIN
788 
789     -- GSCC defaulting local variables.
790     l_full_path := g_path || 'find_tax_freight_lines';
791 
792     -- ========================= FND LOG ===========================
793        psa_utils.debug_other_string(g_state_level,l_full_path, ' START Tax_freight_lines ');
794        psa_utils.debug_other_string(g_state_level,l_full_path, ' Starting the process ');
795     -- ========================= FND LOG ===========================
796 
797 	OPEN  c_tax_freight;
798 	FETCH c_tax_freight INTO l_line_type_rec;
799 	CLOSE c_tax_freight;
800 
804 
801     -- ========================= FND LOG ===========================
802        psa_utils.debug_other_string(g_state_level,l_full_path, ' l_line_type_rec.line_type  --> ' || l_line_type_rec.line_type );
803     -- ========================= FND LOG ===========================
805 	IF l_line_type_rec.line_type IS NULL THEN
806          -- ========================= FND LOG ===========================
807             psa_utils.debug_other_string(g_state_level,l_full_path, ' RETURN --> ' || p_line_type);
808          -- ========================= FND LOG ===========================
809          RETURN p_line_type;
810 	ELSE
811          -- ========================= FND LOG ===========================
812             psa_utils.debug_other_string(g_state_level,l_full_path, ' RETURN --> ' || p_adjustment_type);
813          -- ========================= FND LOG ===========================
814          RETURN p_adjustment_type;
815 	END IF;
816 
817 END FIND_TAX_FREIGHT_LINES;
818 
819 END PSA_MFAR_ADJUSTMENTS;