DBA Data[Home] [Help]

PACKAGE BODY: APPS.CN_CALC_SQL_EXPS_PVT

Source


1 PACKAGE BODY cn_calc_sql_exps_pvt AS
2   /*$Header: cnvcexpb.pls 120.10.12010000.2 2008/12/08 10:23:18 venjayar ship $*/
3   g_pkg_name CONSTANT VARCHAR2(30) := 'CN_CALC_SQL_EXPS_PVT';
4 
5   PROCEDURE get_usage_info(
6     p_exp_type_code IN            cn_calc_sql_exps.exp_type_code%TYPE
7   , x_usage_info    OUT NOCOPY    VARCHAR2
8   ) IS
9   BEGIN
10     x_usage_info  := fnd_message.get_string('CN', p_exp_type_code);
11   EXCEPTION
12     WHEN OTHERS THEN
13       x_usage_info  := NULL;
14   END get_usage_info;
15 
16   PROCEDURE classify_expression(
17     p_org_id           IN            cn_calc_sql_exps.org_id%TYPE
18   , p_sql_select       IN            VARCHAR2
19   ,   -- CLOBs
20     p_sql_from         IN            VARCHAR2
21   , p_piped_sql_select IN            VARCHAR2
22   , p_piped_sql_from   IN            VARCHAR2
23   , x_status           IN OUT NOCOPY cn_calc_sql_exps.status%TYPE
24   , x_exp_type_code    IN OUT NOCOPY cn_calc_sql_exps.exp_type_code%TYPE
25   , x_msg_count        OUT NOCOPY    NUMBER
26   , x_msg_data         OUT NOCOPY    VARCHAR2
27   ) IS
28     l_dummy   PLS_INTEGER;
29     l_pos     PLS_INTEGER;
30     l_alias   VARCHAR2(30);
31     l_new_sql VARCHAR2(4100);
32     l_pe_tbl  num_tbl_type;
33 
34     CURSOR external_table IS
35       SELECT 1
36         FROM cn_calc_ext_tables
37        WHERE alias = l_alias
38          AND (org_id = p_org_id)
39          AND internal_table_id IN(
40                SELECT object_id
41                  FROM cn_objects
42                 WHERE (NAME = 'CN_COMMISSION_LINES' OR NAME = 'CN_COMMISSION_HEADERS')
43                   AND object_type = 'TBL'
44                   AND (org_id = p_org_id));
45   BEGIN
46     -- parse the expression
47     IF LENGTH(p_sql_select) + LENGTH(p_sql_from) > 4000 THEN
48       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
49         fnd_message.set_name('CN', 'CN_EXP_TOO_LONG');
50         fnd_msg_pub.ADD;
51       END IF;
52 
53       RAISE fnd_api.g_exc_error;
54     END IF;
55 
56     DECLARE
57       l_sql_statement VARCHAR2(4100);
58 
59       TYPE rc IS REF CURSOR;
60 
61       dummy_cur       rc;
62       dummy_val       VARCHAR2(4000);
63     BEGIN
64       x_status         := 'VALID';
65       l_sql_statement  :=
66                          'select ' || p_sql_select || ' from ' || p_sql_from || ' where rownum < 1';
67       l_sql_statement  :=
68         REPLACE(
69           REPLACE(REPLACE(l_sql_statement, 'p_commission_line_id', '100'), 'RateResult', '100')
70         , 'ForecastAmount'
71         , '100'
72         );
73       -- if we see anything like [PlanElementID]PE.[something], replace it
74       -- with a constant 0
75       parse_plan_elements(l_sql_statement, l_pe_tbl, l_new_sql);
76       l_sql_statement  := l_new_sql;
77 
78       OPEN dummy_cur FOR l_sql_statement;
79       FETCH dummy_cur INTO dummy_val;
80       CLOSE dummy_cur;
81     EXCEPTION
82       WHEN OTHERS THEN
83         x_status  := 'INVALID';
84 
85         IF dummy_cur%ISOPEN THEN
86           CLOSE dummy_cur;
87         END IF;
88 
89         IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error) THEN
90           fnd_message.set_name('CN', 'CN_INVALID_EXP');
91           fnd_message.set_token('EXPRESSION', SQLERRM);
92           fnd_msg_pub.ADD;
93         END IF;
94 
95         fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
96         , p_encoded                    => fnd_api.g_false);
97     END;
98 
99     IF (p_piped_sql_select IS NULL OR p_piped_sql_from IS NULL) THEN
100       RETURN;
101     END IF;
102 
103     -- check whether there is a column from cn_commission_lines/headers
104     -- or if there is a plan element
105     IF (
106            INSTR(p_piped_sql_select, 'CL.', 1, 1) = 1
107         OR INSTR(p_piped_sql_select, '|CL.', 1, 1) > 0
108         OR INSTR(p_piped_sql_select, '(CL.', 1, 1) > 0
109         OR INSTR(p_piped_sql_select, '+CL.', 1, 1) > 0
110         OR INSTR(p_piped_sql_select, '-CL.', 1, 1) > 0
111         OR INSTR(p_piped_sql_select, '*CL.', 1, 1) > 0
112         OR INSTR(p_piped_sql_select, '/CL.', 1, 1) > 0
113         OR INSTR(p_piped_sql_select, 'CH.', 1, 1) = 1
114         OR INSTR(p_piped_sql_select, '|CH.', 1, 1) > 0
115         OR INSTR(p_piped_sql_select, '(CH.', 1, 1) > 0
116         OR INSTR(p_piped_sql_select, '+CH.', 1, 1) > 0
117         OR INSTR(p_piped_sql_select, '-CH.', 1, 1) > 0
118         OR INSTR(p_piped_sql_select, '*CH.', 1, 1) > 0
119         OR INSTR(p_piped_sql_select, '/CH.', 1, 1) > 0
120         OR INSTR(p_piped_sql_select, 'p_commission_line_id', 1, 1) > 0
121        ) THEN
122       x_exp_type_code  := 'Y';
123     ELSE
124       x_exp_type_code  := 'N';
125     END IF;
126 
127     -- check whether there is any column from a table which is mapped to cn_commission_lines/headers.
128     -- if there is any such column, the expression is considered trx_based.
129     IF (INSTR(x_exp_type_code, 'N', 1, 1) = 1) THEN
130       l_pos  := 1;
131 
132       LOOP
133         l_pos    := INSTR(p_piped_sql_from, ' ', l_pos, 1);
134 
135         IF (l_pos = 0) THEN
136           EXIT;
137         END IF;
138 
139         l_pos    := l_pos + 1;
140         l_alias  := SUBSTR(p_piped_sql_from, l_pos, INSTR(p_piped_sql_from, '|', l_pos, 1) - l_pos);
141 
142         OPEN external_table;
143         FETCH external_table INTO l_dummy;
144         CLOSE external_table;
145 
146         IF (l_dummy = 1) THEN
147           x_exp_type_code  := 'Y';
148           EXIT;
149         END IF;
150       END LOOP;
151     END IF;
152 
153     -- check whether there is group function in the sql statement
154     IF (
155            INSTR(p_piped_sql_select, 'AVG(', 1, 1) > 0
156         OR INSTR(p_piped_sql_select, 'COUNT(', 1, 1) > 0
157         OR INSTR(p_piped_sql_select, 'MIN(', 1, 1) > 0
158         OR INSTR(p_piped_sql_select, 'MAX(', 1, 1) > 0
159         OR INSTR(p_piped_sql_select, 'STDDEV(', 1, 1) > 0
160         OR INSTR(p_piped_sql_select, 'SUM(', 1, 1) > 0
161         OR INSTR(p_piped_sql_select, 'VARIANCE(', 1, 1) > 0
162        ) THEN
163       x_exp_type_code  := x_exp_type_code || 'Y';
164     ELSE
165       x_exp_type_code  := x_exp_type_code || 'N';
166     END IF;
167 
168     -- check whether RateResult is used
169     l_pos  := INSTR(p_piped_sql_select, 'RateResult', 1, 1);
170 
171     IF (l_pos > 0) THEN
172       x_exp_type_code  := x_exp_type_code || 'Y';
173     ELSE
174       x_exp_type_code  := x_exp_type_code || 'N';
175     END IF;
176 
177     -- check whether RateResult is the first component and is used only once
178     IF (l_pos = 1 AND INSTR(p_piped_sql_select, 'RateResult', 11, 1) = 0) THEN
179       x_exp_type_code  := x_exp_type_code || 'Y';
180     ELSE
181       -- deal with unnecessary leading and ending parentheses
182       x_exp_type_code  := x_exp_type_code || 'N';
183     END IF;
184 
185     -- check whether there is embedded formula
186     IF (INSTR(p_piped_sql_select, 'p_commission_line_id', 1, 1) > 0) THEN
187       x_exp_type_code  := x_exp_type_code || 'Y';
188     ELSE
189       x_exp_type_code  := x_exp_type_code || 'N';
190     END IF;
191 
192     -- check whether ForecastAmount is used
193     IF (INSTR(p_piped_sql_select, 'ForecastAmount', 1, 1) > 0) THEN
194       x_exp_type_code  := x_exp_type_code || 'Y';
195     ELSE
196       x_exp_type_code  := x_exp_type_code || 'N';
197     END IF;
198 
199     -- check whether the embedded formulas have the following flag setting:
200     -- trx_group_code = 'INDIVIDUAL', cumulative_flag = 'N' and itd_flag = 'N'
201     -- and threshold_all_tier_flag = 'N'
202     NULL;   -- to be added later
203 
204     -- convert x_exp_type_code to something that is easy to understand
205     IF (x_exp_type_code IN('YNYYYN', 'YNYYNN')) THEN
206       x_exp_type_code  := 'IO';
207     ELSIF(x_exp_type_code IN('YNYNYN', 'YNYNNN')) THEN
208       x_exp_type_code  := 'IO_ITDN';
209     ELSIF(x_exp_type_code IN('YYYYYN', 'YYYYNN', 'YYYNYN', 'YYYNNN')) THEN
210       x_exp_type_code  := 'GO';
211     ELSIF(x_exp_type_code IN('YYNNYN', 'YYNNNN')) THEN
212       x_exp_type_code  := 'GIGO';
213     ELSIF(x_exp_type_code = 'YNNNYN') THEN
214       x_exp_type_code  := 'IIIO';
215     ELSIF(x_exp_type_code = 'YNNNNN') THEN
216       x_exp_type_code  := 'IIIOIPGP';
217     ELSIF(x_exp_type_code IN('NNYYNY', 'NNYNNY')) THEN
218       x_exp_type_code  := 'FO';
219     ELSIF(x_exp_type_code IN('NNYYNN', 'NNYNNN')) THEN
220       x_exp_type_code  := 'IOGOBOFO';
221     ELSIF(x_exp_type_code = 'NNNNNY') THEN
222       x_exp_type_code  := 'FIFO';
223     ELSIF(x_exp_type_code = 'NNNNNN') THEN
224       x_exp_type_code  := 'IRIOIPGOGPBIBOBPFRFO';
225     ELSE
226       x_exp_type_code  := NULL;
227     END IF;
228 
229     -- check whether it can be used in dynamic rate tables also
230     IF (x_exp_type_code = 'IRIOIPGOGPBIBOBPFRFO') THEN
231       -- if all the tables used are only from cn_quotas_v, cn_period_quotas, cn_srp_quota_assigns,
232       -- and cn_srp_period_quotas, then it can be used in dynamic dimension tiers also
233       IF (p_piped_sql_from = 'DUAL|' OR p_piped_sql_from = 'SYS.DUAL|') THEN
234         x_exp_type_code  := x_exp_type_code || 'DDT';
235       ELSE
236         l_pos  := 1;
237 
238         LOOP
239           l_pos    := INSTR(p_piped_sql_from, ' ', l_pos, 1);
240 
241           IF (l_pos = 0) THEN
242             x_exp_type_code  := x_exp_type_code || 'DDT';
243             EXIT;
244           END IF;
245 
246           l_pos    := l_pos + 1;
247           l_alias  := SUBSTR(p_piped_sql_from, l_pos, INSTR(p_piped_sql_from, '|', l_pos, 1) - l_pos);
248 
249           IF (l_alias NOT IN('CQ', 'CPQ', 'CSQA', 'CSPQ')) THEN
250             EXIT;
251           END IF;
252         END LOOP;
253       END IF;
254     END IF;
255 
256     -- see if expression includes plan element references
257     IF l_pe_tbl.COUNT > 0 THEN
258       IF x_exp_type_code IN('FO', 'FIFO') THEN
259         -- forecast and DDT expressions cannot be used with plan elements
260         x_exp_type_code  := NULL;
261       ELSIF x_exp_type_code IN('IRIOIPGOGPBIBOBPFRFODDT', 'IRIOIPGOGPBIBOBPFRFO') THEN
262         x_exp_type_code  := 'IIIOIPGOGPBIBOBP';
263       ELSIF x_exp_type_code = 'IOGOBOFO' THEN
264         x_exp_type_code  := 'IOGOBO';
265       END IF;
266     END IF;
267   END classify_expression;
268 
269   -- Start of comments
270   --    API name        : Create_Expression
271   --    Type            : Private.
272   --    Function        :
273   --    Pre-reqs        : None.
274   --    Parameters      :
275   --    IN              : p_api_version         IN      NUMBER       Required
276   --                      p_init_msg_list       IN      VARCHAR2     Optional
277   --                        Default = FND_API.G_FALSE
278   --                      p_commit              IN      VARCHAR2     Optional
279   --                        Default = FND_API.G_FALSE
280   --                      p_validation_level    IN      NUMBER       Optional
281   --                        Default = FND_API.G_VALID_LEVEL_FULL
282   --                      p_name                IN      VARCHAR2     Required
283   --                      p_description         IN      VARCHAR2     Optional
284   --                        Default = null
285   --                      p_expression_disp     IN      VARCHAR2     Optional
286   --                        Default = null
287   --                      p_sql_select          IN      VARCHAR2     Optional
288   --                        Default = null
289   --                      p_sql_from            IN      VARCHAR2     Optional
290   --                        Default = null
291   --                      p_piped_expression_disp IN    VARCHAR2     Optional
292   --                        Default = null
293   --                      p_piped_sql_select    IN      VARCHAR2     Optional
294   --                        Default = null
295   --                      p_piped_sql_from      IN      VARCHAR2     Optional
296   --                        Default = null
297   --    OUT             : x_calc_sql_exp_id     OUT     NUMBER
298   --                      x_exp_type_code       OUT     VARCHAR2(30)
299   --                      x_status              OUT     VARCHAR2(30)
300   --                      x_return_status       OUT     VARCHAR2(1)
301   --                      x_msg_count           OUT     NUMBER
302   --                      x_msg_data            OUT     VARCHAR2(4000)
303   --    Version :         Current version       1.0
304   --                      Initial version       1.0
305   --
306   --    Notes           : Create SQL expressions that will be used in calculation.
307   --                      1) Validate the expression and return the result in x_status (Valid or Invalid)
308   --                      2) Classify expressions into sub types for formula validation and dynamic rate table validation
309   --                      3) If there are embedded expressions, record the embedding relations in cn_calc_edges
310   --
311   -- End of comments
312   PROCEDURE create_expression(
313     p_api_version           IN            NUMBER
314   , p_init_msg_list         IN            VARCHAR2 := fnd_api.g_false
315   , p_commit                IN            VARCHAR2 := fnd_api.g_false
316   , p_validation_level      IN            NUMBER := fnd_api.g_valid_level_full
317   , p_org_id                IN            cn_calc_sql_exps.org_id%TYPE
318   , p_name                  IN            cn_calc_sql_exps.NAME%TYPE
319   , p_description           IN            cn_calc_sql_exps.description%TYPE := NULL
320   , p_expression_disp       IN            VARCHAR2 := NULL
321   ,   -- CLOBs
322     p_sql_select            IN            VARCHAR2 := NULL
323   , p_sql_from              IN            VARCHAR2 := NULL
324   , p_piped_expression_disp IN            VARCHAR2 := NULL
325   , p_piped_sql_select      IN            VARCHAR2 := NULL
326   , p_piped_sql_from        IN            VARCHAR2 := NULL
327   , x_calc_sql_exp_id       IN OUT NOCOPY cn_calc_sql_exps.calc_sql_exp_id%TYPE
328   , x_exp_type_code         OUT NOCOPY    cn_calc_sql_exps.exp_type_code%TYPE
329   , x_status                OUT NOCOPY    cn_calc_sql_exps.status%TYPE
330   , x_return_status         OUT NOCOPY    VARCHAR2
331   , x_msg_count             OUT NOCOPY    NUMBER
332   , x_msg_data              OUT NOCOPY    VARCHAR2
333   , x_object_version_number OUT NOCOPY    cn_calc_sql_exps.object_version_number%TYPE
334   ) IS
335     l_api_name    CONSTANT VARCHAR2(30)                            := 'Create_Expression';
336     l_api_version CONSTANT NUMBER                                  := 1.0;
337     l_prompt               cn_lookups.meaning%TYPE;
338     l_dummy                PLS_INTEGER;
339     l_disp_start           PLS_INTEGER;
340     l_select_start         PLS_INTEGER;
341     l_disp_end             PLS_INTEGER;
342     l_select_end           PLS_INTEGER;
343     l_token                VARCHAR2(4000);
344     l_calc_formula_id      cn_calc_formulas.calc_formula_id%TYPE;
345 
346     CURSOR exp_exists IS
347       SELECT 1
348         FROM cn_calc_sql_exps
349        WHERE NAME = p_name AND org_id = p_org_id;
350   BEGIN
351     -- Standard Start of API savepoint
352     SAVEPOINT create_expression;
353 
354     -- Standard call to check for call compatibility.
355     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
356       RAISE fnd_api.g_exc_unexpected_error;
357     END IF;
358 
359     -- Initialize message list if p_init_msg_list is set to TRUE.
360     IF fnd_api.to_boolean(p_init_msg_list) THEN
361       fnd_msg_pub.initialize;
362     END IF;
363 
364     --  Initialize API return status to success
365     x_return_status  := fnd_api.g_ret_sts_success;
366 
367     -- API body
368     IF (p_name IS NULL) THEN
369       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
370         l_prompt  := cn_api.get_lkup_meaning('EXP_NAME', 'CN_PROMPTS');
371         fnd_message.set_name('CN', 'CN_CANNOT_NULL');
372         fnd_message.set_token('OBJ_NAME', l_prompt);
373         fnd_msg_pub.ADD;
374       END IF;
375 
376       RAISE fnd_api.g_exc_error;
377     END IF;
378 
379     OPEN exp_exists;
380     FETCH exp_exists INTO l_dummy;
381     CLOSE exp_exists;
382 
383     IF (l_dummy = 1) THEN
384       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
385         fnd_message.set_name('CN', 'CN_NAME_NOT_UNIQUE');
386         fnd_msg_pub.ADD;
387       END IF;
388 
389       RAISE fnd_api.g_exc_error;
390     END IF;
391 
392     -- make sure name isn't too long
393     IF LENGTH(p_name) > 30 THEN
394       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
395         fnd_message.set_name('CN', 'CN_NAME_TOO_LONG');
396         fnd_message.set_token('LENGTH', 30);
397         fnd_msg_pub.ADD;
398       END IF;
399 
400       RAISE fnd_api.g_exc_error;
401     END IF;
402 
403     -- parse the expression and classify it into sub types
404     classify_expression(
405       p_org_id                     => p_org_id
406     , p_sql_select                 => p_sql_select
407     , p_sql_from                   => p_sql_from
408     , p_piped_sql_select           => p_piped_sql_select
409     , p_piped_sql_from             => p_piped_sql_from
410     , x_status                     => x_status
411     , x_exp_type_code              => x_exp_type_code
412     , x_msg_count                  => x_msg_count
413     , x_msg_data                   => x_msg_data
414     );
415     -- call table handler to create the expression
416     cn_calc_sql_exps_pkg.insert_row(
417       x_org_id                     => p_org_id
418     , x_calc_sql_exp_id            => x_calc_sql_exp_id
419     , x_name                       => p_name
420     , x_description                => p_description
421     , x_status                     => x_status
422     , x_exp_type_code              => x_exp_type_code
423     , x_expression_disp            => p_expression_disp
424     , x_sql_select                 => p_sql_select
425     , x_sql_from                   => p_sql_from
426     , x_piped_sql_select           => p_piped_sql_select
427     , x_piped_sql_from             => p_piped_sql_from
428     , x_piped_expression_disp      => p_piped_expression_disp
429     , x_object_version_number      => x_object_version_number
430     );
431     -- record calc edges
432     l_disp_start     := 1;
433     l_select_start   := 1;
434 
435     LOOP
436       l_disp_end      := INSTR(p_piped_expression_disp, '|', l_disp_start, 1);
437 
438       IF (l_disp_end IS NULL OR l_disp_end = 0) THEN
439         EXIT;
440       END IF;
441 
442       l_token         := SUBSTR(p_piped_expression_disp, l_disp_start, l_disp_end - l_disp_start);
443       l_disp_start    := l_disp_end + 1;
444       l_select_end    := INSTR(p_piped_sql_select, '|', l_select_start, 1);
445 
446       -- if the corresponding piped select part is in parenthesis, it is an embedded expression
447       IF (
448               INSTR(p_piped_sql_select, '(', l_select_start, 1) = l_select_start
449           AND (l_select_end - l_select_start) > 1
450          ) THEN
451         -- insert calc edges (calc edges has no table handler)
452         INSERT INTO cn_calc_edges
453                     (
454                      org_id
455                    , calc_edge_id
456                    , parent_id
457                    , child_id
458                    , edge_type
459                    , creation_date
460                    , created_by
461                    , last_update_login
462                    , last_update_date
463                    , last_updated_by
464                     )
465           SELECT org_id
466                , cn_calc_edges_s.NEXTVAL
467                , x_calc_sql_exp_id
468                , calc_sql_exp_id
469                , 'EE'
470                , SYSDATE
471                , fnd_global.user_id
472                , fnd_global.login_id
473                , SYSDATE
474                , fnd_global.user_id
475             FROM cn_calc_sql_exps
476            WHERE NAME = l_token;
477       ELSIF(INSTR(p_piped_sql_select, 'cn_formula', l_select_start, 1) = l_select_start) THEN
478         l_dummy            := INSTR(p_piped_sql_select, '_', l_select_start, 2) + 1;
479         l_calc_formula_id  :=
480           TO_NUMBER(
481             SUBSTR(p_piped_sql_select, l_dummy, INSTR(p_piped_sql_select, '_', l_dummy, 1) - l_dummy)
482           );
483 
484         INSERT INTO cn_calc_edges
485                     (
486                      org_id
487                    , calc_edge_id
488                    , parent_id
489                    , child_id
490                    , edge_type
491                    , creation_date
492                    , created_by
493                    , last_update_login
494                    , last_update_date
495                    , last_updated_by
496                     )
497              VALUES (
498                      p_org_id
499                    , cn_calc_edges_s.NEXTVAL
500                    , x_calc_sql_exp_id
501                    , l_calc_formula_id
502                    , 'FE'
503                    , SYSDATE
504                    , fnd_global.user_id
505                    , fnd_global.login_id
506                    , SYSDATE
507                    , fnd_global.user_id
508                     );
509       END IF;
510 
511       l_select_start  := l_select_end + 1;
512     END LOOP;
513 
514     -- End of API body.
515 
516     -- Standard check of p_commit.
517     IF fnd_api.to_boolean(p_commit) THEN
518       COMMIT WORK;
519     END IF;
520 
521     -- Standard call to get message count and if count is 1, get message info.
522     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
523     , p_encoded                    => fnd_api.g_false);
524   EXCEPTION
525     WHEN fnd_api.g_exc_error THEN
526       ROLLBACK TO create_expression;
527       x_return_status  := fnd_api.g_ret_sts_error;
528       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
529       , p_encoded                    => fnd_api.g_false);
530     WHEN fnd_api.g_exc_unexpected_error THEN
531       ROLLBACK TO create_expression;
532       x_return_status  := fnd_api.g_ret_sts_unexp_error;
533       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
534       , p_encoded                    => fnd_api.g_false);
535     WHEN OTHERS THEN
536       ROLLBACK TO create_expression;
537       x_return_status  := fnd_api.g_ret_sts_unexp_error;
538 
539       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
540         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
541       END IF;
542 
543       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
544       , p_encoded                    => fnd_api.g_false);
545   END create_expression;
546 
547   -- Start of comments
548   --    API name        : Update_Expressions
549   --    Type            : Private.
550   --    Function        :
551   --    Pre-reqs        : None.
552   --    Parameters      :
553   --    IN              : p_api_version         IN      NUMBER       Required
554   --                      p_init_msg_list       IN      VARCHAR2     Optional
555   --                        Default = FND_API.G_FALSE
556   --                      p_commit              IN      VARCHAR2     Optional
557   --                        Default = FND_API.G_FALSE
558   --                      p_validation_level    IN      NUMBER       Optional
559   --                        Default = FND_API.G_VALID_LEVEL_FULL
560   --                      p_update_parent_also  IN      VARCHAR2     Optional
561   --                        Default = FND_API.G_FALSE
562   --                      p_calc_sql_exp_id     IN      NUMBER       Required
563   --                      p_name                IN      VARCHAR2     Required
564   --                      p_description         IN      VARCHAR2     Optional
565   --                        Default = null
566   --                      p_expression_disp     IN      VARCHAR2     Optional
567   --                        Default = null
568   --                      p_sql_select          IN      VARCHAR2     Optional
569   --                        Default = null
570   --                      p_sql_from            IN      VARCHAR2     Optional
571   --                        Default = null
572   --                      p_piped_expression_disp IN    VARCHAR2     Optional
573   --                        Default = null
574   --                      p_piped_sql_select    IN      VARCHAR2     Optional
575   --                        Default = null
576   --                      p_piped_sql_from      IN      VARCHAR2     Optional
577   --                        Default = null
578   --                      p_ovn                 IN      NUMBER       Required
579   --    OUT             : x_exp_type_code       OUT     VARCHAR2(30)
580   --                      x_status              OUT     VARCHAR2(30)
581   --                      x_return_status       OUT     VARCHAR2(1)
582   --                      x_msg_count           OUT     NUMBER
583   --                      x_msg_data            OUT     VARCHAR2(4000)
584   --    Version :         Current version       1.0
585   --                      Initial version       1.0
586   --
587   --    Notes           : Update SQL expressions that will be used in calculation.
588   --                      1) validate the expression and return the result in x_status (Valid or Invalid)
589   --                      2) re-classify expressions into sub types for formula validation and dynamic rate table validation
590   --                      3) adjust the corresponding embedding relations in cn_calc_edges
591   --                      4) if the expression is used, update the parent expressions, formulas accordingly
592   --
593   -- End of comments
594   PROCEDURE update_expression(
595     p_api_version           IN            NUMBER
596   , p_init_msg_list         IN            VARCHAR2 := fnd_api.g_false
597   , p_commit                IN            VARCHAR2 := fnd_api.g_false
598   , p_validation_level      IN            NUMBER := fnd_api.g_valid_level_full
599   , p_update_parent_also    IN            VARCHAR2 := fnd_api.g_false
600   , p_org_id                IN            cn_calc_sql_exps.org_id%TYPE
601   , p_calc_sql_exp_id       IN            cn_calc_sql_exps.calc_sql_exp_id%TYPE
602   , p_name                  IN            cn_calc_sql_exps.NAME%TYPE
603   , p_description           IN            cn_calc_sql_exps.description%TYPE := NULL
604   , p_expression_disp       IN            VARCHAR2 := NULL
605   ,   -- CLOBs
606     p_sql_select            IN            VARCHAR2 := NULL
607   , p_sql_from              IN            VARCHAR2 := NULL
608   , p_piped_expression_disp IN            VARCHAR2 := NULL
609   , p_piped_sql_select      IN            VARCHAR2 := NULL
610   , p_piped_sql_from        IN            VARCHAR2 := NULL
611   , p_ovn                   IN OUT NOCOPY cn_calc_sql_exps.object_version_number%TYPE
612   , x_exp_type_code         OUT NOCOPY    cn_calc_sql_exps.exp_type_code%TYPE
613   , x_status                OUT NOCOPY    cn_calc_sql_exps.status%TYPE
614   , x_return_status         OUT NOCOPY    VARCHAR2
615   , x_msg_count             OUT NOCOPY    NUMBER
616   , x_msg_data              OUT NOCOPY    VARCHAR2
617   ) IS
618     l_api_name    CONSTANT VARCHAR2(30)                            := 'Update_Expression';
619     l_api_version CONSTANT NUMBER                                  := 1.0;
620     l_prompt               cn_lookups.meaning%TYPE;
621     l_dummy                PLS_INTEGER;
622     l_disp_start           PLS_INTEGER;
623     l_select_start         PLS_INTEGER;
624     l_disp_end             PLS_INTEGER;
625     l_select_end           PLS_INTEGER;
626     l_token                VARCHAR2(4000);
627     l_calc_formula_id      cn_calc_formulas.calc_formula_id%TYPE;
628     l_exp_names            VARCHAR2(4000)                          := '|';
629     l_formula_ids          VARCHAR2(4000)                          := '|';
630 
631     CURSOR parent_exist IS
632       SELECT 1
633         FROM DUAL
634        WHERE (EXISTS(SELECT 1
635                        FROM cn_calc_edges
636                       WHERE child_id = p_calc_sql_exp_id AND edge_type = 'EE'))
637           OR (
638               EXISTS(SELECT 1
639                        FROM cn_calc_formulas
640                       WHERE perf_measure_id = p_calc_sql_exp_id OR output_exp_id = p_calc_sql_exp_id)
641              )
642           OR (
643               EXISTS(
644                   SELECT 1
645                     FROM cn_formula_inputs
646                    WHERE calc_sql_exp_id = p_calc_sql_exp_id
647                          OR f_calc_sql_exp_id = p_calc_sql_exp_id)
648              )
649           OR (EXISTS(SELECT 1
650                        FROM cn_rate_dim_tiers
651                       WHERE min_exp_id = p_calc_sql_exp_id OR max_exp_id = p_calc_sql_exp_id));
652 
653     CURSOR exp_exists IS
654       SELECT 1
655         FROM cn_calc_sql_exps
656        WHERE NAME = p_name AND org_id = p_org_id AND calc_sql_exp_id <> p_calc_sql_exp_id;
657   BEGIN
658     -- Standard Start of API savepoint
659     SAVEPOINT update_expression;
660 
661     -- Standard call to check for call compatibility.
662     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
663       RAISE fnd_api.g_exc_unexpected_error;
664     END IF;
665 
666     -- Initialize message list if p_init_msg_list is set to TRUE.
667     IF fnd_api.to_boolean(p_init_msg_list) THEN
668       fnd_msg_pub.initialize;
669     END IF;
670 
671     --  Initialize API return status to success
672     x_return_status  := fnd_api.g_ret_sts_success;
673 
674     -- API body
675     IF (p_name IS NULL) THEN
676       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
677         l_prompt  := cn_api.get_lkup_meaning('EXP_NAME', 'CN_PROMPTS');
678         fnd_message.set_name('CN', 'CN_CANNOT_NULL');
679         fnd_message.set_token('OBJ_NAME', l_prompt);
680         fnd_msg_pub.ADD;
681       END IF;
682 
683       RAISE fnd_api.g_exc_error;
684     END IF;
685 
686     OPEN exp_exists;
687     FETCH exp_exists INTO l_dummy;
688     CLOSE exp_exists;
689 
690     IF (l_dummy = 1) THEN
691       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
692         fnd_message.set_name('CN', 'CN_NAME_NOT_UNIQUE');
693         fnd_msg_pub.ADD;
694       END IF;
695 
696       RAISE fnd_api.g_exc_error;
697     END IF;
698 
699     -- see if expression is in use
700     OPEN parent_exist;
701     FETCH parent_exist INTO l_dummy;
702     CLOSE parent_exist;
703 
704     IF (l_dummy = 1) THEN
705       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
706         fnd_message.set_name('CN', 'CN_EXP_IN_USE');
707         fnd_msg_pub.ADD;
708       END IF;
709 
710       RAISE fnd_api.g_exc_error;
711     END IF;
712 
713     -- parse the expression and classify it into sub types
714     classify_expression(
715       p_org_id                     => p_org_id
716     , p_sql_select                 => p_sql_select
717     , p_sql_from                   => p_sql_from
718     , p_piped_sql_select           => p_piped_sql_select
719     , p_piped_sql_from             => p_piped_sql_from
720     , x_status                     => x_status
721     , x_exp_type_code              => x_exp_type_code
722     , x_msg_count                  => x_msg_count
723     , x_msg_data                   => x_msg_data
724     );
725     -- check ovn
726     cn_calc_sql_exps_pkg.lock_row(p_calc_sql_exp_id, p_ovn);
727     -- do update
728     cn_calc_sql_exps_pkg.update_row(
729       x_org_id                     => p_org_id
730     , x_calc_sql_exp_id            => p_calc_sql_exp_id
731     , x_name                       => p_name
732     , x_description                => p_description
733     , x_status                     => x_status
734     , x_exp_type_code              => x_exp_type_code
735     , x_expression_disp            => p_expression_disp
736     , x_sql_select                 => p_sql_select
737     , x_sql_from                   => p_sql_from
738     , x_piped_sql_select           => p_piped_sql_select
739     , x_piped_sql_from             => p_piped_sql_from
740     , x_piped_expression_disp      => p_piped_expression_disp
741     , x_object_version_number      => p_ovn
742     );
743     -- insert new calc edges
744     l_disp_start     := 1;
745     l_select_start   := 1;
746 
747     LOOP
748       l_disp_end      := INSTR(p_piped_expression_disp, '|', l_disp_start, 1);
749 
750       IF (l_disp_end IS NULL OR l_disp_end = 0) THEN
751         EXIT;
752       END IF;
753 
754       l_token         := SUBSTR(p_piped_expression_disp, l_disp_start, l_disp_end - l_disp_start);
755       l_disp_start    := l_disp_end + 1;
756       l_select_end    := INSTR(p_piped_sql_select, '|', l_select_start, 1);
757 
758       -- if the corresponding piped select part is in parenthesis, it is an embedded expression
759       IF (
760               INSTR(p_piped_sql_select, '(', l_select_start, 1) = l_select_start
761           AND (l_select_end - l_select_start) > 1
762          ) THEN
763         l_exp_names  := l_exp_names || l_token || '|';
764 
765         INSERT INTO cn_calc_edges
766                     (
767                      org_id
768                    , calc_edge_id
769                    , parent_id
770                    , child_id
771                    , edge_type
772                    , creation_date
773                    , created_by
774                    , last_update_login
775                    , last_update_date
776                    , last_updated_by
777                     )
778           SELECT org_id
779                , cn_calc_edges_s.NEXTVAL
780                , p_calc_sql_exp_id
781                , calc_sql_exp_id
782                , 'EE'
783                , SYSDATE
784                , fnd_global.user_id
785                , fnd_global.login_id
786                , SYSDATE
787                , fnd_global.user_id
788             FROM cn_calc_sql_exps
789            WHERE NAME = l_token
790              AND NOT EXISTS(
791                    SELECT 1
792                      FROM cn_calc_edges
793                     WHERE parent_id = p_calc_sql_exp_id
794                       AND child_id = (SELECT calc_sql_exp_id
795                                         FROM cn_calc_sql_exps
796                                        WHERE NAME = l_token AND edge_type = 'EE'));
797       ELSIF(INSTR(p_piped_sql_select, 'cn_formula', l_select_start, 1) = l_select_start) THEN
798         l_dummy            := INSTR(p_piped_sql_select, '_', l_select_start, 2) + 1;
799         l_calc_formula_id  :=
800           TO_NUMBER(
801             SUBSTR(p_piped_sql_select, l_dummy, INSTR(p_piped_sql_select, '_', l_dummy, 1) - l_dummy)
802           );
803         l_formula_ids      := l_formula_ids || l_calc_formula_id || '|';
804 
805         INSERT INTO cn_calc_edges
806                     (
807                      org_id
808                    , calc_edge_id
809                    , parent_id
810                    , child_id
811                    , edge_type
812                    , creation_date
813                    , created_by
814                    , last_update_login
815                    , last_update_date
816                    , last_updated_by
817                     )
818           SELECT p_org_id
819                , cn_calc_edges_s.NEXTVAL
820                , p_calc_sql_exp_id
821                , l_calc_formula_id
822                , 'FE'
823                , SYSDATE
824                , fnd_global.user_id
825                , fnd_global.login_id
826                , SYSDATE
827                , fnd_global.user_id
828             FROM DUAL
829            WHERE NOT EXISTS(
830                    SELECT 1
831                      FROM cn_calc_edges
832                     WHERE parent_id = p_calc_sql_exp_id
833                       AND child_id = l_calc_formula_id
834                       AND edge_type = 'FE');
835       END IF;
836 
837       l_select_start  := l_select_end + 1;
838     END LOOP;
839 
840     -- delete obsolete calc edges
841     --IF (l_formula_ids <> '|') THEN
842     DELETE FROM cn_calc_edges
843           WHERE parent_id = p_calc_sql_exp_id
844             AND INSTR(l_formula_ids, '|' || child_id || '|', 1, 1) = 0
845             AND edge_type = 'FE';
846 
847     --END IF;
848 
849     --IF (l_exp_names <> '|') THEN
850     DELETE FROM cn_calc_edges a
851           WHERE a.parent_id = p_calc_sql_exp_id
852             AND a.edge_type = 'EE'
853             AND NOT EXISTS(
854                   SELECT 1
855                     FROM cn_calc_sql_exps b
856                    WHERE a.child_id = b.calc_sql_exp_id
857                      AND INSTR(l_exp_names, '|' || b.NAME || '|', 1, 1) > 0);
858 
859     --END IF;
860 
861     -- update parent expressions and formulas also
862     IF (fnd_api.to_boolean(p_update_parent_also)) THEN
863       NULL;
864     END IF;
865 
866     -- End of API body.
867 
868     -- Standard check of p_commit.
869     IF fnd_api.to_boolean(p_commit) THEN
870       COMMIT WORK;
871     END IF;
872 
873     -- Standard call to get message count and if count is 1, get message info.
874     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
875     , p_encoded                    => fnd_api.g_false);
876   EXCEPTION
877     WHEN fnd_api.g_exc_error THEN
878       ROLLBACK TO update_expression;
879       x_return_status  := fnd_api.g_ret_sts_error;
880       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
881       , p_encoded                    => fnd_api.g_false);
882     WHEN fnd_api.g_exc_unexpected_error THEN
883       ROLLBACK TO update_expression;
884       x_return_status  := fnd_api.g_ret_sts_unexp_error;
885       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
886       , p_encoded                    => fnd_api.g_false);
887     WHEN OTHERS THEN
888       ROLLBACK TO update_expression;
889       x_return_status  := fnd_api.g_ret_sts_unexp_error;
890 
891       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
892         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
893       END IF;
894 
895       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
896       , p_encoded                    => fnd_api.g_false);
897   END update_expression;
898 
899   -- Start of comments
900   --      API name        : Delete_Expression
901   --      Type            : Private.
902   --      Function        :
903   --      Pre-reqs        : None.
904   --      Parameters      :
905   --      IN              : p_api_version        IN      NUMBER       Required
906   --                        p_init_msg_list      IN      VARCHAR2     Optional
907   --                          Default = FND_API.G_FALSE
908   --                        p_commit             IN      VARCHAR2     Optional
909   --                          Default = FND_API.G_FALSE
910   --                        p_validation_level   IN      NUMBER       Optional
911   --                          Default = FND_API.G_VALID_LEVEL_FULL
912   --                        p_calc_sql_exp_id    IN      NUMBER
913   --      OUT             : x_return_status      OUT     VARCHAR2(1)
914   --                        x_msg_count          OUT     NUMBER
915   --                        x_msg_data           OUT     VARCHAR2(4000)
916   --      Version :         Current version      1.0
917   --                        Initial version      1.0
918   --
919   --      Notes           : Delete an expression
920   --                        1) if it is used, it can not be deleted
921   --                        2) delete the embedding relations in cn_calc_edges if there is any
922   --
923   -- End of comments
924   PROCEDURE delete_expression(
925     p_api_version      IN            NUMBER
926   , p_init_msg_list    IN            VARCHAR2 := fnd_api.g_false
927   , p_commit           IN            VARCHAR2 := fnd_api.g_false
928   , p_validation_level IN            NUMBER := fnd_api.g_valid_level_full
929   , p_calc_sql_exp_id  IN            cn_calc_sql_exps.calc_sql_exp_id%TYPE
930   , x_return_status    OUT NOCOPY    VARCHAR2
931   , x_msg_count        OUT NOCOPY    NUMBER
932   , x_msg_data         OUT NOCOPY    VARCHAR2
933   ) IS
934     l_api_name    CONSTANT VARCHAR2(30) := 'Delete_Expression';
935     l_api_version CONSTANT NUMBER       := 1.0;
936     l_dummy                PLS_INTEGER;
937 
938     CURSOR parent_exist IS
939       SELECT 1
940         FROM DUAL
941        WHERE (EXISTS(SELECT 1
942                        FROM cn_calc_edges
943                       WHERE child_id = p_calc_sql_exp_id AND edge_type = 'EE'))
944           OR (
945               EXISTS(SELECT 1
946                        FROM cn_calc_formulas
947                       WHERE perf_measure_id = p_calc_sql_exp_id OR output_exp_id = p_calc_sql_exp_id)
948              )
949           OR (
950               EXISTS(
951                   SELECT 1
952                     FROM cn_formula_inputs
953                    WHERE calc_sql_exp_id = p_calc_sql_exp_id
954                          OR f_calc_sql_exp_id = p_calc_sql_exp_id)
955              )
956           OR (EXISTS(SELECT 1
957                        FROM cn_rate_dim_tiers
958                       WHERE min_exp_id = p_calc_sql_exp_id OR max_exp_id = p_calc_sql_exp_id));
959   BEGIN
960     -- Standard Start of API savepoint
961     SAVEPOINT delete_expression;
962 
963     -- Standard call to check for call compatibility.
964     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
965       RAISE fnd_api.g_exc_unexpected_error;
966     END IF;
967 
968     -- Initialize message list if p_init_msg_list is set to TRUE.
969     IF fnd_api.to_boolean(p_init_msg_list) THEN
970       fnd_msg_pub.initialize;
971     END IF;
972 
973     --  Initialize API return status to success
974     x_return_status  := fnd_api.g_ret_sts_success;
975 
976     -- API body
977     OPEN parent_exist;
978     FETCH parent_exist INTO l_dummy;
979     CLOSE parent_exist;
980 
981     IF (l_dummy = 1) THEN
982       IF (fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_error)) THEN
983         fnd_message.set_name('CN', 'CN_EXP_IN_USE');
984         fnd_msg_pub.ADD;
985       END IF;
986 
987       RAISE fnd_api.g_exc_error;
988     END IF;
989 
990     cn_calc_sql_exps_pkg.delete_row(x_calc_sql_exp_id => p_calc_sql_exp_id);
991 
992     DELETE FROM cn_calc_edges e
993           WHERE edge_type IN('EE', 'FE') AND NOT EXISTS(SELECT 1
994                                                           FROM cn_calc_sql_exps
995                                                          WHERE calc_sql_exp_id = e.parent_id);
996 
997     -- End of API body.
998 
999     -- Standard check of p_commit.
1000     IF fnd_api.to_boolean(p_commit) THEN
1001       COMMIT WORK;
1002     END IF;
1003 
1004     -- Standard call to get message count and if count is 1, get message info.
1005     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1006     , p_encoded                    => fnd_api.g_false);
1007   EXCEPTION
1008     WHEN fnd_api.g_exc_error THEN
1009       ROLLBACK TO delete_expression;
1010       x_return_status  := fnd_api.g_ret_sts_error;
1011       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1012       , p_encoded                    => fnd_api.g_false);
1013     WHEN fnd_api.g_exc_unexpected_error THEN
1014       ROLLBACK TO delete_expression;
1015       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1016       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1017       , p_encoded                    => fnd_api.g_false);
1018     WHEN OTHERS THEN
1019       ROLLBACK TO delete_expression;
1020       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1021 
1022       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1023         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
1024       END IF;
1025 
1026       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1027       , p_encoded                    => fnd_api.g_false);
1028   END delete_expression;
1029 
1030   /*-- Start of comments
1031   --      API name        : Get_Parent_Expressions
1032   --      Type            : Private.
1033   --      Function        :
1034   --      Pre-reqs        : None.
1035   --      Parameters      :
1036   --      IN              : p_api_version        IN      NUMBER       Required
1037   --                        p_init_msg_list      IN      VARCHAR2     Optional
1038   --                          Default = FND_API.G_FALSE
1039   --                        p_commit             IN      VARCHAR2     Optional
1040   --                          Default = FND_API.G_FALSE
1041   --                        p_validation_level   IN      NUMBER       Optional
1042   --                          Default = FND_API.G_VALID_LEVEL_FULL
1043   --                        p_calc_sql_exp_id    IN      NUMBER
1044   --      OUT             : x_parents_tbl        OUT     expression_tbl_type
1045   --                        x_return_status      OUT     VARCHAR2(1)
1046   --                        x_msg_count          OUT     NUMBER
1047   --                        x_msg_data           OUT     VARCHAR2(4000)
1048   --      Version :         Current version      1.0
1049   --                        Initial version      1.0
1050   --
1051   --      Notes           : Get parent expressions if there is any
1052   --
1053   -- End of comments
1054   PROCEDURE Get_Parent_Expressions
1055     (p_api_version                  IN      NUMBER                          ,
1056      p_init_msg_list                IN      VARCHAR2 := FND_API.G_FALSE     ,
1057      p_commit                       IN      VARCHAR2 := FND_API.G_FALSE     ,
1058      p_validation_level             IN      NUMBER  :=  FND_API.G_VALID_LEVEL_FULL ,
1059      p_calc_sql_exp_id              IN      CN_CALC_SQL_EXPS.CALC_SQL_EXP_ID%TYPE,
1060      x_parents_tbl                  OUT NOCOPY     parent_expression_tbl_type      ,
1061      x_return_status                OUT NOCOPY     VARCHAR2                        ,
1062      x_msg_count                    OUT NOCOPY     NUMBER                          ,
1063      x_msg_data                     OUT NOCOPY     VARCHAR2                        )
1064     IS
1065        l_api_name                  CONSTANT VARCHAR2(30) := 'Get_Parent_Expressions';
1066        l_api_version               CONSTANT NUMBER       := 1.0;
1067 
1068        i                           pls_integer           := 0;
1069 
1070        -- names of parent performance measures and formulas and dimensions
1071        CURSOR parent_names IS
1072     SELECT name
1073       FROM cn_calc_sql_exps
1074       WHERE calc_sql_exp_id IN (SELECT parent_id
1075               FROM cn_calc_edges
1076               CONNECT BY child_id = PRIOR parent_id
1077               AND edge_type = 'EE'
1078               START WITH child_id = p_calc_sql_exp_id
1079               AND edge_type = 'EE')
1080       UNION ALL
1081       SELECT name
1082       FROM cn_rate_dimensions
1083       WHERE rate_dimension_id in (SELECT rate_dimension_id
1084                   FROM cn_rate_dim_tiers
1085                  WHERE min_exp_id = p_calc_sql_exp_id
1086                 OR max_exp_id = p_calc_sql_exp_id)
1087       UNION ALL
1088       SELECT name
1089       FROM cn_calc_formulas
1090       WHERE perf_measure_id = p_calc_sql_exp_id
1091       OR output_exp_id = p_calc_sql_exp_id
1092       OR f_output_exp_id = p_calc_sql_exp_id
1093       OR (calc_formula_id IN (SELECT calc_formula_id FROM cn_formula_inputs
1094             WHERE calc_sql_exp_id = p_calc_sql_exp_id
1095             OR  f_calc_sql_exp_id = p_calc_sql_exp_id));
1096 
1097   BEGIN
1098      -- Standard call to check for call compatibility.
1099      IF NOT FND_API.Compatible_API_Call
1100        (l_api_version           ,
1101         p_api_version           ,
1102         l_api_name              ,
1103         G_PKG_NAME )
1104        THEN
1105         RAISE FND_API.G_EXC_UNEXPECTED_ERROR;
1106      END IF;
1107      -- Initialize message list if p_init_msg_list is set to TRUE.
1108      IF FND_API.to_Boolean( p_init_msg_list ) THEN
1109         FND_MSG_PUB.initialize;
1110      END IF;
1111      --  Initialize API return status to success
1112      x_return_status := FND_API.G_RET_STS_SUCCESS;
1113 
1114      -- API body
1115      FOR parent_name IN parent_names LOOP
1116         x_parents_tbl(i) := parent_name.name;
1117         i := i + 1;
1118      END LOOP;
1119 
1120      -- End of API body.
1121 
1122      -- Standard check of p_commit.
1123      IF FND_API.To_Boolean( p_commit ) THEN
1124         COMMIT WORK;
1125      END IF;
1126      -- Standard call to get message count and if count is 1, get message info.
1127      FND_MSG_PUB.count_and_get
1128        (p_count                 =>      x_msg_count             ,
1129         p_data                  =>      x_msg_data              ,
1130         p_encoded               =>      FND_API.G_FALSE         );
1131   EXCEPTION
1132      WHEN FND_API.G_EXC_ERROR THEN
1133         x_return_status := FND_API.G_RET_STS_ERROR ;
1134         FND_MSG_PUB.count_and_get
1135     (p_count                 =>      x_msg_count             ,
1136      p_data                  =>      x_msg_data              ,
1137      p_encoded               =>      FND_API.G_FALSE         );
1138      WHEN FND_API.G_EXC_UNEXPECTED_ERROR THEN
1139         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1140         FND_MSG_PUB.count_and_get
1141     (p_count                 =>      x_msg_count             ,
1142      p_data                  =>      x_msg_data              ,
1143      p_encoded               =>      FND_API.G_FALSE         );
1144      WHEN OTHERS THEN
1145         x_return_status := FND_API.G_RET_STS_UNEXP_ERROR ;
1146         IF      FND_MSG_PUB.check_msg_level
1147     (FND_MSG_PUB.G_MSG_LVL_UNEXP_ERROR)
1148     THEN
1149      FND_MSG_PUB.add_exc_msg
1150        (G_PKG_NAME          ,
1151         l_api_name           );
1152         END IF;
1153         FND_MSG_PUB.count_and_get
1154     (p_count                 =>      x_msg_count             ,
1155      p_data                  =>      x_msg_data              ,
1156      p_encoded               =>      FND_API.G_FALSE         );
1157   END Get_Parent_Expressions; */
1158 
1159   /* PROCEDURE get_expr_summary
1160     (p_first                        IN      NUMBER,
1161      p_last                         IN      NUMBER,
1162      p_srch_name                    IN      VARCHAR2 := '%',
1163      x_total_rows                   OUT NOCOPY     NUMBER,
1164      x_result_tbl                   OUT NOCOPY     calc_expression_tbl_type) IS
1165 
1166     l_count                         NUMBER := 0;
1167     l_srch_name                     varchar2(31) := upper(p_srch_name) || '%';
1168 
1169     CURSOR get_rows IS
1170     select calc_sql_exp_id, name, description, status, exp_type_code
1171       from cn_calc_sql_exps
1172      where upper(name) like l_srch_name
1173      order by 2;
1174     CURSOR count_rows IS select count(1) from cn_calc_sql_exps
1175      where upper(name) like l_srch_name;
1176 
1177   BEGIN
1178      open  count_rows;
1179      fetch count_rows into x_total_rows;
1180      close count_rows;
1181      for c in get_rows loop
1182         l_count := l_count + 1;
1183         if l_count >= p_first then
1184      x_result_tbl(l_count) := c;  -- record copy ok because of %types
1185         end if;
1186         if l_count = p_last then
1187      exit;
1188         end if;
1189      end loop;
1190   END get_expr_summary; */
1191 
1192   /* PROCEDURE get_expr_detail
1193     (p_calc_sql_exp_id              IN     CN_CALC_SQL_EXPS.CALC_SQL_EXP_ID%TYPE,
1194      x_name                         OUT NOCOPY    CN_CALC_SQL_EXPS.NAME%TYPE,
1195      x_description                  OUT NOCOPY    CN_CALC_SQL_EXPS.DESCRIPTION%TYPE,
1196      x_status                       OUT NOCOPY    CN_CALC_SQL_EXPS.STATUS%TYPE,
1197      x_exp_type_code                OUT NOCOPY    CN_CALC_SQL_EXPS.EXP_TYPE_CODE%TYPE,
1198      x_expression_disp              OUT NOCOPY    VARCHAR2, -- CLOBs
1199      x_sql_select                   OUT NOCOPY    VARCHAR2,
1200      x_sql_from                     OUT NOCOPY    VARCHAR2,
1201      x_piped_sql_select             OUT NOCOPY    VARCHAR2,
1202      x_piped_sql_from               OUT NOCOPY    VARCHAR2,
1203      x_piped_expression_disp        OUT NOCOPY    VARCHAR2,
1204      x_ovn                          OUT NOCOPY    CN_CALC_SQL_EXPS.OBJECT_VERSION_NUMBER%TYPE) IS
1205 
1206      CURSOR get_data IS
1207         select name, description, status, exp_type_code,
1208          dbms_lob.substr(expression_disp),
1209          dbms_lob.substr(sql_select),
1210            dbms_lob.substr(sql_from),
1211          dbms_lob.substr(piped_sql_select),
1212          dbms_lob.substr(piped_sql_from),
1213          dbms_lob.substr(piped_expression_disp),
1214          object_version_number
1215     from cn_calc_sql_exps where calc_sql_exp_id = p_calc_sql_exp_id;
1216   BEGIN
1217      OPEN  get_data;
1218      FETCH get_data INTO x_name, x_description, x_status, x_exp_type_code,
1219            x_expression_disp, x_sql_select, x_sql_from,
1220            x_piped_sql_select, x_piped_sql_from, x_piped_expression_disp, x_ovn;
1221      CLOSE get_data;
1222   END get_expr_detail; */
1223 
1224   /* FUNCTION add_tree_node(node_value                     VARCHAR2,
1225              node_label                     VARCHAR2,
1226              parent_node_value              VARCHAR2,
1227              element                        VARCHAR2)
1228     RETURN expr_type_rec_type IS
1229      l_rec   expr_type_rec_type;
1230   BEGIN
1231      l_rec.node_value        := node_value;
1232      l_rec.node_label        := nvl(node_label, node_value);
1233      l_rec.parent_node_value := parent_node_value;
1234      l_rec.element           := element;
1235      return l_rec;
1236   END add_tree_node; */
1237 
1238   /* PROCEDURE get_type_tree
1239     (x_types                        OUT NOCOPY    expr_type_tbl_type) IS
1240       cursor osc_elements is
1241       select user_name, name, alias, object_id
1242         from cn_objects
1243        where calc_eligible_flag = 'Y'
1244          and object_type in ('TBL', 'VIEW')
1245          and user_name is not null
1246          and object_id < 0
1247          and name like 'CN%'
1248          and alias is not null
1249     order by user_name;
1250 
1251       cursor table_columns(p_table_id number) is
1252       select user_name, name
1253         from cn_objects
1254        where table_id = p_table_id
1255          and calc_formula_flag = 'Y'
1256          and object_type = 'COL'
1257     order by user_name;
1258 
1259       cursor calc_expressions is
1260       select calc_sql_exp_id, name, dbms_lob.substr(sql_select) node_value
1261         from cn_calc_sql_exps
1262        where status = 'VALID'
1263          and dbms_lob.getlength(sql_select) < 3999
1264     order by name;
1265 
1266       cursor calc_formulas is
1267       select name, 'cn_formula_' || abs(calc_formula_id) || '_' || abs(org_id) ||
1268              '_pkg.get_result(p_commission_line_id)' node_value
1269         from cn_calc_formulas
1270        where formula_status = 'COMPLETE'
1271          and cumulative_flag = 'N'
1272          and trx_group_code = 'INDIVIDUAL'
1273          and itd_flag = 'N'
1274          and formula_type = 'C'
1275     order by name;
1276 
1277       cursor ext_elements is
1278       select user_name, name, alias, object_id
1279         from cn_objects
1280        where calc_eligible_flag = 'Y'
1281          and object_type in ('TBL', 'VIEW')
1282          and user_name is not null
1283          and object_id > 0
1284     order by user_name;
1285 
1286       cursor plan_elements is
1287       select quota_id, name
1288         from cn_quotas_v
1289     order by name;
1290 
1291 
1292 
1293      TYPE vt is table of varchar2(30);
1294      num_functions vt := vt('ABS', 'CEIL', 'EXP', 'FLOOR', 'GREATEST', 'LEAST',
1295           'MOD', 'POWER', 'ROUND', 'SIGN', 'SQRT', 'TO_NUMBER', 'TRUNC');
1296      grp_functions vt := vt('AVG', 'COUNT', 'MAX', 'MIN', 'STDDEV',
1297           'SUM', 'VARIANCE');
1298      oth_functions vt := vt('DECODE', 'NVL');
1299      pe_columns    vt := vt('TARGET_AMOUNT', 'COMMISSION_PAYED_PTD','ITD_TARGET',
1300           'PERIOD_PAYMENT', 'ITD_PAYMENT',
1301           'COMMISSION_PAYED_ITD', 'INPUT_ACHIEVED_PTD',
1302           'INPUT_ACHIEVED_ITD', 'PERF_ACHIEVED_PTD',
1303           'PERF_ACHIEVED_ITD');
1304      l_count       number := 0;
1305   BEGIN
1306      -- add nodes of calculation value tree in DFS order
1307      x_types(l_count) :=
1308        add_tree_node('OSC_ELEMENTS',
1309          cn_api.get_lkup_meaning('OSC_ELEMENTS', 'EXPRESSION_TYPE'),
1310          null, null);
1311      l_count := l_count + 1;
1312      for t in osc_elements loop
1313         x_types(l_count) :=
1314     add_tree_node(t.name || '|' ||t.alias,t.user_name,'OSC_ELEMENTS',null);
1315         l_count := l_count + 1;
1316         for c in table_columns(t.object_id) loop
1317      x_types(l_count) :=
1318        add_tree_node(t.user_name || '.' || c.user_name,c.user_name, t.name,
1319          t.alias || '.' || c.name);
1320      l_count := l_count + 1;
1321         end loop;
1322      end loop;
1323 
1324      x_types(l_count) :=
1325        add_tree_node('EXPRESSIONS',
1326          cn_api.get_lkup_meaning('EXPRESSIONS', 'EXPRESSION_TYPE'),
1327          null, null);
1328      l_count := l_count + 1;
1329      for e in calc_expressions loop
1330         x_types(l_count) :=
1331     add_tree_node(e.name, e.name, 'EXPRESSIONS', '(' ||e.node_value|| ')');
1332         l_count := l_count + 1;
1333      end loop;
1334 
1335      x_types(l_count) :=
1336        add_tree_node('FORMULAS',
1337          cn_api.get_lkup_meaning('FORMULAS', 'EXPRESSION_TYPE'),null,
1338          null);
1339      l_count := l_count + 1;
1340      for f in calc_formulas loop
1341         x_types(l_count) :=
1342     add_tree_node(f.name, f.name, 'FORMULAS', f.node_value);
1343         l_count := l_count + 1;
1344      end loop;
1345 
1346      x_types(l_count) :=
1347        add_tree_node('EXTERNAL_ELEMENTS',
1348          cn_api.get_lkup_meaning('EXTERNAL_ELEMENTS',
1349                'EXPRESSION_TYPE'),
1350          null, null);
1351      l_count := l_count + 1;
1352      for x in ext_elements loop
1353         x_types(l_count) :=
1354     add_tree_node(x.name || '|' || x.alias, x.user_name,
1355             'EXTERNAL_ELEMENTS',
1356             null);
1357         l_count := l_count + 1;
1358         for c in table_columns(x.object_id) loop
1359      x_types(l_count) :=
1360        add_tree_node(x.user_name || '.' || c.user_name,c.user_name, x.name,
1361          x.alias || '.' || c.name);
1362      l_count := l_count + 1;
1363         end loop;
1364      end loop;
1365 
1366      x_types(l_count) :=
1367        add_tree_node('SQL_FUNCTIONS', cn_api.get_lkup_meaning('SQL_FUNCTIONS',
1368                     'EXPRESSION_TYPE'),
1369          null, null);
1370      l_count := l_count + 1;
1371      x_types(l_count) :=
1372        add_tree_node('NUMBER_FUNCTIONS',
1373          cn_api.get_lkup_meaning('NUMBER_FUNCTIONS',
1374                'EXPRESSION_TYPE'),
1375          'SQL_FUNCTIONS', null);
1376      l_count := l_count + 1;
1377      for i in num_functions.first..num_functions.last loop
1378         x_types(l_count) :=
1379     add_tree_node(num_functions(i) || '(', num_functions(i),
1380             'NUMBER_FUNCTIONS', num_functions(i) || '(');
1381         l_count := l_count + 1;
1382      end loop;
1383      x_types(l_count) :=
1384        add_tree_node('GROUP_FUNCTIONS',
1385          cn_api.get_lkup_meaning('GROUP_FUNCTIONS',
1386                'EXPRESSION_TYPE'),
1387          'SQL_FUNCTIONS', null);
1388      l_count := l_count + 1;
1389      for i in grp_functions.first..grp_functions.last loop
1390         x_types(l_count) :=
1391     add_tree_node(grp_functions(i) || '(', grp_functions(i) || '()',
1392             'GROUP_FUNCTIONS', grp_functions(i) || '(');
1393         l_count := l_count + 1;
1394      end loop;
1395 
1396      x_types(l_count) :=
1397        add_tree_node('OTHER_FUNCTIONS',
1398          cn_api.get_lkup_meaning('OTHERS', 'EXPRESSION_TYPE'),
1399          'SQL_FUNCTIONS', null);
1400      l_count := l_count + 1;
1401      for i in oth_functions.first..oth_functions.last loop
1402         x_types(l_count) :=
1403     add_tree_node(oth_functions(i) || '(', oth_functions(i) || '()',
1404             'OTHER_FUNCTIONS',
1405             oth_functions(i) || '(');
1406         l_count := l_count + 1;
1407      end loop;
1408 
1409   -- Previously Commented out - START
1410 
1411      x_types(l_count) :=
1412        add_tree_node('PLAN_ELEMENTS',
1413          cn_api.get_lkup_meaning('PLAN_ELTS', 'EXPRESSION_TYPE'),
1414          null, null);
1415      l_count := l_count + 1;
1416      for i in plan_elements loop
1417         x_types(l_count) :=
1418     add_tree_node(i.quota_id || 'PE', i.name, 'PLAN_ELEMENTS', null);
1419         l_count := l_count + 1;
1420         for j in pe_columns.first..pe_columns.last loop
1421      x_types(l_count) :=
1422        add_tree_node(i.name || '.' || pe_columns(j),
1423          i.name || '.' || pe_columns(j),
1424          i.quota_id || 'PE',
1425          '(' || i.quota_id || 'PE.' || pe_columns(j) || ')');
1426      l_count := l_count + 1;
1427         end loop;
1428      end loop;
1429 
1430   -- Previously Commented out - END
1431 
1432      x_types(l_count) :=
1433        add_tree_node('OTHERS', cn_api.get_lkup_meaning('OTHERS',
1434                    'EXPRESSION_TYPE'),
1435          null, null);
1436      l_count := l_count + 1;
1437      x_types(l_count) :=
1438        add_tree_node(cn_api.get_lkup_meaning('RATE_TABLE_RESULT',
1439                'EXPRESSION_TYPE'),
1440          cn_api.get_lkup_meaning('RATE_TABLE_RESULT',
1441                'EXPRESSION_TYPE'),
1442          'OTHERS', 'RateResult');
1443      l_count := l_count + 1;
1444      x_types(l_count) :=
1445        add_tree_node(cn_api.get_lkup_meaning('FORECAST_AMOUNT',
1446                'EXPRESSION_TYPE'),
1447          cn_api.get_lkup_meaning('FORECAST_AMOUNT',
1448                'EXPRESSION_TYPE'),
1449          'OTHERS', 'ForecastAmount');
1450      l_count := l_count + 1;
1451   END get_type_tree; */
1452 
1453   -- parse a sql select statement looking for included plan elements
1454   -- of the form (1234PE.COLUMN_NAME).  if any are found, include them in
1455   -- the x_plan_elt_tbl and provide a parsed version of the sql select.
1456   PROCEDURE parse_plan_elements(
1457     p_sql_select        IN            VARCHAR2
1458   , x_plan_elt_tbl      OUT NOCOPY    num_tbl_type
1459   , x_parsed_sql_select OUT NOCOPY    VARCHAR2
1460   ) IS
1461     s        VARCHAR2(1);   -- character before 'PE'
1462     pe       VARCHAR2(30);   -- plan element ID
1463     i        NUMBER       := 0;   -- index vars
1464     ix       NUMBER;
1465     openpar  NUMBER;   -- looking for parenthesis
1466     clspar   NUMBER;
1467     CONTINUE BOOLEAN      := TRUE;
1468   BEGIN
1469     ix                   := 0;
1470     x_parsed_sql_select  := p_sql_select;
1471 
1472     WHILE CONTINUE LOOP
1473       i  := INSTR(x_parsed_sql_select, 'PE.', i + 1);
1474 
1475       IF i = 0 THEN
1476         CONTINUE  := FALSE;
1477       ELSE
1478         -- see if character before 'PE' is a number...
1479         -- if so then it's a plan element
1480         s  := SUBSTR(x_parsed_sql_select, i - 1, 1);
1481 
1482         IF s BETWEEN '0' AND '9' THEN
1483           -- get surrounding parenthesis
1484           openpar              := INSTR(x_parsed_sql_select, '(', i - LENGTH(x_parsed_sql_select));
1485           clspar               := INSTR(x_parsed_sql_select, ')', i);
1486           pe                   := SUBSTR(x_parsed_sql_select, openpar + 1, i - openpar - 1);
1487           x_parsed_sql_select  :=
1488                SUBSTR(x_parsed_sql_select, 1, openpar) || '0'
1489                || SUBSTR(x_parsed_sql_select, clspar);
1490           ix                   := ix + 1;
1491           x_plan_elt_tbl(ix)   := pe;
1492         END IF;
1493       END IF;
1494     END LOOP;
1495   END parse_plan_elements;
1496 
1497   -- private procedure used in get_dependent_plan_elts
1498   PROCEDURE dfs(
1499     p_original_node_type               VARCHAR2
1500   , p_original_node_id                 NUMBER
1501   , p_node_type                        VARCHAR2
1502   , p_current_id                       NUMBER
1503   , p_level                            NUMBER
1504   , p_pe_arr             IN OUT NOCOPY num_tbl_type
1505   ) IS
1506     CURSOR get_formula_id IS
1507       SELECT calc_formula_id
1508         FROM cn_quotas_v
1509        WHERE quota_id = p_current_id;
1510 
1511     CURSOR get_exp_ids IS
1512       SELECT ccse.calc_sql_exp_id
1513         FROM cn_calc_sql_exps ccse, cn_calc_formulas ccf, cn_formula_inputs cfi
1514        WHERE (
1515                  (ccse.calc_sql_exp_id = ccf.perf_measure_id)
1516               OR (ccse.calc_sql_exp_id = ccf.output_exp_id)
1517               OR (ccse.calc_sql_exp_id = cfi.calc_sql_exp_id)
1518               OR (ccse.calc_sql_exp_id = cfi.f_calc_sql_exp_id)
1519              )
1520          AND cfi.calc_formula_id = ccf.calc_formula_id
1521          AND ccf.calc_formula_id = p_current_id;
1522 
1523     CURSOR get_child_edges IS
1524       SELECT child_id
1525         FROM cn_calc_edges
1526        WHERE edge_type = 'FE' AND parent_id = p_current_id;
1527 
1528     CURSOR get_sql_sel IS
1529       SELECT DBMS_LOB.SUBSTR(sql_select)
1530         FROM cn_calc_sql_exps
1531        WHERE calc_sql_exp_id = p_current_id;
1532 
1533     l_current_id NUMBER;
1534     l_pe_tbl     cn_calc_sql_exps_pvt.num_tbl_type;
1535     l_sql_sel    VARCHAR2(4000);
1536     l_junk       VARCHAR2(4000);
1537   BEGIN
1538     IF p_node_type = p_original_node_type AND p_current_id = p_original_node_id AND p_level > 0 THEN
1539       fnd_message.set_name('CN', 'CN_PE_CANNOT_REF_ITSEF');
1540       fnd_msg_pub.ADD;
1541       RAISE fnd_api.g_exc_error;
1542     END IF;
1543 
1544     IF p_node_type = 'P' THEN
1545       IF p_level > 0 THEN
1546         -- don't return the root as a dependence
1547         p_pe_arr(p_pe_arr.COUNT)  := p_current_id;
1548       END IF;
1549 
1550       l_current_id  := NULL;
1551 
1552       OPEN get_formula_id;
1553       FETCH get_formula_id INTO l_current_id;
1554       CLOSE get_formula_id;
1555 
1556       IF l_current_id IS NOT NULL THEN
1557         dfs(p_original_node_type, p_original_node_id, 'F', l_current_id, p_level + 1, p_pe_arr);
1558       END IF;
1559     ELSIF p_node_type = 'F' THEN
1560       FOR x IN get_exp_ids LOOP
1561         dfs(p_original_node_type, p_original_node_id, 'E', x.calc_sql_exp_id, p_level + 1
1562         , p_pe_arr);
1563       END LOOP;
1564     ELSIF p_node_type = 'E' THEN
1565       OPEN get_sql_sel;
1566       FETCH get_sql_sel INTO l_sql_sel;
1567       CLOSE get_sql_sel;
1568 
1569       cn_calc_sql_exps_pvt.parse_plan_elements(l_sql_sel, l_pe_tbl, l_junk);
1570 
1571       FOR x IN 1 .. l_pe_tbl.COUNT LOOP
1572         dfs(p_original_node_type, p_original_node_id, 'P', l_pe_tbl(x), p_level + 1, p_pe_arr);
1573       END LOOP;
1574 
1575       FOR x IN get_child_edges LOOP
1576         dfs(p_original_node_type, p_original_node_id, 'F', x.child_id, p_level + 1, p_pe_arr);
1577       END LOOP;
1578     END IF;
1579   END dfs;
1580 
1581   -- given a plan element, formula, or expression, determine all the plan
1582   -- elements referenced directly or indirectly
1583   -- pass in a node type (formula=F, plan element=P, expression=E), and the ID
1584   PROCEDURE get_dependent_plan_elts(
1585     p_api_version      IN            NUMBER
1586   , p_init_msg_list    IN            VARCHAR2 := fnd_api.g_false
1587   , p_commit           IN            VARCHAR2 := fnd_api.g_false
1588   , p_validation_level IN            NUMBER := fnd_api.g_valid_level_full
1589   , p_node_type        IN            VARCHAR2
1590   , p_node_id          IN            NUMBER
1591   , x_plan_elt_id_tbl  OUT NOCOPY    num_tbl_type
1592   , x_return_status    OUT NOCOPY    VARCHAR2
1593   , x_msg_count        OUT NOCOPY    NUMBER
1594   , x_msg_data         OUT NOCOPY    VARCHAR2
1595   ) IS
1596     l_api_name    CONSTANT VARCHAR2(30) := 'get_dependent_plan_elts';
1597     l_api_version CONSTANT NUMBER       := 1.0;
1598   BEGIN
1599     -- Standard call to check for call compatibility.
1600     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
1601       RAISE fnd_api.g_exc_unexpected_error;
1602     END IF;
1603 
1604     -- Initialize message list if p_init_msg_list is set to TRUE.
1605     IF fnd_api.to_boolean(p_init_msg_list) THEN
1606       fnd_msg_pub.initialize;
1607     END IF;
1608 
1609     --  Initialize API return status to success
1610     x_return_status  := fnd_api.g_ret_sts_success;
1611     -- API body
1612     dfs(p_node_type, p_node_id, p_node_type, p_node_id, 0, x_plan_elt_id_tbl);
1613 
1614     -- Standard check of p_commit.
1615     IF fnd_api.to_boolean(p_commit) THEN
1616       COMMIT WORK;
1617     END IF;
1618 
1619     -- Standard call to get message count and if count is 1, get message info.
1620     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1621     , p_encoded                    => fnd_api.g_false);
1622   EXCEPTION
1623     WHEN fnd_api.g_exc_error THEN
1624       x_return_status  := fnd_api.g_ret_sts_error;
1625       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1626       , p_encoded                    => fnd_api.g_false);
1627     WHEN fnd_api.g_exc_unexpected_error THEN
1628       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1629       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1630       , p_encoded                    => fnd_api.g_false);
1631     WHEN OTHERS THEN
1632       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1633 
1634       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1635         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
1636       END IF;
1637 
1638       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1639       , p_encoded                    => fnd_api.g_false);
1640   END get_dependent_plan_elts;
1641 
1642   -- private procedure used in get_parent_plan_elts
1643   PROCEDURE dfs2(
1644     p_original_node_type               VARCHAR2
1645   , p_original_node_id                 NUMBER
1646   , p_node_type                        VARCHAR2
1647   , p_current_id                       NUMBER
1648   , p_level                            NUMBER
1649   , p_pe_arr             IN OUT NOCOPY num_tbl_type
1650   ) IS
1651     CURSOR get_quota_ids IS
1652       SELECT quota_id
1653         FROM cn_quotas_v
1654        WHERE calc_formula_id = p_current_id;
1655 
1656     CURSOR get_exp_ids IS
1657       SELECT calc_sql_exp_id
1658         FROM cn_calc_sql_exps
1659        WHERE DBMS_LOB.SUBSTR(sql_select) LIKE '%(' || p_current_id || 'PE.%';
1660 
1661     CURSOR get_formulas IS
1662       SELECT calc_formula_id
1663         FROM cn_formula_inputs
1664        WHERE calc_sql_exp_id = p_current_id OR f_calc_sql_exp_id = p_current_id
1665       UNION ALL
1666       SELECT calc_formula_id
1667         FROM cn_calc_formulas
1668        WHERE output_exp_id = p_current_id
1669           OR f_output_exp_id = p_current_id
1670           OR perf_measure_id = p_current_id;
1671 
1672     CURSOR get_parent_exps IS
1673       SELECT parent_id exp_id
1674         FROM cn_calc_edges
1675        WHERE edge_type = 'FE' AND child_id = p_current_id;
1676 
1677     l_current_id NUMBER;
1678     l_pe_tbl     cn_calc_sql_exps_pvt.num_tbl_type;
1679   BEGIN
1680     IF p_node_type = p_original_node_type AND p_current_id = p_original_node_id AND p_level > 0 THEN
1681       fnd_message.set_name('CN', 'CN_PE_CANNOT_REF_ITSEF');
1682       fnd_msg_pub.ADD;
1683       RAISE fnd_api.g_exc_error;
1684     END IF;
1685 
1686     IF p_node_type = 'P' THEN
1687       -- Don't return the root as a dependence
1688       IF p_level > 0 THEN
1689         -- Dont add Duplicate Entries
1690         FOR i IN 0..p_pe_arr.COUNT LOOP
1691           -- If we have reached the end of the table, then we can add our element
1692           IF i = p_pe_arr.COUNT THEN
1693             p_pe_arr(p_pe_arr.COUNT)  := p_current_id;
1694             EXIT;
1695           END IF;
1696 
1697           EXIT WHEN p_pe_arr(i) = p_current_id;
1698         END LOOP;
1699       END IF;
1700 
1701       FOR x IN get_exp_ids LOOP
1702         dfs2(p_original_node_type, p_original_node_id, 'E', x.calc_sql_exp_id, p_level + 1
1703         , p_pe_arr);
1704       END LOOP;
1705     ELSIF p_node_type = 'E' THEN
1706       FOR f IN get_formulas LOOP
1707         dfs2(p_original_node_type, p_original_node_id, 'F', f.calc_formula_id, p_level + 1
1708         , p_pe_arr);
1709       END LOOP;
1710     ELSIF p_node_type = 'F' THEN
1711       FOR x IN get_parent_exps LOOP
1712         dfs2(p_original_node_type, p_original_node_id, 'E', x.exp_id, p_level + 1, p_pe_arr);
1713       END LOOP;
1714 
1715       FOR x IN get_quota_ids LOOP
1716         dfs2(p_original_node_type, p_original_node_id, 'P', x.quota_id, p_level + 1, p_pe_arr);
1717       END LOOP;
1718     END IF;
1719   END dfs2;
1720 
1721   -- given a plan element, formula, or expression, determine all the plan
1722   -- elements that reference it directly or indirectly
1723   -- pass in a node type (formula=F, plan element=P, expression=E), and the ID
1724   PROCEDURE get_parent_plan_elts(
1725     p_api_version      IN            NUMBER
1726   , p_init_msg_list    IN            VARCHAR2 := fnd_api.g_false
1727   , p_commit           IN            VARCHAR2 := fnd_api.g_false
1728   , p_validation_level IN            NUMBER := fnd_api.g_valid_level_full
1729   , p_node_type        IN            VARCHAR2
1730   , p_node_id          IN            NUMBER
1731   , x_plan_elt_id_tbl  OUT NOCOPY    num_tbl_type
1732   , x_return_status    OUT NOCOPY    VARCHAR2
1733   , x_msg_count        OUT NOCOPY    NUMBER
1734   , x_msg_data         OUT NOCOPY    VARCHAR2
1735   ) IS
1736     l_api_name    CONSTANT VARCHAR2(30) := 'get_parent_plan_elts';
1737     l_api_version CONSTANT NUMBER       := 1.0;
1738   BEGIN
1739     -- Standard call to check for call compatibility.
1740     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
1741       RAISE fnd_api.g_exc_unexpected_error;
1742     END IF;
1743 
1744     -- Initialize message list if p_init_msg_list is set to TRUE.
1745     IF fnd_api.to_boolean(p_init_msg_list) THEN
1746       fnd_msg_pub.initialize;
1747     END IF;
1748 
1749     --  Initialize API return status to success
1750     x_return_status  := fnd_api.g_ret_sts_success;
1751     -- API body
1752     dfs2(p_node_type, p_node_id, p_node_type, p_node_id, 0, x_plan_elt_id_tbl);
1753 
1754     -- Standard check of p_commit.
1755     IF fnd_api.to_boolean(p_commit) THEN
1756       COMMIT WORK;
1757     END IF;
1758 
1759     -- Standard call to get message count and if count is 1, get message info.
1760     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1761     , p_encoded                    => fnd_api.g_false);
1762   EXCEPTION
1763     WHEN fnd_api.g_exc_error THEN
1764       x_return_status  := fnd_api.g_ret_sts_error;
1765       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1766       , p_encoded                    => fnd_api.g_false);
1767     WHEN fnd_api.g_exc_unexpected_error THEN
1768       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1769       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1770       , p_encoded                    => fnd_api.g_false);
1771     WHEN OTHERS THEN
1772       x_return_status  := fnd_api.g_ret_sts_unexp_error;
1773 
1774       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
1775         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
1776       END IF;
1777 
1778       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
1779       , p_encoded                    => fnd_api.g_false);
1780   END get_parent_plan_elts;
1781 
1782   PROCEDURE parse_sql_select(
1783     p_api_version      IN            NUMBER
1784   , p_init_msg_list    IN            VARCHAR2 := fnd_api.g_false
1785   , p_commit           IN            VARCHAR2 := fnd_api.g_false
1786   , p_validation_level IN            NUMBER := fnd_api.g_valid_level_full
1787   , p_sql_select       IN OUT NOCOPY VARCHAR2
1788   , x_piped_sql_select OUT NOCOPY    VARCHAR2
1789   , x_expr_disp        OUT NOCOPY    VARCHAR2
1790   , x_piped_expr_disp  OUT NOCOPY    VARCHAR2
1791   , x_sql_from         OUT NOCOPY    VARCHAR2
1792   , x_piped_sql_from   OUT NOCOPY    VARCHAR2
1793   , x_return_status    OUT NOCOPY    VARCHAR2
1794   , x_msg_count        OUT NOCOPY    NUMBER
1795   , x_msg_data         OUT NOCOPY    VARCHAR2
1796   ) IS
1797     l_sql_select_left      VARCHAR2(4000) := p_sql_select;
1798     l_ix                   NUMBER;
1799     l_seg                  VARCHAR2(4000);
1800     l_ix2                  NUMBER;
1801     l_seg2                 VARCHAR2(4000);
1802     l_disp_seg             VARCHAR2(4000);
1803     l_table_id             NUMBER;
1804     l_table_name           VARCHAR2(80);
1805 
1806     TYPE vt IS TABLE OF VARCHAR2(80);
1807 
1808     sel_pieces             vt
1809       := vt(
1810           'RateResult'
1811         , 'ForecastAmount'
1812         , 'ABS('
1813         , 'CEIL('
1814         , 'EXP('
1815         , 'FLOOR('
1816         , 'GREATEST('
1817         , 'LEAST('
1818         , 'MOD('
1819         , 'POWER('
1820         , 'ROUND('
1821         , 'SIGN('
1822         , 'SQRT('
1823         , 'TO_NUMBER('
1824         , 'TRUNC('
1825         , 'AVG('
1826         , 'COUNT('
1827         , 'MAX('
1828         , 'MIN('
1829         , 'STDDEV('
1830         , 'SUM('
1831         , 'VARIANCE('
1832         , 'DECODE('
1833         , 'NVL('
1834         , '*'
1835         , '/'
1836         , '.'
1837         , '-'
1838         , '+'
1839         , ','
1840         , ')'
1841         , '('
1842         );
1843     disp_pieces            vt             := sel_pieces;   -- almost the same
1844     opers                  vt             := vt('/', '+', '*', '-', ' ', ',', ')');
1845     ct                     NUMBER         := 0;
1846     success                BOOLEAN;
1847     found_num              BOOLEAN;
1848     l_api_name    CONSTANT VARCHAR2(30)   := 'parse_sql_select';
1849     l_api_version CONSTANT NUMBER         := 1.0;
1850 
1851     CURSOR get_formula_name(l_segment IN VARCHAR2) IS
1852       SELECT NAME
1853         FROM cn_calc_formulas
1854        WHERE    'cn_formula_'
1855              || calc_formula_id
1856              || '_'
1857              || org_id
1858              || '_pkg.get_result(p_commission_line_id)' = l_segment;
1859 
1860     CURSOR get_pe_name(l_segment IN VARCHAR2) IS
1861       SELECT NAME
1862         FROM cn_quotas_v
1863        WHERE quota_id || 'PE' = l_segment;
1864 
1865     CURSOR get_tbl(l_segment IN VARCHAR2) IS
1866       SELECT user_name
1867            , object_id
1868            , NAME
1869         FROM cn_objects
1870        WHERE calc_eligible_flag = 'Y'
1871          AND object_type IN('TBL', 'VIEW')
1872          AND user_name IS NOT NULL
1873          AND alias = l_segment;
1874 
1875     CURSOR get_col(l_segment IN VARCHAR2, l_table_id IN NUMBER) IS
1876       SELECT user_name
1877         FROM cn_objects
1878        WHERE table_id = l_table_id
1879          AND calc_formula_flag = 'Y'
1880          AND object_type = 'COL'
1881          AND user_name IS NOT NULL
1882          AND NAME = l_segment;
1883 
1884     CURSOR get_user_funcs IS
1885       SELECT object_name
1886         FROM user_objects
1887        WHERE object_type = 'FUNCTION' AND status = 'VALID';
1888   BEGIN
1889     -- Standard call to check for call compatibility.
1890     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
1891       RAISE fnd_api.g_exc_unexpected_error;
1892     END IF;
1893 
1894     -- Initialize message list if p_init_msg_list is set to TRUE.
1895     IF fnd_api.to_boolean(p_init_msg_list) THEN
1896       fnd_msg_pub.initialize;
1897     END IF;
1898 
1899     --  Initialize API return status to success
1900     x_return_status  := fnd_api.g_ret_sts_success;
1901     -- translate RateResult and ForecastAmount
1902     disp_pieces(1)   := cn_api.get_lkup_meaning('RATE_TABLE_RESULT', 'EXPRESSION_TYPE');
1903     disp_pieces(2)   := cn_api.get_lkup_meaning('FORECAST_AMOUNT', 'EXPRESSION_TYPE');
1904 
1905     -- Bug 2295522
1906     -- set p_sql_select to upper
1907     SELECT UPPER(p_sql_select)
1908       INTO l_sql_select_left
1909       FROM DUAL;
1910 
1911     -- next build piped sql select
1912     LOOP
1913       ct       := ct + 1;   -- defend against infinite loop
1914       success  := FALSE;
1915 
1916       -- look for plan element
1917       IF SUBSTR(l_sql_select_left, 1, 1) = '(' THEN
1918         -- get close parenthesis
1919         l_ix        := INSTR(l_sql_select_left, '.');
1920         l_seg       := SUBSTR(l_sql_select_left, 2, l_ix - 2);
1921         l_ix2       := INSTR(l_sql_select_left, ')');
1922         l_seg2      := SUBSTR(l_sql_select_left, l_ix + 1, l_ix2 - l_ix - 1);
1923         l_disp_seg  := NULL;
1924 
1925         OPEN get_pe_name(l_seg);   -- get display name of PE
1926         FETCH get_pe_name INTO l_disp_seg;
1927         CLOSE get_pe_name;
1928 
1929         IF l_disp_seg IS NOT NULL THEN
1930           l_sql_select_left   := SUBSTR(l_sql_select_left, l_ix2 + 1);
1931           x_piped_sql_select  := x_piped_sql_select || '(' || l_seg || '.' || l_seg2 || ')|';
1932           x_piped_expr_disp   := x_piped_expr_disp || l_disp_seg || '.' || l_seg2 || '|';
1933           success             := TRUE;
1934         END IF;
1935       END IF;
1936 
1937       -- look for quoted constant
1938       IF SUBSTR(l_sql_select_left, 1, 1) = '''' AND success = FALSE THEN
1939         -- get close quote
1940         l_ix                := INSTR(l_sql_select_left, '''', 2);
1941 
1942         IF l_ix = 0 THEN
1943           fnd_message.set_name('CN', 'CN_SQL_SELECT_PARSE_ERR');
1944           fnd_msg_pub.ADD;
1945           RAISE fnd_api.g_exc_error;
1946         END IF;
1947 
1948         x_piped_sql_select  := x_piped_sql_select || SUBSTR(l_sql_select_left, 1, l_ix) || '|';
1949         x_piped_expr_disp   := x_piped_expr_disp || SUBSTR(l_sql_select_left, 1, l_ix) || '|';
1950         l_sql_select_left   := SUBSTR(l_sql_select_left, l_ix + 1);
1951         success             := TRUE;
1952       END IF;
1953 
1954       -- look for numeric value
1955       IF success = FALSE THEN
1956         found_num  := FALSE;
1957 
1958         WHILE SUBSTR(l_sql_select_left, 1, 1) BETWEEN '0' AND '9'
1959           OR SUBSTR(l_sql_select_left, 1, 1) = '.' LOOP
1960           x_piped_sql_select  := x_piped_sql_select || SUBSTR(l_sql_select_left, 1, 1);
1961           x_piped_expr_disp   := x_piped_expr_disp || SUBSTR(l_sql_select_left, 1, 1);
1962           l_sql_select_left   := SUBSTR(l_sql_select_left, 2);
1963           found_num           := TRUE;
1964           success             := TRUE;
1965         END LOOP;
1966 
1967         IF found_num THEN
1968           x_piped_expr_disp   := x_piped_expr_disp || '|';
1969           x_piped_sql_select  := x_piped_sql_select || '|';
1970         END IF;
1971       END IF;
1972 
1973       -- look for canned value
1974       IF success = FALSE THEN
1975         FOR i IN 1 .. sel_pieces.COUNT LOOP
1976           IF SUBSTR(l_sql_select_left, 1, LENGTH(sel_pieces(i))) = UPPER(sel_pieces(i)) THEN
1977             l_sql_select_left   := SUBSTR(l_sql_select_left, LENGTH(sel_pieces(i)) + 1);
1978             x_piped_sql_select  := x_piped_sql_select || sel_pieces(i) || '|';
1979             x_piped_expr_disp   := x_piped_expr_disp || disp_pieces(i) || '|';
1980             success             := TRUE;
1981             EXIT;
1982           END IF;
1983         END LOOP;
1984       END IF;
1985 
1986       -- look for formula value
1987       IF success = FALSE AND SUBSTR(l_sql_select_left, 1, 10) = 'cn_formula' THEN
1988         -- look for p_commission_line_id
1989         l_ix                := INSTR(l_sql_select_left, 'p_commission_line_id');
1990         l_seg               := SUBSTR(l_sql_select_left, 1, l_ix + 20);
1991         l_sql_select_left   := SUBSTR(l_sql_select_left, l_ix + 21);
1992         x_piped_sql_select  := x_piped_sql_select || l_seg || '|';
1993 
1994         OPEN get_formula_name(l_seg);
1995         FETCH get_formula_name INTO l_seg;
1996         CLOSE get_formula_name;
1997 
1998         x_piped_expr_disp   := x_piped_expr_disp || l_seg || '|';
1999         success             := TRUE;
2000       END IF;
2001 
2002       -- look for user-defined function
2003       IF success = FALSE THEN
2004         FOR f IN get_user_funcs LOOP
2005           IF SUBSTR(l_sql_select_left, 1, LENGTH(f.object_name) + 1) = UPPER(f.object_name) || '(' THEN
2006             -- found a function
2007             x_piped_sql_select  := x_piped_sql_select || f.object_name || '(|';
2008             x_piped_expr_disp   := x_piped_expr_disp || f.object_name || '(|';
2009             l_sql_select_left   := SUBSTR(l_sql_select_left, LENGTH(f.object_name) + 2);
2010             success             := TRUE;
2011           END IF;
2012         END LOOP;
2013       END IF;
2014 
2015       -- trim spaces
2016       IF success = FALSE AND SUBSTR(l_sql_select_left, 1, 1) = ' ' THEN
2017         l_sql_select_left  := SUBSTR(l_sql_select_left, 2);
2018         success            := TRUE;
2019       END IF;
2020 
2021       -- now look for elements like [something].[something else]
2022       IF success = FALSE AND l_sql_select_left IS NOT NULL THEN
2023         -- look for dot and table alias
2024         l_ix                := INSTR(l_sql_select_left, '.');
2025         l_seg               := SUBSTR(l_sql_select_left, 1, l_ix - 1);   -- the alias
2026         l_disp_seg          := NULL;
2027 
2028         OPEN get_tbl(l_seg);
2029         FETCH get_tbl INTO l_disp_seg, l_table_id, l_table_name;
2030         CLOSE get_tbl;
2031 
2032         IF l_disp_seg IS NULL THEN
2033           fnd_message.set_name('CN', 'CN_SQL_SELECT_PARSE_ERR');
2034           fnd_msg_pub.ADD;
2035           RAISE fnd_api.g_exc_error;
2036         END IF;
2037 
2038         -- add to sql from
2039         IF (x_piped_sql_from IS NULL OR INSTR(x_piped_sql_from, l_table_name) = 0) THEN
2040           x_piped_sql_from  := x_piped_sql_from || l_table_name || ' ' || l_seg || '|';   -- don't include the same table twice
2041         END IF;
2042 
2043         x_piped_sql_select  := x_piped_sql_select || l_seg;
2044         x_piped_expr_disp   := x_piped_expr_disp || l_disp_seg;
2045         l_sql_select_left   := SUBSTR(l_sql_select_left, l_ix + 1);
2046         l_ix                := LENGTH(l_sql_select_left) + 1;
2047 
2048         FOR c IN 1 .. opers.COUNT LOOP
2049           IF INSTR(l_sql_select_left, opers(c)) BETWEEN 1 AND l_ix THEN
2050             l_ix  := INSTR(l_sql_select_left, opers(c));
2051           END IF;
2052         END LOOP;
2053 
2054         l_seg               := SUBSTR(l_sql_select_left, 1, l_ix - 1);
2055         l_disp_seg          := NULL;
2056 
2057         OPEN get_col(l_seg, l_table_id);
2058         FETCH get_col INTO l_disp_seg;
2059         CLOSE get_col;
2060 
2061         IF l_disp_seg IS NULL THEN
2062           fnd_message.set_name('CN', 'CN_SQL_SELECT_PARSE_ERR');
2063           fnd_msg_pub.ADD;
2064           RAISE fnd_api.g_exc_error;
2065         END IF;
2066 
2067         x_piped_sql_select  := x_piped_sql_select || '.' || l_seg || '|';
2068         x_piped_expr_disp   := x_piped_expr_disp || '.' || l_disp_seg || '|';
2069         l_sql_select_left   := SUBSTR(l_sql_select_left, l_ix);
2070         success             := TRUE;
2071       END IF;
2072 
2073       IF ct = 400 THEN
2074         fnd_message.set_name('CN', 'CN_SQL_SELECT_PARSE_ERR');
2075         fnd_msg_pub.ADD;
2076         RAISE fnd_api.g_exc_unexpected_error;
2077       END IF;
2078 
2079       IF success = FALSE THEN
2080         EXIT;
2081       END IF;   -- we're done
2082     END LOOP;
2083 
2084     x_expr_disp      := REPLACE(x_piped_expr_disp, '|', '');
2085     p_sql_select     := REPLACE(x_piped_sql_select, '|', '');
2086 
2087     IF x_piped_sql_from IS NULL THEN
2088       x_piped_sql_from  := 'DUAL|';
2089     END IF;
2090 
2091     x_sql_from       := REPLACE(SUBSTR(x_piped_sql_from, 1, LENGTH(x_piped_sql_from) - 1), '|'
2092                        , ', ');   -- trim last comma
2093 
2094     -- Standard check of p_commit.
2095     IF fnd_api.to_boolean(p_commit) THEN
2096       COMMIT WORK;
2097     END IF;
2098 
2099     -- Standard call to get message count and if count is 1, get message info.
2100     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2101     , p_encoded                    => fnd_api.g_false);
2102   EXCEPTION
2103     WHEN fnd_api.g_exc_error THEN
2104       x_return_status  := fnd_api.g_ret_sts_error;
2105       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2106       , p_encoded                    => fnd_api.g_false);
2107     WHEN fnd_api.g_exc_unexpected_error THEN
2108       x_return_status  := fnd_api.g_ret_sts_unexp_error;
2109       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2110       , p_encoded                    => fnd_api.g_false);
2111     WHEN OTHERS THEN
2112       x_return_status  := fnd_api.g_ret_sts_unexp_error;
2113 
2114       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2115         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2116       END IF;
2117 
2118       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2119       , p_encoded                    => fnd_api.g_false);
2120   END parse_sql_select;
2121 
2122   PROCEDURE import(
2123     errbuf          OUT NOCOPY    VARCHAR2
2124   , retcode         OUT NOCOPY    VARCHAR2
2125   , p_imp_header_id IN            NUMBER
2126   , p_org_id        IN            NUMBER
2127   ) IS
2128     l_api_name     CONSTANT VARCHAR2(30)                                  := 'import';
2129     l_status_code           cn_imp_lines.status_code%TYPE                 := 'STAGE';
2130     l_imp_header            cn_imp_headers_pvt.imp_headers_rec_type
2131                                                        := cn_imp_headers_pvt.g_miss_imp_headers_rec;
2132     l_process_audit_id      cn_process_audits.process_audit_id%TYPE;
2133     err_num                 NUMBER;
2134     l_msg_count             NUMBER                                        := 0;
2135     l_exp_id                NUMBER;
2136     l_msg_data              VARCHAR2(4000);
2137     l_processed_row         NUMBER                                        := 0;
2138     l_failed_row            NUMBER                                        := 0;
2139     l_message               VARCHAR2(4000);
2140     l_app_sn                VARCHAR2(30);
2141     l_error_code            VARCHAR2(4000);
2142     l_header_list           VARCHAR2(4000);
2143     l_sql_stmt              VARCHAR2(4000);
2144     l_return_status         VARCHAR2(1);
2145     l_type_code             cn_calc_sql_exps.exp_type_code%TYPE;
2146     my_message              VARCHAR2(4000);
2147     l_status                VARCHAR2(30);
2148     l_sql_from              VARCHAR2(4000);
2149     l_piped_sql_from        VARCHAR2(4000);
2150     l_piped_sql_select      VARCHAR2(4000);
2151     l_piped_expr_disp       VARCHAR2(4000);
2152     l_expr_disp             VARCHAR2(4000);
2153     l_object_version_number cn_calc_sql_exps.object_version_number%TYPE;
2154 
2155     CURSOR get_api_recs IS
2156       SELECT *
2157         FROM cn_exp_api_imp_v
2158        WHERE imp_header_id = p_imp_header_id AND status_code = l_status_code;
2159 
2160     l_api_rec               get_api_recs%ROWTYPE;
2161   BEGIN
2162     retcode                  := 0;
2163     l_object_version_number  := 0;
2164 
2165     -- Get imp_header info
2166     SELECT NAME
2167          , status_code
2168          , server_flag
2169          , imp_map_id
2170          , source_column_num
2171          , import_type_code
2172       INTO l_imp_header.NAME
2173          , l_imp_header.status_code
2174          , l_imp_header.server_flag
2175          , l_imp_header.imp_map_id
2176          , l_imp_header.source_column_num
2177          , l_imp_header.import_type_code
2178       FROM cn_imp_headers
2179      WHERE imp_header_id = p_imp_header_id;
2180 
2181     -- open process audit batch
2182     cn_message_pkg.begin_batch(
2183       x_process_type               => l_imp_header.import_type_code
2184     , x_parent_proc_audit_id       => p_imp_header_id
2185     , x_process_audit_id           => l_process_audit_id
2186     , x_request_id                 => NULL
2187     , p_org_id                     => p_org_id
2188     );
2189     cn_message_pkg.WRITE(
2190       p_message_text =>    'CALCEXPIMP: Start Transfer Data. imp_header_id = ' || TO_CHAR(p_imp_header_id)
2191     , p_message_type => 'MILESTONE'
2192     );
2193 
2194     -- Get source column name list and target column dynamic sql statement
2195     cn_import_pvt.build_error_rec(p_imp_header_id => p_imp_header_id
2196     , x_header_list                => l_header_list, x_sql_stmt => l_sql_stmt);
2197 
2198     OPEN get_api_recs;
2199 
2200     LOOP
2201       FETCH get_api_recs INTO l_api_rec;
2202 
2203       EXIT WHEN get_api_recs%NOTFOUND;
2204 
2205       BEGIN
2206         l_processed_row  := l_processed_row + 1;
2207         l_error_code     := NULL;   -- reset error code
2208         cn_message_pkg.WRITE(
2209           p_message_text               =>    'CALCEXPIMP:Record '
2210                                           || TO_CHAR(l_processed_row)
2211                                           || ' imp_line_id = '
2212                                           || TO_CHAR(l_api_rec.imp_line_id)
2213         , p_message_type               => 'DEBUG'
2214         );
2215 
2216         -- -------- Checking for all required fields ----------------- --
2217         -- Check required field
2218         IF l_api_rec.expression_name IS NULL OR l_api_rec.sql_select IS NULL THEN
2219           l_failed_row  := l_failed_row + 1;
2220           l_error_code  := 'CN_IMP_MISS_REQUIRED';
2221           l_message     := fnd_message.get_string('CN', 'CN_IMP_MISS_REQUIRED');
2222           cn_import_pvt.update_imp_lines(
2223             p_imp_line_id                => l_api_rec.imp_line_id
2224           , p_status_code                => 'FAIL'
2225           , p_error_code                 => l_error_code
2226           );
2227           cn_import_pvt.update_imp_headers(
2228             p_imp_header_id              => p_imp_header_id
2229           , p_status_code                => 'IMPORT_FAIL'
2230           , p_failed_row                 => l_failed_row
2231           );
2232           cn_message_pkg.WRITE(
2233             p_message_text               => 'Record ' || TO_CHAR(l_processed_row) || ':'
2234                                             || l_message
2235           , p_message_type               => 'ERROR'
2236           );
2237           cn_import_pvt.write_error_rec(
2238             p_imp_header_id              => p_imp_header_id
2239           , p_imp_line_id                => l_api_rec.imp_line_id
2240           , p_header_list                => l_header_list
2241           , p_sql_stmt                   => l_sql_stmt
2242           );
2243           retcode       := 2;
2244           errbuf        := l_message;
2245           GOTO end_loop;
2246         END IF;
2247 
2248         -- build components of record
2249         parse_sql_select(
2250           p_api_version                => 1.0
2251         , p_init_msg_list              => fnd_api.g_true
2252         , p_sql_select                 => l_api_rec.sql_select
2253         , x_piped_sql_select           => l_piped_sql_select
2254         , x_expr_disp                  => l_expr_disp
2255         , x_piped_expr_disp            => l_piped_expr_disp
2256         , x_sql_from                   => l_sql_from
2257         , x_piped_sql_from             => l_piped_sql_from
2258         , x_return_status              => l_return_status
2259         , x_msg_count                  => l_msg_count
2260         , x_msg_data                   => l_msg_data
2261         );
2262 
2263         IF l_return_status = fnd_api.g_ret_sts_success THEN
2264           -- do import here
2265           l_exp_id  := NULL;
2266           create_expression(
2267             p_api_version                => 1.0
2268           , p_init_msg_list              => fnd_api.g_false
2269           , p_org_id                     => p_org_id
2270           , p_name                       => l_api_rec.expression_name
2271           , p_description                => l_api_rec.description
2272           , p_expression_disp            => l_expr_disp
2273           , p_sql_select                 => l_api_rec.sql_select
2274           , p_sql_from                   => l_sql_from
2275           , p_piped_expression_disp      => l_piped_expr_disp
2276           , p_piped_sql_select           => l_piped_sql_select
2277           , p_piped_sql_from             => l_piped_sql_from
2278           , x_calc_sql_exp_id            => l_exp_id
2279           , x_exp_type_code              => l_type_code
2280           , x_status                     => l_status
2281           , x_return_status              => l_return_status
2282           , x_msg_count                  => l_msg_count
2283           , x_msg_data                   => l_msg_data
2284           , x_object_version_number      => l_object_version_number
2285           );
2286 
2287           IF l_return_status = fnd_api.g_ret_sts_success THEN
2288             -- update attribute values appropriately since API doesn't
2289             -- handle flexfields
2290             UPDATE cn_calc_sql_exps
2291                SET attribute_category = l_api_rec.attribute_category
2292                  , attribute1 = l_api_rec.attribute1
2293                  , attribute2 = l_api_rec.attribute2
2294                  , attribute3 = l_api_rec.attribute3
2295                  , attribute4 = l_api_rec.attribute4
2296                  , attribute5 = l_api_rec.attribute5
2297                  , attribute6 = l_api_rec.attribute6
2298                  , attribute7 = l_api_rec.attribute7
2299                  , attribute8 = l_api_rec.attribute8
2300                  , attribute9 = l_api_rec.attribute9
2301                  , attribute10 = l_api_rec.attribute10
2302                  , attribute11 = l_api_rec.attribute11
2303                  , attribute12 = l_api_rec.attribute12
2304                  , attribute13 = l_api_rec.attribute13
2305                  , attribute14 = l_api_rec.attribute14
2306                  , attribute15 = l_api_rec.attribute15
2307              WHERE calc_sql_exp_id = l_exp_id;
2308           END IF;
2309         END IF;
2310 
2311         IF l_return_status <> fnd_api.g_ret_sts_success THEN
2312           -- try to get correct message
2313           l_failed_row  := l_failed_row + 1;
2314           my_message    :=
2315                   fnd_msg_pub.get(p_msg_index    => fnd_msg_pub.g_first
2316                   , p_encoded                    => fnd_api.g_false);
2317 
2318           WHILE(my_message IS NOT NULL) LOOP
2319             l_error_code  := my_message;
2320             my_message    := fnd_msg_pub.get(p_encoded => fnd_api.g_false);
2321           END LOOP;
2322 
2323           cn_import_pvt.update_imp_lines(
2324             p_imp_line_id                => l_api_rec.imp_line_id
2325           , p_status_code                => 'FAIL'
2326           , p_error_code                 => NULL
2327           , p_error_msg                  => NVL(l_error_code, 'Unexpected Error')
2328           );
2329           cn_import_pvt.update_imp_headers(
2330             p_imp_header_id              => p_imp_header_id
2331           , p_status_code                => 'IMPORT_FAIL'
2332           , p_failed_row                 => l_failed_row
2333           );
2334           cn_message_pkg.WRITE(
2335             p_message_text               => 'Record ' || TO_CHAR(l_processed_row) || ':'
2336                                             || l_message
2337           , p_message_type               => 'ERROR'
2338           );
2339           cn_import_pvt.write_error_rec(
2340             p_imp_header_id              => p_imp_header_id
2341           , p_imp_line_id                => l_api_rec.imp_line_id
2342           , p_header_list                => l_header_list
2343           , p_sql_stmt                   => l_sql_stmt
2344           );
2345           retcode       := 2;
2346           errbuf        := l_message;
2347           GOTO end_loop;
2348         ELSE
2349           l_error_code  := '';
2350           cn_import_pvt.update_imp_lines(
2351             p_imp_line_id                => l_api_rec.imp_line_id
2352           , p_status_code                => 'COMPLETE'
2353           , p_error_code                 => l_error_code
2354           );
2355           cn_message_pkg.WRITE(
2356             p_message_text               =>    'CALCEXPIMP:Import completed. exp id = '
2357                                             || TO_CHAR(l_exp_id)
2358           , p_message_type               => 'DEBUG'
2359           );
2360         END IF;
2361 
2362         <<end_loop>>
2363         -- update update_imp_headers:process_row
2364         cn_import_pvt.update_imp_headers(
2365           p_imp_header_id              => p_imp_header_id
2366         , p_status_code                => NULL
2367         , p_processed_row              => l_processed_row
2368         );
2369       EXCEPTION
2370         WHEN OTHERS THEN
2371           l_failed_row  := l_failed_row + 1;
2372           l_error_code  := SQLCODE;
2373           l_message     := SUBSTR(SQLERRM, 1, 2000);
2374           cn_import_pvt.update_imp_lines(
2375             p_imp_line_id                => l_api_rec.imp_line_id
2376           , p_status_code                => 'FAIL'
2377           , p_error_code                 => NULL
2378           , p_error_msg                  => l_message
2379           );
2380           cn_import_pvt.update_imp_headers(
2381             p_imp_header_id              => p_imp_header_id
2382           , p_status_code                => 'IMPORT_FAIL'
2383           , p_processed_row              => l_processed_row
2384           , p_failed_row                 => l_failed_row
2385           );
2386           cn_message_pkg.WRITE(
2387             p_message_text               => 'Record ' || TO_CHAR(l_processed_row) || ':'
2388                                             || l_message
2389           , p_message_type               => 'ERROR'
2390           );
2391           cn_import_pvt.write_error_rec(
2392             p_imp_header_id              => p_imp_header_id
2393           , p_imp_line_id                => l_api_rec.imp_line_id
2394           , p_header_list                => l_header_list
2395           , p_sql_stmt                   => l_sql_stmt
2396           );
2397           retcode       := 2;
2398           errbuf        := l_message;
2399       END;
2400     END LOOP;   -- get_api_recs
2401 
2402     IF get_api_recs%ROWCOUNT = 0 THEN
2403       l_processed_row  := 0;
2404     END IF;
2405 
2406     CLOSE get_api_recs;
2407 
2408     IF l_failed_row = 0 AND retcode = 0 THEN
2409       -- update update_imp_headers
2410       cn_import_pvt.update_imp_headers(
2411         p_imp_header_id              => p_imp_header_id
2412       , p_status_code                => 'COMPLETE'
2413       , p_processed_row              => l_processed_row
2414       , p_failed_row                 => l_failed_row
2415       );
2416     END IF;
2417 
2418     cn_message_pkg.WRITE(
2419       p_message_text               =>    'CALCEXPIMP: End Transfer Data. imp_header_id = '
2420                                       || TO_CHAR(p_imp_header_id)
2421     , p_message_type               => 'MILESTONE'
2422     );
2423     -- close process batch
2424     cn_message_pkg.end_batch(l_process_audit_id);
2425     -- Commit all imports
2426     COMMIT;
2427   EXCEPTION
2428     WHEN fnd_api.g_exc_unexpected_error THEN
2429       retcode  := 2;
2430       cn_message_pkg.end_batch(l_process_audit_id);
2431       fnd_msg_pub.count_and_get(p_count => l_msg_count, p_data => errbuf
2432       , p_encoded                    => fnd_api.g_false);
2433     WHEN OTHERS THEN
2434       err_num  := SQLCODE;
2435 
2436       IF err_num = -6501 THEN
2437         retcode  := 2;
2438         errbuf   := fnd_program.MESSAGE;
2439       ELSE
2440         retcode  := 2;
2441 
2442         IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2443           fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2444         END IF;
2445 
2446         fnd_msg_pub.count_and_get(p_count => l_msg_count, p_data => errbuf
2447         , p_encoded                    => fnd_api.g_false);
2448       END IF;
2449 
2450       cn_message_pkg.set_error(l_api_name, errbuf);
2451       cn_message_pkg.end_batch(l_process_audit_id);
2452   END import;
2453 
2454   -- export
2455   PROCEDURE export(
2456     errbuf          OUT NOCOPY    VARCHAR2
2457   , retcode         OUT NOCOPY    VARCHAR2
2458   , p_imp_header_id IN            NUMBER
2459   , p_org_id        IN            NUMBER
2460   ) IS
2461     l_api_name CONSTANT VARCHAR2(30)                              := 'Export';
2462     l_process_audit_id  cn_process_audits.process_audit_id%TYPE;
2463     l_return_status     VARCHAR2(1);
2464     l_msg_data          VARCHAR2(4000);
2465     l_msg_count         NUMBER;
2466     l_col_names         cn_import_pvt.char_data_set_type;
2467     l_data              cn_import_pvt.char_data_set_type;
2468     l_rowcount          NUMBER                                    := 0;
2469     l_longcount         NUMBER                                    := 0;
2470     l_rec_num           NUMBER                                    := 0;
2471     l_message           VARCHAR2(4000);
2472     l_name              VARCHAR2(30);
2473     l_type              VARCHAR2(30);
2474     l_view_name         VARCHAR2(30);
2475     my_message          VARCHAR2(4000);
2476     err_num             NUMBER;
2477     g_max_field_length  NUMBER                                    := 150;
2478 
2479     -- this is a workaround since you cannot declare arrays of a
2480     -- type declared remotely
2481     TYPE vt IS TABLE OF VARCHAR2(30);
2482 
2483     l_col_names_tmp     vt
2484       := vt(
2485           'RECORD_NUM'
2486         , 'EXPRESSION_NAME'
2487         , 'DESCRIPTION'
2488         , 'SQL_SELECT'
2489         , 'ATTRIBUTE_CATEGORY'
2490         , 'ATTRIBUTE1'
2491         , 'ATTRIBUTE2'
2492         , 'ATTRIBUTE3'
2493         , 'ATTRIBUTE4'
2494         , 'ATTRIBUTE5'
2495         , 'ATTRIBUTE6'
2496         , 'ATTRIBUTE7'
2497         , 'ATTRIBUTE8'
2498         , 'ATTRIBUTE9'
2499         , 'ATTRIBUTE10'
2500         , 'ATTRIBUTE11'
2501         , 'ATTRIBUTE12'
2502         , 'ATTRIBUTE13'
2503         , 'ATTRIBUTE14'
2504         , 'ATTRIBUTE15'
2505         );
2506 
2507     CURSOR get_expressions IS
2508       SELECT   NAME expression_name
2509              , description
2510              , DBMS_LOB.SUBSTR(sql_select, g_max_field_length) sql_select
2511              , attribute_category
2512              , attribute1
2513              , attribute2
2514              , attribute3
2515              , attribute4
2516              , attribute5
2517              , attribute6
2518              , attribute7
2519              , attribute8
2520              , attribute9
2521              , attribute10
2522              , attribute11
2523              , attribute12
2524              , attribute13
2525              , attribute14
2526              , attribute15
2527           FROM cn_calc_sql_exps
2528          WHERE org_id = p_org_id
2529       ORDER BY 1;
2530 
2531     CURSOR get_rowcount IS
2532       SELECT COUNT(1)
2533         FROM cn_calc_sql_exps
2534        WHERE org_id = p_org_id;
2535 
2536     CURSOR get_long_rowcount IS
2537       SELECT COUNT(1)
2538         FROM cn_calc_sql_exps
2539        WHERE DBMS_LOB.getlength(sql_select) > g_max_field_length AND org_id = p_org_id;
2540   BEGIN
2541     retcode  := 0;
2542 
2543     -- Get imp_header info
2544     SELECT h.NAME
2545          , h.import_type_code
2546          , t.view_name
2547       INTO l_name
2548          , l_type
2549          , l_view_name
2550       FROM cn_imp_headers h, cn_import_types t
2551      WHERE h.imp_header_id = p_imp_header_id AND t.import_type_code = h.import_type_code;
2552 
2553     -- open process audit batch
2554     cn_message_pkg.begin_batch(
2555       x_process_type               => l_type
2556     , x_parent_proc_audit_id       => p_imp_header_id
2557     , x_process_audit_id           => l_process_audit_id
2558     , x_request_id                 => NULL
2559     , p_org_id                     => p_org_id
2560     );
2561     cn_message_pkg.WRITE
2562                        (
2563       p_message_text               =>    'CN_EXPCALCEXP: Start Transfer Data. imp_header_id = '
2564                                       || TO_CHAR(p_imp_header_id)
2565     , p_message_type               => 'MILESTONE'
2566     );
2567 
2568     -- API call here
2569     -- get column names
2570     FOR i IN 1 .. l_col_names_tmp.COUNT LOOP
2571       l_col_names(i)  := l_col_names_tmp(i);
2572     END LOOP;
2573 
2574     -- we have to get the rowcount first - since the data must be applied
2575     -- sequentially by column... indexes are like
2576     -- 1 n+1 ... 19n+1  (there are 20 columns)
2577     -- 2 n+2 ... 19n+2
2578     -- n 2n  ... 20n
2579     OPEN get_rowcount;
2580     FETCH get_rowcount INTO l_rowcount;
2581     CLOSE get_rowcount;
2582 
2583     OPEN get_long_rowcount;
2584     FETCH get_long_rowcount INTO l_longcount;
2585     CLOSE get_long_rowcount;
2586 
2587     -- now populate the data
2588     FOR EXP IN get_expressions LOOP
2589       l_rec_num                            := l_rec_num + 1;
2590       l_data(l_rowcount * 0 + l_rec_num)   := l_rec_num;
2591       l_data(l_rowcount * 1 + l_rec_num)   := EXP.expression_name;
2592       l_data(l_rowcount * 2 + l_rec_num)   := EXP.description;
2593       l_data(l_rowcount * 3 + l_rec_num)   := EXP.sql_select;
2594       l_data(l_rowcount * 4 + l_rec_num)   := EXP.attribute_category;
2595       l_data(l_rowcount * 5 + l_rec_num)   := EXP.attribute1;
2596       l_data(l_rowcount * 6 + l_rec_num)   := EXP.attribute2;
2597       l_data(l_rowcount * 7 + l_rec_num)   := EXP.attribute3;
2598       l_data(l_rowcount * 8 + l_rec_num)   := EXP.attribute4;
2599       l_data(l_rowcount * 9 + l_rec_num)   := EXP.attribute5;
2600       l_data(l_rowcount * 10 + l_rec_num)  := EXP.attribute6;
2601       l_data(l_rowcount * 11 + l_rec_num)  := EXP.attribute7;
2602       l_data(l_rowcount * 12 + l_rec_num)  := EXP.attribute8;
2603       l_data(l_rowcount * 13 + l_rec_num)  := EXP.attribute9;
2604       l_data(l_rowcount * 14 + l_rec_num)  := EXP.attribute10;
2605       l_data(l_rowcount * 15 + l_rec_num)  := EXP.attribute11;
2606       l_data(l_rowcount * 16 + l_rec_num)  := EXP.attribute12;
2607       l_data(l_rowcount * 17 + l_rec_num)  := EXP.attribute13;
2608       l_data(l_rowcount * 18 + l_rec_num)  := EXP.attribute14;
2609       l_data(l_rowcount * 19 + l_rec_num)  := EXP.attribute15;
2610     END LOOP;
2611 
2612     cn_import_client_pvt.insert_data(
2613       p_api_version                => 1.0
2614     , p_imp_header_id              => p_imp_header_id
2615     , p_import_type_code           => l_type
2616     , p_table_name                 => l_view_name
2617     , p_col_names                  => l_col_names
2618     , p_data                       => l_data
2619     , p_row_count                  => l_rowcount
2620     , x_return_status              => l_return_status
2621     , x_msg_count                  => l_msg_count
2622     , x_msg_data                   => l_msg_data
2623     );
2624 
2625     IF l_return_status <> fnd_api.g_ret_sts_success THEN
2626       cn_import_pvt.update_imp_headers(p_imp_header_id => p_imp_header_id, p_status_code => 'FAIL'
2627       , p_failed_row                 => l_rowcount);
2628       cn_message_pkg.WRITE(
2629         p_message_text               => 'Export threw exception : rts sts ' || l_return_status
2630       , p_message_type               => 'ERROR'
2631       );
2632       my_message  := fnd_msg_pub.get(p_encoded => fnd_api.g_false);
2633 
2634       WHILE(my_message IS NOT NULL) LOOP
2635         l_message   := l_message || my_message || '; ';
2636         my_message  := fnd_msg_pub.get(p_encoded => fnd_api.g_false);
2637       END LOOP;
2638 
2639       cn_message_pkg.WRITE(p_message_text => l_message, p_message_type => 'ERROR');
2640       retcode     := 2;
2641       errbuf      := l_message;
2642     ELSE
2643       -- normal completion
2644       cn_import_pvt.update_imp_headers(
2645         p_imp_header_id              => p_imp_header_id
2646       , p_status_code                => 'COMPLETE'
2647       , p_processed_row              => l_rowcount
2648       , p_staged_row                 => l_rowcount - l_longcount
2649       , p_failed_row                 => l_longcount
2650       );
2651 
2652       -- set cn_imp_lines records status = 'COMPLETE'
2653       UPDATE cn_exp_api_imp_v
2654          SET status_code = 'COMPLETE'
2655        WHERE imp_header_id = p_imp_header_id;
2656 
2657       -- set failed records - where expression was too long
2658       fnd_message.set_name('CN', 'CN_EXPORT_FIELD_TOO_LONG');
2659       fnd_message.set_token('LENGTH', g_max_field_length);
2660       my_message  := fnd_message.get;
2661 
2662       UPDATE cn_exp_api_imp_v
2663          SET status_code = 'FAIL'
2664            , error_msg = my_message
2665        WHERE imp_header_id = p_imp_header_id
2666          AND expression_name IN(SELECT NAME
2667                                   FROM cn_calc_sql_exps
2668                                  WHERE DBMS_LOB.getlength(sql_select) > g_max_field_length);
2669 
2670       cn_message_pkg.WRITE
2671                          (
2672         p_message_text               =>    'CN_EXPCALCEXP: End Transfer Data. imp_header_id = '
2673                                         || TO_CHAR(p_imp_header_id)
2674       , p_message_type               => 'MILESTONE'
2675       );
2676     END IF;
2677 
2678     -- close process batch
2679     cn_message_pkg.end_batch(l_process_audit_id);
2680     -- Commit all imports
2681     COMMIT;
2682   EXCEPTION
2683     WHEN fnd_api.g_exc_unexpected_error THEN
2684       retcode  := 2;
2685       cn_message_pkg.end_batch(l_process_audit_id);
2686       fnd_msg_pub.count_and_get(p_count => l_msg_count, p_data => errbuf
2687       , p_encoded                    => fnd_api.g_false);
2688     WHEN OTHERS THEN
2689       err_num  := SQLCODE;
2690 
2691       IF err_num = -6501 THEN
2692         retcode  := 2;
2693         errbuf   := fnd_program.MESSAGE;
2694       ELSE
2695         retcode  := 2;
2696 
2697         IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2698           fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2699         END IF;
2700 
2701         fnd_msg_pub.count_and_get(p_count => l_msg_count, p_data => errbuf
2702         , p_encoded                    => fnd_api.g_false);
2703       END IF;
2704 
2705       cn_message_pkg.set_error(l_api_name, errbuf);
2706       cn_message_pkg.end_batch(l_process_audit_id);
2707   END export;
2708 
2709   PROCEDURE duplicate_expression(
2710     p_api_version      IN            NUMBER
2711   , p_init_msg_list    IN            VARCHAR2 := fnd_api.g_false
2712   , p_commit           IN            VARCHAR2 := fnd_api.g_false
2713   , p_validation_level IN            NUMBER := fnd_api.g_valid_level_full
2714   , p_old_expr_id      IN            NUMBER
2715   , x_new_expr_id      OUT NOCOPY    NUMBER
2716   , x_new_expr_name    OUT NOCOPY    cn_calc_sql_exps.NAME%TYPE
2717   , x_return_status    OUT NOCOPY    VARCHAR2
2718   , x_msg_count        OUT NOCOPY    NUMBER
2719   , x_msg_data         OUT NOCOPY    VARCHAR2
2720   ) IS
2721     l_api_name     CONSTANT VARCHAR2(30)                                  := 'Duplicate_Expression';
2722     l_api_version  CONSTANT NUMBER                                        := 1.0;
2723     l_org_id                cn_calc_sql_exps.org_id%TYPE;
2724     l_description           cn_calc_sql_exps.description%TYPE;
2725     l_expression_disp       VARCHAR2(32767);
2726     l_sql_select            VARCHAR2(32767);
2727     l_sql_from              VARCHAR2(32767);
2728     l_piped_expression_disp VARCHAR2(32767);
2729     l_piped_sql_select      VARCHAR2(32767);
2730     l_piped_sql_from        VARCHAR2(32767);
2731     x_exp_type_code         cn_calc_sql_exps.exp_type_code%TYPE;
2732     x_status                cn_calc_sql_exps.status%TYPE;
2733     x_object_version_number cn_calc_sql_exps.object_version_number%TYPE;
2734     l_suffix                VARCHAR2(10)                                  := NULL;
2735     l_prefix                VARCHAR2(10)                                  := NULL;
2736   BEGIN
2737     -- Standard Start of API savepoint
2738     SAVEPOINT create_expression;
2739 
2740     -- Standard call to check for call compatibility.
2741     IF NOT fnd_api.compatible_api_call(l_api_version, p_api_version, l_api_name, g_pkg_name) THEN
2742       RAISE fnd_api.g_exc_unexpected_error;
2743     END IF;
2744 
2745     -- Initialize message list if p_init_msg_list is set to TRUE.
2746     IF fnd_api.to_boolean(p_init_msg_list) THEN
2747       fnd_msg_pub.initialize;
2748     END IF;
2749 
2750     --  Initialize API return status to success
2751     x_return_status  := fnd_api.g_ret_sts_success;
2752 
2753     SELECT org_id
2754          , NAME
2755          , description
2756          , expression_disp
2757          , sql_select
2758          , sql_from
2759          , piped_expression_disp
2760          , piped_sql_select
2761          , piped_sql_from
2762       INTO l_org_id
2763          , x_new_expr_name
2764          , l_description
2765          , l_expression_disp
2766          , l_sql_select
2767          , l_sql_from
2768          , l_piped_expression_disp
2769          , l_piped_sql_select
2770          , l_piped_sql_from
2771       FROM cn_calc_sql_exps
2772      WHERE calc_sql_exp_id = p_old_expr_id;
2773 
2774     -- x_new_expr_name := x_new_expr_name || '_2';
2775     cn_plancopy_util_pvt.get_unique_name_for_component(
2776       p_id                         => p_old_expr_id
2777     , p_org_id                     => l_org_id
2778     , p_type                       => 'EXPRESSION'
2779     , p_suffix                     => l_suffix
2780     , p_prefix                     => l_prefix
2781     , x_name                       => x_new_expr_name
2782     , x_return_status              => x_return_status
2783     , x_msg_count                  => x_msg_count
2784     , x_msg_data                   => x_msg_data
2785     );
2786 
2787     IF (x_return_status <> fnd_api.g_ret_sts_success) THEN
2788       RAISE fnd_api.g_exc_error;
2789     END IF;
2790 
2791     create_expression(
2792       p_api_version                => p_api_version
2793     , p_init_msg_list              => p_init_msg_list
2794     , p_commit                     => p_commit
2795     , p_validation_level           => p_validation_level
2796     , p_org_id                     => l_org_id
2797     , p_name                       => x_new_expr_name
2798     , p_description                => l_description
2799     , p_expression_disp            => l_expression_disp
2800     , p_sql_select                 => l_sql_select
2801     , p_sql_from                   => l_sql_from
2802     , p_piped_expression_disp      => l_piped_expression_disp
2803     , p_piped_sql_select           => l_piped_sql_select
2804     , p_piped_sql_from             => l_piped_sql_from
2805     , x_calc_sql_exp_id            => x_new_expr_id
2806     , x_exp_type_code              => x_exp_type_code
2807     , x_status                     => x_status
2808     , x_return_status              => x_return_status
2809     , x_msg_count                  => x_msg_count
2810     , x_msg_data                   => x_msg_data
2811     , x_object_version_number      => x_object_version_number
2812     );
2813 
2814     -- Standard check of p_commit.
2815     IF fnd_api.to_boolean(p_commit) THEN
2816       COMMIT WORK;
2817     END IF;
2818 
2819     -- Standard call to get message count and if count is 1, get message info.
2820     fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2821     , p_encoded                    => fnd_api.g_false);
2822   EXCEPTION
2823     WHEN fnd_api.g_exc_error THEN
2824       ROLLBACK TO duplicate_expression;
2825       x_return_status  := fnd_api.g_ret_sts_error;
2826       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2827       , p_encoded                    => fnd_api.g_false);
2828     WHEN fnd_api.g_exc_unexpected_error THEN
2829       ROLLBACK TO duplicate_expression;
2830       x_return_status  := fnd_api.g_ret_sts_unexp_error;
2831       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2832       , p_encoded                    => fnd_api.g_false);
2833     WHEN OTHERS THEN
2834       ROLLBACK TO duplicate_expression;
2835       x_return_status  := fnd_api.g_ret_sts_unexp_error;
2836 
2837       IF fnd_msg_pub.check_msg_level(fnd_msg_pub.g_msg_lvl_unexp_error) THEN
2838         fnd_msg_pub.add_exc_msg(g_pkg_name, l_api_name);
2839       END IF;
2840 
2841       fnd_msg_pub.count_and_get(p_count => x_msg_count, p_data => x_msg_data
2842       , p_encoded                    => fnd_api.g_false);
2843   END duplicate_expression;
2844 END cn_calc_sql_exps_pvt;