DBA Data[Home] [Help]

PACKAGE BODY: APPS.OKL_STREAMS_UTIL

Source


1 PACKAGE BODY OKL_STREAMS_UTIL AS
2 /* $Header: OKLRSULB.pls 120.30.12020000.5 2013/02/22 23:00:56 rpillay ship $ */
3 
4   PROCEDURE LOG_MESSAGE(p_msgs_tbl            IN  log_msg_tbl,
5                         p_translate           IN  VARCHAR2 DEFAULT G_TRUE,
6                         p_file_name           IN  VARCHAR2,
7 			x_return_status       OUT NOCOPY VARCHAR2)
8   IS
9 
10    CURSOR okl_csr_fnd_msg(p_name IN VARCHAR2)
11    IS
12    SELECT MESSAGE_TEXT
13    FROM FND_NEW_MESSAGES
14    WHERE LANGUAGE_CODE = 'US'
15    AND MESSAGE_NAME LIKE p_name;
16 
17    uFile_type              FILE_TYPE;
18 
19   BEGIN
20        x_return_status := G_RET_STS_SUCCESS;
21         uFile_type := utl_file.fopen(Fnd_Profile.VALUE(G_LOG_DIR),p_file_name,'A');
22 
23 	FOR i IN 1..p_msgs_tbl.COUNT
24 	LOOP
25 
26 	  IF Fnd_Api.TO_BOOLEAN(p_translate)
27 	  THEN
28 	    FOR l_okl_csr_fnd_msg IN okl_csr_fnd_msg(p_msgs_tbl(i))
29 		LOOP
30           utl_file.put_line(uFile_type,l_okl_csr_fnd_msg.message_text);
31         END LOOP;
32       ELSE
33         utl_file.put_line(uFile_type,p_msgs_tbl(i));
34       END IF;
35 
36 	END LOOP;
37 
38       utl_file.fclose(uFile_type);
39 
40   EXCEPTION
41      WHEN utl_file.write_error THEN
42        IF (utl_file.is_open(uFile_type)) THEN
43          utl_file.fclose(uFile_type);
44        END IF;
45 
46      WHEN utl_file.invalid_path THEN
47        x_return_status := G_RET_STS_ERROR;
48 
49      WHEN utl_file.invalid_operation THEN
50        x_return_status := G_RET_STS_ERROR;
51        IF (utl_file.is_open(uFile_type)) THEN
52          utl_file.fclose(uFile_type);
53        END IF;
54      WHEN OTHERS THEN
55        x_return_status := G_RET_STS_UNEXP_ERROR;
56        IF (utl_file.is_open(uFile_type)) THEN
57          utl_file.fclose(uFile_type);
58        END IF;
59 
60   END LOG_MESSAGE;
61 
62   PROCEDURE LOG_MESSAGE(p_msg_name            IN     VARCHAR2,
63                         p_translate           IN  VARCHAR2 DEFAULT G_TRUE ,
64                         p_file_name            IN     VARCHAR2,
65 			x_return_status 	   OUT NOCOPY VARCHAR2)
66   IS
67 
68    CURSOR okl_csr_fnd_msg(p_name IN VARCHAR2)
69    IS
70    SELECT MESSAGE_TEXT
71    FROM FND_NEW_MESSAGES
72    WHERE LANGUAGE_CODE = 'US'
73    AND MESSAGE_NAME LIKE p_name;
74 
75    uFile_type              FILE_TYPE;
76 
77   BEGIN
78        x_return_status := G_RET_STS_SUCCESS;
79         uFile_type := utl_file.fopen(Fnd_Profile.VALUE(G_LOG_DIR),p_file_name,'A');
80 
81 	IF Fnd_Api.TO_BOOLEAN(p_translate)
82 	THEN
83 	  FOR l_okl_csr_fnd_msg IN okl_csr_fnd_msg(p_msg_name)
84       LOOP
85         utl_file.put_line(uFile_type,l_okl_csr_fnd_msg.message_text);
86       END LOOP;
87     ELSE
88       utl_file.put_line(uFile_type,p_msg_name);
89     END IF;
90 
91      utl_file.fclose(uFile_type);
92 
93   EXCEPTION
94      WHEN utl_file.write_error THEN
95        x_return_status := G_RET_STS_ERROR;
96        IF (utl_file.is_open(uFile_type)) THEN
97          utl_file.fclose(uFile_type);
98        END IF;
99 
100      WHEN utl_file.invalid_path THEN
101        x_return_status := G_RET_STS_ERROR;
102 
103      WHEN utl_file.invalid_operation THEN
104        x_return_status := G_RET_STS_ERROR;
105        IF (utl_file.is_open(uFile_type)) THEN
106          utl_file.fclose(uFile_type);
107        END IF;
108      WHEN OTHERS THEN
109        x_return_status := G_RET_STS_UNEXP_ERROR;
110        -- store SQL error message on message stack for caller
111        Okl_Api.SET_MESSAGE(p_app_name    => G_APP_NAME,
112                           p_msg_name     => G_UNEXPECTED_ERROR,
113                           p_token1       => G_SQLCODE_TOKEN,
114                           p_token1_value => SQLCODE,
115                           p_token2       => G_SQLERRM_TOKEN,
116                           p_token2_value => SQLERRM );
117        IF (utl_file.is_open(uFile_type)) THEN
118          utl_file.fclose(uFile_type);
119        END IF;
120 
121   END LOG_MESSAGE;
122 
123   PROCEDURE LOG_MESSAGE(p_msg_count            IN     NUMBER,
124                         p_file_name            IN     VARCHAR2,
125 			x_return_status        OUT NOCOPY VARCHAR2
126                        )
127   IS
128    l_error_msg VARCHAR2(4000) := '';
129    l_msg_text VARCHAR2(2000);
130    l_msg_count NUMBER;
131   l_new_line        VARCHAR2(10) := Fnd_Global.NEWLINE;
132   BEGIN
133        x_return_status := G_RET_STS_SUCCESS;
134 
135      -- GET THE MESSAGES FROM FND_MESSAGES
136      FOR i IN 1..p_msg_count
137      LOOP
138          Fnd_Msg_Pub.get(p_data => l_msg_text,
139                          p_msg_index_out => l_msg_count,
140                          p_encoded => G_FALSE,
141                          p_msg_index => Fnd_Msg_Pub.g_next);
142      	 IF i = 1 THEN
143 	       l_error_msg := l_msg_text;
144      	 ELSE
145 	       l_error_msg := l_error_msg || l_new_line || l_msg_text;
146     	 END IF;
147       END LOOP;
148 
149       LOG_MESSAGE(p_msg_name            => l_error_msg,
150                   p_translate            => G_FALSE,
151                   p_file_name            => p_file_name,
152 	          x_return_status 	 => x_return_status
153                  );
154 
155 
156   EXCEPTION
157      WHEN OTHERS THEN
158        x_return_status := G_RET_STS_UNEXP_ERROR;
159   END LOG_MESSAGE;
160 
161   PROCEDURE GET_FND_PROFILE_VALUE(p_name IN VARCHAR2,
162                                   x_value OUT NOCOPY VARCHAR2)
163   IS
164   BEGIN
165     x_value := Fnd_Profile.VALUE(p_name);
166   EXCEPTION
167      WHEN OTHERS THEN
168        x_value := p_name;
169   END;
170 -- BAKUCHIB Bug 2835092 start
171 --------------------------------------------------------------------------------
172 -- Start of Commnets
173 -- Badrinath Kuchibholta
174 -- Procedure Name       : round_streams_amount
175 -- Description          : Returns PL/SQL table of record rounded amounts
176 --                        of OKL_STRM_ELEMENTS type
177 -- Business Rules       : We sum the amounts given as I/P PL/SQL table first.
178 --                        And then we round the amounts using existing
179 --                        rounding rule and then sum them these up.
180 --                        If we find a difference between rounded amount
181 --                        and non-rounded amount then based on already existing
182 --                        rule we do adjustment to the first amount or
183 --                        last amount or the High value amount of the PL/SQL
184 --                        table of records.We then give the rounded values
185 --                        thru O/P PL/SQL table of records.
186 -- Parameters           : P_chr_id,
187 --                        p_selv_tbl of OKL_STRM_ELEMENTS type
188 --                        x_selv_tbl of OKL_STRM_ELEMENTS type
189 -- Version              : 1.0
190 -- History              : BAKUCHIB  31-JUL-2003 - 2835092 created
191 -- End of Commnets
192 --------------------------------------------------------------------------------
193 FUNCTION Round_Streams_Amount(p_api_version    IN  NUMBER,
194                                 p_init_msg_list  IN  VARCHAR2 DEFAULT Okl_Api.G_FALSE,
195                                 x_msg_count      OUT NOCOPY NUMBER,
196                                 x_msg_data       OUT NOCOPY VARCHAR2,
197                                 p_chr_id         IN okc_k_headers_b.id%TYPE,
198                                 p_selv_tbl       IN Okl_Streams_Pub.selv_tbl_type,
199                                 x_selv_tbl       OUT NOCOPY Okl_Streams_Pub.selv_tbl_type)
200   RETURN VARCHAR2 IS
201     l_api_name               CONSTANT VARCHAR2(30) := 'ROUND_STREAMS_AMOUNT';
202     g_col_name_token         CONSTANT  VARCHAR2(200) := Okl_Api.G_COL_NAME_TOKEN;
203     g_no_match_rec           CONSTANT VARCHAR2(30) := 'OKL_LLA_NO_MATCHING_RECORD';
204     g_invalid_value          CONSTANT VARCHAR2(200) := 'OKL_INVALID_VALUE ';
205     g_rnd_diff_lookup_type   CONSTANT fnd_lookups.lookup_type%TYPE := 'OKL_STRM_APPLY_ROUNDING_DIFF';
206     g_first_lookup_code      CONSTANT fnd_lookups.lookup_code%TYPE := 'ADD_TO_FIRST';
207     g_last_lookup_code       CONSTANT fnd_lookups.lookup_code%TYPE := 'ADD_TO_LAST';
208     g_high_lookup_code       CONSTANT fnd_lookups.lookup_code%TYPE := 'ADD_TO_HIGH';
209     x_return_status                   VARCHAR2(3)  := Okl_Api.G_RET_STS_SUCCESS;
210     ln_grter_amt_ind                  NUMBER := 0;
211     ln_grter_amt                      NUMBER := 0;
212     ln_tot_no_rnd_amount              NUMBER := 0;
213     ln_tot_rnd_amount                 NUMBER := 0;
214     ln_rounded_amount                 NUMBER := 0;
215     ln_rnd_diff_amount                NUMBER := 0;
216     ln_diff_amount                    NUMBER := 0;
217     ln_chr_id                         okc_k_headers_b.id%TYPE := p_chr_id;
218     ln_org_id                         okc_k_headers_b.authoring_org_id%TYPE;
219     lv_currency_code                  okc_k_headers_b.currency_code%TYPE;
220     lv_diff_lookup_code               fnd_lookups.lookup_code%TYPE;
221     g_stop_round_exp                  EXCEPTION;
222     ln_precision1                     NUMBER;
223     g_rounding_error                  EXCEPTION;
224     lv_return_status    VARCHAR2(3) := Okl_Api.G_RET_STS_SUCCESS;
225     --Added by kthiruva on 02-Dec-2004
226     --Bug 4048047 - Start of Changes
227     l_first_rec_index                 NUMBER := 0;
228     l_last_rec_index                  NUMBER := 0;
229     l_min_date                        DATE;
230     l_max_date                        DATE;
231     --Bug 4048047 - End of Changes
232 
233     -- Get the precision for the amounts to Round
234       -- Depending on the Currency code
235       CURSOR get_precision(p_currency_code OKC_K_HEADERS_B.CURRENCY_CODE%TYPE) IS
236       SELECT PRECISION
237       FROM fnd_currencies_vl
238       WHERE currency_code = p_currency_code
239       AND enabled_flag = 'Y'
240       AND NVL(start_date_active, SYSDATE) <= SYSDATE
241       AND NVL(end_date_active, SYSDATE) >= SYSDATE;
242 
243     l_selv_tbl                        Okl_Streams_Pub.selv_tbl_type := p_selv_tbl;
244     -- Get the Rule to Adjust the amount either
245     -- top/bottom/high_value of the PL/SQL tbl record
246     CURSOR get_rnd_diff_lookup(p_lookup_type  fnd_lookups.lookup_type%TYPE)
247     IS
248     SELECT b.stm_apply_rounding_difference
249     FROM fnd_lookups a,
250          OKL_SYS_ACCT_OPTS b
251     WHERE a.lookup_type = p_lookup_type
252     AND a.lookup_code = b.stm_apply_rounding_difference;
253     -- get the currency_code and Authoring_org_id
254     -- from okc_k_headers_b
255     CURSOR get_org_id(p_chr_id  okc_k_headers_b.id%TYPE)
256     IS
257     SELECT authoring_org_id,
258            currency_code
259     FROM okc_k_headers_b
260     WHERE id = p_chr_id;
261 
262     -- Local Function to round the amount depending on the
263     -- Currency code
264     FUNCTION round_amount(p_amount        IN  NUMBER,
265                           p_add_precision IN  NUMBER,
266                           x_amount        OUT NOCOPY NUMBER,
267                           p_currency_code IN okc_k_headers_b.currency_code%TYPE)
268     RETURN VARCHAR2 AS
269       lv_rounding_rule    okl_sys_acct_opts.ael_rounding_rule%TYPE;
270       ln_precision        NUMBER;
271       ln_amount           NUMBER := p_amount;
272       ln_rounded_amount   NUMBER := 0;
273       ln_pos_dot          NUMBER;
274       ln_to_add           NUMBER := 1;
275 --      lv_return_status    VARCHAR2(3) := OKL_API.G_RET_STS_SUCCESS;
276 --      g_rounding_error    EXCEPTION;
277       -- Get the Rule to Round the amount
278       CURSOR get_rounding_rule IS
279       SELECT stm_rounding_rule
280       FROM OKL_SYS_ACCT_OPTS;
281     BEGIN
282       -- Get the Rule to Round the amount
283       OPEN get_rounding_rule;
284       FETCH get_rounding_rule INTO lv_rounding_rule;
285       IF get_rounding_rule%NOTFOUND THEN
286         Okl_Api.set_message(p_app_name     => G_APP_NAME,
287                             p_msg_name     => g_no_match_rec,
288                             p_token1       => g_col_name_token,
289                             p_token1_value => 'Rounding Rule');
290         RAISE g_rounding_error;
291       END IF;
292       CLOSE get_rounding_rule;
293       -- Get the precision for the amounts to Round
294       -- Depending on the Currency code
295 
296 
297       OPEN get_precision(p_currency_code => p_currency_code);
298       FETCH get_precision INTO ln_precision;
299       IF get_precision%NOTFOUND THEN
300         Okl_Api.set_message(p_app_name     => G_APP_NAME,
301                             p_msg_name     => g_no_match_rec,
302                             p_token1       => g_col_name_token,
303                             p_token1_value => 'Currency Code');
304         RAISE g_rounding_error;
305       END IF;
306       CLOSE get_precision;
307       -- We now Processing the rounding depending
308       -- on the rule we derived from the above cursor
309       -- get rounding rule
310       IF (lv_rounding_rule = 'UP') THEN
311         ln_pos_dot := INSTR(TO_CHAR(ln_amount),'.') ;
312         IF (ln_pos_dot > 0) AND
313            (SUBSTR(ln_amount,ln_pos_dot+ln_precision+1 + p_add_precision,1) IS NOT NULL) THEN
314           FOR i IN 1..ln_precision + p_add_precision LOOP
315             ln_to_add := ln_to_add/10;
316           END LOOP;
317           ln_rounded_amount := ln_amount + ln_to_add;
318         ELSE
319           ln_rounded_amount := ln_amount;
320         END IF;
321         ln_rounded_amount := TRUNC(ln_rounded_amount,ln_precision + p_add_precision);
322       ELSIF lv_rounding_rule = 'DOWN' THEN
323         ln_rounded_amount := TRUNC(ln_amount, ln_precision + p_add_precision);
324       ELSIF lv_rounding_rule = 'NEAREST' THEN
325         ln_rounded_amount := ROUND(ln_amount, ln_precision + p_add_precision);
326       END IF;
327       x_amount := ln_rounded_amount;
328       RETURN lv_return_status;
329     EXCEPTION
330       WHEN g_rounding_error THEN
331         IF get_rounding_rule%ISOPEN THEN
332           CLOSE get_rounding_rule;
333         END IF;
334         IF get_precision%ISOPEN THEN
335           CLOSE get_precision;
336         END IF;
337         lv_return_status := Okl_Api.G_RET_STS_ERROR;
338         RETURN lv_return_status;
339       WHEN OTHERS THEN
340         IF get_rounding_rule%ISOPEN THEN
341 
342           CLOSE get_rounding_rule;
343         END IF;
344         IF get_precision%ISOPEN THEN
345           CLOSE get_precision;
346         END IF;
347         lv_return_status := Okl_Api.G_RET_STS_ERROR;
348         RETURN lv_return_status;
349     END round_amount;
350   BEGIN
351 
352     x_return_status := Okl_Api.G_RET_STS_SUCCESS;
353     -- Call start_activity to create savepoint, check compatibility
354     -- and initialize message list
355     x_return_status := Okl_Api.START_ACTIVITY (
356                                l_api_name
357                                ,p_init_msg_list
358                                ,'_PVT'
359                                ,x_return_status);
360     -- Check if activity started successfully
361     IF (x_return_status = Okl_Api.G_RET_STS_UNEXP_ERROR) THEN
362        RAISE Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR;
363     ELSIF (x_return_status = Okl_Api.G_RET_STS_ERROR) THEN
364        RAISE Okl_Api.G_EXCEPTION_ERROR;
365     END IF;
366 
367     IF l_selv_tbl.COUNT > 0 THEN
368       OPEN  get_org_id(p_chr_id => ln_chr_id);
369       FETCH get_org_id INTO ln_org_id,
370                             lv_currency_code;
371       IF get_org_id%NOTFOUND THEN
372         Okl_Api.set_message(p_app_name     => G_APP_NAME,
373                             p_msg_name     => g_no_match_rec,
374                             p_token1       => g_col_name_token,
375                             p_token1_value => 'Contract id');
376         RAISE g_stop_round_exp;
377       END IF;
378       CLOSE get_org_id;
379       -- we need to set the context since the records in
380       -- OKL_SYS_ACCT_OPTS table are stored with regards to the context
381       x_return_status      := Okl_Api.G_RET_STS_SUCCESS;
382       -- IF we have diff btw rounding amounts
383       -- now we decide by the below select stmt
384       -- As to where we need to adjust the amount
385       OPEN  get_rnd_diff_lookup(p_lookup_type => g_rnd_diff_lookup_type);
386       FETCH get_rnd_diff_lookup INTO lv_diff_lookup_code;
387       IF get_rnd_diff_lookup%NOTFOUND THEN
388         Okl_Api.set_message(p_app_name     => G_APP_NAME,
389                             p_msg_name     => g_no_match_rec,
390                             p_token1       => g_col_name_token,
391                             p_token1_value => 'Rounding Diff Lookup');
392         RAISE g_stop_round_exp;
393       END IF;
394       CLOSE get_rnd_diff_lookup;
395 
396       -- Modified by kthiruva on 02-Dec-2004
397       -- Bug 4048047 - Start of Changes
398       -- If the Apply Rounding Diff is ADD_TO_FIRST or ADD_TO_LAST then then the first and the last
399       -- stream element records need to be determined.The first and last stream element record for
400       -- a particular stream header is identified by checking for the min and max stream element date.
401 
402       IF lv_diff_lookup_code = g_first_lookup_code THEN
403          l_first_rec_index := l_selv_tbl.FIRST;
404          l_min_date        := l_selv_tbl(l_selv_tbl.FIRST).stream_element_date;
405       ELSIF lv_diff_lookup_code = g_last_lookup_Code THEN
406          l_last_rec_index  := l_selv_tbl.LAST;
407          l_max_date        := l_Selv_tbl(l_selv_tbl.LAST).stream_element_date;
408       END IF;
409       -- Bug 4048047 - End of Changes
410 
411       -- Need to handle the -ve amount seprately
412       -- since 0 is allways greater than -ve amounts
413       IF lv_diff_lookup_code = g_high_lookup_code THEN
414         IF SIGN(l_selv_tbl(l_selv_tbl.FIRST).amount) = -1 THEN
415           ln_grter_amt :=  l_selv_tbl(l_selv_tbl.FIRST).amount;
416         END IF;
417       END IF;
418 
419       -- Now we scan the Stream element PL/SQL table of records
420       -- Sum up all the amounts
421       FOR i IN l_selv_tbl.FIRST..l_selv_tbl.LAST LOOP
422         ln_tot_no_rnd_amount := ln_tot_no_rnd_amount + l_selv_tbl(i).amount;
423         IF l_selv_tbl(i).amount > ln_grter_amt THEN
424           ln_grter_amt := l_selv_tbl(i).amount;
425           ln_grter_amt_ind := i;
426         END IF;
427         -- Added by kthiruva on 02-Dec-2004
428         -- Bug 4048047 - Start of Changes
429         -- Check to see if there is a stream element with a stream_element_date less than l_min_date.
430         -- If so, the l_first_rec_index is reset.
431         IF trunc(l_selv_tbl(i).stream_element_date) < trunc(l_min_date) THEN
432            l_min_date        := l_selv_tbl(i).stream_element_date;
433            l_first_rec_index := i;
434         END IF;
435         -- Check to see if there is a stream element with a stream_element_date greater than l_max_date.
436         -- If so, the l_last_rec_index is reset.
437         IF trunc(l_selv_tbl(i).stream_element_date) > trunc(l_max_date) THEN
438            l_max_date       := l_selv_tbl(i).stream_element_date;
439            l_last_rec_index := i;
440         END IF;
441         -- Bug 4048047 - End of Changes
442       END LOOP;
443 
444       -- Get the precision for the amounts to Round
445       -- Depending on the Currency code
446 
447       OPEN get_precision(p_currency_code => lv_currency_code);
448       FETCH get_precision INTO ln_precision1;
449       IF get_precision%NOTFOUND THEN
450         Okl_Api.set_message(p_app_name     => G_APP_NAME,
451                             p_msg_name     => g_no_match_rec,
452                             p_token1       => g_col_name_token,
453                             p_token1_value => 'Currency Code');
454         RAISE g_rounding_error;
455       END IF;
456       CLOSE get_precision;
457 
458 
459 --sgorantl(bug#3797982) start change
460       ln_tot_no_rnd_amount := ROUND(ln_tot_no_rnd_amount,ln_precision1);
461 --sgorantl(bug#3797982) end change
462 
463       -- If the first value is 0 and ln_grter_amt = 0
464       -- then we return the first record for adjustment
465       IF lv_diff_lookup_code = g_high_lookup_code THEN
466         IF ln_grter_amt_ind = 0 THEN
467           ln_grter_amt := l_selv_tbl(l_selv_tbl.FIRST).amount;
468           ln_grter_amt_ind := l_selv_tbl.FIRST;
469         END IF;
470       END IF;
471       -- Now we scan the Stream element PL/SQL table of records
472       -- Sum up all the amounts after rounding depending on currency_code
473       FOR i IN l_selv_tbl.FIRST..l_selv_tbl.LAST LOOP
474         x_return_status := round_amount(p_currency_code => lv_currency_code,
475                                         p_add_precision => 0,
476                                         p_amount        => l_selv_tbl(i).amount,
477                                         x_amount        => ln_rounded_amount);
478         IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
479           EXIT WHEN (x_return_status <> Okl_Api.G_RET_STS_SUCCESS);
480         END IF;
481         ln_tot_rnd_amount := ln_tot_rnd_amount + ln_rounded_amount;
482         -- We re-populate the rounded amount into the PL/SQL table of records
483         -- So that we can give the same as output if there is diff
484         -- btw ln_tot_no_rnd_amount and ln_tot_rnd_amount
485         l_selv_tbl(i).amount := ln_rounded_amount;
486       END LOOP;
487       IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
488         RAISE g_stop_round_exp;
489       END IF;
490       -- Now we will see the diff btw ln_tot_no_rnd_amount and ln_tot_rnd_amount
491       -- IF there is diff then as done below
492       IF ln_tot_no_rnd_amount <> ln_tot_rnd_amount THEN
493         -- If the diff correction rule is First then
494 
495         IF lv_diff_lookup_code = g_first_lookup_code THEN
496           -- If the Diff Amount is +ve then we add to the first record of
497           -- pl/sql record of the table
498           ln_diff_amount := ln_tot_no_rnd_amount - ln_tot_rnd_amount;
499           -- Since the pl/sql table of records come in as not rounded
500           -- and in the above we round the pl/sql table of records
501           -- and since we need to do the corrections only on the rounded amont
502           -- hence we need to round the ln_diff_amount variable also.
503           x_return_status := round_amount(p_currency_code => lv_currency_code,
504                                           p_add_precision => 0,
505                                           p_amount        => ln_diff_amount,
506                                           x_amount        => ln_rnd_diff_amount);
507           IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
508             RAISE g_stop_round_exp;
509           END IF;
510           IF SIGN(ln_rnd_diff_amount) = 1 THEN
511             -- Modified by kthiruva on 02-Dec-2004
512             -- Bug 4048047 - Start of Changes
513             l_selv_tbl(l_first_rec_index).amount := l_selv_tbl(l_first_rec_index).amount + ln_rnd_diff_amount;
514             --Bug 4048047 - End of Changes
515           -- If the Diff Amount is -ve then we substract from the first record of
516           -- pl/sql record of the table
517           ELSIF SIGN(ln_rnd_diff_amount) = -1 THEN
518             ln_diff_amount := ln_tot_rnd_amount- ln_tot_no_rnd_amount ;
519             -- Since the pl/sql table of records come in as not rounded
520             -- and in the above we round the pl/sql table of records
521             -- and since we need to do the corrections only on the rounded amont
522             -- hence we need to round the ln_diff_amount variable also.
523             x_return_status := round_amount(p_currency_code => lv_currency_code,
524                                             p_add_precision => 0,
525                                             p_amount        => ln_diff_amount,
526                                             x_amount        => ln_rnd_diff_amount);
527             IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
528               RAISE g_stop_round_exp;
529             END IF;
530             -- Modified by kthiruva on 02-Dec-2004
531             -- Bug 4048047 - Start of Changes
532             l_selv_tbl(l_first_rec_index).amount := l_selv_tbl(l_first_rec_index).amount - (ln_rnd_diff_amount);
533             -- Bug 4048047 - End Of Changes
534           END IF;
535         -- If the diff correction rule is Last then
536         ELSIF lv_diff_lookup_code = g_last_lookup_code THEN
537           -- If the Diff Amount is +ve then we add to the last record of
538           -- pl/sql record of the table
539           ln_diff_amount := ln_tot_no_rnd_amount - ln_tot_rnd_amount;
540           -- Since the pl/sql table of records come in as not rounded
541           -- and in the above we round the pl/sql table of records
542           -- and since we need to do the corrections only on the rounded amont
543           -- hence we need to round the ln_diff_amount variable also.
544           x_return_status := round_amount(p_currency_code => lv_currency_code,
545                                           p_add_precision => 0,
546                                           p_amount        => ln_diff_amount,
547                                           x_amount        => ln_rnd_diff_amount);
548           IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
549             RAISE g_stop_round_exp;
550           END IF;
551           IF SIGN(ln_rnd_diff_amount) = 1 THEN
552             -- Modified by kthiruva on 02-Dec-2004
553             -- Bug 4048047 - Start of Changes
554             l_selv_tbl(l_last_rec_index).amount := l_selv_tbl(l_last_rec_index).amount + (ln_rnd_diff_amount);
555             -- Bug 4048047 - End of Changes
556           -- If the Diff Amount is -ve then we substract from the last record of
557           -- pl/sql record of the table
558           ELSIF SIGN(ln_rnd_diff_amount) = -1 THEN
559             ln_diff_amount := ln_tot_rnd_amount- ln_tot_no_rnd_amount ;
560             -- Since the pl/sql table of records come in as not rounded
561             -- and in the above we round the pl/sql table of records
562             -- and since we need to do the corrections only on the rounded amont
563             -- hence we need to round the ln_diff_amount variable also.
564             x_return_status := round_amount(p_currency_code => lv_currency_code,
565                                             p_add_precision => 0,
566                                             p_amount        => ln_diff_amount,
567                                             x_amount        => ln_rnd_diff_amount);
568             IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
569               RAISE g_stop_round_exp;
570             END IF;
571             -- Modified by kthiruva on 02-Dec-2004
572             -- Bug 4048047 - Start of Changes
573             --Modified by kthiruva for Bug 4730902 on 22-Nov-2005.
574             --The amount needs to be subtracted when the diff is negative
575             l_selv_tbl(l_last_rec_index).amount := l_selv_tbl(l_last_rec_index).amount - (ln_rnd_diff_amount);
576             -- Bug 4048047 - End of Changes
577           END IF;
578         -- If the diff correction rule is High Amount then
579         ELSIF lv_diff_lookup_code = g_high_lookup_code  THEN
580           ln_diff_amount := ln_tot_no_rnd_amount - ln_tot_rnd_amount;
581           -- Since the pl/sql table of records come in as not rounded
582           -- and in the above we round the pl/sql table of records
583           -- and since we need to do the corrections only on the rounded amont
584           -- hence we need to round the ln_diff_amount variable also.
585           x_return_status := round_amount(p_currency_code => lv_currency_code,
586                                           p_add_precision => 0,
587                                           p_amount        => ln_diff_amount,
588                                           x_amount        => ln_rnd_diff_amount);
589           IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
590             RAISE g_stop_round_exp;
591           END IF;
592           -- If the Diff Amount is +ve then we add to the High amount record of
593           -- pl/sql record of the table
594           IF SIGN(ln_rnd_diff_amount) = 1 THEN
595             l_selv_tbl(ln_grter_amt_ind).amount := l_selv_tbl(ln_grter_amt_ind).amount + (ln_rnd_diff_amount);
596           -- If the Diff Amount is -ve then we substract from the High amount record of
597           -- pl/sql record of the table
598           ELSIF SIGN(ln_rnd_diff_amount) = -1 THEN
599             ln_diff_amount := ln_tot_rnd_amount- ln_tot_no_rnd_amount ;
600             -- Since the pl/sql table of records come in as not rounded
601             -- and in the above we round the pl/sql table of records
602             -- and since we need to do the corrections only on the rounded amont
603             -- hence we need to round the ln_diff_amount variable also.
604             x_return_status := round_amount(p_currency_code => lv_currency_code,
605                                             p_add_precision => 0,
606                                             p_amount        => ln_diff_amount,
607                                             x_amount        => ln_rnd_diff_amount);
608 
609             IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
610               RAISE g_stop_round_exp;
611             END IF;
612             l_selv_tbl(ln_grter_amt_ind).amount := l_selv_tbl(ln_grter_amt_ind).amount - (ln_rnd_diff_amount);
613           END IF;
614         END IF;
615         -- There is diff so we set the o/p record with modified record derived above
616         x_selv_tbl := l_selv_tbl;
617       ELSIF ln_tot_no_rnd_amount = ln_tot_rnd_amount THEN
618         -- There is no diff so we set the i/p record back o/p record
619         --Modified by dpsingh on 02-Feb-2006.          x_selv_tbl := p_selv_tbl;
620          --Even when there is no rounding diff, the rounded table l_selv_tbl should only be returned
621          --The unrounded table is being returned incorrectly
622          --Bug 4559800(H) - Start of Changes
623          x_selv_tbl := l_selv_tbl;
624          --Bug 4559800(H) - End of Changes
625       END IF;
626     ELSE
627       Okl_Api.set_message(p_app_name      => G_APP_NAME,
628                           p_msg_name      => G_INVALID_VALUE,
629                           p_token1        => G_COL_NAME_TOKEN,
630                           p_token1_value  => 'p_selv_tbl');
631       RAISE g_stop_round_exp;
632     END IF;
633 
634     Okl_Api.END_ACTIVITY (x_msg_count,
635                           x_msg_data );
636     RETURN x_return_status;
637   EXCEPTION
638      WHEN g_rounding_error THEN
639         IF get_precision%ISOPEN THEN
640           CLOSE get_precision;
641         END IF;
642         lv_return_status := Okl_Api.G_RET_STS_ERROR;
643         RETURN lv_return_status;
644     WHEN g_stop_round_exp THEN
645       IF get_rnd_diff_lookup%ISOPEN THEN
646         CLOSE get_rnd_diff_lookup;
647       END IF;
648       IF get_org_id%ISOPEN THEN
649         CLOSE get_org_id;
650       END IF;
651       x_return_status := Okl_Api.HANDLE_EXCEPTIONS(
652                                  l_api_name,
653                                  G_PKG_NAME,
654                                  'OKL_API.G_RET_STS_ERROR',
655                                  x_msg_count,
656                                  x_msg_data,
657                                  '_PVT');
658       RETURN x_return_status;
659     WHEN OTHERS THEN
660       IF get_rnd_diff_lookup%ISOPEN THEN
661         CLOSE get_rnd_diff_lookup;
662       END IF;
663       IF get_org_id%ISOPEN THEN
664         CLOSE get_org_id;
665       END IF;
666       x_return_status :=Okl_Api.HANDLE_EXCEPTIONS(
667                                 l_api_name,
668                                 G_PKG_NAME,
669                                 'OTHERS',
670                                 x_msg_count,
671                                 x_msg_data,
672                                 '_PVT');
673       RETURN x_return_status;
674   END Round_Streams_Amount;
675 -- BAKUCHIB Bug 2835092 End
676 
677 
678 PROCEDURE get_primary_stream_type
679 (
680  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
681  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
682  x_return_status		OUT NOCOPY VARCHAR2,
683  x_primary_sty_id 		OUT NOCOPY okl_strm_type_b.ID%TYPE
684 )
685 
686 IS
687 
688 CURSOR cntrct_csr (l_khr_id NUMBER)IS
689 SELECT pdt_id, start_date
690 FROM     okl_k_headers_full_v
691 WHERE id = l_khr_id;
692 
693 CURSOR pry_sty_csr (l_pdt_id NUMBER, l_contract_start_date DATE) IS
694 SELECT PRIMARY_STY_ID
695 FROM   OKL_STRM_TMPT_LINES_UV STL
696 WHERE STL.PRIMARY_YN = 'Y'
697 AND STL.PDT_ID = l_pdt_id
698 AND    (STL.START_DATE <= l_contract_start_date)
699 AND    (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
700 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose;
701 
702   l_product_id 			  					NUMBER;
703   l_contract_start_date 	DATE;
704   l_primary_sty_id 			  	NUMBER;
705 
706   -- Santonyr Bug 4056364
707 
708   l_primary_sty_purpose_meaning VARCHAR2(4000);
709 
710 
711 BEGIN
712 
713   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
714 
715 
716   OPEN cntrct_csr (p_khr_id);
717   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
718   CLOSE cntrct_csr;
719 
720 
721 
722   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
723 
724     OPEN pry_sty_csr (l_product_id, l_contract_start_date);
725     FETCH pry_sty_csr INTO l_primary_sty_id;
726       IF  pry_sty_csr%NOTFOUND THEN
727 
728 -- Santonyr Bug 4056364
729 -- Bug 4064253
730 
731             l_primary_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
732             			('OKL_STREAM_TYPE_PURPOSE', p_primary_sty_purpose);
733 
734             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
735                                 p_msg_name      => 'OKL_NO_PRY_STY_FOUND',
736                                 p_token1        => 'PURPOSE',
737                                 p_token1_value  => l_primary_sty_purpose_meaning);
738             RAISE Okl_Api.G_EXCEPTION_ERROR;
739 	 END IF;
740      CLOSE pry_sty_csr;
741 
742   ELSE
743 
744 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
745                           p_msg_name     => 'OKL_NO_PDT_FOUND');
746             RAISE Okl_Api.G_EXCEPTION_ERROR;
747 
748   END IF;
749 
750   x_primary_sty_id := l_primary_sty_id;
751 
752   EXCEPTION
753   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
754      IF cntrct_csr%ISOPEN THEN
755 	    CLOSE cntrct_csr;
756 	 END IF;
757      IF pry_sty_csr%ISOPEN THEN
758 	    CLOSE pry_sty_csr;
759 	 END IF;
760      x_return_status := Okl_Api.G_RET_STS_ERROR ;
761 
762   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
763      IF cntrct_csr%ISOPEN THEN
764 	    CLOSE cntrct_csr;
765 	 END IF;
766      IF pry_sty_csr%ISOPEN THEN
767 	    CLOSE pry_sty_csr;
768 	 END IF;
769      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
770 
771   WHEN OTHERS THEN
772      IF cntrct_csr%ISOPEN THEN
773 	    CLOSE cntrct_csr;
774 	 END IF;
775      IF pry_sty_csr%ISOPEN THEN
776 	    CLOSE pry_sty_csr;
777 	 END IF;
778      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
779       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
780 
781 END get_primary_stream_type;
782 
783 PROCEDURE get_primary_stream_type
784 (
785  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
786  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
787  x_return_status		OUT NOCOPY VARCHAR2,
788  x_primary_sty_id 		OUT NOCOPY okl_strm_type_id_tbl_type
789 )
790 
791 IS
792 
793 CURSOR cntrct_csr (l_khr_id NUMBER)IS
794 SELECT pdt_id, start_date
795 FROM     okl_k_headers_full_v
796 WHERE id = l_khr_id;
797 
798 CURSOR pry_sty_csr (l_pdt_id NUMBER, l_contract_start_date DATE) IS
799 SELECT PRIMARY_STY_ID
800 FROM   OKL_STRM_TMPT_LINES_UV STL
801 WHERE STL.PRIMARY_YN = 'Y'
802 AND STL.PDT_ID = l_pdt_id
803 AND    (STL.START_DATE <= l_contract_start_date)
804 AND    (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
805 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose;
806 
807   l_product_id 			  					NUMBER;
808   l_contract_start_date 	DATE;
809   l_primary_sty_id 			  	NUMBER;
810 -- Santonyr Bug 4056364
811   l_primary_sty_purpose_meaning VARCHAR2(4000);
812 
813 BEGIN
814 
815   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
816 
817 
818   OPEN cntrct_csr (p_khr_id);
819   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
820   CLOSE cntrct_csr;
821 
822 
823 
824   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
825 
826     OPEN pry_sty_csr (l_product_id, l_contract_start_date);
827     FETCH pry_sty_csr INTO l_primary_sty_id;
828       IF  pry_sty_csr%NOTFOUND THEN
829             l_primary_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
830             			('OKL_STREAM_TYPE_PURPOSE', p_primary_sty_purpose);
831       -- Bug 4064253
832 
833             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
834                                 p_msg_name      => 'OKL_NO_PRY_STY_FOUND',
835                                 p_token1        => 'PURPOSE',
836                                 p_token1_value  => l_primary_sty_purpose_meaning);
837             RAISE Okl_Api.G_EXCEPTION_ERROR;
838 	 END IF;
839      CLOSE pry_sty_csr;
840 
841   ELSE
842 
843 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
844                           p_msg_name     => 'OKL_NO_PDT_FOUND');
845             RAISE Okl_Api.G_EXCEPTION_ERROR;
846 
847   END IF;
848 
849   --x_primary_sty_id := l_primary_sty_id;
850 
851   EXCEPTION
852   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
853      IF cntrct_csr%ISOPEN THEN
854 	    CLOSE cntrct_csr;
855 	 END IF;
856      IF pry_sty_csr%ISOPEN THEN
857 	    CLOSE pry_sty_csr;
858 	 END IF;
859      x_return_status := Okl_Api.G_RET_STS_ERROR ;
860 
861   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
862      IF cntrct_csr%ISOPEN THEN
863 	    CLOSE cntrct_csr;
864 	 END IF;
865      IF pry_sty_csr%ISOPEN THEN
866 	    CLOSE pry_sty_csr;
867 	 END IF;
868      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
869 
870   WHEN OTHERS THEN
871      IF cntrct_csr%ISOPEN THEN
872 	    CLOSE cntrct_csr;
873 	 END IF;
874      IF pry_sty_csr%ISOPEN THEN
875 	    CLOSE pry_sty_csr;
876 	 END IF;
877      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
878       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
879 
880 END get_primary_stream_type;
881 
882 PROCEDURE get_primary_stream_type_rep
883 (
884  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
885  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
886  x_return_status		OUT NOCOPY VARCHAR2,
887  x_primary_sty_id 		OUT NOCOPY okl_strm_type_b.ID%TYPE
888 )
889 
890 IS
891 
892 CURSOR cntrct_csr (l_khr_id NUMBER)IS
893 SELECT pdt.reporting_pdt_id, khr.start_date
894 FROM     okl_k_headers_full_v khr, okl_products pdt
895 WHERE khr.id = l_khr_id
896 AND   khr.pdt_id = pdt.id;
897 
898 CURSOR pry_sty_csr (l_pdt_id NUMBER, l_contract_start_date DATE) IS
899 SELECT PRIMARY_STY_ID
900 FROM   OKL_STRM_TMPT_LINES_UV STL
901 WHERE STL.PRIMARY_YN = 'Y'
902 AND STL.PDT_ID = l_pdt_id
903 AND    (STL.START_DATE <= l_contract_start_date)
904 AND    (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
905 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose;
906 
907   l_product_id 			  					NUMBER;
908   l_contract_start_date 	DATE;
909   l_primary_sty_id 			  	NUMBER;
910 
911   -- Santonyr Bug 4056364
912 
913   l_primary_sty_purpose_meaning VARCHAR2(4000);
914 
915 
916 BEGIN
917 
918   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
919 
920 
921   OPEN cntrct_csr (p_khr_id);
922   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
923   CLOSE cntrct_csr;
924 
925 
926 
927   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
928 
929     OPEN pry_sty_csr (l_product_id, l_contract_start_date);
930     FETCH pry_sty_csr INTO l_primary_sty_id;
931       IF  pry_sty_csr%NOTFOUND THEN
932 
933 -- Santonyr Bug 4056364
934 -- Bug 4064253
935 
936             l_primary_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
937             			('OKL_STREAM_TYPE_PURPOSE', p_primary_sty_purpose);
938 
939             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
940                                 p_msg_name      => 'OKL_NO_PRY_STY_FOUND',
941                                 p_token1        => 'PURPOSE',
942                                 p_token1_value  => l_primary_sty_purpose_meaning);
943             RAISE Okl_Api.G_EXCEPTION_ERROR;
944 	 END IF;
945      CLOSE pry_sty_csr;
946 
947   ELSE
948 
949 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
950                           p_msg_name     => 'OKL_NO_PDT_FOUND');
951             RAISE Okl_Api.G_EXCEPTION_ERROR;
952 
953   END IF;
954 
955   x_primary_sty_id := l_primary_sty_id;
956 
957   EXCEPTION
958   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
959      IF cntrct_csr%ISOPEN THEN
960 	    CLOSE cntrct_csr;
961 	 END IF;
962      IF pry_sty_csr%ISOPEN THEN
963 	    CLOSE pry_sty_csr;
964 	 END IF;
965      x_return_status := Okl_Api.G_RET_STS_ERROR ;
966 
967   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
968      IF cntrct_csr%ISOPEN THEN
969 	    CLOSE cntrct_csr;
970 	 END IF;
971      IF pry_sty_csr%ISOPEN THEN
972 	    CLOSE pry_sty_csr;
973 	 END IF;
974      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
975 
976   WHEN OTHERS THEN
977      IF cntrct_csr%ISOPEN THEN
978 	    CLOSE cntrct_csr;
979 	 END IF;
980      IF pry_sty_csr%ISOPEN THEN
981 	    CLOSE pry_sty_csr;
982 	 END IF;
983      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
984       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
985 
986 END get_primary_stream_type_rep;
987 
988 PROCEDURE get_primary_stream_type_rep
989 (
990  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
991  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
992  x_return_status		OUT NOCOPY VARCHAR2,
993  x_primary_sty_id 		OUT NOCOPY okl_strm_type_id_tbl_type
994 )
995 
996 IS
997 
998 CURSOR cntrct_csr (l_khr_id NUMBER)IS
999 SELECT pdt.reporting_pdt_id, khr.start_date
1000 FROM     okl_k_headers_full_v khr, okl_products pdt
1001 WHERE khr.id = l_khr_id
1002 AND   khr.pdt_id = pdt.id;
1003 
1004 CURSOR pry_sty_csr (l_pdt_id NUMBER, l_contract_start_date DATE) IS
1005 SELECT PRIMARY_STY_ID
1006 FROM   OKL_STRM_TMPT_LINES_UV STL
1007 WHERE STL.PRIMARY_YN = 'Y'
1008 AND STL.PDT_ID = l_pdt_id
1009 AND    (STL.START_DATE <= l_contract_start_date)
1010 AND    (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1011 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose;
1012 
1013   l_product_id 			  					NUMBER;
1014   l_contract_start_date 	DATE;
1015   l_primary_sty_id 			  	NUMBER;
1016 -- Santonyr Bug 4056364
1017   l_primary_sty_purpose_meaning VARCHAR2(4000);
1018 
1019 BEGIN
1020 
1021   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1022 
1023 
1024   OPEN cntrct_csr (p_khr_id);
1025   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1026   CLOSE cntrct_csr;
1027 
1028 
1029 
1030   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1031 
1032     OPEN pry_sty_csr (l_product_id, l_contract_start_date);
1033     FETCH pry_sty_csr INTO l_primary_sty_id;
1034       IF  pry_sty_csr%NOTFOUND THEN
1035             l_primary_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1036             			('OKL_STREAM_TYPE_PURPOSE', p_primary_sty_purpose);
1037       -- Bug 4064253
1038 
1039             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1040                                 p_msg_name      => 'OKL_NO_PRY_STY_FOUND',
1041                                 p_token1        => 'PURPOSE',
1042                                 p_token1_value  => l_primary_sty_purpose_meaning);
1043             RAISE Okl_Api.G_EXCEPTION_ERROR;
1044 	 END IF;
1045      CLOSE pry_sty_csr;
1046 
1047   ELSE
1048 
1049 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1050                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1051             RAISE Okl_Api.G_EXCEPTION_ERROR;
1052 
1053   END IF;
1054 
1055   --x_primary_sty_id := l_primary_sty_id;
1056 
1057   EXCEPTION
1058   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1059      IF cntrct_csr%ISOPEN THEN
1060 	    CLOSE cntrct_csr;
1061 	 END IF;
1062      IF pry_sty_csr%ISOPEN THEN
1063 	    CLOSE pry_sty_csr;
1064 	 END IF;
1065      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1066 
1067   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1068      IF cntrct_csr%ISOPEN THEN
1069 	    CLOSE cntrct_csr;
1070 	 END IF;
1071      IF pry_sty_csr%ISOPEN THEN
1072 	    CLOSE pry_sty_csr;
1073 	 END IF;
1074      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1075 
1076   WHEN OTHERS THEN
1077      IF cntrct_csr%ISOPEN THEN
1078 	    CLOSE cntrct_csr;
1079 	 END IF;
1080      IF pry_sty_csr%ISOPEN THEN
1081 	    CLOSE pry_sty_csr;
1082 	 END IF;
1083      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1084       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
1085 
1086 END get_primary_stream_type_rep;
1087 
1088 PROCEDURE get_dependent_stream_type
1089 (
1090  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
1091  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1092  p_dependent_sty_purpose IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1093  x_return_status		 OUT NOCOPY VARCHAR2,
1094  x_dependent_sty_id 	 OUT NOCOPY okl_strm_type_b.ID%TYPE
1095 )
1096 
1097 IS
1098 
1099 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1100 SELECT pdt_id, start_date
1101 FROM     okl_k_headers_full_v
1102 WHERE id = l_khr_id;
1103 
1104 CURSOR dep_sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1105 SELECT DEPENDENT_STY_ID
1106 FROM   OKL_STRM_TMPT_LINES_UV STL
1107 WHERE PRIMARY_YN = 'N'
1108 AND STL.PDT_ID = l_product_id
1109 AND    (STL.START_DATE <= l_contract_start_date)
1110 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1111 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose
1112 AND	   DEPENDENT_STY_PURPOSE =   p_dependent_sty_purpose;
1113 
1114   l_product_id 			  					NUMBER;
1115   l_contract_start_date 	DATE;
1116   l_dependetn_sty_id 			  					NUMBER;
1117 
1118 -- Santonyr Bug 4056364
1119 
1120   l_dep_sty_purpose_meaning VARCHAR2(4000);
1121 
1122 BEGIN
1123 
1124   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1125 
1126 --  DBMS_OUTPUT.PUT_LINE('l_p_khr_id -  ' || p_khr_id);
1127 
1128   OPEN cntrct_csr (p_khr_id);
1129   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1130   CLOSE cntrct_csr;
1131 
1132 --  DBMS_OUTPUT.PUT_LINE('l_pdt_id -  ' || l_product_id);
1133 --  DBMS_OUTPUT.PUT_LINE('l_start_date -  ' || l_contract_start_date);
1134 
1135   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1136 
1137     OPEN dep_sty_csr (l_product_id, l_contract_start_date);
1138     FETCH dep_sty_csr INTO l_dependetn_sty_id;
1139       IF  dep_sty_csr%NOTFOUND THEN
1140 -- Santonyr Bug 4056364
1141             l_dep_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1142             			('OKL_STREAM_TYPE_PURPOSE', p_dependent_sty_purpose);
1143             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1144                                 p_msg_name      => 'OKL_NO_DEP_STY_FOUND',
1145                                 p_token1        => 'PURPOSE',
1146                                 p_token1_value  => l_dep_sty_purpose_meaning);
1147             RAISE Okl_Api.G_EXCEPTION_ERROR;
1148 	 END IF;
1149      CLOSE dep_sty_csr;
1150 
1151   ELSE
1152 
1153 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1154                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1155             RAISE Okl_Api.G_EXCEPTION_ERROR;
1156 
1157   END IF;
1158 
1159   x_dependent_sty_id := l_dependetn_sty_id;
1160 
1161   EXCEPTION
1162   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1163      IF cntrct_csr%ISOPEN THEN
1164 	    CLOSE cntrct_csr;
1165 	 END IF;
1166      IF dep_sty_csr%ISOPEN THEN
1167 	    CLOSE dep_sty_csr;
1168 	 END IF;
1169      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1170 
1171   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1172      IF cntrct_csr%ISOPEN THEN
1173 	    CLOSE cntrct_csr;
1174 	 END IF;
1175      IF dep_sty_csr%ISOPEN THEN
1176 	    CLOSE dep_sty_csr;
1177 	 END IF;
1178      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1179 
1180   WHEN OTHERS THEN
1181      IF cntrct_csr%ISOPEN THEN
1182 	    CLOSE cntrct_csr;
1183 	 END IF;
1184      IF dep_sty_csr%ISOPEN THEN
1185 	    CLOSE dep_sty_csr;
1186 	 END IF;
1187      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1188       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
1189 END get_dependent_stream_type;
1190 
1191 
1192 PROCEDURE get_dependent_stream_type
1193 (
1194  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
1195  p_primary_sty_id        IN okl_strm_type_b.ID%TYPE,
1196  p_dependent_sty_purpose IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1197  x_return_status		 OUT NOCOPY VARCHAR2,
1198  x_dependent_sty_id 	 OUT NOCOPY okl_strm_type_b.ID%TYPE
1199 )
1200 
1201 IS
1202 
1203 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1204 SELECT pdt_id, start_date
1205 FROM     okl_k_headers_full_v
1206 WHERE id = l_khr_id;
1207 
1208 CURSOR dep_sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1209 SELECT DEPENDENT_STY_ID
1210 FROM   OKL_STRM_TMPT_LINES_UV STL
1211 WHERE PRIMARY_YN = 'N'
1212 AND STL.PDT_ID = l_product_id
1213 AND    (STL.START_DATE <= l_contract_start_date)
1214 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1215 AND	   PRIMARY_STY_ID =   p_primary_sty_id
1216 AND	   DEPENDENT_STY_PURPOSE =   p_dependent_sty_purpose;
1217 
1218   l_product_id 			  					NUMBER;
1219   l_contract_start_date 	DATE;
1220   l_dependetn_sty_id 			  					NUMBER;
1221 
1222 -- Santonyr Bug 4056364
1223   l_dep_sty_purpose_meaning VARCHAR2(4000);
1224 
1225 BEGIN
1226 
1227   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1228 
1229 --  DBMS_OUTPUT.PUT_LINE('l_p_khr_id -  ' || p_khr_id);
1230 
1231   OPEN cntrct_csr (p_khr_id);
1232   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1233   CLOSE cntrct_csr;
1234 
1235 --  DBMS_OUTPUT.PUT_LINE('l_pdt_id -  ' || l_product_id);
1236 --  DBMS_OUTPUT.PUT_LINE('l_start_date -  ' || l_contract_start_date);
1237 
1238   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1239 --dbms_output.put_line('Product Id5'||l_product_id);
1240 	--dbms_output.put_line('Contract Strat Date5'||l_contract_start_date);
1241     OPEN dep_sty_csr (l_product_id, l_contract_start_date);
1242     FETCH dep_sty_csr INTO l_dependetn_sty_id;
1243       IF  dep_sty_csr%NOTFOUND THEN
1244 
1245 -- Santonyr Bug 4056364
1246             l_dep_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1247             			('OKL_STREAM_TYPE_PURPOSE', p_dependent_sty_purpose);
1248 
1249             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1250                                 p_msg_name      => 'OKL_NO_DEP_STY_FOUND',
1251                                 p_token1        => 'PURPOSE',
1252                                 p_token1_value  => l_dep_sty_purpose_meaning);
1253 
1254             RAISE Okl_Api.G_EXCEPTION_ERROR;
1255 	 END IF;
1256      CLOSE dep_sty_csr;
1257 
1258   ELSE
1259 
1260 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1261                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1262             RAISE Okl_Api.G_EXCEPTION_ERROR;
1263 
1264   END IF;
1265 
1266   x_dependent_sty_id := l_dependetn_sty_id;
1267 
1268   EXCEPTION
1269   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1270      IF cntrct_csr%ISOPEN THEN
1271 	    CLOSE cntrct_csr;
1272 	 END IF;
1273      IF dep_sty_csr%ISOPEN THEN
1274 	    CLOSE dep_sty_csr;
1275 	 END IF;
1276      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1277 
1278   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1279      IF cntrct_csr%ISOPEN THEN
1280 	    CLOSE cntrct_csr;
1281 	 END IF;
1282      IF dep_sty_csr%ISOPEN THEN
1283 	    CLOSE dep_sty_csr;
1284 	 END IF;
1285      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1286 
1287   WHEN OTHERS THEN
1288      IF cntrct_csr%ISOPEN THEN
1289 	    CLOSE cntrct_csr;
1290 	 END IF;
1291      IF dep_sty_csr%ISOPEN THEN
1292 	    CLOSE dep_sty_csr;
1293 	 END IF;
1294      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1295       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
1296 END get_dependent_stream_type;
1297 
1298 -- Added for bug 6326479  - start
1299 PROCEDURE get_dependent_stream_type
1300 (
1301  p_khr_id  		 IN okl_k_headers_full_v.id%TYPE,
1302  p_product_id            IN okl_k_headers_full_v.pdt_id%TYPE,
1303  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1304  p_dependent_sty_purpose IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1305  x_return_status	 OUT NOCOPY VARCHAR2,
1306  x_dependent_sty_id 	 OUT NOCOPY okl_strm_type_b.ID%TYPE
1307 )
1308 
1309 IS
1310 
1311 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1312 SELECT pdt_id, start_date
1313 FROM     okl_k_headers_full_v
1314 WHERE id = l_khr_id;
1315 
1316 CURSOR dep_sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1317 SELECT DEPENDENT_STY_ID
1318 FROM   OKL_STRM_TMPT_LINES_UV STL
1319 WHERE PRIMARY_YN = 'N'
1320 AND STL.PDT_ID = l_product_id
1321 AND    (STL.START_DATE <= l_contract_start_date)
1322 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1323 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose
1324 AND	   DEPENDENT_STY_PURPOSE =   p_dependent_sty_purpose;
1325 
1326   l_product_id 			  					NUMBER;
1327   l_contract_start_date 	DATE;
1328   l_dependetn_sty_id 			  					NUMBER;
1329 
1330 -- Santonyr Bug 4056364
1331 
1332   l_dep_sty_purpose_meaning VARCHAR2(4000);
1333 
1334 BEGIN
1335 
1336   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1337 
1338   OPEN cntrct_csr (p_khr_id);
1339   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1340   CLOSE cntrct_csr;
1341 
1342   IF (p_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1343 
1344     OPEN dep_sty_csr (p_product_id, l_contract_start_date);
1345     FETCH dep_sty_csr INTO l_dependetn_sty_id;
1346       IF  dep_sty_csr%NOTFOUND THEN
1347 
1348             l_dep_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1349             			('OKL_STREAM_TYPE_PURPOSE', p_dependent_sty_purpose);
1350             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1351                                 p_msg_name      => 'OKL_NO_DEP_STY_FOUND',
1352                                 p_token1        => 'PURPOSE',
1353                                 p_token1_value  => l_dep_sty_purpose_meaning);
1354             RAISE Okl_Api.G_EXCEPTION_ERROR;
1355 	 END IF;
1356      CLOSE dep_sty_csr;
1357 
1358   ELSE
1359 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1360                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1361             RAISE Okl_Api.G_EXCEPTION_ERROR;
1362 
1363   END IF;
1364 
1365   x_dependent_sty_id := l_dependetn_sty_id;
1366 
1367   EXCEPTION
1368   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1369      IF cntrct_csr%ISOPEN THEN
1370 	    CLOSE cntrct_csr;
1371 	 END IF;
1372      IF dep_sty_csr%ISOPEN THEN
1373 	    CLOSE dep_sty_csr;
1374 	 END IF;
1375      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1376 
1377   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1378      IF cntrct_csr%ISOPEN THEN
1379 	    CLOSE cntrct_csr;
1380 	 END IF;
1381      IF dep_sty_csr%ISOPEN THEN
1382 	    CLOSE dep_sty_csr;
1383 	 END IF;
1384      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1385 
1386   WHEN OTHERS THEN
1387      IF cntrct_csr%ISOPEN THEN
1388 	    CLOSE cntrct_csr;
1389 	 END IF;
1390      IF dep_sty_csr%ISOPEN THEN
1391 	    CLOSE dep_sty_csr;
1392 	 END IF;
1393      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1394 END get_dependent_stream_type;
1395 
1396 PROCEDURE get_dependent_stream_type_rep
1397 (
1398  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
1399  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1400  p_dependent_sty_purpose IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1401  x_return_status		 OUT NOCOPY VARCHAR2,
1402  x_dependent_sty_id 	 OUT NOCOPY okl_strm_type_b.ID%TYPE
1403 )
1404 
1405 IS
1406 
1407 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1408 SELECT pdt.reporting_pdt_id, khr.start_date
1409 FROM     okl_k_headers_full_v khr, okl_products pdt
1410 WHERE khr.id = l_khr_id
1411 AND   khr.pdt_id = pdt.id;
1412 
1413 CURSOR dep_sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1414 SELECT DEPENDENT_STY_ID
1415 FROM   OKL_STRM_TMPT_LINES_UV STL
1416 WHERE PRIMARY_YN = 'N'
1417 AND STL.PDT_ID = l_product_id
1418 AND    (STL.START_DATE <= l_contract_start_date)
1419 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1420 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose
1421 AND	   DEPENDENT_STY_PURPOSE =   p_dependent_sty_purpose;
1422 
1423   l_product_id 			  					NUMBER;
1424   l_contract_start_date 	DATE;
1425   l_dependetn_sty_id 			  					NUMBER;
1426 
1427 -- Santonyr Bug 4056364
1428 
1429   l_dep_sty_purpose_meaning VARCHAR2(4000);
1430 
1431 BEGIN
1432 
1433   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1434 
1435 --  DBMS_OUTPUT.PUT_LINE('l_p_khr_id -  ' || p_khr_id);
1436 
1437   OPEN cntrct_csr (p_khr_id);
1438   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1439   CLOSE cntrct_csr;
1440 
1441 --  DBMS_OUTPUT.PUT_LINE('l_pdt_id -  ' || l_product_id);
1442 --  DBMS_OUTPUT.PUT_LINE('l_start_date -  ' || l_contract_start_date);
1443 
1444   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1445 
1446     OPEN dep_sty_csr (l_product_id, l_contract_start_date);
1447     FETCH dep_sty_csr INTO l_dependetn_sty_id;
1448       IF  dep_sty_csr%NOTFOUND THEN
1449 -- Santonyr Bug 4056364
1450             l_dep_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1451             			('OKL_STREAM_TYPE_PURPOSE', p_dependent_sty_purpose);
1452             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1453                                 p_msg_name      => 'OKL_NO_DEP_STY_FOUND',
1454                                 p_token1        => 'PURPOSE',
1455                                 p_token1_value  => l_dep_sty_purpose_meaning);
1456             RAISE Okl_Api.G_EXCEPTION_ERROR;
1457 	 END IF;
1458      CLOSE dep_sty_csr;
1459 
1460   ELSE
1461 
1462 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1463                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1464             RAISE Okl_Api.G_EXCEPTION_ERROR;
1465 
1466   END IF;
1467 
1468   x_dependent_sty_id := l_dependetn_sty_id;
1469 
1470   EXCEPTION
1471   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1472      IF cntrct_csr%ISOPEN THEN
1473 	    CLOSE cntrct_csr;
1474 	 END IF;
1475      IF dep_sty_csr%ISOPEN THEN
1476 	    CLOSE dep_sty_csr;
1477 	 END IF;
1478      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1479 
1480   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1481      IF cntrct_csr%ISOPEN THEN
1482 	    CLOSE cntrct_csr;
1483 	 END IF;
1484      IF dep_sty_csr%ISOPEN THEN
1485 	    CLOSE dep_sty_csr;
1486 	 END IF;
1487      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1488 
1489   WHEN OTHERS THEN
1490      IF cntrct_csr%ISOPEN THEN
1491 	    CLOSE cntrct_csr;
1492 	 END IF;
1493      IF dep_sty_csr%ISOPEN THEN
1494 	    CLOSE dep_sty_csr;
1495 	 END IF;
1496      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1497       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
1498 END get_dependent_stream_type_rep;
1499 
1500 
1501 PROCEDURE get_dependent_stream_type_rep
1502 (
1503  p_khr_id  		   	     IN okl_k_headers_full_v.id%TYPE,
1504  p_primary_sty_id        IN okl_strm_type_b.ID%TYPE,
1505  p_dependent_sty_purpose IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1506  x_return_status		 OUT NOCOPY VARCHAR2,
1507  x_dependent_sty_id 	 OUT NOCOPY okl_strm_type_b.ID%TYPE
1508 )
1509 
1510 IS
1511 
1512 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1513 SELECT pdt.reporting_pdt_id, khr.start_date
1514 FROM     okl_k_headers_full_v khr, okl_products pdt
1515 WHERE khr.id = l_khr_id
1516 AND   khr.pdt_id = pdt.id;
1517 
1518 CURSOR dep_sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1519 SELECT DEPENDENT_STY_ID
1520 FROM   OKL_STRM_TMPT_LINES_UV STL
1521 WHERE PRIMARY_YN = 'N'
1522 AND STL.PDT_ID = l_product_id
1523 AND    (STL.START_DATE <= l_contract_start_date)
1524 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1525 AND	   PRIMARY_STY_ID =   p_primary_sty_id
1526 AND	   DEPENDENT_STY_PURPOSE =   p_dependent_sty_purpose;
1527 
1528   l_product_id 			  					NUMBER;
1529   l_contract_start_date 	DATE;
1530   l_dependetn_sty_id 			  					NUMBER;
1531 
1532 -- Santonyr Bug 4056364
1533   l_dep_sty_purpose_meaning VARCHAR2(4000);
1534 
1535 BEGIN
1536 
1537   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1538 
1539 --  DBMS_OUTPUT.PUT_LINE('l_p_khr_id -  ' || p_khr_id);
1540 
1541   OPEN cntrct_csr (p_khr_id);
1542   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1543   CLOSE cntrct_csr;
1544 
1545 --  DBMS_OUTPUT.PUT_LINE('l_pdt_id -  ' || l_product_id);
1546 --  DBMS_OUTPUT.PUT_LINE('l_start_date -  ' || l_contract_start_date);
1547 
1548   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1549 --dbms_output.put_line('Product Id5'||l_product_id);
1550 	--dbms_output.put_line('Contract Strat Date5'||l_contract_start_date);
1551     OPEN dep_sty_csr (l_product_id, l_contract_start_date);
1552     FETCH dep_sty_csr INTO l_dependetn_sty_id;
1553       IF  dep_sty_csr%NOTFOUND THEN
1554 
1555 -- Santonyr Bug 4056364
1556             l_dep_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1557             			('OKL_STREAM_TYPE_PURPOSE', p_dependent_sty_purpose);
1558 
1559             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1560                                 p_msg_name      => 'OKL_NO_DEP_STY_FOUND',
1561                                 p_token1        => 'PURPOSE',
1562                                 p_token1_value  => l_dep_sty_purpose_meaning);
1563 
1564             RAISE Okl_Api.G_EXCEPTION_ERROR;
1565 	 END IF;
1566      CLOSE dep_sty_csr;
1567 
1568   ELSE
1569 
1570 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1571                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1572             RAISE Okl_Api.G_EXCEPTION_ERROR;
1573 
1574   END IF;
1575 
1576   x_dependent_sty_id := l_dependetn_sty_id;
1577 
1578   EXCEPTION
1579   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1580      IF cntrct_csr%ISOPEN THEN
1581 	    CLOSE cntrct_csr;
1582 	 END IF;
1583      IF dep_sty_csr%ISOPEN THEN
1584 	    CLOSE dep_sty_csr;
1585 	 END IF;
1586      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1587 
1588   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1589      IF cntrct_csr%ISOPEN THEN
1590 	    CLOSE cntrct_csr;
1591 	 END IF;
1592      IF dep_sty_csr%ISOPEN THEN
1593 	    CLOSE dep_sty_csr;
1594 	 END IF;
1595      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1596 
1597   WHEN OTHERS THEN
1598      IF cntrct_csr%ISOPEN THEN
1599 	    CLOSE cntrct_csr;
1600 	 END IF;
1601      IF dep_sty_csr%ISOPEN THEN
1602 	    CLOSE dep_sty_csr;
1603 	 END IF;
1604      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1605       --DBMS_OUTPUT.PUT_LINE(SQLERRM);
1606 END get_dependent_stream_type_rep;
1607 
1608 -- Added for bug 6326479  - start
1609 PROCEDURE get_dependent_stream_type_rep
1610 (
1611  p_khr_id  		 IN okl_k_headers_full_v.id%TYPE,
1612  p_product_id            IN okl_k_headers_full_v.pdt_id%TYPE,
1613  p_primary_sty_purpose   IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1614  p_dependent_sty_purpose IN okl_strm_type_b.STREAM_TYPE_PURPOSE%TYPE,
1615  x_return_status	 OUT NOCOPY VARCHAR2,
1616  x_dependent_sty_id 	 OUT NOCOPY okl_strm_type_b.ID%TYPE
1617 )
1618 
1619 IS
1620 
1621 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1622 SELECT pdt.reporting_pdt_id, khr.start_date
1623 FROM     okl_k_headers_full_v khr, okl_products pdt
1624 WHERE khr.id = l_khr_id
1625 AND   khr.pdt_id = pdt.id;
1626 
1627 CURSOR dep_sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1628 SELECT DEPENDENT_STY_ID
1629 FROM   OKL_STRM_TMPT_LINES_UV STL
1630 WHERE PRIMARY_YN = 'N'
1631 AND STL.PDT_ID = l_product_id
1632 AND    (STL.START_DATE <= l_contract_start_date)
1633 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1634 AND	   PRIMARY_STY_PURPOSE =   p_primary_sty_purpose
1635 AND	   DEPENDENT_STY_PURPOSE =   p_dependent_sty_purpose;
1636 
1637   l_product_id 			  					NUMBER;
1638   l_contract_start_date 	DATE;
1639   l_dependetn_sty_id 			  					NUMBER;
1640 
1641 -- Santonyr Bug 4056364
1642 
1643   l_dep_sty_purpose_meaning VARCHAR2(4000);
1644 
1645 BEGIN
1646 
1647   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1648 
1649   OPEN cntrct_csr (p_khr_id);
1650   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1651   CLOSE cntrct_csr;
1652 
1653   IF (p_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1654 
1655     OPEN dep_sty_csr (p_product_id, l_contract_start_date);
1656     FETCH dep_sty_csr INTO l_dependetn_sty_id;
1657       IF  dep_sty_csr%NOTFOUND THEN
1658 
1659             l_dep_sty_purpose_meaning := OKL_ACCOUNTING_UTIL.GET_LOOKUP_MEANING
1660             			('OKL_STREAM_TYPE_PURPOSE', p_dependent_sty_purpose);
1661             OKL_API.SET_MESSAGE(p_app_name      => g_app_name,
1662                                 p_msg_name      => 'OKL_NO_DEP_STY_FOUND',
1663                                 p_token1        => 'PURPOSE',
1664                                 p_token1_value  => l_dep_sty_purpose_meaning);
1665             RAISE Okl_Api.G_EXCEPTION_ERROR;
1666 	 END IF;
1667      CLOSE dep_sty_csr;
1668 
1669   ELSE
1670 	        Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1671                           p_msg_name     => 'OKL_NO_PDT_FOUND');
1672             RAISE Okl_Api.G_EXCEPTION_ERROR;
1673 
1674   END IF;
1675 
1676   x_dependent_sty_id := l_dependetn_sty_id;
1677 
1678   EXCEPTION
1679   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1680      IF cntrct_csr%ISOPEN THEN
1681 	    CLOSE cntrct_csr;
1682 	 END IF;
1683      IF dep_sty_csr%ISOPEN THEN
1684 	    CLOSE dep_sty_csr;
1685 	 END IF;
1686      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1687 
1688   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1689      IF cntrct_csr%ISOPEN THEN
1690 	    CLOSE cntrct_csr;
1691 	 END IF;
1692      IF dep_sty_csr%ISOPEN THEN
1693 	    CLOSE dep_sty_csr;
1694 	 END IF;
1695      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1696 
1697   WHEN OTHERS THEN
1698      IF cntrct_csr%ISOPEN THEN
1699 	    CLOSE cntrct_csr;
1700 	 END IF;
1701      IF dep_sty_csr%ISOPEN THEN
1702 	    CLOSE dep_sty_csr;
1703 	 END IF;
1704      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1705 END get_dependent_stream_type_rep;
1706 
1707 -- Added for bug 6326479  - End
1708 
1709 -- Evaluates whether a stream type is present in the stream generation
1710 -- template for a contract
1711 FUNCTION strm_tmpt_contains_strm_type
1712 (
1713  p_khr_id  		 IN okl_k_headers_full_v.id%TYPE,
1714  p_sty_id        IN okl_strm_type_b.ID%TYPE
1715 )
1716 RETURN VARCHAR2
1717 IS
1718 
1719 CURSOR cntrct_csr (l_khr_id NUMBER)IS
1720 SELECT pdt_id, start_date
1721 FROM     okl_k_headers_full_v
1722 WHERE id = l_khr_id;
1723 
1724 CURSOR sty_csr (l_product_id NUMBER, l_contract_start_date DATE) IS
1725 SELECT '1'
1726 FROM   OKL_STRM_TMPT_FULL_UV STL
1727 WHERE STL.PDT_ID = l_product_id
1728 AND    (STL.START_DATE <= l_contract_start_date)
1729 AND   (STL.END_DATE >= l_contract_start_date OR STL.END_DATE IS NULL)
1730 AND	   STY_ID =   p_sty_id;
1731 
1732   l_product_id 			  	NUMBER;
1733   l_contract_start_date 	DATE;
1734   l_sty_id                  NUMBER;
1735 
1736 BEGIN
1737 
1738   OPEN cntrct_csr (p_khr_id);
1739   FETCH cntrct_csr INTO l_product_id, l_contract_start_date;
1740   CLOSE cntrct_csr;
1741 
1742   IF (l_product_id IS NOT NULL) AND (l_contract_start_date IS NOT NULL) THEN
1743     OPEN sty_csr (l_product_id, l_contract_start_date);
1744     FETCH sty_csr INTO l_sty_id;
1745     IF  sty_csr%NOTFOUND THEN
1746       CLOSE sty_csr;
1747       RETURN 'N';
1748 	ELSE
1749       CLOSE sty_csr;
1750 	  RETURN 'Y';
1751 	END IF;
1752   ELSE
1753       RETURN 'N';
1754   END IF;
1755 
1756   EXCEPTION
1757   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1758      IF cntrct_csr%ISOPEN THEN
1759 	    CLOSE cntrct_csr;
1760 	 END IF;
1761   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1762      IF cntrct_csr%ISOPEN THEN
1763 	    CLOSE cntrct_csr;
1764 	 END IF;
1765   WHEN OTHERS THEN
1766      IF cntrct_csr%ISOPEN THEN
1767 	    CLOSE cntrct_csr;
1768 	 END IF;
1769 END strm_tmpt_contains_strm_type;
1770 
1771 
1772 -- Gets the status of the stream generation request for external generator
1773 PROCEDURE get_transaction_status
1774 (
1775  p_transaction_number  IN okl_stream_interfaces.transaction_number%TYPE,
1776  x_transaction_status  OUT NOCOPY okl_stream_interfaces.sis_code%TYPE,
1777  x_logfile_name        OUT NOCOPY okl_stream_interfaces.log_file%TYPE,
1778  x_return_status       OUT NOCOPY VARCHAR2
1779 )
1780 IS
1781   l_transaction_status okl_stream_interfaces.sis_code%TYPE := null;
1782   l_logfile_name       okl_stream_interfaces.log_file%TYPE := null;
1783 
1784   CURSOR intf_status_csr(trx_number NUMBER)
1785   IS
1786     SELECT sis_code, log_file FROM okl_stream_interfaces
1787 	WHERE transaction_number = trx_number;
1788 
1789 BEGIN
1790 
1791   OPEN intf_status_csr(p_transaction_number);
1792   FETCH intf_status_csr INTO l_transaction_status, l_logfile_name;
1793 
1794   IF intf_status_csr%NOTFOUND THEN
1795 	 Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1796                          p_msg_name     => 'OKL_TRX_NUM_NOT_FOUND');
1797      RAISE Okl_Api.G_EXCEPTION_ERROR;
1798   END IF;
1799 
1800   CLOSE intf_status_csr;
1801 
1802   x_transaction_status    := l_transaction_status;
1803   x_logfile_name          := l_logfile_name;
1804   x_return_status         := Okl_Api.G_RET_STS_SUCCESS;
1805 
1806 EXCEPTION
1807   WHEN Okl_Api.G_EXCEPTION_ERROR THEN
1808      IF intf_status_csr%ISOPEN THEN
1809 	    CLOSE intf_status_csr;
1810 	 END IF;
1811      x_return_status := Okl_Api.G_RET_STS_ERROR ;
1812   WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
1813      IF intf_status_csr%ISOPEN THEN
1814 	    CLOSE intf_status_csr;
1815 	 END IF;
1816      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1817   WHEN OTHERS THEN
1818      IF intf_status_csr%ISOPEN THEN
1819 	    CLOSE intf_status_csr;
1820 	 END IF;
1821      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
1822 END;
1823 
1824 
1825 -- Added by Santonyr
1826 --------------------------------------------------------------------------------
1827 -- Start of Commnets
1828 -- Procedure Name       : get_pricing_engine
1829 -- Description          : Returns pricing engine for a contract based on the product
1830 --                        stream template
1831 -- Business Rules       :
1832 -- Parameters           : P_khr_id,
1833 -- Version              : 1.0
1834 -- History              : santonyr 10-Dec-2004 - created
1835 -- End of Commnets
1836 --------------------------------------------------------------------------------
1837 
1838 FUNCTION get_pricing_engine(p_khr_id IN okl_k_headers.id%TYPE)
1839 RETURN VARCHAR2
1840 IS
1841 
1842 -- Cursor to fetch the pricing engine for a contract.
1843 
1844 CURSOR prc_eng_csr IS
1845 SELECT
1846    gts.pricing_engine
1847 FROM
1848   okl_k_headers khr,
1849   okl_products_v pdt,
1850   okl_ae_tmpt_sets_v aes,
1851   OKL_ST_GEN_TMPT_SETS gts
1852 WHERE
1853   khr.pdt_id = pdt.id AND
1854   pdt.aes_id = aes.id AND
1855   aes.gts_id = gts.id AND
1856   khr.id  = p_khr_id;
1857 
1858 l_pricing_engine okl_st_gen_tmpt_sets.pricing_engine%TYPE;
1859 
1860 BEGIN
1861 
1862 OPEN prc_eng_csr;
1863 FETCH prc_eng_csr INTO l_pricing_engine;
1864 CLOSE prc_eng_csr;
1865 
1866 RETURN l_pricing_engine;
1867 
1868 EXCEPTION
1869   WHEN OTHERS THEN
1870     IF prc_eng_csr%ISOPEN THEN
1871       CLOSE prc_eng_csr;
1872     END IF;
1873     RETURN NULL;
1874 
1875 END get_pricing_engine;
1876 
1877 -- Added by Santonyr
1878 --------------------------------------------------------------------------------
1879 -- Start of Commnets
1880 -- Procedure Name       : get_pricing_engine
1881 -- Description          : Returns pricing engine for a contract based on the product
1882 --                        stream template
1883 -- Business Rules       :
1884 -- Parameters           : p_khr_id,
1885 -- Version              : 1.0
1886 -- History              : santonyr 10-Dec-2004 - created
1887 -- End of Commnets
1888 --------------------------------------------------------------------------------
1889 
1890 PROCEDURE get_pricing_engine
1891 	(p_khr_id IN okl_k_headers.id%TYPE,
1892 	x_pricing_engine OUT NOCOPY VARCHAR2,
1893 	x_return_status OUT NOCOPY VARCHAR2)
1894 IS
1895 
1896 CURSOR prc_eng_csr IS
1897 SELECT
1898    gts.name
1899 FROM
1900   okl_k_headers khr,
1901   okl_products_v pdt,
1902   okl_ae_tmpt_sets_v aes,
1903   OKL_ST_GEN_TMPT_SETS gts
1904 WHERE
1905   khr.pdt_id = pdt.id AND
1906   pdt.aes_id = aes.id AND
1907   aes.gts_id = gts.id AND
1908   khr.id  = p_khr_id;
1909 
1910 l_pricing_engine okl_st_gen_tmpt_sets.pricing_engine%TYPE;
1911 l_st_tmpt_name okl_st_gen_tmpt_sets.name%TYPE;
1912 
1913 BEGIN
1914   x_return_status         := OKL_API.G_RET_STS_SUCCESS;
1915 
1916   -- Call get_pricing_engine to get the pricing engine
1917 
1918   l_pricing_engine := Okl_Streams_Util.get_pricing_engine(p_khr_id);
1919 
1920   -- Set the message if the pricing engine is NULL
1921 
1922   IF l_pricing_engine IS NULL THEN
1923 
1924      OPEN prc_eng_csr;
1925      FETCH prc_eng_csr INTO l_st_tmpt_name;
1926      CLOSE prc_eng_csr;
1927 
1928      Okl_Api.SET_MESSAGE(p_app_name     => g_app_name,
1929                          p_msg_name     => 'OKL_NO_PRICING_ENGINE',
1930                          p_token1	=> 'STREAM_TEMPLATE',
1931                          p_token1_value => l_st_tmpt_name);
1932 
1933      RAISE OKL_API.G_EXCEPTION_ERROR;
1934   END IF;
1935 
1936   -- Return the pricing engine
1937 
1938   x_pricing_engine := l_pricing_engine;
1939 
1940 EXCEPTION
1941 
1942   WHEN OKL_API.G_EXCEPTION_ERROR THEN
1943      IF prc_eng_csr%ISOPEN THEN
1944        CLOSE prc_eng_csr;
1945      END IF;
1946      x_return_status := OKL_API.G_RET_STS_ERROR ;
1947 
1948   WHEN OTHERS THEN
1949      IF prc_eng_csr%ISOPEN THEN
1950        CLOSE prc_eng_csr;
1951      END IF;
1952      x_return_status := OKL_API.G_RET_STS_UNEXP_ERROR;
1953 
1954 END get_pricing_engine;
1955 
1956 -- Bug 4196515 - Start of Changes
1957 --------------------------------------------------------------------------------
1958 -- Start of Commnets
1959 -- Procedure Name       : round_streams_amount_esg
1960 -- Description          : Returns PL/SQL table of record rounded amounts
1961 --                        of OKL_STRM_ELEMENTS type during the External Stream
1962 --                        Generation Process
1963 -- Business Rules       : We sum the amounts given as I/P PL/SQL table first.
1964 --                        And then we round the amounts using existing
1965 --                        rounding rule and then sum them these up.
1966 --                        If we find a difference between rounded amount
1967 --                        and non-rounded amount then based on already existing
1968 --                        rule we do adjustment to the first amount or
1969 --                        last amount or the High value amount of the PL/SQL
1970 --                        table of records.We then give the rounded values
1971 --                        thru O/P PL/SQL table of records.
1972 -- Parameters           : P_chr_id,
1973 --                        p_selv_tbl of OKL_STRM_ELEMENTS type
1974 --                        x_selv_tbl of OKL_STRM_ELEMENTS type,
1975 --                        p_org_id,
1976 --                        p_precision,
1977 --                        p_currency_code,
1978 --                        p_rounding_rule,
1979 --                        p_apply_rnd_diff
1980 -- End of Commnets
1981 --------------------------------------------------------------------------------
1982 -- The difference between the functions round_streams_amount and
1983 -- round_streams_amount_esg is in the parameters being passed to the call.
1984 
1985 -- Instead of obtaining the values of org_id, precision, currency_code, rounding_rule
1986 -- apply_rounding_difference everytime the function is called by executing cursors,
1987 -- these values are calculated and passed from Okl_Process_Streams_Pvt.process_stream_results
1988 
1989   FUNCTION round_streams_amount_esg(p_api_version    IN  NUMBER,
1990                                 p_init_msg_list  IN  VARCHAR2 DEFAULT OKL_API.G_FALSE,
1991                                 x_msg_count      OUT NOCOPY NUMBER,
1992                                 x_msg_data       OUT NOCOPY VARCHAR2,
1993                                 p_chr_id         IN okc_k_headers_b.id%TYPE,
1994                                 p_selv_tbl       IN okl_streams_pub.selv_tbl_type,
1995                                 x_selv_tbl       OUT NOCOPY okl_streams_pub.selv_tbl_type,
1996                                 p_org_id         IN okc_k_headers_b.authoring_org_id%TYPE,
1997                                 p_precision      IN NUMBER,
1998                                 p_currency_code  IN okc_k_headers_b.currency_code%TYPE,
1999                                 p_rounding_rule  IN okl_sys_acct_opts.stm_rounding_rule%TYPE,
2000                                 p_apply_rnd_diff IN okl_sys_acct_opts.stm_apply_rounding_difference%TYPE)
2001   RETURN VARCHAR2 IS
2002    l_api_name               CONSTANT VARCHAR2(30) := 'ROUND_STREAMS_AMOUNT';
2003     g_col_name_token         CONSTANT  VARCHAR2(200) := Okl_Api.G_COL_NAME_TOKEN;
2004     g_no_match_rec           CONSTANT VARCHAR2(30) := 'OKL_LLA_NO_MATCHING_RECORD';
2005     g_invalid_value          CONSTANT VARCHAR2(200) := 'OKL_INVALID_VALUE ';
2006     g_rnd_diff_lookup_type   CONSTANT fnd_lookups.lookup_type%TYPE := 'OKL_STRM_APPLY_ROUNDING_DIFF';
2007     g_first_lookup_code      CONSTANT fnd_lookups.lookup_code%TYPE := 'ADD_TO_FIRST';
2008     g_last_lookup_code       CONSTANT fnd_lookups.lookup_code%TYPE := 'ADD_TO_LAST';
2009     g_high_lookup_code       CONSTANT fnd_lookups.lookup_code%TYPE := 'ADD_TO_HIGH';
2010     x_return_status                   VARCHAR2(3)  := Okl_Api.G_RET_STS_SUCCESS;
2011     ln_grter_amt_ind                  NUMBER := 0;
2012     ln_grter_amt                      NUMBER := 0;
2013     ln_tot_no_rnd_amount              NUMBER := 0;
2014     ln_tot_rnd_amount                 NUMBER := 0;
2015     ln_rounded_amount                 NUMBER := 0;
2016     ln_rnd_diff_amount                NUMBER := 0;
2017     ln_diff_amount                    NUMBER := 0;
2018     ln_chr_id                         okc_k_headers_b.id%TYPE := p_chr_id;
2019     ln_org_id                         okc_k_headers_b.authoring_org_id%TYPE := p_org_id;
2020     lv_currency_code                  okc_k_headers_b.currency_code%TYPE := p_currency_code;
2021     lv_diff_lookup_code               fnd_lookups.lookup_code%TYPE := p_apply_rnd_diff;
2022     lv_rounding_rule                  fnd_lookups.lookup_code%TYPE := p_rounding_rule;
2023     g_stop_round_exp                  EXCEPTION;
2024     ln_precision1                     NUMBER := p_precision;
2025     g_rounding_error                  EXCEPTION;
2026     lv_return_status    VARCHAR2(3) := Okl_Api.G_RET_STS_SUCCESS;
2027     l_first_rec_index                 NUMBER := 0;
2028     l_last_rec_index                  NUMBER := 0;
2029     l_min_date                        DATE;
2030     l_max_date                        DATE;
2031 
2032       -- Get the precision for the amounts to Round
2033       -- Depending on the Currency code
2034       CURSOR get_precision(p_currency_code OKC_K_HEADERS_B.CURRENCY_CODE%TYPE) IS
2035       SELECT PRECISION
2036       FROM fnd_currencies_vl
2037       WHERE currency_code = p_currency_code
2038       AND enabled_flag = 'Y'
2039       AND NVL(start_date_active, SYSDATE) <= SYSDATE
2040       AND NVL(end_date_active, SYSDATE) >= SYSDATE;
2041 
2042     l_selv_tbl                        Okl_Streams_Pub.selv_tbl_type := p_selv_tbl;
2043     -- Get the Rule to Adjust the amount either
2044     -- top/bottom/high_value of the PL/SQL tbl record
2045     CURSOR get_rnd_diff_lookup(p_lookup_type  fnd_lookups.lookup_type%TYPE)
2046     IS
2047     SELECT b.stm_apply_rounding_difference
2048     FROM fnd_lookups a,
2049          OKL_SYS_ACCT_OPTS b
2050     WHERE a.lookup_type = p_lookup_type
2051     AND a.lookup_code = b.stm_apply_rounding_difference;
2052     -- get the currency_code and Authoring_org_id
2053     -- from okc_k_headers_b
2054     CURSOR get_org_id(p_chr_id  okc_k_headers_b.id%TYPE)
2055     IS
2056     SELECT authoring_org_id,
2057            currency_code
2058     FROM okc_k_headers_b
2059     WHERE id = p_chr_id;
2060 
2061     --Cursor to fetch the Stream Rounding Rule
2062     CURSOR get_rounding_rule IS
2063     SELECT stm_rounding_rule
2064     FROM OKL_SYS_ACCT_OPTS;
2065 
2066 
2067     -- Local Function to round the amount depending on the
2068     -- Currency code
2069     FUNCTION round_amount(p_amount        IN  NUMBER,
2070                           p_add_precision IN  NUMBER,
2071                           x_amount        OUT NOCOPY NUMBER,
2072                           p_currency_code IN okc_k_headers_b.currency_code%TYPE,
2073                           p_precision     IN  NUMBER,
2074                           p_rounding_rule IN  okl_sys_acct_opts.ael_rounding_rule%TYPE)
2075     RETURN VARCHAR2 AS
2076       lv_rounding_rule    okl_sys_acct_opts.ael_rounding_rule%TYPE := p_rounding_rule ;
2077       ln_precision        NUMBER := p_precision;
2078       ln_amount           NUMBER := p_amount;
2079       ln_rounded_amount   NUMBER := 0;
2080       ln_pos_dot          NUMBER;
2081       ln_to_add           NUMBER := 1;
2082       lv_return_status    VARCHAR2(3) := OKL_API.G_RET_STS_SUCCESS;
2083 
2084     BEGIN
2085       IF ((lv_rounding_rule IS NOT NULL) AND (ln_precision IS NOT NULL)) THEN
2086          -- We now Processing the rounding depending
2087          -- on the rule we derived from the above cursor
2088          -- get rounding rule
2089          IF (lv_rounding_rule = 'UP') THEN
2090            ln_pos_dot := INSTR(TO_CHAR(ln_amount),'.') ;
2091            IF (ln_pos_dot > 0) AND
2092            (SUBSTR(ln_amount,ln_pos_dot+ln_precision+1 + p_add_precision,1) IS NOT NULL) THEN
2093               FOR i IN 1..ln_precision + p_add_precision LOOP
2094                 ln_to_add := ln_to_add/10;
2095               END LOOP;
2096               ln_rounded_amount := ln_amount + ln_to_add;
2097            ELSE
2098               ln_rounded_amount := ln_amount;
2099            END IF;
2100            ln_rounded_amount := TRUNC(ln_rounded_amount,ln_precision + p_add_precision);
2101          ELSIF lv_rounding_rule = 'DOWN' THEN
2102            ln_rounded_amount := TRUNC(ln_amount, ln_precision + p_add_precision);
2103          ELSIF lv_rounding_rule = 'NEAREST' THEN
2104            ln_rounded_amount := ROUND(ln_amount, ln_precision + p_add_precision);
2105          END IF;
2106          x_amount := ln_rounded_amount;
2107          RETURN lv_return_status;
2108       ELSE
2109          RAISE OKL_API.G_EXCEPTION_ERROR;
2110       END IF;
2111     EXCEPTION
2112       WHEN OTHERS THEN
2113         lv_return_status := OKL_API.G_RET_STS_ERROR;
2114         RETURN lv_return_status;
2115     END round_amount;
2116   BEGIN
2117 
2118     x_return_status := Okl_Api.G_RET_STS_SUCCESS;
2119     -- Call start_activity to create savepoint, check compatibility
2120     -- and initialize message list
2121     x_return_status := Okl_Api.START_ACTIVITY (
2122                                l_api_name
2123                                ,p_init_msg_list
2124                                ,'_PVT'
2125                                ,x_return_status);
2126     -- Check if activity started successfully
2127     IF (x_return_status = Okl_Api.G_RET_STS_UNEXP_ERROR) THEN
2128        RAISE Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR;
2129     ELSIF (x_return_status = Okl_Api.G_RET_STS_ERROR) THEN
2130        RAISE Okl_Api.G_EXCEPTION_ERROR;
2131     END IF;
2132 
2133     IF l_selv_tbl.COUNT > 0 THEN
2134        --If the org_id or the currency code is not passed to the function , only
2135        --then is the cursor executed.
2136 
2137        IF (ln_org_id IS NULL) OR (lv_currency_code IS NULL) THEN
2138          OPEN  get_org_id(p_chr_id => ln_chr_id);
2139          FETCH get_org_id INTO ln_org_id,
2140                             lv_currency_code;
2141          IF get_org_id%NOTFOUND THEN
2142            OKL_API.set_message(p_app_name     => G_APP_NAME,
2143                             p_msg_name     => g_no_match_rec,
2144                             p_token1       => g_col_name_token,
2145                             p_token1_value => 'Contract id');
2146            RAISE g_stop_round_exp;
2147          END IF;
2148          CLOSE get_org_id;
2149        END IF;
2150 
2151        -- we need to set the context since the records in
2152        -- OKL_SYS_ACCT_OPTS table are stored with regards to the context
2153        x_return_status      := OKL_API.G_RET_STS_SUCCESS;
2154 
2155        --If the apply rounding diff rule is not passed to the function , only
2156        --then is the cursor executed.
2157        IF (lv_diff_lookup_code IS NULL) THEN
2158           -- IF we have diff btw rounding amounts
2159           -- now we decide by the below select stmt
2160           -- As to where we need to adjust the amount
2161           OPEN  get_rnd_diff_lookup(p_lookup_type => g_rnd_diff_lookup_type);
2162           FETCH get_rnd_diff_lookup INTO lv_diff_lookup_code;
2163           IF get_rnd_diff_lookup%NOTFOUND THEN
2164             OKL_API.set_message(p_app_name     => G_APP_NAME,
2165                                 p_msg_name     => g_no_match_rec,
2166                                 p_token1       => g_col_name_token,
2167                                 p_token1_value => 'Rounding Diff Lookup');
2168             RAISE g_stop_round_exp;
2169           END IF;
2170           CLOSE get_rnd_diff_lookup;
2171        END IF;
2172 
2173        --If the rounding rule is not passed to the function , only
2174        --then is the cursor executed.
2175        IF (lv_rounding_rule IS NULL) THEN
2176           -- Get the Rule to Round the amount
2177           OPEN get_rounding_rule;
2178           FETCH get_rounding_rule INTO lv_rounding_rule;
2179           IF get_rounding_rule%NOTFOUND THEN
2180              OKL_API.set_message(p_app_name     => G_APP_NAME,
2181                                  p_msg_name     => g_no_match_rec,
2182                                  p_token1       => g_col_name_token,
2183                                  p_token1_value => 'Rounding Rule');
2184              RAISE g_rounding_error;
2185           END IF;
2186           CLOSE get_rounding_rule;
2187         END IF;
2188       -- Modified by kthiruva on 02-Dec-2004
2189       -- Bug 4048047 - Start of Changes
2190       -- If the Apply Rounding Diff is ADD_TO_FIRST or ADD_TO_LAST then then the first and the last
2191       -- stream element records need to be determined.The first and last stream element record for
2192       -- a particular stream header is identified by checking for the min and max stream element date.
2193 
2194       IF lv_diff_lookup_code = g_first_lookup_code THEN
2195          l_first_rec_index := l_selv_tbl.FIRST;
2196          l_min_date        := l_selv_tbl(l_selv_tbl.FIRST).stream_element_date;
2197       ELSIF lv_diff_lookup_code = g_last_lookup_Code THEN
2198          l_last_rec_index  := l_selv_tbl.LAST;
2199          l_max_date        := l_Selv_tbl(l_selv_tbl.LAST).stream_element_date;
2200       END IF;
2201       -- Bug 4048047 - End of Changes
2202 
2203       -- Need to handle the -ve amount seprately
2204       -- since 0 is allways greater than -ve amounts
2205       IF lv_diff_lookup_code = g_high_lookup_code THEN
2206         IF SIGN(l_selv_tbl(l_selv_tbl.FIRST).amount) = -1 THEN
2207           ln_grter_amt :=  l_selv_tbl(l_selv_tbl.FIRST).amount;
2208         END IF;
2209       END IF;
2210 
2211       -- Now we scan the Stream element PL/SQL table of records
2212       -- Sum up all the amounts
2213       FOR i IN l_selv_tbl.FIRST..l_selv_tbl.LAST LOOP
2214         ln_tot_no_rnd_amount := ln_tot_no_rnd_amount + l_selv_tbl(i).amount;
2215         IF l_selv_tbl(i).amount > ln_grter_amt THEN
2216           ln_grter_amt := l_selv_tbl(i).amount;
2217           ln_grter_amt_ind := i;
2218         END IF;
2219         -- Added by kthiruva on 02-Dec-2004
2220         -- Bug 4048047 - Start of Changes
2221         -- Check to see if there is a stream element with a stream_element_date less than l_min_date.
2222         -- If so, the l_first_rec_index is reset.
2223         IF trunc(l_selv_tbl(i).stream_element_date) < trunc(l_min_date) THEN
2224            l_min_date        := l_selv_tbl(i).stream_element_date;
2225            l_first_rec_index := i;
2226         END IF;
2227         -- Check to see if there is a stream element with a stream_element_date greater than l_max_date.
2228         -- If so, the l_last_rec_index is reset.
2229         IF trunc(l_selv_tbl(i).stream_element_date) > trunc(l_max_date) THEN
2230            l_max_date       := l_selv_tbl(i).stream_element_date;
2231            l_last_rec_index := i;
2232         END IF;
2233         -- Bug 4048047 - End of Changes
2234       END LOOP;
2235 
2236       --If the precision is not passed to the function , only
2237       --then is the cursor executed.
2238       IF (ln_precision1 IS NULL) THEN
2239         -- Get the precision for the amounts to Round
2240         -- Depending on the Currency code
2241         OPEN get_precision(p_currency_code => lv_currency_code);
2242         FETCH get_precision INTO ln_precision1;
2243         IF get_precision%NOTFOUND THEN
2244           OKL_API.set_message(p_app_name     => G_APP_NAME,
2245                             p_msg_name     => g_no_match_rec,
2246                             p_token1       => g_col_name_token,
2247                             p_token1_value => 'Currency Code');
2248           RAISE g_rounding_error;
2249         END IF;
2250         CLOSE get_precision;
2251       END IF;
2252 
2253 
2254 --sgorantl(bug#3797982) start change
2255       ln_tot_no_rnd_amount := ROUND(ln_tot_no_rnd_amount,ln_precision1);
2256 --sgorantl(bug#3797982) end change
2257 
2258       -- If the first value is 0 and ln_grter_amt = 0
2259       -- then we return the first record for adjustment
2260       IF lv_diff_lookup_code = g_high_lookup_code THEN
2261         IF ln_grter_amt_ind = 0 THEN
2262           ln_grter_amt := l_selv_tbl(l_selv_tbl.FIRST).amount;
2263           ln_grter_amt_ind := l_selv_tbl.FIRST;
2264         END IF;
2265       END IF;
2266       -- Now we scan the Stream element PL/SQL table of records
2267       -- Sum up all the amounts after rounding depending on currency_code
2268       FOR i IN l_selv_tbl.FIRST..l_selv_tbl.LAST LOOP
2269         x_return_status := round_amount(p_currency_code => lv_currency_code,
2270                                         p_add_precision => 0,
2271                                         p_amount        => l_selv_tbl(i).amount,
2272                                         x_amount        => ln_rounded_amount,
2273                                         p_precision     => ln_precision1,
2274                                         p_rounding_rule => lv_rounding_rule);
2275         IF x_return_status <> OKL_API.G_RET_STS_SUCCESS THEN
2276           EXIT WHEN (x_return_status <> OKL_API.G_RET_STS_SUCCESS);
2277         END IF;
2278         ln_tot_rnd_amount := ln_tot_rnd_amount + ln_rounded_amount;
2279         -- We re-populate the rounded amount into the PL/SQL table of records
2280         -- So that we can give the same as output if there is diff
2281         -- btw ln_tot_no_rnd_amount and ln_tot_rnd_amount
2282         l_selv_tbl(i).amount := ln_rounded_amount;
2283       END LOOP;
2284       IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
2285         RAISE g_stop_round_exp;
2286       END IF;
2287       -- Now we will see the diff btw ln_tot_no_rnd_amount and ln_tot_rnd_amount
2288       -- IF there is diff then as done below
2289       IF ln_tot_no_rnd_amount <> ln_tot_rnd_amount THEN
2290         -- If the diff correction rule is First then
2291 
2292         IF lv_diff_lookup_code = g_first_lookup_code THEN
2293           -- If the Diff Amount is +ve then we add to the first record of
2294           -- pl/sql record of the table
2295           ln_diff_amount := ln_tot_no_rnd_amount - ln_tot_rnd_amount;
2296           -- Since the pl/sql table of records come in as not rounded
2297           -- and in the above we round the pl/sql table of records
2298           -- and since we need to do the corrections only on the rounded amont
2299           -- hence we need to round the ln_diff_amount variable also.
2300           x_return_status := round_amount(p_currency_code => lv_currency_code,
2301                                           p_add_precision => 0,
2302                                           p_amount        => ln_diff_amount,
2303                                           x_amount        => ln_rnd_diff_amount,
2304                                           p_precision     => ln_precision1,
2305                                           p_rounding_rule => lv_rounding_rule);
2306           IF x_return_status <> OKL_API.G_RET_STS_SUCCESS THEN
2307             RAISE g_stop_round_exp;
2308           END IF;
2309           IF SIGN(ln_rnd_diff_amount) = 1 THEN
2310             -- Modified by kthiruva on 02-Dec-2004
2311             -- Bug 4048047 - Start of Changes
2312             l_selv_tbl(l_first_rec_index).amount := l_selv_tbl(l_first_rec_index).amount + ln_rnd_diff_amount;
2313             --Bug 4048047 - End of Changes
2314           -- If the Diff Amount is -ve then we substract from the first record of
2315           -- pl/sql record of the table
2316           ELSIF SIGN(ln_rnd_diff_amount) = -1 THEN
2317             ln_diff_amount := ln_tot_rnd_amount- ln_tot_no_rnd_amount ;
2318             -- Since the pl/sql table of records come in as not rounded
2319             -- and in the above we round the pl/sql table of records
2320             -- and since we need to do the corrections only on the rounded amont
2321             -- hence we need to round the ln_diff_amount variable also.
2322             x_return_status := round_amount(p_currency_code => lv_currency_code,
2323                                             p_add_precision => 0,
2324                                             p_amount        => ln_diff_amount,
2325                                             x_amount        => ln_rnd_diff_amount,
2326                                             p_precision     => ln_precision1,
2327                                             p_rounding_rule => lv_rounding_rule);
2328             IF x_return_status <> OKL_API.G_RET_STS_SUCCESS THEN
2329               RAISE g_stop_round_exp;
2330             END IF;
2331             -- Modified by kthiruva on 02-Dec-2004
2332             -- Bug 4048047 - Start of Changes
2333             l_selv_tbl(l_first_rec_index).amount := l_selv_tbl(l_first_rec_index).amount - (ln_rnd_diff_amount);
2334             -- Bug 4048047 - End Of Changes
2335           END IF;
2336         -- If the diff correction rule is Last then
2337         ELSIF lv_diff_lookup_code = g_last_lookup_code THEN
2338           -- If the Diff Amount is +ve then we add to the last record of
2339           -- pl/sql record of the table
2340           ln_diff_amount := ln_tot_no_rnd_amount - ln_tot_rnd_amount;
2341           -- Since the pl/sql table of records come in as not rounded
2342           -- and in the above we round the pl/sql table of records
2343           -- and since we need to do the corrections only on the rounded amont
2344           -- hence we need to round the ln_diff_amount variable also.
2345           x_return_status := round_amount(p_currency_code => lv_currency_code,
2346                                           p_add_precision => 0,
2347                                           p_amount        => ln_diff_amount,
2348                                           x_amount        => ln_rnd_diff_amount,
2349                                           p_precision     => ln_precision1,
2350                                           p_rounding_rule => lv_rounding_rule);
2351           IF x_return_status <> OKL_API.G_RET_STS_SUCCESS THEN
2352             RAISE g_stop_round_exp;
2353           END IF;
2354           IF SIGN(ln_rnd_diff_amount) = 1 THEN
2355             -- Modified by kthiruva on 02-Dec-2004
2356             -- Bug 4048047 - Start of Changes
2357             l_selv_tbl(l_last_rec_index).amount := l_selv_tbl(l_last_rec_index).amount + (ln_rnd_diff_amount);
2358             -- Bug 4048047 - End of Changes
2359           -- If the Diff Amount is -ve then we substract from the last record of
2360           -- pl/sql record of the table
2361           ELSIF SIGN(ln_rnd_diff_amount) = -1 THEN
2362             ln_diff_amount := ln_tot_rnd_amount- ln_tot_no_rnd_amount ;
2363             -- Since the pl/sql table of records come in as not rounded
2364             -- and in the above we round the pl/sql table of records
2365             -- and since we need to do the corrections only on the rounded amont
2366             -- hence we need to round the ln_diff_amount variable also.
2367             x_return_status := round_amount(p_currency_code => lv_currency_code,
2368                                             p_add_precision => 0,
2369                                             p_amount        => ln_diff_amount,
2370                                             x_amount        => ln_rnd_diff_amount,
2371                                             p_precision     => ln_precision1,
2372                                             p_rounding_rule => lv_rounding_rule);
2373             IF x_return_status <> Okl_Api.G_RET_STS_SUCCESS THEN
2374               RAISE g_stop_round_exp;
2375             END IF;
2376             -- Modified by kthiruva on 02-Dec-2004
2377             -- Bug 4048047 - Start of Changes
2378             --Modified by kthiruva for Bug 4730902 on 22-Nov-2005.
2379             --The amount needs to be subtracted when the diff is negative
2380             l_selv_tbl(l_last_rec_index).amount := l_selv_tbl(l_last_rec_index).amount - (ln_rnd_diff_amount);
2381             -- Bug 4048047 - End of Changes
2382           END IF;
2383         -- If the diff correction rule is High Amount then
2384         ELSIF lv_diff_lookup_code = g_high_lookup_code  THEN
2385           ln_diff_amount := ln_tot_no_rnd_amount - ln_tot_rnd_amount;
2386           -- Since the pl/sql table of records come in as not rounded
2387           -- and in the above we round the pl/sql table of records
2388           -- and since we need to do the corrections only on the rounded amont
2389           -- hence we need to round the ln_diff_amount variable also.
2390           x_return_status := round_amount(p_currency_code => lv_currency_code,
2391                                           p_add_precision => 0,
2392                                           p_amount        => ln_diff_amount,
2393                                           x_amount        => ln_rnd_diff_amount,
2394                                           p_precision     => ln_precision1,
2395                                           p_rounding_rule => lv_rounding_rule);
2396           IF x_return_status <> OKL_API.G_RET_STS_SUCCESS THEN
2397             RAISE g_stop_round_exp;
2398           END IF;
2399           -- If the Diff Amount is +ve then we add to the High amount record of
2400           -- pl/sql record of the table
2401           IF SIGN(ln_rnd_diff_amount) = 1 THEN
2402             l_selv_tbl(ln_grter_amt_ind).amount := l_selv_tbl(ln_grter_amt_ind).amount + (ln_rnd_diff_amount);
2403           -- If the Diff Amount is -ve then we substract from the High amount record of
2404           -- pl/sql record of the table
2405           ELSIF SIGN(ln_rnd_diff_amount) = -1 THEN
2406             ln_diff_amount := ln_tot_rnd_amount- ln_tot_no_rnd_amount ;
2407             -- Since the pl/sql table of records come in as not rounded
2408             -- and in the above we round the pl/sql table of records
2409             -- and since we need to do the corrections only on the rounded amont
2410             -- hence we need to round the ln_diff_amount variable also.
2411             x_return_status := round_amount(p_currency_code => lv_currency_code,
2412                                             p_add_precision => 0,
2413                                             p_amount        => ln_diff_amount,
2414                                             x_amount        => ln_rnd_diff_amount,
2415                                             p_precision     => ln_precision1,
2416                                             p_rounding_rule => lv_rounding_rule);
2417 
2418             IF x_return_status <> OKL_API.G_RET_STS_SUCCESS THEN
2419               RAISE g_stop_round_exp;
2420             END IF;
2421             l_selv_tbl(ln_grter_amt_ind).amount := l_selv_tbl(ln_grter_amt_ind).amount - (ln_rnd_diff_amount);
2422           END IF;
2423         END IF;
2424         -- There is diff so we set the o/p record with modified record derived above
2425         x_selv_tbl := l_selv_tbl;
2426       ELSIF ln_tot_no_rnd_amount = ln_tot_rnd_amount THEN
2427         -- There is no diff so we set the i/p record back o/p record
2428         --Modified by dpsingh on 02-Feb-2006.          x_selv_tbl := p_selv_tbl;
2429          --Even when there is no rounding diff, the rounded table l_selv_tbl should only be returned
2430          --The unrounded table is being returned incorrectly
2431          --Bug 4559800(H) - Start of Changes
2432          x_selv_tbl := l_selv_tbl;
2433          --Bug 4559800(H) - End of Changes
2434       END IF;
2435     ELSE
2436       Okl_Api.set_message(p_app_name      => G_APP_NAME,
2437                           p_msg_name      => G_INVALID_VALUE,
2438                           p_token1        => G_COL_NAME_TOKEN,
2439                           p_token1_value  => 'p_selv_tbl');
2440       RAISE g_stop_round_exp;
2441     END IF;
2442 
2443     Okl_Api.END_ACTIVITY (x_msg_count,
2444                           x_msg_data );
2445     RETURN x_return_status;
2446   EXCEPTION
2447      WHEN g_rounding_error THEN
2448         IF get_precision%ISOPEN THEN
2449           CLOSE get_precision;
2450         END IF;
2451         lv_return_status := Okl_Api.G_RET_STS_ERROR;
2452         RETURN lv_return_status;
2453     WHEN g_stop_round_exp THEN
2454       IF get_rnd_diff_lookup%ISOPEN THEN
2455         CLOSE get_rnd_diff_lookup;
2456       END IF;
2457       IF get_org_id%ISOPEN THEN
2458         CLOSE get_org_id;
2459       END IF;
2460       x_return_status := Okl_Api.HANDLE_EXCEPTIONS(
2461                                  l_api_name,
2462                                  G_PKG_NAME,
2463                                  'OKL_API.G_RET_STS_ERROR',
2464                                  x_msg_count,
2465                                  x_msg_data,
2466                                  '_PVT');
2467       RETURN x_return_status;
2468     WHEN OTHERS THEN
2469       IF get_rnd_diff_lookup%ISOPEN THEN
2470         CLOSE get_rnd_diff_lookup;
2471       END IF;
2472       IF get_org_id%ISOPEN THEN
2473         CLOSE get_org_id;
2474       END IF;
2475       x_return_status :=Okl_Api.HANDLE_EXCEPTIONS(
2476                                 l_api_name,
2477                                 G_PKG_NAME,
2478                                 'OTHERS',
2479                                 x_msg_count,
2480                                 x_msg_data,
2481                                 '_PVT');
2482       RETURN x_return_status;
2483   END round_streams_amount_esg;
2484   --Bug 4196515-End of Changes
2485 
2486   -- Added by RGOOTY: Start
2487   PROCEDURE get_acc_options(    p_khr_id         IN  okc_k_headers_b.ID%TYPE,
2488                                 x_org_id         OUT NOCOPY okc_k_headers_b.authoring_org_id%TYPE,
2489                                 x_precision      OUT NOCOPY NUMBER,
2490                                 x_currency_code  OUT NOCOPY okc_k_headers_b.currency_code%TYPE,
2491                                 x_rounding_rule  OUT NOCOPY okl_sys_acct_opts.stm_rounding_rule%TYPE,
2492                                 x_apply_rnd_diff OUT NOCOPY okl_sys_acct_opts.stm_apply_rounding_difference%TYPE,
2493                                 x_return_status  OUT NOCOPY VARCHAR2 ) IS
2494 
2495   CURSOR get_org_id(p_chr_id  okc_k_headers_b.id%TYPE)
2496   IS
2497     SELECT authoring_org_id,
2498            currency_code
2499     FROM okc_k_headers_b
2500     WHERE id = p_chr_id;
2501 
2502   CURSOR get_precision(p_currency_code OKC_K_HEADERS_B.CURRENCY_CODE%TYPE)
2503   IS
2504       SELECT PRECISION
2505       FROM fnd_currencies_vl
2506       WHERE currency_code = p_currency_code
2507         AND enabled_flag = 'Y'
2508         AND NVL(start_date_active, SYSDATE) <= SYSDATE
2509         AND NVL(end_date_active, SYSDATE) >= SYSDATE;
2510 
2511   CURSOR get_rounding_rule
2512   IS
2513       SELECT stm_rounding_rule
2514       FROM OKL_SYS_ACCT_OPTS;
2515 
2516   CURSOR get_rnd_diff_lookup(p_lookup_type  fnd_lookups.lookup_type%TYPE)
2517   IS
2518     SELECT b.stm_apply_rounding_difference
2519     FROM fnd_lookups a,
2520          OKL_SYS_ACCT_OPTS b
2521     WHERE a.lookup_type = p_lookup_type
2522     AND a.lookup_code = b.stm_apply_rounding_difference;
2523 
2524   l_org_id              OKC_K_HEADERS_B.AUTHORING_ORG_ID%TYPE;
2525   l_currency_code       okc_k_headers_b.currency_code%type;
2526   l_diff_lookup_code    fnd_lookups.lookup_code%type;
2527   l_precision           number;
2528   l_rounding_rule       okl_sys_acct_opts.ael_rounding_rule%type;
2529 
2530   l_return_status       VARCHAR2(3)  := Okl_Api.G_RET_STS_SUCCESS;
2531 
2532   G_NO_MATCH_REC           CONSTANT VARCHAR2(30) := 'OKL_LLA_NO_MATCHING_RECORD';
2533   G_INVALID_VALUE          CONSTANT VARCHAR2(200) := 'OKL_INVALID_VALUE ';
2534   G_RND_DIFF_LOOKUP_TYPE   CONSTANT FND_LOOKUPS.LOOKUP_TYPE%TYPE := 'OKL_STRM_APPLY_ROUNDING_DIFF';
2535   G_COL_NAME_TOKEN         CONSTANT  VARCHAR2(200) := OKL_API.G_COL_NAME_TOKEN;
2536 
2537   BEGIN
2538     -- Get the Org Id, Currency Code
2539     OPEN  get_org_id(p_chr_id => p_khr_id);
2540     FETCH get_org_id INTO l_org_id,l_currency_code;
2541     IF get_org_id%NOTFOUND THEN
2542         OKL_API.set_message(p_app_name     => G_APP_NAME,
2543                                     p_msg_name     => G_NO_MATCH_REC,
2544                                     p_token1       => G_COL_NAME_TOKEN,
2545                                     p_token1_value => 'Contract id');
2546         RAISE G_EXCEPTION_ERROR;
2547     END IF;
2548     CLOSE get_org_id;
2549 
2550     -- Get Rounding Difference Lookup
2551     OPEN  get_rnd_diff_lookup(p_lookup_type => G_RND_DIFF_LOOKUP_TYPE);
2552     FETCH get_rnd_diff_lookup INTO L_diff_lookup_code;
2553     IF get_rnd_diff_lookup%NOTFOUND THEN
2554         OKL_API.set_message(p_app_name     => G_APP_NAME,
2555                             p_msg_name     => G_NO_MATCH_REC,
2556                             p_token1       => G_COL_NAME_TOKEN,
2557                             p_token1_value => 'Rounding Diff Lookup');
2558         RAISE G_EXCEPTION_ERROR;
2559     END IF;
2560     CLOSE get_rnd_diff_lookup;
2561 
2562     -- Get the Precision
2563     OPEN get_precision(p_currency_code => l_currency_code);
2564     FETCH get_precision INTO l_precision;
2565     IF get_precision%NOTFOUND THEN
2566         OKL_API.set_message(p_app_name     => G_APP_NAME,
2567                             p_msg_name     => G_NO_MATCH_REC,
2568                             p_token1       => G_COL_NAME_TOKEN,
2569                             p_token1_value => 'Currency Code');
2570         RAISE G_EXCEPTION_ERROR;
2571     END IF;
2572     CLOSE get_precision;
2573     -- Get the Rounding Rule
2574     OPEN get_rounding_rule;
2575     FETCH get_rounding_rule INTO l_rounding_rule;
2576     IF get_rounding_rule%NOTFOUND THEN
2577         OKL_API.set_message(p_app_name     => G_APP_NAME,
2578                             p_msg_name     => G_NO_MATCH_REC,
2579                             p_token1       => G_COL_NAME_TOKEN,
2580                             p_token1_value => 'Rounding Rule');
2581         RAISE G_EXCEPTION_ERROR;
2582     END IF;
2583     CLOSE get_rounding_rule;
2584 
2585     x_org_id              := l_org_id;
2586     x_currency_code       := l_currency_code;
2587     x_apply_rnd_diff      := l_diff_lookup_code;
2588     x_precision           := l_precision;
2589     x_rounding_rule       := l_rounding_rule;
2590     x_return_status       := l_return_status;
2591 
2592   EXCEPTION
2593       WHEN G_EXCEPTION_ERROR THEN
2594          IF get_org_id%ISOPEN THEN
2595     	    CLOSE get_org_id;
2596     	 END IF;
2597          IF get_precision%ISOPEN THEN
2598     	    CLOSE get_precision;
2599     	 END IF;
2600          IF get_rounding_rule%ISOPEN THEN
2601     	    CLOSE get_rounding_rule;
2602     	 END IF;
2603          IF get_rnd_diff_lookup%ISOPEN THEN
2604     	    CLOSE get_rnd_diff_lookup;
2605     	 END IF;
2606          x_return_status := Okl_Api.G_RET_STS_ERROR ;
2607 
2608       WHEN OTHERS THEN
2609          IF get_org_id%ISOPEN THEN
2610     	    CLOSE get_org_id;
2611     	 END IF;
2612          IF get_precision%ISOPEN THEN
2613     	    CLOSE get_precision;
2614     	 END IF;
2615          IF get_rounding_rule%ISOPEN THEN
2616     	    CLOSE get_rounding_rule;
2617     	 END IF;
2618          IF get_rnd_diff_lookup%ISOPEN THEN
2619     	    CLOSE get_rnd_diff_lookup;
2620     	 END IF;
2621          x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
2622   END get_acc_options;
2623 
2624   -- Added by RGOOTY: End
2625 
2626 -- Added by RGOOTY: Start
2627   --Modified bu kthiruva on 30-May-2005. The OUT param was made NOCOPY
2628   --Bug 4374085 - Start of Changes
2629   PROCEDURE accumulate_strm_headers(
2630     p_stmv_rec       IN            Okl_Streams_Pub.stmv_rec_type,
2631     x_full_stmv_tbl  IN OUT NOCOPY Okl_Streams_Pub.stmv_tbl_type,
2632     x_return_status  OUT NOCOPY    VARCHAR2)
2633   --Bug 4374085 - End of Change
2634  AS
2635     stmv_count        NUMBER;
2636     l_return_status   VARCHAR2(1);
2637   BEGIN
2638     -- Intialize the return status
2639     l_return_status := OKL_API.G_RET_STS_SUCCESS;
2640     stmv_count := x_full_stmv_tbl.count;
2641     IF ( stmv_count > 0)
2642     THEN
2643       -- Increment the current Index
2644       stmv_count := x_full_stmv_tbl.LAST + 1;
2645     ELSE
2646       stmv_count  := 1;
2647     END IF;
2648     --  Append it to the x_full_stmv_tbl
2649     x_full_stmv_tbl(stmv_count) := p_stmv_rec;
2650 
2651     -- Return the status
2652     x_return_Status := l_return_status;
2653   EXCEPTION
2654     WHEN OKL_API.G_EXCEPTION_ERROR
2655     THEN
2656       x_return_status := G_RET_STS_ERROR;
2657     WHEN OKL_API.G_EXCEPTION_UNEXPECTED_ERROR
2658     THEN
2659       x_return_status := G_RET_STS_UNEXP_ERROR;
2660     WHEN OTHERS
2661     THEN
2662       OKL_API.SET_MESSAGE (
2663         p_app_name     => G_APP_NAME,
2664         p_msg_name     => 'OKL_DB_ERROR',
2665         p_token1       => 'PROG_NAME',
2666         p_token1_value => 'accumulate_strm_headers',
2667         p_token2       => G_SQLCODE_TOKEN,
2668         p_token2_value => sqlcode,
2669         p_token3       => G_SQLERRM_TOKEN,
2670         p_token3_value => sqlerrm);
2671       x_return_status := G_RET_STS_UNEXP_ERROR;
2672   END accumulate_strm_headers;
2673 
2674   --Modified bu kthiruva on 30-May-2005. The OUT param was made NOCOPY
2675   --Bug 4374085 - Start of Changes
2676   PROCEDURE accumulate_strm_elements(
2677     p_stm_index_no   IN            NUMBER,
2678     p_selv_tbl       IN            okl_streams_pub.selv_tbl_type,
2679     x_full_selv_tbl  IN OUT NOCOPY okl_streams_pub.selv_tbl_type,
2680     x_return_status  OUT NOCOPY    VARCHAR2)
2681   --Bug 4374085 - End of Changes
2682   AS
2683     selv_count        NUMBER;
2684     full_selv_count   NUMBER;
2685     i                 NUMBER; -- Index to loop through the Stream Elements table p_selv_tbl
2686     l_return_status   VARCHAR2(1);
2687   BEGIN
2688     -- Intialize the return status
2689     l_return_status := OKL_API.G_RET_STS_SUCCESS;
2690     full_selv_count := x_full_selv_tbl.count;
2691     IF (full_selv_count > 0)
2692     THEN
2693       selv_count := x_full_selv_tbl.LAST + 1;
2694     ELSE
2695       selv_count  := 1;
2696     END IF;
2697     -- Loop through the Stream Elements table and
2698     --  append it to the x_full_Selv_tbl
2699     FOR i in p_selv_tbl.FIRST .. p_selv_tbl.LAST
2700     LOOP
2701       IF p_selv_tbl.EXISTS(i)
2702       THEN
2703         x_full_selv_tbl(selv_count) := p_selv_tbl(i);
2704         -- Store the Parent Index number per each Stream Element Level
2705         IF p_stm_index_no IS NOT NULL
2706         THEN
2707           x_full_selv_tbl(selv_count).parent_index := p_stm_index_no;
2708         END IF;
2709         selv_count := selv_count + 1;
2710       END IF;
2711     END LOOP;
2712     x_return_Status := l_return_status;
2713 
2714   EXCEPTION
2715     WHEN OKL_API.G_EXCEPTION_ERROR
2716     THEN
2717       x_return_status := G_RET_STS_ERROR;
2718     WHEN OKL_API.G_EXCEPTION_UNEXPECTED_ERROR
2719     THEN
2720       x_return_status := G_RET_STS_UNEXP_ERROR;
2721     WHEN OTHERS
2722     THEN
2723       OKL_API.SET_MESSAGE (
2724         p_app_name     => G_APP_NAME,
2725         p_msg_name     => 'OKL_DB_ERROR',
2726         p_token1       => 'PROG_NAME',
2727         p_token1_value => 'accumulate_strm_elements',
2728         p_token2       => G_SQLCODE_TOKEN,
2729         p_token2_value => sqlcode,
2730         p_token3       => G_SQLERRM_TOKEN,
2731         p_token3_value => sqlerrm);
2732       x_return_status := G_RET_STS_UNEXP_ERROR;
2733   END accumulate_strm_elements;
2734   -- Added by RGOOTY: End
2735 
2736   -- Added by kthiruva on 10-Oct-2005
2737   -- Bug 4664698 - Start of changes
2738   --------------------------------------------------------------------------------
2739   -- Start of Commnets
2740   -- Procedure Name       : get_line_id
2741   -- Description          : Fetches the contract line id from the stream interface
2742   --                        tables during the inbound processing
2743   --
2744   -- Business Rules       : Returns kle_id
2745   -- Parameters           : p_trx_number    - Transaction number of the pricing
2746   --                                          request
2747   --                        p_index_number  - The index number which uniquely
2748   --                                          defines every asset line
2749   -- Returns                x_kle_id        - Id of the asset
2750   --                        x_return_status - Return Status of the API
2751   -- Version              : kthiruva 1.0 Created
2752   -- End of Commnets
2753   --------------------------------------------------------------------------------
2754   PROCEDURE get_line_id(
2755     p_trx_number     IN         okl_stream_interfaces.TRANSACTION_NUMBER%TYPE,
2756     p_index_number   IN         okl_sif_ret_levels.INDEX_NUMBER%TYPE,
2757     x_kle_id         OUT NOCOPY NUMBER,
2758     x_return_status  OUT NOCOPY VARCHAR2)
2759   AS
2760    --Curosor to fetch the line_id from the stream interface tables
2761    CURSOR kle_id_csr(p_trx_number IN NUMBER,
2762                      p_index_number IN NUMBER)
2763    IS
2764    SELECT    SILB.KLE_ID
2765    FROM OKL_SIF_RET_LEVELS SRLB,
2766         OKL_SIF_RETS SIRB,
2767         OKL_STREAM_INTERFACES SIFB,
2768         OKL_SIF_LINES SILB
2769    WHERE SIFB.TRANSACTION_NUMBER = p_trx_number
2770    AND SIRB.TRANSACTION_NUMBER = SIFB.TRANSACTION_NUMBER
2771    AND SILB.SIF_ID = SIFB.ID
2772    AND SRLB.SIR_ID = SIRB.ID
2773    AND SRLB.INDEX_NUMBER = SILB.INDEX_NUMBER
2774    AND SRLB.INDEX_NUMBER = p_index_number;
2775 
2776    l_kle_id           NUMBER;
2777    g_no_match_rec           CONSTANT VARCHAR2(30) := 'OKL_LLA_NO_MATCHING_RECORD';
2778    g_col_name_token         CONSTANT  VARCHAR2(200) := Okl_Api.G_COL_NAME_TOKEN;
2779 
2780 
2781   BEGIN
2782     -- Intialize the return status
2783     x_return_status := OKL_API.G_RET_STS_SUCCESS;
2784 
2785     OPEN kle_id_csr(p_trx_number   => p_trx_number,
2786                     p_index_number => p_index_number);
2787 
2788     FETCH kle_id_csr INTO l_kle_id;
2789     IF kle_id_csr%NOTFOUND THEN
2790         OKL_API.set_message(p_app_name     => G_APP_NAME,
2791                             p_msg_name     => G_NO_MATCH_REC,
2792                             p_token1       => G_COL_NAME_TOKEN,
2793                             p_token1_value => 'Contract Line Id');
2794         RAISE G_EXCEPTION_ERROR;
2795     END IF;
2796     CLOSE kle_id_csr;
2797     --Assigning the line_id fetched to the return parameter
2798     x_kle_id := l_kle_id;
2799   EXCEPTION
2800    WHEN Okl_Api.G_EXCEPTION_ERROR THEN
2801      IF kle_id_csr%ISOPEN THEN
2802 	    CLOSE kle_id_csr;
2803 	 END IF;
2804      x_return_status := Okl_Api.G_RET_STS_ERROR ;
2805    WHEN Okl_Api.G_EXCEPTION_UNEXPECTED_ERROR THEN
2806      IF kle_id_csr%ISOPEN THEN
2807 	    CLOSE kle_id_csr;
2808 	 END IF;
2809      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
2810    WHEN OTHERS THEN
2811      IF kle_id_csr%ISOPEN THEN
2812 	    CLOSE kle_id_csr;
2813 	 END IF;
2814      x_return_status := Okl_Api.G_RET_STS_UNEXP_ERROR;
2815   END get_line_id;
2816   -- Bug 4664698 - End of Changes
2817 
2818 procedure get_k_trx_state(p_trx_id IN number,
2819 						  x_rebook_type OUT NOCOPY VARCHAR2,
2820 						  x_rebook_date OUT NOCOPY DATE,
2821 						  x_query_trx_state OUT NOCOPY VARCHAR2,
2822                           x_trx_state OUT NOCOPY CLOB) IS
2823 
2824     CURSOR get_orig_contract_csr( p_khr_id    IN NUMBER)
2825     IS
2826     SELECT rbk_chr.contract_number       rbk_contract_number,
2827            rbk_chr.orig_system_id1       original_chr_id,
2828            trx.rbr_code                  rbk_reason_code,
2829            trx.date_transaction_occurred revision_date,
2830            'ONLINE_REBOOK'               rebook_type
2831            ,rbk_chr.start_date           rbk_chr_start_date
2832            ,orig_chr.start_date          orig_chr_start_date
2833       FROM okc_k_headers_all_b   rbk_chr,
2834            okc_k_headers_all_b   orig_chr,
2835            okl_trx_contracts_all trx
2836      WHERE rbk_chr.id = p_khr_id
2837        AND rbk_chr.orig_system_source_code = 'OKL_REBOOK'
2838        AND trx.khr_id_new = rbk_chr.id
2839        AND trx.tsu_code = 'ENTERED'
2840        AND trx.tcn_type = 'TRBK'
2841        AND rbk_chr.orig_system_id1 = orig_chr.id
2842     UNION
2843     SELECT orig_chr.contract_number       rbk_contract_number,
2844            orig_chr.id                    original_chr_id,
2845            trx.rbr_code                   rbk_reason_code,
2846            trx.date_transaction_occurred  revision_date,
2847            'MASS_REBOOK'                  rebook_type
2848            ,orig_chr.start_date           rbk_chr_start_date
2849            ,orig_chr.start_date           orig_chr_start_date
2850       FROM okc_k_headers_all_b orig_chr,
2851            okl_trx_contracts_all trx
2852      WHERE  orig_chr.id    =  p_khr_id
2853       AND  trx.khr_id     =  orig_chr.id
2854       AND  trx.tsu_code   = 'ENTERED'
2855       AND  trx.tcn_type   = 'TRBK'
2856       AND  EXISTS
2857            (
2858             SELECT '1'
2859               FROM okl_rbk_selected_contract rbk_chr
2860              WHERE rbk_chr.khr_id = orig_chr.id
2861                AND rbk_chr.status <> 'PROCESSED'
2862             );
2863   l_contract_number VARCHAR2(120);
2864   l_contract_id     number;
2865   l_rbk_reason_code varchar2(30);
2866   l_revision_date    date;
2867   l_rebook_type     varchar2(15);
2868   l_purpose_code    varchar2(15);
2869 
2870   cursor get_clob(p_contract_id  IN NUMBER,
2871                   p_purpose_code IN VARCHAR2) IS
2872   select length(a.transaction_state)
2873     from okl_stream_trx_data a,
2874 	     okl_stream_interfaces b
2875    where a.orig_khr_id = p_contract_id
2876      and a.last_trx_state = 'Y'
2877 	 and a.transaction_number = b.transaction_number
2878 	 and nvl(b.purpose_code, 'PRIMARY') = p_purpose_code;
2879 
2880   cursor get_trx_contract(p_trx_id IN NUMBER) IS
2881   select khr_id, nvl(purpose_code, 'PRIMARY') purpose_code
2882     from okl_stream_interfaces
2883    where transaction_number = p_trx_id;
2884 
2885   cursor is_erd_enabled(p_trx_number IN NUMBER ) IS
2886   select nvl(sao.amort_inc_adj_rev_dt_yn, 'N') erd
2887         ,gts.deal_type
2888         ,gts.interest_calc_meth_code
2889     from okl_sys_acct_opts_all sao
2890         ,okl_stream_interfaces osi
2891         ,okc_k_headers_all_b   chr
2892         ,okl_k_headers         khr
2893         ,okl_products          pdt
2894         ,okl_ae_tmpt_sets_all  aes
2895         ,okl_st_gen_tmpt_sets_all gts
2896     Where sao.org_id = chr.authoring_org_id
2897       and chr.id = osi.khr_id
2898       and osi.transaction_number = p_trx_number
2899       and chr.id     = khr.id
2900       and khr.pdt_id = pdt.id
2901       and pdt.aes_id     = aes.id
2902       and aes.gts_id     = gts.id;
2903   -- Modified for the bug: 8870387
2904 
2905   l_copy_contract_id   number;
2906   l_erd_enabled        varchar2(1);
2907   l_orig_khr_start_date      DATE;
2908   l_rbk_khr_start_date       DATE;
2909   l_deal_type                VARCHAR2(300);
2910   l_interest_calc_meth_code  VARCHAR2(300);
2911   l_trx_state_len            NUMBER;
2912 begin
2913 
2914 	 -- find if the prospective rebook feature is enabled for the OU.
2915 	 open is_erd_enabled(p_trx_number => p_trx_id); -- Modified for bug 8870387
2916 	 fetch is_erd_enabled into l_erd_enabled,l_deal_type,l_interest_calc_meth_code;
2917 	 close is_erd_enabled;
2918 
2919      x_rebook_type := 'None';
2920 
2921 	   -- based on the transaction number passed, get the contract_id
2922 	   -- and the context, whether primary or reporting
2923 	   open get_trx_contract(p_trx_id);
2924 	   fetch get_trx_contract into l_copy_contract_id, l_purpose_code;
2925 	   close get_trx_contract;
2926 
2927 	   -- for the copy_contract_id, get the original contract_id, in case of a online rebook
2928        open get_orig_contract_csr(l_copy_contract_id);
2929        fetch get_orig_contract_csr into l_contract_number, l_contract_id,
2930 	                               l_rbk_reason_code, l_revision_date,
2931 								   l_rebook_type,l_rbk_khr_start_date,l_orig_khr_start_date;
2932 
2933        close get_orig_contract_csr;
2934 
2935 	 -- if prospective rebook is enabled, then do the rest.
2936 	 if l_erd_enabled = 'Y' then
2937 
2938            x_rebook_type := 'Prospective';
2939            x_query_trx_state   := 'Y';
2940   	   x_rebook_date := l_revision_date;
2941 
2942 	   -- For normal booking and transactions like Splt Asset, the
2943 	   -- rebook type tag should be populated with a value of 'None'.
2944 	   -- Value should otherwise be 'Prospective', if the feature is enabled.
2945 	   if l_rebook_type not in ('MASS_REBOOK', 'ONLINE_REBOOK') OR
2946 	      l_rebook_type is NULL
2947 	   then
2948          x_rebook_type := 'None';
2949 	   end if;
2950 
2951        -- Case: During Online Revision, Contract Start Date has been Changed
2952        --       Hence, consider this as a Retrospective Case only
2953        IF l_orig_khr_start_date <> l_rbk_khr_start_date
2954        THEN
2955          x_rebook_type := 'None';
2956          x_rebook_date := NULL;
2957        END IF;
2958 
2959        -- Optimizing the Code to fetch the clob only if required !
2960        IF x_rebook_type <> 'None'
2961        THEN
2962          -- for the original contract_id, return the transaction state
2963          open get_clob(l_contract_id, l_purpose_code);
2964          fetch get_clob into l_trx_state_len; --x_trx_state;
2965          close get_clob;
2966        END IF;
2967 
2968 	   -- Override of rebook_type tag to 'None' is done in case a mass rebook
2969 	   -- was initiated before 'Effective Dated Rebook' is enabled, and failed.
2970 	   -- If the feature is enabled at this time, the mass rebook transaction
2971 	   -- should complete as a retrospective one.
2972 	   --if x_trx_state is null and l_rebook_type = 'MASS_REBOOK' then
2973 	   if l_trx_state_len = 0 and l_rebook_type = 'MASS_REBOOK' then
2974 	     x_rebook_type := 'None';
2975 	   end if;
2976    else
2977      IF  l_deal_type LIKE 'LEASE%' AND
2978          l_interest_calc_meth_code = 'REAMORT'
2979      THEN
2980        x_rebook_type := 'None';
2981        x_rebook_date := l_revision_date;
2982        x_query_trx_state   := 'Y';
2983        -- for the original contract_id, return the transaction state
2984        open get_clob(l_contract_id, l_purpose_code);
2985        fetch get_clob into l_trx_state_len; --x_trx_state;
2986        close get_clob;
2987      END IF;
2988    end if;
2989 
2990    x_trx_state := NULL;
2991 
2992 exception
2993   when others then
2994     raise;
2995 end get_k_trx_state;
2996 
2997 -------------------------
2998 procedure update_trx_state(p_khr_id in number,
2999                            p_context in varchar2) IS
3000 
3001 l_trx_number	number;
3002 
3003 cursor get_prim_trx(p_khr_id number) IS
3004 select max(std.transaction_number)
3005   from okl_stream_trx_data std, okl_stream_interfaces osi
3006  where std.orig_khr_id = p_khr_id
3007    and std.transaction_number = osi.transaction_number
3008    and osi.purpose_code is NULL;
3009 
3010 cursor get_rep_trx(p_khr_id number) IS
3011 select max(std.transaction_number)
3012   from okl_stream_trx_data std, okl_stream_interfaces osi
3013  where std.orig_khr_id = p_khr_id
3014    and std.transaction_number = osi.transaction_number
3015    and osi.purpose_code is NOT NULL;
3016 
3017 cursor is_prb_enabled is
3018 select nvl(AMORT_INC_ADJ_REV_DT_YN, 'N')
3019   from okl_sys_acct_opts;
3020 
3021 cursor get_chr_details( p_khr_id IN NUMBER )
3022 IS
3023   select gts.deal_type               deal_type
3024         ,gts.interest_calc_meth_code interest_calc_meth_code
3025     from okc_k_headers_all_b   chr
3026         ,okl_k_headers         khr
3027         ,okl_products          pdt
3028         ,okl_ae_tmpt_sets_all  aes
3029         ,okl_st_gen_tmpt_sets_all gts
3030     Where chr.id = p_khr_id
3031       and chr.id     = khr.id
3032       and khr.pdt_id = pdt.id
3033       and pdt.aes_id     = aes.id
3034       and aes.gts_id     = gts.id;
3035 
3036 l_prb_enabled varchar2(1);
3037 l_deal_type   VARCHAR2(300);
3038 l_interest_calc_meth_code VARCHAR2(300);
3039 begin
3040 
3041    -- verify if the EDR feature is enabled for the OU.
3042    open is_prb_enabled;
3043    fetch is_prb_enabled into l_prb_enabled;
3044    close is_prb_enabled;
3045 
3046    FOR t_rec IN get_chr_details(p_khr_id => p_khr_id )
3047    LOOP
3048     l_deal_type := t_rec.deal_type;
3049     l_interest_calc_meth_code := t_rec.interest_calc_meth_code;
3050    END LOOP;
3051 
3052    -- proceed further if the feature is enabled.
3053    if l_prb_enabled = 'Y' OR
3054       ( l_deal_type LIKE 'LEASE%' AND l_interest_calc_meth_code = 'REAMORT' )
3055    then
3056      if p_context in ('BOTH', 'PRIMARY') then
3057        open get_prim_trx(p_khr_id);
3058 	   fetch get_prim_trx into l_trx_number;
3059 	   close get_prim_trx;
3060 
3061 	    update okl_stream_trx_data
3062 	       set last_trx_state = 'Y'
3063          where orig_khr_id = p_khr_id
3064 	       and transaction_number = l_trx_number;
3065 
3066         update okl_stream_trx_data a
3067 	       set a.last_trx_state = NULL
3068          where a.orig_khr_id = p_khr_id
3069 	       and a.transaction_number < l_trx_number
3070 		   and a.last_trx_state = 'Y'
3071 		   and EXISTS (select b.transaction_number
3072 		                 from okl_stream_interfaces b
3073 				        where b.transaction_number = a.transaction_number
3074 					      and b.purpose_code is NULL);
3075      end if;
3076 
3077      l_trx_number := NULL;
3078 
3079      if p_context in ('BOTH', 'REPORT') then
3080        open get_rep_trx(p_khr_id);
3081 	   fetch get_rep_trx into l_trx_number;
3082 	   close get_rep_trx;
3083 
3084        if l_trx_number is not null then
3085 	      update okl_stream_trx_data
3086 	         set last_trx_state = 'Y'
3087            where orig_khr_id = p_khr_id
3088 	         and transaction_number = l_trx_number;
3089 
3090           update okl_stream_trx_data a
3091 	         set a.last_trx_state = NULL
3092            where a.orig_khr_id = p_khr_id
3093 	         and a.transaction_number < l_trx_number
3094 		     and a.last_trx_state = 'Y'
3095 		     and EXISTS (select b.transaction_number
3096 		                   from okl_stream_interfaces b
3097 				          where b.transaction_number = a.transaction_number
3098 					        and b.purpose_code is NOT NULL);
3099 
3100        end if; -- if l_trx_number is not null
3101 
3102      end if;
3103    end if; -- if prb_enabled = 'Y'
3104 
3105 end update_trx_state;
3106 
3107   --Added by rgooty for bug 9972860
3108   FUNCTION GET_ORP_CODE(p_trx_id IN number) RETURN VARCHAR2 IS
3109 
3110     cursor get_orp_code_csr(p_trx_number IN NUMBER ) IS
3111     select osi.orp_code
3112       from okl_stream_interfaces osi
3113       Where osi.transaction_number = p_trx_number;
3114 
3115      l_orp_code VARCHAR2(300);
3116   begin
3117       l_orp_code := 'None';
3118 
3119       open get_orp_code_csr(p_trx_number => p_trx_id);
3120       fetch get_orp_code_csr into l_orp_code;
3121       close get_orp_code_csr;
3122 
3123       return l_orp_code;
3124   Exception
3125     when others then
3126       return 'None';
3127   END GET_ORP_CODE;
3128 
3129 
3130   PROCEDURE get_var_amort_details(
3131               p_trx_id              IN         NUMBER,
3132               x_trx_state           OUT NOCOPY CLOB,
3133               x_reamort_start_date  OUT NOCOPY DATE,
3134               x_reamort_rate        OUT NOCOPY VARCHAR2,
3135               x_rebook_type         OUT NOCOPY VARCHAR2)
3136   IS
3137     -- Cursor to fetch the Contract ID, Deal Type, Interest Calculation Basis and Stream Generation Puropse [ORIGIN/REPORT]
3138     CURSOR get_trx_contract(p_trx_id IN NUMBER)
3139     IS
3140       SELECT osi.khr_id                   khr_id
3141             ,nvl(purpose_code, 'PRIMARY') purpose_code
3142             ,gts.deal_type                deal_type
3143             ,gts.interest_calc_meth_code  interest_calc_meth_code
3144             ,osi.date_delivery            reamort_date
3145             ,siyb.target_value            target_value
3146         FROM okl_stream_interfaces osi
3147             ,okl_sif_yields        siyb
3148             ,okc_k_headers_all_b   chr
3149             ,okl_k_headers         khr
3150             ,okl_products          pdt
3151             ,okl_ae_tmpt_sets_all  aes
3152             ,okl_st_gen_tmpt_sets_all gts
3153        WHERE osi.transaction_number = p_trx_id
3154          AND siyb.sif_id            = osi.id
3155          AND siyb.target_value IS NOT NULL
3156          AND chr.id     =  osi.khr_id
3157          AND chr.id     = khr.id
3158          AND khr.pdt_id = pdt.id
3159          AND pdt.aes_id = aes.id
3160          AND aes.gts_id = gts.id;
3161 
3162     -- Cursor to fetch the Latest TransactionState CLOB of the given contract
3163     CURSOR get_clob(p_contract_id  IN NUMBER,
3164                     p_purpose_code IN VARCHAR2)
3165     IS
3166       SELECT a.transaction_state
3167         FROM okl_stream_trx_data a,
3168              okl_stream_interfaces b
3169        WHERE a.orig_khr_id = p_contract_id
3170          AND a.last_trx_state = 'Y'
3171          AND a.transaction_number = b.transaction_number
3172          AND nvl(b.purpose_code, 'PRIMARY') = p_purpose_code;
3173 
3174     -- Variables declaration
3175     l_contract_id              NUMBER;
3176     l_purpose_code             VARCHAR2(15);
3177     l_deal_type                VARCHAR2(300);
3178     l_interest_calc_meth_code  VARCHAR2(300);
3179     l_reamort_date             DATE;
3180     l_reamort_rate             NUMBER;
3181     l_rebook_type              VARCHAR2(15);
3182     l_trx_state                CLOB;
3183 
3184   BEGIN
3185     -- Execute cursor to fetch the contract related details
3186     OPEN  get_trx_contract(p_trx_id);
3187     FETCH get_trx_contract INTO l_contract_id, l_purpose_code,
3188                                 l_deal_type, l_interest_calc_meth_code,
3189                                 l_reamort_date, l_reamort_rate;
3190     CLOSE get_trx_contract;
3191 
3192     IF  l_deal_type LIKE 'LEASE%' AND
3193         l_interest_calc_meth_code = 'REAMORT'
3194     THEN
3195       l_rebook_type := 'Reamort';
3196       -- Fetch the TransactionState CLOB of the contract in context and pass it back
3197       OPEN  get_clob(l_contract_id, l_purpose_code);
3198       FETCH get_clob into l_trx_state;
3199       CLOSE get_clob;
3200       -- Logic to fetch the Reamort Start Date and Interest Rate
3201 
3202     END IF;
3203 
3204     x_trx_state                := null;   -- l_trx_state;
3205     --x_trx_state                := dbms_lob.substr( l_trx_state, 32000, 1 );
3206     x_reamort_start_date       := l_reamort_date;
3207     x_reamort_rate             := l_reamort_rate;
3208     x_rebook_type              := l_rebook_type;
3209 
3210   EXCEPTION
3211     WHEN OTHERS
3212     THEN
3213           raise;
3214   END;
3215 
3216 --end rgooty for bug 9972860
3217 
3218   --Added by bkatraga for bug 16344245
3219   PROCEDURE get_balance_details(p_trx_id     IN       NUMBER,
3220                                 p_line_id    IN       NUMBER,
3221                                 x_bal_method OUT NOCOPY VARCHAR2,
3222                                 x_bal_date   OUT NOCOPY DATE,
3223                                 x_bal_amount OUT NOCOPY NUMBER)
3224   IS
3225     CURSOR get_contract_id
3226     IS
3227     SELECT KHR_ID, DEAL_TYPE
3228       FROM OKL_STREAM_INTERFACES
3229      WHERE TRANSACTION_NUMBER = p_trx_id;
3230 
3231     CURSOR chk_rbk_rel_csr (p_contract_id  IN NUMBER)
3232     IS
3233     SELECT '!'
3234       FROM okc_k_headers_all_b CHR
3235      WHERE CHR.ID = p_contract_id
3236        AND CHR.orig_system_source_code IN ('OKL_REBOOK','OKL_RELEASE');
3237 
3238     CURSOR get_bal_amt_date
3239     IS
3240     SELECT AMOUNT_BALANCE_LEGACY,
3241            DT_EFFECTIVE_BALANCE_LEGACY
3242       FROM OKL_K_LINES
3243      WHERE ID = p_line_id;
3244 
3245     CURSOR check_book_trans (p_contract_id  IN NUMBER)
3246     IS
3247     SELECT 'Y'
3248       FROM DUAL
3249      WHERE EXISTS (SELECT 1
3250                      FROM OKL_TRX_CONTRACTS_ALL
3251                     WHERE KHR_ID = p_contract_id
3252                       AND TCN_TYPE IN ('BKG','REL')
3253                       AND TSU_CODE = 'PROCESSED'
3254                       AND REPRESENTATION_TYPE = 'PRIMARY');
3255 
3256     l_contract_id      NUMBER;
3257     l_deal_type        VARCHAR2(10);
3258     l_rbk_rel_khr      VARCHAR2(1) DEFAULT '?';
3259     l_booking_trans    VARCHAR2(1) DEFAULT 'N';
3260   BEGIN
3261     x_bal_method := 'None';
3262     x_bal_date := NULL;
3263     x_bal_amount := NULL;
3264 
3265     OPEN  get_contract_id;
3266     FETCH get_contract_id INTO l_contract_id, l_deal_type;
3267     CLOSE get_contract_id;
3268 
3269     IF(l_deal_type = 'LNBO') THEN
3270       x_bal_method := 'Rate';
3271     END IF;
3272 
3273     -- Check for rebook/release contract
3274     OPEN chk_rbk_rel_csr (p_contract_id => l_contract_id);
3275     FETCH chk_rbk_rel_csr INTO l_rbk_rel_khr;
3276     CLOSE chk_rbk_rel_csr;
3277 
3278     IF(l_rbk_rel_khr = '?') THEN
3279       --Need to check if booking transaction exist for the contract
3280       OPEN  check_book_trans (p_contract_id => l_contract_id);
3281       FETCH check_book_trans INTO l_booking_trans;
3282       CLOSE check_book_trans;
3283 
3284       IF(l_booking_trans = 'N') THEN
3285         OPEN  get_bal_amt_date;
3286         FETCH get_bal_amt_date INTO x_bal_amount,x_bal_date;
3287         CLOSE get_bal_amt_date;
3288 
3289         IF(x_bal_date IS NOT NULL) THEN
3290           x_bal_method := 'ForceBalance';
3291           x_bal_amount := x_bal_amount;
3292         END IF;
3293       END IF;
3294     END IF;
3295 
3296   EXCEPTION
3297   WHEN OTHERS THEN
3298     RAISE;
3299   END get_balance_details;
3300   --end bkatraga for bug 16344245
3301 
3302 END  Okl_Streams_Util;