DBA Data[Home] [Help]

PACKAGE BODY: APPS.XLA_CMP_CONDITION_PKG

Source


1 PACKAGE BODY XLA_CMP_CONDITION_PKG AS
2 /* $Header: xlacpcod.pkb 120.28.12010000.2 2010/01/31 14:49:52 vkasina ship $   */
3 /*===========================================================================+
4 |             Copyright (c) 2001-2002 Oracle Corporation                     |
5 |                       Redwood Shores, CA, USA                              |
6 |                         All rights reserved.                               |
7 +============================================================================+
8 | PACKAGE NAME                                                               |
9 |     xla_cmp_condition_pkg                                                  |
10 |                                                                            |
11 | DESCRIPTION                                                                |
12 |     This is a XLA private package, which contains all the logic required   |
13 |     to generate conditions expressions from AMB specifcations              |
14 |                                                                            |
15 |                                                                            |
16 | HISTORY                                                                    |
17 |     15-JUN-2002 K.Boussema  Created                                        |
18 |     18-FEB-2003 K.Boussema  Added 'dbdrv' command                          |
19 |     21-FEB-2003 K.Boussela  Changed GetCondition function                  |
20 |     13-MAR-2003 K.Boussema    Made changes for the new bulk approach of the|
21 |                               accounting engine                            |
22 |     19-MAR-2003 K.Boussema    Added amb_context_code column                |
23 |     22-APR-2003 K.Boussema    Included Error messages                      |
24 |     02-JUN-2003 K.Boussema    Modified to fix bug 2975670 and bug 2729143  |
25 |     17-JUL-2003 K.Boussema    Reviewd the code                             |
26 |     24-JUL-2003 K.Boussema    Updated the error messages                   |
27 |     30-JUL-2003 K.Boussema    Updated the definition of C_FLEXFIELD_SEGMENT|
28 |     27-SEP-2003 K.Boussema    Reviewed the generation of conditions        |
29 |     18-DEC-2003 K.Boussema    Changed to fix bug 3042840,3307761,3268940   |
30 |                               3310291 and 3320689                          |
31 |     23-FEB-2004 K.Boussema    Made changes for the FND_LOG.                |
32 |     22-MAR-2004 K.Boussema    Added a parameter p_module to the TRACE calls|
33 |                               and the procedure.                           |
34 |     28-APR-2004 K.Boussema  Bug 3596711:                                   |
35 |                                Changed the compiler to allow a row in cond.|
36 |                                with just one bracket, reviewed             |
37 |                                GetOneCondition() function                  |
38 |     11-MAY-2004 K.Boussema  Removed the call to XLA trace routine from     |
39 |                             trace() procedure                              |
40 |     01-JUN-2004 A.Quaglia   Added changes for Transaction Account Builder  |
41 |                             added C_TAD_FLEXFIELD_SEGMENT                  |
42 |                             modified GetOneRowCondition                    |
43 |     02-JUN-2004 A.Quaglia   Changed TAD_ADR with TAB_ADR                   |
44 |     07-Mar-2005 K.Boussema  Changed for ADR-enhancements.                  |
45 |     11-Oct-2005 Jorge Larre Fix for bug 4567102: the compiler must         |
46 |                 consider that when using a segment of a source of type     |
47 |                 flexfield in a condition, if the right operand is a        |
48 |                 constant, the right operand must be treated as a char and  |
49 |                 not as a number.                                           |
50 +===========================================================================*/
51 --
52 
53 g_chr_newline      CONSTANT VARCHAR2(10):= xla_environment_pkg.g_chr_newline;
54 g_chr_dummy        CONSTANT VARCHAR2(10):= '@#$';
55 --
56 -- Get flexfield segment
57 --
58 --
59 
60 C_FLEXFIELD_SEGMENT                     CONSTANT       VARCHAR2(10000):='
61 --
62 xla_ae_code_combination_pkg.get_flex_segment_value(
63    p_combination_id          =>  $ccid$
64  , p_segment_code            => ''$segment_code$''
65  , p_id_flex_code            => ''$id_flex_code$''
66  , p_flex_application_id     => $flexfield_appl_id$
67  , p_application_short_name  => ''$appl_short_name$''
68  , p_source_code             => ''$source_code$''
69  , p_source_type_code        => ''$source_type_code$''
70  , p_source_application_id   => $source_application_id$
71  , p_component_type          => ''$component_type$''
72  , p_component_code          => ''$component_code$''
73  , p_component_type_code     => ''$component_type_code$''
74  , p_component_appl_id       => $component_appl_id$
75  , p_amb_context_code        => ''$amb_context_code$''
76  , p_entity_code             => NULL
77  , p_event_class_code        => NULL
78  , p_ae_header_id            => NULL
79 )'
80 ;
81 
82 C_FLEXFIELD_SEGMENT_2                    CONSTANT       VARCHAR2(10000):='
83 --
84 xla_ae_code_combination_pkg.get_flex_segment_value(
85    p_combination_id          =>  $ccid$
86   ,p_segment_code            => ''$segment_code$''
87   ,p_id_flex_code            => ''$id_flex_code$''
88   ,p_flex_application_id     => $flexfield_appl_id$
89   ,p_application_short_name => ''$appl_short_name$''
90   ,p_source_code             => ''$source_code$''
91   ,p_source_type_code        => ''$source_type_code$''
92   ,p_source_application_id   => $source_application_id$
93   ,p_component_type          => ''$component_type$''
94   ,p_component_code          => ''$component_code$''
95   ,p_component_type_code     => ''$component_type_code$''
96   ,p_component_appl_id       => $component_appl_id$
97   ,p_amb_context_code        => ''$amb_context_code$''
98   ,p_entity_code             => ''$entity_code$''
99   ,p_event_class_code        => ''$event_class_code$''
100   ,p_ae_header_id            => NULL
101 )'
102 ;
103 
104 
105 C_TAD_FLEXFIELD_SEGMENT                     CONSTANT       VARCHAR2(10000):='
106 --
107 get_flexfield_segment(
108    p_mode                            => p_mode
109   ,p_rowid                           => p_rowid
110   ,p_line_index                      => p_line_index
111   ,p_chart_of_accounts_id            => p_chart_of_accounts_id
112   ,p_chart_of_accounts_name          => p_chart_of_accounts_name
113   ,p_ccid                            =>  $ccid$
114   ,p_source_code                     => ''$source_code$''
115   ,p_source_type_code                => ''$source_type_code$''
116   ,p_source_application_id           => $source_application_id$
117   ,p_segment_name                    => ''$segment_code$''
118   ,p_gl_balancing_segment_name       => p_gl_balancing_segment_name
119   ,p_gl_account_segment_name         => p_gl_account_segment_name
120   ,p_gl_intercompany_segment_name    => p_gl_intercompany_segment_name
121   ,p_gl_management_segment_name      => p_gl_management_segment_name
122   ,p_fa_cost_ctr_segment_name        => p_fa_cost_ctr_segment_name
123   ,p_adr_name                        => ''$ADR_NAME$''
124 
125 )'
126 ;
127 --
128 --+==========================================================================+
129 --|                                                                          |
130 --|   Global Variable                                                        |
131 --|                                                                          |
132 --+==========================================================================+
133 --
134 g_component_type                VARCHAR2(30);
135 g_component_code                VARCHAR2(30);
136 g_component_type_code           VARCHAR2(1);
137 g_component_appl_id             INTEGER;
138 g_component_name                VARCHAR2(160);
139 g_amb_context_code              VARCHAR2(30);
140 g_entity_code                   VARCHAR2(30);
141 g_event_class_code              VARCHAR2(30);
142 --
143 --=============================================================================
144 --
145 --
146 --
147 --
148 --
149 --
150 --
151 --
152 --
153 --
154 --                  FND trace
155 --
156 --
157 --
158 --
159 --
160 --
161 --
162 --
163 --
164 --
165 --
166 --=============================================================================
167 --=============================================================================
168 --               *********** Local Trace Routine **********
169 --=============================================================================
170 
171 C_LEVEL_STATEMENT     CONSTANT NUMBER := FND_LOG.LEVEL_STATEMENT;
172 C_LEVEL_PROCEDURE     CONSTANT NUMBER := FND_LOG.LEVEL_PROCEDURE;
173 C_LEVEL_EVENT         CONSTANT NUMBER := FND_LOG.LEVEL_EVENT;
174 C_LEVEL_EXCEPTION     CONSTANT NUMBER := FND_LOG.LEVEL_EXCEPTION;
175 C_LEVEL_ERROR         CONSTANT NUMBER := FND_LOG.LEVEL_ERROR;
176 C_LEVEL_UNEXPECTED    CONSTANT NUMBER := FND_LOG.LEVEL_UNEXPECTED;
177 
178 C_LEVEL_LOG_DISABLED  CONSTANT NUMBER := 99;
179 C_DEFAULT_MODULE      CONSTANT VARCHAR2(240) := 'xla.plsql.xla_cmp_condition_pkg';
180 
181 g_log_level           NUMBER;
182 g_log_enabled         BOOLEAN;
183 
184 PROCEDURE trace
185            (p_msg                        IN VARCHAR2
186            ,p_level                      IN NUMBER
187            ,p_module                     IN VARCHAR2)
188 IS
189 BEGIN
190 ----------------------------------------------------------------------------
191 -- Following is for FND log.
192 ----------------------------------------------------------------------------
193 IF (p_msg IS NULL AND p_level >= g_log_level) THEN
194           fnd_log.message(p_level, p_module);
195 ELSIF p_level >= g_log_level THEN
196           fnd_log.string(p_level, p_module, p_msg);
197 END IF;
198 
199 EXCEPTION
200        WHEN xla_exceptions_pkg.application_exception THEN
201           RAISE;
202        WHEN OTHERS THEN
203           xla_exceptions_pkg.raise_message
204              (p_location   => 'xla_cmp_condition_pkg.trace');
205 END trace;
206 --
207 --
208 --=============================================================================
209 --
210 --
211 --
212 --
213 --
214 --
215 --
216 --
217 --
218 --
219 --                 CONDITION translator
220 --
221 --
222 --
223 --
224 --
225 --
226 --
227 --
228 --
229 --
230 --
231 --=============================================================================
232 --+==========================================================================+
233 --|                                                                          |
234 --| PRIVATE Function                                                         |
235 --|                                                                          |
236 --|                                                                          |
237 --|       Name        : GetOneRowCondition                                   |
238 --|                                                                          |
239 --|       Description : Generates a PL/SQL code from one row condition       |
240 --|                     specified in an AMB condition. Does not perform      |
241 --|                     any syntactic validations on the row condition.      |
242 --|                     Validations are handled by the AMB and the PL/SQL    |
243 --|                     compiler.                                            |
244 --|                                                                          |
245 --|       Return      : Returns a varchar containing a PL/SQL code generated |
246 --|                     from the row condition specification                 |
247 --|                                                                          |
248 --+==========================================================================+
249 
250 FUNCTION GetOneRowCondition   (
251    p_condition_id               IN NUMBER
252  , p_array_cond_source_index    IN OUT NOCOPY xla_cmp_source_pkg.t_array_ByInt
253  , p_rec_sources                IN OUT NOCOPY xla_cmp_source_pkg.t_rec_sources
254  )
255 RETURN VARCHAR2
256 IS
257 --
258 --
259 CURSOR cond_cur (p_condition NUMBER) IS
260 SELECT    xc.user_sequence                    user_sequence
261        ,  xc.bracket_left_code                bracket_left_code
262        ,  xc.bracket_right_code               bracket_right_code
263        ,  xc.source_application_id            source_application_id
264        ,  xc.source_type_code                 source_type_code
265        ,  xc.source_code                      source_code
266        ,  xc.flexfield_segment_code           flexfield_segment
267        ,  xc.value_type_code                  value_type_code
268        ,  xc.value_source_application_id      value_source_application_id
269        ,  xc.value_source_type_code           value_source_type_code
270        ,  xc.value_source_code                value_source_code
271        ,  xc.value_flexfield_segment_code     value_flexfield_segment
272        ,  xc.value_constant                   value_constant
273        ,  xc.line_operator_code               line_operator_code
274        ,  xc.logical_operator_code            logical_operator_code
275 FROM   xla_conditions  xc
276 WHERE  condition_id        =  p_condition
277 ;
278 cond_r               cond_cur%ROWTYPE;
279 l_Idx                BINARY_INTEGER;
280 l_cond               VARCHAR2(32000);
281 l_source             VARCHAR2(32000);
282 l_seg                VARCHAR2(32000);
283 l_rec_sources        xla_cmp_source_pkg.t_rec_sources;
284 l_log_module         VARCHAR2(240);
285 BEGIN
286 IF g_log_enabled THEN
287       l_log_module := C_DEFAULT_MODULE||'.GetOneRowCondition';
288 END IF;
289 IF (C_LEVEL_PROCEDURE >= g_log_level) THEN
290       trace
291          (p_msg      => 'BEGIN of GetOneRowCondition'
292          ,p_level    => C_LEVEL_PROCEDURE
293          ,p_module   => l_log_module);
294 END IF;
295 
296 l_cond := NULL;
297 l_seg  := NULL;
298 l_rec_sources  := p_rec_sources;
299 
300 OPEN cond_cur(p_condition_id);
301 
302 IF (C_LEVEL_STATEMENT >= g_log_level) THEN
303       trace
304          (p_msg      => 'SQL - FETCH from xla_conditions  '
305          ,p_level    => C_LEVEL_STATEMENT
306          ,p_module   => l_log_module);
307 
308 END IF;
309 
310 FETCH cond_cur INTO cond_r;
311 CLOSE cond_cur;
312 
313 -- ============
314 -- left bracket
315 -- ============
316 l_cond := l_cond || NVL(cond_r.bracket_left_code,'') ;
317 
318 -- ============
319 -- left operand
320 -- ============
321 IF cond_r.source_code IS NOT NULL THEN
322 
323        l_Idx := xla_cmp_source_pkg.StackSource  (
324                           p_source_code              => cond_r.source_code
325                         , p_source_type_code         => cond_r.source_type_code
326                         , p_source_application_id    => cond_r.source_application_id
327                         , p_array_source_index       => p_array_cond_source_index
328                         , p_rec_sources              => l_rec_sources
329               );
330 
331        IF (cond_r.flexfield_segment IS NULL) THEN
332          l_source := xla_cmp_source_pkg.GenerateSource(
333                                p_Index                     => l_Idx
334                              , p_rec_sources               => l_rec_sources
335                              , p_translated_flag           => 'N'
336                              );
337 
338          IF NVL(cond_r.line_operator_code,'   ') IN ('D','E') THEN
339            IF (C_LEVEL_STATEMENT >= g_log_level) THEN
340                  trace
341                     (p_msg      => 'add nvl'
342                     ,p_level    => C_LEVEL_STATEMENT
343                     ,p_module   => l_log_module);
344            END IF;
345            IF l_rec_sources.array_datatype_code(l_Idx) = 'D' THEN
346              l_cond := l_cond || 'NVL('||l_source||',TO_DATE(''1'',''j'')) ' ;
347            ELSIF l_rec_sources.array_datatype_code(l_Idx) = 'C' THEN
348              l_cond := l_cond || 'NVL('||l_source||',''
349 '') ' ;
350            ELSE
351              l_cond := l_cond || 'NVL('||l_source||',9E125) ' ;
352            END IF;
353 
354          ELSE
355            l_cond := l_cond || l_source || ' ' ;
356          END IF;
357 
358        ELSE
359          --
360          IF g_component_type = 'TAB_ADR'
361          THEN
362             l_seg  := C_TAD_FLEXFIELD_SEGMENT;
363          ELSE
364             IF g_entity_code IS NULL AND g_event_class_code IS NULL THEN
365                l_seg  := C_FLEXFIELD_SEGMENT;
366             ELSE
367                l_seg  := C_FLEXFIELD_SEGMENT_2;
368             END IF;
369          END IF;
370 
371          --
372          l_seg  := REPLACE(l_seg,'$ccid$', nvl(xla_cmp_source_pkg.GenerateSource(
373                                p_Index                     => l_Idx
374                              , p_rec_sources               => l_rec_sources
375                              , p_translated_flag           => 'N'),' null')
376                              );
377 
378          l_seg := REPLACE(l_seg,'$segment_code$'         , nvl(cond_r.flexfield_segment,' '));
379          l_seg := REPLACE(l_seg,'$id_flex_code$'         , nvl(l_rec_sources.array_id_flex_code(l_Idx),' '));
380          l_seg := REPLACE(l_seg,'$flexfield_appl_id$'    , nvl(TO_CHAR(l_rec_sources.array_flexfield_appl_id(l_Idx)),' '));
381          l_seg := REPLACE(l_seg,'$appl_short_name$'      , nvl(l_rec_sources.array_appl_short_name(l_Idx),' ')  );
382          l_seg := REPLACE(l_seg,'$source_code$'          , nvl(l_rec_sources.array_source_code(l_Idx),' ')      );
383          l_seg := REPLACE(l_seg,'$source_type_code$'     , nvl(l_rec_sources.array_source_type_code(l_Idx),' ') );
384          l_seg := REPLACE(l_seg,'$source_application_id$', nvl(TO_CHAR(l_rec_sources.array_application_id(l_Idx)),' ')  );
385          l_seg := REPLACE(l_seg,'$component_type$'       , nvl(g_component_type,' '));
386          l_seg := REPLACE(l_seg,'$component_code$'       , nvl(g_component_code,' ') );
387          l_seg := REPLACE(l_seg,'$component_type_code$'  , nvl(g_component_type_code,' ') );
388          l_seg := REPLACE(l_seg,'$component_appl_id$'    , nvl(TO_CHAR(g_component_appl_id),' ') );
389          l_seg := REPLACE(l_seg,'$amb_context_code$'     , nvl(g_amb_context_code ,' '));
390          l_seg := REPLACE(l_seg,'$entity_code$'          , nvl(g_entity_code ,' '));
391          l_seg := REPLACE(l_seg,'$event_class_code$'     , nvl(g_event_class_code,' ') );
392 
393          IF NVL(cond_r.line_operator_code,'   ') IN ('D','E') THEN
394             --
395             -- D: '!='
396             -- E: '='
397             --
398             IF (C_LEVEL_STATEMENT >= g_log_level) THEN
399                trace
400                  (p_msg      => 'add nvl to segment'
401                  ,p_level    => C_LEVEL_STATEMENT
402                  ,p_module   => l_log_module);
403             END IF;
404 
405             l_cond := l_cond || 'NVL(' || l_seg || ',''' || g_chr_dummy ||''')';
406 
407          ELSE
408 
409             l_cond := l_cond || l_seg;
410 
411          END IF;--
412 
413        END IF;
414  ELSE
415    null;
416  END IF;
417 
418  -- ==========
419  --  operator
420  -- ==========
421  IF cond_r.line_operator_code IS NOT NULL  THEN
422 
423      -- bugfix 6024311: since Meaning in lookup table will be translated,
424      --                 do not use get_meaning() for meanings that are 'operators'.
425 
426    IF(cond_r.logical_operator_code = 'N') THEN
427      l_cond := rtrim(l_cond) ||' IS NULL ';
428    ELSIF(cond_r.logical_operator_code = 'X') THEN
429      l_cond := rtrim(l_cond) ||' IS NOT NULL ';
430    ELSE
431      l_cond := rtrim(l_cond) ||' '
432                || REPLACE(xla_lookups_pkg.get_meaning('XLA_LINE_OPERATOR_TYPE', cond_r.line_operator_code)
433                           ,'!=','<>')||' ';
434    END IF;
435 
436  END IF;
437 
438  -- ===============
439  --  right operand
440  -- ===============
441  IF cond_r.value_type_code= 'S'  THEN
442  --
443  -- source operand
444  --
445      IF cond_r.value_source_code IS NOT NULL THEN
446 
447               l_Idx := xla_cmp_source_pkg.StackSource  (
448                              p_source_code                => cond_r.value_source_code
449                            , p_source_type_code           => cond_r.value_source_type_code
450                            , p_source_application_id      => cond_r.value_source_application_id
451                            , p_array_source_index         => p_array_cond_source_index
452                            , p_rec_sources              => l_rec_sources
453               );
454 
455            IF (cond_r.value_flexfield_segment IS NULL) THEN
456                 l_source := xla_cmp_source_pkg.GenerateSource(
457                                p_Index                     => l_Idx
458                              , p_rec_sources               => l_rec_sources
459                              , p_translated_flag           => 'N');
460                 --
461                 IF NVL(cond_r.line_operator_code,'   ') IN ('D','E') THEN
462                   IF (C_LEVEL_STATEMENT >= g_log_level) THEN
463                         trace
464                            (p_msg      => 'add nvl'
465                            ,p_level    => C_LEVEL_STATEMENT
466                            ,p_module   => l_log_module);
467                   END IF;
468                   IF l_rec_sources.array_datatype_code(l_Idx) = 'D' THEN
469                     l_cond := l_cond || 'NVL('||l_source||',TO_DATE(''1'',''j'')) ' ;
473                   ELSE
470                   ELSIF l_rec_sources.array_datatype_code(l_Idx) = 'C' THEN
471                     l_cond := l_cond || 'NVL('||l_source||',''
472 '') ' ;
474                     l_cond := l_cond || 'NVL('||l_source||',9E125) ' ;
475                   END IF;
476 
477                 ELSE
478                   l_cond := l_cond || l_source || ' ' ;
479                 END IF;
480 
481            ELSE
482                 --
483                 IF g_component_type = 'TAB_ADR'
484                 THEN
485                    l_seg  := C_TAD_FLEXFIELD_SEGMENT;
486                 ELSE
487                    IF g_entity_code IS NULL AND g_event_class_code IS NULL THEN
488                       l_seg  := C_FLEXFIELD_SEGMENT;
489                    ELSE
490                       l_seg  := C_FLEXFIELD_SEGMENT_2;
491                    END IF;
492                 END IF;
493 
494                 l_seg  := REPLACE(l_seg,'$ccid$', nvl(xla_cmp_source_pkg.GenerateSource(
495                                p_Index                     => l_Idx
496                              , p_rec_sources               => l_rec_sources
497                              , p_translated_flag           => 'N'),' null')
498                              );
499 
500                 l_seg := REPLACE(l_seg,'$segment_code$'         , nvl(cond_r.value_flexfield_segment,' '));
501                 l_seg := REPLACE(l_seg,'$id_flex_code$'         , nvl(l_rec_sources.array_id_flex_code(l_Idx),' ')     );
502                 l_seg := REPLACE(l_seg,'$flexfield_appl_id$'    , nvl(TO_CHAR(l_rec_sources.array_flexfield_appl_id(l_Idx)),' '));
503                 l_seg := REPLACE(l_seg,'$appl_short_name$'      , nvl(l_rec_sources.array_appl_short_name(l_Idx),' ')  );
504                 l_seg := REPLACE(l_seg,'$source_code$'          , nvl(l_rec_sources.array_source_code(l_Idx) ,' '));
505                 l_seg := REPLACE(l_seg,'$source_type_code$'     , nvl(l_rec_sources.array_source_type_code(l_Idx),' ') );
506                 l_seg := REPLACE(l_seg,'$source_application_id$', nvl(TO_CHAR(l_rec_sources.array_application_id(l_Idx)) ,' '));
507                 l_seg := REPLACE(l_seg,'$component_type$'       , nvl(g_component_type,' '));
508                 l_seg := REPLACE(l_seg,'$component_code$'       , nvl(g_component_code ,' '));
509                 l_seg := REPLACE(l_seg,'$component_type_code$'  , nvl(g_component_type_code ,' '));
510                 l_seg := REPLACE(l_seg,'$component_appl_id$'    , nvl(TO_CHAR(g_component_appl_id) ,' '));
511                 l_seg := REPLACE(l_seg,'$amb_context_code$'     , nvl(g_amb_context_code ,' '));
512                 l_seg := REPLACE(l_seg,'$entity_code$'          , nvl(g_entity_code ,' '));
513                 l_seg := REPLACE(l_seg,'$event_class_code$'     , nvl(g_event_class_code ,' '));
514                 --
515              IF NVL(cond_r.line_operator_code,'   ') IN ('D','E') THEN
516                 --
517                 -- D: '!='
518                 -- E: '='
519                 --
520                 IF (C_LEVEL_STATEMENT >= g_log_level) THEN
521                   trace
522                     (p_msg      => 'add nvl to segment'
523                     ,p_level    => C_LEVEL_STATEMENT
524                     ,p_module   => l_log_module);
525                 END IF;
526 
527                 l_cond := l_cond || 'NVL(' || l_seg || ',''' || g_chr_dummy ||''')';
528 
529              ELSE
530 
531                 l_cond := l_cond || l_seg;
532 
533              END IF;--                --
534           END IF;
535              --
536        END IF;
537        --
538    ELSIF  cond_r.value_type_code = 'C' THEN
539 
540        IF cond_r.flexfield_segment is NULL THEN
541 
542           IF  l_rec_sources.array_datatype_code(l_Idx) = 'D' THEN
543           -- date
544               l_cond := l_cond ||REPLACE(' fnd_date.canonical_to_date(''$date$'')'
545                                          ,'$date$', cond_r.value_constant);
546           --
547           ELSIF  l_rec_sources.array_datatype_code(l_Idx)   = 'C' THEN
548           --char
549            l_cond := l_cond ||' '||''''||REPLACE(cond_r.value_constant,'''','''''')||'''';
550 
551           ELSIF (l_rec_sources.array_datatype_code(l_Idx)  = 'N' OR
552                  l_rec_sources.array_datatype_code(l_Idx)  = 'I' OR
553                  l_rec_sources.array_datatype_code(l_Idx)  = 'F' ) THEN
554           --number
555                  l_cond := l_cond ||' '|| cond_r.value_constant;
556           END IF;
557        ELSE
558           --consider the right operand as a char
559           l_cond := l_cond ||' '||''''||REPLACE(cond_r.value_constant,'''','''''')||'''';
560        END IF;
561 ELSE
562   null;
563 END IF;
564 -- ===============
565 --  right bracket
566 -- ===============
567 l_cond := l_cond ||NVL(cond_r.bracket_right_code,'');
568 
569 -- ================
570 --  logic operator
571 -- ================
572 IF cond_r.logical_operator_code IS NOT NULL THEN
573 
574    -- bugfix 6024311: since Meaning in lookup table will be translated,
575    --                 do not use get_meaning() for lookup_type XLA_LOGICAL_OPERATOR_TYPE
576    /*
577    l_cond := l_cond ||' '||xla_lookups_pkg.get_meaning('XLA_LOGICAL_OPERATOR_TYPE',
578                                                    cond_r.logical_operator_code )||' ';
579    */
580    IF(cond_r.logical_operator_code = 'A') THEN
581     	l_cond := rtrim(l_cond) ||' AND ';
582    ELSIF(cond_r.logical_operator_code = 'O') THEN
586 END IF;
583     	l_cond := rtrim(l_cond) ||' OR ';
584    END IF;
585 
587 --
588 -- add new line if operands are not null
589 --
590 IF cond_r.source_code IS NOT NULL THEN
591           l_cond := l_cond || g_chr_newline;
592 END IF;
593 IF (C_LEVEL_PROCEDURE >= g_log_level) THEN
594        trace
595           (p_msg      => 'END of GetOneRowCondition'
596           ,p_level    => C_LEVEL_PROCEDURE
597           ,p_module   => l_log_module);
598 END IF;
599 p_rec_sources  := l_rec_sources;
600 RETURN l_cond;
601 EXCEPTION
602 WHEN VALUE_ERROR THEN
603      IF cond_cur%ISOPEN THEN CLOSE cond_cur; END IF;
604      p_rec_sources  := l_rec_sources;
605      IF (C_LEVEL_EXCEPTION >= g_log_level) THEN
606             trace
607                (p_msg      => 'ERROR: XLA_CMP_COMPILER_ERROR = '||sqlerrm
608                ,p_level    => C_LEVEL_EXCEPTION
609                ,p_module   => l_log_module);
610      END IF;
611      RETURN NULL;
612 WHEN xla_exceptions_pkg.application_exception   THEN
613         IF cond_cur%ISOPEN THEN CLOSE cond_cur; END IF;
614         p_rec_sources  := l_rec_sources;
615         IF (C_LEVEL_EXCEPTION >= g_log_level) THEN
616             trace
617                (p_msg      => 'ERROR: XLA_CMP_COMPILER_ERROR = '||sqlerrm
618                ,p_level    => C_LEVEL_EXCEPTION
619                ,p_module   => l_log_module);
620         END IF;
621         RETURN NULL;
622 WHEN OTHERS    THEN
623       IF cond_cur%ISOPEN THEN CLOSE cond_cur; END IF;
624       p_rec_sources  := l_rec_sources;
625       xla_exceptions_pkg.raise_message
626          (p_location => 'xla_cmp_condition_pkg.GetOneRowCondition ');
627 END GetOneRowCondition;
628 
629 
630 --+==========================================================================+
631 --|                                                                          |
632 --| PUBLIC Function                                                          |
633 --|                                                                          |
634 --|                                                                          |
635 --|       Name        : GetCondition                                         |
636 --|                                                                          |
637 --|       Description : Generates a PL/SQL code from AMB condition           |
638 --|                     specified in an AMB condition. Does not perform      |
639 --|                     any syntactic validations on AMB condition.          |
640 --|                     Validations are handled by the AMB and the PL/SQL    |
641 --|                     compiler.                                            |
642 --|                                                                          |
643 --|       Return      : Returns the translation of the AMB condition into    |
644 --|                     PL/SQL code                                          |
645 --|                                                                          |
646 --+==========================================================================+
647 
648 FUNCTION GetCondition   (
649    p_application_id               IN NUMBER
650  , p_component_type               IN VARCHAR2
651  , p_component_code               IN VARCHAR2
652  , p_component_type_code          IN VARCHAR2
653  , p_component_name               IN VARCHAR2
654  , p_entity_code                  IN VARCHAR2
655  , p_event_class_code             IN VARCHAR2
656  , p_amb_context_code             IN VARCHAR2
657  --
658  , p_description_prio_id          IN NUMBER
659  , p_acctg_line_code              IN VARCHAR2
660  , p_acctg_line_type_code         IN VARCHAR2
661  , p_segment_rule_detail_id       IN NUMBER
662  --
663  , p_array_cond_source_index      IN OUT NOCOPY xla_cmp_source_pkg.t_array_ByInt
664  --
665  , p_rec_sources                  IN OUT NOCOPY xla_cmp_source_pkg.t_rec_sources
666 )
667 RETURN VARCHAR2
668 IS
669 --
670 l_cond               VARCHAR2(32000);
671 l_log_module         VARCHAR2(240);
672 --
673 BEGIN
674 IF g_log_enabled THEN
675       l_log_module := C_DEFAULT_MODULE||'.GetCondition';
676 END IF;
677 IF (C_LEVEL_PROCEDURE >= g_log_level) THEN
678       trace
679          (p_msg      => 'BEGIN of GetCondition'
680          ,p_level    => C_LEVEL_PROCEDURE
681          ,p_module   => l_log_module);
682 END IF;
683 g_component_type              := p_component_type;
684 g_component_code              := p_component_code;
685 g_component_type_code         := p_component_type_code;
686 g_component_name              := p_component_name;
687 g_component_appl_id           := p_application_id;
688 g_entity_code                 := p_entity_code;
689 g_event_class_code            := p_event_class_code;
690 g_amb_context_code            := p_amb_context_code;
691 l_cond                        := NULL;
692 --
693 
694 IF  p_description_prio_id IS NOT NULL THEN
695     FOR condition_rec IN (
696         SELECT   condition_id
697                , user_sequence
698          FROM    xla_conditions xc
699         WHERE xc.application_id   = p_application_id
700           AND xc.amb_context_code = p_amb_context_code
701           AND xc.description_prio_id = p_description_prio_id
702         ORDER BY user_sequence ) LOOP
703 
704        l_cond := l_cond || GetOneRowCondition(
708                );
705                   p_condition_id               => condition_rec.condition_id
706                 , p_array_cond_source_index    => p_array_cond_source_index
707                 , p_rec_sources                => p_rec_sources
709     END LOOP;
710 
711 ELSIF p_segment_rule_detail_id IS NOT NULL THEN
712 -- ADR condition
713 
714   FOR condition_rec IN (
715     SELECT   condition_id
716            , user_sequence
717       FROM    xla_conditions xc
718      WHERE xc.application_id         = p_application_id
719        AND xc.amb_context_code       = p_amb_context_code
720        AND xc.segment_rule_detail_id = p_segment_rule_detail_id
721      ORDER BY user_sequence ) LOOP
722 
723      l_cond := l_cond || GetOneRowCondition(
724                   p_condition_id               => condition_rec.condition_id
725                 , p_array_cond_source_index    => p_array_cond_source_index
726                 , p_rec_sources                => p_rec_sources
727                );
728   END LOOP;
729 
730 ELSIF  p_acctg_line_code         IS NOT NULL    AND
731        p_acctg_line_type_code    IS NOT NULL    AND
732        p_entity_code             IS NOT NULL    AND
733        p_event_class_code        IS NOT NULL   THEN
734 -- Accounting line type condition
735 
736   FOR condition_rec IN (
737      SELECT   condition_id
738             , user_sequence
739        FROM    xla_conditions xc
740       WHERE xc.application_id   = p_application_id
741         AND xc.amb_context_code = p_amb_context_code
742         AND xc.accounting_line_code      = p_acctg_line_code
743         AND xc.accounting_line_type_code = p_acctg_line_type_code
744         AND xc.entity_code               = p_entity_code
745         AND xc.event_class_code          = p_event_class_code
746       ORDER BY user_sequence
747   ) LOOP
748 
749      l_cond := l_cond || GetOneRowCondition(
750                   p_condition_id               => condition_rec.condition_id
751                 , p_array_cond_source_index    => p_array_cond_source_index
752                 , p_rec_sources                => p_rec_sources
753                );
754   END LOOP;
755 
756 END IF;
757 
758 IF (C_LEVEL_PROCEDURE >= g_log_level) THEN
759        trace
760           (p_msg      => 'END of GetCondition'
761           ,p_level    => C_LEVEL_PROCEDURE
762           ,p_module   => l_log_module);
763 END IF;
764 RETURN l_cond;
765 EXCEPTION
766 WHEN VALUE_ERROR THEN
767      IF (C_LEVEL_EXCEPTION >= g_log_level) THEN
768             trace
769                (p_msg      => 'ERROR: XLA_CMP_COMPILER_ERROR = '||sqlerrm
770                ,p_level    => C_LEVEL_EXCEPTION
771                ,p_module   => l_log_module);
772      END IF;
773      RETURN NULL;
774 WHEN xla_exceptions_pkg.application_exception   THEN
775      IF (C_LEVEL_EXCEPTION >= g_log_level) THEN
776             trace
777                (p_msg      => 'ERROR: XLA_CMP_COMPILER_ERROR = '||sqlerrm
778                ,p_level    => C_LEVEL_EXCEPTION
779                ,p_module   => l_log_module);
780      END IF;
781      RETURN NULL;
782 WHEN OTHERS    THEN
783       xla_exceptions_pkg.raise_message
784          (p_location => 'xla_cmp_condition_pkg.GetCondition ');
785 END GetCondition;
786 
787 --=============================================================================
788 --
789 --
790 --
791 --
792 --
793 --
794 --
795 --
796 --
797 --
798 --                               PACKAGE BODY
799 --
800 --
801 --
802 --
803 --
804 --
805 --
806 --
807 --
808 --
809 --
810 --=============================================================================
811 --=============================================================================
812 --          *********** Initialization routine **********
813 --=============================================================================
814 
815 BEGIN
816 
817    g_log_level      := FND_LOG.G_CURRENT_RUNTIME_LEVEL;
818    g_log_enabled    := fnd_log.test
819                           (log_level  => g_log_level
820                           ,module     => C_DEFAULT_MODULE);
821 
822    IF NOT g_log_enabled  THEN
823       g_log_level := C_LEVEL_LOG_DISABLED;
824    END IF;
825 END xla_cmp_condition_pkg; --