DBA Data[Home] [Help]

PACKAGE BODY: APPS.IEC_CRITERIA_UTIL_PVT

Source


1 PACKAGE BODY      IEC_CRITERIA_UTIL_PVT AS
2 /* $Header: IECCRUTB.pls 115.4 2004/05/18 19:38:07 minwang noship $ */
3 
4 g_pkg_name CONSTANT VARCHAR2(30) := 'IEC_CRITERIA_UTIL_PVT';
5 
6 TYPE RULE_CRITERIA IS RECORD ( OWNER_ID IEC_G_RULES.OWNER_ID%TYPE
7                              , RULE_ID IEC_G_RULES.RULE_ID%TYPE
8                              , CRITERIA_ID IEC_G_FIELD_CRITERIA.CRITERIA_ID%TYPE
9                              , CRITERIA_COMB_CODE IEC_G_FIELD_CRITERIA.COMBINATION_CODE%TYPE
10                              , FIELD_NAME IEC_G_FIELDS.FIELD_NAME%TYPE
11                              , FIELD_VALUE IEC_G_FIELDS.FIELD_VALUE%TYPE
12                              , FIELD_OP_CODE IEC_G_FIELDS.OPERATOR_CODE%TYPE
13                              , FIELD_OPERATOR IEC_O_ALG_OP_DEFS_B.SQL_OPERATOR%TYPE
14                              , UNARY_FLAG IEC_O_ALG_OP_DEFS_B.IS_UNARY_FLAG%TYPE
15                              , FIELD_DATATYPE USER_TAB_COLUMNS.DATA_TYPE%TYPE
16                              );
17 
18 TYPE BIND_VARIABLE IS RECORD ( NAME         VARCHAR2(30)
19                              , DATA_TYPE    NUMBER
20                              , DATE_VALUE   DATE
21                              , NUMBER_VALUE NUMBER
22                              , STRING_VALUE VARCHAR2(500));
23 
24 TYPE BindVariableCollection IS TABLE OF BIND_VARIABLE INDEX BY BINARY_INTEGER;
25 TYPE ruleCriteriaCollection IS TABLE OF RULE_CRITERIA INDEX BY BINARY_INTEGER;
26 
27 -----------------------------++++++-------------------------------
28 --
29 -- Start of comments
30 --
31 --  API name    : Get_Criteria
32 --  Type        : Private
33 --  Pre-reqs    : None
34 --  Function    : Procedure will append the criteria currently
35 --                present in the IEC_G_RULES, IEC_G_FIELD_CRITERIA,
36 --                and IEC_G_FIELDS tables for the specified owner_id,
37 --                and owner_type_code to the ruleCriteriaCollection
38 --                x_criteria_collection.  The owner is either a
39 --                subset or record filter.
40 --
41 --  Parameters  : p_source_id            IN     NUMBER                       Required
42 --                p_owner_id             IN     NUMBER                       Required
43 --                p_owner_type_code      IN     VARCHAR2                     Required
44 --                p_view_name            IN     VARCHAR2                     Required
45 --                x_criteria_collection  IN OUT ruleCriteriaCollection       Required
46 --                x_return_code             OUT VARCHAR2                     Required
47 --
48 --  Version     : Initial version 1.0
49 --
50 -- End of comments
51 --
52 -----------------------------++++++-------------------------------
53 PROCEDURE Get_Criteria
54    ( p_source_id           IN            NUMBER
55    , p_owner_id            IN            NUMBER
56    , p_owner_type_code     IN            VARCHAR2
57    , p_view_name           IN            VARCHAR2
58    , x_criteria_collection IN OUT NOCOPY ruleCriteriaCollection
59    , x_return_code            OUT NOCOPY VARCHAR2
60    )
61 IS
62 
63   l_status_code VARCHAR2(1);
64   l_index       NUMBER;
65   L_FIELD_TYPE  USER_TAB_COLUMNS.DATA_TYPE%TYPE;
66 
67 BEGIN
68   l_status_code := FND_API.G_RET_STS_SUCCESS;
69 
70   ----------------------------------------------------------------
71   -- Set a save point that can be rolled back to for this procedure.
72   ----------------------------------------------------------------
73   SAVEPOINT GET_CRITERIA_SP;
74 
75   X_RETURN_CODE := FND_API.G_RET_STS_SUCCESS;
76 
77   ----------------------------------------------------------------
78   -- Retrieve all of the rules that have been defined for this
79   -- entity from the IEC_G_RULES table.
80   ----------------------------------------------------------------
81   FOR rule_rec IN (SELECT RULE_ID
82                    FROM   IEC_G_RULES
83                    WHERE  OWNER_ID = p_owner_id
84                    AND    OWNER_TYPE_CODE = p_owner_type_code)
85   LOOP
86 
87     ----------------------------------------------------------------
88     -- Retrieve all of the field criteria that have been defined for
89     -- the current rule from the IEC_G_FIELD_CRITERIA table.  The
90     -- combination code is also retrieved, this is either an AND
91     -- or an OR value that is used when creating the entity's
92     -- contribution to the dynamic SQL where clause.
93     ----------------------------------------------------------------
94     FOR criteria_rec IN (SELECT CRITERIA_ID
95                          ,      COMBINATION_CODE
96                          FROM   IEC_G_FIELD_CRITERIA
97                          WHERE  RULE_ID = rule_rec.RULE_ID)
98     LOOP
99 
100       ----------------------------------------------------------------
101       -- Retrieve all of the fields that have been defined for
102       -- the current field criterion from the IEC_G_FIELDS table.  The
103       -- columns retrieved are used when creating the entity's
104       -- contribution to the dynamic SQL where clause.
105       ----------------------------------------------------------------
106       FOR field_rec IN (SELECT A.FIELD_NAME FIELD_NAME
107                         ,      A.FIELD_VALUE FIELD_VALUE
108                         ,      A.OPERATOR_CODE OPERATOR_CODE
109                         ,      B.SQL_OPERATOR SQL_OPERATOR
110                         ,      B.IS_UNARY_FLAG IS_UNARY_FLAG
111                         FROM   IEC_G_FIELDS A
112                         ,      IEC_O_ALG_OP_DEFS_B B
113                         WHERE  A.CRITERIA_ID = criteria_rec.CRITERIA_ID
114                         AND    A.OPERATOR_CODE = B.OPERATOR_CODE)
115       LOOP
116 
117         ----------------------------------------------------------------
118         -- We need to get the data type for the view column used in
119         -- order to handle it correctly when we create the dynamic SQL.
120         ----------------------------------------------------------------
121         BEGIN
122           SELECT DATA_TYPE
123           INTO   L_FIELD_TYPE
124           FROM   USER_TAB_COLUMNS
125           WHERE  TABLE_NAME = P_VIEW_NAME
126           AND    COLUMN_NAME = field_rec.FIELD_NAME;
127         EXCEPTION
128           ----------------------------------------------------------------
129           -- There isn't a column in the specified view, or the view
130           -- doesn't exist.  We probably should invalidate the entity
131           -- at this point, but for now we just skip this column and try
132           -- to continue.
133           ----------------------------------------------------------------
134           WHEN NO_DATA_FOUND THEN
135             EXIT;
136 
137           WHEN OTHERS THEN
138             RAISE;
139 
140         END;
141 
142         ----------------------------------------------------------------
143         -- Store all of the relevant information that will be needed to
144         -- build the entity's criteria portion of the dynamic SQL statement.
145         ----------------------------------------------------------------
146         l_index := x_criteria_collection.COUNT + 1;
147         x_criteria_collection(l_index).OWNER_ID :=  p_owner_id;
148         x_criteria_collection(l_index).RULE_ID :=  rule_rec.RULE_ID;
149         x_criteria_collection(l_index).CRITERIA_ID :=  criteria_rec.CRITERIA_ID;
150         x_criteria_collection(l_index).CRITERIA_COMB_CODE :=  criteria_rec.COMBINATION_CODE;
151         x_criteria_collection(l_index).FIELD_NAME :=  field_rec.FIELD_NAME;
152         x_criteria_collection(l_index).FIELD_VALUE :=  field_rec.FIELD_VALUE;
153         x_criteria_collection(l_index).FIELD_OP_CODE :=  field_rec.OPERATOR_CODE;
154         x_criteria_collection(l_index).FIELD_OPERATOR :=  field_rec.SQL_OPERATOR;
155         x_criteria_collection(l_index).UNARY_FLAG :=  field_rec.IS_UNARY_FLAG;
156         x_criteria_collection(l_index).FIELD_DATATYPE :=  L_FIELD_TYPE;
157 
158       END LOOP; -- end field loop
159 
160 
161     END LOOP; -- end criteria loop
162 
163 
164   END LOOP; -- end rule loop
165 
166 
167 EXCEPTION
168    WHEN OTHERS THEN
169       ROLLBACK TO GET_CRITERIA_SP;
170       X_RETURN_CODE := FND_API.G_RET_STS_UNEXP_ERROR;
171       RAISE;
172 
173 END Get_Criteria;
174 
175 -----------------------------++++++-------------------------------
176 --
177 -- Start of comments
178 --
179 --  API name    : Get_CriteriaStrings
180 --  Type        : Private
181 --  Pre-reqs    : None
182 --  Function    : Parse the ruleCriteriaCollection to create a string
183 --                representation of the criteria (SQL) that will be
184 --                appended to x_criteria_strings.  This query, represented
185 --                as DBMS_SQL.VARCHAR2S can be executed via DBMS_SQL.
186 --
187 --  Parameters  : p_source_id            IN     NUMBER                       Required
188 --                p_criteria_collection  IN     ruleCriteriaCollection       Required
189 --                x_criteria_strings     IN OUT DBMS_SQL.VARCHAR2S           Required
190 --                x_return_code             OUT VARCHAR2                     Required
191 --
192 --  Version     : Initial version 1.0
193 --
194 -- End of comments
195 --
196 -----------------------------++++++-------------------------------
197 PROCEDURE Get_CriteriaStrings
198    ( p_source_id            IN            NUMBER
199    , p_criteria_collection  IN            ruleCriteriaCollection
200    , x_criteria_strings     IN OUT NOCOPY DBMS_SQL.VARCHAR2S
201    , x_return_code             OUT NOCOPY VARCHAR2
202    )
203 IS
204   l_status_code VARCHAR2(1);
205   l_index NUMBER;
206 
207   l_last_owner_id IEC_G_RULES.OWNER_ID%TYPE;
208   l_last_rule_id IEC_G_RULES.RULE_ID%TYPE;
209   l_last_criteria_id IEC_G_FIELD_CRITERIA.CRITERIA_ID%TYPE;
210 
211   l_first_field_flag BOOLEAN := TRUE;
212   l_first_rule_flag BOOLEAN := TRUE;
213   l_first_criteria_flag BOOLEAN := TRUE;
214 
215   l_curr_string VARCHAR2(2000);
216   l_field_value_cln VARCHAR2(240);
217 
218 BEGIN
219   l_status_code := 'S';
220   l_last_owner_id := -1;
221   l_last_rule_id := -1;
222   l_last_criteria_id := -1;
223   ----------------------------------------------------------------
224   -- Initialize the return code.
225   ----------------------------------------------------------------
226   X_RETURN_CODE := FND_API.G_RET_STS_SUCCESS;
227 
228   ----------------------------------------------------------------
229   -- Create save point for this procedure.
230   ----------------------------------------------------------------
231   SAVEPOINT GET_CRITERIA_STRINGS_SP;
232 
233   ----------------------------------------------------------------
234   -- If we have criteria then we need to build the string,
235   -- otherwise we simply return with no additional criteria being
236   -- added.
237   ----------------------------------------------------------------
238   IF p_criteria_collection.COUNT > 0
239   THEN
240 
241     FOR i IN 1..p_criteria_collection.COUNT
242     LOOP
243 
244       ----------------------------------------------------------------
245       -- If this is the first criteria owner then we need a paranthesis to
246       -- group all of the rules for this owner.
247       ----------------------------------------------------------------
248       IF l_last_owner_id = -1
249       THEN
250         l_curr_string := l_curr_string || ' (';
251 
252       ----------------------------------------------------------------
253       -- This is a new set of rules for a new owner.
254       ----------------------------------------------------------------
255       ELSIF l_last_owner_id <> p_criteria_collection(i).OWNER_ID
256       THEN
257         l_curr_string := l_curr_string || '))) OR (';
258         l_first_rule_flag := TRUE;
259       END IF;
260 
261       ----------------------------------------------------------------
262       -- Set the value of the last owner id for future iterations.
263       ----------------------------------------------------------------
264       l_last_owner_id := p_criteria_collection(i).OWNER_ID;
265 
266       ----------------------------------------------------------------
267       -- If this is the first rule then we need a paranthesis to
268       -- group all of the criteria for this rule.
269       ----------------------------------------------------------------
270       IF l_first_rule_flag = TRUE
271       THEN
272         l_curr_string := l_curr_string || ' (';
273         l_first_rule_flag := FALSE;
274         l_first_criteria_flag := TRUE;
275 
276       ----------------------------------------------------------------
277       -- This is a new rule for the owner.
278       ----------------------------------------------------------------
279       ELSIF l_last_rule_id <> p_criteria_collection(i).RULE_ID
280       THEN
281         l_curr_string := l_curr_string || ')) OR (';
282         l_first_criteria_flag := TRUE;
283       END IF;
284 
285       ----------------------------------------------------------------
286       -- Set the value of the last rule id for future iterations.
287       ----------------------------------------------------------------
288       l_last_rule_id := p_criteria_collection(i).RULE_ID;
289 
290       ----------------------------------------------------------------
291       -- If this is the first criteria or a new criteria then add
292       -- parenthesis for grouping of fields.
293       ----------------------------------------------------------------
294       IF (l_first_criteria_flag = TRUE)
295       THEN
296         l_curr_string := l_curr_string || ' (';
297         l_first_field_flag := TRUE;
298         l_first_criteria_flag := FALSE;
299 
300       ----------------------------------------------------------------
301       -- This is a new criteria (not the first) for the rule.
302       ----------------------------------------------------------------
303       ELSIF l_last_criteria_id <> p_criteria_collection(i).CRITERIA_ID
304       THEN
305         l_curr_string := l_curr_string || ') AND (';
306         l_first_field_flag := TRUE;
307       END IF;
308 
309       ----------------------------------------------------------------
310       -- Set the value of the last criteria id for future iterations.
311       ----------------------------------------------------------------
312       l_last_criteria_id := p_criteria_collection(i).CRITERIA_ID;
313 
314       ----------------------------------------------------------------
315       -- If this is the first field.
316       ----------------------------------------------------------------
317       IF (l_first_field_flag = TRUE)
318       THEN
319         l_curr_string := l_curr_string || ' (';
320         l_first_field_flag := FALSE;
321 
322       ----------------------------------------------------------------
323       -- If this is not the first field then append the criteria
324       -- combination code in front of the (.
325       ----------------------------------------------------------------
326       ELSE
327         l_curr_string := l_curr_string ||
328                          p_criteria_collection(i).CRITERIA_COMB_CODE ||
329                          ' (';
330       END IF;
331 
332       l_curr_string := l_curr_string || 'UPPER(' ||
333                        p_criteria_collection(i).FIELD_NAME || ') ';
334 
335       ----------------------------------------------------------------
336       -- Append the operator.
340       ----------------------------------------------------------------
337       ----------------------------------------------------------------
338       l_curr_string := l_curr_string || p_criteria_collection(i).FIELD_OPERATOR;
339 
341       -- If the unary flag is set to 'N' then we have to append a
342       -- value.
343       ----------------------------------------------------------------
344       IF p_criteria_collection(i).UNARY_FLAG = 'N'
345       THEN
346 
347         ----------------------------------------------------------------
348         -- If this is a VARCHAR2 field then put quotes around everything.
349         ----------------------------------------------------------------
350         IF (p_criteria_collection(i).FIELD_DATATYPE = 'VARCHAR2')
351         THEN
352           l_curr_string := l_curr_string || ' ''';
353 
354           -- Escape all quotes in field value to prevent sql injection
355           l_field_value_cln := NULL;
356           FOR j IN 1..LENGTH(p_criteria_collection(i).FIELD_VALUE) LOOP
357              IF SUBSTR(p_criteria_collection(i).FIELD_VALUE, j, 1) = '''' THEN
358                 l_field_value_cln := l_field_value_cln || '''' || SUBSTR(p_criteria_collection(i).FIELD_VALUE, j, 1);
359              ELSE
360                 l_field_value_cln := l_field_value_cln || SUBSTR(p_criteria_collection(i).FIELD_VALUE, j, 1);
361              END IF;
362           END LOOP;
363 
364           ----------------------------------------------------------------
365           -- If the sql operator is like then we have to figure out where
366           -- to place the wildcards.
367           ----------------------------------------------------------------
368           IF (p_criteria_collection(i).FIELD_OPERATOR = 'LIKE')
369           THEN
370 
371             ----------------------------------------------------------------
372             --  If the operation is "begins with" then place the
373             --  wildcard at the beginning.
374             ----------------------------------------------------------------
375             IF (p_criteria_collection(i).FIELD_OP_CODE = 'BGWITH')
376             THEN
377 
378               l_curr_string := l_curr_string || UPPER(l_field_value_cln) || '%';
379 
380             ----------------------------------------------------------------
381             --  If the operation is "ends with" then place the
382             --  wildcard at the end.
383             ----------------------------------------------------------------
384             ELSIF (p_criteria_collection(i).FIELD_OP_CODE = 'ENDWITH')
385             THEN
386               l_curr_string := l_curr_string || '%' || UPPER(l_field_value_cln);
387 
388             ----------------------------------------------------------------
389             --  If the operation is "contains" then place the
390             --  wildcard at the beginning and end.
391             ----------------------------------------------------------------
392             ELSIF (p_criteria_collection(i).FIELD_OP_CODE = 'CONTAINS')
393             THEN
394               l_curr_string := l_curr_string || '%' || UPPER(l_field_value_cln) || '%';
395 
396             ELSE
397               ----------------------------------------------------------------
398               -- This should throw an error.  Not sure if this should
399               -- somehow signal to turn a subset off or not.
400               ----------------------------------------------------------------
401               NULL;
402             END IF;
403 
404           ELSE
405             l_curr_string := l_curr_string || UPPER(l_field_value_cln);
406           END IF;
407 
408           l_curr_string := l_curr_string || ''' ';
409 
410         ----------------------------------------------------------------
411         -- If this is not a VARCHAR2 field then don't worry about the
412         -- uppercase.
413         ----------------------------------------------------------------
414         ELSE
415           l_curr_string := l_curr_string || UPPER(p_criteria_collection(i).FIELD_VALUE);
416         END IF;
417 
418       END IF;
419 
420       ----------------------------------------------------------------
421       -- Close the grouping around this field.
422       ----------------------------------------------------------------
423       l_curr_string := l_curr_string || ') ';
424 
425       ----------------------------------------------------------------
426       -- If this is the last entry then we need to close up the
427       -- subset, rule, and criteria grouping.
428       ----------------------------------------------------------------
429       IF (i = p_criteria_collection.COUNT)
430       THEN
431         l_curr_string := l_curr_string || '))) ';
432       END IF;
433 
434       l_index := x_criteria_strings.COUNT + 1;
435       x_criteria_strings(l_index) := l_curr_string;
436       l_curr_string := '';
437     END LOOP;
438   END IF;
439 
440 EXCEPTION
441     WHEN OTHERS THEN
442       ROLLBACK TO GET_CRITERIA_STRINGS_SP;
443       X_RETURN_CODE := FND_API.G_RET_STS_UNEXP_ERROR;
444       RAISE;
445 
446 END Get_CriteriaStrings;
447 
448 -----------------------------++++++-------------------------------
449 --
450 -- Start of comments
451 --
452 --  API name    : Append_RecFilterCriteriaClause
453 --  Type        : Private
454 --  Pre-reqs    : None
458 --
455 --  Function    : Append a SQL representation of the record filter criteria
456 --                to a collection of VARCHAR2s.  This query, represented
457 --                as DBMS_SQL.VARCHAR2S can be executed via DBMS_SQL.
459 --  Parameters  : p_source_id            IN     NUMBER                       Required
460 --                p_record_filter_id     IN     NUMBER                       Required
461 --                p_source_type_view     IN     VARCHAR2                     Required
462 --                x_criteria_sql         IN OUT DBMS_SQL.VARCHAR2S           Required
463 --                x_return_code             OUT VARCHAR2                     Required
464 --
465 --  Version     : Initial version 1.0
466 --
467 -- End of comments
468 --
469 -----------------------------++++++-------------------------------
470 PROCEDURE Append_RecFilterCriteriaClause
471    ( p_source_id            IN            NUMBER
472    , p_record_filter_id     IN            NUMBER
473    , p_source_type_view     IN            VARCHAR2
474    , x_criteria_sql         IN OUT NOCOPY DBMS_SQL.VARCHAR2S
475    , x_return_code             OUT NOCOPY VARCHAR2
476    )
477 IS
478   l_status_code VARCHAR2(1);
479   l_criteria_collection ruleCriteriaCollection;
480 
481 BEGIN
482   l_status_code := 'S';
483   ----------------------------------------------------------------
484   -- Initialize the return code.
485   ----------------------------------------------------------------
486   X_RETURN_CODE := FND_API.G_RET_STS_SUCCESS;
487 
488   Get_Criteria(p_source_id, p_record_filter_id, 'RLC', p_source_type_view, l_criteria_collection, l_status_code);
489 
490   ----------------------------------------------------------------
491   -- If rules where found for this record filter then continue
492   -- otherwise stop processing and alert the calling procedure
493   -- by returning a N.
494   ----------------------------------------------------------------
495   IF (l_criteria_collection.COUNT > 0)
496   THEN
497      Get_CriteriaStrings(p_source_id, l_criteria_collection, x_criteria_sql, l_status_code);
498   ELSE
499      X_RETURN_CODE := 'N';
500   END IF;
501 
502 
503 EXCEPTION
504     WHEN OTHERS THEN
505       X_RETURN_CODE := FND_API.G_RET_STS_UNEXP_ERROR;
506       RAISE;
507 END Append_RecFilterCriteriaClause;
508 
509 -----------------------------++++++-------------------------------
510 --
511 -- Start of comments
512 --
513 --  API name    : Append_SubsetCriteriaClause
514 --  Type        : Private
515 --  Pre-reqs    : None
516 --  Function    : Append a SQL representation of the subset criteria
517 --                to a collection of VARCHAR2S.  This query, represented
518 --                as DBMS_SQL.VARCHAR2S can be executed via DBMS_SQL.
519 --
520 --  Parameters  : p_source_id            IN     NUMBER                       Required
521 --                p_record_filter_id     IN     NUMBER                       Required
522 --                p_source_type_view     IN     VARCHAR2                       Required
523 --                x_criteria_sql         IN OUT DBMS_SQL.VARCHAR2S           Required
524 --                x_return_code             OUT VARCHAR2                     Required
525 --
526 --  Version     : Initial version 1.0
527 --
528 -- End of comments
529 --
530 -----------------------------++++++-------------------------------
531 PROCEDURE Append_SubsetCriteriaClause
532    ( p_source_id            IN            NUMBER
533    , p_subset_id            IN            NUMBER
534    , p_source_type_view     IN            VARCHAR2
535    , x_criteria_sql         IN OUT NOCOPY DBMS_SQL.VARCHAR2S
536    , x_return_code             OUT NOCOPY VARCHAR2
537    )
538 IS
539   l_status_code VARCHAR2(1);
540   l_criteria_collection ruleCriteriaCollection;
541 
542 BEGIN
543   l_status_code := 'S';
544   ----------------------------------------------------------------
545   -- Initialize the return code.
546   ----------------------------------------------------------------
547   X_RETURN_CODE := FND_API.G_RET_STS_SUCCESS;
548 
549   Get_Criteria(p_source_id, p_subset_id, 'SUBSET', p_source_type_view, l_criteria_collection, l_status_code);
550 
551   Get_CriteriaStrings(p_source_id, l_criteria_collection, x_criteria_sql, l_status_code);
552 
553 
554 EXCEPTION
555     WHEN OTHERS THEN
556       X_RETURN_CODE := FND_API.G_RET_STS_UNEXP_ERROR;
557       RAISE;
558 
559 END Append_SubsetCriteriaClause;
560 
561 END IEC_CRITERIA_UTIL_PVT;