DBA Data[Home] [Help]

PACKAGE BODY: APPS.BSC_MO_INDICATOR_PKG

Source


1 Package Body BSC_MO_INDICATOR_PKG AS
2 /* $Header: BSCMOIDB.pls 120.4.12000000.2 2007/01/29 12:44:12 abatham ship $ */
3 g_newline VARCHAR2(10):= '
4 ';
5 g_error VARCHAR2(1000);
6 gRecDims VARCHAR2(1000) := null;
7 g_current_indicator BSC_METADATA_OPTIMIZER_PKG.clsIndicator;
8 g_current_dimset number;
9 
10 
11 TYPE cNumMeasuresMap IS RECORD(
12 value varchar2(2000));
13 TYPE tab_cNumMeasuresMap is table of cNumMeasuresMap index by VARCHAR2(300);
14 
15 g_objective_measures tab_cNumMeasuresMap;
16 g_objective_measures_inited boolean := false;
17 
18 
19 Function GetProjectionTableName(TableName IN VARCHAR2) RETURN VARCHAR2 IS
20     pos NUMBER;
21     PTName VARCHAR2(100);
22 
23 BEGIN
24     pos := InStr(TableName, '_', -1);
25     If pos > 0 Then
26         PTName := substr(TableName, 1, pos) || 'PT';
27     Else
28         PTName := TableName || '_PT';
29     End If;
30 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
31         bsc_mo_helper_pkg.writeTmp('Done with GetProjectionTable, returning '||PTName);
32 	END IF;
33 
34     return PTName;
35 
36     EXCEPTION WHEN OTHERS THEN
37         g_error := sqlerrm;
38         bsc_mo_helper_pkg.TerminateWithMsg( 'Exception in GetProjectionTableName : '||g_error);
39         raise;
40 End ;
41 --****************************************************************************
42 --GetFreeDivZeroExpression
43 --
44 --***************************************************************************
45 Function GetFreeDivZeroExpression(expression IN VARCHAR2) RETURN VARCHAR2 IS
46 l_stmt varchar2(1000);
47 l_res varchar2(1000);
48 cv CurTyp;
49 CURSOR cExp IS
50 SELECT BSC_UPDATE_UTIL.Get_Free_Div_Zero_Expression(expression) NEWEXPRESSION FROM DUAL;
51 
52 BEGIN
53 
54     open cExp;
55     fetch cExp into l_res;
56     close cExp;
57 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
58         bsc_mo_helper_pkg.writeTmp( 'Done with GetFreeDivZeroExpression, returning '||l_res);
59 	END IF;
60 
61     return l_res;
62     EXCEPTION WHEN OTHERS THEN
63 	g_error := sqlerrm;
64 	bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetFreeDivZeroExpression :' ||g_error);
65 	raise;
66 End;
67 
68 --****************************************************************************
69 --  getTableLevel
70 --
71 --    DESCRIPTION:
72 --       This function is used only in the BSC-MV Architecture.
73 --****************************************************************************
74 
75 Function getTableLevel(TableName IN VARCHAR2, colTables BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable) RETURN NUMBER IS
76     l_level NUMBER;
77     sourceTable VARCHAR2(100);
78     l_index NUMBER;
79 BEGIN
80     l_index := BSC_MO_HELPER_PKG.findIndex(colTables, TableName);
81     sourceTable := colTables(l_index).originTable;
82     If sourceTable IS NOT NULL Then
83         l_level := 1 + getTableLevel(sourceTable, colTables);
84     Else
85         l_level := 1;
86     End If;
87     return l_level;
88    EXCEPTION WHEN OTHERS THEN
89      g_error := sqlerrm;
90      bsc_mo_helper_pkg.writeTmp('Exception, tableName='||TableName||' colTables=', FND_LOG.LEVEL_EXCEPTION, true);
91      bsc_mo_helper_pkg.write_this(colTables, FND_LOG.LEVEL_EXCEPTION, true);
92      bsc_mo_helper_pkg.TerminateWithMsg('Exception in getTableLevel : '||g_error);
93      raise;
94 End;
95 
96 --***************************************************************************
97 --FindDimensionGroupIndexForKey
98 --
99 --  DESCRIPTION:
100 --     Returns the index of the dril family of the collection
101 --     p_dimension_families which the given dimension belongs to.
102 --
103 --  PARAMETERS:
104 --     p_dimension_families: drills families collection
105 --     Key: dimension key
106 --
107 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
108 --***************************************************************************
109 Function FindDimensionGroupIndexForKey(p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels, p_Key IN VARCHAR2) return NUMBER IS
110     iDimensionLevels NUMBER;
111     DimensionLevels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
112     Dril BSC_METADATA_OPTIMIZER_PKG.clsLevels;
113     i NUMBER;
114 
115     l_groups DBMS_SQL.NUMBER_TABLE;
116     l_group_id NUMBER;
117 
118 BEGIN
119   IF (p_dimension_families.count =0) THEN
120     return -1;
121   END IF;
122   l_groups := BSC_MO_HELPER_PKG.getGroupIds(p_dimension_families);
123   iDimensionLevels := l_groups.first;
124   LOOP
125     EXIT WHEN l_groups.count = 0;
126     l_group_id := l_groups(iDimensionLevels);
127     DimensionLevels := BSC_MO_HELPER_PKG.get_tab_clsLevels (p_dimension_families, l_group_id);
128     IF (DimensionLevels.count >0) THEN
129        i := DimensionLevels.first;
130        LOOP
131          Dril := DimensionLevels(i);
132          If Dril.keyName = p_Key Then
133            return iDimensionLevels;
134          END IF;
135     	 EXIT WHEN i=DimensionLevels.last;
136          i := DimensionLevels.next(i);
137       END LOOP;
138     END IF;
139     EXIT WHEN iDimensionLevels= l_groups.last;
140     iDimensionLevels := l_groups.next(iDimensionLevels);
141   END LOOP;
142   return -1;
143   EXCEPTION WHEN OTHERS THEN
144     g_error := sqlerrm;
145     bsc_mo_helper_pkg.writeTmp('Exception, p_key='||p_key||', Dimension families=', FND_LOG.LEVEL_EXCEPTION, true);
146     bsc_mo_helper_pkg.write_this(p_dimension_families, FND_LOG.LEVEL_EXCEPTION, true);
147     bsc_mo_helper_pkg.TerminateWithMsg('Exception in FindDimensionGroupIndexForKey : '||g_error);
148     raise;
149 End;
150 
151 FUNCTION get_n_parents(p_s_table IN VARCHAR2,
152                         p_s_table_list BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable,
153 						p_level_num IN NUMBER)
154 RETURN DBMS_SQL.VARCHAR2_TABLE IS
155   l_level NUMBER;
156   sourceTable VARCHAR2(100);
157   l_index NUMBER;
158   l_table_name VARCHAR2(400);
159   l_n_parents DBMS_SQL.VARCHAR2_TABLE ;
160 BEGIN
161   l_n_parents(0) := p_s_table;
162   l_table_name := p_s_table;
163   FOR i IN 1..p_level_num LOOP
164     l_index := BSC_MO_HELPER_PKG.findIndex(p_s_table_list, l_table_name);
165     l_table_name  := p_s_table_list(l_index).originTable;
166     IF (l_table_name IS NULL) THEN
167       return l_n_parents;
168     END IF;
169     l_n_parents(l_n_parents.count) := l_table_name;
170   END LOOP;
171   return l_n_parents;
172   EXCEPTION WHEN OTHERS THEN
173     g_error := sqlerrm;
174     bsc_mo_helper_pkg.writeTmp('Exception, p_s_table='||p_s_table||', p_s_table_list=', FND_LOG.LEVEL_EXCEPTION, true);
175     bsc_mo_helper_pkg.write_this(p_s_table_list, FND_LOG.LEVEL_EXCEPTION, true);
176     bsc_mo_helper_pkg.TerminateWithMsg('Exception in get_n_parents : '||g_error);
177     raise;
178 
179 END;
180 
181 -- P1 4148992 for query configured in bsc_kpi_data_tables
182 --
183 PROCEDURE find_join_betweens_levels(p_key IN BSC_METADATA_OPTIMIZER_PKG.clsKeyField,
184    p_zmv_key IN BSC_METADATA_OPTIMIZER_PKG.clsKeyField,
185    p_dimensions IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
186    p_join_level OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE,
187    p_join_parent OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE,
188    p_join_parent_fk OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE)
189 IS
190 cursor cJoin (p_indicator NUMBER, p_dimset NUMBER, p_level_name VARCHAR2) IS
191 select distinct levels.level_table_name child_level, parent_levels.level_table_name parent_level,
192 relation_col parent_fk, level
193 from bsc_sys_dim_level_rels  rels,
194 bsc_sys_dim_levels_b levels,
195 bsc_sys_dim_levels_b parent_levels,
196 bsc_kpi_dim_levels_b kpi_levels
197 where rels.dim_level_id = levels.dim_level_id
198 and levels.level_table_name = kpi_levels.level_table_name
199 and rels.parent_dim_level_id = parent_levels.dim_level_id
200 and kpi_levels.indicator = p_indicator
201 and kpi_levels.dim_set_id = p_dimset
202 connect by prior rels.dim_level_id||rels.relation_type = rels.parent_dim_level_id||1 -- relation_type=1
203 start with parent_dim_level_id = (select dim_level_id from bsc_sys_dim_levels_b where level_table_name = p_level_name)
204 order by level;
205 
206 l_dim VARCHAR2(100);
207 l_parent VARCHAR2(100);
208 l_dim_fk VARCHAR2(100);
209 
210 l_dim_group_index number ;
211 l_dimension_levels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
212 l_index NUMBER;
213 l_level_table_high VARCHAR2(100);
214 l_level_table_low VARCHAR2(100);
215 BEGIN
216   bsc_mo_helper_pkg.writeTmp('In Find join betweeen levels, p_key='||p_key.keyName||', p_zmv_key='||p_zmv_key.keyName, FND_LOG.LEVEL_STATEMENT, false);
217   l_dim_group_index := FindDimensionGroupIndexForKey(p_dimensions, p_key.KeyName);
218   l_dimension_levels := BSC_MO_HELPER_PKG.get_Tab_clsLevels(p_dimensions, l_dim_group_index) ;
219   -- Find the dimension level for the lower level key
220   l_index := BSC_MO_HELPER_PKG.FindIndex(l_dimension_levels,p_key.KeyName);
221   l_level_table_high := l_dimension_levels(l_index).dimTable;
222   l_index := BSC_MO_HELPER_PKG.FindIndex(l_dimension_levels,p_zmv_key.KeyName);
223   l_level_table_low := l_dimension_levels(l_index).dimTable;
224   bsc_mo_helper_pkg.writeTmp('l_level_table_high='||l_level_table_high||', l_level_table_low='||l_level_table_low, FND_LOG.LEVEL_STATEMENT, false);
225   OPEN cJoin(g_current_indicator.code, g_current_dimset, l_level_table_high);
226   LOOP
227     FETCH cJoin INTO l_dim, l_parent, l_dim_fk, l_index;
228     EXIT WHEN cJoin%NOTFOUND;
229     EXIT WHEN l_dim_fk=p_zmv_key.keyName;
230     p_join_level(p_join_level.count) := l_dim;
231     p_join_parent(p_join_parent.count) := l_parent;
232     p_join_parent_fk(p_join_parent_fk.count) := l_dim_fk;
233   END LOOP;
234   CLOSE cJoin;
235   EXCEPTION WHEN OTHERS THEN
236     bsc_mo_helper_pkg.TerminateWithMsg('Exception in find_join_betweens_levels:'||sqlerrm);
237     raise;
238 END;
239 
240 PROCEDURE get_join_info(p_keys IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField,
241 p_zmv_keys IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField,
242 p_zero_code_states IN DBMS_SQL.NUMBER_TABLE,
243 p_dimensions IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
244 p_join_dimensions OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE,
245 p_join_parents OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE,
246 p_join_dimension_fk OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE,
247 p_zmv_fk OUT NOCOPY DBMS_SQL.VARCHAR2_TABLE) IS
248  l_join_dimensions DBMS_SQL.VARCHAR2_TABLE;
249  l_join_parent DBMS_SQL.VARCHAR2_TABLE;
250  l_join_parent_fk DBMS_SQL.VARCHAR2_TABLE;
251  l_stack varchar2(32000);
252 BEGIN
253   FOR i IN p_keys.first..p_keys.last LOOP
254     bsc_mo_helper_pkg.writeTmp('p_keys('||i||')='||p_keys(i).keyName, FND_LOG.LEVEL_STATEMENT, false);
255     IF (p_keys(i).keyName <> p_zmv_keys(i).keyName AND p_zero_code_states(i) =0) THEN
256       bsc_mo_helper_pkg.writeTmp('Find join betweeen levels', FND_LOG.LEVEL_STATEMENT, false);
257       find_join_betweens_levels(
258 	      p_keys(i),
259 		  p_zmv_keys(i),
260 		  p_dimensions,
261 	      l_join_dimensions,
262           l_join_parent ,
263           l_join_parent_fk );
264       bsc_mo_helper_pkg.writeTmp('Found join betweeen levels ', FND_LOG.LEVEL_STATEMENT, false);
265       bsc_mo_helper_pkg.writeTmp('l_join_dimensions are ', FND_LOG.LEVEL_STATEMENT, false);
266       bsc_mo_helper_pkg.write_this(l_join_dimensions, FND_LOG.LEVEL_STATEMENT, false);
267       bsc_mo_helper_pkg.writeTmp('l_join_parents are ', FND_LOG.LEVEL_STATEMENT, false);
268       bsc_mo_helper_pkg.write_this(l_join_parent, FND_LOG.LEVEL_STATEMENT, false);
269       bsc_mo_helper_pkg.writeTmp('l_join_parent_fk are ', FND_LOG.LEVEL_STATEMENT, false);
270       bsc_mo_helper_pkg.write_this(l_join_parent_fk, FND_LOG.LEVEL_STATEMENT, false);
271       IF (l_join_dimensions.count>0) THEN
272       FOR j IN l_join_dimensions.first..l_join_dimensions.last LOOP
273         p_join_dimensions(p_join_dimensions.count) := l_join_dimensions(j);
274         p_join_parents(p_join_parents.count) := l_join_parent(j);
275         p_join_dimension_fk(p_join_dimension_fk.count) := l_join_parent_fk(j);
276         p_zmv_fk(p_zmv_fk.count) := p_zmv_keys(i).keyName;
277       END LOOP;
278       END IF;
279     END IF;
280   END LOOP;
281   EXCEPTION WHEN OTHERS THEN
282     bsc_mo_helper_pkg.writeTmp('p_keys, p_zmv_keys, p_zero_code_states, p_dimensions in order', FND_LOG.LEVEL_EXCEPTION, true);
283     bsc_mo_helper_pkg.write_this(p_keys, FND_LOG.LEVEL_EXCEPTION, true);
284     bsc_mo_helper_pkg.write_this(p_zmv_keys, FND_LOG.LEVEL_EXCEPTION, true);
285     bsc_mo_helper_pkg.write_this(p_zero_code_states, FND_LOG.LEVEL_EXCEPTION, true);
286     bsc_mo_helper_pkg.write_this(p_dimensions, FND_LOG.LEVEL_EXCEPTION, true);
287 	bsc_mo_helper_pkg.TerminateWithMsg('Exception in get_join_info:'||sqlerrm);
288     raise;
289 END;
290 
291 --****************************************************************************
292 --  optimize_zmv_clause
293 --  Bug fix for : 3944813
294 --    DESCRIPTION:
295 --       This function is to generate optimized SQL statements for iViewer.
296 --       We will reuse ZMVs from lower levels to speed up the iViewer query
297 --       performance. For eg. if MV levels=2 and an iViewer zero code query
298 --       is on level 3, we redirect the query to the lower level ZMV to use
299 --       the aggregated results from the lower level. We will need to join to
300 --       dimensions levels.
301 --****************************************************************************
302 FUNCTION optimize_zmv_clause(p_dimensions IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
303                              p_s_table_list IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable,
304                              p_s_table IN VARCHAR2,
305 							 p_table_level IN NUMBER,
306 							 p_keys IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField,
307 							 p_zero_code_states IN DBMS_SQL.NUMBER_TABLE,
308 							 p_system_levels IN NUMBER,
309 							 p_sql_stmt IN OUT NOCOPY VARCHAR2)
310 RETURN BOOLEAN IS
311   l_nlevel_parents DBMS_SQL.VARCHAR2_TABLE;
312   l_highest_table_with_zmv VARCHAR2(400);
313   l_zmv_keys BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
314   b_zmv_exists boolean := false;
315   l_zmv VARCHAR2(400);
316 
317   l_dim_group_index NUMBER;
318   l_index NUMBER;
319   l_dimension_levels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
320 
321   CURSOR cParentFK(p_lower_dim_table IN VARCHAR2, p_higher_dim_table IN VARCHAR2) IS
322   SELECT RELATION_COL
323   FROM BSC_SYS_DIM_LEVEL_RELS RELS, BSC_SYS_DIM_LEVELS_B LVLA, BSC_SYS_DIM_LEVELS_B LVLB
324   WHERE LVLA.level_table_name = p_lower_dim_table
325   AND LVLB.level_table_name = p_higher_dim_table
326   AND LVLA.dim_level_id = rels.dim_level_id
327   AND LVLB.dim_level_id = rels.parent_dim_level_id;
328 
329   b_dimensions_joined boolean := true;
330 
331 
332   l_select_keys_clause VARCHAR2(4000);
333   l_select_rest VARCHAR2(4000);
334   l_from_clause VARCHAR2(4000);
335   l_where_clause VARCHAR2(4000);
336   l_group_by_clause VARCHAR2(4000);
337   b_zero_code_key_exists boolean :=false;
338   l_join_dimensions DBMS_SQL.VARCHAR2_TABLE;
339   l_join_dimensions_fk DBMS_SQL.VARCHAR2_TABLE;
340   l_join_parents DBMS_SQL.VARCHAR2_TABLE;
341   l_zmv_fk DBMS_SQL.VARCHAR2_TABLE;
342 
343 BEGIN
344   IF (p_table_level<=p_system_levels) THEN
345     return false;
346   END IF;
347   -- note that get_n_parents returns the current s_table at position 0, and then its parents
348   -- at positions 1, 2 etc
349   bsc_mo_helper_pkg.writeTmp('Inside Optimize ZMV clause, p_table_level='||p_table_level||', p_system_levels='||p_system_levels, FND_LOG.level_Statement, false);
350   bsc_mo_helper_pkg.writeTmp('Zero Code states = ', FND_LOG.level_Statement, false);
351   bsc_mo_helper_pkg.write_this(p_zero_code_states, FND_LOG.level_Statement, false);
352   l_select_rest := p_sql_stmt;
353   l_nlevel_parents := get_n_parents(p_s_table, p_s_table_list, p_table_level-p_system_levels);
354   bsc_mo_helper_pkg.write_this(l_nlevel_parents, FND_LOG.level_Statement, false);
355   IF l_nlevel_parents.count = 1 THEN -- no parents, only 1 level, itself
356     bsc_mo_helper_pkg.writeTmp('Completed Optimize ZMV clause', FND_LOG.level_Statement, false);
357     return false;
358   END IF;
359   l_highest_table_with_zmv := l_nlevel_parents(l_nlevel_parents.last);
360   -- BSC Multiple Optimizers to run
361   --l_zmv_keys := BSC_MO_HELPER_PKG.getAllKeyFields(l_highest_table_with_zmv);
362   l_index := BSC_MO_HELPER_PKG.findIndex(p_s_table_list, l_highest_table_with_zmv);
363   bsc_mo_helper_pkg.writeTmp('Highest table with zmv is '||l_highest_table_with_zmv||', with index='||l_index, FND_LOG.level_Statement, false);
364   l_zmv_keys := p_s_table_list(l_index).keys;
365 
366   IF (p_keys.count <> l_zmv_keys.count) THEN -- MN rel
367     bsc_mo_helper_pkg.writeTmp('Completed Optimize ZMV clause', FND_LOG.level_Statement, false);
368     return false;
369   END IF;
370   b_zmv_exists := false;
371   FOR i IN l_zmv_keys.first..l_zmv_keys.last LOOP
372     If l_zmv_keys(i).CalculateCode0 and keyFieldExists(p_keys, l_zmv_keys(i).keyName) and p_zero_code_states(i) = 1 Then
373       b_zmv_exists :=true;
374       EXIT;
375     END IF;
376   END LOOP;
377   IF (b_zmv_exists = false) THEN
378     bsc_mo_helper_pkg.writeTmp('Completed Optimize ZMV clause, Zero code mv with values for this level comb does not exist, returning false', FND_LOG.level_Statement, false);
379     return false;
380   ELSE
381     bsc_mo_helper_pkg.writeTmp('ZMV exists ', FND_LOG.level_Statement, false);
382   END IF;
383   l_zmv := l_highest_table_with_zmv||'_ZMV';
384   -- Note: l_nlevel_parents(0) is the same as the current S table
385   -- Only l_nlevel_parents(1) and higher are the real parents
386   -- if all zero_code_states are 0, then go directly to ZMV
387   b_dimensions_joined := false;
388   FOR i IN p_Keys.first..p_Keys.last LOOP
389     -- even if a value is selected (ie not zero code), we can ignore joining to the dimension
390     -- if the key exists in the ZMV also
391     IF (p_zero_code_states(i) = 0 AND keyFieldExists(l_zmv_keys, p_keys(i).keyName)=false) THEN
392       b_dimensions_joined := true;
393       EXIT;
394     END IF;
395   END LOOP;
396 
397   -- Generate the FROM clause
398   l_from_clause := ' FROM '||l_zmv|| ' '||l_zmv||',';
399   l_where_clause := ' WHERE ';
400 
401   IF (b_dimensions_joined) THEN
402     get_join_info(p_keys, l_zmv_keys, p_zero_code_states, p_dimensions, l_join_dimensions, l_join_parents, l_join_dimensions_fk, l_zmv_fk);
403     FOR i IN l_join_dimensions.first..l_join_dimensions.last LOOP
404 	  l_from_clause := l_from_clause || ' '||l_join_dimensions(i)||' '||l_join_dimensions(i)||',';
405 	  if bsc_im_utils.is_column_in_object(l_join_dimensions(i), 'LANGUAGE') then
406         l_where_clause := l_where_clause||l_join_dimensions(i)||'.language='''||BSC_IM_UTILS.get_lang||''''||' AND ';
407       end if;
408     END LOOP;
409     -- add rest of the joins
410     FOR i IN l_join_dimensions.first..l_join_dimensions.last-1 LOOP
411       IF (l_join_parents(i+1) = l_join_dimensions(i)) THEN-- Same dimension
412 	    l_where_clause := l_where_clause || ' '||l_join_dimensions(i)||'.CODE = '||l_join_dimensions(i+1)||'.'||l_join_dimensions_fk(i+1)||' AND ';
413 	  ELSE -- join to zmv
414 	    l_where_clause := l_where_clause || ' '||l_join_dimensions(i)||'.CODE = '||l_zmv||'.'||l_zmv_fk(i)||' AND ';
415 	  END IF;
416     END LOOP;
417     -- handle last join to ZMV
418     l_where_clause := l_where_clause || ' '||l_join_dimensions(l_join_dimensions.last)||'.CODE = '||l_zmv||'.'||l_zmv_fk(l_zmv_fk.last)||' AND ';
419   END IF;
420   -- Remove the comma
421   l_from_clause := substr(l_from_clause, 1, length(l_from_clause)-1);
422 
423   -- We need to add the ZMV. alias to the SELECT column keys
424   IF (b_dimensions_joined) THEN
425     bsc_mo_helper_pkg.writeTmp('Dimensions have been joined to, so we need to change the select clause', FND_LOG.level_Statement, false);
426   END IF;
427   l_select_keys_clause := 'SELECT ';
428   l_group_by_clause := ' GROUP BY ';
429   FOR j IN p_Keys.first..p_Keys.last LOOP
430       If p_zero_code_states(j) = 1 Then
431         l_select_keys_clause := l_select_keys_clause || '0 ' || p_keys(j).keyName || ', ';
432         IF keyFieldExists(l_zmv_keys, p_keys(j).keyName) AND p_keys(j).calculateCode0 THEN
433           l_where_clause := l_where_clause ||p_keys(j).keyName||' = 0 AND ';
434         END IF;
435       Else
436         IF keyFieldExists(l_zmv_keys, p_keys(j).keyName) THEN
437           l_select_keys_clause := l_select_keys_clause || l_zmv||'.';
438         END IF;
439         l_select_keys_clause := l_select_keys_clause ||p_keys(j).keyName || ', ';
440         l_group_by_clause := l_group_by_clause ||p_keys(j).keyName||',';
441       End If;
442   END LOOP;
443   IF (trim(l_where_clause) = 'WHERE') THEN
444     l_where_clause := null;
445   ELSE
446     l_where_clause := substr(l_where_clause, 1, length(l_where_clause)-5);
447   END IF;
448   bsc_mo_helper_pkg.writeTmp('l_where_clause final='||l_where_clause, FND_LOG.level_Statement, false);
449 
450   bsc_mo_helper_pkg.writeTmp('l_select_keys_clause='||l_select_keys_clause, FND_LOG.level_Statement, false);
451   bsc_mo_helper_pkg.writeTmp('Intermediate l_group_by_clause='||l_group_by_clause, FND_LOG.level_Statement, false);
452   l_group_by_clause := l_group_by_clause ||' PERIODICITY_ID, YEAR, TYPE, PERIOD, PERIOD_TYPE_ID ';
453   bsc_mo_helper_pkg.writeTmp('l_group_by_clause final='||l_group_by_clause, FND_LOG.level_Statement, false);
454   p_sql_stmt := l_select_keys_clause||' '||l_select_rest||' '||l_from_clause||' '||l_where_clause||' '||l_group_by_clause;
455   bsc_mo_helper_pkg.writeTmp('Completed Optimize ZMV clause, sql_stmt='||p_sql_stmt, FND_LOG.level_Statement, false);
456   return true;
457   EXCEPTION WHEN OTHERS THEN
458     bsc_mo_helper_pkg.writeTmp('Completed optimize_zmv_clause with error : '||sqlerrm, fnd_log.level_exception, true);
459     bsc_mo_helper_pkg.TerminateWithMsg('Exception in optimize_zmv_clause:'||sqlerrm);
460     bsc_mo_helper_pkg.writeTmp('l_where_clause final='||l_where_clause, FND_LOG.level_exception, true);
461     raise;
462     return false;
463 END;
464 
465 
466 --****************************************************************************
467 --  GetColConfigKpiMV
468 --
469 --    DESCRIPTION:
470 --       This function is used only in the BSC-MV Architecture.
471 --       Given the table it will return a collection
472 --       with the configuration for all the combinations of zero codes
473 --       and the sql or mv to be used by iviewer
474 --
475 --****************************************************************************
476 Function GetColConfigKpiMV(
477                           STable BSC_METADATA_OPTIMIZER_PKG.clsBasicTable,
478                           TableLevel NUMBER,
479 						  p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
480 						  colSummaryTables IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable
481                           )
482   RETURN BSC_METADATA_OPTIMIZER_PKG.tab_clsConfigKpiMV IS
483     colConfigKpiMV BSC_METADATA_OPTIMIZER_PKG.tab_clsConfigKpiMV;
484     configKpiMV BSC_METADATA_OPTIMIZER_PKG.clsConfigKpiMV;
485     MVName VARCHAR2(100);
486     zmvName VARCHAR2(100);
487     keyColumn BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
488     Dato BSC_METADATA_OPTIMIZER_PKG.clsDataField;
489     arrCombinationsB DBMS_SQL.VARCHAR2_TABLE;
490     numCombinationsB NUMBER;
491     arrCombinationsA DBMS_SQL.VARCHAR2_TABLE;
492     numCombinationsA NUMBER;
493     i NUMBER;
494     anyKeyNeedZeroCode Boolean;
495     isTotalCombination Boolean;
496     newCombination VARCHAR2(100);
497     sql_stmt VARCHAR2(4000);
498     group_by VARCHAR2(1000);
499     state VARCHAR2(100);
500     New_clsConfigKpiMV BSC_METADATA_OPTIMIZER_PKG.clsConfigKpiMV;
501     STable_Keys BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
502     STable_Data BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
503 	l_groups DBMS_SQL.NUMBER_TABLE;
504 	bForcedSQL boolean := false;
505 
506     -- added for bug 3944813
507 
508 	l_zero_code_states DBMS_SQL.NUMBER_TABLE;
509     l_select_key_clause VARCHAR2(4000);
510     l_from_clause VARCHAR2(4000);
511     l_where_clause VARCHAR2(4000);
512     l_stack varchar2(32000);
513     l_newline varchar2(10):='
514 ';
515 BEGIN
516   l_groups := BSC_MO_HELPER_PKG.getGroupIds(p_dimension_families);
517   bsc_mo_helper_pkg.writeTmp('# of levels = '||l_groups.count||' while max allowed = '||BSC_BIA_WRAPPER.MAX_ALLOWED_LEVELS, FND_LOG.LEVEL_STATEMENT, false);
518   -- AWs, assume ZMV exists
519   IF (g_current_indicator.Impl_Type = 2) THEN
520     bForcedSQL := false;
521   ELSIF (l_groups.count > BSC_BIA_WRAPPER.MAX_ALLOWED_LEVELS) THEN
522     bForcedSQL := true;
523     bsc_mo_helper_pkg.writeTmp('Going to convert MVs to SQL because of DB limitation... # of levels = '||l_groups.count||' while max allowed = '||BSC_BIA_WRAPPER.MAX_ALLOWED_LEVELS, FND_LOG.LEVEL_statement, true);
524     --l_stack := l_stack || 'Going to convert MVs to SQL because of DB limitation... # of levels = '||l_groups.count||' while max allowed = '||BSC_BIA_WRAPPER.MAX_ALLOWED_LEVELS||l_newline;
525   END IF;
526   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
527     bsc_mo_helper_pkg.writeTmp(' ');
528     bsc_mo_helper_pkg.writeTmp('In GetColConfigKpiMV , TableLevel = '||TableLevel||', LevelConfig ='||STable.LevelConfig);
529   END IF;
530   bsc_mo_helper_pkg.write_this(STable);
531   MVName := STable.Name || '_MV';
532   If STable.LevelConfig IS NULL Then
533     --Table has no dimensions
534     configKpiMV.LevelComb := '?';
535     configKpiMV.DataSource := 'MV';
536     configKpiMV.MVName := MVName;
537     configKpiMV.SqlStmt := null;
538     colConfigKpiMV(0) := configKpiMV;
539     return colConfigKpiMV;
540   End If;
541   --Table has dimensions
542   anyKeyNeedZeroCode := False;
543   arrCombinationsA(0) := STable.LevelConfig;
544   numCombinationsA := 1;
545   --BSC Multiple Optimizers
546   --STable_Keys := bsc_mo_helper_pkg.getAllKeyFields(STable.name);
547   i := BSC_MO_HELPER_PKG.findIndex(colSummaryTables, STable.name);
548   STable_Keys := colSummaryTables (i).keys;
549   FOR i IN STable_Keys.first..STable_Keys.last LOOP
550     keyColumn := STable_keys(i);
551     bsc_mo_helper_pkg.write_this(keyColumn);
552     If keyColumn.CalculateCode0 Then
553       anyKeyNeedZeroCode := True;
554       arrCombinationsB.delete;
555       numCombinationsB := 0;
556       For j IN 0..(numCombinationsA - 1) LOOP
557         --By design if the key needs zero code the character corresponding to this
558         -- key in STable.level_Comb is "?"
559         --We need to create two entries one with 0 (selected) and one with 1 (all)
560         newCombination := substr( arrCombinationsA(j), 1, keyColumn.dimIndex) ||
561                                  '0' || substr(arrCombinationsA(j), keyColumn.dimIndex + 2);
562         arrCombinationsB(numCombinationsB) := newCombination;
563         numCombinationsB := numCombinationsB + 1;
564         newCombination := substr(arrCombinationsA(j), 1, keyColumn.dimIndex) ||
565                                  '1' || substr(arrCombinationsA(j), keyColumn.dimIndex + 2);
566         arrCombinationsB(numCombinationsB) := newCombination;
567         numCombinationsB := numCombinationsB + 1;
568       END LOOP;
569       arrCombinationsA := arrCombinationsB;
570       numCombinationsA := arrCombinationsA.count;
571     End If;
572   END LOOP;
573   If anyKeyNeedZeroCode Then
574     bsc_mo_helper_pkg.writeTmp('Zero code is needed, no. of combinations = '||numCombinationsB, FND_LOG.level_Statement, false);
575     For i IN 0..numCombinationsB - 1 LOOP
576       bsc_mo_helper_pkg.writeTmp('Processing combination '||i||'='||arrCombinationsB(i), FND_LOG.level_Statement, false);
577       l_stack := null;
578       configKpiMV := New_clsConfigKpiMV;
579       configKpiMV.LevelComb := arrCombinationsB(i);
580       isTotalCombination := False;
581       l_select_key_clause := 'SELECT ';
582       --sql_stmt := 'SELECT ';
583       group_by := null;
584       l_zero_code_states.delete;
585       l_stack := l_stack || 'check 1'||l_newline;
586       FOR j IN STable_Keys.first..STable_Keys.last LOOP
587         keyColumn := STable_Keys (j);
588         l_stack := l_stack || 'key = '||keyColumn.keyName ||l_newline;
589         If keyColumn.CalculateCode0 Then
590           l_stack := l_stack || 'Calc zero code'||l_newline;
591           state := substr(arrCombinationsB(i), keyColumn.dimIndex + 1, 1);
592           -- BEGIN added for bug 3944813
593           l_zero_code_states(l_zero_code_states.count) := state;
594           -- END added for bug 3944813
595           l_stack := l_stack || 'State='||state||l_newline;
596           If state = 1 Then
597             isTotalCombination := True;
598             l_select_key_clause := l_select_key_clause || '0 ' || keyColumn.keyName || ', ';
599           Else
600             l_select_key_clause := l_select_key_clause || keyColumn.keyName || ', ';
601             group_by := group_by || keyColumn.keyName || ', ';
602           End If;
603         Else
604           l_stack := l_stack || 'Dont Calc zero code'||l_newline;
605           l_zero_code_states(l_zero_code_states.count) := 0;
606           l_select_key_clause := l_select_key_clause || keyColumn.keyName || ', ';
607           group_by := group_by || keyColumn.keyName || ', ';
608         End If;
609       END LOOP;
610       If (isTotalCombination=false) Then
611         l_stack := l_stack || 'Total comb is false'||l_newline;
612         --This combination does not get any zero code
613         configKpiMV.DataSource := 'MV';
614         configKpiMV.MVName := MVName;
615         configKpiMV.SqlStmt := null;
616       Else
617         l_stack := l_stack || 'Total comb is true'||l_newline;
618         -- bug 3835059, autogenerate sqls instead of MVs if # of levels > BSC_METADATA_OPTIMIZER_PKG.MAX_ALLOWED_LEVELS
619         If (NOT bForcedSQL) AND TableLevel <= to_number(BSC_METADATA_OPTIMIZER_PKG.g_Adv_Summarization_Level) Then
620           --There will be a MV for the zero code
621           configKpiMV.DataSource := 'MV';
622           configKpiMV.MVName := STable.name || '_ZMV';
623           configKpiMV.SqlStmt := null;
624           l_stack := l_stack || 'MV exists'||l_newline;
625         Else
626           l_stack := l_stack || 'Need to configure SQL for zero code combination'||l_newline;
627           --Need to configure a SQL to get zero code for this combination
628           sql_stmt := null;
629           sql_stmt := sql_stmt || 'PERIODICITY_ID, YEAR, TYPE, PERIOD, PERIOD_TYPE_ID';
630           group_by := group_by || 'PERIODICITY_ID, YEAR, TYPE, PERIOD, PERIOD_TYPE_ID';
631           --BSC Multiple Optimizer
632           --STable_Data := bsc_mo_helper_pkg.getAllDataFields(STable.name);
633           STable_Data := STable.Data;
634           FOR j IN STable_Data.first..STable_Data.last LOOP
635             Dato := STable_Data(j);
636             If Dato.AvgLFlag = 'Y' Then
637               sql_stmt := sql_stmt || ', ' ||GetFreeDivZeroExpression('SUM(' || Dato.AvgLTotalColumn
638                                     || ')/SUM(' || Dato.AvgLCounterColumn || ')') || ' ' || Dato.fieldName;
639             Else
640               sql_stmt := sql_stmt || ', ' ||Dato.aggFunction || '(' || Dato.fieldName || ') ' || Dato.fieldName;
641               l_stack := l_stack || 'check 2, sql_stmt is  '||sql_stmt||l_newline;
642             End If;
643           END LOOP;
644           -- BEGIN added for bug 3944813
645           bsc_mo_helper_pkg.writeTmp('Calling Optimize ZMV clause', FND_LOG.level_Statement, false);
646           l_stack := l_stack || 'Calling Optimize ZMV clause'||l_newline;
647           IF (bForcedSQL =false) -- bug 4139837
648                AND TableLevel > to_number(BSC_METADATA_OPTIMIZER_PKG.g_Adv_Summarization_Level)
649                AND to_number(BSC_METADATA_OPTIMIZER_PKG.g_Adv_Summarization_Level) > 0
650                AND g_current_indicator.Impl_Type = 1
651 			   AND (optimize_zmv_clause(p_dimension_families,
652 								   colSummaryTables,
653 								   STable.Name,
654 								   TableLevel,
655 								   STable_Keys,
656 								   l_zero_code_states,
657 								   to_number(BSC_METADATA_OPTIMIZER_PKG.g_Adv_Summarization_Level),
658 								   sql_stmt)=true) THEN
659             bsc_mo_helper_pkg.writeTmp('Optimized sql_stmt='||sql_stmt, FND_LOG.level_Statement, false);
660 
661           ELSE
662 	        sql_stmt := l_select_key_clause || sql_stmt || ' FROM ' || MVName;
663             sql_stmt := sql_stmt || ' GROUP BY ' || group_by;
664           END IF;
665           l_stack := l_stack || 'sql_stmt is '||sql_stmt||l_newline;
666           -- END added for bug 3944813
667           configKpiMV.DataSource := 'SQL';
668           configKpiMV.MVName := MVName;
669           configKpiMV.SqlStmt := sql_stmt;
670         End If;
671       End If;
672       colConfigKpiMV(colConfigKpiMV.count) := configKpiMV;
673     END LOOP;
674   Else
675     --No key needs zero code
676     --Iviewer will read from the MV
677     configKpiMV.LevelComb := STable.LevelConfig;
678     configKpiMV.DataSource := 'MV';
679     configKpiMV.MVName := MVName;
680     configKpiMV.SqlStmt := null;
681     colConfigKpiMV(colConfigKpiMV.count) := configKpiMV;
682   End If;
683   return colConfigKpiMV;
684   EXCEPTION WHEN OTHERS THEN
685     g_error := sqlerrm;
686 	bsc_mo_helper_pkg.writeTmp('Exception in GetColConfigKpiMV : '||g_error, FND_LOG.LEVEL_STATEMENT, true);
687 	bsc_mo_helper_pkg.writeTmp('Stack is '||l_stack, FND_LOG.LEVEL_STATEMENT, true);
688 	bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetColConfigKpiMV : '||g_error);
689     raise;
690 End ;
691 
692 
693 PROCEDURE clearDrill(pDrill IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.clsLevels) IS
694 l_new BSC_METADATA_OPTIMIZER_PKG.clsLevels;
695 BEGIn
696     pDrill := l_new;
697 END;
698 
699 
700 --****************************************************************************
701 --fieldExistsInLov
702 --
703 --  DESCRIPTION:
704 --     Return TRUE if the given field exist in the collection gLov
705 --
706 --  PARAMETERS:
707 --     measure: field name
708 --
709 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
710 --***************************************************************************
711 
712 Function fieldExistsInLov(measure IN VARCHAR2,
713 -- BSC Autogen
714 p_source IN VARCHAR2) RETURN BOOLEAN IS
715     measure_field BSC_METADATA_OPTIMIZER_PKG.clsMeasureLOV;
716     i NUMBER ;
717 
718 BEGIN
719   IF (BSC_METADATA_OPTIMIZER_PKG.gLOV.count = 0) THEN
720     return false;
721   END IF;
722   i :=  BSC_METADATA_OPTIMIZER_PKG.gLov.first;
723   LOOP
724     measure_field := BSC_METADATA_OPTIMIZER_PKG.gLOV(i);
725     IF (upper(measure_field.fieldName) = upper(measure)
726     -- BSC Autogen
727 	AND upper(measure_field.source) = upper(p_source)) THEN
728 	  return True;
729     END IF;
730     EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gLov.last;
731     i := BSC_METADATA_OPTIMIZER_PKG.gLOV.next(i);
732   END LOOP;
733   return false;
734   EXCEPTION WHEN OTHERS THEN
735     g_error := sqlerrm;
736 	bsc_mo_helper_pkg.TerminateWithMsg('Exception in fieldExistsInLov for field '||measure||' : '||g_error);
737     raise;
738 End ;
739 
740 
741 
742 --***************************************************************************
743 -- IndexRelation1N : IndexRelacion1N
744 --  DESCRIPTION:
745 --     Returns the index of the 1n relation from the colletion of parents
746 --     of the given dimension. Returns -1 if it is not found
747 --  PARAMETERS:
748 --     Maestra: dimension name
749 --     maestrapadre: name of the parent dimension
750 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
751 --***************************************************************************
752 Function IndexRelation1N(tablename IN VARCHAR2, masterTableName IN VARCHAR2 ) RETURN NUMBER IS
753  i NUMBER;
754  j NUMBER;
755  l_parent_name DBMS_SQL.VARCHAR2_TABLE;
756  l_dummy NUMBER;
757 
758 BEGIN
759     i := BSC_MO_HELPER_PKG.findindex(BSC_METADATA_OPTIMIZER_PKG.gMastertable, tablename);
760 
761 
762     IF (BSC_METADATA_OPTIMIZER_PKG.gMastertable(i).parent_name IS NULL ) THEN
763 	   return -1;
764     END IF;
765 
766     l_dummy := BSC_MO_HELPER_PKG.decomposestring(BSC_METADATA_OPTIMIZER_PKG.gMastertable(i).parent_name, ',', l_parent_name);
767 
768     j := l_parent_name.first;
769     LOOP
770         IF UPPER(l_parent_name(j)) = UPPER(masterTableName) Then
771 		    return i;
772         END IF;
773 	EXIT WHEN j = l_parent_name.last;
774 	j := l_parent_name.next(j);
775     END LOOP;
776 
777     return -1;
778     EXCEPTION WHEN OTHERS THEN
779         g_error := sqlerrm;
780 	    bsc_mo_helper_pkg.TerminateWithMsg('Exception in IndexRelation1N : '||g_error||', tablename='||tablename||', masterTableName='||masterTableName);
781             bsc_mo_helper_pkg.writeTmp('Dimension tables are  ', FND_LOG.LEVEL_ERROR, true);
782             bsc_mo_helper_pkg.write_this(BSC_METADATA_OPTIMIZER_PKG.gMastertable, FND_LOG.LEVEL_ERROR, true);
783         raise;
784 End;
785 
786 
787 
788 --****************************************************************************
789 --IndexRelacionMN
790 --
791 --  DESCRIPTION:
792 --     Returns the index of the MN relation from the collection gRelacioneMN.
793 --     Returns 0 if it is not found.
794 --     A relation exists no matter the order of the dimension tables
795 --  PARAMETERS:
796 --     TablaA: name of the dimension table A
797 --     TablaB: name of the dimension table B
798 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
799 --***************************************************************************
800 Function IndexRelationMN(TableA IN VARCHAR2, TableB IN VARCHAR2) return NUMBER IS
801 i NUMBER;
802 j NUMBER;
803 
804 BEGIN
805     i :=  BSC_METADATA_OPTIMIZER_PKG.gRelationsMN.count;
806 
807     IF (i = 0) THEN
808 	   return -1;
809     END IF;
810 
811     i := BSC_METADATA_OPTIMIZER_PKG.gRelationsMN.first;
812     LOOP
813 
814         If ((UPPER(BSC_METADATA_OPTIMIZER_PKG.gRelationsMN(i).TableA) = UPPER(TableA)) And
815            (UPPER(BSC_METADATA_OPTIMIZER_PKG.gRelationsMN(i).TableB) = UPPER(TableB))) Or
816            ((UPPER(BSC_METADATA_OPTIMIZER_PKG.gRelationsMN(i).TableA) = UPPER(TableB)) And
817            (UPPER(BSC_METADATA_OPTIMIZER_PKG.gRelationsMN(i).TableB) = UPPER(TableA))) Then
818 		   return i;
819         END IF;
820         EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gRelationsMN.last;
821         i := BSC_METADATA_OPTIMIZER_PKG.gRelationsMN.next(i);
822     END LOOP;
823 
824     return -1;
825     EXCEPTION WHEN OTHERS THEN
826         g_error := sqlerrm;
827 	    bsc_mo_helper_pkg.TerminateWithMsg('Exception in IndexRelationMN : '||g_error);
828         raise;
829 End;
830 
831 
832 
833 
834 --****************************************************************************
835 --GetPeriodicityOrigin
836 --  DESCRIPTION:
837 --     Return the code of the periodicity within colPeriodicidades
838 --     where the given periodicity can be originated from.
839 --     Return -1 if it can not be originated from any of them.
840 --
841 --  PARAMETERS:
842 --     colPeriodicidades: collection of periodicities
843 --     Periodicidad: periodicity code
844 --     forTargetLevel: true  -Only see periodicities with TargetLevel = 1
845 --                       false -See all periodicities
846 --
847 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
848 --***************************************************************************
849 
850 Function GetPeriodicityOrigin(colPeriodicities IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsIndicPeriodicity,
851 				Periodicity IN NUMBER,
852                                forTargetLevel IN Boolean) RETURN NUMBER IS
853     PERIODIC BSC_METADATA_OPTIMIZER_PKG.clsIndicPeriodicity;
854     l_return NUMBER := -1;
855     l_count NUMBER := -1;
856     l_per_table DBMS_SQL.NUMBER_TABLE;
857     l_dummy NUMBER;
858 
859     l_stack VARCHAR2(32000);
860 
861 
862     l_index number;
863 BEGIN
864     IF (BSC_METADATA_OPTIMIZER_PKG.g_log) THEN
865         bsc_mo_helper_pkg.writeTmp('Starting GetPeriodicityOrigin for Periodicity='|| Periodicity
866                 ||', forTargetLevel='||bsc_mo_helper_pkg.boolean_decode(forTargetLevel));
867         bsc_mo_helper_pkg.write_this(colPeriodicities);
868     END IF;
869     l_count := colPeriodicities.first;
870 
871 
872     LOOP
873         IF (length(l_stack) > 31000) THEN
874             l_stack := null;
875         END IF;
876 
877         l_stack := 'Looping...';
878 	    EXIT WHEN colPeriodicities.count =0;
879 	    PERIODIC := colPeriodicities(l_count);
880         l_stack := l_stack||g_newline||'check2, l_count = '||l_count||', periodic.code = '||periodic.code||', peridociity = '||periodicity;
881 
882         IF PERIODIC.Code <> Periodicity Then
883             IF (Not forTargetLevel) Or (forTargetLevel And PERIODIC.TargetLevel = 1) Then
884                 l_stack := l_stack||g_newline||'check 2b';
885                 l_index := BSC_MO_HELPER_PKG.findIndex(BSC_METADATA_OPTIMIZER_PKG.gPeriodicities, Periodicity);
886                 l_stack := l_stack||g_newline||'check 2c, l_index = '||l_index;
887                 l_per_table := BSC_MO_HELPER_PKG.decomposestringtonumber(BSC_METADATA_OPTIMIZER_PKG.gPeriodicities(l_index).PeriodicityOrigin, ',');
888                 l_stack := l_stack||g_newline||'check 3';
889                 IF  BSC_MO_HELPER_PKG.FindIndex(l_per_table, PERIODIC.Code) >= 0 Then
890                       l_stack := l_stack||g_newline||'check4';
891 		              l_return := PERIODIC.Code;
892                       IF (BSC_METADATA_OPTIMIZER_PKG.g_log) THEN
893                         bsc_mo_helper_pkg.writeTmp('returning '||l_return);
894                         END IF;
895 		              return l_return;
896                 END IF;
897                 l_stack := l_stack||g_newline||'check5';
898             END IF;
899         END IF;
900         l_stack := l_stack||g_newline||'l_count = '||l_count||', colPeriodicities.last = '||colPeriodicities.last;
901 	    EXIT WHEN l_count = colPeriodicities.last;
902         l_count := colPeriodicities.next(l_count);
903         l_stack := l_stack||g_newline||'l_count = '||l_count;
904         IF (length(l_stack) > 30000) THEN
905            if (BSC_METADATA_OPTIMIZER_PKG.g_log) Then
906               bsc_mo_helper_pkg.writeTmp(l_stack);
907            else
908               -- retain last 20000 chars
909               l_stack := substr(l_stack, 10000, length(l_stack));
910            end if;
911         END IF;
912     END LOOP;
913     IF (BSC_METADATA_OPTIMIZER_PKG.g_log) THEN
914       bsc_mo_helper_pkg.writeTmp('returning '||l_return);
915     END IF;
916     RETURN L_RETURN;
917 
918     EXCEPTION WHEN OTHERS THEN
919         g_error := sqlerrm;
920 	    bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetPeriodicityOrigin, '||g_error);
921 	    bsc_mo_helper_pkg.writeTmp('Stack is '||l_stack, fnd_log.level_exception, true);
922         raise;
923 END;
924 
925 --****************************************************************************
926 --IsFilteredIndicator
927 --  DESCRIPTION:
928 --     This function returns TRUE if the given indicator and configuration
929 --     has filters.
930 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
931 --***************************************************************************
932 
933 Function IsFilteredIndicator(Indicator IN NUMBER, Configuration IN NUMBER) RETURN Boolean IS
934 
935 	l_stmt VARCHAR2(1000);
936  	l_temp1 number;
937 	l_temp2 number;
938     cv CurTyp;
939 
940     CURSOR cFilter(pIndicator IN NUMBER, pConfig IN NUMBER)  IS
941     SELECT count(1)
942 	 FROM BSC_KPI_DIM_LEVELS_B K, BSC_SYS_DIM_LEVELS_B S
943 	WHERE UPPER(K.LEVEL_TABLE_NAME) = UPPER(S.LEVEL_TABLE_NAME)
944 	AND K.INDICATOR = pIndicator
945 	AND K.DIM_SET_ID = pConfig
946 	AND UPPER(S.LEVEL_VIEW_NAME) <> UPPER(K.LEVEL_VIEW_NAME)
947 	AND K.STATUS = 2;
948 BEGIN
949 null;
950     --Since MLS Dimensions, the level_table_name is always different
951     --from level_view_name. So we need to change this query.
952 
953 
954     OPEN cFilter(Indicator, Configuration);
955     FETCH cFilter INTO l_temp1;
956     CLOSE cFilter;
957 
958     IF (l_temp1 =0 )  THEN
959 	   return false;
960     Else
961 	   return true;
962     END IF;
963 
964     EXCEPTION WHEN OTHERS THEN
965         g_error := sqlerrm;
966 	    bsc_mo_helper_pkg.TerminateWithMsg('Exception in IsFilteredIndicator : '||g_error);
967         raise;
968 End;
969 
970 
971 PROCEDURE init_measure_counts(l_list IN DBMS_SQL.number_table) IS
972   l_dummy varchar2(1000);
973   l_stmt varchar2(4000) := 'SELECT kpi.indicator||''_''|| i.dim_set_id hash_index, COUNT(M.MEASURE_COL) NUM_DATA_COLUMNS
974     FROM BSC_SYS_MEASURES M, '||BSC_METADATA_OPTIMIZER_PKG.g_dbmeasure_tmp_table||' I,
975     BSC_KPIS_VL kpi
976     WHERE I.MEASURE_ID = M.MEASURE_ID
977     AND kpi.indicator = i.indicator
978     AND M.TYPE = 0
979     AND NVL(M.SOURCE, ''BSC'') IN (''BSC'', ''PMF'')
980     AND NVL(M.SOURCE, ''BSC'') <> decode(kpi.short_name, null, ''PMF'', ''-1'')
981     GROUP BY kpi.indicator||''_''|| i.dim_set_id ';
982     numDataColumns number;
983   l_hash_index dbms_sql.varchar2_table;
984   l_num_measures dbms_sql.number_table;
985   cv CurTyp;
986 BEGIN
987   l_dummy := bsc_mo_helper_pkg.Get_New_Big_In_Cond_Number(4, 'INDICATOR');
988   bsc_mo_helper_pkg.Add_Value_Bulk(4, l_list);
989   OPEN cv FOR l_stmt;
990   FETCH cv BULK COLLECT INTO l_hash_index, l_num_measures;
991   CLOSE cv;
992   FOR i IN 1..l_hash_index.count LOOP
993     g_objective_measures(l_hash_index(i)).value := l_num_measures(i);
994   END LOOP;
995   EXCEPTION WHEN OTHERS THEN
996     g_error := sqlerrm;
997     bsc_mo_helper_pkg.TerminateWithMsg('Exception in init_measure_count : '||g_error||', stmt='||l_stmt);
998     raise;
999 END;
1000 
1001 --***************************************************************************
1002 --GetNumDataColumns
1003 --  DESCRIPTION:
1004 --     Get the number of data columns of the indicator for the given
1005 --     dimension set.
1006 --  PARAMETERS:
1007 --     Indic: indicator code
1008 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1009 --**************************************************************************
1010 Function GetNumDataColumns(Indic IN NUMBER, DimSet IN NUMBER) RETURN NUMBER IS
1011 
1012     l_stmt varchar2(10000) :=
1013     'SELECT COUNT(M.MEASURE_COL) NUM_DATA_COLUMNS
1014     FROM BSC_SYS_MEASURES M, '||BSC_METADATA_OPTIMIZER_PKG.g_dbmeasure_tmp_table||' I
1015     WHERE I.MEASURE_ID = M.MEASURE_ID
1016     AND I.DIM_SET_ID = :1
1017     AND I.INDICATOR = :2
1018     AND M.TYPE = 0
1019 	AND NVL(M.SOURCE, ''BSC'') IN (''BSC'', ''PMF'')
1020 	AND NVL(M.SOURCE, ''BSC'') <> :3';
1021     numDataColumns number;
1022     cv CurTyp;
1023     CURSOR cExists IS
1024     select count(1) from user_objects where object_name = BSC_METADATA_OPTIMIZER_PKG.g_dbmeasure_tmp_table;
1025 
1026     CURSOR cNumCols(pIgnore VARCHAR2) IS
1027     SELECT COUNT(M.MEASURE_COL) NUM_DATA_COLUMNS
1028     FROM BSC_SYS_MEASURES M, BSC_DB_MEASURE_BY_DIM_SET_V I
1029     WHERE I.MEASURE_ID = M.MEASURE_ID
1030     AND I.DIM_SET_ID = DimSet
1031     AND I.INDICATOR = Indic
1032     AND M.TYPE = 0
1033     AND NVL(M.SOURCE, 'BSC') in('BSC', 'PMF')
1034     AND NVL(M.SOURCE, 'BSC') <> pIgnore;
1035     l_short_name VARCHAR2(400);
1036 BEGIN
1037 
1038   IF (g_objective_measures.exists(Indic||'_'||DimSet)) THEN
1039     return g_objective_measures(Indic||'_'||DimSet).value;
1040   END IF;
1041   SELECT short_name INTO l_short_name FROM bsc_kpis_vl where indicator = Indic;
1042 
1043   --BSC-PMF Integration: Even though a PMF measure cannot be present in a BSC
1044   --dimension set, I am going to do the validation to filter out PMF measures
1045   -- Bug 4301819
1046   -- Dont include PMF measures if this is created by objective definer
1047   IF (l_short_name is null) THEN -- created by objective definer, so source shouldnt be = 'PMF'
1048     OPEN cv FOR l_stmt USING DimSet, Indic, 'PMF';
1049   ELSE
1050     OPEN cv FOR l_stmt USING DimSet, Indic, '-1';
1051   END IF;
1052   FETCH cv INTO numDataColumns;
1053   CLOSE cv;
1054   g_objective_measures(Indic||'_'||DimSet).value := numDataColumns;
1055 
1056   return numDataColumns;
1057 
1058   EXCEPTION WHEN OTHERS THEN
1059     g_error := sqlerrm;
1060     bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetNumDataColumns : '||g_error);
1061     raise;
1062 End;
1063 
1064 
1065 Function GetSourceDimensionSet(Indic IN NUMBER, DimSet IN NUMBER) return VARCHAR2 IS
1066 
1067    CURSOR cSourceDimSet IS
1068    SELECT NVL(SOURCE, 'BSC') DSSOURCE
1069 			FROM BSC_SYS_DIM_LEVELS_B S, BSC_KPI_DIM_LEVELS_B K
1070 			WHERE S.LEVEL_TABLE_NAME = K.LEVEL_TABLE_NAME
1071 			AND K.INDICATOR = Indic AND K.DIM_SET_ID = DimSet  AND K.STATUS = 2;
1072     l_ret VARCHAR2(100);
1073     cv CurTyp;
1074 
1075 BEGIN
1076 
1077     --BSC-PMF Integration: In a dimension set there is no BSC and PMF dimensions
1078     -- at the same time. The criteria to get the source of a dimension set is
1079     -- the source of the fisrt dimension level of the dimension set
1080 
1081     OPEN cSourceDimSet;
1082 
1083 	FETCH cSourceDimSet INTO l_ret;
1084     If cSourceDimSet%NOTFOUND Then
1085         l_ret := 'BSC';
1086     END IF;
1087 	close cSourceDimSet;
1088 
1089 	return l_ret;
1090     EXCEPTION WHEN OTHERS THEN
1091         g_error := sqlerrm;
1092 	    bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetSourceDimensionSet : '||g_error);
1093         raise;
1094 End;
1095 
1096 
1097 
1098 --***************************************************************************
1099 --GetConfigurationsForIndic : GetColConfiguracionesIndic
1100 --  DESCRIPTION:
1101 --     Get the collection with the configurations of the indicator
1102 --  PARAMETERS:
1103 --     Indic: indicator code
1104 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1105 --*************************************************************************
1106 Function GetConfigurationsForIndic(Indic IN NUMBER) return DBMS_SQL.NUMBER_TABLE IS
1107     colConfigurationes dbms_sql.number_table;
1108     colMeasures BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
1109     Configuration NUMBER;
1110     CURSOR cConfigs IS
1111         SELECT DISTINCT DIM_SET_ID
1112         FROM BSC_DB_DATASET_DIM_SETS_V
1113         WHERE INDICATOR = Indic
1114         ORDER BY DIM_SET_ID;
1115 
1116     DimSet NUMBER;
1117     cv CurTyp;
1118     l_src VARCHAR2(100);
1119     l_num number := 0;
1120 
1121 BEGIN
1122 
1123     OPEN cConfigs;
1124 
1125     LOOP
1126         --BSC-PMF Integration: Only get BSC dimension sets
1127         FETCH cConfigs INTO DimSet;
1128         EXIT WHEN cConfigs%NOTFOUND;
1129         --l_src := GetSourceDimensionSet(Indic, DimSet) ;
1130 
1131         --BIS DIMENSIONS: We need to consider dimension sets that have
1132         --BSC meaures not matter if the dimensions are from BIS or BSC.
1133         --So we do not need this validatino anymore.
1134         --If l_src = 'BSC' Then
1135             --We need to validate that there is at least one BSC data column
1136             --associated to this dimension set.
1137             L_NUM := GetNumDataColumns(Indic, DimSet) ;
1138 
1139             If l_num > 0 Then
1140                 Configuration := DimSet;
1141                 colConfigurationes(colConfigurationes.count) := Configuration;
1142             END IF;
1143         --END IF;
1144     END LOOP;
1145     close cConfigs;
1146 
1147     --bsc_mo_helper_pkg.write_this(colConfigurationes);
1148     return colConfigurationes;
1149 
1150 
1151     EXCEPTION WHEN OTHERS THEN
1152     g_error := sqlerrm;
1153     bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetConfigurationsForIndic for Indic='||Indic||', error is '||g_error);
1154     fnd_message.set_name('BSC', 'BSC_RETR_DIMSET_KPI_FAILED');
1155 	fnd_message.set_token('INDICATOR', Indic);
1156     app_exception.raise_exception;
1157 
1158 
1159 End;
1160 
1161 --***************************************************************************
1162 --ConfigureTablesSharedIndicatorsNoFilters
1163 --  DESCRIPTION:
1164 --     Configure shared indicators without filters same tables as master indicator
1165 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1166 --***************************************************************************
1167 
1168 PROCEDURE ConfigureMasterSharedIndics IS
1169     Indicator BSC_METADATA_OPTIMIZER_PKG.clsIndicator;
1170     colConfigurationes dbms_sql.number_table;
1171     Configuration NUMBER;
1172     i NUMBER;
1173     j NUMBER;
1174 
1175     l_stmt VARCHAR2(3000);
1176 
1177 BEGIN
1178 
1179 null;
1180 
1181 
1182     IF (BSC_METADATA_OPTIMIZER_PKG.gIndicators.count =0) THEN
1183 	   return;
1184     END IF;
1185     i := BSC_METADATA_OPTIMIZER_PKG.gIndicators.first;
1186 
1187 
1188     LOOP
1189 	   Indicator := BSC_METADATA_OPTIMIZER_PKG.gIndicators(i);
1190         --Only consider new indicators or indicators that have been modified.
1191         --BSC-MV Note: If there is change of summarization level
1192         --we need to process all the indicators.
1193 
1194         If (Indicator.Action_Flag = 3) Or (Indicator.Action_Flag <> 2 And BSC_METADATA_OPTIMIZER_PKG.g_Sum_Level_Change <> 0) Then
1195             --Get the list of configurations of the kpi
1196 
1197             colConfigurationes := GetConfigurationsForIndic(Indicator.Code);
1198 		    j := colConfigurationes.first;
1199 	        LOOP
1200 		          EXIT WHEN colConfigurationes.count=0;
1201 		          Configuration := colConfigurationes(j);
1202 
1203                 If Indicator.Share_Flag = 2 And (Not IsFilteredIndicator(Indicator.Code, Configuration))
1204 				And  (Not IsFilteredIndicator(Indicator.source_indicator, Configuration))Then
1205                     DELETE FROM BSC_KPI_DATA_TABLES WHERE INDICATOR = Indicator.code  AND DIM_SET_ID = Configuration;
1206 
1207                     --BSC-MV Note: include columns MV_NAME and PROJECTION_SOURCE, DATA_SOURCE, SQL_STMT
1208                     -- and PROJECTION_DATA
1209                     --3182722
1210                     l_stmt := 'INSERT INTO BSC_KPI_DATA_TABLES ( INDICATOR,PERIODICITY_ID,
1211                                 DIM_SET_ID, LEVEL_COMB, TABLE_NAME, FILTER_CONDITION  ';
1212                     If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
1213                         l_stmt := l_stmt ||', MV_NAME, PROJECTION_SOURCE , DATA_SOURCE , SQL_STMT , PROJECTION_DATA ';
1214                     End If;
1215                     l_stmt := l_stmt ||' )  SELECT :1,  PERIODICITY_ID, :2, LEVEL_COMB, TABLE_NAME, FILTER_CONDITION ';
1216                     If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
1217                         l_stmt := l_stmt ||', MV_NAME, PROJECTION_SOURCE , DATA_SOURCE , SQL_STMT, PROJECTION_DATA ';
1218                     End If;
1219                     l_stmt := l_stmt ||' FROM BSC_KPI_DATA_TABLES WHERE INDICATOR = :3 AND DIM_SET_ID = :4';
1220 
1221                     execute immediate l_stmt using Indicator.code, Configuration, Indicator.Source_Indicator, Configuration;
1222 
1223                 End If;
1224                 EXIT WHEN j=colConfigurationes.last;
1225 		        j := colConfigurationes.next(j);
1226             END LOOP;
1227 
1228         End If;
1229         EXIT WHEN i =BSC_METADATA_OPTIMIZER_PKG.gIndicators.last;
1230 	    i := BSC_METADATA_OPTIMIZER_PKG.gIndicators.next(i);
1231     END LOOP;
1232 
1233     EXCEPTION WHEN OTHERS THEN
1234         g_error := sqlerrm;
1235         bsc_mo_helper_pkg.TerminateWithMsg('Exception in ConfigureMasterSharedIndics : '||g_error);
1236         raise;
1237 END;
1238 
1239 --***************************************************************************
1240 --keyFieldExists - ExisteCampoLlave
1241 --
1242 --  DESCRIPTION:
1243 --     Returns TRUE if exists the key in the collection. The collection
1244 --     is of objects of class clsCampoLlave.
1245 --  PARAMETERS:
1246 --     colCamposLlaves: collection
1247 --     Llave: key name
1248 --
1249 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1250 --***************************************************************************
1251 Function keyFieldExists(colCamposLlaves IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField, keyName IN VARCHAR2) return Boolean IS
1252    CampoLlave BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
1253    i NUMBER;
1254 
1255 BEGIN
1256 
1257     IF (colCamposLlaves.count = 0) THEN
1258 	   return false;
1259     END IF;
1260     i := colCamposLlaves.first;
1261     LOOP
1262 	    CampoLlave:= colCamposLlaves(i);
1263         If Upper(CampoLlave.keyName) = Upper(keyName) Then
1264 	       return true;
1265         END IF;
1266 	    EXIT WHEN i = colCamposLlaves.last;
1267 	    i := colCamposLlaves.next(i);
1268     END LOOP;
1269 
1270     return false;
1271     EXCEPTION WHEN OTHERS THEN
1272         g_error := sqlerrm;
1273         bsc_mo_helper_pkg.TerminateWithMsg('EXCEPTION IN keyFieldExists : '||g_error);
1274         raise;
1275 End;
1276 
1277 --****************************************************************************
1278 --SameDisaggregatioins : sonMismasDesagregaciones
1279 --
1280 --  DESCRIPTION:
1281 --     Say if the dissagregations are the same
1282 --
1283 --  PARAMETERS:
1284 --     PeriodicityA: periodicity A
1285 --     keysA: Dissagregation A
1286 --     PeriodicityB: peridiodicity B
1287 --     keysB: Dissagregation B
1288 --
1289 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1290 --***************************************************************************
1291 Function SameDisaggregations(PeriodicityA IN NUMBER,
1292   --tableA IN VARCHAR2,
1293   tableA BSC_METADATA_OPTIMIZER_PKG.clsTable,
1294 			PeriodicityB IN NUMBER,
1295 			--tableB IN VARCHAR2
1296 			tableB BSC_METADATA_OPTIMIZER_PKG.clsTable
1297 			) return Boolean IS
1298     keyNameIgual Boolean;
1299     keyNameA BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
1300     l_res boolean := false;
1301     i NUMBER;
1302     keysA BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
1303     keysB BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
1304 
1305 BEGIN
1306 
1307   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1308     bsc_mo_helper_pkg.writeTmp('Inside SameDisaggregations, PeriodicityA='||PeriodicityA||', PeriodicityB='||PeriodicityB);
1309   END IF;
1310   --BSC Multiple optimizers
1311   keysA := tableA.keys;
1312   keysB := tableB.keys;
1313   If PeriodicityA = PeriodicityB Then
1314     If keysA.Count = keysB.Count Then
1315       keyNameIgual := True;
1316       IF (keysA.count>0) THEN
1317         i := keysA.first;
1318         LOOP
1319           keyNameA := keysA(i);
1320           If Not keyFieldExists(keysB, keyNameA.keyName) Then
1321             keyNameIgual := False;
1322             EXIT;
1323           END IF;
1324           EXIT WHEN i = keysA.last;
1325           i := keysA.next(i);
1326         END LOOP;
1327       END IF;
1328       If keyNameIgual Then
1329         IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1330           bsc_mo_helper_pkg.writeTmp('Completed SameDisaggregations, returning true');
1331         END IF;
1332         return true;
1333       END IF;
1334     END IF;
1335   END IF;
1336   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1337     bsc_mo_helper_pkg.writeTmp('Completed SameDisaggregations, returning '||bsc_mo_helper_pkg.boolean_decode(l_res));
1338   END IF;
1339   return l_res;
1340   EXCEPTION WHEN OTHERS THEN
1341     g_error := sqlerrm;
1342     bsc_mo_helper_pkg.TerminateWithMsg('EXCEPTION in SameDisaggregations : '||g_error);
1343     raise;
1344 End ;
1345 
1346 --****************************************************************************
1347 --GetTargetTable
1348 --  DESCRIPTION:
1349 --     Return the name of the taregt table corresponding to the given table.
1350 --     It looks the target tables in gTablas for tables of the same indicator
1351 --     and configuration. The target table must have the same periodicity and
1352 --     same dimension levels of the given table.
1353 --     It returns '' in case there is no target table.
1354 --
1355 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1356 --***************************************************************************
1357 Function GetTargetTable(p_table IN BSC_METADATA_OPTIMIZER_PKG.clsTable) return VARCHAR2 IS
1358 
1359     tbl BSC_METADATA_OPTIMIZER_PKG.clsTable;
1360     targetTable varchar2(100);
1361     keyField BSC_METADATA_OPTIMIZER_PKG.clskeyField;
1362     i NUMBER;
1363 
1364 BEGIN
1365   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1366     bsc_mo_helper_pkg.writeTmp('Inside GetTargetTable, pTable is');
1367   END IF;
1368   bsc_mo_helper_pkg.write_this(p_table);
1369   targetTable := null;
1370   i := BSC_METADATA_OPTIMIZER_PKG.gTables.first;
1371   LOOP
1372     EXIT WHEN BSC_METADATA_OPTIMIZER_PKG.gTables.count=0;
1373     tbl := BSC_METADATA_OPTIMIZER_PKG.gTables(i);
1374     If tbl.Indicator = p_table.Indicator And tbl.Configuration = p_table.Configuration And tbl.IsTargetTable Then
1375       If SameDisaggregations(tbl.Periodicity, tbl, p_table.Periodicity, p_table) Then
1376         targetTable := tbl.Name;
1377         Exit;
1378       END IF;
1379     END IF;
1380     EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gTables.last;
1381     i := BSC_METADATA_OPTIMIZER_PKG.gTables.next(i);
1382   END LOOP;
1383   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1384     bsc_mo_helper_pkg.writeTmp('Completed GetTargetTable, returning '||targetTable);
1385   END IF;
1386   return targetTable;
1387   EXCEPTION WHEN OTHERS THEN
1388     g_error := sqlerrm;
1389     bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetTargetTable : '||g_error);
1390     raise;
1391 End;
1392 
1393 Function OriginTableHasTarget(p_table IN BSC_METADATA_OPTIMIZER_PKG.clsTable) return Boolean IS
1394   res Boolean;
1395   tableOri VARCHAR2(1000);
1396   l_res boolean :=false;
1397   i NUMBER;
1398   l_index NUMBER;
1399   l_origin_table DBMS_SQL.VARCHAR2_TABLE;
1400   l_dummy NUMBER;
1401 BEGIN
1402   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1403     bsc_mo_helper_pkg.writeTmp('Inside OriginTableHasTarget, p_table = ');
1404   END IF;
1405   l_dummy := BSC_MO_HELPER_PKG.decomposestring(p_table.originTable, ',', l_origin_table);
1406   i := l_origin_table.first;
1407   LOOP
1408     EXIT WHEN l_origin_table.count =0;
1409     tableOri := l_origin_table(i);
1410     l_res := True;
1411     l_index := BSC_MO_HELPER_PKG.findIndex(BSC_METADATA_OPTIMIZER_PKG.gTables, tableOri);
1412     If Not BSC_METADATA_OPTIMIZER_PKG.gTables(l_index).HasTargets Then
1413       IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1414         bsc_mo_helper_pkg.writeTmp('Compl OriginTableHasTarget, returning false');
1415       END IF;
1416       return false;
1417     END IF;
1418     EXIT WHEN i = l_origin_table.last;
1419     i := l_origin_table.next(i);
1420   END LOOP;
1421   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1422     bsc_mo_helper_pkg.writeTmp('Compl OriginTableHasTarget, returning '||bsc_mo_helper_pkg.boolean_decode(l_res));
1423   END IF;
1424   return l_res;
1425   EXCEPTION WHEN OTHERS THEN
1426     g_error := sqlerrm;
1427     bsc_mo_helper_pkg.TerminateWithMsg('Exception in OriginTableHasTarget : '||g_error);
1428     raise;
1429 End;
1430 
1431 --****************************************************************************
1432 --TableAlreadyVisited
1433 --
1434 --  DESCRIPTION:
1435 --     Return true if all origin tables are already been visited (They are
1436 --     in the array arrVisitedTables())
1437 --
1438 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1439 --***************************************************************************
1440 
1441 Function TableAlreadyVisited(p_table IN BSC_METADATA_OPTIMIZER_PKG.clsTable, arrVisitedTables in dbms_sql.varchar2_table,
1442 			 numVisitedTables in number) return Boolean is
1443   OriTable VARCHAR2(1000);
1444   i NUMBER;
1445   l_origin_table DBMS_SQL.VARCHAR2_TABLE;
1446   l_dummy NUMBER;
1447 BEGIN
1448 
1449   l_dummy := BSC_MO_HELPER_PKG.decomposestring(p_table.originTable, ',', l_origin_table);
1450   i := l_origin_table.first;
1451   LOOP
1452     EXIT WHEN l_origin_table.count=0;
1453     OriTable := l_origin_table(i);
1454     If Not BSC_MO_HELPER_PKG.searchStringExists(arrVisitedTables, numVisitedTables, OriTable) Then
1455       return false;
1456     END IF;
1457     EXIT WHEN i = l_origin_table.last;
1458     i := l_origin_table.next(i);
1459   END LOOP;
1460   return true;
1461   EXCEPTION WHEN OTHERS THEN
1462     g_error := sqlerrm;
1463     bsc_mo_helper_pkg.TerminateWithMsg('Exception in TableAlreadyVisited : '||g_error);
1464     raise;
1465 End;
1466 --****************************************************************************
1467 --ConnectTargetTables
1468 --  DESCRIPTION:
1469 --     Connect the target tables of the indicator to the summary tables of
1470 --     the indicator.
1471 --     Tables are already in collection gTablas
1472 --     Some of the target tables can be deleted from gTablas becuase
1473 --     are not used.
1474 --  PARAMETERS:
1475 --     Indicator: indicator
1476 --     Configuration: configuration
1477 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1478 --***************************************************************************
1479 PROCEDURE ConnectTargetTables(Indicator IN BSC_METADATA_OPTIMIZER_PKG.clsIndicator, Configuration IN NUMBER) IS
1480   arrVisitedTables dbms_sql.varchar2_table;
1481   numVisitedTables NUMBER;
1482   anyTableVisited  Boolean;
1483   l_table BSC_METADATA_OPTIMIZER_PKG.clsTable;
1484   targetTable varchar2(100);
1485   tableOri varchar2(100);
1486   i NUMBER;
1487   pt_name VARCHAR2(100);
1488   l_stmt VARCHAR2(1000);
1489   l_index1 NUMBER;
1490   l_next number;
1491 BEGIN
1492   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1493     bsc_mo_helper_pkg.writeTmp( 'In ConnectTargetTables, Configuration='||Configuration||', Indicator='||', System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, true);
1494   END IF;
1495   bsc_mo_helper_pkg.write_this(Indicator);
1496   numVisitedTables := 0;
1497   anyTableVisited := True;
1498   --BSC-MV Note: There is a special case in this Implementation with Targets at different
1499   --levels. When a table for targets merge into the summary table, we need to calculate
1500   --projection. That is the current logic. But the projection cannot be done in MV. Also
1501   --it cannot be done in base tables. For this special case we are going to create the
1502   --summary tables in the database and calculate the projection. Then iViewer needs to
1503   --read actuals and tagets from MV and projection from the summary table.
1504 
1505   --We need to visist the indicator tables in source-<target order
1506   --and connect the target table
1507   While anyTableVisited LOOP
1508     anyTableVisited := False;
1509     IF (BSC_METADATA_OPTIMIZER_PKG.gTables.count >0) THEN
1510       i := BSC_METADATA_OPTIMIZER_PKG.gTables.first;
1511     END IF;
1512     LOOP
1513       EXIT WHEN BSC_METADATA_OPTIMIZER_PKG.gTables.count=0;
1514       l_table := BSC_METADATA_OPTIMIZER_PKG.gTables(i);
1515       --Check only tables of the given indicator and configuration and are not target tables
1516       IF (l_table.Indicator = Indicator.Code) And (l_table.Configuration = Configuration) And
1517             (Not l_table.IsTargetTable) THEN
1518         --Check if the table has not already been visited
1519         IF Not BSC_MO_HELPER_PKG.searchStringExists(arrVisitedTables, numVisitedTables, l_table.Name) THEN
1520           IF TableAlreadyVisited(l_table, arrVisitedTables, numVisitedTables) THEN
1521             IF Not OriginTableHasTarget(l_table) THEN
1522               --If the origin table has targets then we do not need to
1523               --connect target table to this table
1524               targetTable := GetTargetTable(l_table);
1525               IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1526                 BSC_MO_HELPER_PKG.writeTmp('Target table is :' ||targetTable);
1527               END IF;
1528               IF targetTable IS NOT NULL THEN
1529                 IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1530                   BSC_MO_HELPER_PKG.writeTmp('assigning target table is');
1531                 END IF;
1532                 tableOri := targetTable;
1533                 IF (l_table.originTable1 IS NOT NULL) THEN
1534                   l_table.originTable1 := l_table.originTable1 ||',';
1535                 END IF;
1536                 l_table.originTable1 := l_table.originTable1||tableOri;
1537                 l_table.HasTargets := True;
1538                 l_index1 := bsc_mo_helper_pkg.findIndex(BSC_METADATA_OPTIMIZER_PKG.gTables, targetTable);
1539                 BSC_METADATA_OPTIMIZER_PKG.gTables(l_index1).UsedForTargets := True;
1540                 --BSC-MV Note: This table receives target. For that reason
1541                 --it needs to calculate projection. The projection table needs to be
1542                 --created in the database.
1543                 --Also configure iViewer to read projection from this table.
1544                 If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV and l_table.impl_type=1 Then
1545                   pt_name := GetProjectionTableName(l_table.name);
1546                   l_Table.projectionTable := pt_name;
1547                   UPDATE BSC_KPI_DATA_TABLES SET PROJECTION_SOURCE = 1,
1548                                     PROJECTION_DATA = pt_name
1549                                     WHERE INDICATOR = Indicator.code
1550                                     AND DIM_SET_ID = COnfiguration
1551                                     AND TABLE_NAME = l_table.name;
1552                 END IF;
1553               END IF;
1554             ELSE
1555               --If the origin table has targets then this table has targets
1556               l_table.HasTargets := True;
1557               --BSC-MV Note: This table does not receives direclty targets
1558               --but we need this table to maintain the projections
1559               --at higher levels. This table needs to be created in the database.
1560               --Also configure iViewer to read projection from this table.
1561               If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV and l_table.impl_type=1 Then
1562                 pt_name := GetProjectionTableName(l_Table.Name);
1563                 l_Table.projectionTable := pt_name;
1564                 UPDATE BSC_KPI_DATA_TABLES SET PROJECTION_SOURCE = 1,
1565                                 PROJECTION_DATA = pt_name
1566                                 WHERE INDICATOR = Indicator.code
1567                                 AND DIM_SET_ID = COnfiguration
1568                                 AND TABLE_NAME = l_table.name;
1569               End If;
1570             END IF;
1571             --Add the table to array of visited tables
1572             arrVisitedTables(numVisitedTables):= l_table.Name;
1573             numVisitedTables := numVisitedTables + 1;
1574             anyTableVisited := True;
1575           END IF;
1576         END IF;
1577         BSC_METADATA_OPTIMIZER_PKG.gTables(i) := l_table;
1578       END IF;
1579       EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gTables.last;
1580 	  i := BSC_METADATA_OPTIMIZER_PKG.gTables.next(i);
1581 	END LOOP;
1582   END LOOP;    -- END OF WHILE
1583   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1584     BSC_MO_HELPER_PKG.writeTmp('remove target tables not being used');
1585   END IF;
1586   --remove target tables not being used
1587   i := BSC_METADATA_OPTIMIZER_PKG.gTables.first;
1588   LOOP
1589     EXIT WHEN BSC_METADATA_OPTIMIZER_PKG.gTables.Count = 0;
1590     IF (BSC_METADATA_OPTIMIZER_PKG.gTables(i).Indicator = Indicator.Code) And (BSC_METADATA_OPTIMIZER_PKG.gTables(i).Configuration = Configuration) And
1591       BSC_METADATA_OPTIMIZER_PKG.gTables(i).IsTargetTable And (Not BSC_METADATA_OPTIMIZER_PKG.gTables(i).UsedForTargets) Then
1592       IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1593         BSC_MO_HELPER_PKG.writeTmp('1 Going to delete '||BSC_METADATA_OPTIMIZER_PKG.gTables(i).name);
1594       END IF;
1595       IF (i = BSC_METADATA_OPTIMIZER_PKG.gTables.last) THEN
1596         BSC_METADATA_OPTIMIZER_PKG.gTables.delete(i);
1597         EXIT;
1598       ELSE
1599         l_next := BSC_METADATA_OPTIMIZER_PKG.gTables.next(i);
1600         BSC_METADATA_OPTIMIZER_PKG.gTables.delete(i);
1601         i := -1;
1602       END IF;
1603     END IF;
1604     IF (i <> -1) THEN
1605       EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gTables.last;
1606       i := BSC_METADATA_OPTIMIZER_PKG.gTables.next(i);
1607     ELSE
1608       i := l_next;
1609     END IF;
1610   END LOOP;
1611   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1612     bsc_mo_helper_pkg.writeTmp( 'Done with ConnectTargetTables, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, true);
1613   END IF;
1614   EXCEPTION WHEN OTHERS THEN
1615 	g_error := sqlerrm;
1616 	bsc_mo_helper_pkg.TerminateWithMsg('Exception in ConnectTargetTables :' ||g_error);
1617 	raise;
1618 END;
1619 
1620 --****************************************************************************
1621 --GetKeyNum: GetNumeroLlave
1622 --  DESCRIPTION:
1623 --     Get the drill number corresponding to the given key
1624 --  PARAMETERS:
1625 --     p_dimension_families: collection of drill families
1626 --     NomLlave: key name
1627 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1628 --***************************************************************************
1629 Function GetKeyNum(p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels, NomkeyName IN VARCHAR2)
1630 return NUMBER IS
1631     Dril BSC_METADATA_OPTIMIZER_PKG.clsLevels;
1632     DimensionLevels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
1633     i NUMBER;
1634     j NUMBER;
1635     l_res NUMBER := -1;
1636     l_groups DBMS_SQL.NUMBER_TABLE;
1637     group_id NUMBER;
1638 
1639  BEGIN
1640 
1641     l_groups := BSC_MO_HELPER_PKG.getGroupIds(p_dimension_families);
1642 	i := l_groups.first;
1643 
1644 	LOOP
1645       EXIT WHEN l_groups.count = 0;
1646 	  DimensionLevels := BSC_MO_HELPER_PKG.get_Tab_clsLevels(p_dimension_families, i) ;
1647 	  j := DimensionLevels.first;
1648 	  LOOP
1649           EXIT WHEN DimensionLevels.count=0;
1650 		  Dril := DimensionLevels(j);
1651 	      If UPPER(Dril.keyName) = UPPER(NomkeyName) Then
1652                return Dril.Num;
1653           END IF;
1654 		  EXIT WHEN j = DimensionLevels.last;
1655 		  j := DimensionLevels.next(j);
1656 	  END LOOP;
1657 
1658 	  EXIT WHEN i = l_groups.last;
1659 	  i := l_groups.next(i);
1660     END LOOP;
1661 
1662     return l_res;
1663 
1664     EXCEPTION WHEN OTHERS THEN
1665         g_error := sqlerrm;
1666         bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetKeyNum : '||g_error);
1667         raise;
1668 End;
1669 
1670 --****************************************************************************
1671 --deduce_and_configure_s_tables : ConfigurarTablasIndicatorConfiguration
1672 --  DESCRIPTION:
1673 --     Deduce each one of the tables needed by the kpi in the given
1674 --     configuration.
1675 --     For this tables are added to the collection gTablas.
1676 --     Also configure metadata in order to the indicator reads from them.
1677 --  PARAMETERS:
1678 --     Indicator: indicator
1679 --     Configuration: configuration
1680 --     colBasicaTablas: collection of base tables
1681 --     colPeriodicidades: colection of periodicities
1682 --     p_dimension_families: collection of drill families
1683 --     forTargetLevel: true -Tables are for Targets
1684 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
1685 --***************************************************************************
1686 PROCEDURE deduce_and_configure_s_tables (Indicator IN BSC_METADATA_OPTIMIZER_PKG.clsIndicator,
1687                        Configuration IN NUMBER,
1688                        colSummaryTables IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable,
1689                        colPeriodicities IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsIndicPeriodicity,
1690                        p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
1691                        forTargetLevel IN Boolean)IS
1692 
1693   L_Periodicity BSC_METADATA_OPTIMIZER_PKG.clsIndicPeriodicity;
1694   L_Periodicity_Origin NUMBER;
1695   Basica BSC_METADATA_OPTIMIZER_PKG.clsBasicTable;
1696   L_Table BSC_METADATA_OPTIMIZER_PKG.clsTable;
1697   keyBasica BSC_METADATA_OPTIMIZER_PKG.clskeyField;
1698   key BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
1699   DatoBasica BSC_METADATA_OPTIMIZER_PKG.clsDataField;
1700   Dato BSC_METADATA_OPTIMIZER_PKG.clsDataField;
1701 
1702   l_stmt VARCHAR2(1000);
1703   cond   VARCHAR2(1000);
1704   CodPrimerDril NUMBER;
1705   msg VARCHAR2(1000);
1706   TableName VARCHAR2(1000);
1707   i NUMBER;
1708   j NUMBER;
1709   k NUMBER;
1710   l NUMBER;
1711 
1712   l_test NUMBER;
1713   basic_keys BSC_METADATA_OPTIMIZER_PKG.tab_clskeyField;
1714   basic_data BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
1715 
1716   table_keys BSC_METADATA_OPTIMIZER_PKG.tab_clskeyField;
1717   table_data BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
1718   TableLevel NUMBER;
1719   configKpiMV BSC_METADATA_OPTIMIZER_PKG.clsConfigKpiMV;
1720   colConfigKpiMV BSC_METADATA_OPTIMIZER_PKG.tab_clsConfigKpiMV;
1721   l_counter NUMBER;
1722   first_periodicity_id NUMBEr := 0;
1723 
1724   TYPE tab_clsKPIData IS TABLE OF BSC_KPI_DATA_TABLES%ROWTYPE index by binary_integer;
1725   l_kpidata_record BSC_KPI_DATA_TABLES%ROWTYPE ;
1726   l_tbl_kpidata tab_clsKPIData;
1727 BEGIN
1728   bsc_mo_helper_pkg.writeTmp( ' ');
1729   bsc_mo_helper_pkg.writeTmp( 'Inside deduce_and_configure_s_tables, Configuration = '||Configuration ||', forTargetLevel='
1730       ||bsc_mo_helper_pkg.boolean_decode(forTargetLevel)||', System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_procedure, false);
1731   --Delete from BSC_KPI_DATA_TABLES the records for this indicator and configuration
1732   If Not forTargetLevel Then
1733     --The tables are not for targets
1734     DELETE FROM BSC_KPI_DATA_TABLES WHERE INDICATOR = Indicator.Code
1735     AND DIM_SET_ID = Configuration;
1736   END IF;
1737   IF (colPeriodicities.count >0) THEN
1738     i := colPeriodicities.first;
1739   ELSE
1740     bsc_mo_helper_pkg.writeTmp( 'Compl. deduce_and_configure_s_tables, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_procedure, false);
1741 	return;
1742   END IF;
1743   LOOP
1744     L_Periodicity := colPeriodicities(i);
1745     IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1746       BSC_MO_HELPER_PKG.writeTmp('Periodicity = '||l_periodicity.code);
1747       BSC_MO_HELPER_PKG.writeTmp('---------------');
1748     END IF;
1749     If (Not forTargetLevel) Or (forTargetLevel And l_periodicity.TargetLevel = 1) Then
1750       If Indicator.OptimizationMode <> 0 Then
1751         --if the indicator is no-precalculated then it can have change of periodicity
1752         L_Periodicity_Origin := GetPeriodicityOrigin(colPeriodicities, L_Periodicity.Code, forTargetLevel);
1753       Else
1754         --the indicator is pre-calculated. All tables of the indicator will be base tables.
1755         L_Periodicity_Origin := -1;
1756       END IF;
1757       IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1758         BSC_MO_HELPER_PKG.writeTmp('L_Periodicity_Origin = '||L_Periodicity_Origin);
1759       END IF;
1760       j := colSummaryTables.first;
1761       LOOP
1762         EXIT WHEN colSummaryTables.count =0;
1763         L_Table := bsc_mo_helper_pkg.new_clsTable;
1764         Basica := colSummaryTables(j);
1765         IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
1766           bsc_mo_helper_pkg.writeTmp( 'Processing table '||Basica.name);
1767           bsc_mo_helper_pkg.write_this(Basica);
1768         END IF;
1769         --BSC Multiple Optimizers
1770         --basic_keys := BSC_MO_HELPER_PKG.getAllKeyFields(Basica.Name);
1771         --basic_data := BSC_MO_HELPER_PKG.getAllDataFields(Basica.Name);
1772         basic_keys := Basica.keys;
1773         basic_data := Basica.data;
1774         L_Table.Name := Basica.Name || '_'|| L_Periodicity.Code;
1775         L_Table.Type := 1;
1776         L_Table.Periodicity := L_Periodicity.Code;
1777         If L_Periodicity_Origin <> -1 And Basica.OriginTable IS NULL Then
1778           --The periodicity is originated from another one and
1779           --this table is not originated from another in the same periodicity
1780           --Keys
1781           k := basic_keys.first;
1782           LOOP
1783             EXIT WHEN basic_keys.count=0;
1784             keyBasica.keyName := null;
1785             keyBasica := basic_keys(k);
1786             key := bsc_mo_helper_pkg.new_clsKeyField;
1787             key.keyName := keyBasica.keyName;
1788             key.Origin := keyBasica.keyName;
1789             key.NeedsCode0 := keyBasica.NeedsCode0;
1790             --BSC-MV Note: In BSC-MV architecture we need to configure zero code
1791             --on all the tables needing zero code.
1792             If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
1793               key.CalculateCode0 := keyBasica.CalculateCode0;
1794             Else
1795               key.CalculateCode0 := False;
1796             End If;
1797             key.FilterViewName := keyBasica.FilterViewName;
1798             Table_keys(Table_keys.count) := key;
1799             EXIT WHEN k = basic_keys.last;
1800             k := basic_keys.next(k);
1801           END LOOP;
1802           --Data and L_TablesOri
1803           IF (L_Table.originTable IS NOT NULL) THEN
1804             L_Table.originTable := L_Table.originTable || ','||L_Table.originTable ||Basica.Name || '_'||  L_Periodicity_Origin;
1805           ELSE
1806             L_Table.originTable := L_Table.originTable ||Basica.Name || '_'||  L_Periodicity_Origin;
1807           END IF;
1808           k := basic_data.first;
1809           LOOP
1810             EXIT WHEN basic_data.count =0;
1811             DatoBasica := basic_data(k);
1812             If DatoBasica.AvgLFlag = 'Y' Then
1813               --Note: removed the name of the table as prefix of the column
1814               --I do not see that the same column could be in two origin tables.
1815               DatoBasica.Origin := GetFreeDivZeroExpression('SUM(' || DatoBasica.AvgLTotalColumn ||
1816                         ')/SUM(' || DatoBasica.AvgLCounterColumn || ')');
1817             Else
1818               DatoBasica.Origin := DatoBasica.aggFunction || '(' || DatoBasica.fieldName || ')';
1819             END IF;
1820             Table_Data(Table_Data.count) :=  DatoBasica ;
1821             EXIT WHEN k = basic_data.last;
1822             k := basic_data.next(k);
1823           END LOOP;
1824         Else
1825           --Keys
1826           k := basic_keys.first;
1827           table_keys := basic_keys;
1828           --Data and TablasOri
1829           If Basica.originTable IS NOT NULL Then
1830             --The table is originated from another indicator table
1831             --in the same periodicity
1832             IF (L_Table.originTable IS NOT NULL) THEN
1833               L_Table.originTable := L_Table.originTable||','||Basica.originTable || '_'|| L_Periodicity.Code;
1834             ELSE
1835               L_Table.originTable := Basica.originTable || '_'|| L_Periodicity.Code;
1836             END IF;
1837             k := basic_data.first;
1838             LOOP
1839               EXIT WHEN basic_data.count = 0;
1840               Dato := basic_data(k);
1841               If Dato.AvgLFlag = 'Y' Then
1842                 --Note: removed the name of the table as prefix of the column
1843                 --I do not see that the same column could be in two origin tables.
1844                 Dato.Origin := GetFreeDivZeroExpression('SUM(' ||
1845                 Dato.AvgLTotalColumn||')/SUM('||Dato.AvgLCounterColumn||')');
1846               Else
1847                 Dato.Origin := Dato.aggFunction|| '('|| Dato.fieldName || ')';
1848               END IF;
1849               Table_Data(Table_Data.count) := Dato;
1850               EXIT WHEN k = basic_data.last;
1851               k := basic_data.next(k);
1852             END LOOP;
1853           Else -- Basica.origile IS NULL
1854             --The table is not generated from another indicator table
1855             --This is a base table o the indicator.
1856             --We calculate average at lowest level and formula at lowest level
1857             --where the lowest level is the lowest level of the kpi.
1858             --No set L_Table.TablasOri, we do not know the name yet
1859             k :=basic_data.first;
1860             LOOP
1861               EXIT WHEN basic_data.count =0;
1862               Dato := basic_data(k);
1863               --Note: removed the name of the table as prefix of the column
1864               --I do not see that the same column could be in two origin tables.
1865               IF ( Dato.InternalColumnType=0) THEN
1866                 Dato.Origin := Dato.aggFunction|| '(' || Dato.fieldName || ')';
1867               ELSIF (Dato.InternalColumnType=1) THEN
1868                 Dato.Origin := GetFreeDivZeroExpression(Dato.aggFunction ||'(' || Dato.InternalColumnSource ||')');
1869               ELSIF (Dato.InternalColumnType=2) THEN
1870                 Dato.Origin := GetFreeDivZeroExpression('SUM(' ||Dato.InternalColumnSource || ')');
1871               ELSIF (Dato.InternalColumnType=3) THEN
1872                 Dato.Origin := GetFreeDivZeroExpression('COUNT('||Dato.InternalColumnSource || ')');
1873               END IF;
1874               IF (Table_Data.count>0) THEN
1875                 Table_Data(Table_Data.last+1) := Dato;
1876               ELSE
1877                 Table_Data(0) := Dato;
1878               END IF;
1879               EXIT WHEN k = basic_data.last;
1880               k := basic_data.next(k);
1881             END LOOP;
1882           END IF;--Basica.originTable IS NOT NULL
1883         END IF; --L_Periodicity_Origin <> -1
1884         --Indicator and configuration
1885         L_Table.Indicator := Indicator.Code;
1886         L_Table.Configuration := Configuration;
1887         L_Table.EDW_Flag := Indicator.EDW_Flag;
1888         L_Table.IsTargetTable := forTargetLevel;
1889         L_Table.HasTargets := False;
1890         L_Table.UsedForTargets := False;
1891         --BSC-MV Note: If we are in upgrade (sum level changes from NULL to NOTNULL)
1892         --and the indicator is in production the falg this table with upgradeFlag = 1
1893         If (BSC_METADATA_OPTIMIZER_PKG.g_Sum_Level_Change = 1) And (Indicator.Action_Flag <> 3) Then
1894           L_Table.upgradeFlag := 1;
1895         End If;
1896 
1897         L_Table.impl_type := g_current_indicator.Impl_Type;
1898         --Add the table to gTablas
1899         IF (BSC_METADATA_OPTIMIZER_PKG.gTables.count>0)THEN
1900           l_test := BSC_MO_HELPER_PKG.findIndex(BSC_METADATA_OPTIMIZER_PKG.gTables, L_Table.name);
1901           IF (l_test >0 ) THEN --corruption
1902             l_test := -1;
1903           END IF;
1904           BSC_MO_HELPER_PKG.addTable(L_Table, Table_Keys, Table_data, 'deduce_and_configure_s_tables');
1905         ELSE
1906           BSC_MO_HELPER_PKG.addTable(L_Table, Table_keys, Table_data, 'deduce_and_configure_s_tables');
1907         END IF;
1908         Table_keys.delete; -- cleanup
1909         Table_data.delete; -- cleanup
1910         --Configure metadata in order to the indicator read from this table
1911         If Not forTargetLevel Then
1912           --Tables for targets only are not read by the indicator
1913           If first_periodicity_id = 0 Then
1914             --This is the first periodicity. Only in this case we insert records
1915             --one by one in BSC_KPI_DATA_TABLES. For other periodicities
1916             --we will insert all the records with one query based on the records of this  periodicity
1917             cond := null;
1918             k := basic_keys.first;
1919             LOOP
1920               EXIT WHEN basic_keys.count = 0;
1921               keyBasica := basic_keys(k);
1922               If cond IS NULL Then
1923                 cond := 'D'|| GetKeyNum(p_dimension_families, keyBasica.keyName);
1924               Else
1925                 cond := cond || ', D' || GetKeyNum(p_dimension_families, keyBasica.keyName);
1926               END IF;
1927               EXIT when k = basic_keys.last;
1928               k := basic_keys.next(k);
1929             END LOOP;
1930             --EDW Note: For EDW KPIs we need to user the union view name in BSC_KPI_DATA_TABLES
1931             If L_Table.EDW_Flag = 1 Then
1932               TableName := L_Table.Name || BSC_METADATA_OPTIMIZER_PKG.EDW_UNION_VIEW_EXT;
1933             Else
1934               TableName := L_Table.Name;
1935             END IF;
1936             --BSC-MV Note: We need to configure one entry for each combination
1937             --of zero codes. If the level of the table is greater than
1938             --g_adv_sum_level then we configure a SQL statement else we
1939             --configure to read from the ZMV (MV for zero codes)
1940             If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
1941               IF (g_current_indicator.Impl_Type=2) THEN -- AW, so set tablelevel as 0
1942                 TableLevel := 0;
1943               ELSE
1944                 TableLevel := getTableLevel(Basica.Name, colSummaryTables);
1945               END IF;
1946               -- bug 3835059, we need to create sql stmts instead of mv if # of
1947               -- levels > BSC_METADATA_OPTIMIZER_PKG.MAX_ALLOWED_LEVELS
1948               colConfigKpiMV := GetColConfigKpiMV(Basica, TableLevel, p_dimension_families, colSummaryTables);
1949               l_stmt := 'INSERT INTO BSC_KPI_DATA_TABLES (INDICATOR, PERIODICITY_ID, DIM_SET_ID, LEVEL_COMB,
1950                           TABLE_NAME, FILTER_CONDITION, MV_NAME, PROJECTION_SOURCE, DATA_SOURCE, SQL_STMT, PROJECTION_DATA)
1951                           VALUES(:1, :2, :3, :4, :5, :6, :7, :8, :9, :10, :11)';
1952               l_counter := colConfigKpiMV.first;
1953               LOOP
1954                 EXIT WHEN colConfigKpiMV.count = 0;
1955                 configKpiMV := colConfigKpiMV (l_counter);
1956                 l_kpidata_record.INDICATOR := Indicator.Code;
1957                 l_kpidata_record.PERIODICITY_ID :=  L_Periodicity.Code;
1958                 l_kpidata_record.DIM_SET_ID := Configuration;
1959                 l_kpidata_record.LEVEL_COMB :=  configKpiMV.LevelComb;
1960                 l_kpidata_record.TABLE_NAME :=   TableName;
1961                 l_kpidata_record.FILTER_CONDITION := cond;
1962                 l_kpidata_record.MV_NAME := configKpiMV.MVName;
1963                 l_kpidata_record.PROJECTION_SOURCE := 0;
1964                 l_kpidata_record.DATA_SOURCE := configKpiMV.DataSource;
1965                 l_kpidata_record.SQL_STMT :=  configKpiMV.SqlStmt;
1966                 l_kpidata_record.PROJECTION_DATA := null;
1967                 l_tbl_kpidata(l_tbl_kpidata.count+1):= l_kpidata_record;
1968                 /*Execute IMMEDIATE l_stmt USING
1969                               Indicator.Code , L_Periodicity.Code, Configuration, configKpiMV.LevelComb, TableName , cond,
1970                               configKpiMV.MVName, 0,  configKpiMV.DataSource, configKpiMV.SqlStmt, '';*/
1971                 EXIT WHEN l_counter = colConfigKpiMV.last;
1972                 l_counter := colConfigKpiMV.next(l_counter);
1973               END LOOP;
1974             Else
1975               l_kpidata_record.INDICATOR := Indicator.Code;
1976                 l_kpidata_record.PERIODICITY_ID :=  L_Periodicity.Code;
1977                 l_kpidata_record.DIM_SET_ID := Configuration;
1978                 l_kpidata_record.LEVEL_COMB :=  nvl(Basica.levelConfig, '?');
1979                 l_kpidata_record.TABLE_NAME :=   TableName;
1980                 l_kpidata_record.FILTER_CONDITION := cond;
1981                 l_kpidata_record.MV_NAME := null;
1982                 l_kpidata_record.PROJECTION_SOURCE := null;
1983                 l_kpidata_record.DATA_SOURCE := null;
1984                 l_kpidata_record.SQL_STMT :=  null;
1985                 l_kpidata_record.PROJECTION_DATA := null;
1986                 l_tbl_kpidata(l_tbl_kpidata.count+1):= l_kpidata_record;
1987                 /*INSERT INTO BSC_KPI_DATA_TABLES
1988                         (INDICATOR, PERIODICITY_ID, DIM_SET_ID,
1989                         LEVEL_COMB, TABLE_NAME, FILTER_CONDITION)
1990                         VALUES(Indicator.Code,  L_Periodicity.Code, Configuration,
1991                         nvl(Basica.levelConfig, '?'), TableName, cond);*/
1992             End If;
1993           End If;
1994         End If;
1995         EXIT WHEN j = colSummaryTables.last;
1996         j := colSummaryTables.next(j);
1997       END LOOP;
1998       FORALL ii IN 1..l_tbl_kpidata.count
1999         INSERT INTO BSC_KPI_DATA_TABLES values l_tbl_kpidata(ii);
2000       l_tbl_kpidata.delete;
2001       --BSC_KPI_DATA_TABLES was already configured for the fisrt periodicity
2002       --For this periodcity we can insert same set of records based on the first
2003       --periodicity so we avoid to do one by one again
2004       --3135168
2005       If Not forTargetLevel Then
2006         If first_periodicity_id <> 0 Then
2007           INSERT INTO BSC_KPI_DATA_TABLES
2008                   (INDICATOR, PERIODICITY_ID, DIM_SET_ID, LEVEL_COMB,
2009                   TABLE_NAME, FILTER_CONDITION, MV_NAME, PROJECTION_SOURCE,
2010                   DATA_SOURCE, SQL_STMT, PROJECTION_DATA)
2011                   SELECT INDICATOR, L_Periodicity.Code , DIM_SET_ID, LEVEL_COMB,
2012                   SUBSTR(TABLE_NAME,1,INSTR(TABLE_NAME, '_', -1))||L_Periodicity.Code TABLE_NAME,
2013                   FILTER_CONDITION, MV_NAME, PROJECTION_SOURCE, DATA_SOURCE, SQL_STMT, PROJECTION_DATA
2014                   FROM BSC_KPI_DATA_TABLES
2015                   WHERE INDICATOR = Indicator.Code
2016                   AND PERIODICITY_ID = first_periodicity_id
2017                   AND DIM_SET_ID = Configuration;
2018         Else
2019           first_periodicity_id := L_Periodicity.Code;
2020         End If;
2021       End If;
2022     END IF;
2023     EXIT WHEN i = colPeriodicities.last;
2024     i := colPeriodicities.next(i);
2025   END LOOP;
2026   bsc_mo_helper_pkg.writeTmp( 'Compl. deduce_and_configure_s_tables, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_procedure, false);
2027 
2028   EXCEPTION WHEN OTHERS THEN
2029   l_stmt := sqlerrm;
2030   bsc_mo_helper_pkg.writeTmp( 'exception in deduce_and_configure_s_tables:'||l_stmt, FND_LOG.LEVEL_UNEXPECTED, true);
2031   fnd_message.set_name('BSC', 'BSC_KPICONFIG_SYSTABLES_FAILED');
2032 	fnd_message.set_token('INDICATOR', Indicator.code);
2033   fnd_message.set_token('DIMENSION_SET', Configuration);
2034   g_error := fnd_message.get;
2035   bsc_mo_helper_pkg.terminatewithMsg(g_error);
2036   raise;
2037 
2038 End ;
2039 
2040 
2041 --****************************************************************************
2042 --GetKeyOrigin : GetLlaveOrigen
2043 --  DESCRIPTION:
2044 --   Return the name of the key where the given key is originated from, within
2045 --   the given list of keys.
2046 --   We know that the key is originated from one of them.
2047 --
2048 --  PARAMETERS:
2049 --   keyNameOri: collection of keys
2050 --   Llave: key name
2051 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2052 --***************************************************************************
2053 Function GetKeyOrigin(keyNamesOri IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField, keyName IN VARCHAR2) return VARCHAR2 IS
2054   keyNameOri BSC_METADATA_OPTIMIZER_PKG.clskeyField;
2055   i NUMBER;
2056   l_index1 number;
2057   l_index2 number;
2058 
2059 BEGIN
2060 
2061   --First check if the same key exists in the list of origin keys
2062   IF (keyNamesOri.count= 0) THEN
2063      return null;
2064   END IF;
2065 	i := keyNamesOri.first;
2066 
2067   LOOP
2068        keyNameOri :=  keyNamesOri(i);
2069        If Upper(keyNameOri.keyName) = Upper(keyName) Then
2070           return keyNameOri.keyName;
2071        END IF;
2072 	     EXIT WHEN i = keyNamesOri.last;
2073 	     i := keyNamesOri.next(i);
2074    END LOOP;
2075 
2076   --If it was not found, It looks a parent.
2077   i := keyNamesOri.first;
2078   LOOP
2079   	   keyNameOri := keyNamesOri(i);
2080 
2081   	   l_index1 := BSC_MO_HELPER_PKG.findKeyIndex(BSC_METADATA_OPTIMIZER_PKG.gMasterTable, keyNameOri.keyName);
2082    	   l_index2 := BSC_MO_HELPER_PKG.findKeyIndex(BSC_METADATA_OPTIMIZER_PKG.gMasterTable, keyName);
2083        If (l_index1>=0 AND l_index2>=0 AND
2084           IndexRelation1N(BSC_METADATA_OPTIMIZER_PKG.gMasterTable(l_index1).Name,
2085                    BSC_METADATA_OPTIMIZER_PKG.gMasterTable(l_index2).Name) >= 0 ) Then
2086           return keyNameOri.keyName;
2087        END IF;
2088 	     EXIT WHEN i = keyNamesOri.last;
2089 	     i:= keyNamesOri.next(i);
2090   END LOOP;
2091 
2092   return null;
2093   EXCEPTION WHEN OTHERS THEN
2094       g_error := sqlerrm;
2095       bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetKeyOrigin : '||g_error);
2096       raise;
2097 End;
2098 
2099 
2100 --***************************************************************************
2101 -- keyOriginExists: SePuedeOriginarLlaves
2102 --  DESCRIPTION:
2103 --   Returns TRUE if the list of keys in LlavesDest can be originated
2104 --   from the list of drill in LlavesOri.
2105 --   This is possible if all keys in the target can be originated from
2106 --   'some key in the source and only one change of dissagregation
2107 --
2108 --   Bug 2911828: Also need to see if the keys belong to the same family
2109 --   within the kpi. For that reason we are passing p_dimension_families
2110 --  PARAMETERS:
2111 --   LlavesDest: target keys collection
2112 --   LlavesOri: source keys collection
2113 --
2114 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2115 --***************************************************************************
2116 
2117 Function keyOriginExists(keyNameDest IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField,
2118                 keyNameOri IN BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField,
2119           p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels) return Boolean IS
2120   DrilOri BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
2121   DrilDest BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
2122   numChanges NUMBER;
2123   originExists boolean;
2124   FamilyIndex number;
2125   i NUMBER;
2126   j NUMBER;
2127   k NUMBER;
2128   l_index1 NUMBER;
2129   l_index2 NUMBER;
2130 BEGIN
2131   --Bug#3361564 08-JAN-2004 Metadata is creating a loop between summary tables
2132   -- in some cases with MN relations.
2133   -- We can enforce a rule where a table with x number of dimensions never
2134   -- can be generated from a table with less number of dimensions
2135   If keyNameOri.Count < keyNameDest.Count Then
2136     return false;
2137   End If;
2138   numChanges := 0;
2139   IF (keyNameDest.count > 0) THEN
2140     i := keyNameDest.first;
2141   END IF;
2142   LOOP
2143     EXIT WHEN keyNameDest.count =0;
2144     DrilDest := keyNameDest(i);
2145     originExists := False;
2146     FamilyIndex := FindDimensionGroupIndexForKey(p_dimension_families, DrilDest.keyName);
2147     IF (keyNameOri.count>0) THEN
2148       j := keyNameOri.first;
2149       LOOP
2150         DrilOri := keyNameOri(j);
2151         If Upper(DrilDest.keyName) = Upper(DrilOri.keyName) Then
2152           originExists := True;
2153           Exit;
2154         END IF;
2155         If FindDimensionGroupIndexForKey(p_dimension_families, DrilOri.keyName) = FamilyIndex Then
2156           --Both keys origin and target belong to the same familiy of drill within the kpi.
2157           l_index1 := BSC_MO_HELPER_PKG.findKeyindex(BSC_METADATA_OPTIMIZER_PKG.gMasterTable, DrilOri.keyName);
2158       	  l_index2 := BSC_MO_HELPER_PKG.findKeyindex(BSC_METADATA_OPTIMIZER_PKG.gMasterTable, DrilDest.keyName);
2159           If IndexRelation1N(BSC_METADATA_OPTIMIZER_PKG.gMasterTable(l_index1).Name ,
2160                        BSC_METADATA_OPTIMIZER_PKG.gMasterTable(l_index2).Name) >= 0 Then
2161             originExists := True;
2162             numChanges := numChanges + 1;
2163             Exit;
2164           END IF;
2165         END IF;
2166 	    EXIT WHEN j = keyNameOri.last;
2167 	    j := keyNameOri.next(j);
2168       END LOOP;
2169 	END IF;
2170     If Not originExists Then
2171       return false;
2172     END IF;
2173 	EXIT WHEN i = keyNameDest.last;
2174 	i := keyNameDest.next(i);
2175   END LOOP;
2176   If numChanges > 1 Then
2177     return False;
2178   Else
2179      return true;
2180   END IF;
2181   EXCEPTION WHEN OTHERS THEN
2182     g_error := sqlerrm;
2183     bsc_mo_helper_pkg.TerminateWithMsg('Exception in keyOriginExists : '||g_error);
2184     raise;
2185 End ;
2186 
2187 --****************************************************************************
2188 --DeduceInternalGraph
2189 --  DESCRIPTION:
2190 --     Deduce the internal tables tree of the indicator.
2191 --
2192 --  PARAMETERS:
2193 --     colSummaryTables: base tables collection
2194 --
2195 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2196 --***************************************************************************
2197 PROCEDURE DeduceInternalGraph(
2198   colSummaryTables IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable,
2199   p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
2200   forTargetLevel IN Boolean) IS
2201   l_s_table BSC_METADATA_OPTIMIZER_PKG.clsBasicTable;
2202   Basica1 BSC_METADATA_OPTIMIZER_PKG.clsBasicTable;
2203   keyName BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
2204   originExists Boolean;
2205   i NUMBER;
2206   j NUMBER;
2207   k NUMBER;
2208   l_index NUMBER;
2209   l_s_table_keys BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
2210   l_s_table_measures BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
2211   Basic1_keys BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
2212   Basic1_data BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
2213 
2214 BEGIN
2215 
2216   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2217     bsc_mo_helper_pkg.writeTmp(' ');
2218     bsc_mo_helper_pkg.writeTmp('Inside DeduceInternalGraph, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, true);
2219     bsc_mo_helper_pkg.writeTmp('  colSummaryTables is as above', FND_LOG.LEVEL_STATEMENT);
2220   END IF;
2221   IF (colSummaryTables.count >0) THEN
2222     i := colSummaryTables.first;
2223   END IF;
2224   LOOP
2225     EXIT WHEN colSummaryTables.count=0;
2226     l_s_table := colSummaryTables(i);
2227     l_s_table_keys := l_s_table.keys;
2228     l_s_table_measures := l_s_table.data;
2229     --For each base table, look if it possible to be originated from any other table
2230     originExists := False;
2231     j := colSummaryTables.first;
2232     LOOP
2233       Basica1 := colSummaryTables(j);
2234       --different than itself
2235       If Basica1.Name <> l_s_table.Name Then
2236         Basic1_keys := Basica1.keys;
2237         Basic1_data := Basica1.data;
2238         If keyOriginExists(l_s_table_keys, Basic1_keys, p_dimension_families) Then
2239           IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2240             bsc_mo_helper_pkg.writeTmp( ' ');
2241           END IF;
2242           --l_s_table can be originated from Basica1
2243           --For each key assign the properties Origen and CalcularCod0
2244           IF (l_s_table_keys.count > 0) THEN
2245              k := l_s_table_keys.first;
2246              LOOP
2247                keyName := l_s_table_keys(k);
2248                IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2249                   bsc_mo_helper_pkg.writeTmp( 'Processing key');
2250                   bsc_mo_helper_pkg.write_this(keyName);
2251                END IF;
2252                --assign the origin field with the name of the key where it is originated from.
2253                keyName.Origin := GetKeyOrigin(Basic1_keys, keyName.keyName);
2254                --BSC-MV Note: In BSC-MV architecture we need to configure zero code
2255                --on all the tables needing zero code.
2256                --Tables for targets only there is no need to calculate zero code.
2257                If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
2258                  --BSC-MV/V Architecture
2259                  If Not forTargetLevel Then
2260                    If keyName.NeedsCode0 Then
2261                      keyName.CalculateCode0 := True;
2262                    End If;
2263                  End If;
2264                ELSE
2265                  --Table architecture
2266                  --If there is key change and the key needs code 0 then CalculateCode0 = True
2267                  IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2268                    bsc_mo_helper_pkg.writeTmp( 'Table architecture, keyName.Origin='||
2269                      keyName.Origin||', keyName.keyName='||keyName.keyName);
2270                  END IF;
2271                  If Upper(keyName.Origin) <> UPPER(keyName.keyName) Then
2272                    If keyName.NeedsCode0  Then
2273                      IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2274                        bsc_mo_helper_pkg.writeTmp('1 Switching CalculateCode0 to TRUE for table '||
2275                          l_s_table.name||', key='||keyName.keyName);
2276                      END IF;
2277                      keyName.calculateCode0 := True;
2278                    End If;
2279                  Else
2280                    --If there is no key change and needs code 0 but the origin
2281                    --key does not need code 0 then CalcularCod0 = true
2282                    If keyName.NeedsCode0 Then
2283                      l_index := BSC_MO_HELPER_PKG.findindex(Basic1_keys, keyName.Origin);
2284                      IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2285                        bsc_mo_helper_pkg.writeTmp( 'l_index = '||l_index||', Basic1_keys('||l_index||') = ');
2286                        bsc_mo_helper_pkg.write_this(Basic1_Keys(l_index));
2287                      END IF;
2288                      If L_INDEX>=0 THEN
2289                        IF   (Basic1_keys(l_index).NeedsCode0) Then
2290                          null;
2291                        ELSE
2292                          IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2293                            bsc_mo_helper_pkg.writeTmp('2 Switching CalculateCode0 to TRUE for table '||l_s_table.name||', key='||keyName.keyName);
2294                          END IF;
2295                          keyName.calculateCode0 := True;
2296                        END IF;
2297                      End If;
2298                    End If;
2299                  End If;
2300                END IF;
2301                l_s_table_keys(k) := keyName ;
2302                EXIT WHEN k =l_s_table_keys.last;
2303                k := l_s_table_keys.next(k);
2304              END LOOP;
2305              -- will delete and insert keys
2306              --BSC Multiple Optimizers
2307              --BSC_MO_HELPER_PKG.insertKeys(l_s_table.name, l_s_table_keys);
2308              l_s_table.keys := l_s_table_keys;
2309            END IF;
2310            --assign the property TablaOri with the name of the origin table
2311            l_s_table.originTable := Basica1.Name;
2312            originExists := True;
2313            Exit;
2314          END IF;
2315        END IF;
2316        EXIT WHEN j = colSummaryTables.last;
2317        j := colSummaryTables.next(j);
2318      END LOOP;
2319      If Not originExists Then
2320        IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2321          bsc_mo_helper_pkg.writeTmp('It was not possible to generate the table from another one.');
2322        END IF;
2323        --It was not possible to generate the table from another one.
2324        --For each key, assign the properties Origen and CalcularCod0
2325        IF (l_s_table_keys.count>0) THEN
2326          j := l_s_table_keys.first;
2327          LOOP
2328            keyName := l_s_table_keys(j);
2329            --Leave the field Origen in ''
2330           IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2331             bsc_mo_helper_pkg.writeTmp( 'Processing key');
2332             bsc_mo_helper_pkg.write_this(keyName);
2333           END IF;
2334           If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
2335             --BSC-MV Note: In this architecture
2336             -- No zero code needed in tables for targets
2337             If Not forTargetLevel Then
2338               --If the key needs code 0 then CalcularCod0 = True
2339               If keyName.NeedsCode0 Then
2340               	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2341                   bsc_mo_helper_pkg.writeTmp('3 Switching CalculateCode0 to TRUE for table '||l_s_table.name||', key='||keyName.keyName);
2342                	END IF;
2343                 keyName.calculateCode0 := True;
2344               End If;
2345             End If;
2346           Else
2347             --If the key needs code 0 then CalcularCod0 = True
2348             If keyName.NeedsCode0 Then
2349               keyName.CalculateCode0 := True;
2350               IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2351                 bsc_mo_helper_pkg.writeTmp('4 Switching CalculateCode0 to TRUE for table '||l_s_table.name||', key='||keyName.keyName);
2352               END IF;
2353             END IF;
2354           END IF;
2355           l_s_table_keys(j) := keyName;
2356         EXIT WHEN j = l_s_table_keys.last;
2357         j :=  l_s_table_keys.next(j);
2358    	  END LOOP;
2359       -- will delete and insert keys
2360       --BSC Multiple Optimizers
2361       --BSC_MO_HELPER_PKG.insertKeys(l_s_table.name, l_s_table_keys);
2362       l_s_table.keys := l_s_table_keys;
2363     END IF;
2364     --leave the property TablaOri in ''
2365   END IF;
2366 
2367     IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2368       bsc_mo_helper_pkg.writeTmp( ' ');
2369     END IF;
2370     colSummaryTables(i) := l_s_table;
2371     EXIT WHEN i = colSummaryTables.last;
2372     i := colSummaryTables.next(i);
2373   END LOOP;
2374 
2375 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2376       bsc_mo_helper_pkg.writeTmp('Completed DeduceInternalGraph, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, true);
2377       bsc_mo_helper_pkg.writeTmp('  colSummaryTables is ', FND_LOG.LEVEL_STATEMENT);
2378       bsc_mo_helper_pkg.write_this(colSummaryTables);
2379 	END IF;
2380 
2381     EXCEPTION WHEN OTHERS THEN
2382     g_error := sqlerrm;
2383     bsc_mo_helper_pkg.TerminateWithMsg('Exception in DeduceInternalGraph : '||g_error);
2384     fnd_message.set_name('BSC', 'BSC_REL_DEDUCTION_FAILED');
2385     app_exception.raise_exception;
2386 End;
2387 
2388 
2389 
2390 --****************************************************************************
2391 --  order_level_string
2392 --  DESCRIPTION:
2393 --     Order the string of levels configuration.
2394 --     Example:
2395 --       ConfDriles = '?0?0'
2396 --       Looking into p_dimension_families we know that the string
2397 --       of level configuration is in this order: 0,2,1,3
2398 --       This function returns the character in the right order
2399 --       0,1,2,3 --> '??00'
2400 --
2401 --  PARAMETERS:
2402 --     ConfDriles: drills configuration
2403 --     p_dimension_families: collection of drill families of the indicator
2404 --
2405 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2406 --***************************************************************************
2407 Function order_level_string(p_level_string IN VARCHAR2,
2408 p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels) return VARCHAR2
2409 IS
2410   arrOrdenDrilesActual  dbms_sql.number_table;
2411   arrOrdenDriles      dbms_sql.number_table;
2412   arrConfDriles       dbms_sql.varchar2_table;
2413   numDriles           NUMBER;
2414   i               NUMBER;
2415   j               NUMBER;
2416   temp              NUMBER;
2417   l_ordered_level_string       varchar2(1000);
2418   tempC             varchar2(1000);
2419   DimLevels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
2420   l_groups DBMS_SQL.NUMBER_TABLE;
2421   l_group_id NUMBER;
2422 
2423 BEGIN
2424 
2425   l_groups := bsc_mo_helper_pkg.getGroupIds(p_dimension_families);
2426   numDriles := 0;
2427   For i IN 0..l_groups.Count-1 loop
2428     DimLevels := bsc_mo_helper_pkg.get_tab_clsLevels(p_dimension_families, l_groups(i));
2429     For j IN 0..DimLevels.Count-1  LOOP
2430       arrOrdenDrilesActual(numDriles) := DimLevels(j).Num;
2431       arrOrdenDriles(numDriles) := DimLevels(j).Num;
2432       arrConfDriles(numDriles) := Trim(substr(p_level_string, numDriles + 1, 1));
2433       numDriles := numDriles + 1;
2434     END LOOP;
2435   END LOOP;
2436 
2437   --order arrOrdenDriles() and arrConfDriles()
2438   For i in 0..numDriles - 1 LOOP
2439     For j in i + 1.. numDriles - 1 LOOP
2440       If arrOrdenDriles(i) > arrOrdenDriles(j) Then
2441         temp := arrOrdenDriles(i);
2442         arrOrdenDriles(i) := arrOrdenDriles(j);
2443         arrOrdenDriles(j) := temp;
2444         tempC := arrConfDriles(i);
2445         arrConfDriles(i) := arrConfDriles(j);
2446         arrConfDriles(j) := tempC;
2447       END IF;
2448     END LOOP;
2449   END LOOP;
2450 
2451   l_ordered_level_string := null;
2452   For i in 0..numDriles - 1 LOOP
2453     l_ordered_level_string := l_ordered_level_string || arrConfDriles(i);
2454   END LOOP;
2455   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2456     bsc_mo_helper_pkg.writeTmp( 'Done with order_level_string, returning '||l_ordered_level_string, FND_LOG.LEVEL_PROCEDURE);
2457   END IF;
2458 
2459   return l_ordered_level_string;
2460 
2461   EXCEPTION WHEN OTHERS THEN
2462   g_error := sqlerrm;
2463   bsc_mo_helper_pkg.TerminateWithMsg('Exception in order_level_string : '||g_error);
2464 	RAISE;
2465 End;
2466 
2467 
2468 
2469 --****************************************************************************
2470 --  GetFilterViewName
2471 --
2472 --  DESCRIPTION:
2473 --     Returns the name of the filter view for the given indicator,
2474 --     configuration and key
2475 --
2476 --  PARAMETERS:
2477 --     Indicator: indicator code
2478 --     Configuration: configuration
2479 --     CampoLlave: key name
2480 --
2481 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2482 --***************************************************************************
2483 Function GetFilterViewName(Indicator IN NUMBER, Configuration IN NUMBER, CampoLlave IN VARCHAR2) return VARCHAR2 IS
2484   l_stmt varchar2(1000);
2485   l_return varchar2(1000) := null;
2486   cv CurTyp;
2487   CURSOR cLevelViewName (pIndicator IN NUMBER, pConfiguration IN NUMBER, pKeyCol IN VARCHAR2) IS
2488   SELECT LEVEL_VIEW_NAME FROM BSC_KPI_DIM_LEVELS_B
2489   WHERE INDICATOR = pIndicator
2490   AND DIM_SET_ID = pConfiguration
2491   AND LEVEL_PK_COL = pKeyCol;
2492 BEGIN
2493 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2494       bsc_mo_helper_pkg.writeTmp( 'Inside GetFilterViewName, Indicator='||Indicator||', Configuration='||Configuration
2495        ||', CampoLlave='||CampoLlave , FND_LOG.LEVEL_PROCEDURE);
2496    	END IF;
2497 
2498 
2499 	OPEN cLevelViewName(Indicator, Configuration, upper(CampoLlave));
2500 	FETCH cLevelViewName INTO l_return;
2501 	CLOSE cLevelViewName;
2502 
2503 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2504       bsc_mo_helper_pkg.writeTmp( 'Completed GetFilterViewName, returning '||l_return, FND_LOG.LEVEL_PROCEDURE);
2505 	END IF;
2506 
2507 	return l_return;
2508 
2509   EXCEPTION WHEN OTHERS THEN
2510   g_error := sqlerrm;
2511   bsc_mo_helper_pkg.TerminateWithMsg('Exception in GetFilterViewName : '||g_error);
2512 	RAISE;
2513 
2514 End ;
2515 
2516 
2517 
2518 --****************************************************************************
2519 --  IsIndicatorPnL
2520 --  DESCRIPTION:
2521 --     Return TRUE if the indicator is type PnL
2522 --  PARAMETERS:
2523 --     Ind: Indicator code
2524 --
2525 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2526 --***************************************************************************
2527 Function IsIndicatorPnL(Ind IN Integer, pUseGIndics boolean) return Boolean IS
2528 l_index NUMBER;
2529 l_indicator BSC_METADATA_OPTIMIZER_PKG.clsIndicator;
2530 BEGIN
2531 
2532 	if (pUseGIndics) then
2533  	  l_index := BSC_MO_HELPER_PKG.findindex(BSC_METADATA_OPTIMIZER_PKG.gIndicators, Ind);
2534  	  l_indicator := BSC_METADATA_OPTIMIZER_PKG.gIndicators(l_index);
2535   else
2536     l_index := BSC_MO_HELPER_PKG.findindex(BSC_MO_DOC_PKG.gDocIndicators, Ind);
2537     l_indicator := BSC_MO_DOC_PKG.gDocIndicators(l_index);
2538   end if;
2539 
2540   If l_indicator.IndicatorType = 1 And l_indicator.ConfigType = 3 Then
2541       return true;
2542   Else
2543       return false;
2544   END IF;
2545 
2546   EXCEPTION WHEN OTHERS THEN
2547   g_error := sqlerrm;
2548   bsc_mo_helper_pkg.TerminateWithMsg('Exception in IsIndicatorPnL for '||Ind||' : '||g_error);
2549 	RAISE;
2550 
2551 End;
2552 
2553 --****************************************************************************
2554 --  EsIndicatorBalance
2555 --
2556 --  DESCRIPTION:
2557 --     Returns TRUE is the indicator is type Balance
2558 --
2559 --  PARAMETERS:
2560 --     Ind: Indicator code
2561 --
2562 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2563 --***************************************************************************
2564 Function IsIndicatorBalance(Ind IN NUMBER, pUseGIndics boolean) return Boolean IS
2565 l_index NUMBER;
2566 l_indicator BSC_METADATA_OPTIMIZER_PKG.clsIndicator;
2567 BEGIN
2568 
2569 	if (pUseGIndics) then
2570     l_index := BSC_MO_HELPER_PKG.findindex(BSC_METADATA_OPTIMIZER_PKG.gIndicators, Ind);
2571     l_indicator := BSC_METADATA_OPTIMIZER_PKG.gIndicators(l_index);
2572   else
2573     l_index := BSC_MO_HELPER_PKG.findindex(BSC_MO_DOC_PKG.gDocIndicators, Ind);
2574     l_indicator := BSC_MO_DOC_PKG.gDocIndicators(l_index);
2575   end if;
2576 
2577   If l_indicator.IndicatorType = 1 And l_indicator.ConfigType = 2 Then
2578       return true;
2579   Else
2580 	   return false;
2581   END IF;
2582   EXCEPTION WHEN OTHERS THEN
2583   g_error := sqlerrm;
2584   bsc_mo_helper_pkg.TerminateWithMsg('Exception in IsIndicatorBalance for '||ind||' : '||g_error);
2585 	RAISE;
2586 End;
2587 
2588 --****************************************************************************
2589 --  IsIndicatorBalanceOrPnL : EsIndicatorBalanceoPyg
2590 --
2591 --  DESCRIPTION:
2592 --     Return TRUE if the indicator is type Balance or PnL
2593 --
2594 --  PARAMETERS:
2595 --     Ind: indicator code
2596 --
2597 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2598 --***************************************************************************
2599 Function IsIndicatorBalanceOrPnL(Ind IN Integer, pUseGIndics boolean)  return Boolean IS
2600 Begin
2601   If IsIndicatorBalance(Ind, pUseGIndics) Or IsIndicatorPnL(Ind, pUseGIndics) Then
2602 	   return true;
2603   Else
2604 	   return false;
2605   END IF;
2606 
2607   EXCEPTION WHEN OTHERS THEN
2608   g_error := sqlerrm;
2609   bsc_mo_helper_pkg.TerminateWithMsg('Exception in IsIndicatorBalanceOrPnL for '||ind||' : '||g_error);
2610 	RAISE;
2611 
2612 End;
2613 
2614 --****************************************************************************
2615 --  CopyOfColDataColumns
2616 --
2617 --  DESCRIPTION:
2618 --     Returns a copy of the given data columns collection
2619 --     colDataColumns is collection of object of class clsDataField
2620 --
2621 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2622 --***************************************************************************
2623 Function CopyOfColDataColumns(colDataColumns IN BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField)
2624 return BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField IS
2625 Begin
2626 	return colDataColumns;
2627 End ;
2628 
2629 
2630 --****************************************************************************
2631 --  CalcCartesianProduct : CalcProdCartesiano
2632 --
2633 --  DESCRIPTION:
2634 --     Calculate in the multidimensional array p_cartesian_product() all points
2635 --     of a n-dimensional space. The number of dimensions is given in the
2636 --     perameter p_num_dimensions.
2637 --     The number of intervals in the dimension i is in the array
2638 --     dimensionSizes(i)
2639 --     Example: If p_num_dimensions = 3 and dimensionSizes = |3|2|1|
2640 --     p_cartesian_product = |1|1|1|
2641 --               |1|2|1|
2642 --                |2|1|1|
2643 --                |2|2|1|
2644 --                |3|1|1|
2645 --                |3|2|1|
2646 --     Note: The intervals in the dimension i are enumerated from 1 to
2647 --     dimensionSizes(i). It does not include 0.
2648 --
2649 --  PARAMETERS:
2650 --     p_cartesian_product(): Matrix to initialize.
2651 --     p_num_dimensions: Number of dimensions
2652 --     dimensionSizes(): Array with the size of each dimension
2653 --
2654 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2655 --***************************************************************************
2656 
2657 
2658 PROCEDURE CalcCartesianProduct(p_cartesian_product IN OUT NOCOPY  DBMS_SQL.NUMBER_TABLE,
2659                    p_num_dimensions IN Integer,
2660                    dimensionSizes IN OUT NOCOPY DBMS_SQL.NUMBER_TABLE) IS
2661 
2662   l_num_tables NUMBER;
2663   iTimes NUMBER;
2664   l_repeat_count NUMBER;
2665   iRow NUMBER;
2666 BEGIN
2667 
2668   If p_num_dimensions = 0 Then
2669       return;
2670   END IF;
2671   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2672     bsc_mo_helper_pkg.writeTmp( 'Inside CalcCartesianProduct, p_num_dimensions='||p_num_dimensions||' p_cartesian_product is ');
2673     bsc_mo_helper_pkg.write_this(p_cartesian_product, FND_LOG.LEVEL_STATEMENT);
2674     bsc_mo_helper_pkg.writeTmp( 'dimensionSizes is ', FND_LOG.LEVEL_STATEMENT);
2675     bsc_mo_helper_pkg.write_this(dimensionSizes, FND_LOG.LEVEL_STATEMENT);
2676   END IF;
2677 
2678   l_num_tables := 1;
2679   For i in  0..p_num_dimensions - 1 LOOP
2680       l_num_tables := l_num_tables * dimensionSizes(i);
2681   END LOOP;
2682 
2683 
2684   iTimes := 1;
2685   l_repeat_count := l_num_tables;
2686   For i in  0..p_num_dimensions - 1 LOOP
2687       iRow := 0;
2688       l_repeat_count := floor(l_repeat_count / dimensionSizes(i));
2689       For iIterations in 1.. iTimes LOOP
2690         For iPoints IN  1..dimensionSizes(i) LOOP
2691           For iRepeat in 1..l_repeat_count LOOP
2692               p_cartesian_product(i*l_num_tables+iRow) := iPoints;
2693               iRow := iRow + 1;
2694           END LOOP;
2695         END LOOP;
2696       END LOOP;
2697       iTimes := iTimes * dimensionSizes(i);
2698 
2699   END LOOP;
2700 
2701 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2702       bsc_mo_helper_pkg.writeTmp( 'Compl. CalcCartesianProduct, Cartesian product is ', FND_LOG.LEVEL_PROCEDURE);
2703       bsc_mo_helper_pkg.write_this(p_cartesian_product, FND_LOG.LEVEL_STATEMENT);
2704       bsc_mo_helper_pkg.writeTmp( 'dimensionSizes is ', FND_LOG.LEVEL_STATEMENT);
2705       bsc_mo_helper_pkg.write_this(dimensionSizes, FND_LOG.LEVEL_STATEMENT);
2706 	END IF;
2707 
2708   EXCEPTION WHEN OTHERS THEN
2709   g_error := sqlerrm;
2710   bsc_mo_helper_pkg.TerminateWithMsg('Exception in CalcCartesianProduct '||g_error);
2711 	RAISE;
2712 
2713 End ;
2714 
2715 FUNCTION getRecursiveDimensions return VARCHAR2 IS
2716 l_dim_list bsc_varchar2_table_type;
2717 l_num_dim_list number := 0;
2718 l_error varchar2(1000);
2719 BEGIN
2720   bsc_olap_main.get_list_of_rec_dim(l_dim_list, l_num_dim_list, l_error);
2721   gRecDims := null;
2722   for i in 1..l_num_dim_list loop
2723     gRecDims := gRecDims||''''||l_dim_list(i)||'''';
2724     if (i <> l_num_dim_list) then
2725       gRecDims := gRecDims ||',';
2726     end if;
2727   end loop;
2728   return gRecDims;
2729   EXCEPTION when others then
2730   g_error := sqlerrm;
2731   bsc_mo_helper_pkg.TerminateWithMsg('Exception in getRecursiveDimensions');
2732   RAISE;
2733 END;
2734 
2735 FUNCTION IsRecursiveKey(pIndicator IN NUMBER, pKey IN VARCHAR2) return BOOLEAN IS
2736 l_stmt VARCHAR2(1000);
2737 l_temp VARCHAR2(1000);
2738 cv CurTyp;
2739 l_num number;
2740 BEGIN
2741   IF (gRecDims IS NULL) THEN
2742     gRecDims := getRecursiveDimensions;
2743   END IF;
2744   l_stmt := 'select 1 from bsc_kpi_dim_levels_b where indicator =:1
2745 	and level_pk_col = :2
2746 	and level_table_name in	(
2747 	select level_table_name  from bsc_sys_dim_levels_b
2748 	where short_name in ('|| gRecDims||')
2749            or dim_level_id in
2750               (select dim_level_id from bsc_sys_dim_level_rels
2751                 where dim_level_id = parent_dim_level_id))
2752         ';
2753 
2754   OPEN CV for l_stmt using pIndicator, pKey;
2755   FETCH CV INTO l_num;
2756   IF (CV%FOUND) THEN -- this is a recursive key
2757     CLOSE CV;
2758     bsc_mo_helper_pkg.writeTmp(pKey||' is a recursive key..', FND_LOG.LEVEL_STATEMENT, false);
2759     return true;
2760   END IF;
2761   CLOSE CV;
2762   return false;
2763   EXCEPTION when others then
2764   g_error := sqlerrm;
2765   bsc_mo_helper_pkg.TerminateWithMsg('Exception in isRecursiveKey for Indicator='||pIndicator||', key='||pKey||':'||g_error);
2766   RAISE;
2767 END;
2768 
2769 --****************************************************************************
2770 --GetBasicTables : GetColBasicaTablas
2771 --
2772 --  DESCRIPTION:
2773 --   Generates the collection of base tables of the indicator.
2774 --   This collection is of objects of class clsBasicaTablas
2775 --
2776 --  PARAMETERS:
2777 --   Indicator: indicator code
2778 --   Configuration: configuration
2779 --   colDimLevelCombinations: collection of combinations of drill families
2780 --   p_dimension_families: collection of families of drills of the indicator
2781 --   forTargetLevel: true  -The procedure is called to get base tables for targets
2782 --   colDataColumns: collection of data columns
2783 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
2784 --***************************************************************************
2785 Function GetBasicTables(Indicator IN  BSC_METADATA_OPTIMIZER_PKG.clsIndicator, Configuration IN NUMBER,
2786                    colDimLevelCombinations IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevelCombinations,
2787                    p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
2788                    forTargetLevel IN Boolean,
2789                    colDataColumns IN BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField)
2790                    RETURN BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable IS
2791 
2792   colBasicaTablas  BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable;
2793   Basica BSC_METADATA_OPTIMIZER_PKG.clsBasicTable;
2794   Basic_keys BSC_METADATA_OPTIMIZER_PKG.tab_clsKeyField;
2795   Basic_data BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
2796 
2797   CampoLlave BSC_METADATA_OPTIMIZER_PKG.clsKeyField;
2798   p_cartesian_product DBMS_SQL.NUMBER_TABLE;
2799 
2800   NumDimensions NUMBER;
2801   NumLevels NUMBER;
2802   dimensionSizes dbms_sql.number_table;
2803   idimension NUMBER;
2804   i NUMBER;
2805   j NUMBER;
2806 
2807   l_index1 NUMBER;
2808   l_index2 NUMBER;
2809 
2810   iPoints NUMBER;
2811   lstCodsDriles varchar2(1000);
2812   cLevel varchar2(1000);
2813   ConfDriles varchar2(1000);
2814   NumFamilias NUMBER;
2815   ifamilia NUMBER;
2816   Dril BSC_METADATA_OPTIMIZER_PKG.clsLevels;
2817   Dril1 BSC_METADATA_OPTIMIZER_PKG.clsLevels;
2818   msg varchar2(1000);
2819   TableNameStart varchar2(1000);
2820   l_temp NUMBER;
2821   l_tempv VARCHAR2(100);
2822 
2823   l_groups DBMS_SQL.NUMBER_TABLE;
2824   l_group_id NUMBER;
2825   l_drillCombination BSC_METADATA_OPTIMIZER_PKG.tab_clsLevelCombinations;
2826   l_drillCombination2 BSC_METADATA_OPTIMIZER_PKG.tab_clsLevelCombinations;
2827 
2828   l_drillString VARCHAR2(4000);
2829   l_drillTable DBMS_SQL.VARCHAR2_TABLE;
2830 
2831   l_level_groups DBMS_SQL.NUMBER_TABLE;
2832   l_level_group_id NUMBER;
2833   l_dimLevels  BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
2834 
2835 BEGIN
2836   l_groups := BSC_MO_HELPER_PKG.getGroupIDs(colDimLevelCombinations);
2837   l_level_groups := BSC_MO_HELPER_PKG.getGroupIDs(p_dimension_families);
2838   NumDimensions := l_groups.count;
2839   bsc_mo_helper_pkg.writeTmp( 'Inside GetBasicTables, Configuration ='||Configuration||', forTargetLevel ='
2840         ||bsc_mo_helper_pkg.boolean_decode(forTargetLevel ) ||', System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_PROCEDURE, FALSE);
2841   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2842 	bsc_mo_helper_pkg.writeTmp( 'Indicator is ');
2843     bsc_mo_helper_pkg.write_this(Indicator);
2844     bsc_mo_helper_pkg.writeTmp( 'colDimLevelCombinations is as above');
2845     bsc_mo_helper_pkg.writeTmp( 'p_dimension_families is as above');
2846     bsc_mo_helper_pkg.writeTmp( 'colDataColumns is as above');
2847   END IF;
2848   If forTargetLevel Then
2849     TableNameStart := 'BSC_SB_';
2850   Else
2851     TableNameStart := 'BSC_S_';
2852   END IF;
2853 
2854 
2855   If NumDimensions = 0 Then
2856     --The indicator does not have dimensions. It does not have any level.
2857     --Only one table
2858     --Name
2859     Basica := BSC_MO_HELPER_PKG.new_clsBasicTable;
2860     Basica.Name := TableNameStart || Indicator.Code || '_'||  Configuration || '_'|| '0';
2861     --Keys
2862     --It does not have. The table only has YEAR TYPE PERIOD
2863     --Confdriles is  ''
2864     --TablaOri is ''
2865     IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2866       bsc_mo_helper_pkg.writeTmp('  ');
2867       bsc_mo_helper_pkg.writeTmp('Adding colBasicaTablas, Basica is ');
2868       bsc_mo_helper_pkg.write_this(Basica);
2869     END IF;
2870     Basica.keys := Basic_keys;
2871     Basica.data := colDataColumns;
2872     --BSC_MO_HELPER_PKG.insertBasicTable(Basica, Basic_keys, colDataColumns);
2873     colBasicaTablas(colBasicaTablas.count) := Basica;
2874   Else
2875     --The indicator has at least one dimension
2876     --Calculate the cartesian product between the combinations of each dimension level
2877     NumLevels := 0;
2878     For i in 0..NumDimensions-1 LOOP
2879       l_drillCombination := BSC_MO_HELPER_PKG.get_tab_clsLevelCombinations(colDimLevelCombinations, l_groups(i));
2880       dimensionSizes(i) := l_drillCombination.Count;
2881       If NumLevels = 0 Then
2882         NumLevels := dimensionSizes(i);
2883       Else
2884         NumLevels := NumLevels * dimensionSizes(i);
2885       END IF;
2886     END LOOP;
2887     CalcCartesianProduct( p_cartesian_product, NumDimensions, dimensionSizes );
2888     --One table for each element of the cartesian product
2889     For iPoints in 0..NumLevels - 1        LOOP
2890       --Keys
2891       --Add level from each dimension
2892       lstCodsDriles := null;
2893       ConfDriles := null;
2894       Basica := BSC_MO_HELPER_PKG.new_clsBasicTable;
2895       Basic_keys.delete;
2896       For idimension IN 0..NumDimensions - 1 LOOP
2897         l_index1 := to_number(p_cartesian_product(idimension*NumLevels + iPoints))-1;
2898         l_drillCombination := BSC_MO_HELPER_PKG.get_tab_clsLevelCombinations(colDimLevelCombinations, l_groups(idimension));
2899         l_drillString := l_drillCombination(l_index1).Levels;
2900         l_drillTable := bsc_mo_helper_pkg.getDecomposedString(l_drillString, ',');
2901         j := l_drillTable.first;
2902         l_tempv :=null;
2903         LOOP
2904           EXIT WHEN l_drillTable.count = 0;
2905           cLevel := l_drillTable(j);
2906           CampoLlave := bsc_mo_helper_pkg.new_clsKeyField;
2907           CampoLlave.keyName := cLevel;
2908           --NecesitaCod0
2909           --If the level is the first one in the dimension
2910           --is unique in the combination --> true
2911           IF l_DrillTable.Count = 1 Then
2912             l_dimLevels := bsc_mo_helper_pkg.get_tab_clsLevels(p_dimension_families, l_groups(idimension));
2913             If UPPER(l_dimLevels(0).keyName) = UPPER(cLevel)
2914               -- AND (NOT IsRecursiveKey(Indicator.code, cLevel))
2915               Then
2916               --If the indicator is a Balance or PnL:
2917               --If the drill is the account drill (the first drill of the first family) then we dont need to calculate zero code
2918               If IsIndicatorBalanceOrPnL(Indicator.Code, true) And idimension = 0 Then
2919                 CampoLlave.NeedsCode0 := False;
2920               Else
2921                 CampoLlave.NeedsCode0 := True;
2922               END IF;
2923             Else
2924               CampoLlave.NeedsCode0 := False;
2925             END IF;
2926           END IF;
2927           --CalcularCod0 is false
2928           CampoLlave.CalculateCode0 := False;
2929           --FilterViewName
2930           If Indicator.OptimizationMode <> 0 Then
2931             --non pre-calculated
2932             CampoLlave.FilterViewName := null;
2933           Else
2934             --pre-calculated
2935             CampoLlave.FilterViewName := GetFilterViewName(Indicator.Code, Configuration, CampoLlave.keyName);
2936           END IF;
2937           --BSC-MV Note: Need this property to store the index of dimension
2938           --within the kpi
2939           l_dimLevels := bsc_mo_helper_pkg.get_tab_clsLevels(p_dimension_families, l_groups(idimension));
2940           CampoLlave.dimIndex := l_dimLevels(bsc_mo_helper_pkg.findIndex(l_dimLevels,  CampoLlave.keyName)).Num;
2941           --Add the key to the list of keys of the base table
2942           Basic_keys(Basic_keys.count) := CampoLlave;
2943           l_temp := BSC_MO_HELPER_PKG.findIndex(l_dimLevels, CampoLlave.keyName);
2944           lstCodsDriles := lstCodsDriles || l_dimLevels(l_temp).Num;
2945           EXIT WHEN j = l_drillTable.last;
2946           j:= l_drillTable.next(j);
2947         END LOOP;
2948         ConfDriles := ConfDriles || l_drillCombination(l_index1).levelConfig;
2949       END LOOP;
2950       --Name
2951       --Bug 3108495 If the indicator has several dimensions (more that 10 independent) the
2952       --name of the table results too long
2953       Basica.Name := TableNameStart || Indicator.Code || '_' || Configuration || '_' || iPoints;
2954       IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2955         bsc_mo_helper_pkg.writeTmp( ' ');
2956         bsc_mo_helper_pkg.writeTmp( ' ');
2957       END IF;
2958       --ConfDriles
2959       Basica.levelConfig := order_level_string(ConfDriles, p_dimension_families);
2960       --Put ? at the begining in case the indicator is Balance or PnL because the drill 0
2961       --is the Type of Account drill
2962       If IsIndicatorBalanceOrPnL(Indicator.Code, true) Then
2963         Basica.levelConfig := '?'|| Basica.levelConfig;
2964       END IF;
2965       --TablaOri
2966       --TablaOri is ''
2967       Basica.keys := Basic_Keys;
2968       Basica.Data := colDataColumns;
2969       colBasicaTablas(colBasicaTablas.count) := Basica;
2970       --BSC_MO_HELPER_PKG.insertBasicTable(Basica, Basic_Keys, colDataColumns);
2971     END LOOP;
2972   END IF;
2973   bsc_mo_helper_pkg.writeTmp( 'Compl GetBasicTables, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_procedure, false);
2974   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
2975 	  bsc_mo_helper_pkg.writeTmp( 'Returning colBasicaTablas as ');
2976       bsc_mo_helper_pkg.write_this(colBasicaTablas);
2977   END IF;
2978   return colBasicaTablas;
2979 
2980   EXCEPTION WHEN OTHERS THEN
2981   bsc_mo_helper_pkg.TerminateWithError('BSC_BASICTABLE_DEDUCT_FAILED');
2982   fnd_message.set_name('BSC', 'BSC_BASICTABLE_DEDUCT_FAILED');
2983 	fnd_message.set_token('INDICATOR', Indicator.code);
2984   fnd_message.set_token('DIMENSION_SET', Configuration);
2985 
2986   app_exception.raise_exception;
2987 
2988 
2989 End;
2990 
2991 
2992 
2993 --****************************************************************************
2994 --InsertDataColumnInDBMeasureCols
2995 --
2996 --  DESCRIPTION:
2997 --   Creates the record for the internal column in BSC_DB_MEASURE_COLS_TL
2998 --
2999 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3000 --***************************************************************************
3001 PROCEDURE  InsertInDBMeasureCols(p_measure IN BSC_METADATA_OPTIMIZER_PKG.clsMeasureLOV) IS
3002 
3003 l_stmt VARCHAR2(1000);
3004 i NUMBER;
3005 
3006 BEGIN
3007 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3008    bsc_mo_helper_pkg.writeTmp( 'Inside InsertInDBMeasureCols, p_measure = ');
3009 	END IF;
3010 
3011    bsc_mo_helper_pkg.write_this(p_measure);
3012   --Delete the records if exists
3013   l_stmt := 'DELETE FROM BSC_DB_MEASURE_COLS_TL WHERE MEASURE_COL = :1';
3014   EXECUTE IMMEDIATE l_stmt using p_measure.fieldName;
3015 
3016   --Because it is a TL table, we need to insert the record for every supported language
3017   i := BSC_METADATA_OPTIMIZER_PKG.gInstalled_Languages.first;
3018 
3019   LOOP
3020       EXIT WHEN BSC_METADATA_OPTIMIZER_PKG.gInstalled_Languages.count = 0;
3021       INSERT INTO BSC_DB_MEASURE_COLS_TL (
3022       	  MEASURE_COL, LANGUAGE, SOURCE_LANG,
3023         HELP, MEASURE_GROUP_ID, PROJECTION_ID, MEASURE_TYPE)
3024 		VALUES (p_measure.fieldName, BSC_METADATA_OPTIMIZER_PKG.gInstalled_Languages(i),  BSC_METADATA_OPTIMIZER_PKG.gLangCode,
3025 			 p_measure.Description, p_measure.groupCode, p_measure.prjMethod,p_measure.measureType );
3026       EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gInstalled_Languages.last;
3027       i := BSC_METADATA_OPTIMIZER_PKG.gInstalled_Languages.next(i);
3028   END LOOP;
3029 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3030   bsc_mo_helper_pkg.writeTmp( 'Compl. InsertInDBMeasureCols');
3031 	END IF;
3032 
3033 
3034   EXCEPTION WHEN OTHERS THEN
3035   g_error := sqlerrm;
3036   BSC_MO_HELPER_PKG.TerminateWithMsg('Exception in InsertInDBMeasureCols '||g_error);
3037 	RAISE;
3038 
3039 End;
3040 
3041 
3042 --****************************************************************************
3043 --AddInternalColumnInDB
3044 --
3045 --  DESCRIPTION:
3046 --   Creates the record for the internal column in BSC_DB_MEASURE_COLS_TL
3047 --   and also added to the collection gLov.
3048 --   Projection method and type (balance or statistic) are deduced from
3049 --   the base columns.
3050 --
3051 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3052 --***************************************************************************
3053 PROCEDURE AddInternalColumnInDB(internalColumn IN VARCHAR2, InternalColumnType NUMBER,
3054                   baseColumns IN dbms_sql.varchar2_table , numBaseColumns IN NUMBER) IS
3055   l_measure BSC_METADATA_OPTIMIZER_PKG.clsMeasureLOV;
3056   i NUMBER;
3057   prjMethod NUMBER;
3058   l_temp number;
3059 BEGIN
3060 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3061       bsc_mo_helper_pkg.writeTmp( 'Inside AddInternalColumnInDB, internalColumn='||internalColumn
3062         ||', InternalColumnType='||InternalColumnType||', numBaseColumns='||numBaseColumns||' baseColumns=');
3063       bsc_mo_helper_pkg.write_this(baseColumns);
3064 	END IF;
3065 
3066   l_measure.fieldName := internalColumn;
3067   l_measure.source := 'BSC';
3068   l_temp := bsc_mo_helper_pkg.findIndex(BSC_METADATA_OPTIMIZER_PKG.gLov, baseColumns(baseColumns.first), 'BSC');
3069 
3070   l_measure.groupCode := BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).groupCode;
3071   l_measure.Description :=  BSC_MO_HELPER_PKG.Get_LookUp_Value('BSC_UI_BACKEND', 'INTERNAL_COLUMN');
3072 
3073   IF (InternalColumnType =1) THEN
3074         --Formula
3075         --The projection method of the calculated column is deduced from the
3076         --projection method of the operands:
3077         --If the projection method for one of the operands is 'No forecast'
3078         --then the projection method for the calculated column is 'No forecast'
3079         --Else, If the projection method of one of the operands is 'Custom' then:
3080         --If the projection method of one of the operands is 'Plan-based' then
3081         --the projection method of the calculated column is 'Plan-based'
3082         --Else, the projection method is 'Moving Average'
3083         --Else, if the projection method of one of the operands is 'Plan-based' then
3084         --the projection method of the calculated column is 'Plan-based'.
3085         --Else, the projection method of the calculated column is 'Moving Average'
3086         --Projection methods:
3087         --0: No Forecast
3088         --1: Moving Averge
3089         --3: Plan-Based
3090         --4: Custom
3091         l_measure.prjMethod := 1; --Moving average has the lowest priority
3092         i := baseColumns.first;
3093         LOOP
3094           EXIT WHEN baseColumns.count = 0;
3095           l_temp := bsc_mo_helper_pkg.findIndex(BSC_METADATA_OPTIMIZER_PKG.gLov, baseColumns(i), 'BSC');
3096           prjMethod := BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).prjMethod;
3097           If prjMethod = 0 Then
3098               --No forecast
3099               l_measure.prjMethod := 0;
3100               EXIT;
3101           END IF;
3102 
3103           If prjMethod = 3 Then
3104               --Plan-Based
3105               l_measure.prjMethod := 3;
3106           Else
3107               --Moving Average of Custom
3108               If l_measure.prjMethod <> 3 Then
3109                 l_measure.prjMethod := 1;
3110               END IF;
3111           END IF;
3112           EXIT WHEN i = baseColumns.last;
3113           i := baseColumns.next(i);
3114         END LOOP;
3115 
3116         --The type of the calculated column (Balance or Statistics) is
3117         --deduced from the type of the operands. If at least one of the operands
3118         --is Balance Type, then the calculated column is Balance.
3119         --Measure types:
3120         --1: Statistic
3121         --2: Balance
3122         i := baseColumns.first;
3123         LOOP
3124           EXIT WHEN baseColumns.count = 0;
3125           l_temp := bsc_mo_helper_pkg.findIndex(BSC_METADATA_OPTIMIZER_PKG.gLov, baseColumns(i), 'BSC');
3126           l_measure.measureType := BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).measureType;
3127           If l_measure.measureType = 2 Then
3128               EXIT;
3129           END IF;
3130           EXIT WHEN i = baseColumns.last;
3131           i := baseColumns.next(i);
3132         END LOOP;
3133   ELSIF (InternalColumnType=2 OR InternalColumnType=3) THEN
3134         --Total and counter for Average at Lowest Level
3135 
3136         --Projection method and type are the same of the base column
3137         --In this case there is only one base column
3138         l_temp := bsc_mo_helper_pkg.findIndex(BSC_METADATA_OPTIMIZER_PKG.gLov, baseColumns(baseColumns.first), 'BSC');
3139         l_measure.prjMethod := BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).prjMethod;
3140         l_measure.measureType := BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).measureType;
3141   END IF;
3142 
3143   If Not FieldExistsInLoV(internalColumn, 'BSC') Then
3144       IF (BSC_METADATA_OPTIMIZER_PKG.gLov.count>0) THEN
3145         BSC_METADATA_OPTIMIZER_PKG.gLov(BSC_METADATA_OPTIMIZER_PKG.gLov.last+1) := l_measure;
3146       ELSE
3147         BSC_METADATA_OPTIMIZER_PKG.gLov(0) := l_measure;
3148       END IF;
3149   Else
3150       --Update the filed with the new information
3151       l_temp := bsc_mo_helper_pkg.findIndex(BSC_METADATA_OPTIMIZER_PKG.gLov, internalColumn, 'BSC');
3152       BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).groupCode := l_measure.groupCode;
3153       BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).Description := l_measure.Description;
3154       BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).measureType := l_measure.measureType;
3155       BSC_METADATA_OPTIMIZER_PKG.gLov(l_temp).prjMethod := l_measure.prjMethod;
3156   END IF;
3157 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3158       bsc_mo_helper_pkg.writeTmp( 'Going to InsertInDBMeasureCols');
3159 	END IF;
3160 
3161   InsertInDBMeasureCols( l_measure);
3162 
3163 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3164       bsc_mo_helper_pkg.writeTmp( 'Compl AddInternalColumnInDB');
3165 	END IF;
3166 
3167 
3168   EXCEPTION WHEN OTHERS THEN
3169       g_error := sqlerrm;
3170       BSC_MO_HELPER_PKG.TerminateWithMsg('Exception in AddInternalColumnInDB : '||g_error||', l_temp='||l_temp||', baseColumns(baseColumns.first)='||baseColumns(baseColumns.first)||' list of values is ');
3171     BSC_MO_HELPER_PKG.write_this(BSC_METADATA_OPTIMIZER_PKG.gLov, FND_LOG.LEVEL_EXCEPTION, true);
3172       raise;
3173 End;
3174 
3175 
3176 
3177 --****************************************************************************
3178 --SetMeasurePropertyDB
3179 --  DESCRIPTION:
3180 --   Update the given proeprty of the meaaure in the column
3181 --   S_COLOR_FORMULA of BSC_SYS_MEAURES
3182 --   given data column
3183 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3184 --***************************************************************************
3185 
3186 PROCEDURE SetMeasurePropertyDB(dataColumn IN VARCHAR2, propertyName IN VARCHAR2, propertyValue IN VARCHAR2)
3187 IS
3188    l_stmt VARCHAR2(1000);
3189 
3190 BEGIN
3191   UPDATE BSC_SYS_MEASURES
3192 	SET S_COLOR_FORMULA = BSC_APPS.SET_PROPERTY_VALUE(S_COLOR_FORMULA, propertyName, propertyValue)
3193 	WHERE UPPER(MEASURE_COL) =  upper(dataColumn)
3194 	AND TYPE = 0 AND NVL(SOURCE, 'BSC') = 'BSC';
3195 
3196   EXCEPTION WHEN OTHERS THEN
3197       g_error := sqlerrm;
3198       BSC_MO_HELPER_PKG.TerminateWithMsg('Exception in SetMeasurePropertyDB : '||g_error);
3199       raise;
3200 End;
3201 
3202 
3203 
3204 --***************************************************************************
3205 --GetAgregFunction : GetAggregateFunction
3206 --  DESCRIPTION:
3207 --   Returns in FuncAgreg and pAvgL the aggregation function of the
3208 --   given data column
3209 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3210 --***************************************************************************
3211 PROCEDURE GetAggregateFunction(dataColumn IN VARCHAR2, FuncAgreg IN OUT NOCOPY VARCHAR2, pAvgL IN OUT NOCOPY VARCHAR2,
3212               AvgLTotalColumn IN OUT NOCOPY VARCHAR2, AvgLCounterColumn IN OUT NOCOPY VARCHAR2) IS
3213 
3214   l_stmt VARCHAR2(1000);
3215   aggFunction VARCHAR2(1000);
3216 CURSOR C1(p1 VARCHAR2, p2 VARCHAR2, p3 VARCHAR2, p4 VARCHAR2) IS
3217 SELECT NVL(OPERATION, 'SUM') AS OPER,
3218  NVL(BSC_APPS.GET_PROPERTY_VALUE(S_COLOR_FORMULA, p1),'N') AS PAVGL,
3219  BSC_APPS.GET_PROPERTY_VALUE(S_COLOR_FORMULA, p2) AS PAVGLTOTAL,
3220  BSC_APPS.GET_PROPERTY_VALUE(S_COLOR_FORMULA, p3) AS PAVGLCOUNTER
3221  FROM BSC_SYS_MEASURES
3222  WHERE UPPER(MEASURE_COL) = UPPER(p4)
3223  AND TYPE = 0
3224  AND NVL(SOURCE, 'BSC') = 'BSC';
3225 
3226 cRow c1%ROWTYPE;
3227 
3228 BEGIN
3229   OPEN c1(BSC_METADATA_OPTIMIZER_PKG.C_PAVGL,
3230 		BSC_METADATA_OPTIMIZER_PKG.C_PAVGLTOTAL,
3231 		BSC_METADATA_OPTIMIZER_PKG.C_PAVGLCOUNTER,
3232 		dataColumn);
3233   FETCH c1 INto cRow;
3234   If c1%NOTFOUND Then
3235       FuncAgreg := null;
3236       pAvgL := null;
3237       AvgLTotalColumn := null;
3238       AvgLCounterColumn := null;
3239   Else
3240       FuncAgreg := cRow.OPER;
3241       pAvgL := cRow.PAVGL;
3242       AvgLTotalColumn := null;
3243       If (crow.PAVGLTOTAL is not null) Then
3244         AvgLTotalColumn := cRow.PAVGLTOTAL;
3245       END IF;
3246       AvgLCounterColumn := null;
3247       If (cRow.PAVGLCOUNTER IS NOT NULL) Then
3248         AvgLCounterColumn := cRow.PAVGLCOUNTER;
3249       END IF;
3250   END IF;
3251   close c1;
3252 
3253   EXCEPTION WHEN OTHERS THEN
3254   g_error := sqlerrm;
3255   BSC_MO_HELPER_PKG.TerminateWithMsg('Exception in GetAggregateFunction '||g_error);
3256 	RAISE;
3257 
3258 End;
3259 
3260 --***************************************************************************
3261 --getNextInternalColumnName
3262 --  DESCRIPTION:
3263 --   Returns the next Internal Column Name
3264 --   BSCIC<next value from sequence BSC_INTERNAL_COLUMN_S>
3265 --
3266 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3267 --***************************************************************************
3268 Function getNextInternalColumnName RETURN VARCHAR2 IS
3269 l_seq NUMBER;
3270 
3271 
3272 BEGIN
3273   SELECT BSC_INTERNAL_COLUMN_S.NEXTVAL INTO l_seq FROM DUAL;
3274 	return 'BSCIC'||l_seq;
3275 End;
3276 
3277 --****************************************************************************
3278 --DataFieldExists : ExisteCampoDato
3279 --  DESCRIPTION:
3280 --   Returns TRUE if the field exist in the collection. The collection
3281 --   if of objects of class clsDataField
3282 --
3283 --  PARAMETERS:
3284 --   colMeasures: collection
3285 --   measure: field name
3286 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3287 --***************************************************************************
3288 Function dataFieldExists(colMeasures IN BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField, measure IN VARCHAR2)
3289 RETURN BOOLEAN IS
3290   l_measure BSC_METADATA_OPTIMIZER_PKG.clsDataField;
3291   i NUMBER;
3292 
3293 BEGIn
3294 
3295   IF colMeasures.count = 0 THEN
3296       return FALSE;
3297   END IF;
3298   i := colMeasures.first;
3299   LOOP
3300 	   l_measure := colMeasures(i);
3301      If (UPPER(l_measure.fieldName) = UPPER(measure)) Then
3302 		  return true;
3303      END IF;
3304 	   EXIT WHEN i = colMeasures.last;
3305 	   i := colMeasures.next(i);
3306   END LOOP;
3307   return false;
3308 
3309   EXCEPTION WHEN OTHERS THEN
3310       g_error := sqlerrm;
3311       BSC_MO_HELPER_PKG.TerminateWithMsg('Exception dataFieldExists, '||g_error);
3312       raise;
3313 End;
3314 
3315 --****************************************************************************
3316 --DataFieldExists : ExisteCampoDato
3317 --  DESCRIPTION:
3318 --   Returns TRUE if the field exist in the collection. The collection
3319 --   if of objects of class clsCampoDatos
3320 --
3321 --  PARAMETERS:
3322 --   colMeasures: collection
3323 --   measure: field name
3324 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3325 --***************************************************************************
3326 Function dataFieldExistsForSource(colMeasures IN BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField,
3327   measure IN VARCHAR2,
3328   p_source IN VARCHAR2
3329   )
3330 RETURN BOOLEAN IS
3331   l_measure BSC_METADATA_OPTIMIZER_PKG.clsDataField;
3332   i NUMBER;
3333 BEGIn
3334   IF colMeasures.count = 0 THEN
3335     return FALSE;
3336   END IF;
3337   i := colMeasures.first;
3338   LOOP
3339 	l_measure := colMeasures(i);
3340     If (UPPER(l_measure.fieldName) = UPPER(measure) and l_measure.source=p_source) Then
3341 	  return true;
3342     END IF;
3343 	EXIT WHEN i = colMeasures.last;
3344 	i := colMeasures.next(i);
3345   END LOOP;
3346   return false;
3347   EXCEPTION WHEN OTHERS THEN
3348       g_error := sqlerrm;
3349       BSC_MO_HELPER_PKG.TerminateWithMsg('Exception dataFieldExistsForSource, '||g_error);
3350       raise;
3351 End;
3352 
3353 --****************************************************************************
3354 --  GetCamposExpresion
3355 --
3356 --   DESCRIPTION:
3357 --     Get in an array the list of fields in the given expression.
3358 --     Return the number of fields.
3359 --     Example. Expresion = 'IIF(Not IsNull(SUM(A)), C, B)'
3360 --     CamposExpresion() = |A|C|B|, GetCamposExpresion = 3
3361 --  PARAMETERS:
3362 --     CamposExpresion(): array to be populated
3363 --     Expresion: expression
3364 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3365 --****************************************************************************
3366 Function GetFieldExpresion(CamposExpresion IN OUT NOCOPY dbms_sql.varchar2_table, Expresion IN VARCHAR2) return NUMBER IS
3367   i NUMBER;
3368 
3369   NumCamposExpresion VARCHAR2(1000);
3370   Campos dbms_sql.varchar2_table;
3371   NumCampos NUMBER;
3372   cExpresion VARCHAR2(1000);
3373 BEGIN
3374 
3375   cExpresion := Expresion;
3376   --Replace the operators by ' '
3377   i := BSC_METADATA_OPTIMIZER_PKG.gReservedOperators.first;
3378 
3379   LOOP
3380 	   cExpresion := Replace(cExpresion, BSC_METADATA_OPTIMIZER_PKG.gReservedOperators(i), ' ');
3381      EXIT WHEN i = BSC_METADATA_OPTIMIZER_PKG.gReservedOperators.last;
3382      i := BSC_METADATA_OPTIMIZER_PKG.gReservedOperators.next(i);
3383   END LOOP;
3384 
3385   --Break down the expression which is separated by ' '
3386 
3387   NumCampos := BSC_MO_HELPER_PKG.DecomposeString(cExpresion, ' ', Campos);
3388   NumCampos := Campos.count;
3389   NumCamposExpresion := 0;
3390   i:= Campos.first;
3391   LOOP
3392       EXIT WHEN Campos.count = 0;
3393       If Campos(i) IS NOT NULL Then
3394         If BSC_MO_HELPER_PKG.FindIndexVARCHAR2(BSC_METADATA_OPTIMIZER_PKG.gReservedFunctions, Campos(i)) = -1 Then
3395           --The word campos(i) is not a reserved function
3396           If UPPER(Campos(i)) <> 'NULL' Then
3397               --the word is not 'NULL'
3398               If Not  BSC_MO_HELPER_PKG.IsNumber(Campos(i)) Then
3399                 --the word is not a constant
3400                 CamposExpresion(NumCamposExpresion) := Campos(i);
3401                 NumCamposExpresion := NumCamposExpresion + 1;
3402               END IF;
3403           END IF;
3404         END IF;
3405       END IF;
3406       EXIT WHEN i = Campos.last;
3407       i := Campos.next(i);
3408   END LOOP;
3409 	return NumCamposExpresion;
3410 
3411   EXCEPTION WHEN OTHERS THEN
3412       BSC_MO_HELPER_PKG.TerminateWithMsg('Exception in GetFieldExpresion : '||sqlerrm);
3413       raise;
3414 
3415 End;
3416 
3417 
3418 --***************************************************************************
3419 --clearDataFields
3420 --  DESCRIPTION:
3421 --   Get the list of data fields for an indicator. It is returned in a
3422 --   collection of object of class clsDataField
3423 --
3424 --  PARAMETERS:
3425 --   Indic: indicator code
3426 --   Configuration: configuration
3427 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3428 --***************************************************************************
3429 
3430 PROCEDURE clearDataField(dataField IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.clsDataField) IS
3431   dataField_null BSC_METADATA_OPTIMIZER_PKG.clsDataField;
3432 BEGIN
3433   dataField:=dataField_null ;
3434 END;
3435 
3436 
3437 --****************************************************************************
3438 --GetDataFields
3439 --  DESCRIPTION:
3440 --   Get the list of data fields for an indicator. It is returned in a
3441 --   collection of object of class clsDataField
3442 --
3443 --  PARAMETERS:
3444 --   Indic: indicator code
3445 --   Configuration: configuration
3446 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3447 --***************************************************************************
3448 
3449 Function GetDataFields(Indic IN NUMBER, Configuration IN NUMBER, WithInternalColumns IN Boolean)
3450  RETURN BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField IS
3451 
3452     l_stmt  VARCHAR2(1000);
3453     l_measure_name varchar2(1000);
3454     l_measure_names_list dbms_sql.varchar2_table;
3455     l_num_measures NUMBER;
3456     FuncAgreg varchar2(1000);
3457     l_measure_column BSC_METADATA_OPTIMIZER_PKG.clsDataField;
3458     l_col_measure_columns BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
3459     TenerEnCuentaCampo NUMBER;
3460     i  NUMBER;
3461     msg VARCHAR2(1000);
3462 
3463     pFormulaSource VARCHAR2(1000);
3464     pAvgL VARCHAR2(1000);
3465     pAvgLTotal VARCHAR2(1000);
3466     pAvgLCounter VARCHAR2(1000);
3467     FuncAgregSingleColumn VARCHAR2(1000);
3468     pAvgLSingleColumn VARCHAR2(1000);
3469     AvgLTotalColumn VARCHAR2(1000);
3470     AvgLCounterColumn VARCHAR2(1000);
3471     baseColumn dbms_sql.varchar2_table;
3472 
3473  l_stmt2 VARCHAR2(10000):= 'SELECT M.MEASURE_COL, NVL(M.OPERATION, ''SUM'') AS OPER,
3474  BSC_APPS.GET_PROPERTY_VALUE(M.S_COLOR_FORMULA, :1) AS PFORMULASOURCE,
3475  NVL(BSC_APPS.GET_PROPERTY_VALUE(M.S_COLOR_FORMULA, :2 ),''N'') AS PAVGL,
3476  BSC_APPS.GET_PROPERTY_VALUE(M.S_COLOR_FORMULA, :3) AS PAVGLTOTAL,
3477  BSC_APPS.GET_PROPERTY_VALUE(M.S_COLOR_FORMULA, :4) AS PAVGLCOUNTER '||
3478  -- BSC Autogen
3479  ', nvl(M.SOURCE, ''BSC'')
3480  FROM BSC_SYS_MEASURES M, '||BSC_METADATA_OPTIMIZER_PKG.g_dbmeasure_tmp_table||' I
3481  WHERE I.MEASURE_ID = M.MEASURE_ID
3482  AND I.DIM_SET_ID = :5
3483  AND I.INDICATOR = :6
3484  AND M.TYPE = 0';
3485 
3486  L_MEASURE_COL VARCHAR2(4000);
3487  L_OPER VARCHAR2(100);
3488  L_PFORMULASOURCE VARCHAR2(1000);
3489  L_PAVGL VARCHAR2(1000);
3490  L_PAVGLTOTAL VARCHAR2(1000);
3491  L_PAVGLCOUNTER VARCHAR2(1000);
3492  l_source VARCHAR2(100);
3493  cv CurTyp;
3494 
3495 BEGIN
3496   bsc_mo_helper_pkg.writeTmp( 'Inside GetDataFields, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, false);
3497   select short_name into l_source from bsc_kpis_vl
3498   where indicator=Indic;
3499   -- Bug 4301819
3500   -- Dont include PMF measures if this is created by objective definer
3501   IF (l_source is null) THEN -- created by objective definer
3502     l_stmt2 := l_stmt2 ||' AND NVL(M.SOURCE, ''BSC'') = ''BSC''';
3503   ELSE -- created by Report definer
3504     l_stmt2 := l_stmt2 ||' AND NVL(M.SOURCE, ''BSC'') IN (''BSC'',''PMF'')';
3505   END IF;
3506   l_stmt2 := l_stmt2 ||' ORDER BY MEASURE_COL ';
3507   l_source := null;
3508   -- BSC Autogen, comment below no longer valid
3509   --BSC-PMF Integration: Even though a PMF measure cannot be present in a BSC
3510   --dimension set, I am going to do the validation to filter out PMF measures
3511   OPEN cv for l_stmt2 USING BSC_METADATA_OPTIMIZER_PKG.C_PFORMULASOURCE,
3512 		BSC_METADATA_OPTIMIZER_PKG.C_PAVGL,
3513 		BSC_METADATA_OPTIMIZER_PKG.C_PAVGLTOTAL,
3514 		BSC_METADATA_OPTIMIZER_PKG.C_PAVGLCOUNTER, Configuration, Indic;
3515   LOOP
3516     FETCH cv INTO L_MEASURE_COL, L_OPER, L_PFORMULASOURCE, L_PAVGL, L_PAVGLTOTAL, L_PAVGLCOUNTER, l_source ;
3517     EXIT WHEN cv%NOTFOUND;
3518     FuncAgreg := L_OPER;
3519     l_measure_name := L_MEASURE_COL;
3520     pFormulaSource := null;
3521     If (L_PFORMULASOURCE IS NOT NULL) Then
3522     pFormulaSource := L_PFORMULASOURCE;
3523     END IF;
3524     pAvgL := L_PAVGL;
3525     pAvgLTotal := null;
3526     If (L_PAVGLTOTAL IS NOT NULL) Then
3527       pAvgLTotal := L_PAVGLTOTAL;
3528     END IF;
3529     pAvgLCounter := null;
3530     If (L_PAVGLCOUNTER IS NOT NULL) Then
3531       pAvgLCounter := L_PAVGLCOUNTER;
3532     END IF;
3533     l_num_measures := GetFieldExpresion(l_measure_names_list, l_measure_name);
3534     l_num_measures := l_measure_names_list.count;
3535 	FOR i IN l_measure_names_list.first..l_measure_names_list.last LOOP
3536 	  If fieldExistsINLOV(l_measure_names_list(i), l_source) Then
3537         If Not DataFieldExists(l_col_measure_columns, l_measure_names_list(i)) Then
3538         --Get the aggregation function and Avgl flag of the column (single column)
3539           bsc_mo_helper_pkg.writeTmp('Getting the aggregate function for '||l_measure_names_list(i));
3540 		  GetAggregateFunction (l_measure_names_list(i), FuncAgregSingleColumn, pAvgLSingleColumn, AvgLTotalColumn, AvgLCounterColumn);
3541           bsc_mo_helper_pkg.writeTmp('FuncAgregSingleColumn='||FuncAgregSingleColumn||', pAvgLSingleColumn='||pAvgLSingleColumn
3542             ||', AvgLTotalColumn='||AvgLTotalColumn||', AvgLCounterColumn='||AvgLCounterColumn);
3543           If FuncAgregSingleColumn IS NULL Then
3544 		    FuncAgregSingleColumn := FuncAgreg;
3545 		  END IF;
3546           If pAvgLSingleColumn IS NULL Then
3547 		    pAvgLSingleColumn := pAvgL;
3548 		  END IF;
3549 		  l_measure_column := bsc_mo_helper_pkg.new_clsDataField;
3550           l_measure_column.fieldName := l_measure_names_list(i);
3551           l_measure_column.source := nvl(l_source, 'BSC');
3552           l_measure_column.aggFunction := FuncAgregSingleColumn;
3553           --l_measure_column.Origen is not set
3554           l_measure_column.AvgLFlag := pAvgLSingleColumn;
3555           bsc_mo_helper_pkg.writeTmp('l_measure_column.fieldName='||l_measure_column.fieldName||',l_measure_column.aggFunction='||
3556 	      l_measure_column.aggFunction||', pAvgLSingleColumn='||pAvgLSingleColumn);
3557 		  If pAvgLSingleColumn = 'Y' And WithInternalColumns Then
3558             --This is a single column, we can have AvgL on a single column.
3559             --We need to internal columns: one for total and one for counter
3560             --Also we need to add the internal columns in gLov and in
3561             --BSC_DB_MEASURES_COLS_TL table
3562             baseColumn(0) := l_measure_names_list(i);
3563             If AvgLTotalColumn IS NULL Then
3564               AvgLTotalColumn := getNextInternalColumnName;
3565               --Update the measure property pAvgLTotal in the database
3566               SetMeasurePropertyDB (l_measure_names_list(i), BSC_METADATA_OPTIMIZER_PKG.C_PAVGLTOTAL, AvgLTotalColumn);
3567             END IF;
3568             l_measure_column.AvgLTotalColumn := AvgLTotalColumn;
3569             AddInternalColumnInDB(AvgLTotalColumn, 2, baseColumn, 1);
3570             If AvgLCounterColumn IS NULL Then
3571               AvgLCounterColumn := getNextInternalColumnName;
3572               --Update the measure property pAvgLCounter in the database
3573               SetMeasurePropertyDB (l_measure_names_list(i), BSC_METADATA_OPTIMIZER_PKG.C_PAVGLCOUNTER, AvgLCounterColumn);
3574             END IF;
3575             l_measure_column.AvgLCounterColumn := AvgLCounterColumn;
3576             AddInternalColumnInDB(AvgLCounterColumn, 3, baseColumn, 1);
3577           END IF;
3578           l_measure_column.InternalColumnType := 0 ; --Normal
3579           l_col_measure_columns(l_col_measure_columns.count) :=  l_measure_column;
3580           If pAvgLSingleColumn = 'Y' And WithInternalColumns Then
3581             --Add the two internal column for AvgL in the collection
3582             --Column for Total
3583             l_measure_column := bsc_mo_helper_pkg.new_clsDataField;
3584             l_measure_column.fieldName := AvgLTotalColumn;
3585             l_measure_column.source := nvl(l_source, 'BSC');
3586             l_measure_column.aggFunction := 'SUM';
3587             --l_measure_column.Origen is not set
3588             l_measure_column.AvgLFlag := 'N';
3589             --l_measure_column.avgLTotalColumn does not apply
3590             --l_measure_column.avgLCounterColumn does not apply
3591             l_measure_column.InternalColumnType := 2; --Internal column for Total of AvgL
3592             l_measure_column.InternalColumnSource := l_measure_names_list(i);
3593             l_col_measure_columns(l_col_measure_columns.count) := l_measure_column;
3594             --Column for Counter
3595             l_measure_column := bsc_mo_helper_pkg.new_clsDataField;
3596             l_measure_column.fieldName := AvgLCounterColumn;
3597             l_measure_column.source := nvl(l_source, 'BSC');
3598             l_measure_column.aggFunction := 'SUM';
3599             --l_measure_column.Origen is not set
3600             l_measure_column.AvgLFlag := 'N';
3601             --l_measure_column.avgLTotalColumn does not apply
3602             --l_measure_column.avgLCounterColumn does not apply
3603             l_measure_column.InternalColumnType := 3; --Internal column for Counter of AvgL
3604             l_measure_column.InternalColumnSource := l_measure_names_list(i);
3605             l_col_measure_columns(l_col_measure_columns.last + 1) := l_measure_column;
3606           END IF;-- END OF If pAvgLSingleColumn = 'Y' And WithInternalColumns
3607         --BSC Autogen
3608 		ELSE
3609 		  --Bug 4273572
3610 		  If DataFieldExistsForSource(l_col_measure_columns, l_measure_names_list(i), l_source) THEN
3611 		    null;--ignore this as we may have a, b and (a+b)
3612 		  ELSE
3613 		    -- raise error, two measures with same name (possibly one PMF and one BSC)
3614             fnd_message.set_name('BSC', 'BSC_PMA_OPT_DUP_MEASURE');
3615             fnd_message.set_token('OBJECTIVE', Indic);
3616             fnd_message.set_token('MEASURE_NAME', l_measure_names_list(i));
3617             g_error := fnd_message.get;
3618             bsc_mo_helper_pkg.writeTmp('ERROR BSC_PMA_OPT_DUP_MEASURE(Duplicate measure names) : '||g_error, FND_LOG.LEVEL_EXCEPTION, true);
3619             bsc_mo_helper_pkg.terminateWithMsg(g_error);
3620             raise bsc_metadata_optimizer_pkg.optimizer_exception ;
3621 	        EXIT ;
3622 	      END IF;
3623 		END IF;
3624       Else
3625         fnd_message.set_name('BSC', 'BSC_FIELDNME_NOT_REGISTERED');
3626         fnd_message.set_token('FIELD_NAME', l_measure_names_list(i));
3627         fnd_message.set_token('INDICATOR_CODE', Indic);
3628         g_error := fnd_message.get;
3629         IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3630           bsc_mo_helper_pkg.writeTmp(g_error);
3631 		  bsc_mo_helper_pkg.writeTmp('ERROR : BSC_FIELDNME_NOT_REGISTERED : '||g_error);
3632         END IF;
3633 	    bsc_mo_helper_pkg.terminateWithMsg(g_error);
3634         raise bsc_metadata_optimizer_pkg.optimizer_exception ;
3635 	    EXIT ;
3636       END IF;
3637     END LOOP;
3638     --Now add internal column if the formula needs to calculated in another column
3639     If WithInternalColumns Then
3640       If pFormulaSource IS NOT NULL Then
3641         --Add the internal column in gLov and in BSC_DB_MEASURES_COLS_TL table
3642         AddInternalColumnInDB(pFormulaSource, 1, l_measure_names_list, l_num_measures);
3643         l_measure_column := bsc_mo_helper_pkg.new_clsDataField;
3644         l_measure_column.fieldName := pFormulaSource;
3645         l_measure_column.source := nvl(l_source, 'BSC');
3646         l_measure_column.aggFunction := FuncAgreg;
3647         --l_measure_column.Origen is not set
3648         l_measure_column.AvgLFlag := pAvgL;
3649         If pAvgL = 'Y' Then
3650         --This is a formula calculated in another column, we can have AvgL on a that.
3651         --We need to internal columns: one for total and one for counter
3652         --Also we need to add the internal columns in gLov and in
3653         --BSC_DB_MEASURES_COLS_TL table
3654         If pAvgLTotal IS NULL Then
3655           pAvgLTotal := getNextInternalColumnName ;
3656           --Update the measure property pAvgLTotal in the database
3657           SetMeasurePropertyDB( l_measure_name, BSC_METADATA_OPTIMIZER_PKG.C_PAVGLTOTAL, pAvgLTotal);
3658         END IF;
3659         AddInternalColumnInDB(pAvgLTotal, 2, l_measure_names_list, l_num_measures);
3660         l_measure_column.AvgLTotalColumn := pAvgLTotal;
3661         If pAvgLCounter IS NULL Then
3662           pAvgLCounter := getNextInternalColumnName;
3663           --Update the measure property pAvgLTotal in the database
3664           SetMeasurePropertyDB( l_measure_name, BSC_METADATA_OPTIMIZER_PKG.C_PAVGLCOUNTER, pAvgLCounter);
3665         END IF;
3666         AddInternalColumnInDB( pAvgLCounter, 3, l_measure_names_list, l_num_measures);
3667         l_measure_column.AvgLCounterColumn := pAvgLCounter;
3668       END IF;
3669       l_measure_column.InternalColumnType := 1; --Internal column for formula
3670       l_measure_column.InternalColumnSource := l_measure_name; -- Formula Example A/B
3671       l_col_measure_columns(l_col_measure_columns.last +1 ) :=  l_measure_column;
3672       If pAvgL = 'Y' Then
3673         --Add the two internal column for AvgL in the collection
3674         --Bug 2993089: When the column is not a formula but has the option
3675         --Apply rollup to formula', the columns for Average at lowest level
3676         --are already in colCamporDatos.
3677         --We need to evaluate this situation adding te condition
3678         --If Not ExisteCampoDato(l_col_measure_columns, <internal column for AvgL>)
3679         --Column for Total
3680         If Not DataFieldExists(l_col_measure_columns, pAvgLTotal) Then
3681 		  l_measure_column := bsc_mo_helper_pkg.new_clsDataField;
3682           l_measure_column.fieldName := pAvgLTotal;
3683           l_measure_column.source := nvl(l_source, 'BSC');
3684           l_measure_column.aggFunction := 'SUM';
3685           --l_measure_column.Origen is not set
3686           l_measure_column.AvgLFlag := 'N';
3687           l_measure_column.InternalColumnType := 2; -- 'Internal column for Total of AvgL
3688           l_measure_column.InternalColumnSource := l_measure_name; -- 'Formula Example A/B
3689           l_col_measure_columns(l_col_measure_columns.last+1) :=  l_measure_column ;
3690         END IF;
3691         --Column for Counter
3692         If Not DataFieldExists(l_col_measure_columns, pAvgLCounter) Then
3693           l_measure_column := bsc_mo_helper_pkg.new_clsDataField;
3694           l_measure_column.fieldName := pAvgLCounter;
3695           l_measure_column.source := nvl(l_source, 'BSC');
3696           l_measure_column.aggFunction := 'SUM';
3697           --l_measure_column.Origen is not set
3698           l_measure_column.AvgLFlag := 'N';
3699           --l_measure_column.avgLTotalColumn does not apply
3700           --l_measure_column.avgLCounterColumn does not apply
3701           l_measure_column.InternalColumnType := 3; --Internal column for Counter of AvgL
3702           l_measure_column.InternalColumnSource := l_measure_name; --Formula Example A/B
3703           l_col_measure_columns(l_col_measure_columns.last+1) := l_measure_column ;
3704         END IF;
3705       END IF;
3706     END IF;
3707     END IF;
3708   END Loop;
3709   close cv;
3710   bsc_mo_helper_pkg.writeTmp( 'Compl. GetDataFields, System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, false);
3711   return l_col_measure_columns;
3712   EXCEPTION WHEN OTHERS THEN
3713     fnd_message.set_name('BSC', 'BSC_BASICTABLE_DEDUCT_FAILED');
3714 	fnd_message.set_token('INDICATOR', Indic);
3715     fnd_message.set_token('DIMENSION_SET', Configuration);
3716     g_error := fnd_message.get;
3717     bsc_mo_helper_pkg.terminatewithMsg(g_error);
3718     raise;
3719   --app_exception.raise_exception;
3720 
3721 End;
3722 
3723 --****************************************************************************
3724 --GetStrCombinationsMN
3725 --
3726 --  DESCRIPTION:
3727 --   Retunrs all combinations found in a set of strings.
3728 --   The prameter 'combo' is a collection of items of class clsCadema.
3729 --   The function retunrs a collection of items of class
3730 --   Example. combo = 'A', 'B', 'C'
3731 --   GetStrCombinationsMN = 'A', 'B', 'C', 'A' 'B', 'A' 'C', 'B' 'C',
3732 --                  'A' 'B' 'C'
3733 --   Additionally, if exist at least one 1n relation between
3734 --   the elements of the combination then it is rejected.
3735 --  PARAMETERS:
3736 --   combo: set of strings.
3737 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3738 --***************************************************************************
3739 
3740 Function GetStrCombinationsMN(combo IN dbms_sql.varchar2_table)
3741  return dbms_sql.varchar2_table IS
3742   StringCombination dbms_sql.varchar2_table;
3743   StringCombination1 dbms_sql.varchar2_table;
3744 
3745   Combination dbms_sql.varchar2_table;
3746   Combination1 dbms_sql.varchar2_table;
3747 
3748   str varchar2(1000);
3749   str1 varchar2(1000);
3750   combo1 dbms_sql.varchar2_table;
3751   i  NUMBER;
3752   j NUMBER;
3753   Rel1NExists  Boolean;
3754 
3755   l_temp1 nUMBER;
3756 l_temp2 NUMBER;
3757 BEGIN
3758   i := combo.first;
3759   If combo.Count = 1 Then
3760     StringCombination(0) := combo(combo.first);
3761     return StringCombination;
3762   END IF;
3763   i := combo.first;
3764   str  := combo(i);
3765   Combination(0) :=  str;
3766   StringCombination(0) := str;
3767   LOOP
3768     EXIT WHEN i=combo.last;
3769     i := combo.next(i);
3770     str  := combo(i);
3771     combo1(combo1.count):= str;
3772   END LOOP;
3773   StringCombination1 := GetStrCombinationsMN(combo1);
3774   IF (StringCombination1.count > 0) THEN
3775     i := StringCombination1.first;
3776   END IF;
3777   LOOP
3778     EXIT WHEN StringCombination1.count =0;
3779     Combination1 := BSC_MO_HELPER_PKG.getDecomposedString(StringCombination1(i), ',');
3780     Combination.delete;
3781     IF (Combination1.count >0) THEN
3782       j:= Combination1.first;
3783       LOOP
3784         str := Combination1(j);
3785         IF (Combination.count>0) THEN
3786           Combination( Combination.last+1) := str;
3787         ELSE
3788           Combination(0) := str;
3789         END IF;
3790         EXIT WHEN j = Combination1.last;
3791         j := Combination1.next(j);
3792       END LOOP;
3793     END IF;
3794     StringCombination(StringCombination.count) :=  BSC_MO_HELPER_PKG.ConsolidateString(Combination, ',');
3795     EXIT WHEN i =  StringCombination1.last;
3796     i := StringCombination1.next(i);
3797   END LOOP;
3798   IF (StringCombination1.count > 0) THEN
3799     i := StringCombination1.first;
3800   END IF;
3801   LOOP
3802     EXIT WHEN StringCombination1.count =0;
3803     Combination1 := BSC_MO_HELPER_PKG.getDecomposedString(StringCombination1(i), ',');
3804     Rel1NExists := False;
3805     Combination.delete;
3806     str := combo(combo.first) ;
3807     Combination(Combination.count) := str;
3808     IF (Combination1.count >0) THEN
3809       j := Combination1.first;
3810     END IF;
3811     LOOP
3812       EXIT WHEN Combination1.count =0;
3813       str1 := Combination1(j);
3814       --It is not a combination if there is at least one 1n relation between two drills
3815       l_temp1 := BSC_MO_HELPER_PKG.FindKeyIndex(BSC_METADATA_OPTIMIZER_PKG.gMastertable, str1);
3816       l_temp2 := BSC_MO_HELPER_PKG.FindKeyIndex(BSC_METADATA_OPTIMIZER_PKG.gMastertable, combo(0));
3817       If (l_temp1>=0 AND l_temp2>=0 AND
3818         IndexRelation1N(BSC_METADATA_OPTIMIZER_PKG.gMastertable(l_temp1).Name,
3819                                BSC_METADATA_OPTIMIZER_PKG.gMastertable(l_temp2).Name) = -1 )Then
3820         Combination( Combination.count) := str1;
3821       Else
3822         Rel1NExists := True;
3823         Exit;
3824       END IF;
3825       EXIT WHEN j = Combination1.last;
3826       j := Combination1.next(j);
3827     END LOOP;
3828     If Not Rel1NExists Then
3829       StringCombination(StringCombination.count) := BSC_MO_HELPER_PKG.ConsolidateString(Combination, ',');
3830     END IF;
3831     EXIT WHEN i = StringCombination1.last;
3832     i := StringCombination1.next(i);
3833   END LOOP;
3834   bsc_mo_helper_pkg.write_this(StringCombination);
3835   RETURN StringCombination;
3836   EXCEPTION WHEN OTHERS THEN
3837     g_error := sqlerrm;
3838     bsc_mo_helper_pkg.terminateWithMsg( 'Exception in GetStrCombinationsMN '||g_error);
3839 	RAISE;
3840 End;
3841 
3842 --****************************************************************************
3843 --GetLevelCombinations
3844 --  DESCRIPTION:
3845 --     Get the collection of combinations of drills of each familiy
3846 --
3847 --  PARAMETERS:
3848 --     p_dimension_families: collection of drill families
3849 --     forTargetLevel: true  -Only take drill with TargetLevel = 1
3850 --                              When calculation targets at different level
3851 --                       false -Take all drill
3852 --
3853 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
3854 --***************************************************************************
3855 
3856 Function GetLevelCombinations(
3857         p_dimension_families IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels,
3858         forTargetLevel IN BOOLEAN)
3859         RETURN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevelCombinations IS
3860 
3861   colDimLevelCombinations BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevelCombinations;
3862   DimLevelCombinations BSC_METADATA_OPTIMIZER_PKG.tab_clsLevelCombinations;
3863   LevelCombinations BSC_METADATA_OPTIMIZER_PKG.clsLevelCombinations;
3864 
3865   DrilC VARCHAR2(1000);
3866   ConfDriles VARCHAR2(1000);
3867 
3868   DimensionLevels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
3869 
3870   idril NUMBER;
3871   jDril NUMBER;
3872   numDriles NUMBER;
3873 
3874   colRelsMN dbms_sql.varchar2_table; --collection of objects of class clsCadena
3875   RelMN varchar2(1000);
3876 
3877   conjCombinacsMN dbms_sql.varchar2_table;
3878   CombinacMN dbms_sql.varchar2_table;
3879   ElementoCombinacMN varchar2(1000);
3880   indexDrilComparar NUMBER;
3881 
3882   l_ct1 NUMBER ;
3883   l_ct2 NUMBER ;
3884   l_ct3 NUMBER;
3885 
3886   l_temp_rel VARCHAR2(100);
3887 
3888   l_groups DBMS_SQL.NUMBER_TABLE;
3889   DimLevels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
3890   l_level_group_id NUMBER;
3891   l_comb_group_id NUMBER := 0;
3892 
3893   l_dummy NUMBER := 0;
3894 
3895   l_varchar_table DBMS_SQL.varchar2_table;
3896   l_stack VARCHAR2(32000);
3897 
3898 BEGIN
3899 
3900 
3901 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3902   bsc_mo_helper_pkg.writeTmp( 'Inside GetLevelCombinations, p_dimension_families.count is '||p_dimension_families.count);
3903 	END IF;
3904 
3905   bsc_mo_helper_pkg.write_this(p_dimension_families);
3906 
3907   l_groups := BSC_MO_HELPER_PKG.getGroupIds(p_dimension_families);
3908   IF (l_groups.count >0) THEN
3909 	  l_ct1 := l_groups.first ;
3910   ELSE
3911 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3912      bsc_mo_helper_pkg.writeTmp( 'Compl GetLevelCombinations 0 values');
3913 	END IF;
3914 
3915 	   return colDimLevelCombinations;
3916   END IF;
3917 
3918 
3919   --For each drill family, it get the collection of drill combinations
3920 
3921   LOOP
3922      DimLevelCombinations.delete;
3923 	 DimensionLevels := BSC_MO_HELPER_PKG.get_tab_clsLevels(p_dimension_families, l_groups(l_ct1));
3924 	  --It creates a new element clsCombinacsFliasDriles for the current drill family
3925       --Go through the list of drills from the end to the beginning of the current drill family
3926       IF (length(l_stack) > 31000) THEN
3927         l_stack := null;
3928       END IF;
3929 
3930       l_stack := l_stack || ' GetLevelCombinations - 1';
3931       numDriles := DimensionLevels.last;
3932       idril := numDriles;
3933       l_stack := l_stack || ' GetLevelCombinations - 2, numDriles = '||numDriles;
3934 	   LOOP
3935         EXIT WHEN DimensionLevels.count = 0;
3936         LevelCombinations.Levels := null; -- clear field
3937         LevelCombinations.LevelConfig := null; -- clear field
3938         If (Not forTargetLevel) Or (forTargetLevel And DimensionLevels(idril).TargetLevel = 1) Then
3939           --For each drill it creates a combination of drills
3940           --It is created with just one element which is the name of the key of the current drill
3941 
3942           DrilC := DimensionLevels(idril).keyName;
3943 
3944           LevelCombinations.Levels :=  DrilC;
3945           ConfDriles := null;
3946           --Characters of ConfDriles corresponding to the drills of the right of the current drill are assigned with '1'
3947 		      FOR jDril IN iDril+1..numDriles LOOP
3948 		          ConfDriles := ConfDriles ||'1';
3949 		      END LOOP;
3950           --The character of ConfDriles that correspond to the current drill:
3951           If idril = 0 Then --It is the current drill and its the first one
3952               ConfDriles := '?' || ConfDriles;
3953           Else
3954               ConfDriles := '0' || ConfDriles;
3955           END IF;
3956           --Characters that correspond to the drills of the left of the current drill
3957           colRelsMN.delete;
3958 
3959 
3960 
3961 		      FOR jDril IN REVERSE 0..idril-1 LOOP
3962               l_stack := l_stack || ' GetLevelCombinations - 3, jDril='||jDril;
3963               If  instr(DimensionLevels(idril).Parents1N, DimensionLevels(jDril).keyName) > 0 Then
3964                 --the current drill is child of jDril
3965                 ConfDriles := '?' || ConfDriles;
3966               Else
3967                 ConfDriles := '1' || ConfDriles;
3968                 --keep this mn relationship in the collection of mn relationships
3969                 RelMN := DimensionLevels(jDril).keyName;
3970                 colRelsMN(colRelsMN.count):= RelMN;
3971               END IF;
3972           END LOOP;
3973           LevelCombinations.levelConfig := ConfDriles;
3974           l_stack := l_stack || ' GetLevelCombinations - 4, LevelCombinations.drillConfig='||LevelCombinations.levelConfig;
3975           --Add the drill combination to the list of drill combinations of the family
3976 
3977           DimLevelCombinations(DimLevelCombinations.count) := LevelCombinations;
3978 
3979           l_stack := l_stack || ' GetLevelCombinations - 4.1';
3980 
3981           -- reorder colRelsMN
3982           for i in 0..(floor(colRelsMN.count/2)- 1) loop
3983               l_temp_rel := colRelsMN(i);
3984               colRelsMN(i) := colRelsMN(colRelsMN.last - i);
3985               colRelsMN(colRelsMN.last - i) := l_temp_rel;
3986           end loop;
3987 
3988           If colRelsMN.Count > 0 Then
3989               l_stack := l_stack || ' GetLevelCombinations - 4.2';
3990               --Add the drills combinations to the list of drills combinations of the family
3991               --whose drills are related to drills which has mn relation with the current drill
3992               --get a set of all posible combinations between the drills which there was mn relationship
3993           	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
3994                 bsc_mo_helper_pkg.writeTmp('Calling GetStrCombinationsMN with :');
3995                 bsc_mo_helper_pkg.write_THIS(colRelsMN);
3996                 bsc_mo_helper_pkg.writeTmp('......');
3997           	END IF;
3998 
3999               conjCombinacsMN := GetStrCombinationsMN(colRelsMN);
4000           	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4001                 bsc_mo_helper_pkg.writeTmp('GetStrCombinationsMN returned :');
4002                 bsc_mo_helper_pkg.write_THIS(conjCombinacsMN);
4003                 bsc_mo_helper_pkg.writeTmp('......');
4004           	END IF;
4005 
4006               l_stack := l_stack || ' GetLevelCombinations - 4.22';
4007 
4008 		        IF (conjCombinacsMN.count > 0) THEN
4009                 l_ct3 := conjCombinacsMN.first;
4010               END IF;
4011               l_stack := l_stack || ' GetLevelCombinations - 4.23';
4012 		        LOOP
4013 
4014                 l_stack := l_stack || ' GetLevelCombinations - 4.25';
4015 			        EXIT WHEN conjCombinacsMN.count=0;
4016                 l_stack := l_stack || '  GetLevelCombinations - 4.3';
4017 			        l_dummy := BSC_MO_HELPER_PKG.decomposeString(conjCombinacsMN(l_ct3), ',', CombinacMN);
4018                 --For each combination MN it has to create an element in the list of drill combinations
4019                 --for the family being analyzed
4020                 --Drills
4021                 --The list of drills is made up of elements of the combination mn andthe current drill
4022                 LevelCombinations := bsc_mo_helper_pkg.new_clsLevelCombinations;
4023 			        l_ct2 := CombinacMN.count;
4024 			        IF (l_ct2 >0) THEN
4025                   l_ct2 := CombinacMN.first;
4026                 END IF;
4027 
4028 			        LOOP
4029                   EXIT WHEN CombinacMN.count = 0;
4030                   l_stack := l_stack || ' GetLevelCombinations - 4.4';
4031                   IF (LevelCombinations.levels IS NOT NULL) THEN
4032                       LevelCombinations.levels := LevelCombinations.levels||',';
4033                   END IF;
4034                   LevelCombinations.levels := LevelCombinations.levels||CombinacMN(l_ct2);
4035                   EXIT WHEN l_ct2 = CombinacMN.last;
4036                   l_ct2 := CombinacMN.next(l_ct2);
4037                 END LOOP;
4038                 l_stack := l_stack || ' GetLevelCombinations - 4.41';
4039                 DrilC := DimensionLevels(idril).keyName;
4040                 IF (LevelCombinations.levels IS NOT NULL) THEN
4041                       LevelCombinations.levels := LevelCombinations.levels||',';
4042                 END IF;
4043                 LevelCombinations.levels := LevelCombinations.levels||DrilC;
4044 
4045                 --ConfDriles
4046                 ConfDriles := null;
4047                 --Characters of ConfDriles corresponding to the drills of the right
4048                 --of the current drill are assigned with '1'
4049 			         jDril := idril +1;
4050 
4051 			         FOR jDril IN idril+1..numDriles LOOP
4052                   l_stack := l_stack || ' GetLevelCombinations - 4.5';
4053                   ConfDriles := ConfDriles || '1';
4054 			         END LOOP;
4055                 --The character of ConfDriles corresponding to the current drill:
4056                 ConfDriles := '0' || ConfDriles;
4057                 --Character corresponding to the left of the current drill
4058                 indexDrilComparar := idril;
4059                 --jDril := idril -1;
4060 						FOR jDril IN REVERSE 0..idril-1 LOOP
4061                   If BSC_MO_HELPER_PKG.findindexVARCHAR2(CombinacMN, DimensionLevels(jDril).keyName) >= 0 Then
4062                       --the drill belong to the current mn combination
4063                       ConfDriles := '0' || ConfDriles;
4064                       indexDrilComparar := jDril;
4065                   Else
4066                       l_dummy := BSC_MO_HELPER_PKG.decomposeString(DimensionLevels(indexDrilComparar).Parents1N, ',', l_varchar_table);
4067                       If BSC_MO_HELPER_PKG.findindexVARCHAR2(l_varchar_table,
4068                         DimensionLevels(jDril).keyName) >= 0 Then
4069                         ConfDriles := '?'||ConfDriles;
4070                       Else
4071                         ConfDriles := '1' || ConfDriles;
4072                       END IF;
4073                   END IF;
4074                   l_stack := l_stack || ' GetLevelCombinations - 4.6';
4075 			         END LOOP;
4076                 LevelCombinations.levelConfig := ConfDriles;
4077                 --Add the combination of drills to the list of drill combinations of the family
4078                 IF (DimLevelCombinations.count>0) THEN
4079                       DimLevelCombinations(DimLevelCombinations.last+1):= LevelCombinations;
4080                 ELSE
4081                       DimLevelCombinations(0):= LevelCombinations;
4082                 END IF;
4083                 EXIT WHEN l_Ct3 = conjCombinacsMN.last;
4084                 l_ct3 := conjCombinacsMN.next(l_ct3);
4085               END LOOP;
4086           END IF;-- colRelsMN.Count > 0
4087         END IF;--Not forTargetLevel)
4088         l_stack := l_stack || ' GetLevelCombinations - 4.7, iDril='||iDril;
4089 		  EXIT WHEN idril = DimensionLevels.first;
4090 		  idril := DimensionLevels.prior(idril);
4091       END LOOP;
4092       l_stack := l_stack || ' GetLevelCombinations - 5';
4093 
4094       bsc_mo_helper_pkg.add_tabrec_clsLevelComb(colDimLevelCombinations, DimLevelCombinations, l_groups(l_ct1));
4095 
4096       EXIT WHEN l_ct1 = l_groups.last;
4097 	  l_ct1 := l_groups.next(l_ct1);
4098 
4099   END LOOP;
4100 
4101 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4102       bsc_mo_helper_pkg.writeTmp( 'Compl GetLevelCombinations');
4103 	END IF;
4104 
4105 
4106 	return colDimLevelCombinations;
4107   EXCEPTION WHEN OTHERS THEN
4108       DrilC := sqlerrm;
4109       bsc_mo_helper_pkg.terminateWithMsg('Exception in GetLevelCOmbinations : '||drilC);
4110       FND_FILE.put_line(FND_FILE.LOG, l_stack);
4111       raise;
4112 End;
4113 
4114 
4115 --****************************************************************************
4116 --IndexFliaDrilesHayRelacion
4117 --
4118 --  DESCRIPTION:
4119 --   Returns the index of the drills family of the collection
4120 --   ColDimLevelFamilies which the given dimension belongs to.
4121 --
4122 --  PARAMETERS:
4123 --   ColDimLevelFamilies: drills families collection
4124 --   Maestra: dimension table name
4125 --
4126 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4127 --***************************************************************************
4128 
4129 Function get_dimension_family(tabtabDrills IN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels, dimTable IN VARCHAR2)
4130 return NUMBER IS
4131   l_levels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
4132   l_level  BSC_METADATA_OPTIMIZER_PKG.clsLevels;
4133   l_ct NUMBER := 0;
4134   l_ct2 NUMBER := 0;
4135   l_groups DBMS_SQL.NUMBER_TABLE;
4136   l_dummy NUMBER;
4137   l_varchar_table DBMS_SQL.VARCHAR2_TABLE;
4138 BEGIN
4139   IF (tabtabDrills.count =0 ) THEN
4140 	   return -1;
4141   END IF;
4142   l_groups := BSC_MO_HELPER_PKG.getgroupids(tabtabDrills);
4143   --l_ct := l_groups.first;
4144   FOR l_ct IN l_groups.first..l_groups.last LOOP
4145     l_levels := BSC_MO_HELPER_PKG.get_tab_clsLevels(tabtabDrills, l_groups(l_ct));
4146     --l_ct2 := l_levels.first;
4147     FOR l_ct2 IN l_levels.first..l_levels.last LOOP
4148       l_level := l_levels(l_ct2);
4149       If IndexRelation1N(dimTable, l_level.dimTable) >= 0 Then
4150         -- check none of the other levels have this as a parent level
4151         /*l_dummy := BSC_MO_HELPER_PKG.decomposeString(l_level.Parents1N, ',', l_varchar_table);
4152         IF (l_varchar_table.count >0) THEN
4153           FOR k IN l_varchar_table.first..l_varchar_table.last LOOP
4154             If IndexRelation1N(l_varchar_Table(k), l_level.dimTable) >= 0 THEN
4155               return -1;
4156             END IF;
4157           END LOOP;
4158         END IF;
4159         */
4160         return l_ct;
4161       END IF;
4162       If IndexRelationMN(dimTable, l_level.dimTable) >= 0 Then
4163         return l_ct;
4164       END IF;
4165       --EXIT WHEN l_ct2 = l_levels.last;
4166       --l_ct2 := l_levels.next(l_ct2);
4167  	END LOOP;
4168     --EXIT WHEN l_ct = l_groups.last;
4169     --l_ct := l_groups.next(l_ct);
4170   END LOOP;
4171   return -1;
4172   EXCEPTION WHEN OTHERS THEN
4173     g_error := sqlerrm;
4174     bsc_mo_helper_pkg.terminateWithMsg('Exception in get_dimension_family '||g_error);
4175 	RAISE;
4176 End ;
4177 
4178 
4179 
4180 --****************************************************************************
4181 --GetColDimLevelFamilies
4182 --
4183 --  DESCRIPTION:
4184 --   Get the collection of level families of the indicator
4185 --
4186 --  PARAMETERS:
4187 --   Indic: indicator code
4188 --   Configuration: configuration
4189 --
4190 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4191 --***************************************************************************
4192 Function GetLevelCollection(Indic IN NUMBER, Configuration IN NUMBER)
4193 RETURN BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels IS
4194     l_dimension_families BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels;
4195     DimensionLevels BSC_METADATA_OPTIMIZER_PKG.tab_clsLevels;
4196     cLevel BSC_METADATA_OPTIMIZER_PKG.clsLevels;
4197     tDril BSC_METADATA_OPTIMIZER_PKG.clsLevels;
4198 
4199     l_parents1n varchar2(1000);
4200     l_parentsMN varchar2(1000);
4201     tPadre1n  varchar2(1000);
4202     tPadremn varchar2(1000);
4203     l_dim_index NUMBER;
4204     l_level_table VARCHAR2(1000);
4205     l_level_pk_col VARCHAR2(1000);
4206     Name VARCHAR2(1000);
4207     TargetLevel NUMBER;
4208     l_stmt varchar2(1000);
4209     DimensionLevelsNum NUMBER;
4210     msg VARCHAR2(1000);
4211     l_count number;
4212 
4213     l_ct Number;
4214     cv CurTyp;
4215 
4216     l_group_id NUMBER := 0;
4217     cdril_parents1N DBMS_SQL.VARCHAR2_TABLE;
4218     cdril_parentsMN DBMS_SQL.VARCHAR2_TABLE;
4219     tdril_parents1N DBMS_SQL.VARCHAR2_TABLE;
4220     tdril_parentsMN DBMS_SQL.VARCHAR2_TABLE;
4221 
4222 
4223 BEGIN
4224   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4225     bsc_mo_helper_pkg.writeTmp( 'Inside GetLevelCollection, Indic = '||Indic||', Configuration = '||Configuration);
4226   END IF;
4227   l_stmt := 'SELECT DISTINCT DIM_LEVEL_INDEX, LEVEL_TABLE_NAME, LEVEL_PK_COL, NAME, NVL(TARGET_LEVEL,1) AS TAR_LEVEL' ||
4228    	' FROM BSC_KPI_DIM_LEVELS_VL WHERE INDICATOR = :1 AND DIM_SET_ID = :2  AND STATUS = 2';
4229   ----dbms_output.put_line('Chk1');
4230   IF IsIndicatorBalanceOrPnL(Indic, true) Then
4231     --The level 0 which is the Type of Account drill is excluded. This drill is
4232     --not considered to generate the tables
4233     l_stmt:= l_stmt||' AND DIM_LEVEL_INDEX <> 0';
4234   END IF;
4235   l_stmt := l_stmt||' ORDER BY DIM_LEVEL_INDEX';
4236   OPEN cv FOR l_stmt using Indic, Configuration;
4237   LOOP
4238     Fetch cv into l_dim_index, l_level_table, l_level_pk_col, Name, TargetLevel;
4239     EXIT WHEN cv%NOTFOUND;
4240     cLevel             := bsc_mo_helper_pkg.new_clsLevels;
4241     cLevel.keyName     := l_level_pk_col;
4242     cLevel.dimTable    := l_level_table;
4243     cLevel.Num         := l_dim_index;
4244     cLevel.Name        := Name;
4245     cLevel.TargetLevel := TargetLevel;
4246     IF (BSC_METADATA_OPTIMIZER_PKG.g_log) THEN
4247       bsc_mo_helper_pkg.writeTmp('Considering level '||l_level_table||' checking for relationship to existing levels', 1, false);
4248     END IF;
4249     DimensionLevelsNum := get_dimension_family(l_dimension_families, l_level_table);
4250     IF (BSC_METADATA_OPTIMIZER_PKG.g_log) THEN
4251       bsc_mo_helper_pkg.writeTmp('DimensionLevelsNum = '||DimensionLevelsNum);
4252     END IF;
4253     -- Get the index of the dimension family which this drill belongs to.
4254     If DimensionLevelsNum <> -1 Then
4255       IF (BSC_METADATA_OPTIMIZER_PKG.g_log) THEN
4256         bsc_mo_helper_pkg.writeTmp('Relationship exists');
4257       END IF;
4258       --Level belongs to family DimensionLevelsNum.
4259       --Check each level of this family and see which drill has 1n or mn
4260       --relationship with this one
4261       DimensionLevels := BSC_MO_HELPER_PKG.get_tab_clsLevels(l_dimension_families, DimensionLevelsNum);
4262       l_count := DimensionLevels.first;
4263       LOOP
4264         EXIT WHEN DimensionLevels.count = 0;
4265         tdril := bsc_mo_helper_pkg.new_clsLevels;
4266         tDril := DimensionLevels(l_count);
4267         If IndexRelation1N(l_level_table, tDril.dimTable) >= 0 Then
4268           --There is 1n relationship with this drill
4269           l_parents1n  := tDril.keyName;
4270           IF (cLevel.Parents1N IS NOT NULL ) THEN
4271             cLevel.Parents1N := cLevel.Parents1N||',';
4272           END IF;
4273           cLevel.Parents1N := cLevel.Parents1N||l_parents1n;
4274           --The 1n relations of the parent drill are also (by transitivity)
4275           --1n with the current drill
4276           tDril_parents1N := bsc_mo_helper_pkg.getDecomposedString(tDril.Parents1N, ',');
4277           IF (tDril_parents1N.count>0)THEN
4278             l_ct := tDril_parents1N.first;
4279             LOOP
4280               tPadre1n := tDril_parents1N(l_ct);
4281               IF (cLevel.Parents1N IS NOT NULL) THEN
4282                 cLevel.Parents1N := cLevel.Parents1N ||',';
4283               END IF;
4284               cLevel.Parents1N := cLevel.Parents1N||tPadre1n;
4285               EXIT WHEN l_ct = tDril_Parents1N.last;
4286               l_ct := tDril_Parents1N.next(l_ct);
4287             END LOOP;
4288           END IF;
4289           --The mn relations of the parent drill are also (by transitivity)
4290           --mn with the current drill
4291           cDril_parentsMN := bsc_mo_helper_pkg.getDecomposedString(cLevel.ParentsMN, ',');
4292           tDril_parentsMN := bsc_mo_helper_pkg.getDecomposedString(tDril.ParentsMN, ',');
4293           IF tDril_parentsMN.count > 0 THEN
4294             l_ct := tDril_parentsMN.first;
4295             LOOP
4296               tPadremn := tDril_parentsMN(l_ct);
4297               IF (cLevel.ParentsMN IS NOT NULL) THEN
4298                 cLevel.ParentsMN := cLevel.ParentsMN ||',';
4299               END IF;
4300               cLevel.ParentsMN := cLevel.ParentsMN ||tPadremn;
4301               EXIT WHEN l_Ct = tDril_ParentsMN.last;
4302               l_ct := tDril_ParentsMN.next(l_ct);
4303             END LOOP;
4304           END IF;
4305         END IF;--IndexRelation1N(l_level_table, tDril.dimTable) >= 0
4306         If IndexRelationMN(l_level_table, tDril.dimTable) >= 0 Then
4307           --There is mn relation with this drill
4308           l_parentsMN := tDril.keyName;
4309           IF (cLevel.ParentsMN IS NOT NULL) THEN
4310             cLevel.ParentsMN := cLevel.ParentsMN||',';
4311           END IF;
4312           cLevel.ParentsMN := cLevel.ParentsMN|| l_parentsMN;
4313           --The 1n relations of the parent drill are also (by transitivity)
4314           --mn with the current drill
4315           tDril_parents1n := bsc_mo_helper_pkg.getDecomposedString(tDril.Parents1N, ',');
4316           IF (tDril_parents1N.count >0) THEN
4317             l_ct := tDril_parents1N.first;
4318             LOOP
4319               tPadre1n := tDril_parents1N(l_ct)  ;
4320               IF (cLevel.ParentsMN IS NOT NULL )THEN
4321                 cLevel.ParentsMN := cLevel.ParentsMN||',';
4322               END IF;
4323               cLevel.ParentsMN := cLevel.ParentsMN||tPadre1n;
4324               EXIT WHEN l_ct = tDril_Parents1N.last;
4325               l_ct := tDril_Parents1N.next(l_ct);
4326             END LOOP;
4327           END IF;
4328           --The mn relations of the parent drill are also (by transitivity)
4329           --mn with the current drill
4330           tDril_parentsMN := bsc_mo_helper_pkg.getDecomposedString(tDril.ParentsMN, ',');
4331           IF (tDril_parentsMN.count >0) THEN
4332             l_ct := tDril_parentsMN.first;
4333             LOOP
4334               tPadremn := tDril_parentsMN(l_ct) ;
4335               IF (cLevel.ParentsMN IS NOT NULL) THEN
4336                 cLevel.parentsMN := cLevel.parentsMN||',';
4337               END IF;
4338               cLevel.ParentsMN := cLevel.ParentsMN || tPadremn;
4339               EXIT WHEN l_ct = tDril_ParentsMN.last;
4340               l_ct := tDril_ParentsMN.next(l_ct);
4341             END LOOP;
4342           END IF;
4343         END IF;--IndexRelationMN(l_level_table, tDril.Maestra) >= 0
4344         EXIT WHEN l_count =  DimensionLevels.last;
4345         l_count := DimensionLevels.next(l_count);
4346       END LOOP;
4347       --Review target levels
4348       IF cLevel.TargetLevel = 1 Then
4349         --If target apply to this level, then
4350         --it must apply for drils at the left (Parents)
4351         l_ct := DimensionLevels.count;
4352         IF l_ct > 0 THEN
4353           l_ct := DimensionLevels.first;
4354           LOOP
4355             tDril := DimensionLevels(l_ct);
4356             tDril.TargetLevel := 1;
4357             EXIT WHEN l_ct = DimensionLevels.last;
4358             l_ct := DimensionLevels.next(l_ct);
4359           END LOOP;
4360         END IF;
4361       END IF;
4362       DimensionLevels.delete;
4363       DimensionLevels(0) := cLevel;
4364       bsc_mo_helper_pkg.add_tabrec_clsLevels(l_dimension_families, DimensionLevels, DimensionLevelsNum);
4365     Else
4366       --The drill does not belong to any family previously created.
4367       --So, create a new family of drill with this drill
4368       --Review target level
4369       --This is the first drill in this family, then target must apply
4370       cLevel.TargetLevel := 1;
4371       DimensionLevels.delete;
4372       DimensionLevels(0) := cLevel;
4373       bsc_mo_helper_pkg.add_tabrec_clsLevels(l_dimension_families,  DimensionLevels, l_group_id);
4374       l_group_id := l_group_id +1;
4375     END IF;--If DimensionLevelsNum <> 0
4376   END Loop;
4377   close cv;
4378   IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4379     bsc_mo_helper_pkg.writeTmp( 'Compl GetLevelCollection');
4380     bsc_mo_helper_pkg.write_this(l_dimension_families);
4381   END IF;
4382   return l_dimension_families;
4383   EXCEPTION WHEN OTHERS THEN
4384     l_stmt := sqlerrm;
4385     bsc_mo_helper_pkg.TerminateWithMsg( ' Exception in GetLevelCollection : '||l_stmt);
4386     fnd_message.set_name('BSC', 'BSC_RETR_DIM_KPI_FAILED');
4387   fnd_message.set_token('INDICATOR', Indic);
4388     fnd_message.set_token('DIMENSION_SET', Configuration);
4389     g_error := fnd_message.get;
4390     bsc_mo_helper_pkg.terminatewithMsg(g_error);
4391     raise;
4392   --app_exception.raise_exception;
4393 
4394 
4395 End;
4396 --****************************************************************************
4397 --FlagTLOtherPeriodicities
4398 --  DESCRIPTION:
4399 --     Flag the TargetLevel of all periodicities in the collection
4400 --     that can be generated from the ones selected by the user
4401 --  PARAMETERS:
4402 --     colPeriodicities: collection of clsIndicPeriodicity
4403 --
4404 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4405 --***************************************************************************
4406 PROCEDURE FlagTLOtherPeriodicities(colPeriodicities IN OUT NOCOPY BSC_METADATA_OPTIMIZER_PKG.tab_clsIndicPeriodicity)
4407 IS
4408   atLeastOneChange Boolean;
4409    indicPer BSC_METADATA_OPTIMIZER_PKG.clsIndicPeriodicity;
4410   l_count NUMBER;
4411 
4412 BEGIN
4413 
4414 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4415       bsc_mo_helper_pkg.writeTmp( 'Inside FlagTLOtherPeriodicities, colPeriodicities = ');
4416       bsc_mo_helper_pkg.write_this(colPeriodicities);
4417 	END IF;
4418 
4419   atLeastOneChange := True;
4420 
4421   While atLeastOneChange LOOP
4422 	  atLeastOneChange := False;
4423 	  l_count := colPeriodicities.first;
4424       --For Each indicPer In colPeriodicities
4425 	  LOOP
4426        IF (colPeriodicities.count=0) THEN EXIT; END IF;
4427 	     indicPer := colPeriodicities(l_count);
4428        If indicPer.TargetLevel = 0 Then
4429           --This periodicity has not been selected
4430           If GetPeriodicityOrigin(colPeriodicities, indicPer.Code, True) <> -1 Then
4431               indicPer.TargetLevel := 1;
4432               atLeastOneChange := True;
4433               bsc_mo_helper_pkg.writeTmp('atLeastOneChange is true');
4434               colPeriodicities(l_count) := indicPer;
4435           END IF;
4436        END IF;
4437 	     EXIT WHEN l_count = colPeriodicities.last;
4438  	     l_count := colPeriodicities.next(l_count);
4439       END LOOP;
4440 
4441   END LOOP;
4442 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4443     bsc_mo_helper_pkg.writeTmp( 'Compl FlagTLOtherPeriodicities');
4444 	END IF;
4445 
4446 
4447   EXCEPTION WHEN OTHERS THEN
4448   G_ERROR := sqlerrm;
4449   bsc_mo_helper_pkg.TerminateWithMsg( 'Exception in FlagTLOtherPeriodicities '||G_ERROR);
4450 	RAISE;
4451 
4452 End;
4453 
4454 
4455 --****************************************************************************
4456 --GetPeriodicities: GetColPeriodicidadesIndic
4457 --  DESCRIPTION:
4458 --   Get the collection of periodicity codes of the indicator
4459 --  PARAMETERS:
4460 --   Indic: indicator code
4461 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4462 --***************************************************************************
4463 
4464 Function GetPeriodicities(Indic IN NUMBER) RETURN BSC_METADATA_OPTIMIZER_PKG.tab_clsIndicPeriodicity IS
4465 
4466   colPeriodicities BSC_METADATA_OPTIMIZER_PKG.tab_clsIndicPeriodicity;
4467   CURSOR cPeriodicities IS
4468   SELECT PERIODICITY_ID, NVL(TARGET_LEVEL, 1) AS TAR_LEVEL
4469   FROM BSC_KPI_PERIODICITIES
4470   WHERE INDICATOR = Indic ORDER BY PERIODICITY_ID;
4471   l_per NUMBER;
4472   l_tar NUMBER;
4473   cv CurTyp;
4474   l_periodicity BSC_METADATA_OPTIMIZER_PKG.clsIndicPeriodicity := null;
4475 BEGIN
4476 
4477   OPEN cPeriodicities;
4478   LOOP
4479 	   FETCH cPeriodicities INTO l_per, l_tar;
4480 	   EXIT WHEN cPeriodicities%NOTFOUND;
4481      l_periodicity.code := l_per;
4482 	   l_periodicity.TargetLevel := l_tar;
4483      IF (colPeriodicities.count>0) THEN
4484         colPeriodicities(colPeriodicities.last+1) := l_periodicity;
4485      ELSE
4486         colPeriodicities(0) := l_periodicity;
4487      END IF;
4488   END LOOP;
4489   close cPeriodicities;
4490   return colPeriodicities;
4491 
4492 
4493   EXCEPTION WHEN OTHERS THEN
4494   BSC_MO_HELPER_PKG.TerminateWithError('BSC_RETR_KPI_PERIOD_FAILED');
4495   fnd_message.set_name('BSC', 'BSC_RETR_KPI_PERIOD_FAILED');
4496 	fnd_message.set_token('INDICATOR', Indic);
4497   app_exception.raise_exception;
4498 
4499 End;
4500 
4501 
4502 --****************************************************************************
4503 -- ConfigureIndics : TablasIndicatorConfiguration
4504 --  DESCRIPTION:
4505 --   Deduce each one of the tables needed by the kpi in the given
4506 --   configuration.
4507 --   For this tables are added to the collection gTablas.
4508 --   Also configure metadata in order to the indicator reads from them.
4509 --  PARAMETERS:
4510 --   Indicator: indicator
4511 --   Configuration: configuration
4512 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4513 --***************************************************************************
4514 --****************************************************************************
4515 -- ConfigureIndics : TablasIndicatorConfiguration
4516 --  DESCRIPTION:
4517 --   Deduce each one of the tables needed by the kpi in the given
4518 --   configuration.
4519 --   For this tables are added to the collection gTablas.
4520 --   Also configure metadata in order to the indicator reads from them.
4521 --  PARAMETERS:
4522 --   Indicator: indicator
4523 --   Configuration: configuration
4524 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4525 --***************************************************************************
4526 PROCEDURE ConfigureIndics(Indicator IN BSC_METADATA_OPTIMIZER_PKG.clsIndicator, Configuration IN NUMBER) IS
4527   colPeriodicities 	BSC_METADATA_OPTIMIZER_PKG.tab_clsIndicPeriodicity;
4528   colDrills		BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevels;
4529   colDrillCombination BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevelCombinations;
4530   colDrillCombinationTL BSC_METADATA_OPTIMIZER_PKG.tab_tab_clsLevelCombinations;
4531   colBasicTables 	BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable;
4532   colBasicTablesTL 	BSC_METADATA_OPTIMIZER_PKG.tab_clsBasicTable;
4533   colDataColumns	BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
4534   i  NUMBER;
4535   iNext NUMBER;
4536   bLast boolean;
4537 BEGIN
4538   bsc_mo_helper_pkg.writeTmp('  ', fnd_log.level_statement, false);
4539   bsc_mo_helper_pkg.writeTmp( 'Inside ConfigureIndics for '||Indicator.code||', dimension set = '||Configuration||', System time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, true);
4540   g_current_dimset := Configuration;
4541   g_current_indicator := Indicator;
4542   If Indicator.Share_Flag = 0 Or Indicator.Share_Flag = 1 Or
4543      (
4544 	   Indicator.Share_Flag = 2 AND
4545 	   (IsFilteredIndicator(Indicator.Code, Configuration) OR
4546 	    IsFilteredIndicator(Indicator.source_indicator, Configuration)
4547        )
4548      ) Then
4549     --If the indicator is normal or master or shared with filters then for this configuration
4550     --we make the system tables
4551     --Get the list of periodicities for the indicator
4552     colPeriodicities := GetPeriodicities(Indicator.Code);
4553     If Indicator.OptimizationMode = 2 Then
4554       --The indicator needs targets at different levels
4555       --We need to flag all periodicities that can be generated from
4556       --the ones selected by the user
4557       FlagTLOtherPeriodicities (colPeriodicities);
4558     END IF;
4559     --Get the list of drill families of the indicator in the given configuration
4560     colDrills := GetLevelCollection(Indicator.Code, Configuration);
4561 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4562       bsc_mo_helper_pkg.writeTmp('  ');
4563       bsc_mo_helper_pkg.writeTmp('Level Collection is');
4564       bsc_mo_helper_pkg.write_this(colDrills);
4565 	END IF;
4566     --Get the list of combinations of levels of each familiy
4567 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4568       bsc_mo_helper_pkg.writeTmp('Get the list of level combinations ');
4569 	END IF;
4570     colDrillCombination := GetLevelCombinations(colDrills, False);
4571 	IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4572       bsc_mo_helper_pkg.write_this(colDrillCombination);
4573       bsc_mo_helper_pkg.writetmp('  ');
4574     END IF;
4575     If Indicator.OptimizationMode = 2 Then
4576       --The indicator needs targets at different levels
4577       colDrillCombinationTL := GetLevelCombinations(colDrills, True);
4578       bsc_mo_helper_pkg.write_this(colDrillCombinationTL);
4579     END IF;
4580     --Get the list of data columns of the indicator in the given configuration
4581     colDataColumns := GetDataFields(Indicator.Code, Configuration, True);
4582     bsc_mo_helper_pkg.write_this(colDataColumns);
4583     --Generate the list of base tables for the indicator
4584     colBasicTables := GetBasicTables(Indicator, Configuration, colDrillCombination, colDrills, False, colDataColumns);
4585     If Indicator.OptimizationMode = 2 Then
4586       --The indicator needs targets at different levels
4587       colBasicTablesTL := GetBasicTables(Indicator, Configuration, colDrillCombinationTL, colDrills, True, colDataColumns);
4588     END IF;
4589     --Deduce the internal table tree for the indicator
4590     --BSC-MV Note: Added forTargetLevel parameter to DeducirGrafoInterno()
4591     If Indicator.OptimizationMode <> 0 Then
4592       --If the indicator is no-precalculated then we calculate the internal table tree
4593       deduceInternalGraph (colBasicTables, colDrills, False);
4594       If Indicator.OptimizationMode = 2 Then
4595         deduceInternalGraph(colBasicTablesTL, colDrills, True);
4596       END IF;
4597     END IF;
4598     --Deduce each one of the tables needed by the kpi in the given configuration.
4599     --For this tables are added to the collection gTablas.
4600     --Also configure metadata in order to the indicator reads from them.
4601     deduce_and_configure_s_tables(Indicator, Configuration, colBasicTables, colPeriodicities, colDrills, False);
4602     If Indicator.OptimizationMode = 2 Then
4603       deduce_and_configure_s_tables(Indicator, Configuration, colBasicTablesTL, colPeriodicities, colDrills, True);
4604       ConnectTargetTables(Indicator, Configuration);
4605     END IF;
4606     --BSC-MV Note: If the indicator is processed only for Summarization Level Change
4607     --(example for 2 to 3 or 3 to 2), I do not need the tables in gTablas.
4608     --I just wanted to re-configure BSC_KPI_DATA_TABLES and not re-configure loader.
4609     --Remove indicator tables from gTablas
4610     bLast := false;
4611     If (Indicator.Action_Flag = 0 Or Indicator.Action_Flag = 4) And bsc_metadata_optimizer_pkg.g_Sum_Level_Change = 2 Then
4612       i := bsc_metadata_optimizer_pkg.gTables.first;
4613       LOOP
4614         EXIT WHEN bsc_metadata_optimizer_pkg.gTables.count = 0;
4615         IF (i = bsc_metadata_optimizer_pkg.gTables.last) THEN
4616           bLast := true;
4617         END IF;
4618         If (bsc_metadata_optimizer_pkg.gTables(i).Indicator = Indicator.Code) And
4619                 (bsc_metadata_optimizer_pkg.gTables(i).Configuration = Configuration) Then
4620           IF (NOT bLast) THEN
4621             iNext := bsc_metadata_optimizer_pkg.gTables.next(i);
4622           END IF;
4623           IF BSC_METADATA_OPTIMIZER_PKG.g_log THEN
4624             BSC_MO_HELPER_PKG.writeTmp('2 Going to delete '||BSC_METADATA_OPTIMIZER_PKG.gTables(i).name);
4625           END IF;
4626           bsc_metadata_optimizer_pkg.gTables.delete(i);
4627           i := iNext;
4628         ELSE
4629           i := bsc_metadata_optimizer_pkg.gTables.next(i);
4630         END IF;
4631         EXIT WHEN bLast = true;
4632       END Loop;
4633     End If;
4634   END IF;
4635   bsc_mo_helper_pkg.writeTmp( 'Compl ConfigureIndics, system time is '||bsc_mo_helper_pkg.get_time, fnd_log.level_statement, true);
4636   EXCEPTION WHEN OTHERS THEN
4637     bsc_mo_helper_pkg.writeTmp( 'Exception in ConfigureIndics : '||sqlerrm, fnd_log.level_exception, true);
4638     fnd_message.set_name('BSC', 'BSC_KPI_TBLS_SET_DEDUCT_FAILED');
4639 	fnd_message.set_token('INDICATOR', Indicator.code);
4640     fnd_message.set_token('DIMENSION_SET', Configuration);
4641     g_error := fnd_message.get ;
4642     bsc_mo_helper_pkg.terminatewithMsg(g_error);
4643     raise;
4644 End;
4645 
4646 
4647 --****************************************************************************
4648 --  GetColConfigurationsforIndic
4649 --    DESCRIPTION:
4650 --       Get the collection with the configurations of the indicator
4651 --    PARAMETERS:
4652 --       Indic: indicator code
4653 --    AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4654 --***************************************************************************
4655 Function GetColConfigForIndic(Indic IN NUMBER) return DBMS_SQL.NUMBER_TABLE IS
4656   colConfigurations dbms_sql.number_table;
4657   colMeasures BSC_METADATA_OPTIMIZER_PKG.tab_clsDataField;
4658   Configuration NUMBER;
4659   DimSet NUMBER;
4660   CURSOR cConfigs IS
4661   SELECT DISTINCT DIM_SET_ID FROM BSC_DB_DATASET_DIM_SETS_V
4662   WHERE INDICATOR = Indic  ORDER BY DIM_SET_ID;
4663 BEGIN
4664   OPEN cConfigs;
4665   LOOP
4666     FETCH cConfigs INTO DimSet;
4667     EXIT WHEN cConfigs%NOTFOUND;
4668     --BSC-PMF Integration: Only get BSC dimension sets
4669     --We need to validate that there is at least one BSC data column
4670     --associated to this dimension set.
4671     If GetNumDataColumns(Indic, DimSet) > 0 Then
4672       Configuration := DimSet;
4673       colConfigurations(colConfigurations.count) := configuration;
4674     END IF;
4675   END Loop;
4676   CLOSE cConfigs;
4677   return colConfigurations;
4678   EXCEPTION WHEN OTHERS THEN
4679     g_error := sqlerrm;
4680     bsc_mo_helper_pkg.TerminateWithMsg(' Exception in GetColConfigForIndic : '||g_error);
4681     fnd_message.set_name('BSC', 'BSC_RETR_DIMSET_KPI_FAILED');
4682 	fnd_message.set_token('INDICATOR', Indic);
4683     app_exception.raise_exception;
4684 End;
4685 --***************************************************************************
4686 --TablasIndicatores
4687 --
4688 --  DESCRIPTION:
4689 --     Deduce set of tables used directly by each indicator.
4690 --
4691 --  AUTHOR/DATE  -  MODIFICATIONS (AUTHOR/DATE/DESCRIPTION):
4692 --***************************************************************************
4693 PROCEDURE IndicatorTables IS
4694     Indicator BSC_METADATA_OPTIMIZER_PKG.clsIndicator;
4695     colConfigurations dbms_sql.number_table;
4696     l_Configuration Number;
4697     l_stmt VARCHAR2(1000);
4698     l_count number := 0;
4699     l_configs Number := 0;
4700     l_list dbms_sql.number_table;
4701 BEGIN
4702   bsc_mo_helper_pkg.writeTmp( 'Inside IndicatorTables, # = '||BSC_METADATA_OPTIMIZER_PKG.gIndicators.count, fnd_log.level_statement, true);
4703   IF BSC_METADATA_OPTIMIZER_PKG.gIndicators.count >0 THEN
4704     l_count := BSC_METADATA_OPTIMIZER_PKG.gIndicators.first;
4705   END IF;
4706 
4707   --Perf. fix, instead of getting # of data columns for each indicator, get it in one shot
4708   FOR i IN BSC_METADATA_OPTIMIZER_PKG.gIndicators.first..BSC_METADATA_OPTIMIZER_PKG.gIndicators.last LOOP
4709     --Consider only new indicators or changed indicators
4710     IF BSC_METADATA_OPTIMIZER_PKG.gIndicators(i).Action_Flag = 3
4711        Or
4712        (Indicator.Action_Flag <> 2 And BSC_METADATA_OPTIMIZER_PKG.g_Sum_Level_Change <> 0) THEN
4713       l_list(l_list.count+1) := BSC_METADATA_OPTIMIZER_PKG.gIndicators(i).code;
4714     END IF;
4715   END LOOP;
4716   init_measure_counts(l_list);
4717   LOOP
4718     EXIT WHEN BSC_METADATA_OPTIMIZER_PKG.gIndicators.count = 0;
4719     Indicator := BSC_METADATA_OPTIMIZER_PKG.gIndicators(l_count);
4720     bsc_mo_helper_pkg.writeTmp('Processing indic ');
4721     bsc_mo_helper_pkg.write_this(Indicator);
4722     --Consider only new indicators or changed indicators
4723     -- Note: ANy logic change shd be propagated to the init above
4724     IF Indicator.Action_Flag = 3
4725        Or
4726        (Indicator.Action_Flag <> 2 And BSC_METADATA_OPTIMIZER_PKG.g_Sum_Level_Change <> 0) THEN
4727       --Get the list of configurations of the kpi
4728       colConfigurations := GetColConfigForIndic(Indicator.Code);
4729       l_configs := colConfigurations.first;
4730       bsc_mo_helper_pkg.writeTmp('colConfigurations.count = '||colConfigurations.count);
4731       LOOP
4732         EXIT WHEN colConfigurations.count = 0;
4733         l_configuration := colConfigurations(l_configs);
4734         bsc_mo_helper_pkg.writeTmp('Processing Indicator='||Indicator.Code||', dim set='||l_configuration||':'||bsc_mo_helper_pkg.get_time, FND_LOG.LEVEL_STATEMENT, true);
4735         ConfigureIndics(Indicator, l_configuration);
4736         EXIT WHEN l_configs = colConfigurations.last;
4737         l_configs := colConfigurations.next(l_configs);
4738       END LOOP;
4739       --BSC-MV Note: Save the summarization level in BSC_KPI_PROPERTIES
4740       If BSC_METADATA_OPTIMIZER_PKG.g_BSC_MV Then
4741         bsc_mo_helper_pkg.WriteInfoMatrix(Indicator.Code, 'ADV_SUM_LEVEL',
4742                         to_number(BSC_METADATA_OPTIMIZER_PKG.g_Adv_Summarization_Level));
4743       End If;
4744     END IF;
4745 	EXIT when l_count = BSC_METADATA_OPTIMIZER_PKG.gIndicators.last;
4746     l_count := BSC_METADATA_OPTIMIZER_PKG.gIndicators.next(l_count) ;
4747   END LOOP;
4748   --Configure shared indicators without filters same tables as master indicator
4749   ConfigureMasterSharedIndics;
4750   bsc_mo_helper_pkg.writeTmp( 'Compl IndicatorTables', fnd_log.level_statement, true);
4751   exception when others then
4752     g_error := sqlerrm;
4753     BSC_MO_HELPER_PKG.TerminateWithMsg('IndicatorTables failed with : '||g_error);
4754     raise;
4755     --app_exception.raise_exception;
4756 End;
4757 END BSC_MO_INDICATOR_PKG;